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

source: branches/DEV_r1879_FCM/NEMOGCM/NEMO/TOP_SRC/TRP/trczdf_exp.F90 @ 2013

Last change on this file since 2013 was 2013, checked in by smasson, 14 years ago

remove propertie svn:executabe of fortran files in DEV_r1879_FCM

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