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

source: branches/DEV_r1784_mid_year_merge_2010/NEMO/TOP_SRC/TRP/trczdf_imp.F90 @ 1953

Last change on this file since 1953 was 1953, checked in by acc, 14 years ago

ticket #684 step 3: Add in changes from the trunk between revisions 1784 and 1821. No conflicts so far

  • Property svn:executable set to *
  • Property svn:keywords set to Id
File size: 12.1 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      !!
78      !! * Arguments
79      USE oce, ONLY :   ztrtrd => ua    ! use ua as 3D workspace
80
81      INTEGER, INTENT( in ) ::   kt           ! ocean time-step index
82      INTEGER ::   ikst, ikenm2, ikstp1
83      !! * Local declarations
84      INTEGER ::   ji, jj, jk, jn             ! dummy loop indices
85      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   &
86         zwd, zws, zwi,          &  ! ???
87         zwx, zwy, zwt              ! ???
88#if defined key_trc_diatrd
89      REAL(wp) ::  ztra      ! temporary scalars
90#endif
91      REAL(wp), DIMENSION(jpi,jpj,jpk,jptra) ::   &
92         ztrd
93      CHARACTER (len=22) :: charout
94      !!---------------------------------------------------------------------
95
96      IF( kt == nittrc000 ) THEN
97         WRITE(numout,*)
98         WRITE(numout,*) 'trc_zdf_implicit : vertical tracer mixing'
99         WRITE(numout,*) '~~~~~~~~~~~~~~~'
100      ENDIF
101
102      ! 0. Local constant initialization
103      ! --------------------------------
104      IF( ln_trcadv_cen2 .OR. ln_trcadv_tvd ) THEN
105         ! time step = 2 rdttra with Arakawa or TVD advection scheme
106         IF( neuler == 0 .AND. kt == nittrc000 ) THEN
107            rdttrc(:) =  rdttra(:) * FLOAT(ndttrc)             ! restarting with Euler time stepping
108         ELSEIF( kt <= nittrc000 + ndttrc ) THEN
109            rdttrc(:) = 2. * rdttra(:) * FLOAT(ndttrc)         ! leapfrog
110         ENDIF
111      ELSE
112         rdttrc(:) =  rdttra(:) * FLOAT(ndttrc)     
113      ENDIF
114
115      ! Initialisation
116      zwd( 1 ,:,:) = 0.e0     ;     zwd(jpi,:,:) = 0.e0
117      zws( 1 ,:,:) = 0.e0     ;     zws(jpi,:,:) = 0.e0
118      zwi( 1 ,:,:) = 0.e0     ;     zwi(jpi,:,:) = 0.e0
119      !                                         
120      ! 0. Matrix construction
121      ! ----------------------
122
123      ! Diagonal, inferior, superior
124      ! (including the bottom boundary condition via avs masked
125      DO jk = 1, jpkm1                   
126         DO jj = 2, jpjm1                                   
127            DO ji = fs_2, fs_jpim1   ! vector opt.
128               zwi(ji,jj,jk) = - rdttrc(jk) * fstravs(ji,jj,jk  ) /( fse3t(ji,jj,jk) * fse3w(ji,jj,jk  ) )
129               zws(ji,jj,jk) = - rdttrc(jk) * fstravs(ji,jj,jk+1) /( fse3t(ji,jj,jk) * fse3w(ji,jj,jk+1) )
130               zwd(ji,jj,jk) = 1. - zwi(ji,jj,jk) - zws(ji,jj,jk)
131            END DO
132         END DO
133      END DO
134
135      ! Surface boudary conditions
136      DO jj = 2, jpjm1       
137         DO ji = fs_2, fs_jpim1
138            zwi(ji,jj,1) = 0.e0
139            zwd(ji,jj,1) = 1. - zws(ji,jj,1) 
140         END DO
141      END DO
142
143      !                                                       ! ===========
144      DO jn = 1, jptra                                        ! tracer loop
145         !                                                    ! ===========
146         IF( l_trdtrc ) ztrtrd(:,:,:) = tra(:,:,:,jn)         ! ??? validation needed
147
148    zwt( 1 ,:,:) = 0.e0     ;     zwt(jpi,:,:) = 0.e0     
149         zwt(  :,:,1) = 0.e0     ;     zwt(  :,:,jpk) = 0.e0
150         
151         ! Second member construction
152         DO jk = 1, jpkm1
153            DO jj = 2, jpjm1     
154               DO ji = fs_2, fs_jpim1
155                  zwy(ji,jj,jk) = trb(ji,jj,jk,jn) + rdttrc(jk) * tra(ji,jj,jk,jn)
156               END DO
157            END DO
158         END DO
159         
160         
161         ! Matrix inversion from the first level
162         !----------------------------------------------------------------------
163         !   solve m.x = y  where m is a tri diagonal matrix ( jpk*jpk )
164         !
165         !        ( zwd1 zws1   0    0    0  )( zwx1 ) ( zwy1 )
166         !        ( zwi2 zwd2 zws2   0    0  )( zwx2 ) ( zwy2 )
167         !        (  0   zwi3 zwd3 zws3   0  )( zwx3 )=( zwy3 )
168         !        (        ...               )( ...  ) ( ...  )
169         !        (  0    0    0   zwik zwdk )( zwxk ) ( zwyk )
170         !
171         !   m is decomposed in the product of an upper and lower triangular matrix
172         !   The 3 diagonal terms are in 2d arrays: zwd, zws, zwi
173         !   The second member is in 2d array zwy
174         !   The solution is in 2d array zwx
175         !   The 3d arry zwt is a work space array
176         !   zwy is used and then used as a work space array : its value is modified!
177         !
178         !   N.B. the starting vertical index (ikst) is equal to 1 except for
179         !   the resolution of tke matrix where surface tke value is prescribed
180         !   so that ikstrt=2.
181        ikst = 1
182        ikstp1 = ikst + 1
183        ikenm2 = jpk - 2
184       
185        DO jj = 2, jpjm1
186           DO ji = fs_2, fs_jpim1
187              zwt(ji,jj,ikst) = zwd(ji,jj,ikst)
188           END DO
189        END DO
190       
191        DO jk = ikstp1, jpkm1
192           DO jj = 2, jpjm1
193              DO ji = fs_2, fs_jpim1
194                 zwt(ji,jj,jk) = zwd(ji,jj,jk) - zwi(ji,jj,jk) * zws(ji,jj,jk-1) / zwt(ji,jj,jk-1)
195              END DO
196           END DO
197        END DO
198       
199        DO jk = ikstp1, jpkm1
200           DO jj = 2, jpjm1
201              DO ji = fs_2, fs_jpim1
202                 zwy(ji,jj,jk) = zwy(ji,jj,jk) - zwi(ji,jj,jk) / zwt(ji,jj,jk-1) * zwy(ji,jj,jk-1)
203              END DO
204           END DO
205        END DO
206       
207        DO jj = 2, jpjm1
208           DO ji = fs_2, fs_jpim1
209              zwx(ji,jj,jpkm1) = zwy(ji,jj,jpkm1) / zwt(ji,jj,jpkm1)
210           END DO
211        END DO
212       
213        DO jk = ikenm2, ikst, -1
214           DO jj = 2, jpjm1
215              DO ji = fs_2, fs_jpim1
216                 zwx(ji,jj,jk) = ( zwy(ji,jj,jk) - zws(ji,jj,jk) * zwx(ji,jj,jk+1) ) / zwt(ji,jj,jk)
217              END DO
218           END DO
219        END DO
220
221#if defined key_trc_diatrd
222         ! Compute and save the vertical diffusive of tracers trends
223#  if defined key_trcldf_iso
224         DO jk = 1, jpkm1
225            DO jj = 2, jpjm1
226               DO ji = fs_2, fs_jpim1   ! vector opt.
227                  ztra = ( zwx(ji,jj,jk) - trb(ji,jj,jk,jn) ) / rdttrc(jk)
228                  IF (luttrd(jn)) trtrd(ji,jj,jk,ikeep(jn),6) = ztra - tra(ji,jj,jk,jn) + trtrd(ji,jj,jk,ikeep(jn),6)
229               END DO
230            END DO
231         END DO
232#  else
233         DO jk = 1, jpkm1
234            DO jj = 2, jpjm1
235               DO ji = fs_2, fs_jpim1   ! vector opt.
236                  ztra = ( zwx(ji,jj,jk) - trb(ji,jj,jk,jn) ) / rdttrc(jk)
237                  IF (luttrd(jn)) trtrd(ji,jj,jk,ikeep(jn),6) = ztra - tra(ji,jj,jk,jn)
238               END DO
239            END DO
240         END DO
241#  endif
242#endif
243
244         ! Save the masked passive tracer after in tra
245         ! (c a u t i o n:  tracer not its trend, Leap-frog scheme done
246         !                  it will not be done in tranxt)
247         DO jk = 1, jpkm1
248            DO jj = 2, jpjm1
249               DO ji = fs_2, fs_jpim1
250                  tra(ji,jj,jk,jn) = zwx(ji,jj,jk) * tmask(ji,jj,jk)
251               END DO
252            END DO
253         END DO
254
255         IF( l_trdtrc ) THEN                            ! trends
256            DO jk = 1, jpkm1
257               ztrtrd(:,:,jk) = ( ( tra(:,:,jk,jn) - trb(:,:,jk,jn) ) / rdttrc(jk) ) - ztrtrd(:,:,jk)
258            END DO
259            IF (luttrd(jn)) CALL trd_mod_trc(ztrtrd, jn, jptrc_trd_zdf, kt)
260         END IF
261
262         IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
263            ztrd(:,:,:,:) = 0.
264            DO jk = 1, jpkm1
265               DO jj = 2, jpjm1
266                  DO ji = fs_2, fs_jpim1
267                     ztrd(ji,jj,jk,jn) = ( zwx(ji,jj,jk) - trb(ji,jj,jk,jn) ) / rdttrc(jk)
268                  END DO
269               END DO
270            END DO
271         ENDIF
272
273         !                                                    ! ===========
274      END DO                                                  ! tracer loop
275      !                                                       ! ===========
276
277      IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
278         WRITE(charout, FMT="('zdf - imp')")
279         CALL prt_ctl_trc_info(charout)
280         CALL prt_ctl_trc(tab4d=ztrd, mask=tmask, clinfo=ctrcnm,clinfo2='trd')
281      ENDIF
282
283   END SUBROUTINE trc_zdf_imp
284
285#else
286   !!----------------------------------------------------------------------
287   !!   Dummy module :                      NO passive tracer
288   !!----------------------------------------------------------------------
289CONTAINS
290   SUBROUTINE trc_zdf_imp (kt )              ! Empty routine
291      INTEGER, INTENT(in) :: kt
292      WRITE(*,*) 'trc_zdf_imp: You should not have seen this print! error?', kt
293   END SUBROUTINE trc_zdf_imp
294#endif
295   
296!!==============================================================================
297END MODULE trczdf_imp
Note: See TracBrowser for help on using the repository browser.