1 | MODULE iceforcing |
---|
2 | !!====================================================================== |
---|
3 | !! *** MODULE iceforcing *** |
---|
4 | !! Sea-Ice : air-ice forcing fields |
---|
5 | !!===================================================================== |
---|
6 | !! History : 4.0 ! 2017-08 (C. Rousset) Original code |
---|
7 | !!---------------------------------------------------------------------- |
---|
8 | #if defined key_lim3 |
---|
9 | !!---------------------------------------------------------------------- |
---|
10 | !! 'key_lim3' : ESIM sea-ice model |
---|
11 | !!---------------------------------------------------------------------- |
---|
12 | USE oce ! ocean dynamics and tracers |
---|
13 | USE dom_oce ! ocean space and time domain |
---|
14 | USE ice ! sea-ice: variables |
---|
15 | USE sbc_oce ! Surface boundary condition: ocean fields |
---|
16 | USE sbc_ice ! Surface boundary condition: ice fields |
---|
17 | USE usrdef_sbc ! Surface boundary condition: user defined |
---|
18 | USE sbcblk ! Surface boundary condition: bulk |
---|
19 | USE sbccpl ! Surface boundary condition: coupled interface |
---|
20 | USE icealb ! sea-ice: albedo |
---|
21 | ! |
---|
22 | USE in_out_manager ! I/O manager |
---|
23 | USE iom ! I/O manager library |
---|
24 | USE lib_mpp ! MPP library |
---|
25 | USE lib_fortran ! fortran utilities (glob_sum + no signed zero) |
---|
26 | USE lbclnk ! lateral boundary conditions (or mpp links) |
---|
27 | USE timing ! Timing |
---|
28 | |
---|
29 | IMPLICIT NONE |
---|
30 | PRIVATE |
---|
31 | |
---|
32 | PUBLIC ice_forcing_tau ! called by icestp.F90 |
---|
33 | PUBLIC ice_forcing_flx ! called by icestp.F90 |
---|
34 | PUBLIC ice_forcing_init ! called by icestp.F90 |
---|
35 | |
---|
36 | !! * Substitutions |
---|
37 | # include "vectopt_loop_substitute.h90" |
---|
38 | !!---------------------------------------------------------------------- |
---|
39 | !! NEMO/ICE 4.0 , UCL NEMO Consortium (2017) |
---|
40 | !! $Id: icestp.F90 8319 2017-07-11 15:00:44Z clem $ |
---|
41 | !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) |
---|
42 | !!---------------------------------------------------------------------- |
---|
43 | CONTAINS |
---|
44 | |
---|
45 | SUBROUTINE ice_forcing_tau( kt, ksbc, utau_ice, vtau_ice ) |
---|
46 | !!------------------------------------------------------------------- |
---|
47 | !! *** ROUTINE ice_forcing_tau *** |
---|
48 | !! |
---|
49 | !! ** Purpose : provide surface boundary condition for sea ice (momentum) |
---|
50 | !! |
---|
51 | !! ** Action : It provides the following fields: |
---|
52 | !! utau_ice, vtau_ice : surface ice stress (U- & V-points) [N/m2] |
---|
53 | !!------------------------------------------------------------------- |
---|
54 | INTEGER, INTENT(in) :: kt ! ocean time step |
---|
55 | INTEGER, INTENT(in) :: ksbc ! type of sbc flux ( 1 = user defined formulation, |
---|
56 | ! 3 = bulk formulation, |
---|
57 | ! 4 = Pure Coupled formulation) |
---|
58 | REAL(wp), DIMENSION(jpi,jpj), INTENT(out) :: utau_ice, vtau_ice |
---|
59 | !! |
---|
60 | INTEGER :: ji, jj ! dummy loop index |
---|
61 | REAL(wp), DIMENSION(jpi,jpj) :: zutau_ice, zvtau_ice |
---|
62 | !!------------------------------------------------------------------- |
---|
63 | |
---|
64 | IF( nn_timing == 1 ) CALL timing_start('ice_forcing') |
---|
65 | |
---|
66 | IF( kt == nit000 .AND. lwp ) THEN |
---|
67 | WRITE(numout,*) |
---|
68 | WRITE(numout,*)'ice_forcing_tau: Surface boundary condition for sea ice (momentum)' |
---|
69 | WRITE(numout,*)'~~~~~~~~~~~~~~~' |
---|
70 | ENDIF |
---|
71 | |
---|
72 | SELECT CASE( ksbc ) |
---|
73 | CASE( jp_usr ) ; CALL usrdef_sbc_ice_tau( kt ) ! user defined formulation |
---|
74 | CASE( jp_blk ) ; CALL blk_ice_tau ! Bulk formulation |
---|
75 | CASE( jp_purecpl ) ; CALL sbc_cpl_ice_tau( utau_ice , vtau_ice ) ! Coupled formulation |
---|
76 | END SELECT |
---|
77 | |
---|
78 | IF( ln_mixcpl) THEN ! Case of a mixed Bulk/Coupled formulation |
---|
79 | CALL sbc_cpl_ice_tau( zutau_ice , zvtau_ice ) |
---|
80 | DO jj = 2, jpjm1 |
---|
81 | DO ji = 2, jpim1 |
---|
82 | utau_ice(ji,jj) = utau_ice(ji,jj) * xcplmask(ji,jj,0) + zutau_ice(ji,jj) * ( 1. - xcplmask(ji,jj,0) ) |
---|
83 | vtau_ice(ji,jj) = vtau_ice(ji,jj) * xcplmask(ji,jj,0) + zvtau_ice(ji,jj) * ( 1. - xcplmask(ji,jj,0) ) |
---|
84 | END DO |
---|
85 | END DO |
---|
86 | CALL lbc_lnk_multi( utau_ice, 'U', -1., vtau_ice, 'V', -1. ) |
---|
87 | ENDIF |
---|
88 | |
---|
89 | IF( nn_timing == 1 ) CALL timing_stop('ice_forcing') |
---|
90 | ! |
---|
91 | END SUBROUTINE ice_forcing_tau |
---|
92 | |
---|
93 | |
---|
94 | SUBROUTINE ice_forcing_flx( kt, ksbc ) |
---|
95 | !!------------------------------------------------------------------- |
---|
96 | !! *** ROUTINE ice_forcing_flx *** |
---|
97 | !! |
---|
98 | !! ** Purpose : provide surface boundary condition for sea ice (flux) |
---|
99 | !! |
---|
100 | !! ** Action : It provides the following fields used in sea ice model: |
---|
101 | !! emp_oce , emp_ice = E-P over ocean and sea ice [Kg/m2/s] |
---|
102 | !! sprecip = solid precipitation [Kg/m2/s] |
---|
103 | !! evap_ice = sublimation [Kg/m2/s] |
---|
104 | !! qsr_tot , qns_tot = solar & non solar heat flux (total) [W/m2] |
---|
105 | !! qsr_ice , qns_ice = solar & non solar heat flux over ice [W/m2] |
---|
106 | !! dqns_ice = non solar heat sensistivity [W/m2] |
---|
107 | !! qemp_oce, qemp_ice, qprec_ice, qevap_ice = sensible heat (associated with evap & precip) [W/m2] |
---|
108 | !! + some fields that are not used outside this module: |
---|
109 | !! qla_ice = latent heat flux over ice [W/m2] |
---|
110 | !! dqla_ice = latent heat sensistivity [W/m2] |
---|
111 | !! tprecip = total precipitation [Kg/m2/s] |
---|
112 | !! alb_ice = albedo above sea ice |
---|
113 | !!------------------------------------------------------------------- |
---|
114 | INTEGER, INTENT(in) :: kt ! ocean time step |
---|
115 | INTEGER, INTENT(in) :: ksbc ! flux formulation (user defined, bulk or Pure Coupled) |
---|
116 | ! |
---|
117 | INTEGER :: ji, jj, jl ! dummy loop index |
---|
118 | REAL(wp), DIMENSION(jpi,jpj,jpl) :: zalb_os, zalb_cs ! ice albedo under overcast/clear sky |
---|
119 | REAL(wp), DIMENSION(jpi,jpj) :: zalb ! 2D workspace |
---|
120 | !!-------------------------------------------------------------------- |
---|
121 | ! |
---|
122 | IF( nn_timing == 1 ) CALL timing_start('ice_forcing_flx') |
---|
123 | |
---|
124 | IF( kt == nit000 .AND. lwp ) THEN |
---|
125 | WRITE(numout,*) |
---|
126 | WRITE(numout,*)'ice_forcing_flx: Surface boundary condition for sea ice (flux)' |
---|
127 | WRITE(numout,*)'~~~~~~~~~~~~~~~' |
---|
128 | ENDIF |
---|
129 | |
---|
130 | ! --- cloud-sky and overcast-sky ice albedos --- ! |
---|
131 | CALL ice_alb( t_su, h_i, h_s, ln_pnd_alb, a_ip_frac, h_ip, zalb_cs, zalb_os ) |
---|
132 | |
---|
133 | ! albedo depends on cloud fraction because of non-linear spectral effects |
---|
134 | !!gm cldf_ice is a real, DOCTOR naming rule: start with cd means CHARACTER passed in argument ! |
---|
135 | alb_ice(:,:,:) = ( 1. - cldf_ice ) * zalb_cs(:,:,:) + cldf_ice * zalb_os(:,:,:) |
---|
136 | ! |
---|
137 | ! |
---|
138 | SELECT CASE( ksbc ) !== fluxes over sea ice ==! |
---|
139 | ! |
---|
140 | CASE( jp_usr ) !--- user defined formulation |
---|
141 | CALL usrdef_sbc_ice_flx( kt, h_s, h_i ) |
---|
142 | CASE( jp_blk ) !--- bulk formulation |
---|
143 | CALL blk_ice_flx ( t_su, h_s, h_i, alb_ice ) ! |
---|
144 | IF( ln_mixcpl ) CALL sbc_cpl_ice_flx( picefr=at_i_b, palbi=alb_ice, psst=sst_m, pist=t_su, phs=h_s, phi=h_i ) |
---|
145 | IF( nn_flxdist /= -1 ) CALL ice_flx_dist ( t_su, alb_ice, qns_ice, qsr_ice, dqns_ice, evap_ice, devap_ice, nn_flxdist ) |
---|
146 | SELECT CASE( nice_jules ) |
---|
147 | CASE( np_jules_ACTIVE ) ! compute conduction flux and surface temperature (as in Jules surface module) |
---|
148 | CALL blk_ice_qcn ( nn_monocat, t_su, t_bo, h_s, h_i ) |
---|
149 | END SELECT |
---|
150 | CASE ( jp_purecpl ) !--- coupled formulation |
---|
151 | CALL sbc_cpl_ice_flx( picefr=at_i_b, palbi=alb_ice, psst=sst_m, pist=t_su, phs=h_s, phi=h_i ) |
---|
152 | IF( nn_flxdist /= -1 ) CALL ice_flx_dist ( t_su, alb_ice, qns_ice, qsr_ice, dqns_ice, evap_ice, devap_ice, nn_flxdist ) |
---|
153 | END SELECT |
---|
154 | |
---|
155 | !--- output ice albedo and surface albedo ---! |
---|
156 | IF( iom_use('icealb') ) THEN |
---|
157 | WHERE( at_i_b <= epsi06 ) ; zalb(:,:) = rn_alb_oce |
---|
158 | ELSEWHERE ; zalb(:,:) = SUM( alb_ice * a_i_b, dim=3 ) / at_i_b |
---|
159 | END WHERE |
---|
160 | CALL iom_put( "icealb" , zalb(:,:) ) |
---|
161 | ENDIF |
---|
162 | IF( iom_use('albedo') ) THEN |
---|
163 | zalb(:,:) = SUM( alb_ice * a_i_b, dim=3 ) + rn_alb_oce * ( 1._wp - at_i_b ) |
---|
164 | CALL iom_put( "albedo" , zalb(:,:) ) |
---|
165 | ENDIF |
---|
166 | ! |
---|
167 | IF( nn_timing == 1 ) CALL timing_stop('ice_forcing_flx') |
---|
168 | ! |
---|
169 | END SUBROUTINE ice_forcing_flx |
---|
170 | |
---|
171 | |
---|
172 | SUBROUTINE ice_flx_dist( ptn_ice, palb_ice, pqns_ice, pqsr_ice, pdqn_ice, pevap_ice, pdevap_ice, k_iceflx ) |
---|
173 | !!------------------------------------------------------------------- |
---|
174 | !! *** ROUTINE ice_flx_dist *** |
---|
175 | !! |
---|
176 | !! ** Purpose : update the ice surface boundary condition by averaging |
---|
177 | !! and/or redistributing fluxes on ice categories |
---|
178 | !! |
---|
179 | !! ** Method : average then redistribute |
---|
180 | !! |
---|
181 | !! ** Action : depends on k_iceflx |
---|
182 | !! = -1 Do nothing (needs N(cat) fluxes) |
---|
183 | !! = 0 Average N(cat) fluxes then apply the average over the N(cat) ice |
---|
184 | !! = 1 Average N(cat) fluxes then redistribute over the N(cat) ice |
---|
185 | !! using T-ice and albedo sensitivity |
---|
186 | !! = 2 Redistribute a single flux over categories |
---|
187 | !!------------------------------------------------------------------- |
---|
188 | INTEGER , INTENT(in ) :: k_iceflx ! redistributor |
---|
189 | REAL(wp), DIMENSION(:,:,:), INTENT(in ) :: ptn_ice ! ice surface temperature |
---|
190 | REAL(wp), DIMENSION(:,:,:), INTENT(in ) :: palb_ice ! ice albedo |
---|
191 | REAL(wp), DIMENSION(:,:,:), INTENT(inout) :: pqns_ice ! non solar flux |
---|
192 | REAL(wp), DIMENSION(:,:,:), INTENT(inout) :: pqsr_ice ! net solar flux |
---|
193 | REAL(wp), DIMENSION(:,:,:), INTENT(inout) :: pdqn_ice ! non solar flux sensitivity |
---|
194 | REAL(wp), DIMENSION(:,:,:), INTENT(inout) :: pevap_ice ! sublimation |
---|
195 | REAL(wp), DIMENSION(:,:,:), INTENT(inout) :: pdevap_ice ! sublimation sensitivity |
---|
196 | ! |
---|
197 | INTEGER :: jl ! dummy loop index |
---|
198 | ! |
---|
199 | REAL(wp), DIMENSION(jpi,jpj) :: z1_at_i ! inverse of concentration |
---|
200 | ! |
---|
201 | REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: z_qsr_m ! Mean solar heat flux over all categories |
---|
202 | REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: z_qns_m ! Mean non solar heat flux over all categories |
---|
203 | REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: z_evap_m ! Mean sublimation over all categories |
---|
204 | REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: z_dqn_m ! Mean d(qns)/dT over all categories |
---|
205 | REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: z_devap_m ! Mean d(evap)/dT over all categories |
---|
206 | REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: zalb_m ! Mean albedo over all categories |
---|
207 | REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: ztem_m ! Mean temperature over all categories |
---|
208 | !!---------------------------------------------------------------------- |
---|
209 | ! |
---|
210 | WHERE ( at_i (:,:) > 0._wp ) ; z1_at_i(:,:) = 1._wp / at_i (:,:) |
---|
211 | ELSEWHERE ; z1_at_i(:,:) = 0._wp |
---|
212 | END WHERE |
---|
213 | |
---|
214 | SELECT CASE( k_iceflx ) !== averaged on all ice categories ==! |
---|
215 | ! |
---|
216 | CASE( 0 , 1 ) |
---|
217 | ! |
---|
218 | ALLOCATE( z_qns_m(jpi,jpj), z_qsr_m(jpi,jpj), z_dqn_m(jpi,jpj), z_evap_m(jpi,jpj), z_devap_m(jpi,jpj) ) |
---|
219 | ! |
---|
220 | z_qns_m (:,:) = SUM( a_i(:,:,:) * pqns_ice (:,:,:) , dim=3 ) * z1_at_i(:,:) |
---|
221 | z_qsr_m (:,:) = SUM( a_i(:,:,:) * pqsr_ice (:,:,:) , dim=3 ) * z1_at_i(:,:) |
---|
222 | z_dqn_m (:,:) = SUM( a_i(:,:,:) * pdqn_ice (:,:,:) , dim=3 ) * z1_at_i(:,:) |
---|
223 | z_evap_m (:,:) = SUM( a_i(:,:,:) * pevap_ice (:,:,:) , dim=3 ) * z1_at_i(:,:) |
---|
224 | z_devap_m(:,:) = SUM( a_i(:,:,:) * pdevap_ice(:,:,:) , dim=3 ) * z1_at_i(:,:) |
---|
225 | DO jl = 1, jpl |
---|
226 | pqns_ice (:,:,jl) = z_qns_m (:,:) |
---|
227 | pqsr_ice (:,:,jl) = z_qsr_m (:,:) |
---|
228 | pdqn_ice (:,:,jl) = z_dqn_m (:,:) |
---|
229 | pevap_ice (:,:,jl) = z_evap_m(:,:) |
---|
230 | pdevap_ice(:,:,jl) = z_devap_m(:,:) |
---|
231 | END DO |
---|
232 | ! |
---|
233 | DEALLOCATE( z_qns_m, z_qsr_m, z_dqn_m, z_evap_m, z_devap_m ) |
---|
234 | ! |
---|
235 | END SELECT |
---|
236 | ! |
---|
237 | SELECT CASE( k_iceflx ) !== redistribution on all ice categories ==! |
---|
238 | ! |
---|
239 | CASE( 1 , 2 ) |
---|
240 | ! |
---|
241 | ALLOCATE( zalb_m(jpi,jpj), ztem_m(jpi,jpj) ) |
---|
242 | ! |
---|
243 | zalb_m(:,:) = SUM( a_i(:,:,:) * palb_ice(:,:,:) , dim=3 ) * z1_at_i(:,:) |
---|
244 | ztem_m(:,:) = SUM( a_i(:,:,:) * ptn_ice (:,:,:) , dim=3 ) * z1_at_i(:,:) |
---|
245 | DO jl = 1, jpl |
---|
246 | pqns_ice (:,:,jl) = pqns_ice (:,:,jl) + pdqn_ice (:,:,jl) * ( ptn_ice(:,:,jl) - ztem_m(:,:) ) |
---|
247 | pevap_ice(:,:,jl) = pevap_ice(:,:,jl) + pdevap_ice(:,:,jl) * ( ptn_ice(:,:,jl) - ztem_m(:,:) ) |
---|
248 | pqsr_ice (:,:,jl) = pqsr_ice (:,:,jl) * ( 1._wp - palb_ice(:,:,jl) ) / ( 1._wp - zalb_m(:,:) ) |
---|
249 | END DO |
---|
250 | ! |
---|
251 | DEALLOCATE( zalb_m, ztem_m ) |
---|
252 | ! |
---|
253 | END SELECT |
---|
254 | ! |
---|
255 | END SUBROUTINE ice_flx_dist |
---|
256 | |
---|
257 | SUBROUTINE ice_forcing_init |
---|
258 | !!------------------------------------------------------------------- |
---|
259 | !! *** ROUTINE ice_forcing_init *** |
---|
260 | !! |
---|
261 | !! ** Purpose : Physical constants and parameters linked to the ice |
---|
262 | !! dynamics |
---|
263 | !! |
---|
264 | !! ** Method : Read the namforcing namelist and check the ice-dynamic |
---|
265 | !! parameter values called at the first timestep (nit000) |
---|
266 | !! |
---|
267 | !! ** input : Namelist namforcing |
---|
268 | !!------------------------------------------------------------------- |
---|
269 | INTEGER :: ios, ioptio ! Local integer output status for namelist read |
---|
270 | !! |
---|
271 | NAMELIST/namforcing/ rn_cio, rn_blow_s, nn_flxdist, nice_jules |
---|
272 | !!------------------------------------------------------------------- |
---|
273 | ! |
---|
274 | REWIND( numnam_ice_ref ) ! Namelist namforcing in reference namelist : Ice dynamics |
---|
275 | READ ( numnam_ice_ref, namforcing, IOSTAT = ios, ERR = 901) |
---|
276 | 901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namforcing in reference namelist', lwp ) |
---|
277 | ! |
---|
278 | REWIND( numnam_ice_cfg ) ! Namelist namforcing in configuration namelist : Ice dynamics |
---|
279 | READ ( numnam_ice_cfg, namforcing, IOSTAT = ios, ERR = 902 ) |
---|
280 | 902 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namforcing in configuration namelist', lwp ) |
---|
281 | IF(lwm) WRITE ( numoni, namforcing ) |
---|
282 | ! |
---|
283 | IF(lwp) THEN ! control print |
---|
284 | WRITE(numout,*) |
---|
285 | WRITE(numout,*) 'ice_forcing_init: ice parameters for ice dynamics ' |
---|
286 | WRITE(numout,*) '~~~~~~~~~~~~~~~' |
---|
287 | WRITE(numout,*) ' Namelist namforcing:' |
---|
288 | WRITE(numout,*) ' drag coefficient for oceanic stress rn_cio = ', rn_cio |
---|
289 | WRITE(numout,*) ' coefficient for ice-lead partition of snowfall rn_blow_s = ', rn_blow_s |
---|
290 | WRITE(numout,*) ' Multicategory heat flux formulation nn_flxdist = ', nn_flxdist |
---|
291 | WRITE(numout,*) ' Jules coupling (0=no, 1=emulated, 2=active) nice_jules = ', nice_jules |
---|
292 | ENDIF |
---|
293 | ! |
---|
294 | IF(lwp) WRITE(numout,*) |
---|
295 | SELECT CASE( nn_flxdist ) ! ESIM Multi-category heat flux formulation |
---|
296 | CASE( -1 ) |
---|
297 | IF(lwp) WRITE(numout,*) ' ESIM: use per-category fluxes (nn_flxdist = -1) ' |
---|
298 | CASE( 0 ) |
---|
299 | IF(lwp) WRITE(numout,*) ' ESIM: use average per-category fluxes (nn_flxdist = 0) ' |
---|
300 | CASE( 1 ) |
---|
301 | IF(lwp) WRITE(numout,*) ' ESIM: use average then redistribute per-category fluxes (nn_flxdist = 1) ' |
---|
302 | IF( ln_cpl ) CALL ctl_stop( 'ice_thd_init: the chosen nn_flxdist for ESIM in coupled mode must be /=1' ) |
---|
303 | CASE( 2 ) |
---|
304 | IF(lwp) WRITE(numout,*) ' ESIM: Redistribute a single flux over categories (nn_flxdist = 2) ' |
---|
305 | IF( .NOT. ln_cpl ) CALL ctl_stop( 'ice_thd_init: the chosen nn_flxdist for ESIM in forced mode must be /=2' ) |
---|
306 | CASE DEFAULT |
---|
307 | CALL ctl_stop( 'ice_thd_init: ESIM option, nn_flxdist, should be between -1 and 2' ) |
---|
308 | END SELECT |
---|
309 | ! |
---|
310 | END SUBROUTINE ice_forcing_init |
---|
311 | |
---|
312 | #else |
---|
313 | !!---------------------------------------------------------------------- |
---|
314 | !! Default option : Empty module NO ESIM sea-ice model |
---|
315 | !!---------------------------------------------------------------------- |
---|
316 | #endif |
---|
317 | |
---|
318 | !!====================================================================== |
---|
319 | END MODULE iceforcing |
---|