1 | MODULE sbcssm |
---|
2 | !!====================================================================== |
---|
3 | !! *** MODULE sbcssm *** |
---|
4 | !! Off-line : interpolation of the physical fields |
---|
5 | !!====================================================================== |
---|
6 | !! History : 3.4 ! 2012-03 (S. Alderson) original code |
---|
7 | !!---------------------------------------------------------------------- |
---|
8 | |
---|
9 | !!---------------------------------------------------------------------- |
---|
10 | !! sbc_ssm_init : initialization, namelist read, and SAVEs control |
---|
11 | !! sbc_ssm : Interpolation of the fields |
---|
12 | !!---------------------------------------------------------------------- |
---|
13 | USE oce ! ocean dynamics and tracers variables |
---|
14 | USE c1d ! 1D configuration: lk_c1d |
---|
15 | USE dom_oce ! ocean domain: variables |
---|
16 | USE zdf_oce ! ocean vertical physics: variables |
---|
17 | USE sbc_oce ! surface module: variables |
---|
18 | USE phycst ! physical constants |
---|
19 | USE eosbn2 ! equation of state - Brunt Vaisala frequency |
---|
20 | USE lbclnk ! ocean lateral boundary conditions (or mpp link) |
---|
21 | USE zpshde ! z-coord. with partial steps: horizontal derivatives |
---|
22 | USE closea ! for ln_closea |
---|
23 | USE icb_oce ! for icebergs |
---|
24 | ! |
---|
25 | USE in_out_manager ! I/O manager |
---|
26 | USE iom ! I/O library |
---|
27 | USE lib_mpp ! distributed memory computing library |
---|
28 | USE prtctl ! print control |
---|
29 | USE fldread ! read input fields |
---|
30 | USE timing ! Timing |
---|
31 | |
---|
32 | IMPLICIT NONE |
---|
33 | PRIVATE |
---|
34 | |
---|
35 | PUBLIC sbc_ssm_init ! called by sbc_init |
---|
36 | PUBLIC sbc_ssm ! called by sbc |
---|
37 | |
---|
38 | CHARACTER(len=100) :: cn_dir ! Root directory for location of ssm files |
---|
39 | LOGICAL :: ln_3d_uve ! specify whether input velocity data is 3D |
---|
40 | LOGICAL :: ln_read_frq ! specify whether we must read frq or not |
---|
41 | |
---|
42 | LOGICAL :: l_sasread ! Ice intilisation: =T read a file ; =F anaytical initilaistion |
---|
43 | LOGICAL :: l_initdone = .false. |
---|
44 | INTEGER :: nfld_3d |
---|
45 | INTEGER :: nfld_2d |
---|
46 | |
---|
47 | INTEGER :: jf_tem ! index of temperature |
---|
48 | INTEGER :: jf_sal ! index of salinity |
---|
49 | INTEGER :: jf_usp ! index of u velocity component |
---|
50 | INTEGER :: jf_vsp ! index of v velocity component |
---|
51 | INTEGER :: jf_ssh ! index of sea surface height |
---|
52 | INTEGER :: jf_e3t ! index of first T level thickness |
---|
53 | INTEGER :: jf_frq ! index of fraction of qsr absorbed in the 1st T level |
---|
54 | |
---|
55 | TYPE(FLD), ALLOCATABLE, DIMENSION(:) :: sf_ssm_3d ! structure of input fields (file information, fields read) |
---|
56 | TYPE(FLD), ALLOCATABLE, DIMENSION(:) :: sf_ssm_2d ! structure of input fields (file information, fields read) |
---|
57 | |
---|
58 | !!---------------------------------------------------------------------- |
---|
59 | !! NEMO/SAS 4.0 , NEMO Consortium (2018) |
---|
60 | !! $Id$ |
---|
61 | !! Software governed by the CeCILL license (see ./LICENSE) |
---|
62 | !!---------------------------------------------------------------------- |
---|
63 | CONTAINS |
---|
64 | |
---|
65 | SUBROUTINE sbc_ssm( kt, Kbb, Kmm ) |
---|
66 | !!---------------------------------------------------------------------- |
---|
67 | !! *** ROUTINE sbc_ssm *** |
---|
68 | !! |
---|
69 | !! ** Purpose : Prepares dynamics and physics fields from a NEMO run |
---|
70 | !! for an off-line simulation using surface processes only |
---|
71 | !! |
---|
72 | !! ** Method : calculates the position of data |
---|
73 | !! - interpolates data if needed |
---|
74 | !!---------------------------------------------------------------------- |
---|
75 | INTEGER, INTENT(in) :: kt ! ocean time-step index |
---|
76 | INTEGER, INTENT(in) :: Kbb, Kmm ! ocean time level indices |
---|
77 | ! (not needed for SAS but needed to keep a consistent interface in sbcmod.F90) |
---|
78 | ! |
---|
79 | INTEGER :: ji, jj ! dummy loop indices |
---|
80 | REAL(wp) :: ztinta ! ratio applied to after records when doing time interpolation |
---|
81 | REAL(wp) :: ztintb ! ratio applied to before records when doing time interpolation |
---|
82 | !!---------------------------------------------------------------------- |
---|
83 | ! |
---|
84 | IF( ln_timing ) CALL timing_start( 'sbc_ssm') |
---|
85 | |
---|
86 | IF ( l_sasread ) THEN |
---|
87 | IF( nfld_3d > 0 ) CALL fld_read( kt, 1, sf_ssm_3d ) !== read data at kt time step ==! |
---|
88 | IF( nfld_2d > 0 ) CALL fld_read( kt, 1, sf_ssm_2d ) !== read data at kt time step ==! |
---|
89 | ! |
---|
90 | IF( ln_3d_uve ) THEN |
---|
91 | IF( .NOT. ln_linssh ) THEN |
---|
92 | e3t_m(:,:) = sf_ssm_3d(jf_e3t)%fnow(:,:,1) * tmask(:,:,1) ! vertical scale factor |
---|
93 | ELSE |
---|
94 | e3t_m(:,:) = e3t_0(:,:,1) ! vertical scale factor |
---|
95 | ENDIF |
---|
96 | ssu_m(:,:) = sf_ssm_3d(jf_usp)%fnow(:,:,1) * umask(:,:,1) ! u-velocity |
---|
97 | ssv_m(:,:) = sf_ssm_3d(jf_vsp)%fnow(:,:,1) * vmask(:,:,1) ! v-velocity |
---|
98 | ELSE |
---|
99 | IF( .NOT. ln_linssh ) THEN |
---|
100 | e3t_m(:,:) = sf_ssm_2d(jf_e3t)%fnow(:,:,1) * tmask(:,:,1) ! vertical scale factor |
---|
101 | ELSE |
---|
102 | e3t_m(:,:) = e3t_0(:,:,1) ! vertical scale factor |
---|
103 | ENDIF |
---|
104 | ssu_m(:,:) = sf_ssm_2d(jf_usp)%fnow(:,:,1) * umask(:,:,1) ! u-velocity |
---|
105 | ssv_m(:,:) = sf_ssm_2d(jf_vsp)%fnow(:,:,1) * vmask(:,:,1) ! v-velocity |
---|
106 | ENDIF |
---|
107 | ! |
---|
108 | sst_m(:,:) = sf_ssm_2d(jf_tem)%fnow(:,:,1) * tmask(:,:,1) ! temperature |
---|
109 | sss_m(:,:) = sf_ssm_2d(jf_sal)%fnow(:,:,1) * tmask(:,:,1) ! salinity |
---|
110 | ssh_m(:,:) = sf_ssm_2d(jf_ssh)%fnow(:,:,1) * tmask(:,:,1) ! sea surface height |
---|
111 | IF( ln_read_frq ) THEN |
---|
112 | frq_m(:,:) = sf_ssm_2d(jf_frq)%fnow(:,:,1) * tmask(:,:,1) ! solar penetration |
---|
113 | ELSE |
---|
114 | frq_m(:,:) = 1._wp |
---|
115 | ENDIF |
---|
116 | ELSE |
---|
117 | sss_m(:,:) = 35._wp ! =35. to obtain a physical value for the freezing point |
---|
118 | CALL eos_fzp( sss_m(:,:), sst_m(:,:) ) ! sst_m is set at the freezing point |
---|
119 | ssu_m(:,:) = 0._wp |
---|
120 | ssv_m(:,:) = 0._wp |
---|
121 | ssh_m(:,:) = 0._wp |
---|
122 | IF( .NOT. ln_linssh ) e3t_m(:,:) = e3t_0(:,:,1) !clem: necessary at least for sas2D |
---|
123 | frq_m(:,:) = 1._wp ! - - |
---|
124 | ssh (:,:,Kmm) = 0._wp ! - - |
---|
125 | ENDIF |
---|
126 | |
---|
127 | IF ( nn_ice == 1 ) THEN |
---|
128 | ts(:,:,1,jp_tem,Kmm) = sst_m(:,:) |
---|
129 | ts(:,:,1,jp_sal,Kmm) = sss_m(:,:) |
---|
130 | ts(:,:,1,jp_tem,Kbb) = sst_m(:,:) |
---|
131 | ts(:,:,1,jp_sal,Kbb) = sss_m(:,:) |
---|
132 | ENDIF |
---|
133 | uu (:,:,1,Kbb) = ssu_m(:,:) |
---|
134 | vv (:,:,1,Kbb) = ssv_m(:,:) |
---|
135 | |
---|
136 | IF(sn_cfctl%l_prtctl) THEN ! print control |
---|
137 | CALL prt_ctl(tab2d_1=sst_m, clinfo1=' sst_m - : ', mask1=tmask ) |
---|
138 | CALL prt_ctl(tab2d_1=sss_m, clinfo1=' sss_m - : ', mask1=tmask ) |
---|
139 | CALL prt_ctl(tab2d_1=ssu_m, clinfo1=' ssu_m - : ', mask1=umask ) |
---|
140 | CALL prt_ctl(tab2d_1=ssv_m, clinfo1=' ssv_m - : ', mask1=vmask ) |
---|
141 | CALL prt_ctl(tab2d_1=ssh_m, clinfo1=' ssh_m - : ', mask1=tmask ) |
---|
142 | IF( .NOT.ln_linssh ) CALL prt_ctl(tab2d_1=ssh_m, clinfo1=' e3t_m - : ', mask1=tmask ) |
---|
143 | IF( ln_read_frq ) CALL prt_ctl(tab2d_1=frq_m, clinfo1=' frq_m - : ', mask1=tmask ) |
---|
144 | ENDIF |
---|
145 | ! |
---|
146 | IF( l_initdone ) THEN ! Mean value at each nn_fsbc time-step ! |
---|
147 | CALL iom_put( 'ssu_m', ssu_m ) |
---|
148 | CALL iom_put( 'ssv_m', ssv_m ) |
---|
149 | CALL iom_put( 'sst_m', sst_m ) |
---|
150 | CALL iom_put( 'sss_m', sss_m ) |
---|
151 | CALL iom_put( 'ssh_m', ssh_m ) |
---|
152 | IF( .NOT.ln_linssh ) CALL iom_put( 'e3t_m', e3t_m ) |
---|
153 | IF( ln_read_frq ) CALL iom_put( 'frq_m', frq_m ) |
---|
154 | ENDIF |
---|
155 | ! |
---|
156 | IF( ln_timing ) CALL timing_stop( 'sbc_ssm') |
---|
157 | ! |
---|
158 | END SUBROUTINE sbc_ssm |
---|
159 | |
---|
160 | |
---|
161 | SUBROUTINE sbc_ssm_init( Kbb, Kmm ) |
---|
162 | !!---------------------------------------------------------------------- |
---|
163 | !! *** ROUTINE sbc_ssm_init *** |
---|
164 | !! |
---|
165 | !! ** Purpose : Initialisation of sea surface mean data |
---|
166 | !!---------------------------------------------------------------------- |
---|
167 | INTEGER, INTENT(in) :: Kbb, Kmm ! ocean time level indices |
---|
168 | ! (not needed for SAS but needed to keep a consistent interface in sbcmod.F90) |
---|
169 | INTEGER :: ierr, ierr0, ierr1, ierr2, ierr3 ! return error code |
---|
170 | INTEGER :: ifpr ! dummy loop indice |
---|
171 | INTEGER :: inum, idv, idimv, jpm ! local integer |
---|
172 | INTEGER :: ios ! Local integer output status for namelist read |
---|
173 | !! |
---|
174 | CHARACTER(len=100) :: cn_dir ! Root directory for location of core files |
---|
175 | TYPE(FLD_N), ALLOCATABLE, DIMENSION(:) :: slf_3d ! array of namelist information on the fields to read |
---|
176 | TYPE(FLD_N), ALLOCATABLE, DIMENSION(:) :: slf_2d ! array of namelist information on the fields to read |
---|
177 | TYPE(FLD_N) :: sn_tem, sn_sal ! information about the fields to be read |
---|
178 | TYPE(FLD_N) :: sn_usp, sn_vsp |
---|
179 | TYPE(FLD_N) :: sn_ssh, sn_e3t, sn_frq |
---|
180 | !! |
---|
181 | NAMELIST/namsbc_sas/ l_sasread, cn_dir, ln_3d_uve, ln_read_frq, & |
---|
182 | & sn_tem, sn_sal, sn_usp, sn_vsp, sn_ssh, sn_e3t, sn_frq |
---|
183 | !!---------------------------------------------------------------------- |
---|
184 | ! |
---|
185 | IF( ln_rstart .AND. nn_components == jp_iam_sas ) RETURN |
---|
186 | ! |
---|
187 | IF(lwp) THEN |
---|
188 | WRITE(numout,*) |
---|
189 | WRITE(numout,*) 'sbc_ssm_init : sea surface mean data initialisation ' |
---|
190 | WRITE(numout,*) '~~~~~~~~~~~~ ' |
---|
191 | ENDIF |
---|
192 | ! |
---|
193 | READ ( numnam_ref, namsbc_sas, IOSTAT = ios, ERR = 901) |
---|
194 | 901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_sas in reference namelist' ) |
---|
195 | READ ( numnam_cfg, namsbc_sas, IOSTAT = ios, ERR = 902 ) |
---|
196 | 902 IF( ios > 0 ) CALL ctl_nam ( ios , 'namsbc_sas in configuration namelist' ) |
---|
197 | IF(lwm) WRITE ( numond, namsbc_sas ) |
---|
198 | ! |
---|
199 | IF(lwp) THEN ! Control print |
---|
200 | WRITE(numout,*) ' Namelist namsbc_sas' |
---|
201 | WRITE(numout,*) ' Initialisation using an input file l_sasread = ', l_sasread |
---|
202 | WRITE(numout,*) ' Are we supplying a 3D u,v and e3 field ln_3d_uve = ', ln_3d_uve |
---|
203 | WRITE(numout,*) ' Are we reading frq (fraction of qsr absorbed in the 1st T level) ln_read_frq = ', ln_read_frq |
---|
204 | ENDIF |
---|
205 | ! |
---|
206 | !! switch off stuff that isn't sensible with a standalone module |
---|
207 | !! note that we need sbc_ssm called first in sbc |
---|
208 | ! |
---|
209 | IF( ln_apr_dyn ) THEN |
---|
210 | IF( lwp ) WRITE(numout,*) ' ==>>> No atmospheric gradient needed with StandAlone Surface scheme' |
---|
211 | ln_apr_dyn = .FALSE. |
---|
212 | ENDIF |
---|
213 | IF( ln_rnf ) THEN |
---|
214 | IF( lwp ) WRITE(numout,*) ' ==>>> No runoff needed with StandAlone Surface scheme' |
---|
215 | ln_rnf = .FALSE. |
---|
216 | ENDIF |
---|
217 | IF( ln_ssr ) THEN |
---|
218 | IF( lwp ) WRITE(numout,*) ' ==>>> No surface relaxation needed with StandAlone Surface scheme' |
---|
219 | ln_ssr = .FALSE. |
---|
220 | ENDIF |
---|
221 | IF( nn_fwb > 0 ) THEN |
---|
222 | IF( lwp ) WRITE(numout,*) ' ==>>> No freshwater budget adjustment needed with StandAlone Surface scheme' |
---|
223 | nn_fwb = 0 |
---|
224 | ENDIF |
---|
225 | IF( ln_closea ) THEN |
---|
226 | IF( lwp ) WRITE(numout,*) ' ==>>> No closed seas adjustment needed with StandAlone Surface scheme' |
---|
227 | ln_closea = .false. |
---|
228 | ENDIF |
---|
229 | IF( ln_icebergs .AND. ln_M2016 ) THEN |
---|
230 | IF( lwp ) WRITE(numout,*) ' ==>>> ln_iceberg and ln_M2016 not compatible with SAS (need 3d data)' |
---|
231 | CALL ctl_stop('ln_iceberg and ln_M2016 not compatible with SAS (need 3d data)') |
---|
232 | END IF |
---|
233 | ! |
---|
234 | IF( l_sasread ) THEN ! store namelist information in an array |
---|
235 | ! |
---|
236 | !! following code is a bit messy, but distinguishes between when u,v are 3d arrays and |
---|
237 | !! when we have other 3d arrays that we need to read in |
---|
238 | !! so if a new field is added i.e. jf_new, just give it the next integer in sequence |
---|
239 | !! for the corresponding dimension (currently if ln_3d_uve is true, 4 for 2d and 3 for 3d, |
---|
240 | !! alternatively if ln_3d_uve is false, 6 for 2d and 1 for 3d), reset nfld_3d, nfld_2d, |
---|
241 | !! and the rest of the logic should still work |
---|
242 | ! |
---|
243 | jf_tem = 1 ; jf_ssh = 3 ! default 2D fields index |
---|
244 | jf_sal = 2 ; jf_frq = 4 ! |
---|
245 | ! |
---|
246 | IF( ln_3d_uve ) THEN |
---|
247 | jf_usp = 1 ; jf_vsp = 2 ; jf_e3t = 3 ! define 3D fields index |
---|
248 | nfld_3d = 2 + COUNT( (/.NOT.ln_linssh/) ) ! number of 3D fields to read |
---|
249 | nfld_2d = 3 + COUNT( (/ln_read_frq/) ) ! number of 2D fields to read |
---|
250 | ELSE |
---|
251 | jf_usp = 4 ; jf_e3t = 6 ! update 2D fields index |
---|
252 | jf_vsp = 5 ; jf_frq = 6 + COUNT( (/.NOT.ln_linssh/) ) |
---|
253 | ! |
---|
254 | nfld_3d = 0 ! no 3D fields to read |
---|
255 | nfld_2d = 5 + COUNT( (/.NOT.ln_linssh/) ) + COUNT( (/ln_read_frq/) ) ! number of 2D fields to read |
---|
256 | ENDIF |
---|
257 | ! |
---|
258 | IF( nfld_3d > 0 ) THEN |
---|
259 | ALLOCATE( slf_3d(nfld_3d), STAT=ierr ) ! set slf structure |
---|
260 | IF( ierr > 0 ) THEN |
---|
261 | CALL ctl_stop( 'sbc_ssm_init: unable to allocate slf 3d structure' ) ; RETURN |
---|
262 | ENDIF |
---|
263 | slf_3d(jf_usp) = sn_usp |
---|
264 | slf_3d(jf_vsp) = sn_vsp |
---|
265 | IF( .NOT.ln_linssh ) slf_3d(jf_e3t) = sn_e3t |
---|
266 | ENDIF |
---|
267 | ! |
---|
268 | IF( nfld_2d > 0 ) THEN |
---|
269 | ALLOCATE( slf_2d(nfld_2d), STAT=ierr ) ! set slf structure |
---|
270 | IF( ierr > 0 ) THEN |
---|
271 | CALL ctl_stop( 'sbc_ssm_init: unable to allocate slf 2d structure' ) ; RETURN |
---|
272 | ENDIF |
---|
273 | slf_2d(jf_tem) = sn_tem ; slf_2d(jf_sal) = sn_sal ; slf_2d(jf_ssh) = sn_ssh |
---|
274 | IF( ln_read_frq ) slf_2d(jf_frq) = sn_frq |
---|
275 | IF( .NOT. ln_3d_uve ) THEN |
---|
276 | slf_2d(jf_usp) = sn_usp ; slf_2d(jf_vsp) = sn_vsp |
---|
277 | IF( .NOT.ln_linssh ) slf_2d(jf_e3t) = sn_e3t |
---|
278 | ENDIF |
---|
279 | ENDIF |
---|
280 | ! |
---|
281 | ierr1 = 0 ! default definition if slf_?d(ifpr)%ln_tint = .false. |
---|
282 | IF( nfld_3d > 0 ) THEN |
---|
283 | ALLOCATE( sf_ssm_3d(nfld_3d), STAT=ierr ) ! set sf structure |
---|
284 | IF( ierr > 0 ) THEN |
---|
285 | CALL ctl_stop( 'sbc_ssm_init: unable to allocate sf structure' ) ; RETURN |
---|
286 | ENDIF |
---|
287 | DO ifpr = 1, nfld_3d |
---|
288 | ALLOCATE( sf_ssm_3d(ifpr)%fnow(jpi,jpj,jpk) , STAT=ierr0 ) |
---|
289 | IF( slf_3d(ifpr)%ln_tint ) ALLOCATE( sf_ssm_3d(ifpr)%fdta(jpi,jpj,jpk,2) , STAT=ierr1 ) |
---|
290 | IF( ierr0 + ierr1 > 0 ) THEN |
---|
291 | CALL ctl_stop( 'sbc_ssm_init : unable to allocate sf_ssm_3d array structure' ) ; RETURN |
---|
292 | ENDIF |
---|
293 | END DO |
---|
294 | ! ! fill sf with slf_i and control print |
---|
295 | CALL fld_fill( sf_ssm_3d, slf_3d, cn_dir, 'sbc_ssm_init', '3D Data in file', 'namsbc_ssm' ) |
---|
296 | sf_ssm_3d(jf_usp)%cltype = 'U' ; sf_ssm_3d(jf_usp)%zsgn = -1._wp |
---|
297 | sf_ssm_3d(jf_vsp)%cltype = 'V' ; sf_ssm_3d(jf_vsp)%zsgn = -1._wp |
---|
298 | ENDIF |
---|
299 | ! |
---|
300 | IF( nfld_2d > 0 ) THEN |
---|
301 | ALLOCATE( sf_ssm_2d(nfld_2d), STAT=ierr ) ! set sf structure |
---|
302 | IF( ierr > 0 ) THEN |
---|
303 | CALL ctl_stop( 'sbc_ssm_init: unable to allocate sf 2d structure' ) ; RETURN |
---|
304 | ENDIF |
---|
305 | DO ifpr = 1, nfld_2d |
---|
306 | ALLOCATE( sf_ssm_2d(ifpr)%fnow(jpi,jpj,1) , STAT=ierr0 ) |
---|
307 | IF( slf_2d(ifpr)%ln_tint ) ALLOCATE( sf_ssm_2d(ifpr)%fdta(jpi,jpj,1,2) , STAT=ierr1 ) |
---|
308 | IF( ierr0 + ierr1 > 0 ) THEN |
---|
309 | CALL ctl_stop( 'sbc_ssm_init : unable to allocate sf_ssm_2d array structure' ) ; RETURN |
---|
310 | ENDIF |
---|
311 | END DO |
---|
312 | ! |
---|
313 | CALL fld_fill( sf_ssm_2d, slf_2d, cn_dir, 'sbc_ssm_init', '2D Data in file', 'namsbc_ssm' ) |
---|
314 | IF( .NOT. ln_3d_uve ) THEN |
---|
315 | sf_ssm_2d(jf_usp)%cltype = 'U' ; sf_ssm_2d(jf_usp)%zsgn = -1._wp |
---|
316 | sf_ssm_2d(jf_vsp)%cltype = 'V' ; sf_ssm_2d(jf_vsp)%zsgn = -1._wp |
---|
317 | ENDIF |
---|
318 | ENDIF |
---|
319 | ! |
---|
320 | IF( nfld_3d > 0 ) DEALLOCATE( slf_3d, STAT=ierr ) |
---|
321 | IF( nfld_2d > 0 ) DEALLOCATE( slf_2d, STAT=ierr ) |
---|
322 | ! |
---|
323 | ENDIF |
---|
324 | ! |
---|
325 | CALL sbc_ssm( nit000, Kbb, Kmm ) ! need to define ss?_m arrays used in iceistate |
---|
326 | l_initdone = .TRUE. |
---|
327 | ! |
---|
328 | END SUBROUTINE sbc_ssm_init |
---|
329 | |
---|
330 | !!====================================================================== |
---|
331 | END MODULE sbcssm |
---|