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.
trczdf_exp.F90 in trunk/NEMO/TOP_SRC/TRP – NEMO

source: trunk/NEMO/TOP_SRC/TRP/trczdf_exp.F90 @ 941

Last change on this file since 941 was 941, checked in by cetlod, 16 years ago

phasing the passive tracer transport module to the new version of NEMO, see ticket 143

  • Property svn:executable set to *
File size: 7.8 KB
Line 
1MODULE trczdf_exp
2   !!==============================================================================
3   !!                    ***  MODULE  trczdf_exp  ***
4   !! Ocean passive tracers:  vertical component of the tracer mixing trend using
5   !!                        an explicit time-stepping (time spllitting scheme)
6   !!==============================================================================
7#if defined key_top
8   !!----------------------------------------------------------------------
9   !!   'key_top'                                                TOP models
10   !!----------------------------------------------------------------------
11   !!   trc_zdf_exp  : update the tracer trend with the vertical diffusion
12   !!                  using an explicit time stepping
13   !!----------------------------------------------------------------------
14   !! * Modules used
15   USE oce_trc          ! ocean dynamics and active tracers variables
16   USE trc              ! ocean passive tracers variables
17   USE trctrp_lec       ! passive tracers transport
18   USE prtctl_trc          ! Print control for debbuging
19
20   IMPLICIT NONE
21   PRIVATE
22
23   !! * Routine accessibility
24   PUBLIC trc_zdf_exp          ! routine called by step.F90
25
26   !! * Module variable
27   REAL(wp), DIMENSION(jpk) ::   &
28      rdttrc                     ! vertical profile of 2 x tracer time-step
29
30   !! * Substitutions
31#  include "top_substitute.h90"
32   !!----------------------------------------------------------------------
33   !!   TOP 1.0 , LOCEAN-IPSL (2005)
34   !! $Header$
35   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
36   !!----------------------------------------------------------------------
37
38CONTAINS
39
40   SUBROUTINE trc_zdf_exp( kt )
41      !!----------------------------------------------------------------------
42      !!                  ***  ROUTINE trc_zdf_exp  ***
43      !!                   
44      !! ** Purpose :   Compute the trend due to the vertical tracer mixing
45      !!      using an explicit time stepping and add it to the general trend
46      !!      of the tracer equations.
47      !!
48      !! ** Method  :   The vertical diffusion of tracers  is given by:
49      !!         difft = dz( avt dz(trb) ) = 1/e3t dk+1( avt/e3w dk(trb) )
50      !!      It is evaluated with an Euler scheme, using a time splitting
51      !!      technique.
52      !!      Surface and bottom boundary conditions: no diffusive flux on
53      !!      both tracers (bottom, applied through the masked field avt).
54      !!      Add this trend to the general trend tra :
55      !!          tra = tra + dz( avt dz(t) ) if lk_zdfddm= T)
56      !!
57      !! ** Action : - Update tra with the before vertical diffusion trend
58      !!             - Save the trends  in trtrd ('key_trc_diatrd')
59      !!
60      !! History :
61      !!   6.0  !  90-10  (B. Blanke)  Original code
62      !!   7.0  !  91-11  (G. Madec)
63      !!        !  92-06  (M. Imbard)  correction on tracer trend loops
64      !!        !  96-01  (G. Madec)  statement function for e3
65      !!        !  97-05  (G. Madec)  vertical component of isopycnal
66      !!        !  97-07  (G. Madec)  geopotential diffusion in s-coord
67      !!        !  98-03  (L. Bopp MA Foujols) passive tracer generalisation
68      !!        !  00-05  (MA Foujols) add lbc for tracer trends
69      !!        !  00-06  (O Aumont)  correct isopycnal scheme suppress
70      !!        !                     avt multiple correction
71      !!        !  00-08  (G. Madec)  double diffusive mixing
72      !!   8.5  !  02-08  (G. Madec)  F90: Free form and module
73      !!   9.0  !  04-03  (C. Ethe )  adapted for passive tracers
74      !!---------------------------------------------------------------------
75      !! * Arguments
76      INTEGER, INTENT( in ) ::   kt           ! ocean time-step index
77     
78      !! * Local declarations
79      INTEGER ::   ji, jj, jk, jl, jn             ! dummy loop indices
80      REAL(wp) ::   &
81         zlavmr,                 &  ! ???
82         zave3r, ze3tr,          &  ! ???
83         ztra                  !
84      REAL(wp), DIMENSION(jpi,jpk) ::   &
85         zwx, zwy
86      CHARACTER (len=22) :: charout
87      !!---------------------------------------------------------------------
88
89      IF( kt == nittrc000 ) THEN
90         WRITE(numout,*)
91         WRITE(numout,*) 'trc_zdf_exp : vertical tracer mixing'
92         WRITE(numout,*) '~~~~~~~~~~~~~~~'
93      ENDIF
94
95      ! 0. Local constant initialization
96      ! --------------------------------
97      IF( ln_trcadv_cen2 .OR. ln_trcadv_tvd ) THEN
98         ! time step = 2 rdttra with Arakawa or TVD advection scheme
99         IF( neuler == 0 .AND. kt == nittrc000 ) THEN
100            rdttrc(:) =  rdttra(:) * FLOAT(ndttrc)             ! restarting with Euler time stepping
101         ELSEIF( kt <= nittrc000 + ndttrc ) THEN
102            rdttrc(:) = 2. * rdttra(:) * FLOAT(ndttrc)         ! leapfrog
103         ENDIF
104      ELSE
105         rdttrc(:) =  rdttra(:) * FLOAT(ndttrc)     
106      ENDIF
107
108
109      zlavmr = 1. / FLOAT( n_trczdf_exp )
110
111      DO jn = 1, jptra
112
113         !                                                ! ===============
114         DO jj = 2, jpjm1                                 !  Vertical slab
115            !                                             ! ===============
116            ! 1. Initializations
117            ! ------------------
118
119            ! Surface & bottom boundary conditions: no flux
120            DO ji = 2, jpim1
121               zwy(ji, 1 ) = 0.e0
122               zwy(ji,jpk) = 0.e0
123            END DO
124
125            ! zwx and zwz arrays set to before tracer values
126            DO jk = 1, jpk
127               DO ji = 2, jpim1
128                  zwx(ji,jk) = trb(ji,jj,jk,jn)
129               END DO
130            END DO
131
132
133            ! 2. Time splitting loop
134            ! ----------------------
135
136            DO jl = 1, n_trczdf_exp
137
138               ! first vertical derivative
139               ! double diffusion: fstravs(ji,jj,jk) = avt(ji,jj,jk) /= avs (key_trc_zdfddm)
140               !                   fstravs(ji,jj,jk) = avs(ji,jj,jk) = avt
141               DO jk = 2, jpk
142                  DO ji = 2, jpim1
143                     zave3r = 1.e0 / fse3w(ji,jj,jk) 
144                     zwy(ji,jk) = fstravs(ji,jj,jk) * ( zwx(ji,jk-1) - zwx(ji,jk) ) * zave3r
145                  END DO
146               END DO
147
148
149               ! trend estimation at kt+l*2*rdt/n_zdfexp
150               DO jk = 1, jpkm1
151                  DO ji = 2, jpim1
152                     ze3tr = zlavmr / fse3t(ji,jj,jk)
153                     ! 2nd vertical derivative
154                     ztra = ( zwy(ji,jk) - zwy(ji,jk+1) ) * ze3tr
155                     ! update the tracer trends
156                     tra(ji,jj,jk,jn) = tra(ji,jj,jk,jn) + ztra
157                     ! update tracer fields at kt+l*2*rdt/n_trczdf_exp
158                     zwx(ji,jk) = zwx(ji,jk) + rdttrc(jk) * ztra * tmask(ji,jj,jk)
159                  END DO
160               END DO
161            END DO
162            !                                             ! ===============
163         END DO                                           !   End of slab
164         !                                                ! ===============
165      END DO
166
167      IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
168         WRITE(charout, FMT="('zdf - exp')")
169         CALL prt_ctl_trc_info(charout)
170         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm,clinfo2='trd')
171      ENDIF
172
173   END SUBROUTINE trc_zdf_exp
174
175#else
176   !!----------------------------------------------------------------------
177   !!   Dummy module :                      NO passive tracer
178   !!----------------------------------------------------------------------
179CONTAINS
180   SUBROUTINE trc_zdf_exp (kt )              ! Empty routine
181      INTEGER, INTENT(in) :: kt
182      WRITE(*,*) 'trc_zdf_exp: You should not have seen this print! error?', kt
183   END SUBROUTINE trc_zdf_exp
184#endif
185   
186   !!==============================================================================
187END MODULE trczdf_exp
Note: See TracBrowser for help on using the repository browser.