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

source: branches/2017/dev_r7881_no_wrk_alloc/NEMOGCM/NEMO/OPA_SRC/TRA/trazdf_imp.F90 @ 7910

Last change on this file since 7910 was 7910, checked in by timgraham, 7 years ago

All wrk_alloc removed

  • Property svn:keywords set to Id
File size: 11.0 KB
Line 
1MODULE trazdf_imp
2   !!======================================================================
3   !!                 ***  MODULE  trazdf_imp  ***
4   !! Ocean  tracers:  vertical component of the tracer mixing trend
5   !!======================================================================
6   !! History :  OPA  !  1990-10  (B. Blanke)  Original code
7   !!            7.0  !  1991-11  (G. Madec)
8   !!                 !  1992-06  (M. Imbard) correction on tracer trend loops
9   !!                 !  1996-01  (G. Madec) statement function for e3
10   !!                 !  1997-05  (G. Madec) vertical component of isopycnal
11   !!                 !  1997-07  (G. Madec) geopotential diffusion in s-coord
12   !!                 !  2000-08  (G. Madec) double diffusive mixing
13   !!   NEMO     1.0  !  2002-08  (G. Madec) F90: Free form and module
14   !!            2.0  !  2006-11  (G. Madec) New step reorganisation
15   !!            3.2  !  2009-03  (G. Madec)  heat and salt content trends
16   !!            3.3  !  2010-06  (C. Ethe, G. Madec) Merge TRA-TRC
17   !!             -   !  2011-02  (A. Coward, C. Ethe, G. Madec) improvment of surface boundary condition
18   !!            3.7  !  2015-11  (G. Madec, A. Coward)  non linear free surface by default
19   !!----------------------------------------------------------------------
20 
21   !!----------------------------------------------------------------------
22   !!   tra_zdf_imp   : Update the tracer trend with vertical mixing, nad compute the after tracer field
23   !!----------------------------------------------------------------------
24   USE oce            ! ocean dynamics and tracers variables
25   USE dom_oce        ! ocean space and time domain variables
26   USE zdf_oce        ! ocean vertical physics variables
27   USE trc_oce        ! share passive tracers/ocean variables
28   USE domvvl         ! variable volume
29   USE ldftra         ! lateral mixing type
30   USE ldfslp         ! lateral physics: slope of diffusion
31   USE zdfddm         ! ocean vertical physics: double diffusion
32   USE traldf_triad   ! active tracers: Method of Stabilizing Correction
33   !
34   USE in_out_manager ! I/O manager
35   USE lbclnk         ! ocean lateral boundary conditions (or mpp link)
36   USE lib_mpp        ! MPP library
37   USE timing         ! Timing
38
39   IMPLICIT NONE
40   PRIVATE
41
42   PUBLIC   tra_zdf_imp   !  routine called by step.F90
43
44   !! * Substitutions
45#  include "zdfddm_substitute.h90"
46#  include "vectopt_loop_substitute.h90"
47   !!----------------------------------------------------------------------
48   !! NEMO/OPA 3.7 , NEMO Consortium (2015)
49   !! $Id$
50   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
51   !!----------------------------------------------------------------------
52CONTAINS
53 
54   SUBROUTINE tra_zdf_imp( kt, kit000, cdtype, p2dt, ptb, pta, kjpt ) 
55      !!----------------------------------------------------------------------
56      !!                  ***  ROUTINE tra_zdf_imp  ***
57      !!
58      !! ** Purpose :   Compute the after tracer through a implicit computation
59      !!     of the vertical tracer diffusion (including the vertical component
60      !!     of lateral mixing (only for 2nd order operator, for fourth order
61      !!     it is already computed and add to the general trend in traldf)
62      !!
63      !! ** Method  :  The vertical diffusion of a tracer ,t , is given by:
64      !!          difft = dz( avt dz(t) ) = 1/e3t dk+1( avt/e3w dk(t) )
65      !!      It is computed using a backward time scheme (t=after field)
66      !!      which provide directly the after tracer field.
67      !!      If lk_zdfddm=T, use avs for salinity or for passive tracers
68      !!      Surface and bottom boundary conditions: no diffusive flux on
69      !!      both tracers (bottom, applied through the masked field avt).
70      !!      If iso-neutral mixing, add to avt the contribution due to lateral mixing.
71      !!
72      !! ** Action  : - pta  becomes the after tracer
73      !!---------------------------------------------------------------------
74      INTEGER                              , INTENT(in   ) ::   kt       ! ocean time-step index
75      INTEGER                              , INTENT(in   ) ::   kit000   ! first time step index
76      CHARACTER(len=3)                     , INTENT(in   ) ::   cdtype   ! =TRA or TRC (tracer indicator)
77      INTEGER                              , INTENT(in   ) ::   kjpt     ! number of tracers
78      REAL(wp)                             , INTENT(in   ) ::   p2dt     ! tracer time-step
79      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(in   ) ::   ptb      ! before and now tracer fields
80      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(inout) ::   pta      ! in: tracer trend ; out: after tracer field
81      !
82      INTEGER  ::  ji, jj, jk, jn   ! dummy loop indices
83      REAL(wp) ::  zrhs             ! local scalars
84      REAL(wp), DIMENSION(jpi,jpj,jpk) ::  zwi, zwt, zwd, zws
85      !!---------------------------------------------------------------------
86      !
87      IF( nn_timing == 1 )  CALL timing_start('tra_zdf_imp')
88      !
89      !
90      IF( kt == kit000 )  THEN
91         IF(lwp)WRITE(numout,*)
92         IF(lwp)WRITE(numout,*) 'tra_zdf_imp : implicit vertical mixing on ', cdtype
93         IF(lwp)WRITE(numout,*) '~~~~~~~~~~~ '
94      ENDIF
95      !                                               ! ============= !
96      DO jn = 1, kjpt                                 !  tracer loop  !
97         !                                            ! ============= !
98         !  Matrix construction
99         ! --------------------
100         ! Build matrix if temperature or salinity (only in double diffusion case) or first passive tracer
101         !
102         IF(  ( cdtype == 'TRA' .AND. ( jn == jp_tem .OR. ( jn == jp_sal .AND. lk_zdfddm ) ) ) .OR.   &
103            & ( cdtype == 'TRC' .AND. jn == 1 )  )  THEN
104            !
105            ! vertical mixing coef.: avt for temperature, avs for salinity and passive tracers
106            IF( cdtype == 'TRA' .AND. jn == jp_tem ) THEN   ;   zwt(:,:,2:jpk) = avt  (:,:,2:jpk)
107            ELSE                                            ;   zwt(:,:,2:jpk) = fsavs(:,:,2:jpk)
108            ENDIF
109            zwt(:,:,1) = 0._wp
110            !
111            IF( l_ldfslp ) THEN            ! isoneutral diffusion: add the contribution
112               IF( ln_traldf_msc  ) THEN     ! MSC iso-neutral operator
113                  DO jk = 2, jpkm1
114                     DO jj = 2, jpjm1
115                        DO ji = fs_2, fs_jpim1   ! vector opt.
116                           zwt(ji,jj,jk) = zwt(ji,jj,jk) + akz(ji,jj,jk) 
117                        END DO
118                     END DO
119                  END DO
120               ELSE                          ! standard or triad iso-neutral operator
121                  DO jk = 2, jpkm1
122                     DO jj = 2, jpjm1
123                        DO ji = fs_2, fs_jpim1   ! vector opt.
124                           zwt(ji,jj,jk) = zwt(ji,jj,jk) + ah_wslp2(ji,jj,jk)
125                        END DO
126                     END DO
127                  END DO
128               ENDIF
129            ENDIF
130            !
131            ! Diagonal, lower (i), upper (s)  (including the bottom boundary condition since avt is masked)
132            DO jk = 1, jpkm1
133               DO jj = 2, jpjm1
134                  DO ji = fs_2, fs_jpim1   ! vector opt.
135!!gm BUG  I think, use e3w_a instead of e3w_n
136                     zwi(ji,jj,jk) = - p2dt * zwt(ji,jj,jk  ) / e3w_n(ji,jj,jk  )
137                     zws(ji,jj,jk) = - p2dt * zwt(ji,jj,jk+1) / e3w_n(ji,jj,jk+1)
138                     zwd(ji,jj,jk) = e3t_a(ji,jj,jk) - zwi(ji,jj,jk) - zws(ji,jj,jk)
139                 END DO
140               END DO
141            END DO
142            !
143            !! Matrix inversion from the first level
144            !!----------------------------------------------------------------------
145            !   solve m.x = y  where m is a tri diagonal matrix ( jpk*jpk )
146            !
147            !        ( zwd1 zws1   0    0    0  )( zwx1 ) ( zwy1 )
148            !        ( zwi2 zwd2 zws2   0    0  )( zwx2 ) ( zwy2 )
149            !        (  0   zwi3 zwd3 zws3   0  )( zwx3 )=( zwy3 )
150            !        (        ...               )( ...  ) ( ...  )
151            !        (  0    0    0   zwik zwdk )( zwxk ) ( zwyk )
152            !
153            !   m is decomposed in the product of an upper and lower triangular matrix.
154            !   The 3 diagonal terms are in 3d arrays: zwd, zws, zwi.
155            !   Suffices i,s and d indicate "inferior" (below diagonal), diagonal
156            !   and "superior" (above diagonal) components of the tridiagonal system.
157            !   The solution will be in the 4d array pta.
158            !   The 3d array zwt is used as a work space array.
159            !   En route to the solution pta is used a to evaluate the rhs and then
160            !   used as a work space array: its value is modified.
161            !
162            DO jj = 2, jpjm1        !* 1st recurrence:   Tk = Dk - Ik Sk-1 / Tk-1   (increasing k)
163               DO ji = fs_2, fs_jpim1            ! done one for all passive tracers (so included in the IF instruction)
164                  zwt(ji,jj,1) = zwd(ji,jj,1)
165               END DO
166            END DO
167            DO jk = 2, jpkm1
168               DO jj = 2, jpjm1
169                  DO ji = fs_2, fs_jpim1
170                     zwt(ji,jj,jk) = zwd(ji,jj,jk) - zwi(ji,jj,jk) * zws(ji,jj,jk-1) / zwt(ji,jj,jk-1)
171                  END DO
172               END DO
173            END DO
174            !
175         ENDIF 
176         !         
177         DO jj = 2, jpjm1           !* 2nd recurrence:    Zk = Yk - Ik / Tk-1  Zk-1
178            DO ji = fs_2, fs_jpim1
179               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)
180            END DO
181         END DO
182         DO jk = 2, jpkm1
183            DO jj = 2, jpjm1
184               DO ji = fs_2, fs_jpim1
185                  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
186                  pta(ji,jj,jk,jn) = zrhs - zwi(ji,jj,jk) / zwt(ji,jj,jk-1) * pta(ji,jj,jk-1,jn)
187               END DO
188            END DO
189         END DO
190         !
191         DO jj = 2, jpjm1           !* 3d recurrence:    Xk = (Zk - Sk Xk+1 ) / Tk   (result is the after tracer)
192            DO ji = fs_2, fs_jpim1
193               pta(ji,jj,jpkm1,jn) = pta(ji,jj,jpkm1,jn) / zwt(ji,jj,jpkm1) * tmask(ji,jj,jpkm1)
194            END DO
195         END DO
196         DO jk = jpk-2, 1, -1
197            DO jj = 2, jpjm1
198               DO ji = fs_2, fs_jpim1
199                  pta(ji,jj,jk,jn) = ( pta(ji,jj,jk,jn) - zws(ji,jj,jk) * pta(ji,jj,jk+1,jn) )   &
200                     &             / zwt(ji,jj,jk) * tmask(ji,jj,jk)
201               END DO
202            END DO
203         END DO
204         !                                            ! ================= !
205      END DO                                          !  end tracer loop  !
206      !                                               ! ================= !
207      !
208      !
209      IF( nn_timing == 1 )  CALL timing_stop('tra_zdf_imp')
210      !
211   END SUBROUTINE tra_zdf_imp
212
213   !!==============================================================================
214END MODULE trazdf_imp
Note: See TracBrowser for help on using the repository browser.