1 | MODULE isfstp |
---|
2 | !!====================================================================== |
---|
3 | !! *** MODULE isfstp *** |
---|
4 | !! Ice Shelves : compute iceshelf load, melt and heat flux |
---|
5 | !!====================================================================== |
---|
6 | !! History : 3.2 ! 2011-02 (C.Harris ) Original code isf cav |
---|
7 | !! X.X ! 2006-02 (C. Wang ) Original code bg03 |
---|
8 | !! 3.4 ! 2013-03 (P. Mathiot) Merging + parametrization |
---|
9 | !! 4.1 ! 2019-09 (P. Mathiot) Split param/explicit ice shelf and re-organisation |
---|
10 | !!---------------------------------------------------------------------- |
---|
11 | |
---|
12 | !!---------------------------------------------------------------------- |
---|
13 | !! isfstp : compute iceshelf melt and heat flux |
---|
14 | !!---------------------------------------------------------------------- |
---|
15 | USE isf_oce ! isf variables |
---|
16 | USE isfload, ONLY: isf_load ! ice shelf load |
---|
17 | USE isftbl , ONLY: isf_tbl_lvl ! ice shelf boundary layer |
---|
18 | USE isfpar , ONLY: isf_par, isf_par_init ! ice shelf parametrisation |
---|
19 | USE isfcav , ONLY: isf_cav, isf_cav_init ! ice shelf cavity |
---|
20 | USE isfcpl , ONLY: isfcpl_rst_write, isfcpl_init ! isf variables |
---|
21 | |
---|
22 | USE dom_oce ! ocean space and time domain |
---|
23 | USE oce , ONLY: ssh ! sea surface height |
---|
24 | USE domvvl, ONLY: ln_vvl_zstar ! zstar logical |
---|
25 | ! tipaccs 2d top tidal velocity |
---|
26 | USE zdfdrg, ONLY: r_Cdmin_top, rke0_top, ln_2d_ttv ! vertical physics: top/bottom drag coef. |
---|
27 | ! end tipaccs 2d top tidal velocity |
---|
28 | ! |
---|
29 | USE lib_mpp, ONLY: ctl_stop, ctl_nam |
---|
30 | USE fldread, ONLY: FLD, FLD_N |
---|
31 | USE in_out_manager ! I/O manager |
---|
32 | USE timing |
---|
33 | |
---|
34 | IMPLICIT NONE |
---|
35 | PRIVATE |
---|
36 | |
---|
37 | PUBLIC isf_stp, isf_init, isf_nam ! routine called in sbcmod and divhor |
---|
38 | |
---|
39 | !! * Substitutions |
---|
40 | # include "domzgr_substitute.h90" |
---|
41 | !!---------------------------------------------------------------------- |
---|
42 | !! NEMO/OCE 4.0 , NEMO Consortium (2018) |
---|
43 | !! $Id$ |
---|
44 | !! Software governed by the CeCILL license (see ./LICENSE) |
---|
45 | !!---------------------------------------------------------------------- |
---|
46 | CONTAINS |
---|
47 | |
---|
48 | SUBROUTINE isf_stp( kt, Kmm ) |
---|
49 | !!--------------------------------------------------------------------- |
---|
50 | !! *** ROUTINE isf_stp *** |
---|
51 | !! |
---|
52 | !! ** Purpose : compute total heat flux and total fwf due to ice shelf melt |
---|
53 | !! |
---|
54 | !! ** Method : For each case (parametrisation or explicity cavity) : |
---|
55 | !! - define the before fields |
---|
56 | !! - compute top boundary layer properties |
---|
57 | !! (in case of parametrisation, this is the |
---|
58 | !! depth range model array used to compute mean far fields properties) |
---|
59 | !! - compute fluxes |
---|
60 | !! - write restart variables |
---|
61 | !!---------------------------------------------------------------------- |
---|
62 | INTEGER, INTENT(in) :: kt ! ocean time step |
---|
63 | INTEGER, INTENT(in) :: Kmm ! ocean time level index |
---|
64 | ! |
---|
65 | INTEGER :: jk ! loop index |
---|
66 | #if defined key_qco |
---|
67 | REAL(wp), DIMENSION(jpi,jpj,jpk) :: ze3t ! 3D workspace |
---|
68 | #endif |
---|
69 | !!--------------------------------------------------------------------- |
---|
70 | ! |
---|
71 | IF( ln_timing ) CALL timing_start('isf') |
---|
72 | ! |
---|
73 | !======================================================================= |
---|
74 | ! 1.: compute melt and associated heat fluxes in the ice shelf cavities |
---|
75 | !======================================================================= |
---|
76 | ! |
---|
77 | IF ( ln_isfcav_mlt ) THEN |
---|
78 | ! |
---|
79 | ! 1.1: before time step |
---|
80 | IF ( kt /= nit000 ) THEN |
---|
81 | risf_cav_tsc_b (:,:,:) = risf_cav_tsc (:,:,:) |
---|
82 | fwfisf_cav_b(:,:) = fwfisf_cav(:,:) |
---|
83 | END IF |
---|
84 | ! |
---|
85 | ! 1.2: compute misfkb, rhisf_tbl, rfrac (deepest level, thickness, fraction of deepest cell affected by tbl) |
---|
86 | rhisf_tbl_cav(:,:) = rn_htbl * mskisf_cav(:,:) |
---|
87 | #if defined key_qco |
---|
88 | DO jk = 1, jpk |
---|
89 | ze3t(:,:,jk) = e3t(:,:,jk,Kmm) |
---|
90 | END DO |
---|
91 | CALL isf_tbl_lvl( ht(:,:), ze3t , misfkt_cav, misfkb_cav, rhisf_tbl_cav, rfrac_tbl_cav ) |
---|
92 | #else |
---|
93 | CALL isf_tbl_lvl( ht(:,:), e3t(:,:,:,Kmm), misfkt_cav, misfkb_cav, rhisf_tbl_cav, rfrac_tbl_cav ) |
---|
94 | #endif |
---|
95 | ! |
---|
96 | ! 1.3: compute ice shelf melt |
---|
97 | CALL isf_cav( kt, Kmm, risf_cav_tsc, fwfisf_cav ) |
---|
98 | ! |
---|
99 | END IF |
---|
100 | ! |
---|
101 | !================================================================================= |
---|
102 | ! 2.: compute melt and associated heat fluxes for not resolved ice shelf cavities |
---|
103 | !================================================================================= |
---|
104 | ! |
---|
105 | IF ( ln_isfpar_mlt ) THEN |
---|
106 | ! |
---|
107 | ! 2.1: before time step |
---|
108 | IF ( kt /= nit000 ) THEN |
---|
109 | risf_par_tsc_b(:,:,:) = risf_par_tsc(:,:,:) |
---|
110 | fwfisf_par_b (:,:) = fwfisf_par (:,:) |
---|
111 | END IF |
---|
112 | ! |
---|
113 | ! 2.2: compute misfkb, rhisf_tbl, rfrac (deepest level, thickness, fraction of deepest cell affected by tbl) |
---|
114 | ! by simplicity, we assume the top level where param applied do not change with time (done in init part) |
---|
115 | rhisf_tbl_par(:,:) = rhisf0_tbl_par(:,:) |
---|
116 | #if defined key_qco |
---|
117 | DO jk = 1, jpk |
---|
118 | ze3t(:,:,jk) = e3t(:,:,jk,Kmm) |
---|
119 | END DO |
---|
120 | CALL isf_tbl_lvl( ht(:,:), ze3t , misfkt_par, misfkb_par, rhisf_tbl_par, rfrac_tbl_par ) |
---|
121 | #else |
---|
122 | CALL isf_tbl_lvl( ht(:,:), e3t(:,:,:,Kmm), misfkt_par, misfkb_par, rhisf_tbl_par, rfrac_tbl_par ) |
---|
123 | #endif |
---|
124 | ! |
---|
125 | ! 2.3: compute ice shelf melt |
---|
126 | CALL isf_par( kt, Kmm, risf_par_tsc, fwfisf_par ) |
---|
127 | ! |
---|
128 | END IF |
---|
129 | ! |
---|
130 | !================================================================================== |
---|
131 | ! 3.: output specific restart variable in case of coupling with an ice sheet model |
---|
132 | !================================================================================== |
---|
133 | ! |
---|
134 | IF ( ln_isfcpl .AND. lrst_oce ) CALL isfcpl_rst_write(kt, Kmm) |
---|
135 | ! |
---|
136 | IF( ln_timing ) CALL timing_stop('isf') |
---|
137 | ! |
---|
138 | END SUBROUTINE isf_stp |
---|
139 | |
---|
140 | |
---|
141 | SUBROUTINE isf_init( Kbb, Kmm, Kaa ) |
---|
142 | !!--------------------------------------------------------------------- |
---|
143 | !! *** ROUTINE isfstp_init *** |
---|
144 | !! |
---|
145 | !! ** Purpose : Initialisation of the ice shelf public variables |
---|
146 | !! |
---|
147 | !! ** Method : Read the namisf namelist, check option compatibility and set derived parameters |
---|
148 | !! |
---|
149 | !! ** Action : - read namisf parameters |
---|
150 | !! - allocate memory |
---|
151 | !! - output print |
---|
152 | !! - ckeck option compatibility |
---|
153 | !! - call cav/param/isfcpl init routine |
---|
154 | !!---------------------------------------------------------------------- |
---|
155 | INTEGER, INTENT(in) :: Kbb, Kmm, Kaa ! ocean time level indices |
---|
156 | !!---------------------------------------------------------------------- |
---|
157 | ! |
---|
158 | ! constrain: l_isfoasis need to be known |
---|
159 | ! |
---|
160 | CALL isf_nam() ! Read namelist |
---|
161 | ! |
---|
162 | CALL isf_alloc() ! Allocate public array |
---|
163 | ! |
---|
164 | CALL isf_ctl() ! check option compatibility |
---|
165 | ! |
---|
166 | IF( ln_isfcav ) CALL isf_load( Kmm, risfload ) ! compute ice shelf load |
---|
167 | ! |
---|
168 | ! terminate routine now if no ice shelf melt formulation specify |
---|
169 | IF( ln_isf ) THEN |
---|
170 | ! |
---|
171 | IF( ln_isfcav_mlt ) CALL isf_cav_init() ! initialisation melt in the cavity |
---|
172 | ! |
---|
173 | IF( ln_isfpar_mlt ) CALL isf_par_init() ! initialisation parametrised melt |
---|
174 | ! |
---|
175 | IF( ln_isfcpl ) CALL isfcpl_init( Kbb, Kmm, Kaa ) ! initialisation ice sheet coupling |
---|
176 | ! |
---|
177 | END IF |
---|
178 | |
---|
179 | END SUBROUTINE isf_init |
---|
180 | |
---|
181 | |
---|
182 | SUBROUTINE isf_ctl() |
---|
183 | !!--------------------------------------------------------------------- |
---|
184 | !! *** ROUTINE isf_ctl *** |
---|
185 | !! |
---|
186 | !! ** Purpose : output print and option compatibility check |
---|
187 | !! |
---|
188 | !!---------------------------------------------------------------------- |
---|
189 | IF (lwp) THEN |
---|
190 | WRITE(numout,*) |
---|
191 | WRITE(numout,*) 'isf_init : ice shelf initialisation' |
---|
192 | WRITE(numout,*) '~~~~~~~~~~~~' |
---|
193 | WRITE(numout,*) ' Namelist namisf :' |
---|
194 | ! |
---|
195 | WRITE(numout,*) ' ice shelf cavity (open or parametrised) ln_isf = ', ln_isf |
---|
196 | WRITE(numout,*) |
---|
197 | ! |
---|
198 | IF ( ln_isf ) THEN |
---|
199 | WRITE(numout,*) ' Add debug print in isf module ln_isfdebug = ', ln_isfdebug |
---|
200 | WRITE(numout,*) |
---|
201 | WRITE(numout,*) ' melt inside the cavity ln_isfcav_mlt = ', ln_isfcav_mlt |
---|
202 | IF ( ln_isfcav_mlt) THEN |
---|
203 | WRITE(numout,*) ' melt formulation cn_isfcav_mlt= ', TRIM(cn_isfcav_mlt) |
---|
204 | WRITE(numout,*) ' thickness of the top boundary layer rn_htbl = ', rn_htbl |
---|
205 | WRITE(numout,*) ' gamma formulation cn_gammablk = ', TRIM(cn_gammablk) |
---|
206 | IF ( TRIM(cn_gammablk) .NE. 'spe' ) THEN |
---|
207 | WRITE(numout,*) ' gammat coefficient rn_gammat0 = ', rn_gammat0 |
---|
208 | WRITE(numout,*) ' gammas coefficient rn_gammas0 = ', rn_gammas0 |
---|
209 | ! tipaccs 2d top tidal velocity |
---|
210 | IF (ln_2d_ttv) THEN |
---|
211 | WRITE(numout,*) ' top background ke used (from namdrg_top_tippacs) read from 2d file (see zdfdrg bloc)' |
---|
212 | ELSE |
---|
213 | WRITE(numout,*) ' top background ke used (from namdrg_top) rn_ke0 = ', MAXVAL(rke0_top) |
---|
214 | ENDIF |
---|
215 | ! end tipaccs 2d top tidal velocity |
---|
216 | WRITE(numout,*) ' top drag coef. used (from namdrg_top) rn_Cd0 = ', r_Cdmin_top |
---|
217 | END IF |
---|
218 | END IF |
---|
219 | WRITE(numout,*) '' |
---|
220 | ! |
---|
221 | WRITE(numout,*) ' ice shelf melt parametrisation ln_isfpar_mlt = ', ln_isfpar_mlt |
---|
222 | IF ( ln_isfpar_mlt ) THEN |
---|
223 | WRITE(numout,*) ' isf parametrisation formulation cn_isfpar_mlt = ', TRIM(cn_isfpar_mlt) |
---|
224 | END IF |
---|
225 | WRITE(numout,*) '' |
---|
226 | ! |
---|
227 | WRITE(numout,*) ' Coupling to an ice sheet model ln_isfcpl = ', ln_isfcpl |
---|
228 | IF ( ln_isfcpl ) THEN |
---|
229 | WRITE(numout,*) ' conservation activated ln_isfcpl_cons = ', ln_isfcpl_cons |
---|
230 | WRITE(numout,*) ' number of call of the extrapolation loop = ', nn_drown |
---|
231 | ENDIF |
---|
232 | WRITE(numout,*) '' |
---|
233 | ! |
---|
234 | ELSE |
---|
235 | ! |
---|
236 | IF ( ln_isfcav ) THEN |
---|
237 | WRITE(numout,*) '' |
---|
238 | WRITE(numout,*) ' W A R N I N G: ice shelf cavities are open BUT no melt will be computed or read from file !' |
---|
239 | WRITE(numout,*) '' |
---|
240 | END IF |
---|
241 | ! |
---|
242 | END IF |
---|
243 | |
---|
244 | IF (ln_isfcav) THEN |
---|
245 | WRITE(numout,*) ' Ice shelf load method cn_isfload = ', TRIM(cn_isfload) |
---|
246 | WRITE(numout,*) ' Temperature used to compute the ice shelf load = ', rn_isfload_T |
---|
247 | WRITE(numout,*) ' Salinity used to compute the ice shelf load = ', rn_isfload_S |
---|
248 | END IF |
---|
249 | WRITE(numout,*) '' |
---|
250 | FLUSH(numout) |
---|
251 | |
---|
252 | END IF |
---|
253 | ! |
---|
254 | |
---|
255 | !--------------------------------------------------------------------------------------------------------------------- |
---|
256 | ! sanity check ! issue ln_isfcav not yet known as well as l_isfoasis => move this call in isf_stp ? |
---|
257 | ! melt in the cavity without cavity |
---|
258 | IF ( ln_isfcav_mlt .AND. (.NOT. ln_isfcav) ) & |
---|
259 | & CALL ctl_stop('ice shelf melt in the cavity activated (ln_isfcav_mlt) but no cavity detected in domcfg (ln_isfcav), STOP' ) |
---|
260 | ! |
---|
261 | ! ice sheet coupling without cavity |
---|
262 | IF ( ln_isfcpl .AND. (.NOT. ln_isfcav) ) & |
---|
263 | & CALL ctl_stop('coupling with an ice sheet model detected (ln_isfcpl) but no cavity detected in domcfg (ln_isfcav), STOP' ) |
---|
264 | ! |
---|
265 | IF ( ln_isfcpl .AND. ln_isfcpl_cons .AND. ln_linssh ) & |
---|
266 | & CALL ctl_stop( 'The coupling between NEMO and an ice sheet model with the conservation option does not work with the linssh option' ) |
---|
267 | ! |
---|
268 | IF ( l_isfoasis .AND. .NOT. ln_isf ) CALL ctl_stop( ' OASIS send ice shelf fluxes to NEMO but NEMO does not have the isf module activated' ) |
---|
269 | ! |
---|
270 | IF ( l_isfoasis .AND. ln_isf ) THEN |
---|
271 | ! |
---|
272 | CALL ctl_stop( 'namelist combination ln_cpl and ln_isf not tested' ) |
---|
273 | ! |
---|
274 | ! NEMO coupled to ATMO model with isf cavity need oasis method for melt computation |
---|
275 | IF ( ln_isfcav_mlt .AND. TRIM(cn_isfcav_mlt) /= 'oasis' ) CALL ctl_stop( 'cn_isfcav_mlt = oasis is the only option availble if fwf send by oasis' ) |
---|
276 | IF ( ln_isfpar_mlt .AND. TRIM(cn_isfpar_mlt) /= 'oasis' ) CALL ctl_stop( 'cn_isfpar_mlt = oasis is the only option availble if fwf send by oasis' ) |
---|
277 | ! |
---|
278 | ! oasis melt computation not tested (coded but not tested) |
---|
279 | IF ( ln_isfcav_mlt .OR. ln_isfpar_mlt ) THEN |
---|
280 | IF ( TRIM(cn_isfcav_mlt) == 'oasis' ) CALL ctl_stop( 'cn_isfcav_mlt = oasis not tested' ) |
---|
281 | IF ( TRIM(cn_isfpar_mlt) == 'oasis' ) CALL ctl_stop( 'cn_isfpar_mlt = oasis not tested' ) |
---|
282 | END IF |
---|
283 | ! |
---|
284 | ! oasis melt computation with cavity open and cavity parametrised (not coded) |
---|
285 | IF ( ln_isfcav_mlt .AND. ln_isfpar_mlt ) THEN |
---|
286 | IF ( TRIM(cn_isfpar_mlt) == 'oasis' .AND. TRIM(cn_isfcav_mlt) == 'oasis' ) CALL ctl_stop( 'cn_isfpar_mlt = oasis and cn_isfcav_mlt = oasis not coded' ) |
---|
287 | END IF |
---|
288 | ! |
---|
289 | ! compatibility ice shelf and vvl |
---|
290 | IF( .NOT. ln_vvl_zstar .AND. ln_isf ) CALL ctl_stop( 'Only vvl_zstar has been tested with ice shelf cavity' ) |
---|
291 | ! |
---|
292 | END IF |
---|
293 | END SUBROUTINE isf_ctl |
---|
294 | |
---|
295 | |
---|
296 | SUBROUTINE isf_nam |
---|
297 | !!--------------------------------------------------------------------- |
---|
298 | !! *** ROUTINE isf_nam *** |
---|
299 | !! |
---|
300 | !! ** Purpose : Read ice shelf namelist cfg and ref |
---|
301 | !! |
---|
302 | !!---------------------------------------------------------------------- |
---|
303 | INTEGER :: ios ! Local integer output status for namelist read |
---|
304 | !!---------------------------------------------------------------------- |
---|
305 | NAMELIST/namisf/ ln_isf , & |
---|
306 | & cn_gammablk , rn_gammat0 , rn_gammas0 , rn_htbl, sn_isfcav_fwf, & |
---|
307 | & ln_isfcav_mlt , cn_isfcav_mlt , sn_isfcav_fwf , & |
---|
308 | & ln_isfpar_mlt , cn_isfpar_mlt , sn_isfpar_fwf , & |
---|
309 | & sn_isfpar_zmin, sn_isfpar_zmax, sn_isfpar_Leff, & |
---|
310 | & ln_isfcpl , nn_drown , ln_isfcpl_cons, ln_isfdebug, & |
---|
311 | & cn_isfload , rn_isfload_T , rn_isfload_S , cn_isfdir |
---|
312 | !!---------------------------------------------------------------------- |
---|
313 | ! |
---|
314 | READ ( numnam_ref, namisf, IOSTAT = ios, ERR = 901) |
---|
315 | 901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namisf in reference namelist' ) |
---|
316 | ! |
---|
317 | READ ( numnam_cfg, namisf, IOSTAT = ios, ERR = 902 ) |
---|
318 | 902 IF( ios > 0 ) CALL ctl_nam ( ios , 'namisf in configuration namelist' ) |
---|
319 | IF(lwm) WRITE ( numond, namisf ) |
---|
320 | |
---|
321 | END SUBROUTINE isf_nam |
---|
322 | !! |
---|
323 | !!====================================================================== |
---|
324 | END MODULE isfstp |
---|