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

Last change on this file since 1187 was 1175, checked in by cetlod, 16 years ago

update transport modules to take into account new trends organization, see ticket:248

  • Property svn:executable set to *
  • Property svn:keywords set to Id
File size: 12.2 KB
Line 
1MODULE trczdf_imp
2   !!==============================================================================
3   !!                    ***  MODULE  trczdf_imp  ***
4   !! Ocean passive tracers:  vertical component of the tracer mixing trend
5   !!==============================================================================
6   !! History :  6.0  !  90-10  (B. Blanke)  Original code
7   !!            7.0  !  91-11  (G. Madec)
8   !!                 !  92-06  (M. Imbard)  correction on tracer trend loops
9   !!                 !  96-01  (G. Madec)  statement function for e3
10   !!                 !  97-05  (G. Madec)  vertical component of isopycnal
11   !!                 !  97-07  (G. Madec)  geopotential diffusion in s-coord
12   !!                 !  98-03  (L. Bopp MA Foujols) passive tracer generalisation
13   !!                 !  00-05  (MA Foujols) add lbc for tracer trends
14   !!                 !  00-06  (O Aumont)  correct isopycnal scheme suppress
15   !!                 !                     avt multiple correction
16   !!                 !  00-08  (G. Madec)  double diffusive mixing
17   !!            8.5  !  02-08  (G. Madec)  F90: Free form and module
18   !!            9.0  !  04-03  (C. Ethe )  adapted for passive tracers
19   !!                 !  07-02  (C. Deltel)  Diagnose ML trends for passive tracers
20   !!----------------------------------------------------------------------
21#if defined key_top
22   !!----------------------------------------------------------------------
23   !!   'key_top'                                                TOP models
24   !!----------------------------------------------------------------------
25   !!   trc_zdf_imp  : update the tracer trend with the vertical diffusion
26   !!                  using an implicit time-stepping.
27   !!----------------------------------------------------------------------
28   !! * Modules used
29   USE oce_trc             ! ocean dynamics and active tracers variables
30   USE trp_trc                 ! ocean passive tracers variables
31   USE trctrp_lec          ! passive tracers transport
32   USE prtctl_trc
33   USE trdmld_trc
34   USE trdmld_trc_oce
35
36   IMPLICIT NONE
37   PRIVATE
38
39   !! * Routine accessibility
40   PUBLIC trc_zdf_imp          ! routine called by step.F90
41
42   !! * Module variable
43   REAL(wp), DIMENSION(jpk) ::   &
44      rdttrc                     ! vertical profile of 2 x tracer time-step
45
46   !! * Substitutions
47#  include "top_substitute.h90"
48   !!----------------------------------------------------------------------
49   !!   TOP 1.0 , LOCEAN-IPSL (2005)
50   !! $Id$
51   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
52   !!----------------------------------------------------------------------
53
54CONTAINS
55
56   SUBROUTINE trc_zdf_imp( kt )
57      !!----------------------------------------------------------------------
58      !!                  ***  ROUTINE trc_zdf_imp  ***
59      !!
60      !! ** Purpose :   Compute the trend due to the vertical tracer mixing
61      !!      using an implicit time stepping and add it to the general trend
62      !!      of the tracer equations.
63      !!
64      !! ** Method  :   The vertical diffusion of tracers tra is given by:
65      !!          difft = dz( avt dz(t) ) = 1/e3t dk+1( avt/e3w dk(tra) )
66      !!      It is thus evaluated using a backward time scheme
67      !!      Surface and bottom boundary conditions: no diffusive flux on
68      !!      both tracers (bottom, applied through the masked field avt).
69      !!      Add this trend to the general trend tra :
70      !!          tra = tra + dz( avt dz(t) )
71      !!         (tra = tra + dz( avs dz(t) ) if lk_zdfddmtrc=T)
72      !!
73      !! ** Action  : - Update tra with the before vertical diffusion trend
74      !!              - save the trends
75      !!
76      !!---------------------------------------------------------------------
77      USE oce_trc, ONLY : ztrtrd => ua      ! use ua as 3D workspace
78      !!
79      !! * Arguments
80      INTEGER, INTENT( in ) ::   kt           ! ocean time-step index
81      INTEGER ::   ikst, ikenm2, ikstp1
82      !! * Local declarations
83      INTEGER ::   ji, jj, jk, jn             ! dummy loop indices
84      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   &
85         zwd, zws, zwi,          &  ! ???
86         zwx, zwy, zwt              ! ???
87      REAL(wp) ::  ztra      ! temporary scalars
88      REAL(wp), DIMENSION(jpi,jpj,jpk,jptra) ::   &
89         ztrd
90      CHARACTER (len=22) :: charout
91      !!---------------------------------------------------------------------
92
93      IF( kt == nittrc000 ) THEN
94         WRITE(numout,*)
95         WRITE(numout,*) 'trc_zdf_implicit : vertical tracer mixing'
96         WRITE(numout,*) '~~~~~~~~~~~~~~~'
97      ENDIF
98
99      ! 0. Local constant initialization
100      ! --------------------------------
101      IF( ln_trcadv_cen2 .OR. ln_trcadv_tvd ) THEN
102         ! time step = 2 rdttra with Arakawa or TVD advection scheme
103         IF( neuler == 0 .AND. kt == nittrc000 ) THEN
104            rdttrc(:) =  rdttra(:) * FLOAT(ndttrc)             ! restarting with Euler time stepping
105         ELSEIF( kt <= nittrc000 + ndttrc ) THEN
106            rdttrc(:) = 2. * rdttra(:) * FLOAT(ndttrc)         ! leapfrog
107         ENDIF
108      ELSE
109         rdttrc(:) =  rdttra(:) * FLOAT(ndttrc)     
110      ENDIF
111     !                                                       ! ===========
112      DO jn = 1, jptra                                        ! tracer loop
113         !                                                    ! ===========
114         IF( l_trdtrc ) ztrtrd(:,:,:) = tra(:,:,:,jn)         ! ??? validation needed
115
116    ! Initialisation     
117    zwd( 1 ,:,:) = 0.e0     ;     zwd(jpi,:,:) = 0.e0
118    zws( 1 ,:,:) = 0.e0     ;     zws(jpi,:,:) = 0.e0
119    zwi( 1 ,:,:) = 0.e0     ;     zwi(jpi,:,:) = 0.e0
120    zwt( 1 ,:,:) = 0.e0     ;     zwt(jpi,:,:) = 0.e0     
121         zwt(  :,:,1) = 0.e0     ;     zwt(  :,:,jpk) = 0.e0
122         !                                         
123         ! 0. Matrix construction
124         ! ----------------------
125
126         ! Diagonal, inferior, superior
127         ! (including the bottom boundary condition via avs masked
128         DO jk = 1, jpkm1                                                     
129            DO jj = 2, jpjm1                                     
130               DO ji = fs_2, fs_jpim1   ! vector opt.
131                  zwi(ji,jj,jk) = - rdttrc(jk) * fstravs(ji,jj,jk  ) /( fse3t(ji,jj,jk) * fse3w(ji,jj,jk  ) )
132                  zws(ji,jj,jk) = - rdttrc(jk) * fstravs(ji,jj,jk+1) /( fse3t(ji,jj,jk) * fse3w(ji,jj,jk+1) )
133                  zwd(ji,jj,jk) = 1. - zwi(ji,jj,jk) - zws(ji,jj,jk)
134               END DO
135            END DO
136         END DO
137
138         ! Surface boudary conditions
139         DO jj = 2, jpjm1       
140            DO ji = fs_2, fs_jpim1
141               zwi(ji,jj,1) = 0.e0
142               zwd(ji,jj,1) = 1. - zws(ji,jj,1)
143            END DO
144         END DO
145         
146         ! Second member construction
147         DO jk = 1, jpkm1
148            DO jj = 2, jpjm1     
149               DO ji = fs_2, fs_jpim1
150                  zwy(ji,jj,jk) = trb(ji,jj,jk,jn) + rdttrc(jk) * tra(ji,jj,jk,jn)
151               END DO
152            END DO
153         END DO
154         
155         
156         ! Matrix inversion from the first level
157         !----------------------------------------------------------------------
158         !   solve m.x = y  where m is a tri diagonal matrix ( jpk*jpk )
159         !
160         !        ( zwd1 zws1   0    0    0  )( zwx1 ) ( zwy1 )
161         !        ( zwi2 zwd2 zws2   0    0  )( zwx2 ) ( zwy2 )
162         !        (  0   zwi3 zwd3 zws3   0  )( zwx3 )=( zwy3 )
163         !        (        ...               )( ...  ) ( ...  )
164         !        (  0    0    0   zwik zwdk )( zwxk ) ( zwyk )
165         !
166         !   m is decomposed in the product of an upper and lower triangular matrix
167         !   The 3 diagonal terms are in 2d arrays: zwd, zws, zwi
168         !   The second member is in 2d array zwy
169         !   The solution is in 2d array zwx
170         !   The 3d arry zwt is a work space array
171         !   zwy is used and then used as a work space array : its value is modified!
172         !
173         !   N.B. the starting vertical index (ikst) is equal to 1 except for
174         !   the resolution of tke matrix where surface tke value is prescribed
175         !   so that ikstrt=2.
176        ikst = 1
177        ikstp1 = ikst + 1
178        ikenm2 = jpk - 2
179       
180        DO jj = 2, jpjm1
181           DO ji = fs_2, fs_jpim1
182              zwt(ji,jj,ikst) = zwd(ji,jj,ikst)
183           END DO
184        END DO
185       
186        DO jk = ikstp1, jpkm1
187           DO jj = 2, jpjm1
188              DO ji = fs_2, fs_jpim1
189                 zwt(ji,jj,jk) = zwd(ji,jj,jk) - zwi(ji,jj,jk) * zws(ji,jj,jk-1) / zwt(ji,jj,jk-1)
190              END DO
191           END DO
192        END DO
193       
194        DO jk = ikstp1, jpkm1
195           DO jj = 2, jpjm1
196              DO ji = fs_2, fs_jpim1
197                 zwy(ji,jj,jk) = zwy(ji,jj,jk) - zwi(ji,jj,jk) / zwt(ji,jj,jk-1) * zwy(ji,jj,jk-1)
198              END DO
199           END DO
200        END DO
201       
202        DO jj = 2, jpjm1
203           DO ji = fs_2, fs_jpim1
204              zwx(ji,jj,jpkm1) = zwy(ji,jj,jpkm1) / zwt(ji,jj,jpkm1)
205           END DO
206        END DO
207       
208        DO jk = ikenm2, ikst, -1
209           DO jj = 2, jpjm1
210              DO ji = fs_2, fs_jpim1
211                 zwx(ji,jj,jk) = ( zwy(ji,jj,jk) - zws(ji,jj,jk) * zwx(ji,jj,jk+1) ) / zwt(ji,jj,jk)
212              END DO
213           END DO
214        END DO
215
216#if defined key_trc_diatrd
217         ! Compute and save the vertical diffusive of tracers trends
218#  if defined key_trcldf_iso
219         DO jk = 1, jpkm1
220            DO jj = 2, jpjm1
221               DO ji = fs_2, fs_jpim1   ! vector opt.
222                  ztra = ( zwx(ji,jj,jk) - trb(ji,jj,jk,jn) ) / rdttrc(jk)
223                  IF (luttrd(jn)) trtrd(ji,jj,jk,ikeep(jn),6) = ztra - tra(ji,jj,jk,jn) + trtrd(ji,jj,jk,ikeep(jn),6)
224               END DO
225            END DO
226         END DO
227#  else
228         DO jk = 1, jpkm1
229            DO jj = 2, jpjm1
230               DO ji = fs_2, fs_jpim1   ! vector opt.
231                  ztra = ( zwx(ji,jj,jk) - trb(ji,jj,jk,jn) ) / rdttrc(jk)
232                  IF (luttrd(jn)) trtrd(ji,jj,jk,ikeep(jn),6) = ztra - tra(ji,jj,jk,jn)
233               END DO
234            END DO
235         END DO
236#  endif
237#endif
238
239         ! Save the masked passive tracer after in tra
240         ! (c a u t i o n:  tracer not its trend, Leap-frog scheme done
241         !                  it will not be done in tranxt)
242         DO jk = 1, jpkm1
243            DO jj = 2, jpjm1
244               DO ji = fs_2, fs_jpim1
245                  tra(ji,jj,jk,jn) = zwx(ji,jj,jk) * tmask(ji,jj,jk)
246               END DO
247            END DO
248         END DO
249
250         IF( l_trdtrc ) THEN                            ! trends
251            DO jk = 1, jpkm1
252               ztrtrd(:,:,jk) = ( ( tra(:,:,jk,jn) - trb(:,:,jk,jn) ) / rdttrc(jk) ) - ztrtrd(:,:,jk)
253            END DO
254            IF (luttrd(jn)) CALL trd_mod_trc(ztrtrd, jn, jptrc_trd_zdf, kt)
255         END IF
256
257         IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
258            ztrd(:,:,:,:) = 0.
259            DO jk = 1, jpkm1
260               DO jj = 2, jpjm1
261                  DO ji = fs_2, fs_jpim1
262                     ztrd(ji,jj,jk,jn) = ( zwx(ji,jj,jk) - trb(ji,jj,jk,jn) ) / rdttrc(jk)
263                  END DO
264               END DO
265            END DO
266         ENDIF
267
268         !                                                    ! ===========
269      END DO                                                  ! tracer loop
270      !                                                       ! ===========
271
272      IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
273         WRITE(charout, FMT="('zdf - imp')")
274         CALL prt_ctl_trc_info(charout)
275         CALL prt_ctl_trc(tab4d=ztrd, mask=tmask, clinfo=ctrcnm,clinfo2='trd')
276      ENDIF
277
278   END SUBROUTINE trc_zdf_imp
279
280#else
281   !!----------------------------------------------------------------------
282   !!   Dummy module :                      NO passive tracer
283   !!----------------------------------------------------------------------
284CONTAINS
285   SUBROUTINE trc_zdf_imp (kt )              ! Empty routine
286      INTEGER, INTENT(in) :: kt
287      WRITE(*,*) 'trc_zdf_imp: You should not have seen this print! error?', kt
288   END SUBROUTINE trc_zdf_imp
289#endif
290   
291!!==============================================================================
292END MODULE trczdf_imp
Note: See TracBrowser for help on using the repository browser.