1 | MODULE trdmxl |
---|
2 | !!====================================================================== |
---|
3 | !! *** MODULE trdmxl *** |
---|
4 | !! Ocean diagnostics: mixed layer T-S trends |
---|
5 | !!====================================================================== |
---|
6 | !! History : OPA ! 1995-04 (J. Vialard) Original code |
---|
7 | !! ! 1997-02 (E. Guilyardi) Adaptation global + base cmo |
---|
8 | !! ! 1999-09 (E. Guilyardi) Re-writing + netCDF output |
---|
9 | !! NEMO 1.0 ! 2002-06 (G. Madec) F90: Free form and module |
---|
10 | !! - ! 2004-08 (C. Talandier) New trends organization |
---|
11 | !! 2.0 ! 2005-05 (C. Deltel) Diagnose trends of time averaged ML T & S |
---|
12 | !! 3.5 ! 2012-03 (G. Madec) complete reorganisation + change in the time averaging |
---|
13 | !!---------------------------------------------------------------------- |
---|
14 | |
---|
15 | !!---------------------------------------------------------------------- |
---|
16 | !! trd_mxl : T and S cumulated trends averaged over the mixed layer |
---|
17 | !! trd_mxl_zint : T and S trends vertical integration |
---|
18 | !! trd_mxl_init : initialization step |
---|
19 | !!---------------------------------------------------------------------- |
---|
20 | USE oce ! ocean dynamics and tracers variables |
---|
21 | USE dom_oce ! ocean space and time domain variables |
---|
22 | USE trd_oce ! trends: ocean variables |
---|
23 | USE trdmxl_oce ! ocean variables trends |
---|
24 | USE ldftra ! lateral diffusion: eddy diffusivity & EIV coeff. |
---|
25 | USE zdf_oce ! ocean vertical physics |
---|
26 | USE phycst ! Define parameters for the routines |
---|
27 | USE dianam ! build the name of file (routine) |
---|
28 | USE ldfslp ! iso-neutral slopes |
---|
29 | USE zdfmxl ! mixed layer depth |
---|
30 | USE zdfddm ! ocean vertical physics: double diffusion |
---|
31 | USE lbclnk ! ocean lateral boundary conditions (or mpp link) |
---|
32 | USE trdmxl_rst ! restart for diagnosing the ML trends |
---|
33 | ! |
---|
34 | USE in_out_manager ! I/O manager |
---|
35 | USE ioipsl ! NetCDF library |
---|
36 | USE prtctl ! Print control |
---|
37 | USE restart ! for lrst_oce |
---|
38 | USE lib_mpp ! MPP library |
---|
39 | USE wrk_nemo ! Memory allocation |
---|
40 | USE iom |
---|
41 | |
---|
42 | IMPLICIT NONE |
---|
43 | PRIVATE |
---|
44 | |
---|
45 | PUBLIC trd_mxl ! routine called by step.F90 |
---|
46 | PUBLIC trd_mxl_init ! routine called by opa.F90 |
---|
47 | PUBLIC trd_mxl_zint ! routine called by tracers routines |
---|
48 | |
---|
49 | INTEGER :: nkstp ! current time step |
---|
50 | |
---|
51 | !!gm to be moved from trdmxl_oce |
---|
52 | ! REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: hml ! ML depth (sum of e3t over nmln-1 levels) [m] |
---|
53 | ! REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: tml , sml ! now ML averaged T & S |
---|
54 | ! REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: tmlb_nf, smlb_nf ! not filtered before ML averaged T & S |
---|
55 | ! |
---|
56 | ! |
---|
57 | ! REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: hmlb, hmln ! before, now, and after Mixed Layer depths [m] |
---|
58 | ! |
---|
59 | ! REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: tb_mlb, tb_mln ! before (not filtered) tracer averaged over before and now ML |
---|
60 | ! |
---|
61 | ! REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: tn_mln ! now tracer averaged over now ML |
---|
62 | !!gm end |
---|
63 | |
---|
64 | CHARACTER (LEN=40) :: clhstnam ! name of the trends NetCDF file |
---|
65 | INTEGER :: nh_t, nmoymltrd |
---|
66 | INTEGER :: nidtrd |
---|
67 | INTEGER, ALLOCATABLE, SAVE, DIMENSION(:) :: ndextrd1 |
---|
68 | INTEGER :: ndimtrd1 |
---|
69 | INTEGER :: ionce, icount |
---|
70 | |
---|
71 | !!---------------------------------------------------------------------- |
---|
72 | !! NEMO/OPA 3.3 , NEMO Consortium (2010) |
---|
73 | !! $Id$ |
---|
74 | !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) |
---|
75 | !!---------------------------------------------------------------------- |
---|
76 | CONTAINS |
---|
77 | |
---|
78 | INTEGER FUNCTION trd_mxl_alloc() |
---|
79 | !!---------------------------------------------------------------------- |
---|
80 | !! *** ROUTINE trd_mxl_alloc *** |
---|
81 | !!---------------------------------------------------------------------- |
---|
82 | ALLOCATE( ndextrd1(jpi*jpj) , STAT=trd_mxl_alloc ) |
---|
83 | ! |
---|
84 | IF( lk_mpp ) CALL mpp_sum ( trd_mxl_alloc ) |
---|
85 | IF( trd_mxl_alloc /= 0 ) CALL ctl_warn('trd_mxl_alloc: failed to allocate array ndextrd1') |
---|
86 | END FUNCTION trd_mxl_alloc |
---|
87 | |
---|
88 | |
---|
89 | SUBROUTINE trd_tra_mxl( ptrdx, ptrdy, ktrd, kt, p2dt, kmxln ) |
---|
90 | !!---------------------------------------------------------------------- |
---|
91 | !! *** ROUTINE trd_tra_mng *** |
---|
92 | !! |
---|
93 | !! ** Purpose : Dispatch all trends computation, e.g. 3D output, integral |
---|
94 | !! constraints, barotropic vorticity, kinetic enrgy, |
---|
95 | !! potential energy, and/or mixed layer budget. |
---|
96 | !!---------------------------------------------------------------------- |
---|
97 | REAL(wp), DIMENSION(:,:,:), INTENT(inout) :: ptrdx ! Temperature or U trend |
---|
98 | REAL(wp), DIMENSION(:,:,:), INTENT(inout) :: ptrdy ! Salinity or V trend |
---|
99 | INTEGER , INTENT(in ) :: ktrd ! tracer trend index |
---|
100 | INTEGER , INTENT(in ) :: kt ! time step index |
---|
101 | REAL(wp) , INTENT(in ) :: p2dt ! time step [s] |
---|
102 | REAL(wp), DIMENSION(:,:) , INTENT(in ) :: kmxln ! number of t-box for the vertical average |
---|
103 | ! |
---|
104 | INTEGER :: ji, jj, jk ! dummy loop indices |
---|
105 | !!---------------------------------------------------------------------- |
---|
106 | |
---|
107 | ! !==============================! |
---|
108 | IF ( kt /= nkstp ) THEN != 1st call at kt time step =! |
---|
109 | ! !==============================! |
---|
110 | nkstp = kt |
---|
111 | |
---|
112 | |
---|
113 | ! !== reset trend arrays to zero ==! |
---|
114 | tmltrd(:,:,:) = 0._wp ; smltrd(:,:,:) = 0._wp |
---|
115 | |
---|
116 | |
---|
117 | ! |
---|
118 | wkx(:,:,:) = 0._wp !== now ML weights for vertical averaging ==! |
---|
119 | DO jk = 1, jpktrd ! initialize wkx with vertical scale factor in mixed-layer |
---|
120 | DO jj = 1,jpj |
---|
121 | DO ji = 1,jpi |
---|
122 | IF( jk - kmxln(ji,jj) < 0 ) wkx(ji,jj,jk) = e3t_n(ji,jj,jk) * tmask(ji,jj,jk) |
---|
123 | END DO |
---|
124 | END DO |
---|
125 | END DO |
---|
126 | hmxl(:,:) = 0._wp ! NOW mixed-layer depth |
---|
127 | DO jk = 1, jpktrd |
---|
128 | hmxl(:,:) = hmxl(:,:) + wkx(:,:,jk) |
---|
129 | END DO |
---|
130 | DO jk = 1, jpktrd ! integration weights |
---|
131 | wkx(:,:,jk) = wkx(:,:,jk) / MAX( 1.e-20_wp, hmxl(:,:) ) * tmask(:,:,1) |
---|
132 | END DO |
---|
133 | |
---|
134 | |
---|
135 | ! |
---|
136 | ! !== Vertically averaged T and S ==! |
---|
137 | tml(:,:) = 0._wp ; sml(:,:) = 0._wp |
---|
138 | DO jk = 1, jpktrd |
---|
139 | tml(:,:) = tml(:,:) + wkx(:,:,jk) * tsn(:,:,jk,jp_tem) |
---|
140 | sml(:,:) = sml(:,:) + wkx(:,:,jk) * tsn(:,:,jk,jp_sal) |
---|
141 | END DO |
---|
142 | ! |
---|
143 | ENDIF |
---|
144 | |
---|
145 | |
---|
146 | |
---|
147 | ! mean now trends over the now ML |
---|
148 | tmltrd(:,:,ktrd) = tmltrd(:,:,ktrd) + ptrdx(:,:,jk) * wkx(:,:,jk) ! temperature |
---|
149 | smltrd(:,:,ktrd) = smltrd(:,:,ktrd) + ptrdy(:,:,jk) * wkx(:,:,jk) ! salinity |
---|
150 | |
---|
151 | |
---|
152 | |
---|
153 | !!gm to be put juste before the output ! |
---|
154 | ! ! Lateral boundary conditions |
---|
155 | ! CALL lbc_lnk_multi( tmltrd(:,:,jl), 'T', 1. , smltrd(:,:,jl), 'T', 1. ) |
---|
156 | !!gm end |
---|
157 | |
---|
158 | |
---|
159 | |
---|
160 | SELECT CASE( ktrd ) |
---|
161 | CASE( jptra_npc ) ! non-penetrative convection: regrouped with zdf |
---|
162 | !!gm : to be completed ! |
---|
163 | ! IF( .... |
---|
164 | !!gm end |
---|
165 | CASE( jptra_zdfp ) ! iso-neutral diffusion: "pure" vertical diffusion |
---|
166 | ! ! regroup iso-neutral diffusion in one term |
---|
167 | tmltrd(:,:,jpmxl_ldf) = tmltrd(:,:,jpmxl_ldf) + ( tmltrd(:,:,jpmxl_zdf) - tmltrd(:,:,jpmxl_zdfp) ) |
---|
168 | smltrd(:,:,jpmxl_ldf) = smltrd(:,:,jpmxl_ldf) + ( smltrd(:,:,jpmxl_zdf) - smltrd(:,:,jpmxl_zdfp) ) |
---|
169 | ! ! put in zdf the dia-neutral diffusion |
---|
170 | tmltrd(:,:,jpmxl_zdf) = tmltrd(:,:,jpmxl_zdfp) |
---|
171 | smltrd(:,:,jpmxl_zdf) = smltrd(:,:,jpmxl_zdfp) |
---|
172 | IF( ln_zdfnpc ) THEN |
---|
173 | tmltrd(:,:,jpmxl_zdf) = tmltrd(:,:,jpmxl_zdf) + tmltrd(:,:,jpmxl_npc) |
---|
174 | smltrd(:,:,jpmxl_zdf) = smltrd(:,:,jpmxl_zdf) + smltrd(:,:,jpmxl_npc) |
---|
175 | ENDIF |
---|
176 | ! |
---|
177 | CASE( jptra_atf ) ! last trends of the current time step: perform the time averaging & output |
---|
178 | ! |
---|
179 | ! after ML : zhmla NB will be swaped to provide hmln and hmlb |
---|
180 | ! |
---|
181 | ! entrainement ent_1 : tb_mln - tb_mlb ==>> use previous timestep ztn_mla = tb_mln |
---|
182 | ! " " " tn_mln = tb_mlb (unfiltered tb!) |
---|
183 | ! NB: tn_mln itself comes from the 2 time step before (ta_mla) |
---|
184 | ! |
---|
185 | ! atf trend : ztbf_mln - tb_mln ==>> use previous timestep tn_mla = tb_mln |
---|
186 | ! need to compute tbf_mln, using the current tb |
---|
187 | ! which is the before fitered tracer |
---|
188 | ! |
---|
189 | ! entrainement ent_2 : zta_mla - zta_mln ==>> need to compute zta_mla and zta_mln |
---|
190 | ! |
---|
191 | ! time averaging : mean: CALL trd_mean( kt, ptrd, ptrdm ) |
---|
192 | ! and out put the starting mean value and the total trends |
---|
193 | ! (i.e. difference between starting and ending values) |
---|
194 | ! hat : CALL trd_hat ( kt, ptrd, ptrdm ) |
---|
195 | ! and output the starting hat value and the total hat trends |
---|
196 | ! |
---|
197 | ! swaps : hmlb <== hmln <== zhmla |
---|
198 | ! tb_mlb <== tn_mln <== zta_mla |
---|
199 | ! tb_mln <== ztn_mla ==>> now T over after h, need to be computed here |
---|
200 | ! to be used at next time step (unfiltered before) |
---|
201 | ! |
---|
202 | END SELECT |
---|
203 | ! |
---|
204 | END SUBROUTINE trd_tra_mxl |
---|
205 | |
---|
206 | |
---|
207 | SUBROUTINE trd_mean( kt, ptrd, ptrdm ) |
---|
208 | !!---------------------------------------------------------------------- |
---|
209 | !! *** ROUTINE trd_mean *** |
---|
210 | !! |
---|
211 | !! ** Purpose : |
---|
212 | !!---------------------------------------------------------------------- |
---|
213 | REAL(wp), DIMENSION(:,:,:), INTENT(in ) :: ptrd ! trend at kt |
---|
214 | REAL(wp), DIMENSION(:,:,:), INTENT(inout) :: ptrdm ! cumulative trends at kt |
---|
215 | INTEGER , INTENT(in ) :: kt ! time step index |
---|
216 | !!---------------------------------------------------------------------- |
---|
217 | ! |
---|
218 | IF ( kt == nn_it000 ) ptrdm(:,:,:) = 0._wp |
---|
219 | ! |
---|
220 | ptrdm(:,:,:) = ptrdm(:,:,:) + ptrd(:,:,:) |
---|
221 | ! |
---|
222 | IF ( MOD( kt - nn_it000 + 1, nn_trd ) == 0 ) THEN |
---|
223 | ! |
---|
224 | ! call iom put???? avec en argument le tableau de nom des trends? |
---|
225 | ! |
---|
226 | ENDIF |
---|
227 | ! |
---|
228 | END SUBROUTINE trd_mean |
---|
229 | |
---|
230 | |
---|
231 | SUBROUTINE trd_mxl_zint( pttrdmxl, pstrdmxl, ktrd, ctype ) |
---|
232 | !!---------------------------------------------------------------------- |
---|
233 | !! *** ROUTINE trd_mxl_zint *** |
---|
234 | !! |
---|
235 | !! ** Purpose : Compute the vertical average of the 3D fields given as arguments |
---|
236 | !! to the subroutine. This vertical average is performed from ocean |
---|
237 | !! surface down to a chosen control surface. |
---|
238 | !! |
---|
239 | !! ** Method/usage : |
---|
240 | !! The control surface can be either a mixed layer depth (time varying) |
---|
241 | !! or a fixed surface (jk level or bowl). |
---|
242 | !! Choose control surface with nn_ctls in namelist NAMTRD : |
---|
243 | !! nn_ctls = 0 : use mixed layer with density criterion |
---|
244 | !! nn_ctls = 1 : read index from file 'ctlsurf_idx' |
---|
245 | !! nn_ctls > 1 : use fixed level surface jk = nn_ctls |
---|
246 | !! Note: in the remainder of the routine, the volume between the |
---|
247 | !! surface and the control surface is called "mixed-layer" |
---|
248 | !!---------------------------------------------------------------------- |
---|
249 | INTEGER , INTENT( in ) :: ktrd ! ocean trend index |
---|
250 | CHARACTER(len=2) , INTENT( in ) :: ctype ! 2D surface/bottom or 3D interior physics |
---|
251 | REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT( in ) :: pttrdmxl ! temperature trend |
---|
252 | REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT( in ) :: pstrdmxl ! salinity trend |
---|
253 | ! |
---|
254 | INTEGER :: ji, jj, jk, isum |
---|
255 | REAL(wp), POINTER, DIMENSION(:,:) :: zvlmsk |
---|
256 | !!---------------------------------------------------------------------- |
---|
257 | |
---|
258 | CALL wrk_alloc( jpi, jpj, zvlmsk ) |
---|
259 | |
---|
260 | ! I. Definition of control surface and associated fields |
---|
261 | ! ------------------------------------------------------ |
---|
262 | ! ==> only once per time step <== |
---|
263 | |
---|
264 | IF( icount == 1 ) THEN |
---|
265 | ! |
---|
266 | |
---|
267 | !!gm BUG? |
---|
268 | !!gm CAUTION: double check the definition of nmln it is the nb of w-level, not t-level I guess |
---|
269 | |
---|
270 | |
---|
271 | ! ... Set nmxl(ji,jj) = index of first T point below control surf. or outside mixed-layer |
---|
272 | IF( nn_ctls == 0 ) THEN ! * control surface = mixed-layer with density criterion |
---|
273 | nmxl(:,:) = nmln(:,:) ! array nmln computed in zdfmxl.F90 |
---|
274 | ELSEIF( nn_ctls == 1 ) THEN ! * control surface = read index from file |
---|
275 | nmxl(:,:) = nbol(:,:) |
---|
276 | ELSEIF( nn_ctls >= 2 ) THEN ! * control surface = model level |
---|
277 | nn_ctls = MIN( nn_ctls, jpktrd - 1 ) |
---|
278 | nmxl(:,:) = nn_ctls + 1 |
---|
279 | ENDIF |
---|
280 | |
---|
281 | END IF |
---|
282 | ! |
---|
283 | CALL wrk_dealloc( jpi, jpj, zvlmsk ) |
---|
284 | ! |
---|
285 | END SUBROUTINE trd_mxl_zint |
---|
286 | |
---|
287 | |
---|
288 | SUBROUTINE trd_mxl( kt, p2dt ) |
---|
289 | !!---------------------------------------------------------------------- |
---|
290 | !! *** ROUTINE trd_mxl *** |
---|
291 | !! |
---|
292 | !! ** Purpose : Compute and cumulate the mixed layer trends over an analysis |
---|
293 | !! period, and write NetCDF outputs. |
---|
294 | !! |
---|
295 | !! ** Method/usage : |
---|
296 | !! The stored trends can be chosen twofold (according to the ln_trdmxl_instant |
---|
297 | !! logical namelist variable) : |
---|
298 | !! 1) to explain the difference between initial and final |
---|
299 | !! mixed-layer T & S (where initial and final relate to the |
---|
300 | !! current analysis window, defined by nn_trd in the namelist) |
---|
301 | !! 2) to explain the difference between the current and previous |
---|
302 | !! TIME-AVERAGED mixed-layer T & S (where time-averaging is |
---|
303 | !! performed over each analysis window). |
---|
304 | !! |
---|
305 | !! ** Consistency check : |
---|
306 | !! If the control surface is fixed ( nn_ctls > 1 ), the residual term (dh/dt |
---|
307 | !! entrainment) should be zero, at machine accuracy. Note that in the case |
---|
308 | !! of time-averaged mixed-layer fields, this residual WILL NOT BE ZERO |
---|
309 | !! over the first two analysis windows (except if restart). |
---|
310 | !! N.B. For ORCA2_LIM, use e.g. nn_trd=5, rn_ucf=1., nn_ctls=8 |
---|
311 | !! for checking residuals. |
---|
312 | !! On a NEC-SX5 computer, this typically leads to: |
---|
313 | !! O(1.e-20) temp. residuals (tml_res) when ln_trdmxl_instant=.false. |
---|
314 | !! O(1.e-21) temp. residuals (tml_res) when ln_trdmxl_instant=.true. |
---|
315 | !! |
---|
316 | !! ** Action : |
---|
317 | !! At each time step, mixed-layer averaged trends are stored in the |
---|
318 | !! tmltrd(:,:,jpmxl_xxx) array (see trdmxl_oce.F90 for definitions of jpmxl_xxx). |
---|
319 | !! This array is known when trd_mxl is called, at the end of the stp subroutine, |
---|
320 | !! except for the purely vertical K_z diffusion term, which is embedded in the |
---|
321 | !! lateral diffusion trend. |
---|
322 | !! |
---|
323 | !! In I), this K_z term is diagnosed and stored, thus its contribution is removed |
---|
324 | !! from the lateral diffusion trend. |
---|
325 | !! In II), the instantaneous mixed-layer T & S are computed, and misc. cumulative |
---|
326 | !! arrays are updated. |
---|
327 | !! In III), called only once per analysis window, we compute the total trends, |
---|
328 | !! along with the residuals and the Asselin correction terms. |
---|
329 | !! In IV), the appropriate trends are written in the trends NetCDF file. |
---|
330 | !! |
---|
331 | !! References : Vialard et al.,2001, JPO. |
---|
332 | !!---------------------------------------------------------------------- |
---|
333 | INTEGER , INTENT(in ) :: kt ! ocean time-step index |
---|
334 | REAL(wp), INTENT(in ) :: p2dt ! time step [s] |
---|
335 | ! |
---|
336 | INTEGER :: ji, jj, jk, jl, ik, it, itmod |
---|
337 | LOGICAL :: lldebug = .TRUE. |
---|
338 | REAL(wp) :: zavt, zfn, zfn2 |
---|
339 | ! ! z(ts)mltot : dT/dt over the anlysis window (including Asselin) |
---|
340 | ! ! z(ts)mlres : residual = dh/dt entrainment term |
---|
341 | REAL(wp), POINTER, DIMENSION(:,: ) :: ztmltot , zsmltot , ztmlres , zsmlres , ztmlatf , zsmlatf |
---|
342 | REAL(wp), POINTER, DIMENSION(:,: ) :: ztmltot2, zsmltot2, ztmlres2, zsmlres2, ztmlatf2, zsmlatf2, ztmltrdm2, zsmltrdm2 |
---|
343 | REAL(wp), POINTER, DIMENSION(:,:,:) :: ztmltrd2, zsmltrd2 ! only needed for mean diagnostics |
---|
344 | !!---------------------------------------------------------------------- |
---|
345 | |
---|
346 | CALL wrk_alloc( jpi, jpj, ztmltot , zsmltot , ztmlres , zsmlres , ztmlatf , zsmlatf ) |
---|
347 | CALL wrk_alloc( jpi, jpj, ztmltot2, zsmltot2, ztmlres2, zsmlres2, ztmlatf2, zsmlatf2, ztmltrdm2, zsmltrdm2 ) |
---|
348 | CALL wrk_alloc( jpi, jpj, jpltrd, ztmltrd2, zsmltrd2 ) |
---|
349 | |
---|
350 | ! ====================================================================== |
---|
351 | ! II. Cumulate the trends over the analysis window |
---|
352 | ! ====================================================================== |
---|
353 | |
---|
354 | ztmltrd2(:,:,:) = 0.e0 ; zsmltrd2(:,:,:) = 0.e0 ! <<< reset arrays to zero |
---|
355 | ztmltot2(:,:) = 0.e0 ; zsmltot2(:,:) = 0.e0 |
---|
356 | ztmlres2(:,:) = 0.e0 ; zsmlres2(:,:) = 0.e0 |
---|
357 | ztmlatf2(:,:) = 0.e0 ; zsmlatf2(:,:) = 0.e0 |
---|
358 | |
---|
359 | ! II.1 Set before values of vertically average T and S |
---|
360 | ! ---------------------------------------------------- |
---|
361 | IF( kt > nit000 ) THEN |
---|
362 | ! ... temperature ... ... salinity ... |
---|
363 | tmlb (:,:) = tml (:,:) ; smlb (:,:) = sml (:,:) |
---|
364 | tmlatfn(:,:) = tmltrd(:,:,jpmxl_atf) ; smlatfn(:,:) = smltrd(:,:,jpmxl_atf) |
---|
365 | END IF |
---|
366 | |
---|
367 | |
---|
368 | ! II.3 Initialize mixed-layer "before" arrays for the 1rst analysis window |
---|
369 | ! ------------------------------------------------------------------------ |
---|
370 | IF( kt == 2 ) THEN ! i.e. ( .NOT. ln_rstart ).AND.( kt == nit000 + 1) |
---|
371 | ! |
---|
372 | ! ... temperature ... ... salinity ... |
---|
373 | tmlbb (:,:) = tmlb (:,:) ; smlbb (:,:) = smlb (:,:) |
---|
374 | tmlbn (:,:) = tml (:,:) ; smlbn (:,:) = sml (:,:) |
---|
375 | tmlatfb(:,:) = tmlatfn(:,:) ; smlatfb(:,:) = smlatfn(:,:) |
---|
376 | |
---|
377 | tmltrd_csum_ub (:,:,:) = 0.e0 ; smltrd_csum_ub (:,:,:) = 0.e0 |
---|
378 | tmltrd_atf_sumb(:,:) = 0.e0 ; smltrd_atf_sumb(:,:) = 0.e0 |
---|
379 | |
---|
380 | hmxlbn(:,:) = hmxl(:,:) |
---|
381 | |
---|
382 | IF( ln_ctl ) THEN |
---|
383 | WRITE(numout,*) ' we reach kt == nit000 + 1 = ', nit000+1 |
---|
384 | CALL prt_ctl(tab2d_1=tmlbb , clinfo1=' tmlbb - : ', mask1=tmask, ovlap=1) |
---|
385 | CALL prt_ctl(tab2d_1=tmlbn , clinfo1=' tmlbn - : ', mask1=tmask, ovlap=1) |
---|
386 | CALL prt_ctl(tab2d_1=tmlatfb , clinfo1=' tmlatfb - : ', mask1=tmask, ovlap=1) |
---|
387 | END IF |
---|
388 | ! |
---|
389 | END IF |
---|
390 | |
---|
391 | IF( ( ln_rstart ) .AND. ( kt == nit000 ) .AND. ( ln_ctl ) ) THEN |
---|
392 | IF( ln_trdmxl_instant ) THEN |
---|
393 | WRITE(numout,*) ' restart from kt == nit000 = ', nit000 |
---|
394 | CALL prt_ctl(tab2d_1=tmlbb , clinfo1=' tmlbb - : ', mask1=tmask, ovlap=1) |
---|
395 | CALL prt_ctl(tab2d_1=tmlbn , clinfo1=' tmlbn - : ', mask1=tmask, ovlap=1) |
---|
396 | CALL prt_ctl(tab2d_1=tmlatfb , clinfo1=' tmlatfb - : ', mask1=tmask, ovlap=1) |
---|
397 | ELSE |
---|
398 | WRITE(numout,*) ' restart from kt == nit000 = ', nit000 |
---|
399 | CALL prt_ctl(tab2d_1=tmlbn , clinfo1=' tmlbn - : ', mask1=tmask, ovlap=1) |
---|
400 | CALL prt_ctl(tab2d_1=hmxlbn , clinfo1=' hmxlbn - : ', mask1=tmask, ovlap=1) |
---|
401 | CALL prt_ctl(tab2d_1=tml_sumb , clinfo1=' tml_sumb - : ', mask1=tmask, ovlap=1) |
---|
402 | CALL prt_ctl(tab2d_1=tmltrd_atf_sumb, clinfo1=' tmltrd_atf_sumb - : ', mask1=tmask, ovlap=1) |
---|
403 | CALL prt_ctl(tab3d_1=tmltrd_csum_ub , clinfo1=' tmltrd_csum_ub - : ', mask1=tmask, ovlap=1, kdim=1) |
---|
404 | END IF |
---|
405 | END IF |
---|
406 | |
---|
407 | ! II.4 Cumulated trends over the analysis period |
---|
408 | ! ---------------------------------------------- |
---|
409 | ! |
---|
410 | ! [ 1rst analysis window ] [ 2nd analysis window ] |
---|
411 | ! |
---|
412 | ! o---[--o-----o-----o-----o--]-[--o-----o-----o-----o-----o--]---o-----o--> time steps |
---|
413 | ! nn_trd 2*nn_trd etc. |
---|
414 | ! 1 2 3 4 =5 e.g. =10 |
---|
415 | ! |
---|
416 | IF( ( kt >= 2 ).OR.( ln_rstart ) ) THEN |
---|
417 | ! |
---|
418 | nmoymltrd = nmoymltrd + 1 |
---|
419 | |
---|
420 | ! ... Cumulate over BOTH physical contributions AND over time steps |
---|
421 | DO jl = 1, jpltrd |
---|
422 | tmltrdm(:,:) = tmltrdm(:,:) + tmltrd(:,:,jl) |
---|
423 | smltrdm(:,:) = smltrdm(:,:) + smltrd(:,:,jl) |
---|
424 | END DO |
---|
425 | |
---|
426 | ! ... Special handling of the Asselin trend |
---|
427 | tmlatfm(:,:) = tmlatfm(:,:) + tmlatfn(:,:) |
---|
428 | smlatfm(:,:) = smlatfm(:,:) + smlatfn(:,:) |
---|
429 | |
---|
430 | ! ... Trends associated with the time mean of the ML T/S |
---|
431 | tmltrd_sum (:,:,:) = tmltrd_sum (:,:,:) + tmltrd (:,:,:) ! tem |
---|
432 | tmltrd_csum_ln(:,:,:) = tmltrd_csum_ln(:,:,:) + tmltrd_sum(:,:,:) |
---|
433 | tml_sum (:,:) = tml_sum (:,:) + tml (:,:) |
---|
434 | smltrd_sum (:,:,:) = smltrd_sum (:,:,:) + smltrd (:,:,:) ! sal |
---|
435 | smltrd_csum_ln(:,:,:) = smltrd_csum_ln(:,:,:) + smltrd_sum(:,:,:) |
---|
436 | sml_sum (:,:) = sml_sum (:,:) + sml (:,:) |
---|
437 | hmxl_sum (:,:) = hmxl_sum (:,:) + hmxl (:,:) ! rmxl |
---|
438 | ! |
---|
439 | END IF |
---|
440 | |
---|
441 | ! ====================================================================== |
---|
442 | ! III. Prepare fields for output (get here ONCE PER ANALYSIS PERIOD) |
---|
443 | ! ====================================================================== |
---|
444 | |
---|
445 | ! Convert to appropriate physical units |
---|
446 | ! N.B. It may be useful to check IOIPSL time averaging with : |
---|
447 | ! tmltrd (:,:,:) = 1. ; smltrd (:,:,:) = 1. |
---|
448 | tmltrd(:,:,:) = tmltrd(:,:,:) * rn_ucf ! (actually needed for 1:jpltrd-1, but trdmxl(:,:,jpltrd) |
---|
449 | smltrd(:,:,:) = smltrd(:,:,:) * rn_ucf ! is no longer used, and is reset to 0. at next time step) |
---|
450 | |
---|
451 | ! define time axis |
---|
452 | it = kt |
---|
453 | itmod = kt - nit000 + 1 |
---|
454 | |
---|
455 | MODULO_NTRD : IF( MOD( itmod, nn_trd ) == 0 ) THEN ! nitend MUST be multiple of nn_trd |
---|
456 | ! |
---|
457 | ztmltot (:,:) = 0.e0 ; zsmltot (:,:) = 0.e0 ! reset arrays to zero |
---|
458 | ztmlres (:,:) = 0.e0 ; zsmlres (:,:) = 0.e0 |
---|
459 | ztmltot2(:,:) = 0.e0 ; zsmltot2(:,:) = 0.e0 |
---|
460 | ztmlres2(:,:) = 0.e0 ; zsmlres2(:,:) = 0.e0 |
---|
461 | |
---|
462 | zfn = REAL( nmoymltrd, wp ) ; zfn2 = zfn * zfn |
---|
463 | |
---|
464 | ! III.1 Prepare fields for output ("instantaneous" diagnostics) |
---|
465 | ! ------------------------------------------------------------- |
---|
466 | |
---|
467 | !-- Compute total trends |
---|
468 | ztmltot(:,:) = ( tml(:,:) - tmlbn(:,:) + tmlb(:,:) - tmlbb(:,:) ) / p2dt |
---|
469 | zsmltot(:,:) = ( sml(:,:) - smlbn(:,:) + smlb(:,:) - smlbb(:,:) ) / p2dt |
---|
470 | |
---|
471 | !-- Compute residuals |
---|
472 | ztmlres(:,:) = ztmltot(:,:) - ( tmltrdm(:,:) - tmlatfn(:,:) + tmlatfb(:,:) ) |
---|
473 | zsmlres(:,:) = zsmltot(:,:) - ( smltrdm(:,:) - smlatfn(:,:) + smlatfb(:,:) ) |
---|
474 | |
---|
475 | !-- Diagnose Asselin trend over the analysis window |
---|
476 | ztmlatf(:,:) = tmlatfm(:,:) - tmlatfn(:,:) + tmlatfb(:,:) |
---|
477 | zsmlatf(:,:) = smlatfm(:,:) - smlatfn(:,:) + smlatfb(:,:) |
---|
478 | |
---|
479 | !-- Lateral boundary conditions |
---|
480 | ! ... temperature ... ... salinity ... |
---|
481 | CALL lbc_lnk_multi( ztmltot , 'T', 1., zsmltot , 'T', 1., & |
---|
482 | & ztmlres , 'T', 1., zsmlres , 'T', 1., & |
---|
483 | & ztmlatf , 'T', 1., zsmlatf , 'T', 1. ) |
---|
484 | |
---|
485 | |
---|
486 | ! III.2 Prepare fields for output ("mean" diagnostics) |
---|
487 | ! ---------------------------------------------------- |
---|
488 | |
---|
489 | !-- Update the ML depth time sum (to build the Leap-Frog time mean) |
---|
490 | hmxl_sum(:,:) = hmxlbn(:,:) + 2 * ( hmxl_sum(:,:) - hmxl(:,:) ) + hmxl(:,:) |
---|
491 | |
---|
492 | !-- Compute temperature total trends |
---|
493 | tml_sum (:,:) = tmlbn(:,:) + 2 * ( tml_sum(:,:) - tml(:,:) ) + tml(:,:) |
---|
494 | ztmltot2(:,:) = ( tml_sum(:,:) - tml_sumb(:,:) ) / p2dt ! now in degC/s |
---|
495 | |
---|
496 | !-- Compute salinity total trends |
---|
497 | sml_sum (:,:) = smlbn(:,:) + 2 * ( sml_sum(:,:) - sml(:,:) ) + sml(:,:) |
---|
498 | zsmltot2(:,:) = ( sml_sum(:,:) - sml_sumb(:,:) ) / p2dt ! now in psu/s |
---|
499 | |
---|
500 | !-- Compute temperature residuals |
---|
501 | DO jl = 1, jpltrd |
---|
502 | ztmltrd2(:,:,jl) = tmltrd_csum_ub(:,:,jl) + tmltrd_csum_ln(:,:,jl) |
---|
503 | END DO |
---|
504 | |
---|
505 | ztmltrdm2(:,:) = 0.e0 |
---|
506 | DO jl = 1, jpltrd |
---|
507 | ztmltrdm2(:,:) = ztmltrdm2(:,:) + ztmltrd2(:,:,jl) |
---|
508 | END DO |
---|
509 | |
---|
510 | ztmlres2(:,:) = ztmltot2(:,:) - & |
---|
511 | ( ztmltrdm2(:,:) - tmltrd_sum(:,:,jpmxl_atf) + tmltrd_atf_sumb(:,:) ) |
---|
512 | |
---|
513 | !-- Compute salinity residuals |
---|
514 | DO jl = 1, jpltrd |
---|
515 | zsmltrd2(:,:,jl) = smltrd_csum_ub(:,:,jl) + smltrd_csum_ln(:,:,jl) |
---|
516 | END DO |
---|
517 | |
---|
518 | zsmltrdm2(:,:) = 0. |
---|
519 | DO jl = 1, jpltrd |
---|
520 | zsmltrdm2(:,:) = zsmltrdm2(:,:) + zsmltrd2(:,:,jl) |
---|
521 | END DO |
---|
522 | |
---|
523 | zsmlres2(:,:) = zsmltot2(:,:) - & |
---|
524 | ( zsmltrdm2(:,:) - smltrd_sum(:,:,jpmxl_atf) + smltrd_atf_sumb(:,:) ) |
---|
525 | |
---|
526 | !-- Diagnose Asselin trend over the analysis window |
---|
527 | ztmlatf2(:,:) = ztmltrd2(:,:,jpmxl_atf) - tmltrd_sum(:,:,jpmxl_atf) + tmltrd_atf_sumb(:,:) |
---|
528 | zsmlatf2(:,:) = zsmltrd2(:,:,jpmxl_atf) - smltrd_sum(:,:,jpmxl_atf) + smltrd_atf_sumb(:,:) |
---|
529 | |
---|
530 | !-- Lateral boundary conditions |
---|
531 | ! ... temperature ... ... salinity ... |
---|
532 | CALL lbc_lnk_multi( ztmltot2, 'T', 1., zsmltot2, 'T', 1., & |
---|
533 | & ztmlres2, 'T', 1., zsmlres2, 'T', 1. ) |
---|
534 | ! |
---|
535 | CALL lbc_lnk_multi( ztmltrd2(:,:,:), 'T', 1., zsmltrd2(:,:,:), 'T', 1. ) ! / in the NetCDF trends file |
---|
536 | |
---|
537 | ! III.3 Time evolution array swap |
---|
538 | ! ------------------------------- |
---|
539 | |
---|
540 | ! For T/S instantaneous diagnostics |
---|
541 | ! ... temperature ... ... salinity ... |
---|
542 | tmlbb (:,:) = tmlb (:,:) ; smlbb (:,:) = smlb (:,:) |
---|
543 | tmlbn (:,:) = tml (:,:) ; smlbn (:,:) = sml (:,:) |
---|
544 | tmlatfb(:,:) = tmlatfn(:,:) ; smlatfb(:,:) = smlatfn(:,:) |
---|
545 | |
---|
546 | ! For T mean diagnostics |
---|
547 | tmltrd_csum_ub (:,:,:) = zfn * tmltrd_sum(:,:,:) - tmltrd_csum_ln(:,:,:) |
---|
548 | tml_sumb (:,:) = tml_sum(:,:) |
---|
549 | tmltrd_atf_sumb(:,:) = tmltrd_sum(:,:,jpmxl_atf) |
---|
550 | |
---|
551 | ! For S mean diagnostics |
---|
552 | smltrd_csum_ub (:,:,:) = zfn * smltrd_sum(:,:,:) - smltrd_csum_ln(:,:,:) |
---|
553 | sml_sumb (:,:) = sml_sum(:,:) |
---|
554 | smltrd_atf_sumb(:,:) = smltrd_sum(:,:,jpmxl_atf) |
---|
555 | |
---|
556 | ! ML depth |
---|
557 | hmxlbn (:,:) = hmxl (:,:) |
---|
558 | |
---|
559 | IF( ln_ctl ) THEN |
---|
560 | IF( ln_trdmxl_instant ) THEN |
---|
561 | CALL prt_ctl(tab2d_1=tmlbb , clinfo1=' tmlbb - : ', mask1=tmask, ovlap=1) |
---|
562 | CALL prt_ctl(tab2d_1=tmlbn , clinfo1=' tmlbn - : ', mask1=tmask, ovlap=1) |
---|
563 | CALL prt_ctl(tab2d_1=tmlatfb , clinfo1=' tmlatfb - : ', mask1=tmask, ovlap=1) |
---|
564 | ELSE |
---|
565 | CALL prt_ctl(tab2d_1=tmlbn , clinfo1=' tmlbn - : ', mask1=tmask, ovlap=1) |
---|
566 | CALL prt_ctl(tab2d_1=hmxlbn , clinfo1=' hmxlbn - : ', mask1=tmask, ovlap=1) |
---|
567 | CALL prt_ctl(tab2d_1=tml_sumb , clinfo1=' tml_sumb - : ', mask1=tmask, ovlap=1) |
---|
568 | CALL prt_ctl(tab2d_1=tmltrd_atf_sumb, clinfo1=' tmltrd_atf_sumb - : ', mask1=tmask, ovlap=1) |
---|
569 | CALL prt_ctl(tab3d_1=tmltrd_csum_ub , clinfo1=' tmltrd_csum_ub - : ', mask1=tmask, ovlap=1, kdim=1) |
---|
570 | END IF |
---|
571 | END IF |
---|
572 | |
---|
573 | ! III.4 Convert to appropriate physical units |
---|
574 | ! ------------------------------------------- |
---|
575 | |
---|
576 | ! ... temperature ... ... salinity ... |
---|
577 | ztmltot (:,:) = ztmltot(:,:) * rn_ucf/zfn ; zsmltot (:,:) = zsmltot(:,:) * rn_ucf/zfn |
---|
578 | ztmlres (:,:) = ztmlres(:,:) * rn_ucf/zfn ; zsmlres (:,:) = zsmlres(:,:) * rn_ucf/zfn |
---|
579 | ztmlatf (:,:) = ztmlatf(:,:) * rn_ucf/zfn ; zsmlatf (:,:) = zsmlatf(:,:) * rn_ucf/zfn |
---|
580 | |
---|
581 | tml_sum (:,:) = tml_sum (:,:) / (2*zfn) ; sml_sum (:,:) = sml_sum (:,:) / (2*zfn) |
---|
582 | ztmltot2(:,:) = ztmltot2(:,:) * rn_ucf/zfn2 ; zsmltot2(:,:) = zsmltot2(:,:) * rn_ucf/zfn2 |
---|
583 | ztmltrd2(:,:,:) = ztmltrd2(:,:,:)* rn_ucf/zfn2 ; zsmltrd2(:,:,:) = zsmltrd2(:,:,:)* rn_ucf/zfn2 |
---|
584 | ztmlatf2(:,:) = ztmlatf2(:,:) * rn_ucf/zfn2 ; zsmlatf2(:,:) = zsmlatf2(:,:) * rn_ucf/zfn2 |
---|
585 | ztmlres2(:,:) = ztmlres2(:,:) * rn_ucf/zfn2 ; zsmlres2(:,:) = zsmlres2(:,:) * rn_ucf/zfn2 |
---|
586 | |
---|
587 | hmxl_sum(:,:) = hmxl_sum(:,:) / (2*zfn) ! similar to tml_sum and sml_sum |
---|
588 | |
---|
589 | ! * Debugging information * |
---|
590 | IF( lldebug ) THEN |
---|
591 | ! |
---|
592 | WRITE(numout,*) |
---|
593 | WRITE(numout,*) 'trd_mxl : write trends in the Mixed Layer for debugging process:' |
---|
594 | WRITE(numout,*) '~~~~~~~ ' |
---|
595 | WRITE(numout,*) ' TRA kt = ', kt, 'nmoymltrd = ', nmoymltrd |
---|
596 | WRITE(numout,*) |
---|
597 | WRITE(numout,*) ' >>>>>>>>>>>>>>>>>> TRA TEMPERATURE <<<<<<<<<<<<<<<<<<' |
---|
598 | WRITE(numout,*) ' TRA ztmlres : ', SUM(ztmlres(:,:)) |
---|
599 | WRITE(numout,*) ' TRA ztmltot : ', SUM(ztmltot(:,:)) |
---|
600 | WRITE(numout,*) ' TRA tmltrdm : ', SUM(tmltrdm(:,:)) |
---|
601 | WRITE(numout,*) ' TRA tmlatfb : ', SUM(tmlatfb(:,:)) |
---|
602 | WRITE(numout,*) ' TRA tmlatfn : ', SUM(tmlatfn(:,:)) |
---|
603 | DO jl = 1, jpltrd |
---|
604 | WRITE(numout,*) ' * TRA TREND INDEX jpmxl_xxx = jl = ', jl, & |
---|
605 | & ' tmltrd : ', SUM(tmltrd(:,:,jl)) |
---|
606 | END DO |
---|
607 | WRITE(numout,*) ' TRA ztmlres (jpi/2,jpj/2) : ', ztmlres (jpi/2,jpj/2) |
---|
608 | WRITE(numout,*) ' TRA ztmlres2(jpi/2,jpj/2) : ', ztmlres2(jpi/2,jpj/2) |
---|
609 | WRITE(numout,*) |
---|
610 | WRITE(numout,*) ' >>>>>>>>>>>>>>>>>> TRA SALINITY <<<<<<<<<<<<<<<<<<' |
---|
611 | WRITE(numout,*) ' TRA zsmlres : ', SUM(zsmlres(:,:)) |
---|
612 | WRITE(numout,*) ' TRA zsmltot : ', SUM(zsmltot(:,:)) |
---|
613 | WRITE(numout,*) ' TRA smltrdm : ', SUM(smltrdm(:,:)) |
---|
614 | WRITE(numout,*) ' TRA smlatfb : ', SUM(smlatfb(:,:)) |
---|
615 | WRITE(numout,*) ' TRA smlatfn : ', SUM(smlatfn(:,:)) |
---|
616 | DO jl = 1, jpltrd |
---|
617 | WRITE(numout,*) ' * TRA TREND INDEX jpmxl_xxx = jl = ', jl, & |
---|
618 | & ' smltrd : ', SUM(smltrd(:,:,jl)) |
---|
619 | END DO |
---|
620 | WRITE(numout,*) ' TRA zsmlres (jpi/2,jpj/2) : ', zsmlres (jpi/2,jpj/2) |
---|
621 | WRITE(numout,*) ' TRA zsmlres2(jpi/2,jpj/2) : ', zsmlres2(jpi/2,jpj/2) |
---|
622 | ! |
---|
623 | END IF |
---|
624 | ! |
---|
625 | END IF MODULO_NTRD |
---|
626 | |
---|
627 | ! ====================================================================== |
---|
628 | ! IV. Write trends in the NetCDF file |
---|
629 | ! ====================================================================== |
---|
630 | |
---|
631 | !-- Write the trends for T/S instantaneous diagnostics |
---|
632 | |
---|
633 | IF( ln_trdmxl_instant ) THEN |
---|
634 | |
---|
635 | CALL iom_put( "mxl_depth", hmxl(:,:) ) |
---|
636 | |
---|
637 | !................................. ( ML temperature ) ................................... |
---|
638 | |
---|
639 | !-- Output the fields |
---|
640 | CALL iom_put( "tml" , tml (:,:) ) |
---|
641 | CALL iom_put( "tml_tot" , ztmltot(:,:) ) |
---|
642 | CALL iom_put( "tml_res" , ztmlres(:,:) ) |
---|
643 | |
---|
644 | DO jl = 1, jpltrd - 1 |
---|
645 | CALL iom_put( trim("tml"//ctrd(jl,2)), tmltrd (:,:,jl) ) |
---|
646 | END DO |
---|
647 | |
---|
648 | CALL iom_put( trim("tml"//ctrd(jpmxl_atf,2)), ztmlatf(:,:) ) |
---|
649 | |
---|
650 | !.................................. ( ML salinity ) ..................................... |
---|
651 | |
---|
652 | !-- Output the fields |
---|
653 | CALL iom_put( "sml" , sml (:,:) ) |
---|
654 | CALL iom_put( "sml_tot", zsmltot(:,:) ) |
---|
655 | CALL iom_put( "sml_res", zsmlres(:,:) ) |
---|
656 | |
---|
657 | DO jl = 1, jpltrd - 1 |
---|
658 | CALL iom_put( trim("sml"//ctrd(jl,2)), smltrd(:,:,jl) ) |
---|
659 | END DO |
---|
660 | |
---|
661 | CALL iom_put( trim("sml"//ctrd(jpmxl_atf,2)), zsmlatf(:,:) ) |
---|
662 | |
---|
663 | |
---|
664 | |
---|
665 | ELSE !-- Write the trends for T/S mean diagnostics |
---|
666 | |
---|
667 | CALL iom_put( "mxl_depth", hmxl_sum(:,:) ) |
---|
668 | |
---|
669 | !................................. ( ML temperature ) ................................... |
---|
670 | |
---|
671 | !-- Output the fields |
---|
672 | CALL iom_put( "tml" , tml_sum (:,:) ) |
---|
673 | CALL iom_put( "tml_tot" , ztmltot2(:,:) ) |
---|
674 | CALL iom_put( "tml_res" , ztmlres2(:,:) ) |
---|
675 | |
---|
676 | DO jl = 1, jpltrd - 1 |
---|
677 | CALL iom_put( trim("tml"//ctrd(jl,2)), ztmltrd2(:,:,jl) ) |
---|
678 | END DO |
---|
679 | |
---|
680 | CALL iom_put( trim("tml"//ctrd(jpmxl_atf,2)), ztmlatf2(:,:) ) |
---|
681 | |
---|
682 | !.................................. ( ML salinity ) ..................................... |
---|
683 | |
---|
684 | !-- Output the fields |
---|
685 | CALL iom_put( "sml" , sml_sum (:,:) ) |
---|
686 | CALL iom_put( "sml_tot", zsmltot2(:,:) ) |
---|
687 | CALL iom_put( "sml_res", zsmlres2(:,:) ) |
---|
688 | |
---|
689 | DO jl = 1, jpltrd - 1 |
---|
690 | CALL iom_put( trim("sml"//ctrd(jl,2)), zsmltrd2(:,:,jl) ) |
---|
691 | END DO |
---|
692 | |
---|
693 | CALL iom_put( trim("sml"//ctrd(jpmxl_atf,2)), zsmlatf2(:,:) ) |
---|
694 | ! |
---|
695 | END IF |
---|
696 | ! |
---|
697 | |
---|
698 | IF( MOD( itmod, nn_trd ) == 0 ) THEN |
---|
699 | ! |
---|
700 | ! III.5 Reset cumulative arrays to zero |
---|
701 | ! ------------------------------------- |
---|
702 | nmoymltrd = 0 |
---|
703 | |
---|
704 | ! ... temperature ... ... salinity ... |
---|
705 | tmltrdm (:,:) = 0.e0 ; smltrdm (:,:) = 0.e0 |
---|
706 | tmlatfm (:,:) = 0.e0 ; smlatfm (:,:) = 0.e0 |
---|
707 | tml_sum (:,:) = 0.e0 ; sml_sum (:,:) = 0.e0 |
---|
708 | tmltrd_csum_ln (:,:,:) = 0.e0 ; smltrd_csum_ln (:,:,:) = 0.e0 |
---|
709 | tmltrd_sum (:,:,:) = 0.e0 ; smltrd_sum (:,:,:) = 0.e0 |
---|
710 | |
---|
711 | hmxl_sum (:,:) = 0.e0 |
---|
712 | ! |
---|
713 | END IF |
---|
714 | |
---|
715 | ! ====================================================================== |
---|
716 | ! V. Write restart file |
---|
717 | ! ====================================================================== |
---|
718 | |
---|
719 | IF( lrst_oce ) CALL trd_mxl_rst_write( kt ) |
---|
720 | |
---|
721 | CALL wrk_dealloc( jpi, jpj, ztmltot , zsmltot , ztmlres , zsmlres , ztmlatf , zsmlatf ) |
---|
722 | CALL wrk_dealloc( jpi, jpj, ztmltot2, zsmltot2, ztmlres2, zsmlres2, ztmlatf2, zsmlatf2, ztmltrdm2, zsmltrdm2 ) |
---|
723 | CALL wrk_dealloc( jpi, jpj, jpltrd, ztmltrd2, zsmltrd2 ) |
---|
724 | ! |
---|
725 | END SUBROUTINE trd_mxl |
---|
726 | |
---|
727 | |
---|
728 | SUBROUTINE trd_mxl_init |
---|
729 | !!---------------------------------------------------------------------- |
---|
730 | !! *** ROUTINE trd_mxl_init *** |
---|
731 | !! |
---|
732 | !! ** Purpose : computation of vertically integrated T and S budgets |
---|
733 | !! from ocean surface down to control surface (NetCDF output) |
---|
734 | !!---------------------------------------------------------------------- |
---|
735 | INTEGER :: jl ! dummy loop indices |
---|
736 | INTEGER :: inum ! logical unit |
---|
737 | INTEGER :: ios ! local integer |
---|
738 | REAL(wp) :: zjulian, zsto, zout |
---|
739 | CHARACTER (LEN=40) :: clop |
---|
740 | CHARACTER (LEN=12) :: clmxl, cltu, clsu |
---|
741 | !! |
---|
742 | NAMELIST/namtrd_mxl/ nn_trd , cn_trdrst_in , ln_trdmxl_restart, & |
---|
743 | & nn_ctls, cn_trdrst_out, ln_trdmxl_instant, rn_ucf, rn_rho_c |
---|
744 | !!---------------------------------------------------------------------- |
---|
745 | ! |
---|
746 | REWIND( numnam_ref ) ! Namelist namtrd_mxl in reference namelist : mixed layer trends diagnostic |
---|
747 | READ ( numnam_ref, namtrd_mxl, IOSTAT = ios, ERR = 901 ) |
---|
748 | 901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrd_mxl in reference namelist', lwp ) |
---|
749 | |
---|
750 | REWIND( numnam_cfg ) ! Namelist namtrd_mxl in configuration namelist : mixed layer trends diagnostic |
---|
751 | READ ( numnam_cfg, namtrd_mxl, IOSTAT = ios, ERR = 902 ) |
---|
752 | 902 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrd_mxl in configuration namelist', lwp ) |
---|
753 | IF(lwm) WRITE( numond, namtrd_mxl ) |
---|
754 | ! |
---|
755 | IF(lwp) THEN ! control print |
---|
756 | WRITE(numout,*) |
---|
757 | WRITE(numout,*) ' trd_mxl_init : Mixed-layer trends' |
---|
758 | WRITE(numout,*) ' ~~~~~~~~~~' |
---|
759 | WRITE(numout,*) ' Namelist namtrd : set trends parameters' |
---|
760 | WRITE(numout,*) ' frequency of trends diagnostics (glo) nn_trd = ', nn_trd |
---|
761 | WRITE(numout,*) ' density criteria used to defined the MLD rn_rho_c = ', rn_rho_c |
---|
762 | WRITE(numout,*) ' control surface type (mld) nn_ctls = ', nn_ctls |
---|
763 | WRITE(numout,*) ' restart for ML diagnostics ln_trdmxl_restart = ', ln_trdmxl_restart |
---|
764 | WRITE(numout,*) ' instantaneous or mean ML T/S ln_trdmxl_instant = ', ln_trdmxl_instant |
---|
765 | WRITE(numout,*) ' unit conversion factor rn_ucf = ', rn_ucf |
---|
766 | WRITE(numout,*) ' criteria to compute the MLD rn_rho_c = ', rn_rho_c |
---|
767 | ENDIF |
---|
768 | |
---|
769 | |
---|
770 | |
---|
771 | ! I.1 Check consistency of user defined preferences |
---|
772 | ! ------------------------------------------------- |
---|
773 | |
---|
774 | IF ( rn_rho_c /= rho_c ) CALL ctl_warn( 'Unless you have good reason to do so, you should use the value ', & |
---|
775 | & 'defined in zdfmxl.F90 module to calculate the mixed layer depth' ) |
---|
776 | |
---|
777 | IF( MOD( nitend, nn_trd ) /= 0 ) THEN |
---|
778 | WRITE(numout,cform_err) |
---|
779 | WRITE(numout,*) ' Your nitend parameter, nitend = ', nitend |
---|
780 | WRITE(numout,*) ' is no multiple of the trends diagnostics frequency ' |
---|
781 | WRITE(numout,*) ' you defined, nn_trd = ', nn_trd |
---|
782 | WRITE(numout,*) ' This will not allow you to restart from this simulation. ' |
---|
783 | WRITE(numout,*) ' You should reconsider this choice. ' |
---|
784 | WRITE(numout,*) |
---|
785 | WRITE(numout,*) ' N.B. the nitend parameter is also constrained to be a ' |
---|
786 | WRITE(numout,*) ' multiple of the nn_fsbc parameter ' |
---|
787 | nstop = nstop + 1 |
---|
788 | END IF |
---|
789 | |
---|
790 | ! ! allocate trdmxl arrays |
---|
791 | IF( trd_mxl_alloc() /= 0 ) CALL ctl_stop( 'STOP', 'trd_mxl_init : unable to allocate trdmxl arrays' ) |
---|
792 | IF( trdmxl_oce_alloc() /= 0 ) CALL ctl_stop( 'STOP', 'trd_mxl_init : unable to allocate trdmxl_oce arrays' ) |
---|
793 | |
---|
794 | |
---|
795 | |
---|
796 | nkstp = nit000 - 1 ! current time step indicator initialization |
---|
797 | |
---|
798 | |
---|
799 | |
---|
800 | |
---|
801 | ! I.2 Initialize arrays to zero or read a restart file |
---|
802 | ! ---------------------------------------------------- |
---|
803 | |
---|
804 | nmoymltrd = 0 |
---|
805 | |
---|
806 | ! ... temperature ... ... salinity ... |
---|
807 | tml (:,:) = 0.e0 ; sml (:,:) = 0.e0 ! inst. |
---|
808 | tmltrdm (:,:) = 0.e0 ; smltrdm (:,:) = 0.e0 |
---|
809 | tmlatfm (:,:) = 0.e0 ; smlatfm (:,:) = 0.e0 |
---|
810 | tml_sum (:,:) = 0.e0 ; sml_sum (:,:) = 0.e0 ! mean |
---|
811 | tmltrd_sum (:,:,:) = 0.e0 ; smltrd_sum (:,:,:) = 0.e0 |
---|
812 | tmltrd_csum_ln (:,:,:) = 0.e0 ; smltrd_csum_ln (:,:,:) = 0.e0 |
---|
813 | |
---|
814 | hmxl (:,:) = 0.e0 |
---|
815 | hmxl_sum (:,:) = 0.e0 |
---|
816 | |
---|
817 | IF( ln_rstart .AND. ln_trdmxl_restart ) THEN |
---|
818 | CALL trd_mxl_rst_read |
---|
819 | ELSE |
---|
820 | ! ... temperature ... ... salinity ... |
---|
821 | tmlb (:,:) = 0.e0 ; smlb (:,:) = 0.e0 ! inst. |
---|
822 | tmlbb (:,:) = 0.e0 ; smlbb (:,:) = 0.e0 |
---|
823 | tmlbn (:,:) = 0.e0 ; smlbn (:,:) = 0.e0 |
---|
824 | tml_sumb (:,:) = 0.e0 ; sml_sumb (:,:) = 0.e0 ! mean |
---|
825 | tmltrd_csum_ub (:,:,:) = 0.e0 ; smltrd_csum_ub (:,:,:) = 0.e0 |
---|
826 | tmltrd_atf_sumb(:,:) = 0.e0 ; smltrd_atf_sumb(:,:) = 0.e0 |
---|
827 | END IF |
---|
828 | |
---|
829 | icount = 1 ; ionce = 1 ! open specifier |
---|
830 | |
---|
831 | ! I.3 Read control surface from file ctlsurf_idx |
---|
832 | ! ---------------------------------------------- |
---|
833 | |
---|
834 | IF( nn_ctls == 1 ) THEN |
---|
835 | CALL ctl_opn( inum, 'ctlsurf_idx', 'OLD', 'UNFORMATTED', 'SEQUENTIAL', -1, numout, lwp ) |
---|
836 | READ ( inum, * ) nbol |
---|
837 | CLOSE( inum ) |
---|
838 | END IF |
---|
839 | |
---|
840 | ! ====================================================================== |
---|
841 | ! II. netCDF output initialization |
---|
842 | ! ====================================================================== |
---|
843 | |
---|
844 | ! clmxl = legend root for netCDF output |
---|
845 | IF( nn_ctls == 0 ) THEN ! control surface = mixed-layer with density criterion |
---|
846 | clmxl = 'Mixed Layer ' ! (array nmln computed in zdfmxl.F90) |
---|
847 | ELSE IF( nn_ctls == 1 ) THEN ! control surface = read index from file |
---|
848 | clmxl = ' Bowl ' |
---|
849 | ELSE IF( nn_ctls >= 2 ) THEN ! control surface = model level |
---|
850 | WRITE(clmxl,'(A10,I2,1X)') 'Levels 1 -', nn_ctls |
---|
851 | END IF |
---|
852 | |
---|
853 | |
---|
854 | |
---|
855 | ! II.3 Define the T grid trend file (nidtrd) |
---|
856 | ! ------------------------------------------ |
---|
857 | !-- Define long and short names for the NetCDF output variables |
---|
858 | ! ==> choose them according to trdmxl_oce.F90 <== |
---|
859 | |
---|
860 | ctrd(jpmxl_xad,1) = " Zonal advection" ; ctrd(jpmxl_xad,2) = "_xad" |
---|
861 | ctrd(jpmxl_yad,1) = " Meridional advection" ; ctrd(jpmxl_yad,2) = "_yad" |
---|
862 | ctrd(jpmxl_zad,1) = " Vertical advection" ; ctrd(jpmxl_zad,2) = "_zad" |
---|
863 | ctrd(jpmxl_ldf,1) = " Lateral diffusion" ; ctrd(jpmxl_ldf,2) = "_ldf" |
---|
864 | ctrd(jpmxl_for,1) = " Forcing" ; ctrd(jpmxl_for,2) = "_for" |
---|
865 | ctrd(jpmxl_zdf,1) = " Vertical diff. (Kz)" ; ctrd(jpmxl_zdf,2) = "_zdf" |
---|
866 | ctrd(jpmxl_bbc,1) = " Geothermal flux" ; ctrd(jpmxl_bbc,2) = "_bbc" |
---|
867 | ctrd(jpmxl_bbl,1) = " Adv/diff. Bottom boundary layer" ; ctrd(jpmxl_bbl,2) = "_bbl" |
---|
868 | ctrd(jpmxl_dmp,1) = " Tracer damping" ; ctrd(jpmxl_dmp,2) = "_dmp" |
---|
869 | ctrd(jpmxl_npc,1) = " Non penetrative convec. adjust." ; ctrd(jpmxl_npc,2) = "_npc" |
---|
870 | ctrd(jpmxl_atf,1) = " Asselin time filter" ; ctrd(jpmxl_atf,2) = "_atf" |
---|
871 | |
---|
872 | |
---|
873 | !-- Define physical units |
---|
874 | IF ( rn_ucf == 1. ) THEN ; cltu = "degC/s" ; clsu = "p.s.u./s" |
---|
875 | ELSEIF ( rn_ucf == 3600.*24.) THEN ; cltu = "degC/day" ; clsu = "p.s.u./day" |
---|
876 | ELSE ; cltu = "unknown?" ; clsu = "unknown?" |
---|
877 | END IF |
---|
878 | ! |
---|
879 | END SUBROUTINE trd_mxl_init |
---|
880 | |
---|
881 | !!====================================================================== |
---|
882 | END MODULE trdmxl |
---|