1 | MODULE trcdmp |
---|
2 | !!====================================================================== |
---|
3 | !! *** MODULE trcdmp *** |
---|
4 | !! Ocean physics: internal restoring trend on passive tracers |
---|
5 | !!====================================================================== |
---|
6 | !! History : OPA ! 1991-03 (O. Marti, G. Madec) Original code |
---|
7 | !! ! 1996-01 (G. Madec) statement function for e3 |
---|
8 | !! ! 1997-05 (H. Loukos) adapted for passive tracers |
---|
9 | !! NEMO 9.0 ! 2004-03 (C. Ethe) free form + modules |
---|
10 | !! 3.2 ! 2007-02 (C. Deltel) Diagnose ML trends for passive tracers |
---|
11 | !! 3.3 ! 2010-06 (C. Ethe, G. Madec) merge TRA-TRC |
---|
12 | !!---------------------------------------------------------------------- |
---|
13 | #if defined key_top |
---|
14 | !!---------------------------------------------------------------------- |
---|
15 | !! trc_dmp : update the tracer trend with the internal damping |
---|
16 | !! trc_dmp_init : initialization, namlist read, parameters control |
---|
17 | !!---------------------------------------------------------------------- |
---|
18 | USE oce_trc ! ocean dynamics and tracers variables |
---|
19 | USE trc ! ocean passive tracers variables |
---|
20 | USE trcnam_trp ! passive tracers transport namelist variables |
---|
21 | USE trcdta |
---|
22 | USE tradmp |
---|
23 | USE prtctl_trc ! Print control for debbuging |
---|
24 | USE trdtra |
---|
25 | USE trd_oce |
---|
26 | USE iom |
---|
27 | |
---|
28 | IMPLICIT NONE |
---|
29 | PRIVATE |
---|
30 | |
---|
31 | PUBLIC trc_dmp ! routine called by step.F90 |
---|
32 | PUBLIC trc_dmp_clo ! routine called by step.F90 |
---|
33 | PUBLIC trc_dmp_alloc ! routine called by nemogcm.F90 |
---|
34 | |
---|
35 | REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: restotr ! restoring coeff. on tracers (s-1) |
---|
36 | |
---|
37 | INTEGER, PARAMETER :: npncts = 8 ! number of closed sea |
---|
38 | INTEGER, DIMENSION(npncts) :: nctsi1, nctsj1 ! south-west closed sea limits (i,j) |
---|
39 | INTEGER, DIMENSION(npncts) :: nctsi2, nctsj2 ! north-east closed sea limits (i,j) |
---|
40 | |
---|
41 | !! * Substitutions |
---|
42 | # include "top_substitute.h90" |
---|
43 | !!---------------------------------------------------------------------- |
---|
44 | !! NEMO/TOP 3.3 , NEMO Consortium (2010) |
---|
45 | !! $Id: trcdmp.F90 6308 2016-02-12 11:32:54Z cetlod $ |
---|
46 | !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) |
---|
47 | !!---------------------------------------------------------------------- |
---|
48 | CONTAINS |
---|
49 | |
---|
50 | INTEGER FUNCTION trc_dmp_alloc() |
---|
51 | !!---------------------------------------------------------------------- |
---|
52 | !! *** ROUTINE trc_dmp_alloc *** |
---|
53 | !!---------------------------------------------------------------------- |
---|
54 | ALLOCATE( restotr(jpi,jpj,jpk) , STAT=trc_dmp_alloc ) |
---|
55 | ! |
---|
56 | IF( trc_dmp_alloc /= 0 ) CALL ctl_warn('trc_dmp_alloc: failed to allocate array') |
---|
57 | ! |
---|
58 | END FUNCTION trc_dmp_alloc |
---|
59 | |
---|
60 | |
---|
61 | SUBROUTINE trc_dmp( kt ) |
---|
62 | !!---------------------------------------------------------------------- |
---|
63 | !! *** ROUTINE trc_dmp *** |
---|
64 | !! |
---|
65 | !! ** Purpose : Compute the passive tracer trend due to a newtonian damping |
---|
66 | !! of the tracer field towards given data field and add it to the |
---|
67 | !! general tracer trends. |
---|
68 | !! |
---|
69 | !! ** Method : Newtonian damping towards trdta computed |
---|
70 | !! and add to the general tracer trends: |
---|
71 | !! trn = tra + restotr * (trdta - trb) |
---|
72 | !! The trend is computed either throughout the water column |
---|
73 | !! (nlmdmptr=0) or in area of weak vertical mixing (nlmdmptr=1) or |
---|
74 | !! below the well mixed layer (nlmdmptr=2) |
---|
75 | !! |
---|
76 | !! ** Action : - update the tracer trends tra with the newtonian |
---|
77 | !! damping trends. |
---|
78 | !! - save the trends ('key_trdmxl_trc') |
---|
79 | !!---------------------------------------------------------------------- |
---|
80 | !! |
---|
81 | INTEGER, INTENT( in ) :: kt ! ocean time-step index |
---|
82 | !! |
---|
83 | INTEGER :: ji, jj, jk, jn, jl ! dummy loop indices |
---|
84 | REAL(wp) :: ztra ! temporary scalars |
---|
85 | CHARACTER (len=22) :: charout |
---|
86 | REAL(wp), POINTER, DIMENSION(:,:,:) :: ztrtrd |
---|
87 | REAL(wp), POINTER, DIMENSION(:,:,:) :: ztrcdta ! 3D workspace |
---|
88 | !!---------------------------------------------------------------------- |
---|
89 | ! |
---|
90 | IF( nn_timing == 1 ) CALL timing_start('trc_dmp') |
---|
91 | ! |
---|
92 | ! 0. Initialization (first time-step only) |
---|
93 | ! -------------- |
---|
94 | IF( kt == nittrc000 ) CALL trc_dmp_init |
---|
95 | |
---|
96 | IF( l_trdtrc ) CALL wrk_alloc( jpi, jpj, jpk, ztrtrd ) ! temporary save of trends |
---|
97 | ! |
---|
98 | IF( nb_trcdta > 0 ) THEN ! Initialisation of tracer from a file that may also be used for damping |
---|
99 | ! |
---|
100 | CALL wrk_alloc( jpi, jpj, jpk, ztrcdta ) ! Memory allocation |
---|
101 | ! ! =========== |
---|
102 | DO jn = 1, jptra ! tracer loop |
---|
103 | ! ! =========== |
---|
104 | IF( l_trdtrc ) ztrtrd(:,:,:) = tra(:,:,:,jn) ! save trends |
---|
105 | ! |
---|
106 | IF( ln_trc_ini(jn) ) THEN ! update passive tracers arrays with input data read from file |
---|
107 | |
---|
108 | jl = n_trc_index(jn) |
---|
109 | CALL trc_dta( kt, sf_trcdta(jl) ) ! read tracer data at nit000 |
---|
110 | ztrcdta(:,:,:) = sf_trcdta(jl)%fnow(:,:,:) * tmask(:,:,:) * rf_trfac(jl) |
---|
111 | |
---|
112 | SELECT CASE ( nn_zdmp_tr ) |
---|
113 | ! |
---|
114 | CASE( 0 ) !== newtonian damping throughout the water column ==! |
---|
115 | DO jk = 1, jpkm1 |
---|
116 | DO jj = 2, jpjm1 |
---|
117 | DO ji = fs_2, fs_jpim1 ! vector opt. |
---|
118 | ztra = restotr(ji,jj,jk) * ( ztrcdta(ji,jj,jk) - trb(ji,jj,jk,jn) ) |
---|
119 | tra(ji,jj,jk,jn) = tra(ji,jj,jk,jn) + ztra |
---|
120 | END DO |
---|
121 | END DO |
---|
122 | END DO |
---|
123 | ! |
---|
124 | CASE ( 1 ) !== no damping in the turbocline (avt > 5 cm2/s) ==! |
---|
125 | DO jk = 1, jpkm1 |
---|
126 | DO jj = 2, jpjm1 |
---|
127 | DO ji = fs_2, fs_jpim1 ! vector opt. |
---|
128 | IF( avt(ji,jj,jk) <= 5.e-4_wp ) THEN |
---|
129 | ztra = restotr(ji,jj,jk) * ( ztrcdta(ji,jj,jk) - trb(ji,jj,jk,jn) ) |
---|
130 | tra(ji,jj,jk,jn) = tra(ji,jj,jk,jn) + ztra |
---|
131 | ENDIF |
---|
132 | END DO |
---|
133 | END DO |
---|
134 | END DO |
---|
135 | ! |
---|
136 | CASE ( 2 ) !== no damping in the mixed layer ==! |
---|
137 | DO jk = 1, jpkm1 |
---|
138 | DO jj = 2, jpjm1 |
---|
139 | DO ji = fs_2, fs_jpim1 ! vector opt. |
---|
140 | IF( fsdept(ji,jj,jk) >= hmlp (ji,jj) ) THEN |
---|
141 | ztra = restotr(ji,jj,jk) * ( ztrcdta(ji,jj,jk) - trb(ji,jj,jk,jn) ) |
---|
142 | tra(ji,jj,jk,jn) = tra(ji,jj,jk,jn) + ztra |
---|
143 | END IF |
---|
144 | END DO |
---|
145 | END DO |
---|
146 | END DO |
---|
147 | ! |
---|
148 | END SELECT |
---|
149 | ! |
---|
150 | ENDIF |
---|
151 | ! |
---|
152 | IF( l_trdtrc ) THEN |
---|
153 | ztrtrd(:,:,:) = tra(:,:,:,jn) - ztrtrd(:,:,:) |
---|
154 | CALL trd_tra( kt, 'TRC', jn, jptra_dmp, ztrtrd ) |
---|
155 | END IF |
---|
156 | ! ! =========== |
---|
157 | END DO ! tracer loop |
---|
158 | ! ! =========== |
---|
159 | CALL wrk_dealloc( jpi, jpj, jpk, ztrcdta ) |
---|
160 | ENDIF |
---|
161 | ! |
---|
162 | IF( l_trdtrc ) CALL wrk_dealloc( jpi, jpj, jpk, ztrtrd ) |
---|
163 | ! ! print mean trends (used for debugging) |
---|
164 | IF( ln_ctl ) THEN |
---|
165 | WRITE(charout, FMT="('dmp ')") ; CALL prt_ctl_trc_info(charout) |
---|
166 | CALL prt_ctl_trc( tab4d=tra, mask=tmask, clinfo=ctrcnm, clinfo2='trd' ) |
---|
167 | ENDIF |
---|
168 | ! |
---|
169 | IF( nn_timing == 1 ) CALL timing_stop('trc_dmp') |
---|
170 | ! |
---|
171 | END SUBROUTINE trc_dmp |
---|
172 | |
---|
173 | SUBROUTINE trc_dmp_clo( kt ) |
---|
174 | !!--------------------------------------------------------------------- |
---|
175 | !! *** ROUTINE trc_dmp_clo *** |
---|
176 | !! |
---|
177 | !! ** Purpose : Closed sea domain initialization |
---|
178 | !! |
---|
179 | !! ** Method : if a closed sea is located only in a model grid point |
---|
180 | !! we restore to initial data |
---|
181 | !! |
---|
182 | !! ** Action : nctsi1(), nctsj1() : south-west closed sea limits (i,j) |
---|
183 | !! nctsi2(), nctsj2() : north-east Closed sea limits (i,j) |
---|
184 | !!---------------------------------------------------------------------- |
---|
185 | INTEGER, INTENT( in ) :: kt ! ocean time-step index |
---|
186 | ! |
---|
187 | INTEGER :: ji , jj, jk, jn, jl, jc ! dummy loop indicesa |
---|
188 | INTEGER :: isrow ! local index |
---|
189 | |
---|
190 | !!---------------------------------------------------------------------- |
---|
191 | |
---|
192 | IF( kt == nit000 ) THEN |
---|
193 | ! initial values |
---|
194 | nctsi1(:) = 1 ; nctsi2(:) = 1 |
---|
195 | nctsj1(:) = 1 ; nctsj2(:) = 1 |
---|
196 | |
---|
197 | ! set the closed seas (in data domain indices) |
---|
198 | ! ------------------- |
---|
199 | |
---|
200 | IF( cp_cfg == "orca" ) THEN |
---|
201 | ! |
---|
202 | SELECT CASE ( jp_cfg ) |
---|
203 | ! ! ======================= |
---|
204 | CASE ( 1 ) ! eORCA_R1 configuration |
---|
205 | ! ! ======================= |
---|
206 | isrow = 332 - jpjglo |
---|
207 | ! |
---|
208 | ! Caspian Sea |
---|
209 | nctsi1(1) = 332 ; nctsj1(1) = 243 - isrow |
---|
210 | nctsi2(1) = 344 ; nctsj2(1) = 275 - isrow |
---|
211 | ! ! Lake Superior |
---|
212 | nctsi1(2) = 198 ; nctsj1(2) = 256 - isrow |
---|
213 | nctsi2(2) = 204 ; nctsj2(2) = 262 - isrow |
---|
214 | ! ! Lake Michigan |
---|
215 | nctsi1(3) = 199 ; nctsj1(3) = 248 - isrow |
---|
216 | nctsi2(3) = 203 ; nctsj2(3) = 256 - isrow |
---|
217 | ! ! Lake Huron |
---|
218 | nctsi1(4) = 204 ; nctsj1(4) = 252 - isrow |
---|
219 | nctsi2(4) = 209 ; nctsj2(4) = 255 - isrow |
---|
220 | ! ! Lake Erie |
---|
221 | nctsi1(5) = 206 ; nctsj1(5) = 249 - isrow |
---|
222 | nctsi2(5) = 209 ; nctsj2(5) = 251 - isrow |
---|
223 | ! ! Lake Ontario |
---|
224 | nctsi1(6) = 210 ; nctsj1(6) = 252 - isrow |
---|
225 | nctsi2(6) = 211 ; nctsj2(6) = 252 - isrow |
---|
226 | ! ! Victoria Lake |
---|
227 | nctsi1(7) = 321 ; nctsj1(7) = 180 - isrow |
---|
228 | nctsi2(7) = 322 ; nctsj2(7) = 189 - isrow |
---|
229 | ! ! Baltic Sea |
---|
230 | nctsi1(8) = 297 ; nctsj1(8) = 270 - isrow |
---|
231 | nctsi2(8) = 308 ; nctsj2(8) = 293 - isrow |
---|
232 | |
---|
233 | ! ! ======================= |
---|
234 | CASE ( 2 ) ! ORCA_R2 configuration |
---|
235 | ! ! ======================= |
---|
236 | ! ! Caspian Sea |
---|
237 | nctsi1(1) = 11 ; nctsj1(1) = 103 |
---|
238 | nctsi2(1) = 17 ; nctsj2(1) = 112 |
---|
239 | ! ! Great North American Lakes |
---|
240 | nctsi1(2) = 97 ; nctsj1(2) = 107 |
---|
241 | nctsi2(2) = 103 ; nctsj2(2) = 111 |
---|
242 | ! ! Black Sea 1 : west part of the Black Sea |
---|
243 | nctsi1(3) = 174 ; nctsj1(3) = 107 |
---|
244 | nctsi2(3) = 181 ; nctsj2(3) = 112 |
---|
245 | ! ! Black Sea 2 : est part of the Black Sea |
---|
246 | nctsi1(4) = 2 ; nctsj1(4) = 107 |
---|
247 | nctsi2(4) = 6 ; nctsj2(4) = 112 |
---|
248 | ! ! Baltic Sea |
---|
249 | nctsi1(5) = 145 ; nctsj1(5) = 116 |
---|
250 | nctsi2(5) = 150 ; nctsj2(5) = 126 |
---|
251 | ! ! ======================= |
---|
252 | CASE ( 4 ) ! ORCA_R4 configuration |
---|
253 | ! ! ======================= |
---|
254 | ! ! Caspian Sea |
---|
255 | nctsi1(1) = 4 ; nctsj1(1) = 53 |
---|
256 | nctsi2(1) = 4 ; nctsj2(1) = 56 |
---|
257 | ! ! Great North American Lakes |
---|
258 | nctsi1(2) = 49 ; nctsj1(2) = 55 |
---|
259 | nctsi2(2) = 51 ; nctsj2(2) = 56 |
---|
260 | ! ! Black Sea |
---|
261 | nctsi1(3) = 88 ; nctsj1(3) = 55 |
---|
262 | nctsi2(3) = 91 ; nctsj2(3) = 56 |
---|
263 | ! ! Baltic Sea |
---|
264 | nctsi1(4) = 75 ; nctsj1(4) = 59 |
---|
265 | nctsi2(4) = 76 ; nctsj2(4) = 61 |
---|
266 | ! ! ======================= |
---|
267 | CASE ( 025 ) ! ORCA_R025 configuration |
---|
268 | ! ! ======================= |
---|
269 | ! Caspian + Aral sea |
---|
270 | nctsi1(1) = 1330 ; nctsj1(1) = 645 |
---|
271 | nctsi2(1) = 1400 ; nctsj2(1) = 795 |
---|
272 | ! ! Azov Sea |
---|
273 | nctsi1(2) = 1284 ; nctsj1(2) = 722 |
---|
274 | nctsi2(2) = 1304 ; nctsj2(2) = 747 |
---|
275 | ! |
---|
276 | END SELECT |
---|
277 | ! |
---|
278 | ENDIF |
---|
279 | ! |
---|
280 | |
---|
281 | ! convert the position in local domain indices |
---|
282 | ! -------------------------------------------- |
---|
283 | DO jc = 1, npncts |
---|
284 | nctsi1(jc) = mi0( nctsi1(jc) ) |
---|
285 | nctsj1(jc) = mj0( nctsj1(jc) ) |
---|
286 | |
---|
287 | nctsi2(jc) = mi1( nctsi2(jc) ) |
---|
288 | nctsj2(jc) = mj1( nctsj2(jc) ) |
---|
289 | END DO |
---|
290 | ! |
---|
291 | ENDIF |
---|
292 | |
---|
293 | ! Restore close seas values to initial data |
---|
294 | IF( ln_trcdta .AND. nb_trcdta > 0 ) THEN ! Initialisation of tracer from a file that may also be used for damping |
---|
295 | ! |
---|
296 | IF(lwp) WRITE(numout,*) |
---|
297 | IF(lwp) WRITE(numout,*) ' trc_dmp_clo : Restoring of nutrients on close seas at time-step kt = ', kt |
---|
298 | IF(lwp) WRITE(numout,*) |
---|
299 | ! |
---|
300 | DO jn = 1, jptra |
---|
301 | IF( ln_trc_ini(jn) ) THEN ! update passive tracers arrays with input data read from file |
---|
302 | jl = n_trc_index(jn) |
---|
303 | CALL trc_dta( kt, sf_trcdta(jl) ) ! read tracer data at nit000 |
---|
304 | DO jc = 1, npncts |
---|
305 | DO jk = 1, jpkm1 |
---|
306 | DO jj = nctsj1(jc), nctsj2(jc) |
---|
307 | DO ji = nctsi1(jc), nctsi2(jc) |
---|
308 | trn(ji,jj,jk,jn) = sf_trcdta(jl)%fnow(ji,jj,jk) * tmask(ji,jj,jk) * rf_trfac(jl) |
---|
309 | trb(ji,jj,jk,jn) = trn(ji,jj,jk,jn) |
---|
310 | ENDDO |
---|
311 | ENDDO |
---|
312 | ENDDO |
---|
313 | ENDDO |
---|
314 | ENDIF |
---|
315 | ENDDO |
---|
316 | ! |
---|
317 | ENDIF |
---|
318 | ! |
---|
319 | END SUBROUTINE trc_dmp_clo |
---|
320 | |
---|
321 | |
---|
322 | SUBROUTINE trc_dmp_init |
---|
323 | !!---------------------------------------------------------------------- |
---|
324 | !! *** ROUTINE trc_dmp_init *** |
---|
325 | !! |
---|
326 | !! ** Purpose : Initialization for the newtonian damping |
---|
327 | !! |
---|
328 | !! ** Method : read the nammbf namelist and check the parameters |
---|
329 | !! called by trc_dmp at the first timestep (nittrc000) |
---|
330 | !!---------------------------------------------------------------------- |
---|
331 | ! |
---|
332 | INTEGER :: imask !local file handle |
---|
333 | |
---|
334 | IF( nn_timing == 1 ) CALL timing_start('trc_dmp_init') |
---|
335 | ! |
---|
336 | |
---|
337 | IF( lzoom ) nn_zdmp_tr = 0 ! restoring to climatology at closed north or south boundaries |
---|
338 | SELECT CASE ( nn_zdmp_tr ) |
---|
339 | CASE ( 0 ) ; IF(lwp) WRITE(numout,*) ' tracer damping throughout the water column' |
---|
340 | CASE ( 1 ) ; IF(lwp) WRITE(numout,*) ' no tracer damping in the turbocline (avt > 5 cm2/s)' |
---|
341 | CASE ( 2 ) ; IF(lwp) WRITE(numout,*) ' no tracer damping in the mixed layer' |
---|
342 | CASE DEFAULT |
---|
343 | WRITE(ctmp1,*) 'bad flag value for nn_zdmp_tr = ', nn_zdmp_tr |
---|
344 | CALL ctl_stop(ctmp1) |
---|
345 | END SELECT |
---|
346 | |
---|
347 | IF( .NOT. ln_tradmp ) & |
---|
348 | & CALL ctl_stop( 'passive trace damping need key_tradmp to compute damping coef.' ) |
---|
349 | ! |
---|
350 | ! ! Read damping coefficients from file |
---|
351 | !Read in mask from file |
---|
352 | CALL iom_open ( cn_resto_tr, imask) |
---|
353 | CALL iom_get ( imask, jpdom_autoglo, 'resto', restotr) |
---|
354 | CALL iom_close( imask ) |
---|
355 | ! |
---|
356 | IF( nn_timing == 1 ) CALL timing_stop('trc_dmp_init') |
---|
357 | ! |
---|
358 | END SUBROUTINE trc_dmp_init |
---|
359 | |
---|
360 | #else |
---|
361 | !!---------------------------------------------------------------------- |
---|
362 | !! Dummy module : No passive tracer |
---|
363 | !!---------------------------------------------------------------------- |
---|
364 | CONTAINS |
---|
365 | SUBROUTINE trc_dmp( kt ) ! Empty routine |
---|
366 | INTEGER, INTENT(in) :: kt |
---|
367 | WRITE(*,*) 'trc_dmp: You should not have seen this print! error?', kt |
---|
368 | END SUBROUTINE trc_dmp |
---|
369 | #endif |
---|
370 | |
---|
371 | |
---|
372 | !!====================================================================== |
---|
373 | END MODULE trcdmp |
---|