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/UKMO/dev_r5518_GO6_package/NEMOGCM/NEMO/OPA_SRC/TRA – NEMO

source: branches/UKMO/dev_r5518_GO6_package/NEMOGCM/NEMO/OPA_SRC/TRA/trazdf_exp.F90 @ 11643

Last change on this file since 11643 was 11101, checked in by frrh, 5 years ago

Merge changes from Met Office GMED ticket 450 to reduce unnecessary
text output from NEMO.
This output, which is typically not switchable, is rarely of interest
in normal (non-debugging) runs and simply redunantley consumes extra
file space.
Further, the presence of this text output has been shown to
significantly degrade performance of models which are run during
Met Office HPC RAID (disk) checks.
The new code introduces switches which are configurable via the
changes made in the associated Met Office MOCI ticket 399.

File size: 8.7 KB
RevLine 
[3]1MODULE trazdf_exp
2   !!==============================================================================
3   !!                    ***  MODULE  trazdf_exp  ***
[2528]4   !! Ocean  tracers:  vertical component of the tracer mixing trend using
5   !!                  a split-explicit time-stepping
[3]6   !!==============================================================================
[1110]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
[2528]18   !!            3.3  !  2010-06  (C. Ethe, G. Madec) Merge TRA-TRC
[3]19   !!----------------------------------------------------------------------
[1110]20
[3]21   !!----------------------------------------------------------------------
[1110]22   !!   tra_zdf_exp  : compute the tracer the vertical diffusion trend using a
23   !!                  split-explicit time stepping and provide the after tracer
24   !!----------------------------------------------------------------------
[3]25   USE oce             ! ocean dynamics and active tracers
26   USE dom_oce         ! ocean space and time domain
[2528]27   USE domvvl          ! variable volume levels
[3]28   USE zdf_oce         ! ocean vertical physics
29   USE zdfddm          ! ocean vertical physics: double diffusion
[2715]30   USE trc_oce         ! share passive tracers/Ocean variables
[3]31   USE in_out_manager  ! I/O manager
[2715]32   USE lib_mpp         ! MPP library
[3294]33   USE wrk_nemo        ! Memory Allocation
34   USE timing          ! Timing
[3]35
36   IMPLICIT NONE
37   PRIVATE
38
[1110]39   PUBLIC   tra_zdf_exp   ! routine called by step.F90
[3]40
41   !! * Substitutions
42#  include "domzgr_substitute.h90"
43#  include "zdfddm_substitute.h90"
[1110]44#  include "vectopt_loop_substitute.h90"
[3]45   !!----------------------------------------------------------------------
[2528]46   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
47   !! $Id$
[2715]48   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
[3]49   !!----------------------------------------------------------------------
50CONTAINS
51
[3294]52   SUBROUTINE tra_zdf_exp( kt, kit000, cdtype, p2dt, kn_zdfexp,   &
[2528]53      &                                ptb , pta      , kjpt )
[3]54      !!----------------------------------------------------------------------
55      !!                  ***  ROUTINE tra_zdf_exp  ***
56      !!                   
[1110]57      !! ** Purpose :   Compute the after tracer fields due to the vertical
58      !!      tracer mixing alone, and then due to the whole tracer trend.
[3]59      !!
[1110]60      !! ** Method  : - The after tracer fields due to the vertical diffusion
61      !!      of tracers alone is given by:
[2528]62      !!                zwx = ptb + p2dt difft
63      !!      where difft = dz( avt dz(ptb) ) = 1/e3t dk+1( avt/e3w dk(ptb) )
64      !!           (if lk_zdfddm=T use avs on salinity and passive tracers instead of avt)
[1110]65      !!      difft is evaluated with an Euler split-explit scheme using a
66      !!      no flux boundary condition at both surface and bottomi boundaries.
67      !!      (N.B. bottom condition is applied through the masked field avt).
68      !!              - the after tracer fields due to the whole trend is
69      !!      obtained in leap-frog environment by :
[2528]70      !!          pta = zwx + p2dt pta
[1110]71      !!              - in case of variable level thickness (lk_vvl=T) the
72      !!     the leap-frog is applied on thickness weighted tracer. That is:
[2528]73      !!          pta = [ ptb*e3tb + e3tn*( zwx - ptb + p2dt pta ) ] / e3tn
[3]74      !!
[2528]75      !! ** Action : - after tracer fields pta
[1110]76      !!---------------------------------------------------------------------
[2715]77      !
[2528]78      INTEGER                              , INTENT(in   ) ::   kt          ! ocean time-step index
[3294]79      INTEGER                              , INTENT(in   ) ::   kit000      ! first time step index
[2528]80      CHARACTER(len=3)                     , INTENT(in   ) ::   cdtype      ! =TRA or TRC (tracer indicator)
81      INTEGER                              , INTENT(in   ) ::   kjpt        ! number of tracers
82      INTEGER                              , INTENT(in   ) ::   kn_zdfexp   ! number of sub-time step
83      REAL(wp), DIMENSION(        jpk     ), INTENT(in   ) ::   p2dt        ! vertical profile of tracer time-step
84      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(in   ) ::   ptb         ! before and now tracer fields
85      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(inout) ::   pta         ! tracer trend
[2715]86      !
[2528]87      INTEGER  ::  ji, jj, jk, jn, jl        ! dummy loop indices
88      REAL(wp) ::  zlavmr, zave3r, ze3tr     ! local scalars
89      REAL(wp) ::  ztra, ze3tb               !   -      -
[3294]90      REAL(wp), POINTER, DIMENSION(:,:,:) ::  zwx, zwy
[3]91      !!---------------------------------------------------------------------
[3294]92      !
93      IF( nn_timing == 1 )  CALL timing_start('tra_zdf_exp')
94      !
95      CALL wrk_alloc( jpi, jpj, jpk, zwx, zwy ) 
96      !
[3]97
[3294]98      IF( kt == kit000 )  THEN
[457]99         IF(lwp) WRITE(numout,*)
[2528]100         IF(lwp) WRITE(numout,*) 'tra_zdf_exp : explicit vertical mixing on ', cdtype
[457]101         IF(lwp) WRITE(numout,*) '~~~~~~~~~~~'
[11101]102         IF(lwp .AND. lflush) CALL flush(numout)
[457]103      ENDIF
[3]104
[1110]105      ! Initializations
106      ! ---------------
[2528]107      zlavmr = 1. / float( kn_zdfexp )         ! Local constant
[1110]108      !
109      !
[2528]110      DO jn = 1, kjpt                          ! loop over tracers
111         !
112         zwy(:,:, 1 ) = 0.e0     ! surface boundary conditions: no flux
113         zwy(:,:,jpk) = 0.e0     ! bottom  boundary conditions: no flux
114         !
115         zwx(:,:,:)   = ptb(:,:,:,jn)  ! zwx array set to before tracer values
[457]116
[2528]117         ! Split-explicit loop  (after tracer due to the vertical diffusion alone)
118         ! -------------------
119         !
120         DO jl = 1, kn_zdfexp
121            !                     ! first vertical derivative
122            DO jk = 2, jpk
123               DO jj = 2, jpjm1 
124                  DO ji = fs_2, fs_jpim1   ! vector opt.
125                     zave3r = 1.e0 / fse3w_n(ji,jj,jk) 
126                     IF( cdtype == 'TRA' .AND. jn == jp_tem ) THEN  ! temperature : use of avt
127                        zwy(ji,jj,jk) =   avt(ji,jj,jk) * ( zwx(ji,jj,jk-1) - zwx(ji,jj,jk) ) * zave3r
128                     ELSE                                           ! salinity or pass. tracer : use of avs
129                        zwy(ji,jj,jk) = fsavs(ji,jj,jk) * ( zwx(ji,jj,jk-1) - zwx(ji,jj,jk) ) * zave3r
130                     END IF
131                  END DO
[1110]132               END DO
133            END DO
[2528]134            !
135            DO jk = 1, jpkm1      ! second vertical derivative   ==> tracer at kt+l*2*rdt/nn_zdfexp
136               DO jj = 2, jpjm1 
137                  DO ji = fs_2, fs_jpim1   ! vector opt.
138                     ze3tr = zlavmr / fse3t_n(ji,jj,jk)
139                     zwx(ji,jj,jk) = zwx(ji,jj,jk) + p2dt(jk) * ( zwy(ji,jj,jk) - zwy(ji,jj,jk+1) ) * ze3tr
140                  END DO
[1110]141               END DO
[3]142            END DO
[2528]143            !
[3]144         END DO
145
[2528]146         ! After tracer due to all trends
147         ! ------------------------------
148         IF( lk_vvl ) THEN          ! variable level thickness : leap-frog on tracer*e3t
149            DO jk = 1, jpkm1
150               DO jj = 2, jpjm1 
151                  DO ji = fs_2, fs_jpim1   ! vector opt.
152                     ze3tb = fse3t_b(ji,jj,jk) / fse3t(ji,jj,jk)                          ! before e3t
153                     ztra  = zwx(ji,jj,jk) - ptb(ji,jj,jk,jn) + p2dt(jk) * pta(ji,jj,jk,jn)       ! total trends * 2*rdt
154                     pta(ji,jj,jk,jn) = ( ze3tb * ptb(ji,jj,jk,jn) + ztra ) * tmask(ji,jj,jk)
155                  END DO
[3]156               END DO
[1110]157            END DO
[2528]158         ELSE                       ! fixed level thickness : leap-frog on tracers
159            DO jk = 1, jpkm1
160               DO jj = 2, jpjm1 
161                  DO ji = fs_2, fs_jpim1   ! vector opt.
162                     pta(ji,jj,jk,jn) = ( zwx(ji,jj,jk) + p2dt(jk) * pta(ji,jj,jk,jn) ) * tmask(ji,jj,jk)
163                  END DO
[3]164               END DO
165            END DO
[2528]166         ENDIF
167         !
168      END DO
[1110]169      !
[3294]170      CALL wrk_dealloc( jpi, jpj, jpk, zwx, zwy ) 
[2715]171      !
[3294]172      IF( nn_timing == 1 )  CALL timing_stop('tra_zdf_exp')
173      !
[3]174   END SUBROUTINE tra_zdf_exp
175
176   !!==============================================================================
177END MODULE trazdf_exp
Note: See TracBrowser for help on using the repository browser.