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/2014/dev_r4650_UKMO7_STARTHOUR/NEMOGCM/NEMO/TOP_SRC/TRP – NEMO

source: branches/2014/dev_r4650_UKMO7_STARTHOUR/NEMOGCM/NEMO/TOP_SRC/TRP/trcdmp.F90 @ 5075

Last change on this file since 5075 was 5075, checked in by timgraham, 9 years ago

Upgraded branch to current head of trunk (r5072) so it can be used with the trunk

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