1 | MODULE sbcmod |
---|
2 | !!====================================================================== |
---|
3 | !! *** MODULE sbcmod *** |
---|
4 | !! Surface module : provide to the ocean its surface boundary condition |
---|
5 | !!====================================================================== |
---|
6 | !! History : 3.0 ! 2006-07 (G. Madec) Original code |
---|
7 | !! 3.1 ! 2008-08 (S. Masson, A. Caubel, E. Maisonnave, G. Madec) coupled interface |
---|
8 | !! 3.3 ! 2010-04 (M. Leclair, G. Madec) Forcing averaged over 2 time steps |
---|
9 | !! 3.3 ! 2010-10 (S. Masson) add diurnal cycle |
---|
10 | !! 3.3 ! 2010-09 (D. Storkey) add ice boundary conditions (BDY) |
---|
11 | !! - ! 2010-11 (G. Madec) ice-ocean stress always computed at each ocean time-step |
---|
12 | !! - ! 2010-10 (J. Chanut, C. Bricaud, G. Madec) add the surface pressure forcing |
---|
13 | !! 3.4 ! 2011-11 (C. Harris) CICE added as an option |
---|
14 | !! 3.5 ! 2012-11 (A. Coward, G. Madec) Rethink of heat, mass and salt surface fluxes |
---|
15 | !! 3.6 ! 2014-11 (P. Mathiot, C. Harris) add ice shelves melting |
---|
16 | !! 4.0 ! 2016-06 (L. Brodeau) new general bulk formulation |
---|
17 | !! 4.0 ! 2019-03 (F. Lemarié & G. Samson) add ABL compatibility (ln_abl=TRUE) |
---|
18 | !! 4.2 ! 2020-12 (G. Madec, E. Clementi) modified wave forcing and coupling |
---|
19 | !!---------------------------------------------------------------------- |
---|
20 | |
---|
21 | !!---------------------------------------------------------------------- |
---|
22 | !! sbc_init : read namsbc namelist |
---|
23 | !! sbc : surface ocean momentum, heat and freshwater boundary conditions |
---|
24 | !! sbc_final : Finalize CICE ice model (if used) |
---|
25 | !!---------------------------------------------------------------------- |
---|
26 | USE oce ! ocean dynamics and tracers |
---|
27 | USE dom_oce ! ocean space and time domain |
---|
28 | USE closea ! closed seas |
---|
29 | USE phycst ! physical constants |
---|
30 | USE sbc_oce ! Surface boundary condition: ocean fields |
---|
31 | USE trc_oce ! shared ocean-passive tracers variables |
---|
32 | USE sbc_ice ! Surface boundary condition: ice fields |
---|
33 | USE sbcdcy ! surface boundary condition: diurnal cycle |
---|
34 | USE sbcssm ! surface boundary condition: sea-surface mean variables |
---|
35 | USE sbcflx ! surface boundary condition: flux formulation |
---|
36 | USE sbcblk ! surface boundary condition: bulk formulation |
---|
37 | USE sbcabl ! atmospheric boundary layer |
---|
38 | USE sbcice_if ! surface boundary condition: ice-if sea-ice model |
---|
39 | #if defined key_si3 |
---|
40 | USE icestp ! surface boundary condition: SI3 sea-ice model |
---|
41 | #endif |
---|
42 | USE sbcice_cice ! surface boundary condition: CICE sea-ice model |
---|
43 | USE sbccpl ! surface boundary condition: coupled formulation |
---|
44 | USE cpl_oasis3 ! OASIS routines for coupling |
---|
45 | USE sbcclo ! surface boundary condition: closed sea correction |
---|
46 | USE sbcssr ! surface boundary condition: sea surface restoring |
---|
47 | USE sbcrnf ! surface boundary condition: runoffs |
---|
48 | USE sbcapr ! surface boundary condition: atmo pressure |
---|
49 | USE sbcfwb ! surface boundary condition: freshwater budget |
---|
50 | USE icbstp ! Icebergs |
---|
51 | USE icb_oce , ONLY : ln_passive_mode ! iceberg interaction mode |
---|
52 | USE traqsr ! active tracers: light penetration |
---|
53 | USE sbcwave ! Wave module |
---|
54 | USE bdy_oce , ONLY: ln_bdy |
---|
55 | USE usrdef_sbc ! user defined: surface boundary condition |
---|
56 | USE closea ! closed sea |
---|
57 | USE lbclnk ! ocean lateral boundary conditions (or mpp link) |
---|
58 | ! |
---|
59 | USE prtctl ! Print control (prt_ctl routine) |
---|
60 | USE iom ! IOM library |
---|
61 | USE in_out_manager ! I/O manager |
---|
62 | USE lib_mpp ! MPP library |
---|
63 | USE timing ! Timing |
---|
64 | USE wet_dry |
---|
65 | USE diu_bulk, ONLY: ln_diurnal_only ! diurnal SST diagnostic |
---|
66 | |
---|
67 | IMPLICIT NONE |
---|
68 | PRIVATE |
---|
69 | |
---|
70 | PUBLIC sbc ! routine called by step.F90 |
---|
71 | PUBLIC sbc_init ! routine called by opa.F90 |
---|
72 | |
---|
73 | INTEGER :: nsbc ! type of surface boundary condition (deduced from namsbc informations) |
---|
74 | !! * Substitutions |
---|
75 | # include "do_loop_substitute.h90" |
---|
76 | !!---------------------------------------------------------------------- |
---|
77 | !! NEMO/OCE 4.0 , NEMO Consortium (2018) |
---|
78 | !! $Id$ |
---|
79 | !! Software governed by the CeCILL license (see ./LICENSE) |
---|
80 | !!---------------------------------------------------------------------- |
---|
81 | CONTAINS |
---|
82 | |
---|
83 | SUBROUTINE sbc_init( Kbb, Kmm, Kaa ) |
---|
84 | !!--------------------------------------------------------------------- |
---|
85 | !! *** ROUTINE sbc_init *** |
---|
86 | !! |
---|
87 | !! ** Purpose : Initialisation of the ocean surface boundary computation |
---|
88 | !! |
---|
89 | !! ** Method : Read the namsbc namelist and set derived parameters |
---|
90 | !! Call init routines for all other SBC modules that have one |
---|
91 | !! |
---|
92 | !! ** Action : - read namsbc parameters |
---|
93 | !! - nsbc: type of sbc |
---|
94 | !!---------------------------------------------------------------------- |
---|
95 | INTEGER, INTENT(in) :: Kbb, Kmm, Kaa ! ocean time level indices |
---|
96 | INTEGER :: ios, icpt ! local integer |
---|
97 | LOGICAL :: ll_purecpl, ll_opa, ll_not_nemo ! local logical |
---|
98 | !! |
---|
99 | NAMELIST/namsbc/ nn_fsbc , & |
---|
100 | & ln_usr , ln_flx , ln_blk , ln_abl, & |
---|
101 | & ln_cpl , ln_mixcpl, nn_components, & |
---|
102 | & nn_ice , ln_ice_embd, & |
---|
103 | & ln_traqsr, ln_dm2dc , & |
---|
104 | & ln_rnf , nn_fwb , ln_ssr , ln_apr_dyn, & |
---|
105 | & ln_wave , nn_lsm |
---|
106 | !!---------------------------------------------------------------------- |
---|
107 | ! |
---|
108 | IF(lwp) THEN |
---|
109 | WRITE(numout,*) |
---|
110 | WRITE(numout,*) 'sbc_init : surface boundary condition setting' |
---|
111 | WRITE(numout,*) '~~~~~~~~ ' |
---|
112 | ENDIF |
---|
113 | ! |
---|
114 | ! !** read Surface Module namelist |
---|
115 | READ ( numnam_ref, namsbc, IOSTAT = ios, ERR = 901) |
---|
116 | 901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc in reference namelist' ) |
---|
117 | READ ( numnam_cfg, namsbc, IOSTAT = ios, ERR = 902 ) |
---|
118 | 902 IF( ios > 0 ) CALL ctl_nam ( ios , 'namsbc in configuration namelist' ) |
---|
119 | IF(lwm) WRITE( numond, namsbc ) |
---|
120 | ! |
---|
121 | #if defined key_mpp_mpi |
---|
122 | ncom_fsbc = nn_fsbc ! make nn_fsbc available for lib_mpp |
---|
123 | #endif |
---|
124 | #if ! defined key_si3 |
---|
125 | IF( nn_ice == 2 ) nn_ice = 0 ! without key key_si3 you cannot use si3... |
---|
126 | #endif |
---|
127 | ! |
---|
128 | ! |
---|
129 | IF(lwp) THEN !* Control print |
---|
130 | WRITE(numout,*) ' Namelist namsbc (partly overwritten with CPP key setting)' |
---|
131 | WRITE(numout,*) ' frequency update of sbc (and ice) nn_fsbc = ', nn_fsbc |
---|
132 | WRITE(numout,*) ' Type of air-sea fluxes : ' |
---|
133 | WRITE(numout,*) ' user defined formulation ln_usr = ', ln_usr |
---|
134 | WRITE(numout,*) ' flux formulation ln_flx = ', ln_flx |
---|
135 | WRITE(numout,*) ' bulk formulation ln_blk = ', ln_blk |
---|
136 | WRITE(numout,*) ' ABL formulation ln_abl = ', ln_abl |
---|
137 | WRITE(numout,*) ' Surface wave (forced or coupled) ln_wave = ', ln_wave |
---|
138 | WRITE(numout,*) ' Type of coupling (Ocean/Ice/Atmosphere) : ' |
---|
139 | WRITE(numout,*) ' ocean-atmosphere coupled formulation ln_cpl = ', ln_cpl |
---|
140 | WRITE(numout,*) ' mixed forced-coupled formulation ln_mixcpl = ', ln_mixcpl |
---|
141 | !!gm lk_oasis is controlled by key_oasis3 ===>>> It shoud be removed from the namelist |
---|
142 | WRITE(numout,*) ' OASIS coupling (with atm or sas) lk_oasis = ', lk_oasis |
---|
143 | WRITE(numout,*) ' components of your executable nn_components = ', nn_components |
---|
144 | WRITE(numout,*) ' Sea-ice : ' |
---|
145 | WRITE(numout,*) ' ice management in the sbc (=0/1/2/3) nn_ice = ', nn_ice |
---|
146 | WRITE(numout,*) ' ice embedded into ocean ln_ice_embd = ', ln_ice_embd |
---|
147 | WRITE(numout,*) ' Misc. options of sbc : ' |
---|
148 | WRITE(numout,*) ' Light penetration in temperature Eq. ln_traqsr = ', ln_traqsr |
---|
149 | WRITE(numout,*) ' daily mean to diurnal cycle qsr ln_dm2dc = ', ln_dm2dc |
---|
150 | WRITE(numout,*) ' Sea Surface Restoring on SST and/or SSS ln_ssr = ', ln_ssr |
---|
151 | WRITE(numout,*) ' FreshWater Budget control (=0/1/2) nn_fwb = ', nn_fwb |
---|
152 | WRITE(numout,*) ' Patm gradient added in ocean & ice Eqs. ln_apr_dyn = ', ln_apr_dyn |
---|
153 | WRITE(numout,*) ' runoff / runoff mouths ln_rnf = ', ln_rnf |
---|
154 | WRITE(numout,*) ' nb of iterations if land-sea-mask applied nn_lsm = ', nn_lsm |
---|
155 | ENDIF |
---|
156 | ! |
---|
157 | IF( .NOT.ln_usr ) THEN ! the model calendar needs some specificities (except in user defined case) |
---|
158 | IF( MOD( rday , rn_Dt ) /= 0. ) CALL ctl_stop( 'the time step must devide the number of second of in a day' ) |
---|
159 | IF( MOD( rday , 2. ) /= 0. ) CALL ctl_stop( 'the number of second of in a day must be an even number' ) |
---|
160 | IF( MOD( rn_Dt , 2. ) /= 0. ) CALL ctl_stop( 'the time step (in second) must be an even number' ) |
---|
161 | ENDIF |
---|
162 | ! !** check option consistency |
---|
163 | ! |
---|
164 | IF(lwp) WRITE(numout,*) !* Single / Multi - executable (NEMO / OPA+SAS) |
---|
165 | SELECT CASE( nn_components ) |
---|
166 | CASE( jp_iam_nemo ) |
---|
167 | IF(lwp) WRITE(numout,*) ' ==>>> NEMO configured as a single executable (i.e. including both OPA and Surface module)' |
---|
168 | CASE( jp_iam_opa ) |
---|
169 | IF(lwp) WRITE(numout,*) ' ==>>> Multi executable configuration. Here, OPA component' |
---|
170 | IF( .NOT.lk_oasis ) CALL ctl_stop( 'sbc_init : OPA-SAS coupled via OASIS, but key_oasis3 disabled' ) |
---|
171 | IF( ln_cpl ) CALL ctl_stop( 'sbc_init : OPA-SAS coupled via OASIS, but ln_cpl = T in OPA' ) |
---|
172 | IF( ln_mixcpl ) CALL ctl_stop( 'sbc_init : OPA-SAS coupled via OASIS, but ln_mixcpl = T in OPA' ) |
---|
173 | CASE( jp_iam_sas ) |
---|
174 | IF(lwp) WRITE(numout,*) ' ==>>> Multi executable configuration. Here, SAS component' |
---|
175 | IF( .NOT.lk_oasis ) CALL ctl_stop( 'sbc_init : OPA-SAS coupled via OASIS, but key_oasis3 disabled' ) |
---|
176 | IF( ln_mixcpl ) CALL ctl_stop( 'sbc_init : OPA-SAS coupled via OASIS, but ln_mixcpl = T in OPA' ) |
---|
177 | CASE DEFAULT |
---|
178 | CALL ctl_stop( 'sbc_init : unsupported value for nn_components' ) |
---|
179 | END SELECT |
---|
180 | ! !* coupled options |
---|
181 | IF( ln_cpl ) THEN |
---|
182 | IF( .NOT. lk_oasis ) CALL ctl_stop( 'sbc_init : coupled mode with an atmosphere model (ln_cpl=T)', & |
---|
183 | & ' required to defined key_oasis3' ) |
---|
184 | ENDIF |
---|
185 | IF( ln_mixcpl ) THEN |
---|
186 | IF( .NOT. lk_oasis ) CALL ctl_stop( 'sbc_init : mixed forced-coupled mode (ln_mixcpl=T) ', & |
---|
187 | & ' required to defined key_oasis3' ) |
---|
188 | IF( .NOT.ln_cpl ) CALL ctl_stop( 'sbc_init : mixed forced-coupled mode (ln_mixcpl=T) requires ln_cpl = T' ) |
---|
189 | IF( nn_components /= jp_iam_nemo ) & |
---|
190 | & CALL ctl_stop( 'sbc_init : the mixed forced-coupled mode (ln_mixcpl=T) ', & |
---|
191 | & ' not yet working with sas-opa coupling via oasis' ) |
---|
192 | ENDIF |
---|
193 | ! !* sea-ice |
---|
194 | SELECT CASE( nn_ice ) |
---|
195 | CASE( 0 ) !- no ice in the domain |
---|
196 | CASE( 1 ) !- Ice-cover climatology ("Ice-if" model) |
---|
197 | CASE( 2 ) !- SI3 ice model |
---|
198 | IF( .NOT.( ln_blk .OR. ln_cpl .OR. ln_abl .OR. ln_usr ) ) & |
---|
199 | & CALL ctl_stop( 'sbc_init : SI3 sea-ice model requires ln_blk or ln_cpl or ln_abl or ln_usr = T' ) |
---|
200 | CASE( 3 ) !- CICE ice model |
---|
201 | IF( .NOT.( ln_blk .OR. ln_cpl .OR. ln_abl .OR. ln_usr ) ) & |
---|
202 | & CALL ctl_stop( 'sbc_init : CICE sea-ice model requires ln_blk or ln_cpl or ln_abl or ln_usr = T' ) |
---|
203 | IF( lk_agrif ) & |
---|
204 | & CALL ctl_stop( 'sbc_init : CICE sea-ice model not currently available with AGRIF' ) |
---|
205 | CASE DEFAULT !- not supported |
---|
206 | END SELECT |
---|
207 | IF( ln_diurnal .AND. .NOT. (ln_blk.OR.ln_abl) ) CALL ctl_stop( "sbc_init: diurnal flux processing only implemented for bulk forcing" ) |
---|
208 | ! |
---|
209 | ! !** allocate and set required variables |
---|
210 | ! |
---|
211 | ! !* allocate sbc arrays |
---|
212 | IF( sbc_oce_alloc() /= 0 ) CALL ctl_stop( 'sbc_init : unable to allocate sbc_oce arrays' ) |
---|
213 | #if ! defined key_si3 && ! defined key_cice |
---|
214 | IF( sbc_ice_alloc() /= 0 ) CALL ctl_stop( 'sbc_init : unable to allocate sbc_ice arrays' ) |
---|
215 | #endif |
---|
216 | ! |
---|
217 | ! |
---|
218 | IF( sbc_ssr_alloc() /= 0 ) CALL ctl_stop( 'STOP', 'sbc_init : unable to allocate sbc_ssr arrays' ) |
---|
219 | IF( .NOT.ln_ssr ) THEN !* Initialize qrp and erp if no restoring |
---|
220 | qrp(:,:) = 0._wp |
---|
221 | erp(:,:) = 0._wp |
---|
222 | ENDIF |
---|
223 | ! |
---|
224 | IF( nn_ice == 0 ) THEN !* No sea-ice in the domain : ice fraction is always zero |
---|
225 | IF( nn_components /= jp_iam_opa ) fr_i(:,:) = 0._wp ! except for OPA in SAS-OPA coupled case |
---|
226 | ENDIF |
---|
227 | ! |
---|
228 | sfx (:,:) = 0._wp !* salt flux due to freezing/melting |
---|
229 | fmmflx(:,:) = 0._wp !* freezing minus melting flux |
---|
230 | cloud_fra(:,:) = pp_cldf !* cloud fraction over sea ice (used in si3) |
---|
231 | |
---|
232 | taum(:,:) = 0._wp !* wind stress module (needed in GLS in case of reduced restart) |
---|
233 | |
---|
234 | ! ! Choice of the Surface Boudary Condition (set nsbc) |
---|
235 | nday_qsr = -1 ! allow initialization at the 1st call !LB: now warm-layer of COARE* calls "sbc_dcy_param" of sbcdcy.F90! |
---|
236 | IF( ln_dm2dc ) THEN !* daily mean to diurnal cycle |
---|
237 | !LB:nday_qsr = -1 ! allow initialization at the 1st call |
---|
238 | IF( .NOT.( ln_flx .OR. ln_blk .OR. ln_abl ) .AND. nn_components /= jp_iam_opa ) & |
---|
239 | & CALL ctl_stop( 'qsr diurnal cycle from daily values requires flux, bulk or abl formulation' ) |
---|
240 | ENDIF |
---|
241 | ! !* Choice of the Surface Boudary Condition |
---|
242 | ! (set nsbc) |
---|
243 | ! |
---|
244 | ll_purecpl = ln_cpl .AND. .NOT.ln_mixcpl |
---|
245 | ll_opa = nn_components == jp_iam_opa |
---|
246 | ll_not_nemo = nn_components /= jp_iam_nemo |
---|
247 | icpt = 0 |
---|
248 | ! |
---|
249 | IF( ln_usr ) THEN ; nsbc = jp_usr ; icpt = icpt + 1 ; ENDIF ! user defined formulation |
---|
250 | IF( ln_flx ) THEN ; nsbc = jp_flx ; icpt = icpt + 1 ; ENDIF ! flux formulation |
---|
251 | IF( ln_blk ) THEN ; nsbc = jp_blk ; icpt = icpt + 1 ; ENDIF ! bulk formulation |
---|
252 | IF( ln_abl ) THEN ; nsbc = jp_abl ; icpt = icpt + 1 ; ENDIF ! ABL formulation |
---|
253 | IF( ll_purecpl ) THEN ; nsbc = jp_purecpl ; icpt = icpt + 1 ; ENDIF ! Pure Coupled formulation |
---|
254 | IF( ll_opa ) THEN ; nsbc = jp_none ; icpt = icpt + 1 ; ENDIF ! opa coupling via SAS module |
---|
255 | ! |
---|
256 | IF( icpt /= 1 ) CALL ctl_stop( 'sbc_init : choose ONE and only ONE sbc option' ) |
---|
257 | ! |
---|
258 | IF(lwp) THEN !- print the choice of surface flux formulation |
---|
259 | WRITE(numout,*) |
---|
260 | SELECT CASE( nsbc ) |
---|
261 | CASE( jp_usr ) ; WRITE(numout,*) ' ==>>> user defined forcing formulation' |
---|
262 | CASE( jp_flx ) ; WRITE(numout,*) ' ==>>> flux formulation' |
---|
263 | CASE( jp_blk ) ; WRITE(numout,*) ' ==>>> bulk formulation' |
---|
264 | CASE( jp_abl ) ; WRITE(numout,*) ' ==>>> ABL formulation' |
---|
265 | CASE( jp_purecpl ) ; WRITE(numout,*) ' ==>>> pure coupled formulation' |
---|
266 | !!gm abusive use of jp_none ?? ===>>> need to be check and changed by adding a jp_sas parameter |
---|
267 | CASE( jp_none ) ; WRITE(numout,*) ' ==>>> OPA coupled to SAS via oasis' |
---|
268 | IF( ln_mixcpl ) WRITE(numout,*) ' + forced-coupled mixed formulation' |
---|
269 | END SELECT |
---|
270 | IF( ll_not_nemo ) WRITE(numout,*) ' + OASIS coupled SAS' |
---|
271 | ENDIF |
---|
272 | ! |
---|
273 | ! !* OASIS initialization |
---|
274 | ! |
---|
275 | IF( lk_oasis ) CALL sbc_cpl_init( nn_ice ) ! Must be done before: (1) first time step |
---|
276 | ! ! (2) the use of nn_fsbc |
---|
277 | ! nn_fsbc initialization if OPA-SAS coupling via OASIS |
---|
278 | ! SAS time-step has to be declared in OASIS (mandatory) -> nn_fsbc has to be modified accordingly |
---|
279 | IF( nn_components /= jp_iam_nemo ) THEN |
---|
280 | IF( nn_components == jp_iam_opa ) nn_fsbc = cpl_freq('O_SFLX') / NINT(rn_Dt) |
---|
281 | IF( nn_components == jp_iam_sas ) nn_fsbc = cpl_freq('I_SFLX') / NINT(rn_Dt) |
---|
282 | ! |
---|
283 | IF(lwp)THEN |
---|
284 | WRITE(numout,*) |
---|
285 | WRITE(numout,*)" OPA-SAS coupled via OASIS : nn_fsbc re-defined from OASIS namcouple ", nn_fsbc |
---|
286 | WRITE(numout,*) |
---|
287 | ENDIF |
---|
288 | ENDIF |
---|
289 | ! |
---|
290 | ! !* check consistency between model timeline and nn_fsbc |
---|
291 | IF( ln_rst_list .OR. nn_stock /= -1 ) THEN ! we will do restart files |
---|
292 | IF( MOD( nitend - nit000 + 1, nn_fsbc) /= 0 ) THEN |
---|
293 | WRITE(ctmp1,*) 'sbc_init : experiment length (', nitend - nit000 + 1, ') is NOT a multiple of nn_fsbc (', nn_fsbc, ')' |
---|
294 | CALL ctl_stop( ctmp1, 'Impossible to properly do model restart' ) |
---|
295 | ENDIF |
---|
296 | IF( .NOT. ln_rst_list .AND. MOD( nn_stock, nn_fsbc) /= 0 ) THEN ! we don't use nn_stock if ln_rst_list |
---|
297 | WRITE(ctmp1,*) 'sbc_init : nn_stock (', nn_stock, ') is NOT a multiple of nn_fsbc (', nn_fsbc, ')' |
---|
298 | CALL ctl_stop( ctmp1, 'Impossible to properly do model restart' ) |
---|
299 | ENDIF |
---|
300 | ENDIF |
---|
301 | ! |
---|
302 | IF( MOD( rday, REAL(nn_fsbc, wp) * rn_Dt ) /= 0 ) & |
---|
303 | & CALL ctl_warn( 'sbc_init : nn_fsbc is NOT a multiple of the number of time steps in a day' ) |
---|
304 | ! |
---|
305 | IF( ln_dm2dc .AND. NINT(rday) / ( nn_fsbc * NINT(rn_Dt) ) < 8 ) & |
---|
306 | & CALL ctl_warn( 'sbc_init : diurnal cycle for qsr: the sampling of the diurnal cycle is too small...' ) |
---|
307 | ! |
---|
308 | |
---|
309 | ! !** associated modules : initialization |
---|
310 | ! |
---|
311 | CALL sbc_ssm_init ( Kbb, Kmm ) ! Sea-surface mean fields initialization |
---|
312 | ! |
---|
313 | IF( l_sbc_clo ) CALL sbc_clo_init ! closed sea surface initialisation |
---|
314 | ! |
---|
315 | IF( ln_blk ) CALL sbc_blk_init ! bulk formulae initialization |
---|
316 | |
---|
317 | IF( ln_abl ) CALL sbc_abl_init ! Atmospheric Boundary Layer (ABL) |
---|
318 | |
---|
319 | IF( ln_ssr ) CALL sbc_ssr_init ! Sea-Surface Restoring initialization |
---|
320 | ! |
---|
321 | ! |
---|
322 | CALL sbc_rnf_init( Kmm ) ! Runof initialization |
---|
323 | ! |
---|
324 | IF( ln_apr_dyn ) CALL sbc_apr_init ! Atmo Pressure Forcing initialization |
---|
325 | ! |
---|
326 | #if defined key_si3 |
---|
327 | IF( lk_agrif .AND. nn_ice == 0 ) THEN ! allocate ice arrays in case agrif + ice-model + no-ice in child grid |
---|
328 | IF( sbc_ice_alloc() /= 0 ) CALL ctl_stop('STOP', 'sbc_ice_alloc : unable to allocate arrays' ) |
---|
329 | ELSEIF( nn_ice == 2 ) THEN |
---|
330 | CALL ice_init( Kbb, Kmm, Kaa ) ! ICE initialization |
---|
331 | ENDIF |
---|
332 | #endif |
---|
333 | IF( nn_ice == 3 ) CALL cice_sbc_init( nsbc, Kbb, Kmm ) ! CICE initialization |
---|
334 | ! |
---|
335 | IF( ln_wave ) THEN |
---|
336 | CALL sbc_wave_init ! surface wave initialisation |
---|
337 | ELSE |
---|
338 | IF(lwp) WRITE(numout,*) |
---|
339 | IF(lwp) WRITE(numout,*) ' No surface waves : all wave related logical set to false' |
---|
340 | ln_sdw = .false. |
---|
341 | ln_stcor = .false. |
---|
342 | ln_cdgw = .false. |
---|
343 | ln_tauoc = .false. |
---|
344 | ln_wave_test = .false. |
---|
345 | ln_charn = .false. |
---|
346 | ln_taw = .false. |
---|
347 | ln_phioc = .false. |
---|
348 | ln_bern_srfc = .false. |
---|
349 | ln_breivikFV_2016 = .false. |
---|
350 | ln_vortex_force = .false. |
---|
351 | ln_stshear = .false. |
---|
352 | ENDIF |
---|
353 | ! |
---|
354 | END SUBROUTINE sbc_init |
---|
355 | |
---|
356 | |
---|
357 | SUBROUTINE sbc( kt, Kbb, Kmm ) |
---|
358 | !!--------------------------------------------------------------------- |
---|
359 | !! *** ROUTINE sbc *** |
---|
360 | !! |
---|
361 | !! ** Purpose : provide at each time-step the ocean surface boundary |
---|
362 | !! condition (momentum, heat and freshwater fluxes) |
---|
363 | !! |
---|
364 | !! ** Method : blah blah to be written ????????? |
---|
365 | !! CAUTION : never mask the surface stress field (tke sbc) |
---|
366 | !! |
---|
367 | !! ** Action : - set the ocean surface boundary condition at before and now |
---|
368 | !! time step, i.e. |
---|
369 | !! utau_b, vtau_b, qns_b, qsr_b, emp_n, sfx_b, qrp_b, erp_b |
---|
370 | !! utau , vtau , qns , qsr , emp , sfx , qrp , erp |
---|
371 | !! - updte the ice fraction : fr_i |
---|
372 | !!---------------------------------------------------------------------- |
---|
373 | INTEGER, INTENT(in) :: kt ! ocean time step |
---|
374 | INTEGER, INTENT(in) :: Kbb, Kmm ! ocean time level indices |
---|
375 | INTEGER :: jj, ji ! dummy loop argument |
---|
376 | ! |
---|
377 | LOGICAL :: ll_sas, ll_opa ! local logical |
---|
378 | ! |
---|
379 | REAL(wp) :: zthscl ! wd tanh scale |
---|
380 | REAL(wp), DIMENSION(jpi,jpj) :: zwdht, zwght ! wd dep over wd limit, wgt |
---|
381 | |
---|
382 | !!--------------------------------------------------------------------- |
---|
383 | ! |
---|
384 | IF( ln_timing ) CALL timing_start('sbc') |
---|
385 | ! |
---|
386 | ! ! ---------------------------------------- ! |
---|
387 | IF( kt /= nit000 ) THEN ! Swap of forcing fields ! |
---|
388 | ! ! ---------------------------------------- ! |
---|
389 | utau_b(:,:) = utau(:,:) ! Swap the ocean forcing fields |
---|
390 | vtau_b(:,:) = vtau(:,:) ! (except at nit000 where before fields |
---|
391 | qns_b (:,:) = qns (:,:) ! are set at the end of the routine) |
---|
392 | emp_b (:,:) = emp (:,:) |
---|
393 | sfx_b (:,:) = sfx (:,:) |
---|
394 | IF( ln_rnf ) THEN |
---|
395 | rnf_b (:,: ) = rnf (:,: ) |
---|
396 | rnf_tsc_b(:,:,:) = rnf_tsc(:,:,:) |
---|
397 | ENDIF |
---|
398 | ! |
---|
399 | ENDIF |
---|
400 | ! ! ---------------------------------------- ! |
---|
401 | ! ! forcing field computation ! |
---|
402 | ! ! ---------------------------------------- ! |
---|
403 | ! |
---|
404 | ll_sas = nn_components == jp_iam_sas ! component flags |
---|
405 | ll_opa = nn_components == jp_iam_opa |
---|
406 | ! |
---|
407 | IF( .NOT.ll_sas ) CALL sbc_ssm ( kt, Kbb, Kmm ) ! mean ocean sea surface variables (sst_m, sss_m, ssu_m, ssv_m) |
---|
408 | ! |
---|
409 | ! !== sbc formulation ==! |
---|
410 | ! |
---|
411 | ! |
---|
412 | SELECT CASE( nsbc ) ! Compute ocean surface boundary condition |
---|
413 | ! ! (i.e. utau,vtau, qns, qsr, emp, sfx) |
---|
414 | CASE( jp_usr ) ; CALL usrdef_sbc_oce( kt, Kbb ) ! user defined formulation |
---|
415 | CASE( jp_flx ) ; CALL sbc_flx ( kt ) ! flux formulation |
---|
416 | CASE( jp_blk ) |
---|
417 | IF( ll_sas ) CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice, Kbb, Kmm ) ! OPA-SAS coupling: SAS receiving fields from OPA |
---|
418 | !!!!!!!!!!! ATTENTION:ln_wave is not only used for oasis coupling !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
---|
419 | IF( ln_wave ) THEN |
---|
420 | IF ( lk_oasis ) CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice, Kbb, Kmm ) ! OPA-wave coupling |
---|
421 | CALL sbc_wave ( kt, Kmm ) |
---|
422 | ENDIF |
---|
423 | CALL sbc_blk ( kt ) ! bulk formulation for the ocean |
---|
424 | ! |
---|
425 | CASE( jp_abl ) |
---|
426 | IF( ll_sas ) CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice, Kbb, Kmm ) ! OPA-SAS coupling: SAS receiving fields from OPA |
---|
427 | CALL sbc_abl ( kt ) ! ABL formulation for the ocean |
---|
428 | ! |
---|
429 | CASE( jp_purecpl ) ; CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice, Kbb, Kmm ) ! pure coupled formulation |
---|
430 | CASE( jp_none ) |
---|
431 | IF( ll_opa ) CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice, Kbb, Kmm ) ! OPA-SAS coupling: OPA receiving fields from SAS |
---|
432 | END SELECT |
---|
433 | ! |
---|
434 | IF( ln_mixcpl ) CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice, Kbb, Kmm ) ! forced-coupled mixed formulation after forcing |
---|
435 | ! |
---|
436 | IF( ln_wave .AND. ln_tauoc ) THEN ! Wave stress reduction |
---|
437 | DO_2D( 0, 0, 0, 0) |
---|
438 | utau(ji,jj) = utau(ji,jj) * ( tauoc_wave(ji,jj) + tauoc_wave(ji-1,jj) ) * 0.5_wp |
---|
439 | vtau(ji,jj) = vtau(ji,jj) * ( tauoc_wave(ji,jj) + tauoc_wave(ji,jj-1) ) * 0.5_wp |
---|
440 | END_2D |
---|
441 | ! |
---|
442 | CALL lbc_lnk( 'sbcwave', utau, 'U', -1. ) |
---|
443 | CALL lbc_lnk( 'sbcwave', vtau, 'V', -1. ) |
---|
444 | ! |
---|
445 | taum(:,:) = taum(:,:)*tauoc_wave(:,:) |
---|
446 | ! |
---|
447 | IF( kt == nit000 ) CALL ctl_warn( 'sbc: You are subtracting the wave stress to the ocean.', & |
---|
448 | & 'If not requested select ln_tauoc=.false.' ) |
---|
449 | ! |
---|
450 | ELSEIF( ln_wave .AND. ln_taw ) THEN ! Wave stress reduction |
---|
451 | utau(:,:) = utau(:,:) - tawx(:,:) + twox(:,:) |
---|
452 | vtau(:,:) = vtau(:,:) - tawy(:,:) + twoy(:,:) |
---|
453 | CALL lbc_lnk( 'sbcwave', utau, 'U', -1. ) |
---|
454 | CALL lbc_lnk( 'sbcwave', vtau, 'V', -1. ) |
---|
455 | ! |
---|
456 | DO_2D( 0, 0, 0, 0) |
---|
457 | taum(ji,jj) = sqrt((.5*(utau(ji-1,jj)+utau(ji,jj)))**2 + (.5*(vtau(ji,jj-1)+vtau(ji,jj)))**2) |
---|
458 | END_2D |
---|
459 | ! |
---|
460 | IF( kt == nit000 ) CALL ctl_warn( 'sbc: You are subtracting the wave stress to the ocean.', & |
---|
461 | & 'If not requested select ln_taw=.false.' ) |
---|
462 | ! |
---|
463 | ENDIF |
---|
464 | CALL lbc_lnk( 'sbcmod', taum(:,:), 'T', 1. ) |
---|
465 | ! |
---|
466 | ! !== Misc. Options ==! |
---|
467 | ! |
---|
468 | SELECT CASE( nn_ice ) ! Update heat and freshwater fluxes over sea-ice areas |
---|
469 | CASE( 1 ) ; CALL sbc_ice_if ( kt, Kbb, Kmm ) ! Ice-cover climatology ("Ice-if" model) |
---|
470 | #if defined key_si3 |
---|
471 | CASE( 2 ) ; CALL ice_stp ( kt, Kbb, Kmm, nsbc ) ! SI3 ice model |
---|
472 | #endif |
---|
473 | CASE( 3 ) ; CALL sbc_ice_cice ( kt, nsbc ) ! CICE ice model |
---|
474 | END SELECT |
---|
475 | |
---|
476 | IF( ln_icebergs ) THEN |
---|
477 | CALL icb_stp( kt ) ! compute icebergs |
---|
478 | ! Icebergs do not melt over the haloes. |
---|
479 | ! So emp values over the haloes are no more consistent with the inner domain values. |
---|
480 | ! A lbc_lnk is therefore needed to ensure reproducibility and restartability. |
---|
481 | ! see ticket #2113 for discussion about this lbc_lnk. |
---|
482 | IF( .NOT. ln_passive_mode ) CALL lbc_lnk( 'sbcmod', emp, 'T', 1.0_wp ) ! ensure restartability with icebergs |
---|
483 | ENDIF |
---|
484 | |
---|
485 | IF( ln_rnf ) CALL sbc_rnf( kt ) ! add runoffs to fresh water fluxes |
---|
486 | |
---|
487 | IF( ln_ssr ) CALL sbc_ssr( kt ) ! add SST/SSS damping term |
---|
488 | |
---|
489 | IF( nn_fwb /= 0 ) CALL sbc_fwb( kt, nn_fwb, nn_fsbc, Kmm ) ! control the freshwater budget |
---|
490 | |
---|
491 | ! Special treatment of freshwater fluxes over closed seas in the model domain |
---|
492 | ! Should not be run if ln_diurnal_only |
---|
493 | IF( l_sbc_clo ) CALL sbc_clo( kt ) |
---|
494 | |
---|
495 | !!$!RBbug do not understand why see ticket 667 |
---|
496 | !!$!clem: it looks like it is necessary for the north fold (in certain circumstances). Don't know why. |
---|
497 | !!$ CALL lbc_lnk( 'sbcmod', emp, 'T', 1.0_wp ) |
---|
498 | IF( ll_wd ) THEN ! If near WAD point limit the flux for now |
---|
499 | zthscl = atanh(rn_wd_sbcfra) ! taper frac default is .999 |
---|
500 | zwdht(:,:) = ssh(:,:,Kmm) + ht_0(:,:) - rn_wdmin1 ! do this calc of water |
---|
501 | ! depth above wd limit once |
---|
502 | WHERE( zwdht(:,:) <= 0.0 ) |
---|
503 | taum(:,:) = 0.0 |
---|
504 | utau(:,:) = 0.0 |
---|
505 | vtau(:,:) = 0.0 |
---|
506 | qns (:,:) = 0.0 |
---|
507 | qsr (:,:) = 0.0 |
---|
508 | emp (:,:) = min(emp(:,:),0.0) !can allow puddles to grow but not shrink |
---|
509 | sfx (:,:) = 0.0 |
---|
510 | END WHERE |
---|
511 | zwght(:,:) = tanh(zthscl*zwdht(:,:)) |
---|
512 | WHERE( zwdht(:,:) > 0.0 .and. zwdht(:,:) < rn_wd_sbcdep ) ! 5 m hard limit here is arbitrary |
---|
513 | qsr (:,:) = qsr(:,:) * zwght(:,:) |
---|
514 | qns (:,:) = qns(:,:) * zwght(:,:) |
---|
515 | taum (:,:) = taum(:,:) * zwght(:,:) |
---|
516 | utau (:,:) = utau(:,:) * zwght(:,:) |
---|
517 | vtau (:,:) = vtau(:,:) * zwght(:,:) |
---|
518 | sfx (:,:) = sfx(:,:) * zwght(:,:) |
---|
519 | emp (:,:) = emp(:,:) * zwght(:,:) |
---|
520 | END WHERE |
---|
521 | ENDIF |
---|
522 | ! |
---|
523 | IF( kt == nit000 ) THEN ! set the forcing field at nit000 - 1 ! |
---|
524 | ! ! ---------------------------------------- ! |
---|
525 | IF( ln_rstart .AND. & !* Restart: read in restart file |
---|
526 | & iom_varid( numror, 'utau_b', ldstop = .FALSE. ) > 0 ) THEN |
---|
527 | IF(lwp) WRITE(numout,*) ' nit000-1 surface forcing fields red in the restart file' |
---|
528 | CALL iom_get( numror, jpdom_auto, 'utau_b', utau_b ) ! before i-stress (U-point) |
---|
529 | CALL iom_get( numror, jpdom_auto, 'vtau_b', vtau_b ) ! before j-stress (V-point) |
---|
530 | CALL iom_get( numror, jpdom_auto, 'qns_b', qns_b ) ! before non solar heat flux (T-point) |
---|
531 | ! The 3D heat content due to qsr forcing is treated in traqsr |
---|
532 | ! CALL iom_get( numror, jpdom_auto, 'qsr_b' , qsr_b ) ! before solar heat flux (T-point) |
---|
533 | CALL iom_get( numror, jpdom_auto, 'emp_b', emp_b ) ! before freshwater flux (T-point) |
---|
534 | ! To ensure restart capability with 3.3x/3.4 restart files !! to be removed in v3.6 |
---|
535 | IF( iom_varid( numror, 'sfx_b', ldstop = .FALSE. ) > 0 ) THEN |
---|
536 | CALL iom_get( numror, jpdom_auto, 'sfx_b', sfx_b ) ! before salt flux (T-point) |
---|
537 | ELSE |
---|
538 | sfx_b (:,:) = sfx(:,:) |
---|
539 | ENDIF |
---|
540 | ELSE !* no restart: set from nit000 values |
---|
541 | IF(lwp) WRITE(numout,*) ' nit000-1 surface forcing fields set to nit000' |
---|
542 | utau_b(:,:) = utau(:,:) |
---|
543 | vtau_b(:,:) = vtau(:,:) |
---|
544 | qns_b (:,:) = qns (:,:) |
---|
545 | emp_b (:,:) = emp (:,:) |
---|
546 | sfx_b (:,:) = sfx (:,:) |
---|
547 | ENDIF |
---|
548 | ENDIF |
---|
549 | ! ! ---------------------------------------- ! |
---|
550 | IF( lrst_oce ) THEN ! Write in the ocean restart file ! |
---|
551 | ! ! ---------------------------------------- ! |
---|
552 | IF(lwp) WRITE(numout,*) |
---|
553 | IF(lwp) WRITE(numout,*) 'sbc : ocean surface forcing fields written in ocean restart file ', & |
---|
554 | & 'at it= ', kt,' date= ', ndastp |
---|
555 | IF(lwp) WRITE(numout,*) '~~~~' |
---|
556 | CALL iom_rstput( kt, nitrst, numrow, 'utau_b' , utau ) |
---|
557 | CALL iom_rstput( kt, nitrst, numrow, 'vtau_b' , vtau ) |
---|
558 | CALL iom_rstput( kt, nitrst, numrow, 'qns_b' , qns ) |
---|
559 | ! The 3D heat content due to qsr forcing is treated in traqsr |
---|
560 | ! CALL iom_rstput( kt, nitrst, numrow, 'qsr_b' , qsr ) |
---|
561 | CALL iom_rstput( kt, nitrst, numrow, 'emp_b' , emp ) |
---|
562 | CALL iom_rstput( kt, nitrst, numrow, 'sfx_b' , sfx ) |
---|
563 | ENDIF |
---|
564 | ! ! ---------------------------------------- ! |
---|
565 | ! ! Outputs and control print ! |
---|
566 | ! ! ---------------------------------------- ! |
---|
567 | IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN |
---|
568 | CALL iom_put( "empmr" , emp - rnf ) ! upward water flux |
---|
569 | CALL iom_put( "empbmr" , emp_b - rnf ) ! before upward water flux ( needed to recalculate the time evolution of ssh in offline ) |
---|
570 | CALL iom_put( "saltflx", sfx ) ! downward salt flux (includes virtual salt flux beneath ice in linear free surface case) |
---|
571 | CALL iom_put( "fmmflx", fmmflx ) ! Freezing-melting water flux |
---|
572 | CALL iom_put( "qt" , qns + qsr ) ! total heat flux |
---|
573 | CALL iom_put( "qns" , qns ) ! solar heat flux |
---|
574 | CALL iom_put( "qsr" , qsr ) ! solar heat flux |
---|
575 | IF( nn_ice > 0 .OR. ll_opa ) CALL iom_put( "ice_cover", fr_i ) ! ice fraction |
---|
576 | CALL iom_put( "taum" , taum ) ! wind stress module |
---|
577 | CALL iom_put( "wspd" , wndm ) ! wind speed module over free ocean or leads in presence of sea-ice |
---|
578 | CALL iom_put( "qrp", qrp ) ! heat flux damping |
---|
579 | CALL iom_put( "erp", erp ) ! freshwater flux damping |
---|
580 | ENDIF |
---|
581 | ! |
---|
582 | IF(sn_cfctl%l_prtctl) THEN ! print mean trends (used for debugging) |
---|
583 | CALL prt_ctl(tab2d_1=fr_i , clinfo1=' fr_i - : ', mask1=tmask ) |
---|
584 | CALL prt_ctl(tab2d_1=(emp-rnf) , clinfo1=' emp-rnf - : ', mask1=tmask ) |
---|
585 | CALL prt_ctl(tab2d_1=(sfx-rnf) , clinfo1=' sfx-rnf - : ', mask1=tmask ) |
---|
586 | CALL prt_ctl(tab2d_1=qns , clinfo1=' qns - : ', mask1=tmask ) |
---|
587 | CALL prt_ctl(tab2d_1=qsr , clinfo1=' qsr - : ', mask1=tmask ) |
---|
588 | CALL prt_ctl(tab3d_1=tmask , clinfo1=' tmask - : ', mask1=tmask, kdim=jpk ) |
---|
589 | CALL prt_ctl(tab3d_1=ts(:,:,:,jp_tem,Kmm), clinfo1=' sst - : ', mask1=tmask, kdim=1 ) |
---|
590 | CALL prt_ctl(tab3d_1=ts(:,:,:,jp_sal,Kmm), clinfo1=' sss - : ', mask1=tmask, kdim=1 ) |
---|
591 | CALL prt_ctl(tab2d_1=utau , clinfo1=' utau - : ', mask1=umask, & |
---|
592 | & tab2d_2=vtau , clinfo2=' vtau - : ', mask2=vmask ) |
---|
593 | ENDIF |
---|
594 | |
---|
595 | IF( kt == nitend ) CALL sbc_final ! Close down surface module if necessary |
---|
596 | ! |
---|
597 | IF( ln_timing ) CALL timing_stop('sbc') |
---|
598 | ! |
---|
599 | END SUBROUTINE sbc |
---|
600 | |
---|
601 | |
---|
602 | SUBROUTINE sbc_final |
---|
603 | !!--------------------------------------------------------------------- |
---|
604 | !! *** ROUTINE sbc_final *** |
---|
605 | !! |
---|
606 | !! ** Purpose : Finalize CICE (if used) |
---|
607 | !!--------------------------------------------------------------------- |
---|
608 | ! |
---|
609 | IF( nn_ice == 3 ) CALL cice_sbc_final |
---|
610 | ! |
---|
611 | END SUBROUTINE sbc_final |
---|
612 | |
---|
613 | !!====================================================================== |
---|
614 | END MODULE sbcmod |
---|