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/UKMO/NEMO_4.0_mirror_text_diagnostics/src/OCE/TRA – NEMO

source: NEMO/branches/UKMO/NEMO_4.0_mirror_text_diagnostics/src/OCE/TRA/trazdf.F90 @ 14565

Last change on this file since 14565 was 10986, checked in by andmirek, 5 years ago

GMED 462 add flush

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