1 | MODULE iceupdate |
---|
2 | !!====================================================================== |
---|
3 | !! *** MODULE iceupdate *** |
---|
4 | !! Sea-ice : computation of the flux at the sea ice/ocean interface |
---|
5 | !!====================================================================== |
---|
6 | !! History : 4.0 ! 2018 (many people) SI3 [aka Sea Ice cube] |
---|
7 | !!---------------------------------------------------------------------- |
---|
8 | #if defined key_si3 |
---|
9 | !!---------------------------------------------------------------------- |
---|
10 | !! 'key_si3' SI3 sea-ice model |
---|
11 | !!---------------------------------------------------------------------- |
---|
12 | !! ice_update_alloc : allocate the iceupdate arrays |
---|
13 | !! ice_update_init : initialisation |
---|
14 | !! ice_update_flx : updates mass, heat and salt fluxes at the ocean surface |
---|
15 | !! ice_update_tau : update i- and j-stresses, and its modulus at the ocean surface |
---|
16 | !!---------------------------------------------------------------------- |
---|
17 | USE phycst ! physical constants |
---|
18 | USE dom_oce ! ocean domain |
---|
19 | USE ice ! sea-ice: variables |
---|
20 | USE sbc_ice ! Surface boundary condition: ice fields |
---|
21 | USE sbc_oce ! Surface boundary condition: ocean fields |
---|
22 | USE sbccpl ! Surface boundary condition: coupled interface |
---|
23 | USE icealb ! sea-ice: albedo parameters |
---|
24 | USE traqsr ! add penetration of solar flux in the calculation of heat budget |
---|
25 | USE icectl ! sea-ice: control prints |
---|
26 | USE zdfdrg , ONLY : ln_drgice_imp |
---|
27 | ! |
---|
28 | USE in_out_manager ! I/O manager |
---|
29 | USE iom ! I/O manager library |
---|
30 | USE lib_mpp ! MPP library |
---|
31 | USE lib_fortran ! fortran utilities (glob_sum + no signed zero) |
---|
32 | USE lbclnk ! lateral boundary conditions (or mpp links) |
---|
33 | USE timing ! Timing |
---|
34 | |
---|
35 | IMPLICIT NONE |
---|
36 | PRIVATE |
---|
37 | |
---|
38 | PUBLIC ice_update_init ! called by ice_init |
---|
39 | PUBLIC ice_update_flx ! called by ice_stp |
---|
40 | PUBLIC ice_update_tau ! called by ice_stp |
---|
41 | |
---|
42 | REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) :: utau_oce, vtau_oce ! air-ocean surface i- & j-stress [N/m2] |
---|
43 | REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) :: tmod_io ! modulus of the ice-ocean velocity [m/s] |
---|
44 | |
---|
45 | !! * Substitutions |
---|
46 | # include "do_loop_substitute.h90" |
---|
47 | !!---------------------------------------------------------------------- |
---|
48 | !! NEMO/ICE 4.0 , NEMO Consortium (2018) |
---|
49 | !! $Id$ |
---|
50 | !! Software governed by the CeCILL license (see ./LICENSE) |
---|
51 | !!---------------------------------------------------------------------- |
---|
52 | CONTAINS |
---|
53 | |
---|
54 | INTEGER FUNCTION ice_update_alloc() |
---|
55 | !!------------------------------------------------------------------- |
---|
56 | !! *** ROUTINE ice_update_alloc *** |
---|
57 | !!------------------------------------------------------------------- |
---|
58 | ALLOCATE( utau_oce(jpi,jpj), vtau_oce(jpi,jpj), tmod_io(jpi,jpj), STAT=ice_update_alloc ) |
---|
59 | ! |
---|
60 | CALL mpp_sum( 'iceupdate', ice_update_alloc ) |
---|
61 | IF( ice_update_alloc /= 0 ) CALL ctl_stop( 'STOP', 'ice_update_alloc: failed to allocate arrays' ) |
---|
62 | ! |
---|
63 | END FUNCTION ice_update_alloc |
---|
64 | |
---|
65 | |
---|
66 | SUBROUTINE ice_update_flx( kt ) |
---|
67 | !!------------------------------------------------------------------- |
---|
68 | !! *** ROUTINE ice_update_flx *** |
---|
69 | !! |
---|
70 | !! ** Purpose : Update the surface ocean boundary condition for heat |
---|
71 | !! salt and mass over areas where sea-ice is non-zero |
---|
72 | !! |
---|
73 | !! ** Action : - computes the heat and freshwater/salt fluxes |
---|
74 | !! at the ice-ocean interface. |
---|
75 | !! - Update the ocean sbc |
---|
76 | !! |
---|
77 | !! ** Outputs : - qsr : sea heat flux: solar |
---|
78 | !! - qns : sea heat flux: non solar |
---|
79 | !! - emp : freshwater budget: volume flux |
---|
80 | !! - sfx : salt flux |
---|
81 | !! - fr_i : ice fraction |
---|
82 | !! - tn_ice : sea-ice surface temperature |
---|
83 | !! - alb_ice : sea-ice albedo (recomputed only for coupled mode) |
---|
84 | !! |
---|
85 | !! References : Goosse, H. et al. 1996, Bul. Soc. Roy. Sc. Liege, 65, 87-90. |
---|
86 | !! Tartinville et al. 2001 Ocean Modelling, 3, 95-108. |
---|
87 | !! These refs are now obsolete since everything has been revised |
---|
88 | !! The ref should be Rousset et al., 2015 |
---|
89 | !!--------------------------------------------------------------------- |
---|
90 | INTEGER, INTENT(in) :: kt ! number of iteration |
---|
91 | ! |
---|
92 | INTEGER :: ji, jj, jl, jk ! dummy loop indices |
---|
93 | REAL(wp) :: zqsr ! New solar flux received by the ocean |
---|
94 | REAL(wp), DIMENSION(jpi,jpj) :: z2d ! 2D workspace |
---|
95 | !!--------------------------------------------------------------------- |
---|
96 | IF( ln_timing ) CALL timing_start('iceupdate') |
---|
97 | |
---|
98 | IF( kt == nit000 .AND. lwp ) THEN |
---|
99 | WRITE(numout,*) |
---|
100 | WRITE(numout,*)'ice_update_flx: update fluxes (mass, salt and heat) at the ice-ocean interface' |
---|
101 | WRITE(numout,*)'~~~~~~~~~~~~~~' |
---|
102 | ENDIF |
---|
103 | |
---|
104 | ! Net heat flux on top of the ice-ocean (W.m-2) |
---|
105 | !---------------------------------------------- |
---|
106 | qt_atm_oi(:,:) = qns_tot(:,:) + qsr_tot(:,:) |
---|
107 | |
---|
108 | ! --- case we bypass ice thermodynamics --- ! |
---|
109 | IF( .NOT. ln_icethd ) THEN ! we suppose ice is impermeable => ocean is isolated from atmosphere |
---|
110 | qt_atm_oi (:,:) = ( 1._wp - at_i_b(:,:) ) * ( qns_oce(:,:) + qsr_oce(:,:) ) + qemp_oce(:,:) |
---|
111 | qt_oce_ai (:,:) = ( 1._wp - at_i_b(:,:) ) * qns_oce(:,:) + qemp_oce(:,:) |
---|
112 | emp_ice (:,:) = 0._wp |
---|
113 | qemp_ice (:,:) = 0._wp |
---|
114 | qevap_ice (:,:,:) = 0._wp |
---|
115 | ENDIF |
---|
116 | |
---|
117 | DO_2D( 1, 1, 1, 1 ) |
---|
118 | |
---|
119 | ! Solar heat flux reaching the ocean (max) = zqsr (W.m-2) |
---|
120 | !--------------------------------------------------- |
---|
121 | zqsr = qsr_tot(ji,jj) - SUM( a_i_b(ji,jj,:) * ( qsr_ice(ji,jj,:) - qtr_ice_bot(ji,jj,:) ) ) |
---|
122 | |
---|
123 | ! Total heat flux reaching the ocean = qt_oce_ai (W.m-2) |
---|
124 | !--------------------------------------------------- |
---|
125 | qt_oce_ai(ji,jj) = qt_atm_oi(ji,jj) - hfx_sum(ji,jj) - hfx_bom(ji,jj) - hfx_bog(ji,jj) & |
---|
126 | & - hfx_dif(ji,jj) - hfx_opw(ji,jj) - hfx_snw(ji,jj) & |
---|
127 | & + hfx_thd(ji,jj) + hfx_dyn(ji,jj) + hfx_res(ji,jj) & |
---|
128 | & + hfx_sub(ji,jj) - SUM( qevap_ice(ji,jj,:) * a_i_b(ji,jj,:) ) + hfx_spr(ji,jj) |
---|
129 | |
---|
130 | ! New qsr and qns used to compute the oceanic heat flux at the next time step |
---|
131 | !---------------------------------------------------------------------------- |
---|
132 | ! if warming and some ice remains, then we suppose that the whole solar flux has been consumed to melt the ice |
---|
133 | ! else ( cooling or no ice left ), then we suppose that no solar flux has been consumed |
---|
134 | ! |
---|
135 | IF( fhld(ji,jj) > 0._wp .AND. at_i(ji,jj) > 0._wp ) THEN !-- warming and some ice remains |
---|
136 | ! solar flux transmitted thru the 1st level of the ocean (i.e. not used by sea-ice) |
---|
137 | qsr(ji,jj) = ( 1._wp - at_i_b(ji,jj) ) * qsr_oce(ji,jj) * ( 1._wp - frq_m(ji,jj) ) & |
---|
138 | ! + solar flux transmitted thru ice and the 1st ocean level (also not used by sea-ice) |
---|
139 | & + SUM( a_i_b(ji,jj,:) * qtr_ice_bot(ji,jj,:) ) * ( 1._wp - frq_m(ji,jj) ) |
---|
140 | ! |
---|
141 | ELSE !-- cooling or no ice left |
---|
142 | qsr(ji,jj) = zqsr |
---|
143 | ENDIF |
---|
144 | ! |
---|
145 | ! the non-solar is simply derived from the solar flux |
---|
146 | qns(ji,jj) = qt_oce_ai(ji,jj) - qsr(ji,jj) |
---|
147 | |
---|
148 | ! Mass flux at the atm. surface |
---|
149 | !----------------------------------- |
---|
150 | wfx_sub(ji,jj) = wfx_snw_sub(ji,jj) + wfx_ice_sub(ji,jj) |
---|
151 | |
---|
152 | ! Mass flux at the ocean surface |
---|
153 | !------------------------------------ |
---|
154 | ! ice-ocean mass flux |
---|
155 | wfx_ice(ji,jj) = wfx_bog(ji,jj) + wfx_bom(ji,jj) + wfx_sum(ji,jj) + wfx_sni(ji,jj) & |
---|
156 | & + wfx_opw(ji,jj) + wfx_dyn(ji,jj) + wfx_res(ji,jj) + wfx_lam(ji,jj) |
---|
157 | |
---|
158 | ! snw-ocean mass flux |
---|
159 | wfx_snw(ji,jj) = wfx_snw_sni(ji,jj) + wfx_snw_dyn(ji,jj) + wfx_snw_sum(ji,jj) |
---|
160 | |
---|
161 | ! total mass flux at the ocean/ice interface |
---|
162 | fmmflx(ji,jj) = - wfx_ice(ji,jj) - wfx_snw(ji,jj) - wfx_pnd(ji,jj) - wfx_err_sub(ji,jj) ! ice-ocean mass flux saved at least for biogeochemical model |
---|
163 | emp (ji,jj) = emp_oce(ji,jj) - wfx_ice(ji,jj) - wfx_snw(ji,jj) - wfx_pnd(ji,jj) - wfx_err_sub(ji,jj) ! atm-ocean + ice-ocean mass flux |
---|
164 | |
---|
165 | ! Salt flux at the ocean surface |
---|
166 | !------------------------------------------ |
---|
167 | sfx(ji,jj) = sfx_bog(ji,jj) + sfx_bom(ji,jj) + sfx_sum(ji,jj) + sfx_sni(ji,jj) + sfx_opw(ji,jj) & |
---|
168 | & + sfx_res(ji,jj) + sfx_dyn(ji,jj) + sfx_bri(ji,jj) + sfx_sub(ji,jj) + sfx_lam(ji,jj) |
---|
169 | |
---|
170 | ! Mass of snow and ice per unit area |
---|
171 | !---------------------------------------- |
---|
172 | snwice_mass_b(ji,jj) = snwice_mass(ji,jj) ! save mass from the previous ice time step |
---|
173 | ! ! new mass per unit area |
---|
174 | snwice_mass (ji,jj) = tmask(ji,jj,1) * ( rhos * vt_s(ji,jj) + rhoi * vt_i(ji,jj) + rhow * (vt_ip(ji,jj) + vt_il(ji,jj)) ) |
---|
175 | ! ! time evolution of snow+ice mass |
---|
176 | snwice_fmass (ji,jj) = ( snwice_mass(ji,jj) - snwice_mass_b(ji,jj) ) * r1_Dt_ice |
---|
177 | |
---|
178 | END_2D |
---|
179 | |
---|
180 | ! Storing the transmitted variables |
---|
181 | !---------------------------------- |
---|
182 | fr_i (:,:) = at_i(:,:) ! Sea-ice fraction |
---|
183 | tn_ice(:,:,:) = t_su(:,:,:) ! Ice surface temperature |
---|
184 | |
---|
185 | ! Snow/ice albedo (only if sent to coupler, useless in forced mode) |
---|
186 | !------------------------------------------------------------------ |
---|
187 | CALL ice_alb( t_su, h_i, h_s, ln_pnd_alb, a_ip_eff, h_ip, cloud_fra, alb_ice ) ! ice albedo |
---|
188 | |
---|
189 | ! |
---|
190 | IF( lrst_ice ) THEN !* write snwice_mass fields in the restart file |
---|
191 | CALL update_rst( 'WRITE', kt ) |
---|
192 | ENDIF |
---|
193 | ! |
---|
194 | ! output all fluxes |
---|
195 | !------------------ |
---|
196 | ! |
---|
197 | ! --- salt fluxes [kg/m2/s] --- ! |
---|
198 | ! ! sfxice = sfxbog + sfxbom + sfxsum + sfxsni + sfxopw + sfxres + sfxdyn + sfxbri + sfxsub + sfxlam |
---|
199 | IF( iom_use('sfxice' ) ) CALL iom_put( 'sfxice', sfx * 1.e-03 ) ! salt flux from total ice growth/melt |
---|
200 | IF( iom_use('sfxbog' ) ) CALL iom_put( 'sfxbog', sfx_bog * 1.e-03 ) ! salt flux from bottom growth |
---|
201 | IF( iom_use('sfxbom' ) ) CALL iom_put( 'sfxbom', sfx_bom * 1.e-03 ) ! salt flux from bottom melting |
---|
202 | IF( iom_use('sfxsum' ) ) CALL iom_put( 'sfxsum', sfx_sum * 1.e-03 ) ! salt flux from surface melting |
---|
203 | IF( iom_use('sfxlam' ) ) CALL iom_put( 'sfxlam', sfx_lam * 1.e-03 ) ! salt flux from lateral melting |
---|
204 | IF( iom_use('sfxsni' ) ) CALL iom_put( 'sfxsni', sfx_sni * 1.e-03 ) ! salt flux from snow ice formation |
---|
205 | IF( iom_use('sfxopw' ) ) CALL iom_put( 'sfxopw', sfx_opw * 1.e-03 ) ! salt flux from open water formation |
---|
206 | IF( iom_use('sfxdyn' ) ) CALL iom_put( 'sfxdyn', sfx_dyn * 1.e-03 ) ! salt flux from ridging rafting |
---|
207 | IF( iom_use('sfxbri' ) ) CALL iom_put( 'sfxbri', sfx_bri * 1.e-03 ) ! salt flux from brines |
---|
208 | IF( iom_use('sfxres' ) ) CALL iom_put( 'sfxres', sfx_res * 1.e-03 ) ! salt flux from undiagnosed processes |
---|
209 | IF( iom_use('sfxsub' ) ) CALL iom_put( 'sfxsub', sfx_sub * 1.e-03 ) ! salt flux from sublimation |
---|
210 | |
---|
211 | ! --- mass fluxes [kg/m2/s] --- ! |
---|
212 | CALL iom_put( 'emp_oce', emp_oce ) ! emp over ocean (taking into account the snow blown away from the ice) |
---|
213 | CALL iom_put( 'emp_ice', emp_ice ) ! emp over ice (taking into account the snow blown away from the ice) |
---|
214 | |
---|
215 | ! ! vfxice = vfxbog + vfxbom + vfxsum + vfxsni + vfxopw + vfxdyn + vfxres + vfxlam + vfxpnd |
---|
216 | CALL iom_put( 'vfxice' , wfx_ice ) ! mass flux from total ice growth/melt |
---|
217 | CALL iom_put( 'vfxbog' , wfx_bog ) ! mass flux from bottom growth |
---|
218 | CALL iom_put( 'vfxbom' , wfx_bom ) ! mass flux from bottom melt |
---|
219 | CALL iom_put( 'vfxsum' , wfx_sum ) ! mass flux from surface melt |
---|
220 | CALL iom_put( 'vfxlam' , wfx_lam ) ! mass flux from lateral melt |
---|
221 | CALL iom_put( 'vfxsni' , wfx_sni ) ! mass flux from snow-ice formation |
---|
222 | CALL iom_put( 'vfxopw' , wfx_opw ) ! mass flux from growth in open water |
---|
223 | CALL iom_put( 'vfxdyn' , wfx_dyn ) ! mass flux from dynamics (ridging) |
---|
224 | CALL iom_put( 'vfxres' , wfx_res ) ! mass flux from undiagnosed processes |
---|
225 | CALL iom_put( 'vfxpnd' , wfx_pnd ) ! mass flux from melt ponds |
---|
226 | CALL iom_put( 'vfxsub' , wfx_ice_sub ) ! mass flux from ice sublimation (ice-atm.) |
---|
227 | CALL iom_put( 'vfxsub_err', wfx_err_sub ) ! "excess" of sublimation sent to ocean |
---|
228 | |
---|
229 | IF ( iom_use( 'vfxthin' ) ) THEN ! mass flux from ice growth in open water + thin ice (<20cm) => comparable to observations |
---|
230 | WHERE( hm_i(:,:) < 0.2 .AND. hm_i(:,:) > 0. ) ; z2d = wfx_bog |
---|
231 | ELSEWHERE ; z2d = 0._wp |
---|
232 | END WHERE |
---|
233 | CALL iom_put( 'vfxthin', wfx_opw + z2d ) |
---|
234 | ENDIF |
---|
235 | |
---|
236 | ! ! vfxsnw = vfxsnw_sni + vfxsnw_dyn + vfxsnw_sum |
---|
237 | CALL iom_put( 'vfxsnw' , wfx_snw ) ! mass flux from total snow growth/melt |
---|
238 | CALL iom_put( 'vfxsnw_sum' , wfx_snw_sum ) ! mass flux from snow melt at the surface |
---|
239 | CALL iom_put( 'vfxsnw_sni' , wfx_snw_sni ) ! mass flux from snow melt during snow-ice formation |
---|
240 | CALL iom_put( 'vfxsnw_dyn' , wfx_snw_dyn ) ! mass flux from dynamics (ridging) |
---|
241 | CALL iom_put( 'vfxsnw_sub' , wfx_snw_sub ) ! mass flux from snow sublimation (ice-atm.) |
---|
242 | CALL iom_put( 'vfxsnw_pre' , wfx_spr ) ! snow precip |
---|
243 | |
---|
244 | ! --- heat fluxes [W/m2] --- ! |
---|
245 | ! ! qt_atm_oi - qt_oce_ai = hfxdhc - ( dihctrp + dshctrp ) |
---|
246 | IF( iom_use('qsr_oce' ) ) CALL iom_put( 'qsr_oce' , qsr_oce * ( 1._wp - at_i_b ) ) ! solar flux at ocean surface |
---|
247 | IF( iom_use('qns_oce' ) ) CALL iom_put( 'qns_oce' , qns_oce * ( 1._wp - at_i_b ) + qemp_oce ) ! non-solar flux at ocean surface |
---|
248 | IF( iom_use('qsr_ice' ) ) CALL iom_put( 'qsr_ice' , SUM( qsr_ice * a_i_b, dim=3 ) ) ! solar flux at ice surface |
---|
249 | IF( iom_use('qns_ice' ) ) CALL iom_put( 'qns_ice' , SUM( qns_ice * a_i_b, dim=3 ) + qemp_ice ) ! non-solar flux at ice surface |
---|
250 | IF( iom_use('qtr_ice_bot') ) CALL iom_put( 'qtr_ice_bot', SUM( qtr_ice_bot * a_i_b, dim=3 ) ) ! solar flux transmitted thru ice |
---|
251 | IF( iom_use('qtr_ice_top') ) CALL iom_put( 'qtr_ice_top', SUM( qtr_ice_top * a_i_b, dim=3 ) ) ! solar flux transmitted thru ice surface |
---|
252 | IF( iom_use('qt_oce' ) ) CALL iom_put( 'qt_oce' , ( qsr_oce + qns_oce ) * ( 1._wp - at_i_b ) + qemp_oce ) |
---|
253 | IF( iom_use('qt_ice' ) ) CALL iom_put( 'qt_ice' , SUM( ( qns_ice + qsr_ice ) * a_i_b, dim=3 ) + qemp_ice ) |
---|
254 | IF( iom_use('qt_oce_ai' ) ) CALL iom_put( 'qt_oce_ai' , qt_oce_ai * tmask(:,:,1) ) ! total heat flux at the ocean surface: interface oce-(ice+atm) |
---|
255 | IF( iom_use('qt_atm_oi' ) ) CALL iom_put( 'qt_atm_oi' , qt_atm_oi * tmask(:,:,1) ) ! total heat flux at the oce-ice surface: interface atm-(ice+oce) |
---|
256 | IF( iom_use('qemp_oce' ) ) CALL iom_put( 'qemp_oce' , qemp_oce ) ! Downward Heat Flux from E-P over ocean |
---|
257 | IF( iom_use('qemp_ice' ) ) CALL iom_put( 'qemp_ice' , qemp_ice ) ! Downward Heat Flux from E-P over ice |
---|
258 | |
---|
259 | ! heat fluxes from ice transformations |
---|
260 | ! ! hfxdhc = hfxbog + hfxbom + hfxsum + hfxopw + hfxdif + hfxsnw - ( hfxthd + hfxdyn + hfxres + hfxsub + hfxspr ) |
---|
261 | CALL iom_put ('hfxbog' , hfx_bog ) ! heat flux used for ice bottom growth |
---|
262 | CALL iom_put ('hfxbom' , hfx_bom ) ! heat flux used for ice bottom melt |
---|
263 | CALL iom_put ('hfxsum' , hfx_sum ) ! heat flux used for ice surface melt |
---|
264 | CALL iom_put ('hfxopw' , hfx_opw ) ! heat flux used for ice formation in open water |
---|
265 | CALL iom_put ('hfxdif' , hfx_dif ) ! heat flux used for ice temperature change |
---|
266 | CALL iom_put ('hfxsnw' , hfx_snw ) ! heat flux used for snow melt |
---|
267 | CALL iom_put ('hfxerr' , hfx_err_dif ) ! heat flux error after heat diffusion |
---|
268 | |
---|
269 | ! heat fluxes associated with mass exchange (freeze/melt/precip...) |
---|
270 | CALL iom_put ('hfxthd' , hfx_thd ) ! |
---|
271 | CALL iom_put ('hfxdyn' , hfx_dyn ) ! |
---|
272 | CALL iom_put ('hfxres' , hfx_res ) ! |
---|
273 | CALL iom_put ('hfxsub' , hfx_sub ) ! |
---|
274 | CALL iom_put ('hfxspr' , hfx_spr ) ! Heat flux from snow precip heat content |
---|
275 | |
---|
276 | ! other heat fluxes |
---|
277 | IF( iom_use('hfxsensib' ) ) CALL iom_put( 'hfxsensib' , -qsb_ice_bot * at_i_b ) ! Sensible oceanic heat flux |
---|
278 | IF( iom_use('hfxcndbot' ) ) CALL iom_put( 'hfxcndbot' , SUM( qcn_ice_bot * a_i_b, dim=3 ) ) ! Bottom conduction flux |
---|
279 | IF( iom_use('hfxcndtop' ) ) CALL iom_put( 'hfxcndtop' , SUM( qcn_ice_top * a_i_b, dim=3 ) ) ! Surface conduction flux |
---|
280 | |
---|
281 | ! controls |
---|
282 | !--------- |
---|
283 | #if ! defined key_agrif |
---|
284 | IF( ln_icediachk ) CALL ice_cons_final('iceupdate') ! conservation |
---|
285 | #endif |
---|
286 | IF( ln_icectl ) CALL ice_prt (kt, iiceprt, jiceprt, 3, 'Final state ice_update') ! prints |
---|
287 | IF( sn_cfctl%l_prtctl ) CALL ice_prt3D ('iceupdate') ! prints |
---|
288 | IF( ln_timing ) CALL timing_stop ('iceupdate') ! timing |
---|
289 | ! |
---|
290 | END SUBROUTINE ice_update_flx |
---|
291 | |
---|
292 | |
---|
293 | SUBROUTINE ice_update_tau( kt, pu_oce, pv_oce ) |
---|
294 | !!------------------------------------------------------------------- |
---|
295 | !! *** ROUTINE ice_update_tau *** |
---|
296 | !! |
---|
297 | !! ** Purpose : Update the ocean surface stresses due to the ice |
---|
298 | !! |
---|
299 | !! ** Action : * at each ice time step (every nn_fsbc time step): |
---|
300 | !! - compute the modulus of ice-ocean relative velocity |
---|
301 | !! (*rho*Cd) at T-point (C-grid) or I-point (B-grid) |
---|
302 | !! tmod_io = rhoco * | U_ice-U_oce | |
---|
303 | !! - update the modulus of stress at ocean surface |
---|
304 | !! taum = (1-a) * taum + a * tmod_io * | U_ice-U_oce | |
---|
305 | !! * at each ocean time step (every kt): |
---|
306 | !! compute linearized ice-ocean stresses as |
---|
307 | !! Utau = tmod_io * | U_ice - pU_oce | |
---|
308 | !! using instantaneous current ocean velocity (usually before) |
---|
309 | !! |
---|
310 | !! NB: - ice-ocean rotation angle no more allowed |
---|
311 | !! - here we make an approximation: taum is only computed every ice time step |
---|
312 | !! This avoids mutiple average to pass from T -> U,V grids and next from U,V grids |
---|
313 | !! to T grid. taum is used in TKE and GLS, which should not be too sensitive to this approximaton... |
---|
314 | !! |
---|
315 | !! ** Outputs : - utau, vtau : surface ocean i- and j-stress (u- & v-pts) updated with ice-ocean fluxes |
---|
316 | !! - taum : modulus of the surface ocean stress (T-point) updated with ice-ocean fluxes |
---|
317 | !!--------------------------------------------------------------------- |
---|
318 | INTEGER , INTENT(in) :: kt ! ocean time-step index |
---|
319 | REAL(wp), DIMENSION(jpi,jpj), INTENT(in) :: pu_oce, pv_oce ! surface ocean currents |
---|
320 | ! |
---|
321 | INTEGER :: ji, jj ! dummy loop indices |
---|
322 | REAL(wp) :: zat_u, zutau_ice, zu_t, zmodt ! local scalar |
---|
323 | REAL(wp) :: zat_v, zvtau_ice, zv_t, zrhoco ! - - |
---|
324 | REAL(wp) :: zflagi ! - - |
---|
325 | !!--------------------------------------------------------------------- |
---|
326 | IF( ln_timing ) CALL timing_start('ice_update') |
---|
327 | |
---|
328 | IF( kt == nit000 .AND. lwp ) THEN |
---|
329 | WRITE(numout,*) |
---|
330 | WRITE(numout,*)'ice_update_tau: update stress at the ice-ocean interface' |
---|
331 | WRITE(numout,*)'~~~~~~~~~~~~~~' |
---|
332 | ENDIF |
---|
333 | |
---|
334 | zrhoco = rho0 * rn_cio |
---|
335 | ! |
---|
336 | IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN !== Ice time-step only ==! (i.e. surface module time-step) |
---|
337 | DO_2D( 0, 0, 0, 0 ) !* update the modulus of stress at ocean surface (T-point) |
---|
338 | ! ! 2*(U_ice-U_oce) at T-point |
---|
339 | zu_t = u_ice(ji,jj) + u_ice(ji-1,jj) - u_oce(ji,jj) - u_oce(ji-1,jj) |
---|
340 | zv_t = v_ice(ji,jj) + v_ice(ji,jj-1) - v_oce(ji,jj) - v_oce(ji,jj-1) |
---|
341 | ! ! |U_ice-U_oce|^2 |
---|
342 | zmodt = 0.25_wp * ( zu_t * zu_t + zv_t * zv_t ) |
---|
343 | ! ! update the ocean stress modulus |
---|
344 | taum(ji,jj) = ( 1._wp - at_i(ji,jj) ) * taum(ji,jj) + at_i(ji,jj) * zrhoco * zmodt |
---|
345 | tmod_io(ji,jj) = zrhoco * SQRT( zmodt ) ! rhoco * |U_ice-U_oce| at T-point |
---|
346 | END_2D |
---|
347 | CALL lbc_lnk( 'iceupdate', taum, 'T', 1.0_wp, tmod_io, 'T', 1.0_wp ) |
---|
348 | ! |
---|
349 | utau_oce(:,:) = utau(:,:) !* save the air-ocean stresses at ice time-step |
---|
350 | vtau_oce(:,:) = vtau(:,:) |
---|
351 | ! |
---|
352 | ENDIF |
---|
353 | ! |
---|
354 | ! !== every ocean time-step ==! |
---|
355 | IF ( ln_drgice_imp ) THEN |
---|
356 | ! Save drag with right sign to update top drag in the ocean implicit friction |
---|
357 | rCdU_ice(:,:) = -r1_rho0 * tmod_io(:,:) * at_i(:,:) * tmask(:,:,1) |
---|
358 | zflagi = 0._wp |
---|
359 | ELSE |
---|
360 | zflagi = 1._wp |
---|
361 | ENDIF |
---|
362 | ! |
---|
363 | DO_2D( 0, 0, 0, 0 ) !* update the stress WITHOUT an ice-ocean rotation angle |
---|
364 | ! ice area at u and v-points |
---|
365 | zat_u = ( at_i(ji,jj) * tmask(ji,jj,1) + at_i (ji+1,jj ) * tmask(ji+1,jj ,1) ) & |
---|
366 | & / MAX( 1.0_wp , tmask(ji,jj,1) + tmask(ji+1,jj ,1) ) |
---|
367 | zat_v = ( at_i(ji,jj) * tmask(ji,jj,1) + at_i (ji ,jj+1 ) * tmask(ji ,jj+1,1) ) & |
---|
368 | & / MAX( 1.0_wp , tmask(ji,jj,1) + tmask(ji ,jj+1,1) ) |
---|
369 | ! ! linearized quadratic drag formulation |
---|
370 | zutau_ice = 0.5_wp * ( tmod_io(ji,jj) + tmod_io(ji+1,jj) ) * ( u_ice(ji,jj) - pu_oce(ji,jj) ) |
---|
371 | zvtau_ice = 0.5_wp * ( tmod_io(ji,jj) + tmod_io(ji,jj+1) ) * ( v_ice(ji,jj) - pv_oce(ji,jj) ) |
---|
372 | ! ! stresses at the ocean surface |
---|
373 | utau(ji,jj) = ( 1._wp - zat_u ) * utau_oce(ji,jj) + zat_u * zutau_ice |
---|
374 | vtau(ji,jj) = ( 1._wp - zat_v ) * vtau_oce(ji,jj) + zat_v * zvtau_ice |
---|
375 | END_2D |
---|
376 | CALL lbc_lnk( 'iceupdate', utau, 'U', -1.0_wp, vtau, 'V', -1.0_wp ) ! lateral boundary condition |
---|
377 | ! |
---|
378 | IF( ln_timing ) CALL timing_stop('ice_update') |
---|
379 | ! |
---|
380 | END SUBROUTINE ice_update_tau |
---|
381 | |
---|
382 | |
---|
383 | SUBROUTINE ice_update_init |
---|
384 | !!------------------------------------------------------------------- |
---|
385 | !! *** ROUTINE ice_update_init *** |
---|
386 | !! |
---|
387 | !! ** Purpose : allocate ice-ocean stress fields and read restarts |
---|
388 | !! containing the snow & ice mass |
---|
389 | !! |
---|
390 | !!------------------------------------------------------------------- |
---|
391 | INTEGER :: ji, jj, jk ! dummy loop indices |
---|
392 | REAL(wp) :: zcoefu, zcoefv, zcoeff ! local scalar |
---|
393 | !!------------------------------------------------------------------- |
---|
394 | ! |
---|
395 | IF(lwp) WRITE(numout,*) |
---|
396 | IF(lwp) WRITE(numout,*) 'ice_update_init: ice-ocean stress init' |
---|
397 | IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~~~' |
---|
398 | ! |
---|
399 | ! ! allocate ice_update array |
---|
400 | IF( ice_update_alloc() /= 0 ) CALL ctl_stop( 'STOP', 'ice_update_init : unable to allocate standard arrays' ) |
---|
401 | ! |
---|
402 | CALL update_rst( 'READ' ) !* read or initialize all required files |
---|
403 | ! |
---|
404 | END SUBROUTINE ice_update_init |
---|
405 | |
---|
406 | |
---|
407 | SUBROUTINE update_rst( cdrw, kt ) |
---|
408 | !!--------------------------------------------------------------------- |
---|
409 | !! *** ROUTINE rhg_evp_rst *** |
---|
410 | !! |
---|
411 | !! ** Purpose : Read or write RHG file in restart file |
---|
412 | !! |
---|
413 | !! ** Method : use of IOM library |
---|
414 | !!---------------------------------------------------------------------- |
---|
415 | CHARACTER(len=*) , INTENT(in) :: cdrw ! 'READ'/'WRITE' flag |
---|
416 | INTEGER, OPTIONAL, INTENT(in) :: kt ! ice time-step |
---|
417 | ! |
---|
418 | INTEGER :: iter ! local integer |
---|
419 | INTEGER :: id1 ! local integer |
---|
420 | !!---------------------------------------------------------------------- |
---|
421 | ! |
---|
422 | IF( TRIM(cdrw) == 'READ' ) THEN ! Read/initialize |
---|
423 | ! ! --------------- |
---|
424 | IF( ln_rstart ) THEN !* Read the restart file |
---|
425 | ! |
---|
426 | id1 = iom_varid( numrir, 'snwice_mass' , ldstop = .FALSE. ) |
---|
427 | ! |
---|
428 | IF( id1 > 0 ) THEN ! fields exist |
---|
429 | CALL iom_get( numrir, jpdom_auto, 'snwice_mass' , snwice_mass ) |
---|
430 | CALL iom_get( numrir, jpdom_auto, 'snwice_mass_b', snwice_mass_b ) |
---|
431 | ELSE ! start from rest |
---|
432 | IF(lwp) WRITE(numout,*) ' ==>> previous run without snow-ice mass output then set it' |
---|
433 | snwice_mass (:,:) = tmask(:,:,1) * ( rhos * vt_s(:,:) + rhoi * vt_i(:,:) ) |
---|
434 | snwice_mass_b(:,:) = snwice_mass(:,:) |
---|
435 | ENDIF |
---|
436 | ELSE !* Start from rest |
---|
437 | IF(lwp) WRITE(numout,*) ' ==>> start from rest: set the snow-ice mass' |
---|
438 | snwice_mass (:,:) = tmask(:,:,1) * ( rhos * vt_s(:,:) + rhoi * vt_i(:,:) ) |
---|
439 | snwice_mass_b(:,:) = snwice_mass(:,:) |
---|
440 | ENDIF |
---|
441 | ! |
---|
442 | ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN ! Create restart file |
---|
443 | ! ! ------------------- |
---|
444 | IF(lwp) WRITE(numout,*) '---- update-rst ----' |
---|
445 | iter = kt + nn_fsbc - 1 ! ice restarts are written at kt == nitrst - nn_fsbc + 1 |
---|
446 | ! |
---|
447 | CALL iom_rstput( iter, nitrst, numriw, 'snwice_mass' , snwice_mass ) |
---|
448 | CALL iom_rstput( iter, nitrst, numriw, 'snwice_mass_b', snwice_mass_b ) |
---|
449 | ! |
---|
450 | ENDIF |
---|
451 | ! |
---|
452 | END SUBROUTINE update_rst |
---|
453 | |
---|
454 | #else |
---|
455 | !!---------------------------------------------------------------------- |
---|
456 | !! Default option Dummy module NO SI3 sea-ice model |
---|
457 | !!---------------------------------------------------------------------- |
---|
458 | #endif |
---|
459 | |
---|
460 | !!====================================================================== |
---|
461 | END MODULE iceupdate |
---|