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 @ 247

Last change on this file since 247 was 247, checked in by opalod, 19 years ago

CL : Add CVS Header and CeCILL licence information

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