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_vopt in trunk/NEMO/TOP_SRC/TRP – NEMO

source: trunk/NEMO/TOP_SRC/TRP/trczdf_imp.F90_vopt @ 186

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

CL + CE : NEMO TRC_SRC start

  • Property svn:eol-style set to native
  • Property svn:executable set to *
  • Property svn:keywords set to Author Date Id Revision
File size: 8.1 KB
Line 
1MODULE trczdf_imp
2   !!==============================================================================
3   !!                    ***  MODULE  trczdf_imp  ***
4   !! Ocean passive tracers:  vertical component of the tracer mixing trend
5   !!==============================================================================
6
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
13   USE trc         ! ocean space and time domain
14   USE trctrp_lec
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   !!   OPA 9.0 , LODYC-IPSL (2003)
30   !!----------------------------------------------------------------------
31
32CONTAINS
33
34   SUBROUTINE trc_zdf_imp( kt )
35      !!----------------------------------------------------------------------
36      !!                  ***  ROUTINE trc_zdf_imp  ***
37      !!
38      !! ** Purpose :   Compute the trend due to the vertical tracer mixing
39      !!      using an implicit time stepping and add it to the general trend
40      !!      of the tracer equations.
41      !!
42      !! ** Method  :   The vertical diffusion of tracers tra is given by:
43      !!          difft = dz( avt dz(t) ) = 1/e3t dk+1( avt/e3w dk(tra) )
44      !!      It is thus evaluated using a backward time scheme
45      !!      Surface and bottom boundary conditions: no diffusive flux on
46      !!      both tracers (bottom, applied through the masked field avt).
47      !!      Add this trend to the general trend tra :
48      !!          tra = tra + dz( avt dz(t) )
49      !!         (tra = tra + dz( avs dz(t) ) if lk_zdfddmtrc=T)
50      !!
51      !! ** Action  : - Update tra with the before vertical diffusion trend
52      !!              - save the trends in trtrd ('key_trc_diatrd')
53      !!
54      !! History :
55      !!   6.0  !  90-10  (B. Blanke)  Original code
56      !!   7.0  !  91-11  (G. Madec)
57      !!        !  92-06  (M. Imbard)  correction on tracer trend loops
58      !!        !  96-01  (G. Madec)  statement function for e3
59      !!        !  97-05  (G. Madec)  vertical component of isopycnal
60      !!        !  97-07  (G. Madec)  geopotential diffusion in s-coord
61      !!        !  98-03  (L. Bopp MA Foujols) passive tracer generalisation
62      !!        !  00-05  (MA Foujols) add lbc for tracer trends
63      !!        !  00-06  (O Aumont)  correct isopycnal scheme suppress
64      !!        !                     avt multiple correction
65      !!        !  00-08  (G. Madec)  double diffusive mixing
66      !!   8.5  !  02-08  (G. Madec)  F90: Free form and module
67      !!   9.0  !  04-03  (C. Ethe )  adapted for passive tracers
68      !!---------------------------------------------------------------------
69      !! * Arguments
70      INTEGER, INTENT( in ) ::   kt           ! ocean time-step index
71      INTEGER ::   ikst, ikenm2, ikstp1
72      !! * Local declarations
73      INTEGER ::   ji, jj, jk, jn             ! dummy loop indices
74      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   &
75         zwd, zws, zwi,          &  ! ???
76         zwx, zwy, zwt, zwz         ! ???
77      REAL(wp) ::  ztra      ! temporary scalars
78
79      REAL(wp), DIMENSION(jpi,jpj,jpk,jptra) ::   &
80         ztrd
81      !!---------------------------------------------------------------------
82
83      IF( kt == nittrc000 ) THEN
84         WRITE(numout,*)
85         WRITE(numout,*) 'trc_zdf_implicit : 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      DO jn = 1 , jptra
103
104    ! Initialisation     
105    zwd( 1 ,:,:) = 0.e0     ;     zwd(jpi,:,:) = 0.e0
106    zws( 1 ,:,:) = 0.e0     ;     zws(jpi,:,:) = 0.e0
107    zwi( 1 ,:,:) = 0.e0     ;     zwi(jpi,:,:) = 0.e0
108    zwt( 1 ,:,:) = 0.e0     ;     zwt(jpi,:,:) = 0.e0     
109         zwt(  :,:,1) = 0.e0     ;     zwt(    :,:,jpk) = 0.e0
110         !                                         
111         ! 0. Matrix construction
112         ! ----------------------
113
114         ! Diagonal, inferior, superior
115         ! (including the bottom boundary condition via avs masked
116         DO jk = 1, jpkm1                                                     
117            DO jj = 2, jpjm1                                     
118               DO ji = fs_2, fs_jpim1   ! vector opt.
119                  zwi(ji,jj,jk) = - rdttrc(jk) * fstravs(ji,jj,jk  ) /( fse3t(ji,jj,jk) * fse3w(ji,jj,jk  ) )
120                  zws(ji,jj,jk) = - rdttrc(jk) * fstravs(ji,jj,jk+1) /( fse3t(ji,jj,jk) * fse3w(ji,jj,jk+1) )
121                  zwd(ji,jj,jk) = 1. - zwi(ji,jj,jk) - zws(ji,jj,jk)
122               END DO
123            END DO
124         ENDDO
125
126         ! Surface boudary conditions
127         DO jj = 2, jpjm1       
128            DO ji = fs_2, fs_jpim1
129               zwi(ji,jj,1) = 0.e0
130               zwd(ji,jj,1) = 1. - zws(ji,jj,1)
131            END DO
132         END DO
133         
134         ! Second member construction
135         DO jk = 1, jpkm1
136            DO jj = 2, jpjm1     
137               DO ji = fs_2, fs_jpim1
138                  zwy(ji,jj,jk) = trb(ji,jj,jk,jn) + rdttrc(jk) * tra(ji,jj,jk,jn)
139               END DO
140            END DO
141         END DO
142         
143 
144   ! Matrix inversion from the first level
145   ikst = 1
146
147#   include "zdf.matrixsolver.vopt.h90"       
148 
149         
150#if defined key_trc_diatrd
151         ! Compute and save the vertical diffusive of tracers trends
152#  if defined key_trc_ldfiso
153         DO jk = 1, jpkm1
154            DO jj = 2, jpjm1
155               DO ji = fs_2, fs_jpim1   ! vector opt.
156                  ztra = ( zwx(ji,jj,jk) - trb(ji,jj,jk,jn) ) / rdttrc(jk)
157                  trtrd(ji,jj,jk,jn,6) = ztra - tra(ji,jj,jk,jn) + trtrd(ji,jj,jk,jn,6)
158               END DO
159            END DO
160         END DO
161#  else
162         DO jk = 1, jpkm1
163            DO jj = 2, jpjm1
164               DO ji = fs_2, fs_jpim1   ! vector opt.
165                  ztra = ( zwx(ji,jj,jk) - trb(ji,jj,jk,jn) ) / rdttrc(jk)
166                  trtrd(ji,jj,jk,jn,6) = ztra - tra(ji,jj,jk,jn)
167               END DO
168            END DO
169         END DO
170#  endif
171#endif 
172         ! Save the masked passive tracer after in tra
173         ! (c a u t i o n:  tracer not its trend, Leap-frog scheme done
174         !                  it will not be done in tranxt)
175         DO jk = 1, jpkm1
176            DO jj = 2, jpjm1
177               DO ji = fs_2, fs_jpim1
178                  tra(ji,jj,jk,jn) = zwx(ji,jj,jk) * tmask(ji,jj,jk)
179               END DO
180            END DO
181         END DO
182
183         IF( l_ctl .AND. lwp ) THEN
184            DO jk = 1, jpkm1
185               DO jj = 2, jpjm1
186                  DO ji = fs_2, fs_jpim1
187                     ztrd(ji,jj,jk,jn) = ( zwx(ji,jj,jk) - trb(ji,jj,jk,jn) ) / rdttrc(jk)
188                  END DO
189               END DO
190            END DO
191         ENDIF
192     
193         IF( l_ctl .AND. lwp ) THEN         ! print mean trends (used for debugging)
194            ztra = SUM( ztrd(2:jpim1,2:jpjm1,1:jpkm1,jn) * tmask(2:jpim1,2:jpjm1,1:jpkm1) )
195            WRITE(numout,*) ' trc/zdf  - ',ctrcnm(jn),' : ', ztra-tra_ctl(jn)
196            tra_ctl(jn) = ztra
197         ENDIF
198         
199      END DO
200
201   END SUBROUTINE trc_zdf_imp
202
203!!==============================================================================
204END MODULE trczdf_imp
Note: See TracBrowser for help on using the repository browser.