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.
dynzdf.F90 in branches/UKMO/dev_r5518_GO6_package/NEMOGCM/NEMO/OPA_SRC/DYN – NEMO

source: branches/UKMO/dev_r5518_GO6_package/NEMOGCM/NEMO/OPA_SRC/DYN/dynzdf.F90 @ 11650

Last change on this file since 11650 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: 6.8 KB
RevLine 
[456]1MODULE dynzdf
2   !!==============================================================================
3   !!                 ***  MODULE  dynzdf  ***
4   !! Ocean dynamics :  vertical component of the momentum mixing trend
5   !!==============================================================================
[2528]6   !! History :  1.0  !  2005-11  (G. Madec)  Original code
7   !!            3.3  !  2010-10  (C. Ethe, G. Madec) reorganisation of initialisation phase
[456]8   !!----------------------------------------------------------------------
[503]9
10   !!----------------------------------------------------------------------
[456]11   !!   dyn_zdf      : Update the momentum trend with the vertical diffusion
[2528]12   !!   dyn_zdf_init : initializations of the vertical diffusion scheme
[456]13   !!----------------------------------------------------------------------
14   USE oce             ! ocean dynamics and tracers variables
15   USE dom_oce         ! ocean space and time domain variables
16   USE zdf_oce         ! ocean vertical physics variables
17
18   USE dynzdf_exp      ! vertical diffusion: explicit (dyn_zdf_exp     routine)
19   USE dynzdf_imp      ! vertical diffusion: implicit (dyn_zdf_imp     routine)
20
21   USE ldfdyn_oce      ! ocean dynamics: lateral physics
[4990]22   USE trd_oce         ! trends: ocean variables
23   USE trddyn          ! trend manager: dynamics
[456]24   USE in_out_manager  ! I/O manager
[2715]25   USE lib_mpp         ! MPP library
[456]26   USE prtctl          ! Print control
[3294]27   USE wrk_nemo        ! Memory Allocation
28   USE timing          ! Timing
[456]29
30   IMPLICIT NONE
31   PRIVATE
32
[2528]33   PUBLIC   dyn_zdf       !  routine called by step.F90
34   PUBLIC   dyn_zdf_init  !  routine called by opa.F90
[456]35
[2528]36   INTEGER  ::   nzdf = 0   ! type vertical diffusion algorithm used, defined from ln_zdf... namlist logicals
37   REAL(wp) ::   r2dt       ! time-step, = 2 rdttra except at nit000 (=rdttra) if neuler=0
[456]38
39   !! * Substitutions
40#  include "domzgr_substitute.h90"
41#  include "zdfddm_substitute.h90"
42#  include "vectopt_loop_substitute.h90"
43   !!----------------------------------------------------------------------
[2528]44   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
[1152]45   !! $Id$
[2528]46   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
[456]47   !!----------------------------------------------------------------------
48
49CONTAINS
50   
51   SUBROUTINE dyn_zdf( kt )
52      !!----------------------------------------------------------------------
53      !!                  ***  ROUTINE dyn_zdf  ***
54      !!
55      !! ** Purpose :   compute the vertical ocean dynamics physics.
56      !!---------------------------------------------------------------------
[2715]57      !!
[456]58      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index
[3294]59      !
60      REAL(wp), POINTER, DIMENSION(:,:,:) ::  ztrdu, ztrdv
[456]61      !!---------------------------------------------------------------------
[3294]62      !
63      IF( nn_timing == 1 )  CALL timing_start('dyn_zdf')
64      !
[456]65      !                                          ! set time step
[2528]66      IF( neuler == 0 .AND. kt == nit000     ) THEN   ;   r2dt =      rdt   ! = rdtra (restart with Euler time stepping)
67      ELSEIF(               kt <= nit000 + 1 ) THEN   ;   r2dt = 2. * rdt   ! = 2 rdttra (leapfrog)
[456]68      ENDIF
69
70      IF( l_trddyn )   THEN                      ! temporary save of ta and sa trends
[3294]71         CALL wrk_alloc( jpi, jpj, jpk, ztrdu, ztrdv ) 
[456]72         ztrdu(:,:,:) = ua(:,:,:)
73         ztrdv(:,:,:) = va(:,:,:)
74      ENDIF
75
76      SELECT CASE ( nzdf )                       ! compute lateral mixing trend and add it to the general trend
[503]77      !
[2528]78      CASE ( 0 )   ;   CALL dyn_zdf_exp( kt, r2dt )      ! explicit scheme
79      CASE ( 1 )   ;   CALL dyn_zdf_imp( kt, r2dt )      ! implicit scheme
[503]80      !
[2715]81      CASE ( -1 )                                        ! esopa: test all possibility with control print
[2528]82                       CALL dyn_zdf_exp( kt, r2dt )
[684]83                       CALL prt_ctl( tab3d_1=ua, clinfo1=' zdf0 - Ua: ', mask1=umask,               &
[2715]84                          &          tab3d_2=va, clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' )
[2528]85                       CALL dyn_zdf_imp( kt, r2dt )
[684]86                       CALL prt_ctl( tab3d_1=ua, clinfo1=' zdf1 - Ua: ', mask1=umask,               &
[2715]87                          &          tab3d_2=va, clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' )
[456]88      END SELECT
89
[503]90      IF( l_trddyn )   THEN                      ! save the vertical diffusive trends for further diagnostics
[456]91         ztrdu(:,:,:) = ua(:,:,:) - ztrdu(:,:,:)
92         ztrdv(:,:,:) = va(:,:,:) - ztrdv(:,:,:)
[4990]93         CALL trd_dyn( ztrdu, ztrdv, jpdyn_zdf, kt )
[3294]94         CALL wrk_dealloc( jpi, jpj, jpk, ztrdu, ztrdv ) 
[456]95      ENDIF
96      !                                          ! print mean trends (used for debugging)
97      IF(ln_ctl)   CALL prt_ctl( tab3d_1=ua, clinfo1=' zdf  - Ua: ', mask1=umask,               &
98            &                    tab3d_2=va, clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' )
[503]99      !
[3294]100      IF( nn_timing == 1 )  CALL timing_stop('dyn_zdf')
[2715]101      !
[456]102   END SUBROUTINE dyn_zdf
103
104
[2528]105   SUBROUTINE dyn_zdf_init
[456]106      !!----------------------------------------------------------------------
[2528]107      !!                 ***  ROUTINE dyn_zdf_init  ***
[456]108      !!
[503]109      !! ** Purpose :   initializations of the vertical diffusion scheme
[456]110      !!
111      !! ** Method  :   implicit (euler backward) scheme (default)
112      !!                explicit (time-splitting) scheme if ln_zdfexp=T
113      !!----------------------------------------------------------------------
114      USE zdftke
[2528]115      USE zdfgls
[456]116      USE zdfkpp
117      !!----------------------------------------------------------------------
[2528]118      !
[456]119      ! Choice from ln_zdfexp read in namelist in zdfini
[503]120      IF( ln_zdfexp ) THEN   ;   nzdf = 0           ! use explicit scheme
121      ELSE                   ;   nzdf = 1           ! use implicit scheme
[456]122      ENDIF
[2528]123      !
[456]124      ! Force implicit schemes
[2528]125      IF( lk_zdftke .OR. lk_zdfgls .OR. lk_zdfkpp )   nzdf = 1   ! TKE, GLS or KPP physics
126      IF( ln_dynldf_iso                           )   nzdf = 1   ! iso-neutral lateral physics
127      IF( ln_dynldf_hor .AND. ln_sco              )   nzdf = 1   ! horizontal lateral physics in s-coordinate
128      !
[503]129      IF( lk_esopa )    nzdf = -1                   ! Esopa key: All schemes used
[2528]130      !
[503]131      IF(lwp) THEN                                  ! Print the choice
[456]132         WRITE(numout,*)
[2528]133         WRITE(numout,*) 'dyn_zdf_init : vertical dynamics physics scheme'
[456]134         WRITE(numout,*) '~~~~~~~~~~~'
135         IF( nzdf == -1 )   WRITE(numout,*) '              ESOPA test All scheme used'
136         IF( nzdf ==  0 )   WRITE(numout,*) '              Explicit time-splitting scheme'
137         IF( nzdf ==  1 )   WRITE(numout,*) '              Implicit (euler backward) scheme'
[11101]138         IF(lflush) CALL flush(numout)
[456]139      ENDIF
[503]140      !
[2528]141   END SUBROUTINE dyn_zdf_init
[456]142
143   !!==============================================================================
144END MODULE dynzdf
Note: See TracBrowser for help on using the repository browser.