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

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

CT : UPDATE142 : Check the consistency between passive tracers transport modules (in TRP directory) and those used for the active tracers

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