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

source: branches/2017/dev_r7881_HPC09_ZDF/NEMOGCM/NEMO/OPA_SRC/TRA/trazdf_exp.F90 @ 7931

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

#1880 (HPC-09): remove key_zdfddm + phasing with last changes of HPC08 branch

  • Property svn:keywords set to Id
File size: 7.6 KB
Line 
1MODULE trazdf_exp
2   !!==============================================================================
3   !!                    ***  MODULE  trazdf_exp  ***
4   !! Ocean  tracers:  vertical component of the tracer mixing trend using
5   !!                  a split-explicit time-stepping
6   !!==============================================================================
7   !! History :  OPA  !  1990-10  (B. Blanke)  Original code
8   !!            7.0  !  1991-11  (G. Madec)
9   !!                 !  1992-06  (M. Imbard)  correction on tracer trend loops
10   !!                 !  1996-01  (G. Madec)  statement function for e3
11   !!                 !  1997-05  (G. Madec)  vertical component of isopycnal
12   !!                 !  1997-07  (G. Madec)  geopotential diffusion in s-coord
13   !!                 !  2000-08  (G. Madec)  double diffusive mixing
14   !!   NEMO     1.0  !  2002-08  (G. Madec)  F90: Free form and module
15   !!             -   !  2004-08  (C. Talandier) New trends organisation
16   !!             -   !  2005-11  (G. Madec)  New organisation
17   !!            3.0  !  2008-04  (G. Madec)  leap-frog time stepping done in trazdf
18   !!            3.3  !  2010-06  (C. Ethe, G. Madec) Merge TRA-TRC
19   !!----------------------------------------------------------------------
20
21   !!----------------------------------------------------------------------
22   !!   tra_zdf_exp   : compute the tracer the vertical diffusion trend using a
23   !!                   split-explicit time stepping and provide the after tracer
24   !!----------------------------------------------------------------------
25   USE oce            ! ocean dynamics and active tracers
26   USE dom_oce        ! ocean space and time domain
27   USE domvvl         ! variable volume levels
28   USE zdf_oce        ! ocean vertical physics
29   USE zdfddm         ! ocean vertical physics: double diffusion
30   USE trc_oce        ! share passive tracers/Ocean variables
31   !
32   USE in_out_manager ! I/O manager
33   USE lib_mpp        ! MPP library
34   USE wrk_nemo       ! Memory Allocation
35   USE timing         ! Timing
36
37   IMPLICIT NONE
38   PRIVATE
39
40   PUBLIC   tra_zdf_exp   ! routine called by step.F90
41
42   !! * Substitutions
43#  include "vectopt_loop_substitute.h90"
44   !!----------------------------------------------------------------------
45   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
46   !! $Id$
47   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
48   !!----------------------------------------------------------------------
49CONTAINS
50
51   SUBROUTINE tra_zdf_exp( kt, kit000, cdtype, p2dt, ksts,   &
52      &                                        ptb , pta , kjpt )
53      !!----------------------------------------------------------------------
54      !!                  ***  ROUTINE tra_zdf_exp  ***
55      !!                   
56      !! ** Purpose :   Compute the after tracer fields due to the vertical
57      !!      tracer mixing alone, and then due to the whole tracer trend.
58      !!
59      !! ** Method  : - The after tracer fields due to the vertical diffusion
60      !!      of tracers alone is given by:
61      !!                ztb = ptb + p2dt difft
62      !!      where difft = dz( avt dz(ptb) ) = 1/e3t dk+1( avt/e3w dk(ptb) )
63      !!           (if ln_zdfddm=T use avs on salinity and passive tracers instead of avt)
64      !!      difft is evaluated with an Euler split-explit scheme using a
65      !!      no flux boundary condition at both surface and bottomi boundaries.
66      !!      (N.B. bottom condition is applied through the masked field avt).
67      !!              - the after tracer fields due to the whole trend is
68      !!      obtained in leap-frog environment applied on thickness weighted tracer by :
69      !!          pta = [ ptb*e3tb + e3tn*( ztb - ptb + p2dt pta ) ] / e3tn
70      !!
71      !! ** Action : - after tracer fields pta
72      !!---------------------------------------------------------------------
73      INTEGER                              , INTENT(in   ) ::   kt       ! ocean time-step index
74      INTEGER                              , INTENT(in   ) ::   kit000   ! first time step index
75      CHARACTER(len=3)                     , INTENT(in   ) ::   cdtype   ! =TRA or TRC (tracer indicator)
76      INTEGER                              , INTENT(in   ) ::   kjpt     ! number of tracers
77      INTEGER                              , INTENT(in   ) ::   ksts     ! number of sub-time step
78      REAL(wp)                             , INTENT(in   ) ::   p2dt     ! vertical profile of 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, jl   ! dummy loop indices
83      REAL(wp) ::  z1_ksts, ze3tr       ! local scalars
84      REAL(wp) ::  ztra, ze3tb    !   -      -
85      REAL(wp), POINTER, DIMENSION(:,:,:) ::  ztb, zwf
86      !!---------------------------------------------------------------------
87      !
88      IF( nn_timing == 1 )  CALL timing_start('tra_zdf_exp')
89      !
90      CALL wrk_alloc( jpi,jpj,jpk,   ztb, zwf ) 
91      !
92      IF( kt == kit000 )  THEN
93         IF(lwp) WRITE(numout,*)
94         IF(lwp) WRITE(numout,*) 'tra_zdf_exp : explicit vertical mixing on ', cdtype
95         IF(lwp) WRITE(numout,*) '~~~~~~~~~~~'
96      ENDIF
97
98      ! Initializations
99      ! ---------------
100      z1_ksts = 1._wp / REAL( ksts, wp )
101      zwf(:,:, 1 ) = 0._wp    ! no flux at the surface and at bottom level
102      zwf(:,:,jpk) = 0._wp
103      !
104      !
105      DO jn = 1, kjpt         !==  loop over tracers  ==!
106         !
107         ztb(:,:,:) = ptb(:,:,:,jn)    ! initial before value for tracer
108         !
109         DO jl = 1, ksts         !==  Split-explicit loop  ==!
110            !             
111            DO jk = 2, jpk             ! 1st vertical derivative (w-flux)
112               DO jj = 2, jpjm1 
113                  DO ji = fs_2, fs_jpim1   ! vector opt.
114                     IF( cdtype == 'TRA' .AND. jn == jp_tem ) THEN  ! temperature : use of avt
115                        zwf(ji,jj,jk) =   avt(ji,jj,jk) * ( ztb(ji,jj,jk-1) - ztb(ji,jj,jk) ) / e3w_b(ji,jj,jk)
116                     ELSE                                           ! salinity or pass. tracer : use of avs
117                        zwf(ji,jj,jk) = avs(ji,jj,jk) * ( ztb(ji,jj,jk-1) - ztb(ji,jj,jk) ) / e3w_b(ji,jj,jk)
118                     END IF
119                  END DO
120               END DO
121            END DO
122            !
123            DO jk = 1, jpkm1           ! 2nd vertical derivative   ==> tracer at kt+l*2*rdt/nn_zdfexp
124               DO jj = 2, jpjm1 
125                  DO ji = fs_2, fs_jpim1   ! vector opt.
126                     ztb(ji,jj,jk) = ztb(ji,jj,jk) + p2dt * ( zwf(ji,jj,jk) - zwf(ji,jj,jk+1) ) / e3t_n(ji,jj,jk)
127                  END DO
128               END DO
129            END DO
130            !
131         END DO                  ! end sub-time stepping
132
133         DO jk = 1, jpkm1        !==  After tracer due to all trends
134            DO jj = 2, jpjm1 
135               DO ji = fs_2, fs_jpim1   ! vector opt.
136                  ze3tb = e3t_b(ji,jj,jk) / e3t_n(ji,jj,jk)
137                  ztra  = ( ztb(ji,jj,jk) - ptb(ji,jj,jk,jn) ) + p2dt * pta(ji,jj,jk,jn)  ! total trend * 2dt
138                  pta(ji,jj,jk,jn) = ( ze3tb * ptb(ji,jj,jk,jn) + ztra ) * tmask(ji,jj,jk)    ! after tracer
139               END DO
140            END DO
141         END DO
142         !
143      END DO                     ! end of tracer loop
144      !
145      CALL wrk_dealloc( jpi,jpj,jpk,   ztb, zwf ) 
146      !
147      IF( nn_timing == 1 )  CALL timing_stop('tra_zdf_exp')
148      !
149   END SUBROUTINE tra_zdf_exp
150
151   !!==============================================================================
152END MODULE trazdf_exp
Note: See TracBrowser for help on using the repository browser.