1 | MODULE trdtra |
---|
2 | !!====================================================================== |
---|
3 | !! *** MODULE trdtra *** |
---|
4 | !! Ocean diagnostics: ocean tracers trends pre-processing |
---|
5 | !!===================================================================== |
---|
6 | !! History : 3.3 ! 2010-06 (C. Ethe) creation for the TRA/TRC merge |
---|
7 | !! 3.5 ! 2012-02 (G. Madec) update the comments |
---|
8 | !!---------------------------------------------------------------------- |
---|
9 | |
---|
10 | !!---------------------------------------------------------------------- |
---|
11 | !! trd_tra : pre-process the tracer trends |
---|
12 | !! trd_tra_adv : transform a div(U.T) trend into a U.grad(T) trend |
---|
13 | !! trd_tra_mng : tracer trend manager: dispatch to the diagnostic modules |
---|
14 | !! trd_tra_iom : output 3D tracer trends using IOM |
---|
15 | !!---------------------------------------------------------------------- |
---|
16 | USE oce ! ocean dynamics and tracers variables |
---|
17 | USE dom_oce ! ocean domain |
---|
18 | USE sbc_oce ! surface boundary condition: ocean |
---|
19 | USE zdf_oce ! ocean vertical physics |
---|
20 | USE trd_oce ! trends: ocean variables |
---|
21 | USE trdtrc ! ocean passive mixed layer tracers trends |
---|
22 | USE trdglo ! trends: global domain averaged |
---|
23 | USE trdpen ! trends: Potential ENergy |
---|
24 | USE trdmxl ! ocean active mixed layer tracers trends |
---|
25 | USE ldftra ! ocean active tracers lateral physics |
---|
26 | USE ldfslp |
---|
27 | USE zdfddm ! vertical physics: double diffusion |
---|
28 | USE phycst ! physical constants |
---|
29 | ! |
---|
30 | USE in_out_manager ! I/O manager |
---|
31 | USE iom ! I/O manager library |
---|
32 | USE lib_mpp ! MPP library |
---|
33 | USE wrk_nemo ! Memory allocation |
---|
34 | |
---|
35 | IMPLICIT NONE |
---|
36 | PRIVATE |
---|
37 | |
---|
38 | PUBLIC trd_tra ! called by all tra_... modules |
---|
39 | |
---|
40 | REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: trdtx, trdty, trdt ! use to store the temperature trends |
---|
41 | REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: avt_evd ! store avt_evd to calculate EVD trend |
---|
42 | |
---|
43 | !! * Substitutions |
---|
44 | # include "zdfddm_substitute.h90" |
---|
45 | # include "vectopt_loop_substitute.h90" |
---|
46 | !!---------------------------------------------------------------------- |
---|
47 | !! NEMO/OPA 3.3 , NEMO Consortium (2010) |
---|
48 | !! $Id$ |
---|
49 | !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) |
---|
50 | !!---------------------------------------------------------------------- |
---|
51 | CONTAINS |
---|
52 | |
---|
53 | INTEGER FUNCTION trd_tra_alloc() |
---|
54 | !!--------------------------------------------------------------------- |
---|
55 | !! *** FUNCTION trd_tra_alloc *** |
---|
56 | !!--------------------------------------------------------------------- |
---|
57 | ALLOCATE( trdtx(jpi,jpj,jpk) , trdty(jpi,jpj,jpk) , trdt(jpi,jpj,jpk) , avt_evd(jpi,jpj,jpk), STAT= trd_tra_alloc ) |
---|
58 | ! |
---|
59 | IF( lk_mpp ) CALL mpp_sum ( trd_tra_alloc ) |
---|
60 | IF( trd_tra_alloc /= 0 ) CALL ctl_warn('trd_tra_alloc: failed to allocate arrays') |
---|
61 | END FUNCTION trd_tra_alloc |
---|
62 | |
---|
63 | |
---|
64 | SUBROUTINE trd_tra( kt, ctype, ktra, ktrd, ptrd, pun, ptra ) |
---|
65 | !!--------------------------------------------------------------------- |
---|
66 | !! *** ROUTINE trd_tra *** |
---|
67 | !! |
---|
68 | !! ** Purpose : pre-process tracer trends |
---|
69 | !! |
---|
70 | !! ** Method : - mask the trend |
---|
71 | !! - advection (ptra present) converte the incoming flux (U.T) |
---|
72 | !! into trend (U.T => -U.grat(T)=div(U.T)-T.div(U)) through a |
---|
73 | !! call to trd_tra_adv |
---|
74 | !! - 'TRA' case : regroup T & S trends |
---|
75 | !! - send the trends to trd_tra_mng (trdtrc) for further processing |
---|
76 | !!---------------------------------------------------------------------- |
---|
77 | INTEGER , INTENT(in) :: kt ! time step |
---|
78 | CHARACTER(len=3) , INTENT(in) :: ctype ! tracers trends type 'TRA'/'TRC' |
---|
79 | INTEGER , INTENT(in) :: ktra ! tracer index |
---|
80 | INTEGER , INTENT(in) :: ktrd ! tracer trend index |
---|
81 | REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(in) :: ptrd ! tracer trend or flux |
---|
82 | REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(in), OPTIONAL :: pun ! now velocity |
---|
83 | REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(in), OPTIONAL :: ptra ! now tracer variable |
---|
84 | ! |
---|
85 | INTEGER :: jk ! loop indices |
---|
86 | REAL(wp), POINTER, DIMENSION(:,:,:) :: zwt, zws, ztrdt, ztrds ! 3D workspace |
---|
87 | !!---------------------------------------------------------------------- |
---|
88 | ! |
---|
89 | CALL wrk_alloc( jpi, jpj, jpk, ztrds ) |
---|
90 | ! |
---|
91 | IF( .NOT. ALLOCATED( trdtx ) ) THEN ! allocate trdtra arrays |
---|
92 | IF( trd_tra_alloc() /= 0 ) CALL ctl_stop( 'STOP', 'trd_tra : unable to allocate arrays' ) |
---|
93 | ENDIF |
---|
94 | |
---|
95 | IF( ctype == 'TRA' .AND. ktra == jp_tem ) THEN !== Temperature trend ==! |
---|
96 | ! |
---|
97 | SELECT CASE( ktrd ) |
---|
98 | ! ! advection: transform the advective flux into a trend |
---|
99 | CASE( jptra_xad ) ; CALL trd_tra_adv( ptrd, pun, ptra, 'X', trdtx ) |
---|
100 | CASE( jptra_yad ) ; CALL trd_tra_adv( ptrd, pun, ptra, 'Y', trdty ) |
---|
101 | CASE( jptra_zad ) ; CALL trd_tra_adv( ptrd, pun, ptra, 'Z', trdt ) |
---|
102 | CASE( jptra_bbc, & ! qsr, bbc: on temperature only, send to trd_tra_mng |
---|
103 | & jptra_qsr ) ; trdt(:,:,:) = ptrd(:,:,:) * tmask(:,:,:) |
---|
104 | ztrds(:,:,:) = 0._wp |
---|
105 | CALL trd_tra_mng( trdt, ztrds, ktrd, kt ) |
---|
106 | CASE( jptra_evd ) ; avt_evd(:,:,:) = ptrd(:,:,:) * tmask(:,:,:) |
---|
107 | CASE DEFAULT ! other trends: masked trends |
---|
108 | trdt(:,:,:) = ptrd(:,:,:) * tmask(:,:,:) ! mask & store |
---|
109 | END SELECT |
---|
110 | ! |
---|
111 | ENDIF |
---|
112 | |
---|
113 | IF( ctype == 'TRA' .AND. ktra == jp_sal ) THEN !== Salinity trends ==! |
---|
114 | ! |
---|
115 | SELECT CASE( ktrd ) |
---|
116 | ! ! advection: transform the advective flux into a trend |
---|
117 | ! ! and send T & S trends to trd_tra_mng |
---|
118 | CASE( jptra_xad ) ; CALL trd_tra_adv( ptrd , pun , ptra, 'X' , ztrds ) |
---|
119 | CALL trd_tra_mng( trdtx, ztrds, ktrd, kt ) |
---|
120 | CASE( jptra_yad ) ; CALL trd_tra_adv( ptrd , pun , ptra, 'Y' , ztrds ) |
---|
121 | CALL trd_tra_mng( trdty, ztrds, ktrd, kt ) |
---|
122 | CASE( jptra_zad ) ; CALL trd_tra_adv( ptrd , pun , ptra, 'Z' , ztrds ) |
---|
123 | CALL trd_tra_mng( trdt , ztrds, ktrd, kt ) |
---|
124 | CASE( jptra_zdfp ) ! diagnose the "PURE" Kz trend (here: just before the swap) |
---|
125 | ! ! iso-neutral diffusion case otherwise jptra_zdf is "PURE" |
---|
126 | CALL wrk_alloc( jpi, jpj, jpk, zwt, zws, ztrdt ) |
---|
127 | ! |
---|
128 | zwt(:,:, 1 ) = 0._wp ; zws(:,:, 1 ) = 0._wp ! vertical diffusive fluxes |
---|
129 | zwt(:,:,jpk) = 0._wp ; zws(:,:,jpk) = 0._wp |
---|
130 | DO jk = 2, jpk |
---|
131 | zwt(:,:,jk) = avt(:,:,jk) * ( tsa(:,:,jk-1,jp_tem) - tsa(:,:,jk,jp_tem) ) / e3w_n(:,:,jk) * tmask(:,:,jk) |
---|
132 | zws(:,:,jk) = fsavs(:,:,jk) * ( tsa(:,:,jk-1,jp_sal) - tsa(:,:,jk,jp_sal) ) / e3w_n(:,:,jk) * tmask(:,:,jk) |
---|
133 | END DO |
---|
134 | ! |
---|
135 | ztrdt(:,:,jpk) = 0._wp ; ztrds(:,:,jpk) = 0._wp |
---|
136 | DO jk = 1, jpkm1 |
---|
137 | ztrdt(:,:,jk) = ( zwt(:,:,jk) - zwt(:,:,jk+1) ) / e3t_n(:,:,jk) |
---|
138 | ztrds(:,:,jk) = ( zws(:,:,jk) - zws(:,:,jk+1) ) / e3t_n(:,:,jk) |
---|
139 | END DO |
---|
140 | CALL trd_tra_mng( ztrdt, ztrds, jptra_zdfp, kt ) |
---|
141 | ! |
---|
142 | ! ! Also calculate EVD trend at this point. |
---|
143 | zwt(:,:,:) = 0._wp ; zws(:,:,:) = 0._wp ! vertical diffusive fluxes |
---|
144 | DO jk = 2, jpk |
---|
145 | zwt(:,:,jk) = avt_evd(:,:,jk) * ( tsa(:,:,jk-1,jp_tem) - tsa(:,:,jk,jp_tem) ) / e3w_n(:,:,jk) * tmask(:,:,jk) |
---|
146 | zws(:,:,jk) = avt_evd(:,:,jk) * ( tsa(:,:,jk-1,jp_sal) - tsa(:,:,jk,jp_sal) ) / e3w_n(:,:,jk) * tmask(:,:,jk) |
---|
147 | END DO |
---|
148 | ! |
---|
149 | ztrdt(:,:,jpk) = 0._wp ; ztrds(:,:,jpk) = 0._wp |
---|
150 | DO jk = 1, jpkm1 |
---|
151 | ztrdt(:,:,jk) = ( zwt(:,:,jk) - zwt(:,:,jk+1) ) / e3t_n(:,:,jk) |
---|
152 | ztrds(:,:,jk) = ( zws(:,:,jk) - zws(:,:,jk+1) ) / e3t_n(:,:,jk) |
---|
153 | END DO |
---|
154 | CALL trd_tra_mng( ztrdt, ztrds, jptra_evd, kt ) |
---|
155 | ! |
---|
156 | CALL wrk_dealloc( jpi, jpj, jpk, zwt, zws, ztrdt ) |
---|
157 | ! |
---|
158 | CASE DEFAULT ! other trends: mask and send T & S trends to trd_tra_mng |
---|
159 | ztrds(:,:,:) = ptrd(:,:,:) * tmask(:,:,:) |
---|
160 | CALL trd_tra_mng( trdt, ztrds, ktrd, kt ) |
---|
161 | END SELECT |
---|
162 | ENDIF |
---|
163 | |
---|
164 | IF( ctype == 'TRC' ) THEN !== passive tracer trend ==! |
---|
165 | ! |
---|
166 | SELECT CASE( ktrd ) |
---|
167 | ! ! advection: transform the advective flux into a masked trend |
---|
168 | CASE( jptra_xad ) ; CALL trd_tra_adv( ptrd , pun , ptra, 'X', ztrds ) |
---|
169 | CASE( jptra_yad ) ; CALL trd_tra_adv( ptrd , pun , ptra, 'Y', ztrds ) |
---|
170 | CASE( jptra_zad ) ; CALL trd_tra_adv( ptrd , pun , ptra, 'Z', ztrds ) |
---|
171 | CASE DEFAULT ! other trends: just masked |
---|
172 | ztrds(:,:,:) = ptrd(:,:,:) * tmask(:,:,:) |
---|
173 | END SELECT |
---|
174 | ! ! send trend to trd_trc |
---|
175 | CALL trd_trc( ztrds, ktra, ktrd, kt ) |
---|
176 | ! |
---|
177 | ENDIF |
---|
178 | ! |
---|
179 | CALL wrk_dealloc( jpi, jpj, jpk, ztrds ) |
---|
180 | ! |
---|
181 | END SUBROUTINE trd_tra |
---|
182 | |
---|
183 | |
---|
184 | SUBROUTINE trd_tra_adv( pf, pun, ptn, cdir, ptrd ) |
---|
185 | !!--------------------------------------------------------------------- |
---|
186 | !! *** ROUTINE trd_tra_adv *** |
---|
187 | !! |
---|
188 | !! ** Purpose : transformed a advective flux into a masked advective trends |
---|
189 | !! |
---|
190 | !! ** Method : use the following transformation: -div(U.T) = - U grad(T) + T.div(U) |
---|
191 | !! i-advective trends = -un. di-1[T] = -( di-1[fi] - tn di-1[un] ) |
---|
192 | !! j-advective trends = -un. di-1[T] = -( dj-1[fi] - tn dj-1[un] ) |
---|
193 | !! k-advective trends = -un. di+1[T] = -( dk+1[fi] - tn dk+1[un] ) |
---|
194 | !! where fi is the incoming advective flux. |
---|
195 | !!---------------------------------------------------------------------- |
---|
196 | REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(in ) :: pf ! advective flux in one direction |
---|
197 | REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(in ) :: pun ! now velocity in one direction |
---|
198 | REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(in ) :: ptn ! now or before tracer |
---|
199 | CHARACTER(len=1) , INTENT(in ) :: cdir ! X/Y/Z direction |
---|
200 | REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT( out) :: ptrd ! advective trend in one direction |
---|
201 | ! |
---|
202 | INTEGER :: ji, jj, jk ! dummy loop indices |
---|
203 | INTEGER :: ii, ij, ik ! index shift as function of the direction |
---|
204 | !!---------------------------------------------------------------------- |
---|
205 | ! |
---|
206 | SELECT CASE( cdir ) ! shift depending on the direction |
---|
207 | CASE( 'X' ) ; ii = 1 ; ij = 0 ; ik = 0 ! i-trend |
---|
208 | CASE( 'Y' ) ; ii = 0 ; ij = 1 ; ik = 0 ! j-trend |
---|
209 | CASE( 'Z' ) ; ii = 0 ; ij = 0 ; ik =-1 ! k-trend |
---|
210 | END SELECT |
---|
211 | ! |
---|
212 | ! ! set to zero uncomputed values |
---|
213 | ptrd(jpi,:,:) = 0._wp ; ptrd(1,:,:) = 0._wp |
---|
214 | ptrd(:,jpj,:) = 0._wp ; ptrd(:,1,:) = 0._wp |
---|
215 | ptrd(:,:,jpk) = 0._wp |
---|
216 | ! |
---|
217 | DO jk = 1, jpkm1 ! advective trend |
---|
218 | DO jj = 2, jpjm1 |
---|
219 | DO ji = fs_2, fs_jpim1 ! vector opt. |
---|
220 | ptrd(ji,jj,jk) = - ( pf (ji,jj,jk) - pf (ji-ii,jj-ij,jk-ik) & |
---|
221 | & - ( pun(ji,jj,jk) - pun(ji-ii,jj-ij,jk-ik) ) * ptn(ji,jj,jk) ) & |
---|
222 | & * r1_e1e2t(ji,jj) / e3t_n(ji,jj,jk) * tmask(ji,jj,jk) |
---|
223 | END DO |
---|
224 | END DO |
---|
225 | END DO |
---|
226 | ! |
---|
227 | END SUBROUTINE trd_tra_adv |
---|
228 | |
---|
229 | |
---|
230 | SUBROUTINE trd_tra_mng( ptrdx, ptrdy, ktrd, kt ) |
---|
231 | !!--------------------------------------------------------------------- |
---|
232 | !! *** ROUTINE trd_tra_mng *** |
---|
233 | !! |
---|
234 | !! ** Purpose : Dispatch all tracer trends computation, e.g. 3D output, |
---|
235 | !! integral constraints, potential energy, and/or |
---|
236 | !! mixed layer budget. |
---|
237 | !!---------------------------------------------------------------------- |
---|
238 | REAL(wp), DIMENSION(:,:,:), INTENT(inout) :: ptrdx ! Temperature or U trend |
---|
239 | REAL(wp), DIMENSION(:,:,:), INTENT(inout) :: ptrdy ! Salinity or V trend |
---|
240 | INTEGER , INTENT(in ) :: ktrd ! tracer trend index |
---|
241 | INTEGER , INTENT(in ) :: kt ! time step |
---|
242 | !!---------------------------------------------------------------------- |
---|
243 | |
---|
244 | IF( neuler == 0 .AND. kt == nit000 ) THEN ; r2dt = rdt ! = rdt (restart with Euler time stepping) |
---|
245 | ELSEIF( kt <= nit000 + 1) THEN ; r2dt = 2. * rdt ! = 2 rdt (leapfrog) |
---|
246 | ENDIF |
---|
247 | |
---|
248 | ! ! 3D output of tracers trends using IOM interface |
---|
249 | IF( ln_tra_trd ) CALL trd_tra_iom ( ptrdx, ptrdy, ktrd, kt ) |
---|
250 | |
---|
251 | ! ! Integral Constraints Properties for tracers trends !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< |
---|
252 | IF( ln_glo_trd ) CALL trd_glo( ptrdx, ptrdy, ktrd, 'TRA', kt ) |
---|
253 | |
---|
254 | ! ! Potential ENergy trends |
---|
255 | IF( ln_PE_trd ) CALL trd_pen( ptrdx, ptrdy, ktrd, kt, r2dt ) |
---|
256 | |
---|
257 | ! ! Mixed layer trends for active tracers |
---|
258 | IF( ln_tra_mxl ) THEN |
---|
259 | !----------------------------------------------------------------------------------------------- |
---|
260 | ! W.A.R.N.I.N.G : |
---|
261 | ! jptra_ldf : called by traldf.F90 |
---|
262 | ! at this stage we store: |
---|
263 | ! - the lateral geopotential diffusion (here, lateral = horizontal) |
---|
264 | ! - and the iso-neutral diffusion if activated |
---|
265 | ! jptra_zdf : called by trazdf.F90 |
---|
266 | ! * in case of iso-neutral diffusion we store the vertical diffusion component in the |
---|
267 | ! lateral trend including the K_z contrib, which will be removed later (see trd_mxl) |
---|
268 | !----------------------------------------------------------------------------------------------- |
---|
269 | |
---|
270 | SELECT CASE ( ktrd ) |
---|
271 | CASE ( jptra_xad ) ; CALL trd_mxl_zint( ptrdx, ptrdy, jpmxl_xad, '3D' ) ! zonal advection |
---|
272 | CASE ( jptra_yad ) ; CALL trd_mxl_zint( ptrdx, ptrdy, jpmxl_yad, '3D' ) ! merid. advection |
---|
273 | CASE ( jptra_zad ) ; CALL trd_mxl_zint( ptrdx, ptrdy, jpmxl_zad, '3D' ) ! vertical advection |
---|
274 | CASE ( jptra_ldf ) ; CALL trd_mxl_zint( ptrdx, ptrdy, jpmxl_ldf, '3D' ) ! lateral diffusion |
---|
275 | CASE ( jptra_bbl ) ; CALL trd_mxl_zint( ptrdx, ptrdy, jpmxl_bbl, '3D' ) ! bottom boundary layer |
---|
276 | CASE ( jptra_zdf ) |
---|
277 | IF( ln_traldf_iso ) THEN ; CALL trd_mxl_zint( ptrdx, ptrdy, jpmxl_ldf, '3D' ) ! lateral diffusion (K_z) |
---|
278 | ELSE ; CALL trd_mxl_zint( ptrdx, ptrdy, jpmxl_zdf, '3D' ) ! vertical diffusion (K_z) |
---|
279 | ENDIF |
---|
280 | CASE ( jptra_dmp ) ; CALL trd_mxl_zint( ptrdx, ptrdy, jpmxl_dmp, '3D' ) ! internal 3D restoring (tradmp) |
---|
281 | CASE ( jptra_qsr ) ; CALL trd_mxl_zint( ptrdx, ptrdy, jpmxl_for, '3D' ) ! air-sea : penetrative sol radiat |
---|
282 | CASE ( jptra_nsr ) ; ptrdx(:,:,2:jpk) = 0._wp ; ptrdy(:,:,2:jpk) = 0._wp |
---|
283 | CALL trd_mxl_zint( ptrdx, ptrdy, jpmxl_for, '2D' ) ! air-sea : non penetr sol radiation |
---|
284 | CASE ( jptra_bbc ) ; CALL trd_mxl_zint( ptrdx, ptrdy, jpmxl_bbc, '3D' ) ! bottom bound cond (geoth flux) |
---|
285 | CASE ( jptra_npc ) ; CALL trd_mxl_zint( ptrdx, ptrdy, jpmxl_npc, '3D' ) ! non penetr convect adjustment |
---|
286 | CASE ( jptra_atf ) ; CALL trd_mxl_zint( ptrdx, ptrdy, jpmxl_atf, '3D' ) ! asselin time filter (last trend) |
---|
287 | ! |
---|
288 | CALL trd_mxl( kt, r2dt ) ! trends: Mixed-layer (output) |
---|
289 | END SELECT |
---|
290 | ! |
---|
291 | ENDIF |
---|
292 | ! |
---|
293 | END SUBROUTINE trd_tra_mng |
---|
294 | |
---|
295 | |
---|
296 | SUBROUTINE trd_tra_iom( ptrdx, ptrdy, ktrd, kt ) |
---|
297 | !!--------------------------------------------------------------------- |
---|
298 | !! *** ROUTINE trd_tra_iom *** |
---|
299 | !! |
---|
300 | !! ** Purpose : output 3D tracer trends using IOM |
---|
301 | !!---------------------------------------------------------------------- |
---|
302 | REAL(wp), DIMENSION(:,:,:), INTENT(inout) :: ptrdx ! Temperature or U trend |
---|
303 | REAL(wp), DIMENSION(:,:,:), INTENT(inout) :: ptrdy ! Salinity or V trend |
---|
304 | INTEGER , INTENT(in ) :: ktrd ! tracer trend index |
---|
305 | INTEGER , INTENT(in ) :: kt ! time step |
---|
306 | !! |
---|
307 | INTEGER :: ji, jj, jk ! dummy loop indices |
---|
308 | INTEGER :: ikbu, ikbv ! local integers |
---|
309 | REAL(wp), POINTER, DIMENSION(:,:) :: z2dx, z2dy ! 2D workspace |
---|
310 | !!---------------------------------------------------------------------- |
---|
311 | ! |
---|
312 | !!gm Rq: mask the trends already masked in trd_tra, but lbc_lnk should probably be added |
---|
313 | ! |
---|
314 | ! Trends evaluated every time step that could go to the standard T file and can be output every ts into a 1ts file if 1ts output is selected |
---|
315 | SELECT CASE( ktrd ) |
---|
316 | ! This total trend is done every time step |
---|
317 | CASE( jptra_tot ) ; CALL iom_put( "ttrd_tot" , ptrdx ) ! model total trend |
---|
318 | CALL iom_put( "strd_tot" , ptrdy ) |
---|
319 | END SELECT |
---|
320 | |
---|
321 | ! These trends are done every second time step. When 1ts output is selected must go different (2ts) file from standard T-file |
---|
322 | IF( MOD( kt, 2 ) == 0 ) THEN |
---|
323 | SELECT CASE( ktrd ) |
---|
324 | CASE( jptra_xad ) ; CALL iom_put( "ttrd_xad" , ptrdx ) ! x- horizontal advection |
---|
325 | CALL iom_put( "strd_xad" , ptrdy ) |
---|
326 | CASE( jptra_yad ) ; CALL iom_put( "ttrd_yad" , ptrdx ) ! y- horizontal advection |
---|
327 | CALL iom_put( "strd_yad" , ptrdy ) |
---|
328 | CASE( jptra_zad ) ; CALL iom_put( "ttrd_zad" , ptrdx ) ! z- vertical advection |
---|
329 | CALL iom_put( "strd_zad" , ptrdy ) |
---|
330 | IF( ln_linssh ) THEN ! cst volume : adv flux through z=0 surface |
---|
331 | CALL wrk_alloc( jpi, jpj, z2dx, z2dy ) |
---|
332 | z2dx(:,:) = wn(:,:,1) * tsn(:,:,1,jp_tem) / e3t_n(:,:,1) |
---|
333 | z2dy(:,:) = wn(:,:,1) * tsn(:,:,1,jp_sal) / e3t_n(:,:,1) |
---|
334 | CALL iom_put( "ttrd_sad", z2dx ) |
---|
335 | CALL iom_put( "strd_sad", z2dy ) |
---|
336 | CALL wrk_dealloc( jpi, jpj, z2dx, z2dy ) |
---|
337 | ENDIF |
---|
338 | CASE( jptra_totad ) ; CALL iom_put( "ttrd_totad" , ptrdx ) ! total advection |
---|
339 | CALL iom_put( "strd_totad" , ptrdy ) |
---|
340 | CASE( jptra_ldf ) ; CALL iom_put( "ttrd_ldf" , ptrdx ) ! lateral diffusion |
---|
341 | CALL iom_put( "strd_ldf" , ptrdy ) |
---|
342 | CASE( jptra_zdf ) ; CALL iom_put( "ttrd_zdf" , ptrdx ) ! vertical diffusion (including Kz contribution) |
---|
343 | CALL iom_put( "strd_zdf" , ptrdy ) |
---|
344 | CASE( jptra_zdfp ) ; CALL iom_put( "ttrd_zdfp", ptrdx ) ! PURE vertical diffusion (no isoneutral contribution) |
---|
345 | CALL iom_put( "strd_zdfp", ptrdy ) |
---|
346 | CASE( jptra_evd ) ; CALL iom_put( "ttrd_evd", ptrdx ) ! EVD trend (convection) |
---|
347 | CALL iom_put( "strd_evd", ptrdy ) |
---|
348 | CASE( jptra_dmp ) ; CALL iom_put( "ttrd_dmp" , ptrdx ) ! internal restoring (damping) |
---|
349 | CALL iom_put( "strd_dmp" , ptrdy ) |
---|
350 | CASE( jptra_bbl ) ; CALL iom_put( "ttrd_bbl" , ptrdx ) ! bottom boundary layer |
---|
351 | CALL iom_put( "strd_bbl" , ptrdy ) |
---|
352 | CASE( jptra_npc ) ; CALL iom_put( "ttrd_npc" , ptrdx ) ! static instability mixing |
---|
353 | CALL iom_put( "strd_npc" , ptrdy ) |
---|
354 | CASE( jptra_bbc ) ; CALL iom_put( "ttrd_bbc" , ptrdx ) ! geothermal heating (only on temperature) |
---|
355 | CASE( jptra_nsr ) ; CALL iom_put( "ttrd_qns" , ptrdx(:,:,1) ) ! surface forcing + runoff (ln_rnf=T) |
---|
356 | CALL iom_put( "strd_cdt" , ptrdy(:,:,1) ) ! output as 2D surface fields |
---|
357 | CASE( jptra_qsr ) ; CALL iom_put( "ttrd_qsr" , ptrdx ) ! penetrative solar radiat. (only on temperature) |
---|
358 | END SELECT |
---|
359 | ! the Asselin filter trend is also every other time step but needs to be lagged one time step |
---|
360 | ! Even when 1ts output is selected can go to the same (2ts) file as the trends plotted every even time step. |
---|
361 | ELSE IF( MOD( kt, 2 ) == 1 ) THEN |
---|
362 | SELECT CASE( ktrd ) |
---|
363 | CASE( jptra_atf ) ; CALL iom_put( "ttrd_atf" , ptrdx ) ! asselin time Filter |
---|
364 | CALL iom_put( "strd_atf" , ptrdy ) |
---|
365 | END SELECT |
---|
366 | END IF |
---|
367 | ! |
---|
368 | END SUBROUTINE trd_tra_iom |
---|
369 | |
---|
370 | !!====================================================================== |
---|
371 | END MODULE trdtra |
---|