New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
trcdmp.F90 in NEMO/branches/2020/dev_r12563_ASINTER-06_ABL_improvement/src/TOP/TRP – NEMO

source: NEMO/branches/2020/dev_r12563_ASINTER-06_ABL_improvement/src/TOP/TRP/trcdmp.F90 @ 12808

Last change on this file since 12808 was 12377, checked in by acc, 4 years ago

The big one. Merging all 2019 developments from the option 1 branch back onto the trunk.

This changeset reproduces 2019/dev_r11943_MERGE_2019 on the trunk using a 2-URL merge
onto a working copy of the trunk. I.e.:

svn merge --ignore-ancestry \

svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/trunk \
svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/branches/2019/dev_r11943_MERGE_2019 ./

The --ignore-ancestry flag avoids problems that may otherwise arise from the fact that
the merge history been trunk and branch may have been applied in a different order but
care has been taken before this step to ensure that all applicable fixes and updates
are present in the merge branch.

The trunk state just before this step has been branched to releases/release-4.0-HEAD
and that branch has been immediately tagged as releases/release-4.0.2. Any fixes
or additions in response to tickets on 4.0, 4.0.1 or 4.0.2 should be done on
releases/release-4.0-HEAD. From now on future 'point' releases (e.g. 4.0.2) will
remain unchanged with periodic releases as needs demand. Note release-4.0-HEAD is a
transitional naming convention. Future full releases, say 4.2, will have a release-4.2
branch which fulfills this role and the first point release (e.g. 4.2.0) will be made
immediately following the release branch creation.

2020 developments can be started from any trunk revision later than this one.

  • Property svn:keywords set to Id
File size: 18.2 KB
Line 
1MODULE 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 trcdta
21   USE tradmp
22   USE trdtra
23   USE trd_oce
24   !
25   USE iom
26   USE prtctl_trc      ! Print control for debbuging
27
28   IMPLICIT NONE
29   PRIVATE
30
31   PUBLIC trc_dmp     
32   PUBLIC trc_dmp_clo   
33   PUBLIC trc_dmp_alloc 
34   PUBLIC trc_dmp_ini   
35
36   INTEGER            , PUBLIC ::   nn_zdmp_tr    !: = 0/1/2 flag for damping in the mixed layer
37   CHARACTER(LEN=200) , PUBLIC ::   cn_resto_tr   !: File containing restoration coefficient
38
39   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   restotr   ! restoring coeff. on tracers (s-1)
40
41   INTEGER, PARAMETER         ::   npncts = 8       ! number of closed sea
42   INTEGER, DIMENSION(npncts) ::   nctsi1, nctsj1   ! south-west closed sea limits (i,j)
43   INTEGER, DIMENSION(npncts) ::   nctsi2, nctsj2   ! north-east closed sea limits (i,j)
44
45   !! * Substitutions
46#  include "do_loop_substitute.h90"
47   !!----------------------------------------------------------------------
48   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
49   !! $Id$
50   !! Software governed by the CeCILL license (see ./LICENSE)
51   !!----------------------------------------------------------------------
52CONTAINS
53
54   INTEGER FUNCTION trc_dmp_alloc()
55      !!----------------------------------------------------------------------
56      !!                   ***  ROUTINE trc_dmp_alloc  ***
57      !!----------------------------------------------------------------------
58      ALLOCATE( restotr(jpi,jpj,jpk) , STAT=trc_dmp_alloc )
59      !
60      IF( trc_dmp_alloc /= 0 )   CALL ctl_warn('trc_dmp_alloc: failed to allocate array')
61      !
62   END FUNCTION trc_dmp_alloc
63
64
65   SUBROUTINE trc_dmp( kt, Kbb, Kmm, ptr, Krhs )
66      !!----------------------------------------------------------------------
67      !!                   ***  ROUTINE trc_dmp  ***
68      !!                 
69      !! ** Purpose :   Compute the passive tracer trend due to a newtonian damping
70      !!      of the tracer field towards given data field and add it to the
71      !!      general tracer trends.
72      !!
73      !! ** Method  :   Newtonian damping towards trdta computed
74      !!      and add to the general tracer trends:
75      !!                     tr(Kmm) = tr(Krhs) + restotr * (trdta - tr(Kbb))
76      !!         The trend is computed either throughout the water column
77      !!      (nlmdmptr=0) or in area of weak vertical mixing (nlmdmptr=1) or
78      !!      below the well mixed layer (nlmdmptr=2)
79      !!
80      !! ** Action  : - update the tracer trends tr(:,:,:,:,Krhs) with the newtonian
81      !!                damping trends.
82      !!              - save the trends ('key_trdmxl_trc')
83      !!----------------------------------------------------------------------
84      INTEGER,                                    INTENT(in   ) :: kt              ! ocean time-step index
85      INTEGER,                                    INTENT(in   ) :: Kbb, Kmm, Krhs  ! time level indices
86      REAL(wp), DIMENSION(jpi,jpj,jpk,jptra,jpt), INTENT(inout) :: ptr             ! passive tracers and RHS of tracer equation
87      !
88      INTEGER ::   ji, jj, jk, jn, jl   ! dummy loop indices
89      CHARACTER (len=22) ::   charout
90      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   ztrtrd
91      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   ztrcdta   ! 3D  workspace
92      !!----------------------------------------------------------------------
93      !
94      IF( ln_timing )   CALL timing_start('trc_dmp')
95      !
96      IF( l_trdtrc )   ALLOCATE( ztrtrd(jpi,jpj,jpk) )   ! 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         ALLOCATE( ztrcdta(jpi,jpj,jpk) )    ! Memory allocation
101         !                                                          ! ===========
102         DO jn = 1, jptra                                           ! tracer loop
103            !                                                       ! ===========
104            IF( l_trdtrc ) ztrtrd(:,:,:) = ptr(:,:,:,jn,Krhs)    ! 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, Kmm, sf_trcdta(jl), rf_trfac(jl), ztrcdta )   ! read tracer data at nit000
110               !
111               SELECT CASE ( nn_zdmp_tr )
112               !
113               CASE( 0 )                !==  newtonian damping throughout the water column  ==!
114                  DO_3D_00_00( 1, jpkm1 )
115                     ptr(ji,jj,jk,jn,Krhs) = ptr(ji,jj,jk,jn,Krhs) + restotr(ji,jj,jk) * ( ztrcdta(ji,jj,jk) - ptr(ji,jj,jk,jn,Kbb) )
116                  END_3D
117                  !
118               CASE ( 1 )                !==  no damping in the turbocline (avt > 5 cm2/s)  ==!
119                  DO_3D_00_00( 1, jpkm1 )
120                     IF( avt(ji,jj,jk) <= avt_c )  THEN
121                        ptr(ji,jj,jk,jn,Krhs) = ptr(ji,jj,jk,jn,Krhs) + restotr(ji,jj,jk) * ( ztrcdta(ji,jj,jk) - ptr(ji,jj,jk,jn,Kbb) )
122                     ENDIF
123                  END_3D
124                  !
125               CASE ( 2 )               !==  no damping in the mixed layer   ==!
126                  DO_3D_00_00( 1, jpkm1 )
127                     IF( gdept(ji,jj,jk,Kmm) >= hmlp (ji,jj) ) THEN
128                        ptr(ji,jj,jk,jn,Krhs) = ptr(ji,jj,jk,jn,Krhs) + restotr(ji,jj,jk) * ( ztrcdta(ji,jj,jk) - ptr(ji,jj,jk,jn,Kbb) )
129                     END IF
130                  END_3D
131                 
132               END SELECT
133               !
134            ENDIF
135            !
136            IF( l_trdtrc ) THEN
137               ztrtrd(:,:,:) = ptr(:,:,:,jn,Krhs) -  ztrtrd(:,:,:)
138               CALL trd_tra( kt, Kmm, Krhs, 'TRC', jn, jptra_dmp, ztrtrd )
139            END IF
140            !                                                       ! ===========
141         END DO                                                     ! tracer loop
142         !                                                          ! ===========
143         DEALLOCATE( ztrcdta )
144      ENDIF
145      !
146      IF( l_trdtrc )  DEALLOCATE( ztrtrd )
147      !                                          ! print mean trends (used for debugging)
148      IF( sn_cfctl%l_prttrc ) THEN
149         WRITE(charout, FMT="('dmp ')")
150         CALL prt_ctl_trc_info(charout)
151         CALL prt_ctl_trc( tab4d=ptr(:,:,:,:,Krhs), mask=tmask, clinfo=ctrcnm, clinfo2='trd' )
152      ENDIF
153      !
154      IF( ln_timing )   CALL timing_stop('trc_dmp')
155      !
156   END SUBROUTINE trc_dmp
157
158
159   SUBROUTINE trc_dmp_ini
160      !!----------------------------------------------------------------------
161      !!                  ***  ROUTINE trc_dmp_ini  ***
162      !!
163      !! ** Purpose :   Initialization for the newtonian damping
164      !!
165      !! ** Method  :   read the nammbf namelist and check the parameters
166      !!              called by trc_dmp at the first timestep (nittrc000)
167      !!----------------------------------------------------------------------
168      INTEGER ::   ios, imask  ! local integers
169      !!
170      NAMELIST/namtrc_dmp/ nn_zdmp_tr , cn_resto_tr
171      !!----------------------------------------------------------------------
172      !
173      READ  ( numnat_ref, namtrc_dmp, IOSTAT = ios, ERR = 909)
174909   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtrc_dmp in reference namelist' )
175      READ  ( numnat_cfg, namtrc_dmp, IOSTAT = ios, ERR = 910)
176910   IF( ios >  0 )   CALL ctl_nam ( ios , 'namtrc_dmp in configuration namelist' )
177      IF(lwm) WRITE ( numont, namtrc_dmp )
178
179      IF(lwp) THEN                       ! Namelist print
180         WRITE(numout,*)
181         WRITE(numout,*) 'trc_dmp : Passive tracers newtonian damping'
182         WRITE(numout,*) '~~~~~~~'
183         WRITE(numout,*) '   Namelist namtrc_dmp : set damping parameter'
184         WRITE(numout,*) '      mixed layer damping option     nn_zdmp_tr  = ', nn_zdmp_tr, '(zoom: forced to 0)'
185         WRITE(numout,*) '      Restoration coeff file         cn_resto_tr = ', cn_resto_tr
186      ENDIF
187      !                          ! Allocate arrays
188      IF( trc_dmp_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'trc_dmp_ini: unable to allocate arrays' )
189      !
190      SELECT CASE ( nn_zdmp_tr )
191      CASE ( 0 )   ;   IF(lwp) WRITE(numout,*) '      ===>>   tracer damping throughout the water column'
192      CASE ( 1 )   ;   IF(lwp) WRITE(numout,*) '      ===>>   no tracer damping in the turbocline (avt > 5 cm2/s)'
193      CASE ( 2 )   ;   IF(lwp) WRITE(numout,*) '      ===>>   no tracer damping in the mixed layer'
194      CASE DEFAULT
195         WRITE(ctmp1,*) 'bad flag value for nn_zdmp_tr = ', nn_zdmp_tr
196         CALL ctl_stop(ctmp1)
197      END SELECT
198
199      IF( .NOT.lk_c1d ) THEN
200         IF( .NOT.ln_tradmp )   &
201            &   CALL ctl_stop( 'passive tracer damping need ln_tradmp to compute damping coef.' )
202         !
203         !                          ! Read damping coefficients from file
204         !Read in mask from file
205         CALL iom_open ( cn_resto_tr, imask)
206         CALL iom_get  ( imask, jpdom_autoglo, 'resto', restotr)
207         CALL iom_close( imask )
208         !
209      ENDIF
210      !
211   END SUBROUTINE trc_dmp_ini
212
213
214   SUBROUTINE trc_dmp_clo( kt, Kbb, Kmm )
215      !!---------------------------------------------------------------------
216      !!                  ***  ROUTINE trc_dmp_clo  ***
217      !!
218      !! ** Purpose :   Closed sea domain initialization
219      !!
220      !! ** Method  :   if a closed sea is located only in a model grid point
221      !!                we restore to initial data
222      !!
223      !! ** Action  :   nctsi1(), nctsj1() : south-west closed sea limits (i,j)
224      !!                nctsi2(), nctsj2() : north-east Closed sea limits (i,j)
225      !!----------------------------------------------------------------------
226      INTEGER, INTENT( in ) ::   kt           ! ocean time-step index
227      INTEGER, INTENT( in ) ::   Kbb, Kmm     ! time level indices
228      !
229      INTEGER :: ji , jj, jk, jn, jl, jc                    ! dummy loop indicesa
230      INTEGER :: isrow                                      ! local index
231      REAL(wp), POINTER, DIMENSION(:,:,:) ::  ztrcdta       ! 3D  workspace
232      !!----------------------------------------------------------------------
233
234      IF( kt == nit000 ) THEN
235         ! initial values
236         nctsi1(:) = 1  ;  nctsi2(:) = 1
237         nctsj1(:) = 1  ;  nctsj2(:) = 1
238
239         ! set the closed seas (in data domain indices)
240         ! -------------------
241
242         IF( cn_cfg == "orca" .OR. cn_cfg == "ORCA") THEN
243            !
244            SELECT CASE ( nn_cfg )
245            !                                           ! =======================
246            CASE ( 1 )                                  ! eORCA_R1 configuration
247            !                                           ! =======================
248            isrow = 332 - jpjglo
249            !
250            nctsi1(1)   = 333  ; nctsj1(1)   = 243 - isrow   ! Caspian Sea
251            nctsi2(1)   = 342  ; nctsj2(1)   = 274 - isrow
252            !                                       
253            nctsi1(2)   = 198  ; nctsj1(2)   = 258 - isrow   ! Lake Superior
254            nctsi2(2)   = 204  ; nctsj2(2)   = 262 - isrow
255            !                                         
256            nctsi1(3)   = 201  ; nctsj1(3)   = 250 - isrow   ! Lake Michigan
257            nctsi2(3)   = 203  ; nctsj2(3)   = 256 - isrow
258            !                                       
259            nctsi1(4)   = 204  ; nctsj1(4)   = 252 - isrow   ! Lake Huron
260            nctsi2(4)   = 209  ; nctsj2(4)   = 256 - isrow
261            !                                       
262            nctsi1(5)   = 206  ; nctsj1(5)   = 249 - isrow   ! Lake Erie
263            nctsi2(5)   = 209  ; nctsj2(5)   = 251 - isrow
264            !                                       
265            nctsi1(6)   = 210  ; nctsj1(6)   = 252 - isrow   ! Lake Ontario
266            nctsi2(6)   = 212  ; nctsj2(6)   = 252 - isrow
267            !                                       
268            nctsi1(7)   = 321  ; nctsj1(7)   = 180 - isrow   ! Victoria Lake
269            nctsi2(7)   = 322  ; nctsj2(7)   = 189 - isrow
270            !                                       
271            nctsi1(8)   = 297  ; nctsj1(8)   = 270 - isrow   ! Baltic Sea
272            nctsi2(8)   = 308  ; nctsj2(8)   = 293 - isrow
273            !                                       
274            !                                           ! =======================
275            CASE ( 2 )                                  !  ORCA_R2 configuration
276               !                                        ! =======================
277               !                                     
278               nctsi1(1)   =  11  ;  nctsj1(1)   = 103       ! Caspian Sea
279               nctsi2(1)   =  17  ;  nctsj2(1)   = 112
280               !                                     
281               nctsi1(2)   =  97  ;  nctsj1(2)   = 107       ! Great North American Lakes
282               nctsi2(2)   = 103  ;  nctsj2(2)   = 111
283               !                                     
284               nctsi1(3)   = 174  ;  nctsj1(3)   = 107       ! Black Sea 1 : west part of the Black Sea
285               nctsi2(3)   = 181  ;  nctsj2(3)   = 112
286              !                                     
287               nctsi1(4)   =   2  ;  nctsj1(4)   = 107      ! Black Sea 2 : est part of the Black Sea
288               nctsi2(4)   =   6  ;  nctsj2(4)   = 112
289               !                                     
290               nctsi1(5)   =  145 ;  nctsj1(5)   = 116       ! Baltic Sea
291               nctsi2(5)   =  150 ;  nctsj2(5)   = 126
292               !                                        ! =======================
293            CASE ( 4 )                                  !  ORCA_R4 configuration
294               !                                        ! =======================
295               !                                   
296               nctsi1(1)   =  4  ;  nctsj1(1)   = 53         ! Caspian Sea
297               nctsi2(1)   =  4  ;  nctsj2(1)   = 56
298               !                                   
299               nctsi1(2)   = 49  ;  nctsj1(2)   = 55         ! Great North American Lakes
300               nctsi2(2)   = 51  ;  nctsj2(2)   = 56
301               !                                   
302               nctsi1(3)   = 88  ;  nctsj1(3)   = 55         ! Black Sea
303               nctsi2(3)   = 91  ;  nctsj2(3)   = 56
304               !                                   
305               nctsi1(4)   = 75  ;  nctsj1(4)   = 59         ! Baltic Sea
306               nctsi2(4)   = 76  ;  nctsj2(4)   = 61
307               !                                        ! =======================
308            CASE ( 025 )                                ! ORCA_R025 configuration
309               !                                        ! =======================
310               !                                   
311               nctsi1(1)   = 1330 ; nctsj1(1)   = 645        ! Caspian + Aral sea
312               nctsi2(1)   = 1400 ; nctsj2(1)   = 795
313               !                                   
314               nctsi1(2)   = 1284 ; nctsj1(2)   = 722        ! Azov Sea
315               nctsi2(2)   = 1304 ; nctsj2(2)   = 747
316               !
317            END SELECT
318            !
319         ENDIF
320         !
321         ! convert the position in local domain indices
322         ! --------------------------------------------
323         DO jc = 1, npncts
324            nctsi1(jc)   = mi0( nctsi1(jc) )
325            nctsj1(jc)   = mj0( nctsj1(jc) )
326            !
327            nctsi2(jc)   = mi1( nctsi2(jc) )
328            nctsj2(jc)   = mj1( nctsj2(jc) )
329         END DO
330         !
331      ENDIF
332
333      ! Restore close seas values to initial data
334      IF( ln_trcdta .AND. nb_trcdta > 0 )  THEN   ! Initialisation of tracer from a file that may also be used for damping
335         !
336         IF(lwp)  WRITE(numout,*)
337         IF(lwp)  WRITE(numout,*) ' trc_dmp_clo : Restoring of nutrients on close seas at time-step kt = ', kt
338         IF(lwp)  WRITE(numout,*)
339         !
340         ALLOCATE( ztrcdta(jpi,jpj,jpk) )   ! Memory allocation
341         !
342         DO jn = 1, jptra
343            IF( ln_trc_ini(jn) ) THEN      ! update passive tracers arrays with input data read from file
344                jl = n_trc_index(jn)
345                CALL trc_dta( kt, Kmm, sf_trcdta(jl), rf_trfac(jl), ztrcdta )   ! read tracer data at nit000
346                DO jc = 1, npncts
347                   DO jk = 1, jpkm1
348                      DO jj = nctsj1(jc), nctsj2(jc)
349                         DO ji = nctsi1(jc), nctsi2(jc)
350                            tr(ji,jj,jk,jn,Kmm) = ztrcdta(ji,jj,jk)
351                            tr(ji,jj,jk,jn,Kbb) = tr(ji,jj,jk,jn,Kmm)
352                         END DO
353                      END DO
354                   END DO
355                END DO
356             ENDIF
357          END DO
358          DEALLOCATE( ztrcdta )
359      ENDIF
360      !
361   END SUBROUTINE trc_dmp_clo
362 
363#else
364   !!----------------------------------------------------------------------
365   !!  Dummy module :                                     No passive tracer
366   !!----------------------------------------------------------------------
367CONTAINS
368   SUBROUTINE trc_dmp( kt )        ! Empty routine
369      INTEGER, INTENT(in) :: kt
370      WRITE(*,*) 'trc_dmp: You should not have seen this print! error?', kt
371   END SUBROUTINE trc_dmp
372#endif
373
374   !!======================================================================
375END MODULE trcdmp
Note: See TracBrowser for help on using the repository browser.