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 @ 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: 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
16   IMPLICIT NONE
17   PRIVATE
18
19   !! * Routine accessibility
20   PUBLIC trc_zdf_imp          ! routine called by step.F90
21
22   !! * Module variable
23   REAL(wp), DIMENSION(jpk) ::   &
24      rdttrc                     ! vertical profile of 2 x tracer time-step
25
26   !! * Substitutions
27#  include "passivetrc_substitute.h90"
28   !!----------------------------------------------------------------------
29   !!   TOP 1.0 , LOCEAN-IPSL (2005)
30   !! $Header$
31   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
32   !!----------------------------------------------------------------------
33
34CONTAINS
35
36   SUBROUTINE trc_zdf_imp( kt )
37      !!----------------------------------------------------------------------
38      !!                  ***  ROUTINE trc_zdf_imp  ***
39      !!
40      !! ** Purpose :   Compute the trend due to the vertical tracer mixing
41      !!      using an implicit time stepping and add it to the general trend
42      !!      of the tracer equations.
43      !!
44      !! ** Method  :   The vertical diffusion of tracers tra is given by:
45      !!          difft = dz( avt dz(t) ) = 1/e3t dk+1( avt/e3w dk(tra) )
46      !!      It is thus evaluated using a backward time scheme
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) )
51      !!         (tra = tra + dz( avs dz(t) ) if lk_zdfddmtrc=T)
52      !!
53      !! ** Action  : - Update tra with the before vertical diffusion trend
54      !!              - save the trends in trtrd ('key_trc_diatrd')
55      !!
56      !! History :
57      !!   6.0  !  90-10  (B. Blanke)  Original code
58      !!   7.0  !  91-11  (G. Madec)
59      !!        !  92-06  (M. Imbard)  correction on tracer trend loops
60      !!        !  96-01  (G. Madec)  statement function for e3
61      !!        !  97-05  (G. Madec)  vertical component of isopycnal
62      !!        !  97-07  (G. Madec)  geopotential diffusion in s-coord
63      !!        !  98-03  (L. Bopp MA Foujols) passive tracer generalisation
64      !!        !  00-05  (MA Foujols) add lbc for tracer trends
65      !!        !  00-06  (O Aumont)  correct isopycnal scheme suppress
66      !!        !                     avt multiple correction
67      !!        !  00-08  (G. Madec)  double diffusive mixing
68      !!   8.5  !  02-08  (G. Madec)  F90: Free form and module
69      !!   9.0  !  04-03  (C. Ethe )  adapted for passive tracers
70      !!---------------------------------------------------------------------
71      !! * Arguments
72      INTEGER, INTENT( in ) ::   kt           ! ocean time-step index
73      INTEGER ::   ikst, ikenm2, ikstp1
74      !! * Local declarations
75      INTEGER ::   ji, jj, jk, jn             ! dummy loop indices
76      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   &
77         zwd, zws, zwi,          &  ! ???
78         zwx, zwy, zwt              ! ???
79      REAL(wp) ::  ztra      ! temporary scalars
80
81      REAL(wp), DIMENSION(jpi,jpj,jpk,jptra) ::   &
82         ztrd
83      !!---------------------------------------------------------------------
84
85      IF( kt == nittrc000 ) THEN
86         WRITE(numout,*)
87         WRITE(numout,*) 'trc_zdf_implicit : 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      DO jn = 1 , jptra
105
106    ! Initialisation     
107    zwd( 1 ,:,:) = 0.e0     ;     zwd(jpi,:,:) = 0.e0
108    zws( 1 ,:,:) = 0.e0     ;     zws(jpi,:,:) = 0.e0
109    zwi( 1 ,:,:) = 0.e0     ;     zwi(jpi,:,:) = 0.e0
110    zwt( 1 ,:,:) = 0.e0     ;     zwt(jpi,:,:) = 0.e0     
111         zwt(  :,:,1) = 0.e0     ;     zwt(  :,:,jpk) = 0.e0
112         !                                         
113         ! 0. Matrix construction
114         ! ----------------------
115
116         ! Diagonal, inferior, superior
117         ! (including the bottom boundary condition via avs masked
118         DO jk = 1, jpkm1                                                     
119            DO jj = 2, jpjm1                                     
120               DO ji = fs_2, fs_jpim1   ! vector opt.
121                  zwi(ji,jj,jk) = - rdttrc(jk) * fstravs(ji,jj,jk  ) /( fse3t(ji,jj,jk) * fse3w(ji,jj,jk  ) )
122                  zws(ji,jj,jk) = - rdttrc(jk) * fstravs(ji,jj,jk+1) /( fse3t(ji,jj,jk) * fse3w(ji,jj,jk+1) )
123                  zwd(ji,jj,jk) = 1. - zwi(ji,jj,jk) - zws(ji,jj,jk)
124               END DO
125            END DO
126         END DO
127
128         ! Surface boudary conditions
129         DO jj = 2, jpjm1       
130            DO ji = fs_2, fs_jpim1
131               zwi(ji,jj,1) = 0.e0
132               zwd(ji,jj,1) = 1. - zws(ji,jj,1)
133            END DO
134         END DO
135         
136         ! Second member construction
137         DO jk = 1, jpkm1
138            DO jj = 2, jpjm1     
139               DO ji = fs_2, fs_jpim1
140                  zwy(ji,jj,jk) = trb(ji,jj,jk,jn) + rdttrc(jk) * tra(ji,jj,jk,jn)
141               END DO
142            END DO
143         END DO
144         
145 
146   ! Matrix inversion from the first level
147   ikst = 1
148
149#   include "zdf.matrixsolver.vopt.h90"       
150 
151         
152#if defined key_trc_diatrd
153         ! Compute and save the vertical diffusive of tracers trends
154#  if defined key_trc_ldfiso
155         DO jk = 1, jpkm1
156            DO jj = 2, jpjm1
157               DO ji = fs_2, fs_jpim1   ! vector opt.
158                  ztra = ( zwx(ji,jj,jk) - trb(ji,jj,jk,jn) ) / rdttrc(jk)
159                  trtrd(ji,jj,jk,jn,6) = ztra - tra(ji,jj,jk,jn) + trtrd(ji,jj,jk,jn,6)
160               END DO
161            END DO
162         END DO
163#  else
164         DO jk = 1, jpkm1
165            DO jj = 2, jpjm1
166               DO ji = fs_2, fs_jpim1   ! vector opt.
167                  ztra = ( zwx(ji,jj,jk) - trb(ji,jj,jk,jn) ) / rdttrc(jk)
168                  trtrd(ji,jj,jk,jn,6) = ztra - tra(ji,jj,jk,jn)
169               END DO
170            END DO
171         END DO
172#  endif
173#endif 
174         ! Save the masked passive tracer after in tra
175         ! (c a u t i o n:  tracer not its trend, Leap-frog scheme done
176         !                  it will not be done in tranxt)
177         DO jk = 1, jpkm1
178            DO jj = 2, jpjm1
179               DO ji = fs_2, fs_jpim1
180                  tra(ji,jj,jk,jn) = zwx(ji,jj,jk) * tmask(ji,jj,jk)
181               END DO
182            END DO
183         END DO
184
185         IF(l_ctl) THEN
186            DO jk = 1, jpkm1
187               DO jj = 2, jpjm1
188                  DO ji = fs_2, fs_jpim1
189                     ztrd(ji,jj,jk,jn) = ( zwx(ji,jj,jk) - trb(ji,jj,jk,jn) ) / rdttrc(jk)
190                  END DO
191               END DO
192            END DO
193         ENDIF
194     
195         IF(l_ctl) THEN         ! print mean trends (used for debugging)
196            ztra = SUM( ztrd(2:nictl,2:njctl,1:jpkm1,jn) * tmask(2:nictl,2:njctl,1:jpkm1) )
197            WRITE(numout,*) ' trc/zdf  - ',ctrcnm(jn),' : ', ztra-tra_ctl(jn)
198            tra_ctl(jn) = ztra 
199         ENDIF
200         
201      END DO
202
203   END SUBROUTINE trc_zdf_imp
204
205#else
206   !!----------------------------------------------------------------------
207   !!   Dummy module :                      NO passive tracer
208   !!----------------------------------------------------------------------
209CONTAINS
210   SUBROUTINE trc_zdf_imp (kt )              ! Empty routine
211      INTEGER, INTENT(in) :: kt
212      WRITE(*,*) 'trc_zdf_imp: You should not have seen this print! error?', kt
213   END SUBROUTINE trc_zdf_imp
214#endif
215   
216!!==============================================================================
217END MODULE trczdf_imp
Note: See TracBrowser for help on using the repository browser.