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 NEMO/branches/2019/fix_sn_cfctl_ticket2328/src/OCE/TRA – NEMO

source: NEMO/branches/2019/fix_sn_cfctl_ticket2328/src/OCE/TRA/trazdf.F90 @ 11869

Last change on this file since 11869 was 11869, checked in by acc, 4 years ago

Branch 2019/fix_sn_cfctl_ticket2328. Changes to enable correct functionality for the sn_cfctl%l_mppout and sn_cfctl%l_mpptop options. These changes also introduce a sn_cfctl%l_oasout option to toggle the OASIS setup information (sbccpl.F90, only) which was yet another misuse of ln_ctl. The next step may be to remove most references to ln_ctl altogether and provide a single control mechanism. TBD. See ticket #2328

  • Property svn:keywords set to Id
File size: 13.8 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/OCE 4.0 , NEMO Consortium (2018)
41   !! $Id$
42   !! Software governed by the CeCILL license (see ./LICENSE)
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( kt == nit000 )  THEN
61         IF(lwp)WRITE(numout,*)
62         IF(lwp)WRITE(numout,*) 'tra_zdf : implicit vertical mixing on T & S'
63         IF(lwp)WRITE(numout,*) '~~~~~~~ '
64      ENDIF
65      !
66      IF( neuler == 0 .AND. kt == nit000 ) THEN   ;   r2dt =      rdt   ! at nit000, =   rdt (restarting with Euler time stepping)
67      ELSEIF( kt <= nit000 + 1           ) THEN   ;   r2dt = 2. * rdt   ! otherwise, = 2 rdt (leapfrog)
68      ENDIF
69      !
70      IF( l_trdtra )   THEN                  !* Save ta and sa trends
71         ALLOCATE( ztrdt(jpi,jpj,jpk) , ztrds(jpi,jpj,jpk) )
72         ztrdt(:,:,:) = tsa(:,:,:,jp_tem)
73         ztrds(:,:,:) = tsa(:,:,:,jp_sal)
74      ENDIF
75      !
76      !                                      !* compute lateral mixing trend and add it to the general trend
77      CALL tra_zdf_imp( kt, nit000, 'TRA', r2dt, tsb, tsa, jpts ) 
78
79!!gm WHY here !   and I don't like that !
80      ! DRAKKAR SSS control {
81      ! JMM avoid negative salinities near river outlet ! Ugly fix
82      ! JMM : restore negative salinities to small salinities:
83      WHERE( tsa(:,:,:,jp_sal) < 0._wp )   tsa(:,:,:,jp_sal) = 0.1_wp
84!!gm
85
86      IF( l_trdtra )   THEN                      ! save the vertical diffusive trends for further diagnostics
87         DO jk = 1, jpkm1
88            ztrdt(:,:,jk) = ( ( tsa(:,:,jk,jp_tem)*e3t_a(:,:,jk) - tsb(:,:,jk,jp_tem)*e3t_b(:,:,jk) ) &
89               &          / (e3t_n(:,:,jk)*r2dt) ) - ztrdt(:,:,jk)
90            ztrds(:,:,jk) = ( ( tsa(:,:,jk,jp_sal)*e3t_a(:,:,jk) - tsb(:,:,jk,jp_sal)*e3t_b(:,:,jk) ) &
91              &           / (e3t_n(:,:,jk)*r2dt) ) - ztrds(:,:,jk)
92         END DO
93!!gm this should be moved in trdtra.F90 and done on all trends
94         CALL lbc_lnk_multi( 'trazdf', ztrdt, 'T', 1. , ztrds, 'T', 1. )
95!!gm
96         CALL trd_tra( kt, 'TRA', jp_tem, jptra_zdf, ztrdt )
97         CALL trd_tra( kt, 'TRA', jp_sal, jptra_zdf, ztrds )
98         DEALLOCATE( ztrdt , ztrds )
99      ENDIF
100      !                                          ! print mean trends (used for debugging)
101      IF(ln_ctl .OR. sn_cfctl%l_mppout)   CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' zdf  - Ta: ', mask1=tmask,               &
102         &                                              tab3d_2=tsa(:,:,:,jp_sal), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' )
103      !
104      IF( ln_timing )   CALL timing_stop('tra_zdf')
105      !
106   END SUBROUTINE tra_zdf
107
108 
109   SUBROUTINE tra_zdf_imp( kt, kit000, cdtype, p2dt, ptb, pta, kjpt ) 
110      !!----------------------------------------------------------------------
111      !!                  ***  ROUTINE tra_zdf_imp  ***
112      !!
113      !! ** Purpose :   Compute the after tracer through a implicit computation
114      !!     of the vertical tracer diffusion (including the vertical component
115      !!     of lateral mixing (only for 2nd order operator, for fourth order
116      !!     it is already computed and add to the general trend in traldf)
117      !!
118      !! ** Method  :  The vertical diffusion of a tracer ,t , is given by:
119      !!          difft = dz( avt dz(t) ) = 1/e3t dk+1( avt/e3w dk(t) )
120      !!      It is computed using a backward time scheme (t=after field)
121      !!      which provide directly the after tracer field.
122      !!      If ln_zdfddm=T, use avs for salinity or for passive tracers
123      !!      Surface and bottom boundary conditions: no diffusive flux on
124      !!      both tracers (bottom, applied through the masked field avt).
125      !!      If iso-neutral mixing, add to avt the contribution due to lateral mixing.
126      !!
127      !! ** Action  : - pta  becomes the after tracer
128      !!---------------------------------------------------------------------
129      INTEGER                              , INTENT(in   ) ::   kt       ! ocean time-step index
130      INTEGER                              , INTENT(in   ) ::   kit000   ! first time step index
131      CHARACTER(len=3)                     , INTENT(in   ) ::   cdtype   ! =TRA or TRC (tracer indicator)
132      INTEGER                              , INTENT(in   ) ::   kjpt     ! number of tracers
133      REAL(wp)                             , INTENT(in   ) ::   p2dt     ! tracer time-step
134      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(in   ) ::   ptb      ! before and now tracer fields
135      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(inout) ::   pta      ! in: tracer trend ; out: after tracer field
136      !
137      INTEGER  ::  ji, jj, jk, jn   ! dummy loop indices
138      REAL(wp) ::  zrhs, zzwi, zzws ! local scalars
139      REAL(wp), DIMENSION(jpi,jpj,jpk) ::  zwi, zwt, zwd, zws
140      !!---------------------------------------------------------------------
141      !
142      !                                               ! ============= !
143      DO jn = 1, kjpt                                 !  tracer loop  !
144         !                                            ! ============= !
145         !  Matrix construction
146         ! --------------------
147         ! Build matrix if temperature or salinity (only in double diffusion case) or first passive tracer
148         !
149         IF(  ( cdtype == 'TRA' .AND. ( jn == jp_tem .OR. ( jn == jp_sal .AND. ln_zdfddm ) ) ) .OR.   &
150            & ( cdtype == 'TRC' .AND. jn == 1 )  )  THEN
151            !
152            ! vertical mixing coef.: avt for temperature, avs for salinity and passive tracers
153            IF( cdtype == 'TRA' .AND. jn == jp_tem ) THEN   ;   zwt(:,:,2:jpk) = avt(:,:,2:jpk)
154            ELSE                                            ;   zwt(:,:,2:jpk) = avs(:,:,2:jpk)
155            ENDIF
156            zwt(:,:,1) = 0._wp
157            !
158            IF( l_ldfslp ) THEN            ! isoneutral diffusion: add the contribution
159               IF( ln_traldf_msc  ) THEN     ! MSC iso-neutral operator
160                  DO jk = 2, jpkm1
161                     DO jj = 2, jpjm1
162                        DO ji = fs_2, fs_jpim1   ! vector opt.
163                           zwt(ji,jj,jk) = zwt(ji,jj,jk) + akz(ji,jj,jk) 
164                        END DO
165                     END DO
166                  END DO
167               ELSE                          ! standard or triad iso-neutral operator
168                  DO jk = 2, jpkm1
169                     DO jj = 2, jpjm1
170                        DO ji = fs_2, fs_jpim1   ! vector opt.
171                           zwt(ji,jj,jk) = zwt(ji,jj,jk) + ah_wslp2(ji,jj,jk)
172                        END DO
173                     END DO
174                  END DO
175               ENDIF
176            ENDIF
177            !
178            ! Diagonal, lower (i), upper (s)  (including the bottom boundary condition since avt is masked)
179            IF( ln_zad_Aimp ) THEN         ! Adaptive implicit vertical advection
180               DO jk = 1, jpkm1
181                  DO jj = 2, jpjm1
182                     DO ji = fs_2, fs_jpim1   ! vector opt. (ensure same order of calculation as below if wi=0.)
183                        zzwi = - p2dt * zwt(ji,jj,jk  ) / e3w_n(ji,jj,jk  )
184                        zzws = - p2dt * zwt(ji,jj,jk+1) / e3w_n(ji,jj,jk+1)
185                        zwd(ji,jj,jk) = e3t_a(ji,jj,jk) - zzwi - zzws   &
186                           &                 + p2dt * ( MAX( wi(ji,jj,jk  ) , 0._wp ) - MIN( wi(ji,jj,jk+1) , 0._wp ) )
187                        zwi(ji,jj,jk) = zzwi + p2dt *   MIN( wi(ji,jj,jk  ) , 0._wp )
188                        zws(ji,jj,jk) = zzws - p2dt *   MAX( wi(ji,jj,jk+1) , 0._wp )
189                    END DO
190                  END DO
191               END DO
192            ELSE
193               DO jk = 1, jpkm1
194                  DO jj = 2, jpjm1
195                     DO ji = fs_2, fs_jpim1   ! vector opt.
196                        zwi(ji,jj,jk) = - p2dt * zwt(ji,jj,jk  ) / e3w_n(ji,jj,jk)
197                        zws(ji,jj,jk) = - p2dt * zwt(ji,jj,jk+1) / e3w_n(ji,jj,jk+1)
198                        zwd(ji,jj,jk) = e3t_a(ji,jj,jk) - zwi(ji,jj,jk) - zws(ji,jj,jk)
199                    END DO
200                  END DO
201               END DO
202            ENDIF
203            !
204            !! Matrix inversion from the first level
205            !!----------------------------------------------------------------------
206            !   solve m.x = y  where m is a tri diagonal matrix ( jpk*jpk )
207            !
208            !        ( zwd1 zws1   0    0    0  )( zwx1 ) ( zwy1 )
209            !        ( zwi2 zwd2 zws2   0    0  )( zwx2 ) ( zwy2 )
210            !        (  0   zwi3 zwd3 zws3   0  )( zwx3 )=( zwy3 )
211            !        (        ...               )( ...  ) ( ...  )
212            !        (  0    0    0   zwik zwdk )( zwxk ) ( zwyk )
213            !
214            !   m is decomposed in the product of an upper and lower triangular matrix.
215            !   The 3 diagonal terms are in 3d arrays: zwd, zws, zwi.
216            !   Suffices i,s and d indicate "inferior" (below diagonal), diagonal
217            !   and "superior" (above diagonal) components of the tridiagonal system.
218            !   The solution will be in the 4d array pta.
219            !   The 3d array zwt is used as a work space array.
220            !   En route to the solution pta is used a to evaluate the rhs and then
221            !   used as a work space array: its value is modified.
222            !
223            DO jj = 2, jpjm1        !* 1st recurrence:   Tk = Dk - Ik Sk-1 / Tk-1   (increasing k)
224               DO ji = fs_2, fs_jpim1            ! done one for all passive tracers (so included in the IF instruction)
225                  zwt(ji,jj,1) = zwd(ji,jj,1)
226               END DO
227            END DO
228            DO jk = 2, jpkm1
229               DO jj = 2, jpjm1
230                  DO ji = fs_2, fs_jpim1
231                     zwt(ji,jj,jk) = zwd(ji,jj,jk) - zwi(ji,jj,jk) * zws(ji,jj,jk-1) / zwt(ji,jj,jk-1)
232                  END DO
233               END DO
234            END DO
235            !
236         ENDIF 
237         !         
238         DO jj = 2, jpjm1           !* 2nd recurrence:    Zk = Yk - Ik / Tk-1  Zk-1
239            DO ji = fs_2, fs_jpim1
240               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)
241            END DO
242         END DO
243         DO jk = 2, jpkm1
244            DO jj = 2, jpjm1
245               DO ji = fs_2, fs_jpim1
246                  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
247                  pta(ji,jj,jk,jn) = zrhs - zwi(ji,jj,jk) / zwt(ji,jj,jk-1) * pta(ji,jj,jk-1,jn)
248               END DO
249            END DO
250         END DO
251         !
252         DO jj = 2, jpjm1           !* 3d recurrence:    Xk = (Zk - Sk Xk+1 ) / Tk   (result is the after tracer)
253            DO ji = fs_2, fs_jpim1
254               pta(ji,jj,jpkm1,jn) = pta(ji,jj,jpkm1,jn) / zwt(ji,jj,jpkm1) * tmask(ji,jj,jpkm1)
255            END DO
256         END DO
257         DO jk = jpk-2, 1, -1
258            DO jj = 2, jpjm1
259               DO ji = fs_2, fs_jpim1
260                  pta(ji,jj,jk,jn) = ( pta(ji,jj,jk,jn) - zws(ji,jj,jk) * pta(ji,jj,jk+1,jn) )   &
261                     &             / zwt(ji,jj,jk) * tmask(ji,jj,jk)
262               END DO
263            END DO
264         END DO
265         !                                            ! ================= !
266      END DO                                          !  end tracer loop  !
267      !                                               ! ================= !
268   END SUBROUTINE tra_zdf_imp
269
270   !!==============================================================================
271END MODULE trazdf
Note: See TracBrowser for help on using the repository browser.