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 | !!---------------------------------------------------------------------- |
---|
17 | |
---|
18 | !!---------------------------------------------------------------------- |
---|
19 | !! sbc_init : read namsbc namelist |
---|
20 | !! sbc : surface ocean momentum, heat and freshwater boundary conditions |
---|
21 | !!---------------------------------------------------------------------- |
---|
22 | USE oce ! ocean dynamics and tracers |
---|
23 | USE dom_oce ! ocean space and time domain |
---|
24 | USE phycst ! physical constants |
---|
25 | USE sbc_oce ! Surface boundary condition: ocean fields |
---|
26 | USE trc_oce ! shared ocean-passive tracers variables |
---|
27 | USE sbc_ice ! Surface boundary condition: ice fields |
---|
28 | USE sbcdcy ! surface boundary condition: diurnal cycle |
---|
29 | USE sbcssm ! surface boundary condition: sea-surface mean variables |
---|
30 | USE sbcapr ! surface boundary condition: atmospheric pressure |
---|
31 | USE sbcana ! surface boundary condition: analytical formulation |
---|
32 | USE sbcflx ! surface boundary condition: flux formulation |
---|
33 | USE sbcblk_clio ! surface boundary condition: bulk formulation : CLIO |
---|
34 | USE sbcblk_core ! surface boundary condition: bulk formulation : CORE |
---|
35 | USE sbcblk_mfs ! surface boundary condition: bulk formulation : MFS |
---|
36 | USE sbcice_if ! surface boundary condition: ice-if sea-ice model |
---|
37 | USE sbcice_lim ! surface boundary condition: LIM 3.0 sea-ice model |
---|
38 | USE sbcice_lim_2 ! surface boundary condition: LIM 2.0 sea-ice model |
---|
39 | USE sbcice_cice ! surface boundary condition: CICE sea-ice model |
---|
40 | USE sbccpl ! surface boundary condition: coupled florulation |
---|
41 | USE cpl_oasis3 ! OASIS routines for coupling |
---|
42 | USE sbcssr ! surface boundary condition: sea surface restoring |
---|
43 | USE sbcflx_adj ! surface boundary condition: sea surface flux adjustment |
---|
44 | USE sbcrnf ! surface boundary condition: runoffs |
---|
45 | USE sbcisf ! surface boundary condition: ice shelf |
---|
46 | USE sbcfwb ! surface boundary condition: freshwater budget |
---|
47 | USE closea ! closed sea |
---|
48 | USE icbstp ! Icebergs! |
---|
49 | |
---|
50 | USE prtctl ! Print control (prt_ctl routine) |
---|
51 | USE iom ! IOM library |
---|
52 | USE in_out_manager ! I/O manager |
---|
53 | USE lib_mpp ! MPP library |
---|
54 | USE timing ! Timing |
---|
55 | USE sbcwave ! Wave module |
---|
56 | USE bdy_par ! Require lk_bdy |
---|
57 | |
---|
58 | IMPLICIT NONE |
---|
59 | PRIVATE |
---|
60 | |
---|
61 | PUBLIC sbc ! routine called by step.F90 |
---|
62 | PUBLIC sbc_init ! routine called by opa.F90 |
---|
63 | |
---|
64 | INTEGER :: nsbc ! type of surface boundary condition (deduced from namsbc informations) |
---|
65 | |
---|
66 | !! * Substitutions |
---|
67 | # include "domzgr_substitute.h90" |
---|
68 | !!---------------------------------------------------------------------- |
---|
69 | !! NEMO/OPA 4.0 , NEMO-consortium (2011) |
---|
70 | !! $Id: sbcmod.F90 5501 2015-06-29 10:08:15Z deazer $ |
---|
71 | !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) |
---|
72 | !!---------------------------------------------------------------------- |
---|
73 | CONTAINS |
---|
74 | |
---|
75 | SUBROUTINE sbc_init |
---|
76 | !!--------------------------------------------------------------------- |
---|
77 | !! *** ROUTINE sbc_init *** |
---|
78 | !! |
---|
79 | !! ** Purpose : Initialisation of the ocean surface boundary computation |
---|
80 | !! |
---|
81 | !! ** Method : Read the namsbc namelist and set derived parameters |
---|
82 | !! Call init routines for all other SBC modules that have one |
---|
83 | !! |
---|
84 | !! ** Action : - read namsbc parameters |
---|
85 | !! - nsbc: type of sbc |
---|
86 | !!---------------------------------------------------------------------- |
---|
87 | INTEGER :: icpt ! local integer |
---|
88 | !! |
---|
89 | NAMELIST/namsbc/ nn_fsbc , ln_ana , ln_flx, ln_blk_clio, ln_blk_core, ln_mixcpl, & |
---|
90 | & ln_blk_mfs, ln_apr_dyn, nn_ice, nn_ice_embd, ln_dm2dc , ln_rnf , & |
---|
91 | & ln_ssr , nn_isf , nn_fwb, ln_cdgw , ln_wave , ln_sdw , & |
---|
92 | & nn_lsm , nn_limflx , nn_components, ln_cpl, ln_flx_adj |
---|
93 | INTEGER :: ios |
---|
94 | INTEGER :: ierr, ierr0, ierr1, ierr2, ierr3, jpm |
---|
95 | LOGICAL :: ll_purecpl |
---|
96 | !!---------------------------------------------------------------------- |
---|
97 | |
---|
98 | IF(lwp) THEN |
---|
99 | WRITE(numout,*) |
---|
100 | WRITE(numout,*) 'sbc_init : surface boundary condition setting' |
---|
101 | WRITE(numout,*) '~~~~~~~~ ' |
---|
102 | ENDIF |
---|
103 | |
---|
104 | REWIND( numnam_ref ) ! Namelist namsbc in reference namelist : Surface boundary |
---|
105 | READ ( numnam_ref, namsbc, IOSTAT = ios, ERR = 901) |
---|
106 | 901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc in reference namelist', lwp ) |
---|
107 | |
---|
108 | REWIND( numnam_cfg ) ! Namelist namsbc in configuration namelist : Parameters of the run |
---|
109 | READ ( numnam_cfg, namsbc, IOSTAT = ios, ERR = 902 ) |
---|
110 | 902 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc in configuration namelist', lwp ) |
---|
111 | IF(lwm) WRITE ( numond, namsbc ) |
---|
112 | |
---|
113 | ! ! overwrite namelist parameter using CPP key information |
---|
114 | IF( Agrif_Root() ) THEN ! AGRIF zoom |
---|
115 | IF( lk_lim2 ) nn_ice = 2 |
---|
116 | IF( lk_lim3 ) nn_ice = 3 |
---|
117 | IF( lk_cice ) nn_ice = 4 |
---|
118 | ENDIF |
---|
119 | IF( cp_cfg == 'gyre' ) THEN ! GYRE configuration |
---|
120 | ln_ana = .TRUE. |
---|
121 | nn_ice = 0 |
---|
122 | ENDIF |
---|
123 | |
---|
124 | IF(lwp) THEN ! Control print |
---|
125 | WRITE(numout,*) ' Namelist namsbc (partly overwritten with CPP key setting)' |
---|
126 | WRITE(numout,*) ' frequency update of sbc (and ice) nn_fsbc = ', nn_fsbc |
---|
127 | WRITE(numout,*) ' Type of sbc : ' |
---|
128 | WRITE(numout,*) ' analytical formulation ln_ana = ', ln_ana |
---|
129 | WRITE(numout,*) ' flux formulation ln_flx = ', ln_flx |
---|
130 | WRITE(numout,*) ' CLIO bulk formulation ln_blk_clio = ', ln_blk_clio |
---|
131 | WRITE(numout,*) ' CORE bulk formulation ln_blk_core = ', ln_blk_core |
---|
132 | WRITE(numout,*) ' MFS bulk formulation ln_blk_mfs = ', ln_blk_mfs |
---|
133 | WRITE(numout,*) ' ocean-atmosphere coupled formulation ln_cpl = ', ln_cpl |
---|
134 | WRITE(numout,*) ' forced-coupled mixed formulation ln_mixcpl = ', ln_mixcpl |
---|
135 | WRITE(numout,*) ' OASIS coupling (with atm or sas) lk_oasis = ', lk_oasis |
---|
136 | WRITE(numout,*) ' components of your executable nn_components = ', nn_components |
---|
137 | WRITE(numout,*) ' Multicategory heat flux formulation (LIM3) nn_limflx = ', nn_limflx |
---|
138 | WRITE(numout,*) ' Misc. options of sbc : ' |
---|
139 | WRITE(numout,*) ' Patm gradient added in ocean & ice Eqs. ln_apr_dyn = ', ln_apr_dyn |
---|
140 | WRITE(numout,*) ' ice management in the sbc (=0/1/2/3) nn_ice = ', nn_ice |
---|
141 | WRITE(numout,*) ' ice-ocean embedded/levitating (=0/1/2) nn_ice_embd = ', nn_ice_embd |
---|
142 | WRITE(numout,*) ' daily mean to diurnal cycle qsr ln_dm2dc = ', ln_dm2dc |
---|
143 | WRITE(numout,*) ' runoff / runoff mouths ln_rnf = ', ln_rnf |
---|
144 | WRITE(numout,*) ' iceshelf formulation nn_isf = ', nn_isf |
---|
145 | WRITE(numout,*) ' Sea Surface Restoring on SST and/or SSS ln_ssr = ', ln_ssr |
---|
146 | WRITE(numout,*) ' Sea Surface Flux adjustment on heat and/or freshwater ln_flx_adj = ', ln_flx_adj |
---|
147 | WRITE(numout,*) ' FreshWater Budget control (=0/1/2) nn_fwb = ', nn_fwb |
---|
148 | WRITE(numout,*) ' closed sea (=0/1) (set in namdom) nn_closea = ', nn_closea |
---|
149 | WRITE(numout,*) ' n. of iterations if land-sea-mask applied nn_lsm = ', nn_lsm |
---|
150 | ENDIF |
---|
151 | |
---|
152 | ! LIM3 Multi-category heat flux formulation |
---|
153 | SELECT CASE ( nn_limflx) |
---|
154 | CASE ( -1 ) |
---|
155 | IF(lwp) WRITE(numout,*) ' Use of per-category fluxes (nn_limflx = -1) ' |
---|
156 | CASE ( 0 ) |
---|
157 | IF(lwp) WRITE(numout,*) ' Average per-category fluxes (nn_limflx = 0) ' |
---|
158 | CASE ( 1 ) |
---|
159 | IF(lwp) WRITE(numout,*) ' Average then redistribute per-category fluxes (nn_limflx = 1) ' |
---|
160 | CASE ( 2 ) |
---|
161 | IF(lwp) WRITE(numout,*) ' Redistribute a single flux over categories (nn_limflx = 2) ' |
---|
162 | END SELECT |
---|
163 | ! |
---|
164 | IF ( nn_components /= jp_iam_nemo .AND. .NOT. lk_oasis ) & |
---|
165 | & CALL ctl_stop( 'STOP', 'sbc_init : OPA-SAS coupled via OASIS, but key_oasis3 disabled' ) |
---|
166 | IF ( nn_components == jp_iam_opa .AND. ln_cpl ) & |
---|
167 | & CALL ctl_stop( 'STOP', 'sbc_init : OPA-SAS coupled via OASIS, but ln_cpl = T in OPA' ) |
---|
168 | IF ( nn_components == jp_iam_opa .AND. ln_mixcpl ) & |
---|
169 | & CALL ctl_stop( 'STOP', 'sbc_init : OPA-SAS coupled via OASIS, but ln_mixcpl = T in OPA' ) |
---|
170 | IF ( ln_cpl .AND. .NOT. lk_oasis ) & |
---|
171 | & CALL ctl_stop( 'STOP', 'sbc_init : OASIS-coupled atmosphere model, but key_oasis3 disabled' ) |
---|
172 | IF( ln_mixcpl .AND. .NOT. lk_oasis ) & |
---|
173 | & CALL ctl_stop( 'the forced-coupled mixed mode (ln_mixcpl) requires the cpp key key_oasis3' ) |
---|
174 | IF( ln_mixcpl .AND. .NOT. ln_cpl ) & |
---|
175 | & CALL ctl_stop( 'the forced-coupled mixed mode (ln_mixcpl) requires ln_cpl = T' ) |
---|
176 | IF( ln_mixcpl .AND. nn_components /= jp_iam_nemo ) & |
---|
177 | & CALL ctl_stop( 'the forced-coupled mixed mode (ln_mixcpl) is not yet working with sas-opa coupling via oasis' ) |
---|
178 | |
---|
179 | ! ! allocate sbc arrays |
---|
180 | IF( sbc_oce_alloc() /= 0 ) CALL ctl_stop( 'STOP', 'sbc_init : unable to allocate sbc_oce arrays' ) |
---|
181 | |
---|
182 | ! ! Checks: |
---|
183 | IF( nn_isf .EQ. 0 ) THEN ! no specific treatment in vicinity of ice shelf |
---|
184 | IF( sbc_isf_alloc() /= 0 ) CALL ctl_stop( 'STOP', 'sbc_init : unable to allocate sbc_isf arrays' ) |
---|
185 | fwfisf (:,:) = 0.0_wp |
---|
186 | fwfisf_b(:,:) = 0.0_wp |
---|
187 | END IF |
---|
188 | IF( nn_ice == 0 .AND. nn_components /= jp_iam_opa ) fr_i(:,:) = 0.e0 ! no ice in the domain, ice fraction is always zero |
---|
189 | |
---|
190 | sfx(:,:) = 0.0_wp ! the salt flux due to freezing/melting will be computed (i.e. will be non-zero) |
---|
191 | ! only if sea-ice is present |
---|
192 | |
---|
193 | fmmflx(:,:) = 0.0_wp ! freezing-melting array initialisation |
---|
194 | |
---|
195 | taum(:,:) = 0.0_wp ! Initialise taum for use in gls in case of reduced restart |
---|
196 | |
---|
197 | ! ! restartability |
---|
198 | IF( ( nn_ice == 2 .OR. nn_ice ==3 ) .AND. .NOT.( ln_blk_clio .OR. ln_blk_core .OR. ln_cpl ) ) & |
---|
199 | & CALL ctl_stop( 'LIM sea-ice model requires a bulk formulation or coupled configuration' ) |
---|
200 | IF( nn_ice == 4 .AND. .NOT.( ln_blk_core .OR. ln_cpl ) ) & |
---|
201 | & CALL ctl_stop( 'CICE sea-ice model requires ln_blk_core or ln_cpl' ) |
---|
202 | IF( nn_ice == 4 .AND. lk_agrif ) & |
---|
203 | & CALL ctl_stop( 'CICE sea-ice model not currently available with AGRIF' ) |
---|
204 | IF( ( nn_ice == 3 .OR. nn_ice == 4 ) .AND. nn_ice_embd == 0 ) & |
---|
205 | & CALL ctl_stop( 'LIM3 and CICE sea-ice models require nn_ice_embd = 1 or 2' ) |
---|
206 | IF( ( nn_ice /= 3 ) .AND. ( nn_limflx >= 0 ) ) & |
---|
207 | & WRITE(numout,*) 'The nn_limflx>=0 option has no effect if sea ice model is not LIM3' |
---|
208 | IF( ( nn_ice == 3 ) .AND. ( ln_cpl ) .AND. ( ( nn_limflx == -1 ) .OR. ( nn_limflx == 1 ) ) ) & |
---|
209 | & CALL ctl_stop( 'The chosen nn_limflx for LIM3 in coupled mode must be 0 or 2' ) |
---|
210 | IF( ( nn_ice == 3 ) .AND. ( .NOT. ln_cpl ) .AND. ( nn_limflx == 2 ) ) & |
---|
211 | & CALL ctl_stop( 'The chosen nn_limflx for LIM3 in forced mode cannot be 2' ) |
---|
212 | |
---|
213 | IF( ln_dm2dc ) nday_qsr = -1 ! initialisation flag |
---|
214 | |
---|
215 | IF( ln_dm2dc .AND. .NOT.( ln_flx .OR. ln_blk_core ) .AND. nn_components /= jp_iam_opa ) & |
---|
216 | & CALL ctl_stop( 'diurnal cycle into qsr field from daily values requires a flux or core-bulk formulation' ) |
---|
217 | |
---|
218 | IF ( ln_wave ) THEN |
---|
219 | !Activated wave module but neither drag nor stokes drift activated |
---|
220 | IF ( .NOT.(ln_cdgw .OR. ln_sdw) ) THEN |
---|
221 | CALL ctl_warn( 'Ask for wave coupling but nor drag coefficient (ln_cdgw=F) neither stokes drift activated (ln_sdw=F)' ) |
---|
222 | !drag coefficient read from wave model definable only with mfs bulk formulae and core |
---|
223 | ELSEIF (ln_cdgw .AND. .NOT.(ln_blk_mfs .OR. ln_blk_core) ) THEN |
---|
224 | CALL ctl_stop( 'drag coefficient read from wave model definable only with mfs bulk formulae and core') |
---|
225 | ENDIF |
---|
226 | ELSE |
---|
227 | IF ( ln_cdgw .OR. ln_sdw ) & |
---|
228 | & CALL ctl_stop('Not Activated Wave Module (ln_wave=F) but & |
---|
229 | & asked coupling with drag coefficient (ln_cdgw =T) or Stokes drift (ln_sdw=T) ') |
---|
230 | ENDIF |
---|
231 | ! ! Choice of the Surface Boudary Condition (set nsbc) |
---|
232 | ll_purecpl = ln_cpl .AND. .NOT. ln_mixcpl |
---|
233 | ! |
---|
234 | icpt = 0 |
---|
235 | IF( ln_ana ) THEN ; nsbc = jp_ana ; icpt = icpt + 1 ; ENDIF ! analytical formulation |
---|
236 | IF( ln_flx ) THEN ; nsbc = jp_flx ; icpt = icpt + 1 ; ENDIF ! flux formulation |
---|
237 | IF( ln_blk_clio ) THEN ; nsbc = jp_clio ; icpt = icpt + 1 ; ENDIF ! CLIO bulk formulation |
---|
238 | IF( ln_blk_core ) THEN ; nsbc = jp_core ; icpt = icpt + 1 ; ENDIF ! CORE bulk formulation |
---|
239 | IF( ln_blk_mfs ) THEN ; nsbc = jp_mfs ; icpt = icpt + 1 ; ENDIF ! MFS bulk formulation |
---|
240 | IF( ll_purecpl ) THEN ; nsbc = jp_purecpl ; icpt = icpt + 1 ; ENDIF ! Pure Coupled formulation |
---|
241 | IF( cp_cfg == 'gyre') THEN ; nsbc = jp_gyre ; ENDIF ! GYRE analytical formulation |
---|
242 | IF( nn_components == jp_iam_opa ) & |
---|
243 | & THEN ; nsbc = jp_none ; icpt = icpt + 1 ; ENDIF ! opa coupling via SAS module |
---|
244 | IF( lk_esopa ) nsbc = jp_esopa ! esopa test, ALL formulations |
---|
245 | ! |
---|
246 | IF( icpt /= 1 .AND. .NOT.lk_esopa ) THEN |
---|
247 | WRITE(numout,*) |
---|
248 | WRITE(numout,*) ' E R R O R in setting the sbc, one and only one namelist/CPP key option ' |
---|
249 | WRITE(numout,*) ' must be choosen. You choose ', icpt, ' option(s)' |
---|
250 | WRITE(numout,*) ' We stop' |
---|
251 | nstop = nstop + 1 |
---|
252 | ENDIF |
---|
253 | IF(lwp) THEN |
---|
254 | WRITE(numout,*) |
---|
255 | IF( nsbc == jp_esopa ) WRITE(numout,*) ' ESOPA test All surface boundary conditions' |
---|
256 | IF( nsbc == jp_gyre ) WRITE(numout,*) ' GYRE analytical formulation' |
---|
257 | IF( nsbc == jp_ana ) WRITE(numout,*) ' analytical formulation' |
---|
258 | IF( nsbc == jp_flx ) WRITE(numout,*) ' flux formulation' |
---|
259 | IF( nsbc == jp_clio ) WRITE(numout,*) ' CLIO bulk formulation' |
---|
260 | IF( nsbc == jp_core ) WRITE(numout,*) ' CORE bulk formulation' |
---|
261 | IF( nsbc == jp_purecpl ) WRITE(numout,*) ' pure coupled formulation' |
---|
262 | IF( nsbc == jp_mfs ) WRITE(numout,*) ' MFS Bulk formulation' |
---|
263 | IF( nsbc == jp_none ) WRITE(numout,*) ' OPA coupled to SAS via oasis' |
---|
264 | IF( ln_mixcpl ) WRITE(numout,*) ' + forced-coupled mixed formulation' |
---|
265 | IF( nn_components/= jp_iam_nemo ) & |
---|
266 | & WRITE(numout,*) ' + OASIS coupled SAS' |
---|
267 | ENDIF |
---|
268 | ! |
---|
269 | IF( lk_oasis ) CALL sbc_cpl_init (nn_ice) ! OASIS initialisation. must be done before: (1) first time step |
---|
270 | ! ! (2) the use of nn_fsbc |
---|
271 | |
---|
272 | ! nn_fsbc initialization if OPA-SAS coupling via OASIS |
---|
273 | ! sas model time step has to be declared in OASIS (mandatory) -> nn_fsbc has to be modified accordingly |
---|
274 | IF ( nn_components /= jp_iam_nemo ) THEN |
---|
275 | |
---|
276 | IF ( nn_components == jp_iam_opa ) nn_fsbc = cpl_freq('O_SFLX') / NINT(rdt) |
---|
277 | IF ( nn_components == jp_iam_sas ) nn_fsbc = cpl_freq('I_SFLX') / NINT(rdt) |
---|
278 | ! |
---|
279 | IF(lwp)THEN |
---|
280 | WRITE(numout,*) |
---|
281 | WRITE(numout,*)" OPA-SAS coupled via OASIS : nn_fsbc re-defined from OASIS namcouple ", nn_fsbc |
---|
282 | WRITE(numout,*) |
---|
283 | ENDIF |
---|
284 | ENDIF |
---|
285 | |
---|
286 | IF( MOD( nitend - nit000 + 1, nn_fsbc) /= 0 .OR. & |
---|
287 | MOD( nstock , nn_fsbc) /= 0 ) THEN |
---|
288 | WRITE(ctmp1,*) 'experiment length (', nitend - nit000 + 1, ') or nstock (', nstock, & |
---|
289 | & ' is NOT a multiple of nn_fsbc (', nn_fsbc, ')' |
---|
290 | CALL ctl_stop( ctmp1, 'Impossible to properly do model restart' ) |
---|
291 | ENDIF |
---|
292 | ! |
---|
293 | IF( MOD( rday, REAL(nn_fsbc, wp) * rdt ) /= 0 ) & |
---|
294 | & CALL ctl_warn( 'nn_fsbc is NOT a multiple of the number of time steps in a day' ) |
---|
295 | ! |
---|
296 | IF( ln_dm2dc .AND. ( ( NINT(rday) / ( nn_fsbc * NINT(rdt) ) ) < 8 ) ) & |
---|
297 | & CALL ctl_warn( 'diurnal cycle for qsr: the sampling of the diurnal cycle is too small...' ) |
---|
298 | |
---|
299 | CALL sbc_ssm_init ! Sea-surface mean fields initialisation |
---|
300 | ! |
---|
301 | ! KY 12/11/2015 |
---|
302 | IF( ln_flx_adj ) CALL sbc_flx_adj_init ! Sea-Surface Flux adjustment |
---|
303 | ! |
---|
304 | IF( ln_ssr ) CALL sbc_ssr_init ! Sea-Surface Restoring initialisation |
---|
305 | ! |
---|
306 | CALL sbc_rnf_init ! Runof initialisation |
---|
307 | ! |
---|
308 | IF( nn_ice == 3 ) CALL sbc_lim_init ! LIM3 initialisation |
---|
309 | |
---|
310 | IF( nn_ice == 4 ) CALL cice_sbc_init( nsbc ) ! CICE initialisation |
---|
311 | |
---|
312 | END SUBROUTINE sbc_init |
---|
313 | |
---|
314 | |
---|
315 | SUBROUTINE sbc( kt ) |
---|
316 | !!--------------------------------------------------------------------- |
---|
317 | !! *** ROUTINE sbc *** |
---|
318 | !! |
---|
319 | !! ** Purpose : provide at each time-step the ocean surface boundary |
---|
320 | !! condition (momentum, heat and freshwater fluxes) |
---|
321 | !! |
---|
322 | !! ** Method : blah blah to be written ????????? |
---|
323 | !! CAUTION : never mask the surface stress field (tke sbc) |
---|
324 | !! |
---|
325 | !! ** Action : - set the ocean surface boundary condition at before and now |
---|
326 | !! time step, i.e. |
---|
327 | !! utau_b, vtau_b, qns_b, qsr_b, emp_n, sfx_b, qrp_b, erp_b |
---|
328 | !! utau , vtau , qns , qsr , emp , sfx , qrp , erp |
---|
329 | !! - updte the ice fraction : fr_i |
---|
330 | !!---------------------------------------------------------------------- |
---|
331 | INTEGER, INTENT(in) :: kt ! ocean time step |
---|
332 | !!--------------------------------------------------------------------- |
---|
333 | ! |
---|
334 | IF( nn_timing == 1 ) CALL timing_start('sbc') |
---|
335 | ! |
---|
336 | ! ! ---------------------------------------- ! |
---|
337 | IF( kt /= nit000 ) THEN ! Swap of forcing fields ! |
---|
338 | ! ! ---------------------------------------- ! |
---|
339 | utau_b(:,:) = utau(:,:) ! Swap the ocean forcing fields |
---|
340 | vtau_b(:,:) = vtau(:,:) ! (except at nit000 where before fields |
---|
341 | qns_b (:,:) = qns (:,:) ! are set at the end of the routine) |
---|
342 | ! The 3D heat content due to qsr forcing is treated in traqsr |
---|
343 | ! qsr_b (:,:) = qsr (:,:) |
---|
344 | emp_b(:,:) = emp(:,:) |
---|
345 | sfx_b(:,:) = sfx(:,:) |
---|
346 | ENDIF |
---|
347 | ! ! ---------------------------------------- ! |
---|
348 | ! ! forcing field computation ! |
---|
349 | ! ! ---------------------------------------- ! |
---|
350 | ! |
---|
351 | IF ( .NOT. lk_bdy ) then |
---|
352 | IF( ln_apr_dyn ) CALL sbc_apr( kt ) ! atmospheric pressure provided at kt+0.5*nn_fsbc |
---|
353 | ENDIF |
---|
354 | ! (caution called before sbc_ssm) |
---|
355 | ! |
---|
356 | IF( nn_components /= jp_iam_sas ) CALL sbc_ssm( kt ) ! ocean sea surface variables (sst_m, sss_m, ssu_m, ssv_m) |
---|
357 | ! ! averaged over nf_sbc time-step |
---|
358 | |
---|
359 | IF (ln_wave) CALL sbc_wave( kt ) |
---|
360 | !== sbc formulation ==! |
---|
361 | |
---|
362 | SELECT CASE( nsbc ) ! Compute ocean surface boundary condition |
---|
363 | ! ! (i.e. utau,vtau, qns, qsr, emp, sfx) |
---|
364 | CASE( jp_gyre ) ; CALL sbc_gyre ( kt ) ! analytical formulation : GYRE configuration |
---|
365 | CASE( jp_ana ) ; CALL sbc_ana ( kt ) ! analytical formulation : uniform sbc |
---|
366 | CASE( jp_flx ) ; CALL sbc_flx ( kt ) ! flux formulation |
---|
367 | CASE( jp_clio ) ; CALL sbc_blk_clio( kt ) ! bulk formulation : CLIO for the ocean |
---|
368 | CASE( jp_core ) |
---|
369 | IF( nn_components == jp_iam_sas ) & |
---|
370 | & CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice ) ! OPA-SAS coupling: SAS receiving fields from OPA |
---|
371 | CALL sbc_blk_core( kt ) ! bulk formulation : CORE for the ocean |
---|
372 | ! from oce: sea surface variables (sst_m, sss_m, ssu_m, ssv_m) |
---|
373 | CASE( jp_purecpl ) ; CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice ) ! pure coupled formulation |
---|
374 | ! |
---|
375 | CASE( jp_mfs ) ; CALL sbc_blk_mfs ( kt ) ! bulk formulation : MFS for the ocean |
---|
376 | CASE( jp_none ) |
---|
377 | IF( nn_components == jp_iam_opa ) & |
---|
378 | CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice ) ! OPA-SAS coupling: OPA receiving fields from SAS |
---|
379 | CASE( jp_esopa ) |
---|
380 | CALL sbc_ana ( kt ) ! ESOPA, test ALL the formulations |
---|
381 | CALL sbc_gyre ( kt ) ! |
---|
382 | CALL sbc_flx ( kt ) ! |
---|
383 | CALL sbc_blk_clio( kt ) ! |
---|
384 | CALL sbc_blk_core( kt ) ! |
---|
385 | CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice ) ! |
---|
386 | END SELECT |
---|
387 | |
---|
388 | IF( ln_mixcpl ) CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice ) ! forced-coupled mixed formulation after forcing |
---|
389 | |
---|
390 | |
---|
391 | ! !== Misc. Options ==! |
---|
392 | |
---|
393 | SELECT CASE( nn_ice ) ! Update heat and freshwater fluxes over sea-ice areas |
---|
394 | CASE( 1 ) ; CALL sbc_ice_if ( kt ) ! Ice-cover climatology ("Ice-if" model) |
---|
395 | CASE( 2 ) ; CALL sbc_ice_lim_2( kt, nsbc ) ! LIM-2 ice model |
---|
396 | CASE( 3 ) ; CALL sbc_ice_lim ( kt, nsbc ) ! LIM-3 ice model |
---|
397 | CASE( 4 ) ; CALL sbc_ice_cice ( kt, nsbc ) ! CICE ice model |
---|
398 | END SELECT |
---|
399 | |
---|
400 | IF( ln_icebergs ) CALL icb_stp( kt ) ! compute icebergs |
---|
401 | |
---|
402 | IF( nn_isf /= 0 ) CALL sbc_isf( kt ) ! compute iceshelves |
---|
403 | |
---|
404 | IF( ln_rnf ) CALL sbc_rnf( kt ) ! add runoffs to fresh water fluxes |
---|
405 | |
---|
406 | ! KY 12/11/2015 |
---|
407 | IF( ln_flx_adj ) CALL sbc_flx_adj( kt ) ! add flux adjustment term |
---|
408 | |
---|
409 | IF( ln_ssr ) CALL sbc_ssr( kt ) ! add SST/SSS damping term |
---|
410 | |
---|
411 | IF( nn_fwb /= 0 ) CALL sbc_fwb( kt, nn_fwb, nn_fsbc ) ! control the freshwater budget |
---|
412 | |
---|
413 | IF( nn_closea == 1 ) CALL sbc_clo( kt ) ! treatment of closed sea in the model domain |
---|
414 | ! ! (update freshwater fluxes) |
---|
415 | !RBbug do not understand why see ticket 667 |
---|
416 | !clem: it looks like it is necessary for the north fold (in certain circumstances). Don't know why. |
---|
417 | CALL lbc_lnk( emp, 'T', 1. ) |
---|
418 | ! |
---|
419 | IF( kt == nit000 ) THEN ! set the forcing field at nit000 - 1 ! |
---|
420 | ! ! ---------------------------------------- ! |
---|
421 | IF( ln_rstart .AND. & !* Restart: read in restart file |
---|
422 | & iom_varid( numror, 'utau_b', ldstop = .FALSE. ) > 0 ) THEN |
---|
423 | IF(lwp) WRITE(numout,*) ' nit000-1 surface forcing fields red in the restart file' |
---|
424 | CALL iom_get( numror, jpdom_autoglo, 'utau_b', utau_b ) ! before i-stress (U-point) |
---|
425 | CALL iom_get( numror, jpdom_autoglo, 'vtau_b', vtau_b ) ! before j-stress (V-point) |
---|
426 | CALL iom_get( numror, jpdom_autoglo, 'qns_b' , qns_b ) ! before non solar heat flux (T-point) |
---|
427 | ! The 3D heat content due to qsr forcing is treated in traqsr |
---|
428 | ! CALL iom_get( numror, jpdom_autoglo, 'qsr_b' , qsr_b ) ! before solar heat flux (T-point) |
---|
429 | CALL iom_get( numror, jpdom_autoglo, 'emp_b', emp_b ) ! before freshwater flux (T-point) |
---|
430 | ! To ensure restart capability with 3.3x/3.4 restart files !! to be removed in v3.6 |
---|
431 | IF( iom_varid( numror, 'sfx_b', ldstop = .FALSE. ) > 0 ) THEN |
---|
432 | CALL iom_get( numror, jpdom_autoglo, 'sfx_b', sfx_b ) ! before salt flux (T-point) |
---|
433 | ELSE |
---|
434 | sfx_b (:,:) = sfx(:,:) |
---|
435 | ENDIF |
---|
436 | ELSE !* no restart: set from nit000 values |
---|
437 | IF(lwp) WRITE(numout,*) ' nit000-1 surface forcing fields set to nit000' |
---|
438 | utau_b(:,:) = utau(:,:) |
---|
439 | vtau_b(:,:) = vtau(:,:) |
---|
440 | qns_b (:,:) = qns (:,:) |
---|
441 | emp_b (:,:) = emp(:,:) |
---|
442 | sfx_b (:,:) = sfx(:,:) |
---|
443 | ENDIF |
---|
444 | ENDIF |
---|
445 | ! ! ---------------------------------------- ! |
---|
446 | IF( lrst_oce ) THEN ! Write in the ocean restart file ! |
---|
447 | ! ! ---------------------------------------- ! |
---|
448 | IF(lwp) WRITE(numout,*) |
---|
449 | IF(lwp) WRITE(numout,*) 'sbc : ocean surface forcing fields written in ocean restart file ', & |
---|
450 | & 'at it= ', kt,' date= ', ndastp |
---|
451 | IF(lwp) WRITE(numout,*) '~~~~' |
---|
452 | CALL iom_rstput( kt, nitrst, numrow, 'utau_b' , utau ) |
---|
453 | CALL iom_rstput( kt, nitrst, numrow, 'vtau_b' , vtau ) |
---|
454 | CALL iom_rstput( kt, nitrst, numrow, 'qns_b' , qns ) |
---|
455 | ! The 3D heat content due to qsr forcing is treated in traqsr |
---|
456 | ! CALL iom_rstput( kt, nitrst, numrow, 'qsr_b' , qsr ) |
---|
457 | CALL iom_rstput( kt, nitrst, numrow, 'emp_b' , emp ) |
---|
458 | CALL iom_rstput( kt, nitrst, numrow, 'sfx_b' , sfx ) |
---|
459 | ENDIF |
---|
460 | |
---|
461 | ! ! ---------------------------------------- ! |
---|
462 | ! ! Outputs and control print ! |
---|
463 | ! ! ---------------------------------------- ! |
---|
464 | IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN |
---|
465 | CALL iom_put( "empmr" , emp - rnf ) ! upward water flux |
---|
466 | CALL iom_put( "saltflx", sfx ) ! downward salt flux |
---|
467 | ! (includes virtual salt flux beneath ice |
---|
468 | ! in linear free surface case) |
---|
469 | CALL iom_put( "fmmflx", fmmflx ) ! Freezing-melting water flux |
---|
470 | CALL iom_put( "qt" , qns + qsr ) ! total heat flux |
---|
471 | CALL iom_put( "qns" , qns ) ! solar heat flux |
---|
472 | CALL iom_put( "qsr" , qsr ) ! solar heat flux |
---|
473 | IF( nn_ice > 0 .OR. nn_components == jp_iam_opa ) CALL iom_put( "ice_cover", fr_i ) ! ice fraction |
---|
474 | CALL iom_put( "taum" , taum ) ! wind stress module |
---|
475 | CALL iom_put( "wspd" , wndm ) ! wind speed module over free ocean or leads in presence of sea-ice |
---|
476 | ENDIF |
---|
477 | ! |
---|
478 | CALL iom_put( "utau", utau ) ! i-wind stress (stress can be updated at |
---|
479 | CALL iom_put( "vtau", vtau ) ! j-wind stress each time step in sea-ice) |
---|
480 | ! |
---|
481 | IF(ln_ctl) THEN ! print mean trends (used for debugging) |
---|
482 | CALL prt_ctl(tab2d_1=fr_i , clinfo1=' fr_i - : ', mask1=tmask, ovlap=1 ) |
---|
483 | CALL prt_ctl(tab2d_1=(emp-rnf + fwfisf), clinfo1=' emp-rnf - : ', mask1=tmask, ovlap=1 ) |
---|
484 | CALL prt_ctl(tab2d_1=(sfx-rnf + fwfisf), clinfo1=' sfx-rnf - : ', mask1=tmask, ovlap=1 ) |
---|
485 | CALL prt_ctl(tab2d_1=qns , clinfo1=' qns - : ', mask1=tmask, ovlap=1 ) |
---|
486 | CALL prt_ctl(tab2d_1=qsr , clinfo1=' qsr - : ', mask1=tmask, ovlap=1 ) |
---|
487 | CALL prt_ctl(tab3d_1=tmask , clinfo1=' tmask - : ', mask1=tmask, ovlap=1, kdim=jpk ) |
---|
488 | CALL prt_ctl(tab3d_1=tsn(:,:,:,jp_tem), clinfo1=' sst - : ', mask1=tmask, ovlap=1, kdim=1 ) |
---|
489 | CALL prt_ctl(tab3d_1=tsn(:,:,:,jp_sal), clinfo1=' sss - : ', mask1=tmask, ovlap=1, kdim=1 ) |
---|
490 | CALL prt_ctl(tab2d_1=utau , clinfo1=' utau - : ', mask1=umask, & |
---|
491 | & tab2d_2=vtau , clinfo2=' vtau - : ', mask2=vmask, ovlap=1 ) |
---|
492 | ENDIF |
---|
493 | |
---|
494 | IF( kt == nitend ) CALL sbc_final ! Close down surface module if necessary |
---|
495 | ! |
---|
496 | IF( nn_timing == 1 ) CALL timing_stop('sbc') |
---|
497 | ! |
---|
498 | END SUBROUTINE sbc |
---|
499 | |
---|
500 | |
---|
501 | SUBROUTINE sbc_final |
---|
502 | !!--------------------------------------------------------------------- |
---|
503 | !! *** ROUTINE sbc_final *** |
---|
504 | !! |
---|
505 | !! ** Purpose : Finalize CICE (if used) |
---|
506 | !!--------------------------------------------------------------------- |
---|
507 | ! |
---|
508 | IF( nn_ice == 4 ) CALL cice_sbc_final |
---|
509 | ! |
---|
510 | END SUBROUTINE sbc_final |
---|
511 | |
---|
512 | !!====================================================================== |
---|
513 | END MODULE sbcmod |
---|