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.
trazdf.F90 in branches/2017/dev_r7881_ENHANCE09_RK3/NEMOGCM/NEMO/OPA_SRC/TRA – NEMO

source: branches/2017/dev_r7881_ENHANCE09_RK3/NEMOGCM/NEMO/OPA_SRC/TRA/trazdf.F90 @ 8568

Last change on this file since 8568 was 8568, checked in by gm, 7 years ago

#1911 (ENHANCE-09): PART I.2 - _NONE option + remove zts + see associated wiki page

  • Property svn:keywords set to Id
File size: 13.0 KB
Line 
1MODULE trazdf
2   !!==============================================================================
3   !!                 ***  MODULE  trazdf  ***
4   !! Ocean active tracers:  vertical component of the tracer mixing trend
5   !!==============================================================================
6   !! History :  1.0  !  2005-11  (G. Madec)  Original code
7   !!            3.0  !  2008-01  (C. Ethe, G. Madec)  merge TRC-TRA
8   !!            4.0  !  2017-06  (G. Madec)  remove explict time-stepping option
9   !!----------------------------------------------------------------------
10
11   !!----------------------------------------------------------------------
12   !!   tra_zdf       : Update the tracer trend with the vertical diffusion
13   !!----------------------------------------------------------------------
14   USE oce            ! ocean dynamics and tracers variables
15   USE dom_oce        ! ocean space and time domain variables
16   USE domvvl         ! variable volume
17   USE phycst         ! physical constant
18   USE zdf_oce        ! ocean vertical physics variables
19   USE sbc_oce        ! surface boundary condition: ocean
20   USE ldftra         ! lateral diffusion: eddy diffusivity
21   USE ldfslp         ! lateral diffusion: iso-neutral slope
22   USE trd_oce        ! trends: ocean variables
23   USE trdtra         ! trends: tracer trend manager
24   !
25   USE in_out_manager ! I/O manager
26   USE prtctl         ! Print control
27   USE lbclnk         ! ocean lateral boundary conditions (or mpp link)
28   USE lib_mpp        ! MPP library
29   USE timing         ! Timing
30
31   IMPLICIT NONE
32   PRIVATE
33
34   PUBLIC   tra_zdf       ! called by step.F90
35   PUBLIC   tra_zdf_imp   ! called by trczdf.F90
36
37   !! * Substitutions
38#  include "vectopt_loop_substitute.h90"
39   !!----------------------------------------------------------------------
40   !! NEMO/OPA 4.0 , NEMO Consortium (2017)
41   !! $Id$
42   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
43   !!----------------------------------------------------------------------
44CONTAINS
45
46   SUBROUTINE tra_zdf( kt )
47      !!----------------------------------------------------------------------
48      !!                  ***  ROUTINE tra_zdf  ***
49      !!
50      !! ** Purpose :   compute the vertical ocean tracer physics.
51      !!---------------------------------------------------------------------
52      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index
53      !
54      INTEGER  ::   jk                   ! Dummy loop indices
55      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::   ztrdt, ztrds   ! 3D workspace
56      !!---------------------------------------------------------------------
57      !
58      IF( ln_timing )   CALL timing_start('tra_zdf')
59      !
60      IF( neuler == 0 .AND. kt == nit000 ) THEN     ! at nit000
61         r2dt =  rdt                                     ! = rdt (restarting with Euler time stepping)
62      ELSEIF( kt <= nit000 + 1) THEN                ! at nit000 or nit000+1
63         r2dt = 2. * rdt                                 ! = 2 rdt (leapfrog)
64      ENDIF
65      !
66      IF( l_trdtra )   THEN                  !* Save ta and sa trends
67         ALLOCATE( ztrdt(jpi,jpj,jpk) , ztrds(jpi,jpj,jpk) )
68         ztrdt(:,:,:) = tsa(:,:,:,jp_tem)
69         ztrds(:,:,:) = tsa(:,:,:,jp_sal)
70      ENDIF
71      !
72      !                                      !* compute lateral mixing trend and add it to the general trend
73      CALL tra_zdf_imp( kt, nit000, 'TRA', r2dt, tsb, tsa, jpts ) 
74
75!!gm WHY here !   and I don't like that !
76      ! DRAKKAR SSS control {
77      ! JMM avoid negative salinities near river outlet ! Ugly fix
78      ! JMM : restore negative salinities to small salinities:
79      WHERE( tsa(:,:,:,jp_sal) < 0._wp )   tsa(:,:,:,jp_sal) = 0.1_wp
80!!gm
81
82      IF( l_trdtra )   THEN                      ! save the vertical diffusive trends for further diagnostics
83         DO jk = 1, jpkm1
84            ztrdt(:,:,jk) = ( ( tsa(:,:,jk,jp_tem) - tsb(:,:,jk,jp_tem) ) / r2dt ) - ztrdt(:,:,jk)
85            ztrds(:,:,jk) = ( ( tsa(:,:,jk,jp_sal) - tsb(:,:,jk,jp_sal) ) / r2dt ) - ztrds(:,:,jk)
86         END DO
87!!gm this should be moved in trdtra.F90 and done on all trends
88         CALL lbc_lnk( ztrdt, 'T', 1. )
89         CALL lbc_lnk( ztrds, 'T', 1. )
90!!gm
91         CALL trd_tra( kt, 'TRA', jp_tem, jptra_zdf, ztrdt )
92         CALL trd_tra( kt, 'TRA', jp_sal, jptra_zdf, ztrds )
93         DEALLOCATE( ztrdt , ztrds )
94      ENDIF
95      !                                          ! print mean trends (used for debugging)
96      IF(ln_ctl)   CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' zdf  - Ta: ', mask1=tmask,               &
97         &                       tab3d_2=tsa(:,:,:,jp_sal), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' )
98      !
99      IF( ln_timing )   CALL timing_stop('tra_zdf')
100      !
101   END SUBROUTINE tra_zdf
102
103 
104   SUBROUTINE tra_zdf_imp( kt, kit000, cdtype, p2dt, ptb, pta, kjpt ) 
105      !!----------------------------------------------------------------------
106      !!                  ***  ROUTINE tra_zdf_imp  ***
107      !!
108      !! ** Purpose :   Compute the after tracer through a implicit computation
109      !!     of the vertical tracer diffusion (including the vertical component
110      !!     of lateral mixing (only for 2nd order operator, for fourth order
111      !!     it is already computed and add to the general trend in traldf)
112      !!
113      !! ** Method  :  The vertical diffusion of a tracer ,t , is given by:
114      !!          difft = dz( avt dz(t) ) = 1/e3t dk+1( avt/e3w dk(t) )
115      !!      It is computed using a backward time scheme (t=after field)
116      !!      which provide directly the after tracer field.
117      !!      If ln_zdfddm=T, use avs for salinity or for passive tracers
118      !!      Surface and bottom boundary conditions: no diffusive flux on
119      !!      both tracers (bottom, applied through the masked field avt).
120      !!      If iso-neutral mixing, add to avt the contribution due to lateral mixing.
121      !!
122      !! ** Action  : - pta  becomes the after tracer
123      !!---------------------------------------------------------------------
124      INTEGER                              , INTENT(in   ) ::   kt       ! ocean time-step index
125      INTEGER                              , INTENT(in   ) ::   kit000   ! first time step index
126      CHARACTER(len=3)                     , INTENT(in   ) ::   cdtype   ! =TRA or TRC (tracer indicator)
127      INTEGER                              , INTENT(in   ) ::   kjpt     ! number of tracers
128      REAL(wp)                             , INTENT(in   ) ::   p2dt     ! tracer time-step
129      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(in   ) ::   ptb      ! before and now tracer fields
130      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(inout) ::   pta      ! in: tracer trend ; out: after tracer field
131      !
132      INTEGER  ::  ji, jj, jk, jn   ! dummy loop indices
133      REAL(wp) ::  zrhs             ! local scalars
134      REAL(wp), DIMENSION(jpi,jpj,jpk) ::  zwi, zwt, zwd, zws
135      !!---------------------------------------------------------------------
136      !
137      IF( ln_timing )   CALL timing_start('tra_zdf_imp')
138      !
139      IF( kt == kit000 )  THEN
140         IF(lwp)WRITE(numout,*)
141         IF(lwp)WRITE(numout,*) 'tra_zdf_imp : implicit vertical mixing on ', cdtype
142         IF(lwp)WRITE(numout,*) '~~~~~~~~~~~ '
143      ENDIF
144      !                                               ! ============= !
145      DO jn = 1, kjpt                                 !  tracer loop  !
146         !                                            ! ============= !
147         !  Matrix construction
148         ! --------------------
149         ! Build matrix if temperature or salinity (only in double diffusion case) or first passive tracer
150         !
151         IF(  ( cdtype == 'TRA' .AND. ( jn == jp_tem .OR. ( jn == jp_sal .AND. ln_zdfddm ) ) ) .OR.   &
152            & ( cdtype == 'TRC' .AND. jn == 1 )  )  THEN
153            !
154            ! vertical mixing coef.: avt for temperature, avs for salinity and passive tracers
155            IF( cdtype == 'TRA' .AND. jn == jp_tem ) THEN   ;   zwt(:,:,2:jpk) = avt(:,:,2:jpk)
156            ELSE                                            ;   zwt(:,:,2:jpk) = avs(:,:,2:jpk)
157            ENDIF
158            zwt(:,:,1) = 0._wp
159            !
160            IF( l_ldfslp ) THEN            ! isoneutral diffusion: add the contribution
161               IF( ln_traldf_msc  ) THEN     ! MSC iso-neutral operator
162                  DO jk = 2, jpkm1
163                     DO jj = 2, jpjm1
164                        DO ji = fs_2, fs_jpim1   ! vector opt.
165                           zwt(ji,jj,jk) = zwt(ji,jj,jk) + akz(ji,jj,jk) 
166                        END DO
167                     END DO
168                  END DO
169               ELSE                          ! standard or triad iso-neutral operator
170                  DO jk = 2, jpkm1
171                     DO jj = 2, jpjm1
172                        DO ji = fs_2, fs_jpim1   ! vector opt.
173                           zwt(ji,jj,jk) = zwt(ji,jj,jk) + ah_wslp2(ji,jj,jk)
174                        END DO
175                     END DO
176                  END DO
177               ENDIF
178            ENDIF
179            !
180            ! Diagonal, lower (i), upper (s)  (including the bottom boundary condition since avt is masked)
181            DO jk = 1, jpkm1
182               DO jj = 2, jpjm1
183                  DO ji = fs_2, fs_jpim1   ! vector opt.
184!!gm BUG  I think, use e3w_a instead of e3w_n, not sure of that
185                     zwi(ji,jj,jk) = - p2dt * zwt(ji,jj,jk  ) / e3w_n(ji,jj,jk  )
186                     zws(ji,jj,jk) = - p2dt * zwt(ji,jj,jk+1) / e3w_n(ji,jj,jk+1)
187                     zwd(ji,jj,jk) = e3t_a(ji,jj,jk) - zwi(ji,jj,jk) - zws(ji,jj,jk)
188                 END DO
189               END DO
190            END DO
191            !
192            !! Matrix inversion from the first level
193            !!----------------------------------------------------------------------
194            !   solve m.x = y  where m is a tri diagonal matrix ( jpk*jpk )
195            !
196            !        ( zwd1 zws1   0    0    0  )( zwx1 ) ( zwy1 )
197            !        ( zwi2 zwd2 zws2   0    0  )( zwx2 ) ( zwy2 )
198            !        (  0   zwi3 zwd3 zws3   0  )( zwx3 )=( zwy3 )
199            !        (        ...               )( ...  ) ( ...  )
200            !        (  0    0    0   zwik zwdk )( zwxk ) ( zwyk )
201            !
202            !   m is decomposed in the product of an upper and lower triangular matrix.
203            !   The 3 diagonal terms are in 3d arrays: zwd, zws, zwi.
204            !   Suffices i,s and d indicate "inferior" (below diagonal), diagonal
205            !   and "superior" (above diagonal) components of the tridiagonal system.
206            !   The solution will be in the 4d array pta.
207            !   The 3d array zwt is used as a work space array.
208            !   En route to the solution pta is used a to evaluate the rhs and then
209            !   used as a work space array: its value is modified.
210            !
211            DO jj = 2, jpjm1        !* 1st recurrence:   Tk = Dk - Ik Sk-1 / Tk-1   (increasing k)
212               DO ji = fs_2, fs_jpim1            ! done one for all passive tracers (so included in the IF instruction)
213                  zwt(ji,jj,1) = zwd(ji,jj,1)
214               END DO
215            END DO
216            DO jk = 2, jpkm1
217               DO jj = 2, jpjm1
218                  DO ji = fs_2, fs_jpim1
219                     zwt(ji,jj,jk) = zwd(ji,jj,jk) - zwi(ji,jj,jk) * zws(ji,jj,jk-1) / zwt(ji,jj,jk-1)
220                  END DO
221               END DO
222            END DO
223            !
224         ENDIF 
225         !         
226         DO jj = 2, jpjm1           !* 2nd recurrence:    Zk = Yk - Ik / Tk-1  Zk-1
227            DO ji = fs_2, fs_jpim1
228               pta(ji,jj,1,jn) = e3t_b(ji,jj,1) * ptb(ji,jj,1,jn) + p2dt * e3t_n(ji,jj,1) * pta(ji,jj,1,jn)
229            END DO
230         END DO
231         DO jk = 2, jpkm1
232            DO jj = 2, jpjm1
233               DO ji = fs_2, fs_jpim1
234                  zrhs = e3t_b(ji,jj,jk) * ptb(ji,jj,jk,jn) + p2dt * e3t_n(ji,jj,jk) * pta(ji,jj,jk,jn)   ! zrhs=right hand side
235                  pta(ji,jj,jk,jn) = zrhs - zwi(ji,jj,jk) / zwt(ji,jj,jk-1) * pta(ji,jj,jk-1,jn)
236               END DO
237            END DO
238         END DO
239         !
240         DO jj = 2, jpjm1           !* 3d recurrence:    Xk = (Zk - Sk Xk+1 ) / Tk   (result is the after tracer)
241            DO ji = fs_2, fs_jpim1
242               pta(ji,jj,jpkm1,jn) = pta(ji,jj,jpkm1,jn) / zwt(ji,jj,jpkm1) * tmask(ji,jj,jpkm1)
243            END DO
244         END DO
245         DO jk = jpk-2, 1, -1
246            DO jj = 2, jpjm1
247               DO ji = fs_2, fs_jpim1
248                  pta(ji,jj,jk,jn) = ( pta(ji,jj,jk,jn) - zws(ji,jj,jk) * pta(ji,jj,jk+1,jn) )   &
249                     &             / zwt(ji,jj,jk) * tmask(ji,jj,jk)
250               END DO
251            END DO
252         END DO
253         !                                            ! ================= !
254      END DO                                          !  end tracer loop  !
255      !                                               ! ================= !
256      !
257      IF( ln_timing )   CALL timing_stop('tra_zdf_imp')
258      !
259   END SUBROUTINE tra_zdf_imp
260
261   !!==============================================================================
262END MODULE trazdf
Note: See TracBrowser for help on using the repository browser.