Newer
Older
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
MODULE icbstp
!!======================================================================
!! *** MODULE icbstp ***
!! Icebergs: initialise variables for iceberg tracking
!!======================================================================
!! History : 3.3.1 ! 2010-01 (Martin&Adcroft) Original code
!! - ! 2011-03 (Madec) Part conversion to NEMO form
!! - ! Removal of mapping from another grid
!! - ! 2011-04 (Alderson) Split into separate modules
!! - ! Move budgets to icbdia routine
!! - ! 2011-05 (Alderson) Add call to copy forcing arrays
!! - ! into icb copies with haloes
!!----------------------------------------------------------------------
!!----------------------------------------------------------------------
!! icb_stp : start iceberg tracking
!! icb_end : end iceberg tracking
!!----------------------------------------------------------------------
USE par_oce ! nemo parameters
USE dom_oce ! ocean domain
USE sbc_oce ! ocean surface forcing
USE phycst ! physical constants
!
USE icb_oce ! iceberg: define arrays
USE icbini ! iceberg: initialisation routines
USE icbutl ! iceberg: utility routines
USE icbrst ! iceberg: restart routines
USE icbdyn ! iceberg: dynamics (ie advection) routines
USE icbclv ! iceberg: calving routines
USE icbthm ! iceberg: thermodynamics routines
USE icblbc ! iceberg: lateral boundary routines (including mpp)
USE icbtrj ! iceberg: trajectory I/O routines
USE icbdia ! iceberg: budget
!
USE in_out_manager ! nemo IO
USE lib_mpp ! massively parallel library
USE iom ! I/O manager
USE fldread ! field read
USE timing ! timing
IMPLICIT NONE
PRIVATE
PUBLIC icb_stp ! routine called in sbcmod.F90 module
PUBLIC icb_end ! routine called in nemogcm.F90 module
!!----------------------------------------------------------------------
!! NEMO/OCE 4.0 , NEMO Consortium (2018)
!! $Id: icbstp.F90 14239 2020-12-23 08:57:16Z smasson $
!! Software governed by the CeCILL license (see ./LICENSE)
!!----------------------------------------------------------------------
CONTAINS
SUBROUTINE icb_stp( kt, Kmm )
!!----------------------------------------------------------------------
!! *** ROUTINE icb_stp ***
!!
!! ** Purpose : iceberg time stepping.
!!
!! ** Method : - top level routine to do things in the correct order
!!----------------------------------------------------------------------
INTEGER, INTENT(in) :: kt ! time step index
INTEGER, INTENT(in) :: Kmm ! ocean time level index
!
LOGICAL :: ll_sample_traj, ll_budget, ll_verbose ! local logical
!!----------------------------------------------------------------------
!
IF( ln_timing ) CALL timing_start('icb_stp')
! !== start of timestep housekeeping ==!

Guillaume Samson
committed
IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN

Guillaume Samson
committed
nktberg = kt

Guillaume Samson
committed
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
IF( nn_test_icebergs < 0 .OR. ln_use_calving ) THEN !* read calving data
!
CALL fld_read ( kt, 1, sf_icb )
src_calving (:,:) = sf_icb(1)%fnow(:,:,1) ! calving in km^3/year (water equivalent)
src_calving_hflx(:,:) = 0._wp ! NO heat flux for now
!
ENDIF
!
berg_grid%floating_melt(:,:) = 0._wp
!
! !* anything that needs to be reset to zero each timestep
CALL icb_dia_step() ! for budgets is dealt with here
!
! !* write out time
ll_verbose = .FALSE.
IF( nn_verbose_write > 0 .AND. MOD( kt-1 , nn_verbose_write ) == 0 ) ll_verbose = ( nn_verbose_level > 0 )
!
IF( ll_verbose ) WRITE(numicb,9100) nktberg, ndastp, nsec_day
9100 FORMAT('kt= ',i8, ' day= ',i8,' secs=',i8)
!
! !* copy nemo forcing arrays into iceberg versions with extra halo
CALL icb_utl_copy( Kmm ) ! only necessary for variables not on T points
!
!
! !== process icebergs ==!
! !
CALL icb_clv_flx( kt ) ! Accumulate ice from calving
! !
CALL icb_clv( kt ) ! Calve excess stored ice into icebergs
! !
!
! !== For each berg, evolve ==!
!
IF( ASSOCIATED(first_berg) ) CALL icb_dyn( kt ) ! ice berg dynamics
IF( lk_mpp ) THEN ; CALL icb_lbc_mpp() ! Send bergs to other PEs
ELSE ; CALL icb_lbc() ! Deal with any cyclic boundaries in non-mpp case
ENDIF
IF( ASSOCIATED(first_berg) ) CALL icb_thm( kt ) ! Ice berg thermodynamics (melting) + rolling
!
!
! !== diagnostics and output ==!
!
! !* For each berg, record trajectory (when needed)
ll_sample_traj = .FALSE.
IF( nn_sample_rate > 0 .AND. MOD(kt-1,nn_sample_rate) == 0 ) ll_sample_traj = .TRUE.
IF( ll_sample_traj .AND. ASSOCIATED(first_berg) ) CALL icb_trj_write( kt )
! !* Gridded diagnostics
! ! To get these iom_put's and those preceding to actually do something
! ! use key_xios in cpp file and create content for XML file
!
CALL iom_put( "calving" , berg_grid%calving (:,:) ) ! 'calving mass input'
CALL iom_put( "berg_floating_melt", berg_grid%floating_melt(:,:) ) ! 'Melt rate of icebergs + bits' , 'kg/m2/s'
CALL iom_put( "berg_stored_ice" , berg_grid%stored_ice (:,:,:) ) ! 'Accumulated ice mass by class', 'kg'
!
CALL icb_dia_put() !* store mean budgets
!
! !* Dump icebergs to screen
IF( nn_verbose_level >= 2 ) CALL icb_utl_print( 'icb_stp, status', kt )
!
! !* Diagnose budgets
ll_budget = .FALSE.
IF( nn_verbose_write > 0 .AND. MOD(kt-1,nn_verbose_write) == 0 ) ll_budget = ln_bergdia
CALL icb_dia( ll_budget )
!
END IF
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
!
IF( lrst_oce ) THEN !* restart
CALL icb_rst_write( kt )
IF( nn_sample_rate > 0 ) CALL icb_trj_sync()
ENDIF
!
IF( ln_timing ) CALL timing_stop('icb_stp')
!
END SUBROUTINE icb_stp
SUBROUTINE icb_end( kt )
!!----------------------------------------------------------------------
!! *** ROUTINE icb_end ***
!!
!! ** Purpose : close iceberg files
!!
!!----------------------------------------------------------------------
INTEGER, INTENT( in ) :: kt ! model time-step index
!!----------------------------------------------------------------------
!
! finish with trajectories if they were written
IF( nn_sample_rate > 0 ) CALL icb_trj_end()
IF(lwp) WRITE(numout,'(a,i6)') 'icebergs: icb_end complete', narea
!
IF( nn_verbose_level > 0 ) THEN
CALL flush( numicb )
CLOSE( numicb )
ENDIF
!
END SUBROUTINE icb_end
!!======================================================================
END MODULE icbstp