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

source: trunk/NEMO/TOP_SRC/TRP/trczdf_imp.F90 @ 376

Last change on this file since 376 was 349, checked in by opalod, 18 years ago

nemo_v1_update_031 : CT : change header names

  • Property svn:eol-style set to native
  • Property svn:executable set to *
  • Property svn:keywords set to Author Date Id Revision
File size: 8.7 KB
Line 
1MODULE trczdf_imp
2   !!==============================================================================
3   !!                    ***  MODULE  trczdf_imp  ***
4   !! Ocean passive tracers:  vertical component of the tracer mixing trend
5   !!==============================================================================
6#if defined key_passivetrc
7   !!----------------------------------------------------------------------
8   !!   trc_zdf_imp  : update the tracer trend with the vertical diffusion
9   !!                  using an implicit time-stepping.
10   !!----------------------------------------------------------------------
11   !! * Modules used
12   USE oce_trc             ! ocean dynamics and active tracers variables
13   USE trc                 ! ocean passive tracers variables
14   USE trctrp_lec          ! passive tracers transport
15   USE prtctl_trc
16
17   IMPLICIT NONE
18   PRIVATE
19
20   !! * Routine accessibility
21   PUBLIC trc_zdf_imp          ! 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_imp( kt )
38      !!----------------------------------------------------------------------
39      !!                  ***  ROUTINE trc_zdf_imp  ***
40      !!
41      !! ** Purpose :   Compute the trend due to the vertical tracer mixing
42      !!      using an implicit time stepping and add it to the general trend
43      !!      of the tracer equations.
44      !!
45      !! ** Method  :   The vertical diffusion of tracers tra is given by:
46      !!          difft = dz( avt dz(t) ) = 1/e3t dk+1( avt/e3w dk(tra) )
47      !!      It is thus evaluated using a backward time scheme
48      !!      Surface and bottom boundary conditions: no diffusive flux on
49      !!      both tracers (bottom, applied through the masked field avt).
50      !!      Add this trend to the general trend tra :
51      !!          tra = tra + dz( avt dz(t) )
52      !!         (tra = tra + dz( avs dz(t) ) if lk_zdfddmtrc=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      INTEGER ::   ikst, ikenm2, ikstp1
75      !! * Local declarations
76      INTEGER ::   ji, jj, jk, jn             ! dummy loop indices
77      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   &
78         zwd, zws, zwi,          &  ! ???
79         zwx, zwy, zwt              ! ???
80      REAL(wp) ::  ztra      ! temporary scalars
81
82      REAL(wp), DIMENSION(jpi,jpj,jpk,jptra) ::   &
83         ztrd
84      CHARACTER (len=22) :: charout
85      !!---------------------------------------------------------------------
86
87      IF( kt == nittrc000 ) THEN
88         WRITE(numout,*)
89         WRITE(numout,*) 'trc_zdf_implicit : vertical tracer mixing'
90         WRITE(numout,*) '~~~~~~~~~~~~~~~'
91      ENDIF
92
93      ! 0. Local constant initialization
94      ! --------------------------------
95      IF( ln_trcadv_cen2 .OR. ln_trcadv_tvd ) THEN
96         ! time step = 2 rdttra with Arakawa or TVD advection scheme
97         IF( neuler == 0 .AND. kt == nittrc000 ) THEN
98            rdttrc(:) =  rdttra(:) * FLOAT(ndttrc)             ! restarting with Euler time stepping
99         ELSEIF( kt <= nittrc000 + 1 ) THEN
100            rdttrc(:) = 2. * rdttra(:) * FLOAT(ndttrc)         ! leapfrog
101         ENDIF
102      ELSE
103         rdttrc(:) =  rdttra(:) * FLOAT(ndttrc)     
104      ENDIF
105
106      DO jn = 1 , jptra
107
108    ! Initialisation     
109    zwd( 1 ,:,:) = 0.e0     ;     zwd(jpi,:,:) = 0.e0
110    zws( 1 ,:,:) = 0.e0     ;     zws(jpi,:,:) = 0.e0
111    zwi( 1 ,:,:) = 0.e0     ;     zwi(jpi,:,:) = 0.e0
112    zwt( 1 ,:,:) = 0.e0     ;     zwt(jpi,:,:) = 0.e0     
113         zwt(  :,:,1) = 0.e0     ;     zwt(  :,:,jpk) = 0.e0
114         !                                         
115         ! 0. Matrix construction
116         ! ----------------------
117
118         ! Diagonal, inferior, superior
119         ! (including the bottom boundary condition via avs masked
120         DO jk = 1, jpkm1                                                     
121            DO jj = 2, jpjm1                                     
122               DO ji = fs_2, fs_jpim1   ! vector opt.
123                  zwi(ji,jj,jk) = - rdttrc(jk) * fstravs(ji,jj,jk  ) /( fse3t(ji,jj,jk) * fse3w(ji,jj,jk  ) )
124                  zws(ji,jj,jk) = - rdttrc(jk) * fstravs(ji,jj,jk+1) /( fse3t(ji,jj,jk) * fse3w(ji,jj,jk+1) )
125                  zwd(ji,jj,jk) = 1. - zwi(ji,jj,jk) - zws(ji,jj,jk)
126               END DO
127            END DO
128         END DO
129
130         ! Surface boudary conditions
131         DO jj = 2, jpjm1       
132            DO ji = fs_2, fs_jpim1
133               zwi(ji,jj,1) = 0.e0
134               zwd(ji,jj,1) = 1. - zws(ji,jj,1)
135            END DO
136         END DO
137         
138         ! Second member construction
139         DO jk = 1, jpkm1
140            DO jj = 2, jpjm1     
141               DO ji = fs_2, fs_jpim1
142                  zwy(ji,jj,jk) = trb(ji,jj,jk,jn) + rdttrc(jk) * tra(ji,jj,jk,jn)
143               END DO
144            END DO
145         END DO
146         
147 
148   ! Matrix inversion from the first level
149   ikst = 1
150
151#   include "zdf.matrixsolver.vopt.h90"       
152 
153         
154#if defined key_trc_diatrd
155         ! Compute and save the vertical diffusive of tracers trends
156#  if defined key_trc_ldfiso
157         DO jk = 1, jpkm1
158            DO jj = 2, jpjm1
159               DO ji = fs_2, fs_jpim1   ! vector opt.
160                  ztra = ( zwx(ji,jj,jk) - trb(ji,jj,jk,jn) ) / rdttrc(jk)
161                  trtrd(ji,jj,jk,jn,6) = ztra - tra(ji,jj,jk,jn) + trtrd(ji,jj,jk,jn,6)
162               END DO
163            END DO
164         END DO
165#  else
166         DO jk = 1, jpkm1
167            DO jj = 2, jpjm1
168               DO ji = fs_2, fs_jpim1   ! vector opt.
169                  ztra = ( zwx(ji,jj,jk) - trb(ji,jj,jk,jn) ) / rdttrc(jk)
170                  trtrd(ji,jj,jk,jn,6) = ztra - tra(ji,jj,jk,jn)
171               END DO
172            END DO
173         END DO
174#  endif
175#endif 
176         ! Save the masked passive tracer after in tra
177         ! (c a u t i o n:  tracer not its trend, Leap-frog scheme done
178         !                  it will not be done in tranxt)
179         DO jk = 1, jpkm1
180            DO jj = 2, jpjm1
181               DO ji = fs_2, fs_jpim1
182                  tra(ji,jj,jk,jn) = zwx(ji,jj,jk) * tmask(ji,jj,jk)
183               END DO
184            END DO
185         END DO
186
187         IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
188            ztrd(:,:,:,:) = 0.
189            DO jk = 1, jpkm1
190               DO jj = 2, jpjm1
191                  DO ji = fs_2, fs_jpim1
192                     ztrd(ji,jj,jk,jn) = ( zwx(ji,jj,jk) - trb(ji,jj,jk,jn) ) / rdttrc(jk)
193                  END DO
194               END DO
195            END DO
196         ENDIF
197
198      END DO
199
200      IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
201         WRITE(charout, FMT="('zdf - imp')")
202         CALL prt_ctl_trc_info(charout)
203         CALL prt_ctl_trc(tab4d=ztrd, mask=tmask, clinfo=ctrcnm,clinfo2='trd')
204      ENDIF
205
206   END SUBROUTINE trc_zdf_imp
207
208#else
209   !!----------------------------------------------------------------------
210   !!   Dummy module :                      NO passive tracer
211   !!----------------------------------------------------------------------
212CONTAINS
213   SUBROUTINE trc_zdf_imp (kt )              ! Empty routine
214      INTEGER, INTENT(in) :: kt
215      WRITE(*,*) 'trc_zdf_imp: You should not have seen this print! error?', kt
216   END SUBROUTINE trc_zdf_imp
217#endif
218   
219!!==============================================================================
220END MODULE trczdf_imp
Note: See TracBrowser for help on using the repository browser.