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 branches/UKMO/r5936_CO6_CO5_shelfdiagnostic/NEMOGCM/NEMO/TOP_SRC/TRP – NEMO

source: branches/UKMO/r5936_CO6_CO5_shelfdiagnostic/NEMOGCM/NEMO/TOP_SRC/TRP/trcdmp.F90 @ 7102

Last change on this file since 7102 was 7102, checked in by jcastill, 7 years ago

Remove svn keys

  • Property svn:keywords set to Id
File size: 17.8 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 prtctl_trc      ! Print control for debbuging
23   USE trdtra
24   USE trd_oce
25   USE iom
26
27   IMPLICIT NONE
28   PRIVATE
29
30   PUBLIC trc_dmp     
31   PUBLIC trc_dmp_clo   
32   PUBLIC trc_dmp_alloc 
33   PUBLIC trc_dmp_ini   
34
35   INTEGER , PUBLIC ::   nn_zdmp_tr    ! = 0/1/2 flag for damping in the mixed layer
36   CHARACTER(LEN=200) , PUBLIC :: cn_resto_tr    !File containing restoration coefficient
37
38   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   restotr   ! restoring coeff. on tracers (s-1)
39
40   INTEGER, PARAMETER           ::   npncts   = 5        ! number of closed sea
41   INTEGER, DIMENSION(npncts)   ::   nctsi1, nctsj1      ! south-west closed sea limits (i,j)
42   INTEGER, DIMENSION(npncts)   ::   nctsi2, nctsj2      ! north-east closed sea limits (i,j)
43
44   !! * Substitutions
45#  include "domzgr_substitute.h90"
46#  include "vectopt_loop_substitute.h90"
47   !!----------------------------------------------------------------------
48   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
49   !! $Id$
50   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
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 )
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      !!                     trn = tra + restotr * (trdta - trb)
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 tra with the newtonian
81      !!                damping trends.
82      !!              - save the trends ('key_trdmxl_trc')
83      !!----------------------------------------------------------------------
84      !!
85      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index
86      !!
87      INTEGER  ::   ji, jj, jk, jn, jl       ! dummy loop indices
88      REAL(wp) ::   ztra                 ! temporary scalars
89      CHARACTER (len=22) :: charout
90      REAL(wp), POINTER, DIMENSION(:,:,:) ::   ztrtrd
91      REAL(wp), POINTER, DIMENSION(:,:,:) ::  ztrcdta   ! 3D  workspace
92      !!----------------------------------------------------------------------
93      !
94      IF( nn_timing == 1 )  CALL timing_start('trc_dmp')
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),rf_trfac(jl) )   ! read tracer data at nit000
110               ztrcdta(:,:,:) = sf_trcdta(jl)%fnow(:,:,:)
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_ini
174      !!----------------------------------------------------------------------
175      !!                  ***  ROUTINE trc_dmp_ini  ***
176      !!
177      !! ** Purpose :   Initialization for the newtonian damping
178      !!
179      !! ** Method  :   read the nammbf namelist and check the parameters
180      !!              called by trc_dmp at the first timestep (nittrc000)
181      !!----------------------------------------------------------------------
182      !
183      INTEGER ::  ios                 ! Local integer output status for namelist read
184      INTEGER :: imask  !local file handle
185      !
186      NAMELIST/namtrc_dmp/ nn_zdmp_tr , cn_resto_tr
187      !!----------------------------------------------------------------------
188
189      IF( nn_timing == 1 )  CALL timing_start('trc_dmp_init')
190      !
191
192      REWIND( numnat_ref )              ! Namelist namtrc_dmp in reference namelist : Passive tracers newtonian damping
193      READ  ( numnat_ref, namtrc_dmp, IOSTAT = ios, ERR = 909)
194909   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dmp in reference namelist', lwp )
195
196      REWIND( numnat_cfg )              ! Namelist namtrc_dmp in configuration namelist : Passive tracers newtonian damping
197      READ  ( numnat_cfg, namtrc_dmp, IOSTAT = ios, ERR = 910)
198910   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dmp in configuration namelist', lwp )
199      IF(lwm) WRITE ( numont, namtrc_dmp )
200
201      IF(lwp) THEN                       ! Namelist print
202         WRITE(numout,*)
203         WRITE(numout,*) 'trc_dmp : Passive tracers newtonian damping'
204         WRITE(numout,*) '~~~~~~~'
205         WRITE(numout,*) '   Namelist namtrc_dmp : set damping parameter'
206         WRITE(numout,*) '      mixed layer damping option     nn_zdmp_tr = ', nn_zdmp_tr, '(zoom: forced to 0)'
207         WRITE(numout,*) '      Restoration coeff file    cn_resto_tr = ', cn_resto_tr
208      ENDIF
209      !
210      IF( lzoom .AND. .NOT.lk_c1d )   nn_zdmp_tr = 0           ! restoring to climatology at closed north or south boundaries
211      SELECT CASE ( nn_zdmp_tr )
212      CASE ( 0 )   ;   IF(lwp) WRITE(numout,*) '   tracer damping throughout the water column'
213      CASE ( 1 )   ;   IF(lwp) WRITE(numout,*) '   no tracer damping in the turbocline (avt > 5 cm2/s)'
214      CASE ( 2 )   ;   IF(lwp) WRITE(numout,*) '   no tracer damping in the mixed layer'
215      CASE DEFAULT
216         WRITE(ctmp1,*) 'bad flag value for nn_zdmp_tr = ', nn_zdmp_tr
217         CALL ctl_stop(ctmp1)
218      END SELECT
219
220      IF( .NOT.lk_c1d ) THEN
221         IF( .NOT. ln_tradmp )   &
222            &   CALL ctl_stop( 'passive trace damping need ln_tradmp to compute damping coef.' )
223         !
224         !                          ! Read damping coefficients from file
225         !Read in mask from file
226         CALL iom_open ( cn_resto_tr, imask)
227         CALL iom_get  ( imask, jpdom_autoglo, 'resto', restotr)
228         CALL iom_close( imask )
229         !
230      ENDIF
231      IF( nn_timing == 1 )  CALL timing_stop('trc_dmp_init')
232      !
233   END SUBROUTINE trc_dmp_ini
234
235   SUBROUTINE trc_dmp_clo( kt )
236      !!---------------------------------------------------------------------
237      !!                  ***  ROUTINE trc_dmp_clo  ***
238      !!
239      !! ** Purpose :   Closed sea domain initialization
240      !!
241      !! ** Method  :   if a closed sea is located only in a model grid point
242      !!                we restore to initial data
243      !!
244      !! ** Action  :   nctsi1(), nctsj1() : south-west closed sea limits (i,j)
245      !!                nctsi2(), nctsj2() : north-east Closed sea limits (i,j)
246      !!----------------------------------------------------------------------
247      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index
248      !
249      INTEGER :: ji , jj, jk, jn, jl, jc                     ! dummy loop indicesa
250      INTEGER :: isrow                                      ! local index
251      REAL(wp), POINTER, DIMENSION(:,:,:) ::  ztrcdta       ! 3D  workspace
252
253      !!----------------------------------------------------------------------
254
255      IF( kt == nit000 ) THEN
256         ! initial values
257         nctsi1(:) = 1  ;  nctsi2(:) = 1
258         nctsj1(:) = 1  ;  nctsj2(:) = 1
259
260         ! set the closed seas (in data domain indices)
261         ! -------------------
262
263         IF( cp_cfg == "orca" ) THEN
264            !
265            SELECT CASE ( jp_cfg )
266            !                                           ! =======================
267            CASE ( 1 )                                  ! eORCA_R1 configuration
268            !                                           ! =======================
269            isrow = 332 - jpjglo
270            !
271                                                        ! Caspian Sea
272            nctsi1(1)   = 332  ; nctsj1(1)   = 243 - isrow
273            nctsi2(1)   = 344  ; nctsj2(1)   = 275 - isrow
274            !                                       
275            !                                           ! =======================
276            CASE ( 2 )                                  !  ORCA_R2 configuration
277               !                                        ! =======================
278               !                                            ! Caspian Sea
279               nctsi1(1)   =  11  ;  nctsj1(1)   = 103
280               nctsi2(1)   =  17  ;  nctsj2(1)   = 112
281               !                                            ! Great North American Lakes
282               nctsi1(2)   =  97  ;  nctsj1(2)   = 107
283               nctsi2(2)   = 103  ;  nctsj2(2)   = 111
284               !                                            ! Black Sea 1 : west part of the Black Sea
285               nctsi1(3)   = 174  ;  nctsj1(3)   = 107
286               nctsi2(3)   = 181  ;  nctsj2(3)   = 112
287              !                                            ! Black Sea 2 : est part of the Black Sea
288               nctsi1(4)   =   2  ;  nctsj1(4)   = 107
289               nctsi2(4)   =   6  ;  nctsj2(4)   = 112
290               !                                            ! Baltic Sea
291               nctsi1(5)   =  145 ;  nctsj1(5)   = 116
292               nctsi2(5)   =  150 ;  nctsj2(5)   = 126
293               !                                        ! =======================
294            CASE ( 4 )                                  !  ORCA_R4 configuration
295               !                                        ! =======================
296               !                                            ! Caspian Sea
297               nctsi1(1)   =  4  ;  nctsj1(1)   = 53
298               nctsi2(1)   =  4  ;  nctsj2(1)   = 56
299               !                                            ! Great North American Lakes
300               nctsi1(2)   = 49  ;  nctsj1(2)   = 55
301               nctsi2(2)   = 51  ;  nctsj2(2)   = 56
302               !                                            ! Black Sea
303               nctsi1(3)   = 88  ;  nctsj1(3)   = 55
304               nctsi2(3)   = 91  ;  nctsj2(3)   = 56
305               !                                            ! Baltic Sea
306               nctsi1(4)   = 75  ;  nctsj1(4)   = 59
307               nctsi2(4)   = 76  ;  nctsj2(4)   = 61
308               !                                        ! =======================
309            CASE ( 025 )                                ! ORCA_R025 configuration
310               !                                        ! =======================
311                                                     ! Caspian + Aral sea
312               nctsi1(1)   = 1330 ; nctsj1(1)   = 645
313               nctsi2(1)   = 1400 ; nctsj2(1)   = 795
314               !                                        ! Azov Sea
315               nctsi1(2)   = 1284 ; nctsj1(2)   = 722
316               nctsi2(2)   = 1304 ; nctsj2(2)   = 747
317               !
318            END SELECT
319            !
320         ENDIF
321         !
322
323         ! convert the position in local domain indices
324         ! --------------------------------------------
325         DO jc = 1, npncts
326            nctsi1(jc)   = mi0( nctsi1(jc) )
327            nctsj1(jc)   = mj0( nctsj1(jc) )
328
329            nctsi2(jc)   = mi1( nctsi2(jc) )
330            nctsj2(jc)   = mj1( nctsj2(jc) )
331         END DO
332         !
333      ENDIF
334
335      ! Restore close seas values to initial data
336      IF( ln_trcdta .AND. nb_trcdta > 0 )  THEN   ! Initialisation of tracer from a file that may also be used for damping
337         !
338         IF(lwp)  WRITE(numout,*)
339         IF(lwp)  WRITE(numout,*) ' trc_dmp_clo : Restoring of nutrients on close seas at time-step kt = ', kt
340         IF(lwp)  WRITE(numout,*)
341         !
342         CALL wrk_alloc( jpi, jpj, jpk, ztrcdta )   ! Memory allocation
343         !
344         DO jn = 1, jptra
345            IF( ln_trc_ini(jn) ) THEN      ! update passive tracers arrays with input data read from file
346                jl = n_trc_index(jn)
347                CALL trc_dta( kt, sf_trcdta(jl),rf_trfac(jl) )   ! read tracer data at nit000
348                ztrcdta(:,:,:) = sf_trcdta(jl)%fnow(:,:,:)
349                DO jc = 1, npncts
350                   DO jk = 1, jpkm1
351                      DO jj = nctsj1(jc), nctsj2(jc)
352                         DO ji = nctsi1(jc), nctsi2(jc)
353                            trn(ji,jj,jk,jn) = ztrcdta(ji,jj,jk) * tmask(ji,jj,jk)
354                            trb(ji,jj,jk,jn) = trn(ji,jj,jk,jn)
355                         ENDDO
356                      ENDDO
357                   ENDDO
358                ENDDO
359             ENDIF
360          ENDDO
361          CALL wrk_dealloc( jpi, jpj, jpk, ztrcdta )
362      ENDIF
363      !
364   END SUBROUTINE trc_dmp_clo
365
366
367#else
368   !!----------------------------------------------------------------------
369   !!  Dummy module :                                     No passive tracer
370   !!----------------------------------------------------------------------
371CONTAINS
372   SUBROUTINE trc_dmp( kt )        ! Empty routine
373      INTEGER, INTENT(in) :: kt
374      WRITE(*,*) 'trc_dmp: You should not have seen this print! error?', kt
375   END SUBROUTINE trc_dmp
376#endif
377
378
379   !!======================================================================
380END MODULE trcdmp
Note: See TracBrowser for help on using the repository browser.