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, E. Maisonnave, G. Madec) coupled interface |
---|
8 | !! 3.3 ! 2010-04 (M. Leclair, G. Madec) Forcing averaged over 2 time steps |
---|
9 | !!---------------------------------------------------------------------- |
---|
10 | |
---|
11 | !!---------------------------------------------------------------------- |
---|
12 | !! sbc_init : read namsbc namelist |
---|
13 | !! sbc : surface ocean momentum, heat and freshwater boundary conditions |
---|
14 | !!---------------------------------------------------------------------- |
---|
15 | USE oce ! ocean dynamics and tracers |
---|
16 | USE dom_oce ! ocean space and time domain |
---|
17 | USE phycst ! physical constants |
---|
18 | |
---|
19 | USE sbc_oce ! Surface boundary condition: ocean fields |
---|
20 | USE sbc_ice ! Surface boundary condition: ice fields |
---|
21 | USE sbcssm ! surface boundary condition: sea-surface mean variables |
---|
22 | USE sbcana ! surface boundary condition: analytical formulation |
---|
23 | USE sbcflx ! surface boundary condition: flux formulation |
---|
24 | USE sbcblk_clio ! surface boundary condition: bulk formulation : CLIO |
---|
25 | USE sbcblk_core ! surface boundary condition: bulk formulation : CORE |
---|
26 | USE sbcice_if ! surface boundary condition: ice-if sea-ice model |
---|
27 | USE sbcice_lim ! surface boundary condition: LIM 3.0 sea-ice model |
---|
28 | USE sbcice_lim_2 ! surface boundary condition: LIM 2.0 sea-ice model |
---|
29 | USE sbccpl ! surface boundary condition: coupled florulation |
---|
30 | USE cpl_oasis3, ONLY:lk_cpl ! are we in coupled mode? |
---|
31 | USE sbcssr ! surface boundary condition: sea surface restoring |
---|
32 | USE sbcrnf ! surface boundary condition: runoffs |
---|
33 | USE sbcfwb ! surface boundary condition: freshwater budget |
---|
34 | USE closea ! closed sea |
---|
35 | |
---|
36 | USE prtctl ! Print control (prt_ctl routine) |
---|
37 | USE restart ! ocean restart |
---|
38 | USE iom |
---|
39 | USE in_out_manager ! I/O manager |
---|
40 | |
---|
41 | IMPLICIT NONE |
---|
42 | PRIVATE |
---|
43 | |
---|
44 | PUBLIC sbc ! routine called by step.F90 |
---|
45 | PUBLIC sbc_init ! routine called by opa.F90 |
---|
46 | |
---|
47 | INTEGER :: nsbc ! type of surface boundary condition (deduced from namsbc informations) |
---|
48 | |
---|
49 | !! * Substitutions |
---|
50 | # include "domzgr_substitute.h90" |
---|
51 | !!---------------------------------------------------------------------- |
---|
52 | !! NEMO/OPA 3.3 , LOCEAN-IPSL (2010) |
---|
53 | !! $Id$ |
---|
54 | !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) |
---|
55 | !!---------------------------------------------------------------------- |
---|
56 | |
---|
57 | CONTAINS |
---|
58 | |
---|
59 | SUBROUTINE sbc_init |
---|
60 | !!--------------------------------------------------------------------- |
---|
61 | !! *** ROUTINE sbc_init *** |
---|
62 | !! |
---|
63 | !! ** Purpose : Initialisation of the ocean surface boundary computation |
---|
64 | !! |
---|
65 | !! ** Method : Read the namsbc namelist and set derived parameters |
---|
66 | !! |
---|
67 | !! ** Action : - read namsbc parameters |
---|
68 | !! - nsbc: type of sbc |
---|
69 | !!---------------------------------------------------------------------- |
---|
70 | INTEGER :: icpt ! temporary integer |
---|
71 | !! |
---|
72 | NAMELIST/namsbc/ nn_fsbc, ln_ana, ln_flx, ln_blk_clio, ln_blk_core, ln_cpl, & |
---|
73 | & nn_ice , ln_dm2dc, ln_rnf, ln_ssr, nn_fwb, nn_ico_cpl |
---|
74 | !!---------------------------------------------------------------------- |
---|
75 | |
---|
76 | IF(lwp) THEN |
---|
77 | WRITE(numout,*) |
---|
78 | WRITE(numout,*) 'sbc_init : surface boundary condition setting' |
---|
79 | WRITE(numout,*) '~~~~~~~~ ' |
---|
80 | ENDIF |
---|
81 | |
---|
82 | REWIND( numnam ) ! Read Namelist namsbc |
---|
83 | READ ( numnam, namsbc ) |
---|
84 | |
---|
85 | ! overwrite namelist parameter using CPP key information |
---|
86 | !!gm here no overwrite, test all option via namelist change: require more incore memory |
---|
87 | !!gm IF( lk_sbc_cpl ) THEN ; ln_cpl = .TRUE. ; ELSE ; ln_cpl = .FALSE. ; ENDIF |
---|
88 | |
---|
89 | IF( Agrif_Root() ) THEN |
---|
90 | IF( lk_lim2 ) nn_ice = 2 |
---|
91 | IF( lk_lim3 ) nn_ice = 3 |
---|
92 | ENDIF |
---|
93 | ! |
---|
94 | IF( cp_cfg == 'gyre' ) THEN |
---|
95 | ln_ana = .TRUE. |
---|
96 | nn_ice = 0 |
---|
97 | ENDIF |
---|
98 | |
---|
99 | ! Control print |
---|
100 | IF(lwp) THEN |
---|
101 | WRITE(numout,*) ' Namelist namsbc (partly overwritten with CPP key setting)' |
---|
102 | WRITE(numout,*) ' frequency update of sbc (and ice) nn_fsbc = ', nn_fsbc |
---|
103 | WRITE(numout,*) ' Type of sbc : ' |
---|
104 | WRITE(numout,*) ' analytical formulation ln_ana = ', ln_ana |
---|
105 | WRITE(numout,*) ' flux formulation ln_flx = ', ln_flx |
---|
106 | WRITE(numout,*) ' CLIO bulk formulation ln_blk_clio = ', ln_blk_clio |
---|
107 | WRITE(numout,*) ' CLIO bulk formulation ln_blk_core = ', ln_blk_core |
---|
108 | WRITE(numout,*) ' coupled formulation (T if key_sbc_cpl) ln_cpl = ', ln_cpl |
---|
109 | WRITE(numout,*) ' Misc. options of sbc : ' |
---|
110 | WRITE(numout,*) ' ice management in the sbc (=0/1/2/3) nn_ice = ', nn_ice |
---|
111 | WRITE(numout,*) ' ice-ocean stress computation (=0/1/2) nn_ico_cpl = ', nn_ico_cpl |
---|
112 | WRITE(numout,*) ' daily mean to diurnal cycle qsr ln_dm2dc = ', ln_dm2dc |
---|
113 | WRITE(numout,*) ' runoff / runoff mouths ln_rnf = ', ln_rnf |
---|
114 | WRITE(numout,*) ' Sea Surface Restoring on SST and/or SSS ln_ssr = ', ln_ssr |
---|
115 | WRITE(numout,*) ' FreshWater Budget control (=0/1/2) nn_fwb = ', nn_fwb |
---|
116 | WRITE(numout,*) ' closed sea (=0/1) (set in namdom) nn_closea = ', nn_closea |
---|
117 | ENDIF |
---|
118 | |
---|
119 | IF( .NOT. ln_rnf ) THEN ! no specific treatment in vicinity of river mouths |
---|
120 | ln_rnf_mouth = .false. |
---|
121 | nkrnf = 0 |
---|
122 | rnfmsk (:,:) = 0.e0 |
---|
123 | rnfmsk_z(:) = 0.e0 |
---|
124 | ENDIF |
---|
125 | IF( nn_ice == 0 ) fr_i(:,:) = 0.e0 ! no ice in the domain, ice fraction is always zero |
---|
126 | |
---|
127 | ! ! restartability |
---|
128 | IF( MOD( nitend - nit000 + 1, nn_fsbc) /= 0 .OR. & |
---|
129 | MOD( nstock , nn_fsbc) /= 0 ) THEN |
---|
130 | WRITE(ctmp1,*) 'experiment length (', nitend - nit000 + 1, ') or nstock (', nstock, & |
---|
131 | & ' is NOT a multiple of nn_fsbc (', nn_fsbc, ')' |
---|
132 | CALL ctl_stop( ctmp1, 'Impossible to properly do model restart' ) |
---|
133 | ENDIF |
---|
134 | ! |
---|
135 | IF( MOD( rday, REAL(nn_fsbc, wp) * rdt ) /= 0 ) & |
---|
136 | & CALL ctl_warn( 'nn_fsbc is NOT a multiple of the number of time steps in a day' ) |
---|
137 | ! |
---|
138 | IF( nn_ice == 2 .AND. .NOT.( ln_blk_clio .OR. ln_blk_core .OR. lk_cpl ) ) & |
---|
139 | & CALL ctl_stop( 'sea-ice model requires a bulk formulation or coupled configuration' ) |
---|
140 | |
---|
141 | ! Choice of the Surface Boudary Condition (set nsbc) |
---|
142 | icpt = 0 |
---|
143 | IF( ln_ana ) THEN ; nsbc = 1 ; icpt = icpt + 1 ; ENDIF ! analytical formulation |
---|
144 | IF( ln_flx ) THEN ; nsbc = 2 ; icpt = icpt + 1 ; ENDIF ! flux formulation |
---|
145 | IF( ln_blk_clio ) THEN ; nsbc = 3 ; icpt = icpt + 1 ; ENDIF ! CLIO bulk formulation |
---|
146 | IF( ln_blk_core ) THEN ; nsbc = 4 ; icpt = icpt + 1 ; ENDIF ! CORE bulk formulation |
---|
147 | IF( ln_cpl ) THEN ; nsbc = 5 ; icpt = icpt + 1 ; ENDIF ! Coupled formulation |
---|
148 | IF( cp_cfg == 'gyre') THEN ; nsbc = 0 ; ENDIF ! GYRE analytical formulation |
---|
149 | IF( lk_esopa ) nsbc = -1 ! esopa test, ALL formulations |
---|
150 | |
---|
151 | IF( icpt /= 1 .AND. .NOT.lk_esopa ) THEN |
---|
152 | WRITE(numout,*) |
---|
153 | WRITE(numout,*) ' E R R O R in setting the sbc, one and only one namelist/CPP key option ' |
---|
154 | WRITE(numout,*) ' must be choosen. You choose ', icpt, ' option(s)' |
---|
155 | WRITE(numout,*) ' We stop' |
---|
156 | nstop = nstop + 1 |
---|
157 | ENDIF |
---|
158 | IF(lwp) THEN |
---|
159 | WRITE(numout,*) |
---|
160 | IF( nsbc == -1 ) WRITE(numout,*) ' ESOPA test All surface boundary conditions' |
---|
161 | IF( nsbc == 0 ) WRITE(numout,*) ' GYRE analytical formulation' |
---|
162 | IF( nsbc == 1 ) WRITE(numout,*) ' analytical formulation' |
---|
163 | IF( nsbc == 2 ) WRITE(numout,*) ' flux formulation' |
---|
164 | IF( nsbc == 3 ) WRITE(numout,*) ' CLIO bulk formulation' |
---|
165 | IF( nsbc == 4 ) WRITE(numout,*) ' CORE bulk formulation' |
---|
166 | IF( nsbc == 5 ) WRITE(numout,*) ' coupled formulation' |
---|
167 | ENDIF |
---|
168 | ! |
---|
169 | END SUBROUTINE sbc_init |
---|
170 | |
---|
171 | |
---|
172 | SUBROUTINE sbc( kt ) |
---|
173 | !!--------------------------------------------------------------------- |
---|
174 | !! *** ROUTINE sbc *** |
---|
175 | !! |
---|
176 | !! ** Purpose : provide at each time-step the ocean surface boundary |
---|
177 | !! condition (momentum, heat and freshwater fluxes) |
---|
178 | !! |
---|
179 | !! ** Method : blah blah to be written ????????? |
---|
180 | !! CAUTION : never mask the surface stress field (tke sbc) |
---|
181 | !! |
---|
182 | !! ** Action : - set the ocean surface boundary condition at before and now |
---|
183 | !! time step, i.e. |
---|
184 | !! utau_b, vtau_b, qns_b, qsr_b, emp_n, emps_b, qrp_b, erp_b |
---|
185 | !! utau , vtau , qns , qsr , emp , emps , qrp , erp |
---|
186 | !! - updte the ice fraction : fr_i |
---|
187 | !!---------------------------------------------------------------------- |
---|
188 | INTEGER, INTENT(in) :: kt ! ocean time step |
---|
189 | !!--------------------------------------------------------------------- |
---|
190 | |
---|
191 | ! ! ---------------------------------------- ! |
---|
192 | IF( kt /= nit000 ) THEN ! Swap of forcing fields ! |
---|
193 | ! ! ---------------------------------------- ! |
---|
194 | utau_b(:,:) = utau(:,:) ! Swap the ocean forcing fields |
---|
195 | vtau_b(:,:) = vtau(:,:) ! (except at nit000 where before fields |
---|
196 | qns_b (:,:) = qns (:,:) ! are set at the end of the routine) |
---|
197 | ! The 3D heat content due to qsr forcing is treated in traqsr |
---|
198 | ! qsr_b (:,:) = qsr (:,:) |
---|
199 | emp_b (:,:) = emp (:,:) |
---|
200 | emps_b(:,:) = emps(:,:) |
---|
201 | ENDIF |
---|
202 | ! ! ---------------------------------------- ! |
---|
203 | ! ! forcing field computation ! |
---|
204 | ! ! ---------------------------------------- ! |
---|
205 | |
---|
206 | CALL iom_setkt( kt + nn_fsbc - 1 ) ! in sbc, iom_put is called every nn_fsbc time step |
---|
207 | ! |
---|
208 | CALL sbc_ssm( kt ) ! ocean sea surface variables (sst_m, sss_m, ssu_m, ssv_m) |
---|
209 | ! ! averaged over nf_sbc time-step |
---|
210 | |
---|
211 | !== sbc formulation ==! |
---|
212 | |
---|
213 | SELECT CASE( nsbc ) ! Compute ocean surface boundary condition |
---|
214 | ! ! (i.e. utau,vtau, qns, qsr, emp, emps) |
---|
215 | CASE( 0 ) ; CALL sbc_gyre ( kt ) ! analytical formulation : GYRE configuration |
---|
216 | CASE( 1 ) ; CALL sbc_ana ( kt ) ! analytical formulation : uniform sbc |
---|
217 | CASE( 2 ) ; CALL sbc_flx ( kt ) ! flux formulation |
---|
218 | CASE( 3 ) ; CALL sbc_blk_clio( kt ) ! bulk formulation : CLIO for the ocean |
---|
219 | CASE( 4 ) ; CALL sbc_blk_core( kt ) ! bulk formulation : CORE for the ocean |
---|
220 | CASE( 5 ) ; CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice ) ! coupled formulation |
---|
221 | CASE( -1 ) |
---|
222 | CALL sbc_ana ( kt ) ! ESOPA, test ALL the formulations |
---|
223 | CALL sbc_gyre ( kt ) ! |
---|
224 | CALL sbc_flx ( kt ) ! |
---|
225 | CALL sbc_blk_clio( kt ) ! |
---|
226 | CALL sbc_blk_core( kt ) ! |
---|
227 | CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice ) ! |
---|
228 | END SELECT |
---|
229 | |
---|
230 | ! !== Misc. Options ==! |
---|
231 | |
---|
232 | !!gm IF( ln_dm2dc ) CALL sbc_dcy( kt ) ! Daily mean qsr distributed over the Diurnal Cycle |
---|
233 | |
---|
234 | SELECT CASE( nn_ice ) ! Update heat and freshwater fluxes over sea-ice areas |
---|
235 | CASE( 1 ) ; CALL sbc_ice_if ( kt ) ! Ice-cover climatology ("Ice-if" model) |
---|
236 | ! |
---|
237 | CASE( 2 ) ; CALL sbc_ice_lim_2( kt, nsbc ) ! LIM 2.0 ice model |
---|
238 | ! |
---|
239 | CASE( 3 ) ; CALL sbc_ice_lim ( kt, nsbc, nn_ico_cpl) ! LIM 3.0 ice model |
---|
240 | END SELECT |
---|
241 | |
---|
242 | IF( ln_rnf ) CALL sbc_rnf( kt ) ! add runoffs to fresh water fluxes |
---|
243 | |
---|
244 | IF( ln_ssr ) CALL sbc_ssr( kt ) ! add SST/SSS damping term |
---|
245 | |
---|
246 | IF( nn_fwb /= 0 ) CALL sbc_fwb( kt, nn_fwb, nn_fsbc ) ! control the freshwater budget |
---|
247 | |
---|
248 | IF( nclosea == 1 ) CALL sbc_clo( kt ) ! treatment of closed sea in the model domain |
---|
249 | ! ! (update freshwater fluxes) |
---|
250 | ! |
---|
251 | ! ! ---------------------------------------- ! |
---|
252 | IF( kt == nit000 ) THEN ! set the forcing field at nit000 - 1 ! |
---|
253 | ! ! ---------------------------------------- ! |
---|
254 | IF( ln_rstart .AND. & !* Restart: read in restart file |
---|
255 | & iom_varid( numror, 'utau_b', ldstop = .FALSE. ) > 0 ) THEN |
---|
256 | IF(lwp) WRITE(numout,*) ' nit000-1 surface forcing fields red in the restart file' |
---|
257 | CALL iom_get( numror, jpdom_autoglo, 'utau_b', utau_b ) ! before i-stress (U-point) |
---|
258 | CALL iom_get( numror, jpdom_autoglo, 'vtau_b', vtau_b ) ! before j-stress (V-point) |
---|
259 | CALL iom_get( numror, jpdom_autoglo, 'qns_b' , qns_b ) ! before non solar heat flux (T-point) |
---|
260 | ! The 3D heat content due to qsr forcing is treated in traqsr |
---|
261 | ! CALL iom_get( numror, jpdom_autoglo, 'qsr_b' , qsr_b ) ! before solar heat flux (T-point) |
---|
262 | CALL iom_get( numror, jpdom_autoglo, 'emp_b' , emp_b ) ! before freshwater flux (T-point) |
---|
263 | CALL iom_get( numror, jpdom_autoglo, 'emps_b', emps_b ) ! before C/D freshwater flux (T-point) |
---|
264 | ELSE !* no restart: set from nit000 values |
---|
265 | IF(lwp) WRITE(numout,*) ' nit000-1 surface forcing fields set to nit000' |
---|
266 | utau_b(:,:) = utau(:,:) |
---|
267 | vtau_b(:,:) = vtau(:,:) |
---|
268 | qns_b (:,:) = qns (:,:) |
---|
269 | ! qsr_b (:,:) = qsr (:,:) |
---|
270 | emp_b (:,:) = emp (:,:) |
---|
271 | emps_b(:,:) = emps(:,:) |
---|
272 | ENDIF |
---|
273 | ENDIF |
---|
274 | |
---|
275 | ! ! ---------------------------------------- ! |
---|
276 | IF( lrst_oce ) THEN ! Write in the ocean restart file ! |
---|
277 | ! ! ---------------------------------------- ! |
---|
278 | IF(lwp) WRITE(numout,*) |
---|
279 | IF(lwp) WRITE(numout,*) 'sbc : ocean surface forcing fields written in ocean restart file ', & |
---|
280 | & 'at it= ', kt,' date= ', ndastp |
---|
281 | IF(lwp) WRITE(numout,*) '~~~~' |
---|
282 | CALL iom_rstput( kt, nitrst, numrow, 'utau_b' , utau ) |
---|
283 | CALL iom_rstput( kt, nitrst, numrow, 'vtau_b' , vtau ) |
---|
284 | CALL iom_rstput( kt, nitrst, numrow, 'qns_b' , qns ) |
---|
285 | ! The 3D heat content due to qsr forcing is treated in traqsr |
---|
286 | ! CALL iom_rstput( kt, nitrst, numrow, 'qsr_b' , qsr ) |
---|
287 | CALL iom_rstput( kt, nitrst, numrow, 'emp_b' , emp ) |
---|
288 | CALL iom_rstput( kt, nitrst, numrow, 'emps_b' , emps ) |
---|
289 | ENDIF |
---|
290 | |
---|
291 | ! ! ---------------------------------------- ! |
---|
292 | ! ! Outputs and control print ! |
---|
293 | ! ! ---------------------------------------- ! |
---|
294 | IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN |
---|
295 | CALL iom_put( "emp" , emp ) ! upward water flux |
---|
296 | CALL iom_put( "emps" , emps ) ! c/d water flux |
---|
297 | CALL iom_put( "qns+qsr", qns + qsr ) ! total heat flux (caution if ln_dm2dc=true, to be |
---|
298 | CALL iom_put( "qns" , qns ) ! solar heat flux moved after the call to iom_setkt) |
---|
299 | CALL iom_put( "qsr" , qsr ) ! solar heat flux moved after the call to iom_setkt) |
---|
300 | IF( nn_ice > 0 ) CALL iom_put( "ice_cover", fr_i ) ! ice fraction |
---|
301 | ENDIF |
---|
302 | ! |
---|
303 | CALL iom_setkt( kt ) ! iom_put outside of sbc is called at every time step |
---|
304 | ! |
---|
305 | CALL iom_put( "utau", utau ) ! i-wind stress (stress can be updated at |
---|
306 | CALL iom_put( "vtau", vtau ) ! j-wind stress each time step in sea-ice) |
---|
307 | CALL iom_put( "taum", taum ) ! wind stress module |
---|
308 | CALL iom_put( "wspd", wndm ) ! wind speed module |
---|
309 | ! |
---|
310 | IF(ln_ctl) THEN ! print mean trends (used for debugging) |
---|
311 | CALL prt_ctl(tab2d_1=fr_i , clinfo1=' fr_i - : ', mask1=tmask, ovlap=1 ) |
---|
312 | CALL prt_ctl(tab2d_1=emp , clinfo1=' emp - : ', mask1=tmask, ovlap=1 ) |
---|
313 | CALL prt_ctl(tab2d_1=emps , clinfo1=' emps - : ', mask1=tmask, ovlap=1 ) |
---|
314 | CALL prt_ctl(tab2d_1=qns , clinfo1=' qns - : ', mask1=tmask, ovlap=1 ) |
---|
315 | CALL prt_ctl(tab2d_1=qsr , clinfo1=' qsr - : ', mask1=tmask, ovlap=1 ) |
---|
316 | CALL prt_ctl(tab3d_1=tmask , clinfo1=' tmask : ', mask1=tmask, ovlap=1, kdim=jpk ) |
---|
317 | CALL prt_ctl(tab3d_1=tn , clinfo1=' sst - : ', mask1=tmask, ovlap=1, kdim=1 ) |
---|
318 | CALL prt_ctl(tab3d_1=sn , clinfo1=' sss - : ', mask1=tmask, ovlap=1, kdim=1 ) |
---|
319 | CALL prt_ctl(tab2d_1=utau , clinfo1=' utau - : ', mask1=umask, & |
---|
320 | & tab2d_2=vtau , clinfo2=' vtau - : ', mask2=vmask, ovlap=1 ) |
---|
321 | ENDIF |
---|
322 | ! |
---|
323 | END SUBROUTINE sbc |
---|
324 | |
---|
325 | !!====================================================================== |
---|
326 | END MODULE sbcmod |
---|