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/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/DYN – NEMO

source: branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/DYN/dynzdf.F90 @ 4400

Last change on this file since 4400 was 3211, checked in by spickles2, 12 years ago

Stephen Pickles, 11 Dec 2011

Commit to bring the rest of the DCSE NEMO development branch
in line with the latest development version. This includes
array index re-ordering of all OPA_SRC/.

  • Property svn:keywords set to Id
File size: 7.1 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
22   USE trdmod          ! ocean active dynamics and tracers trends
23   USE trdmod_oce      ! ocean variables trends
24   USE in_out_manager  ! I/O manager
[2715]25   USE lib_mpp         ! MPP library
[456]26   USE prtctl          ! Print control
27
28   IMPLICIT NONE
29   PRIVATE
30
[2528]31   PUBLIC   dyn_zdf       !  routine called by step.F90
32   PUBLIC   dyn_zdf_init  !  routine called by opa.F90
[456]33
[2528]34   INTEGER  ::   nzdf = 0   ! type vertical diffusion algorithm used, defined from ln_zdf... namlist logicals
35   REAL(wp) ::   r2dt       ! time-step, = 2 rdttra except at nit000 (=rdttra) if neuler=0
[456]36
[3211]37   !! * Control permutation of array indices
38#  include "oce_ftrans.h90"
39#  include "dom_oce_ftrans.h90"
40#  include "zdf_oce_ftrans.h90"
41#  include "ldfdyn_oce_ftrans.h90"
42
[456]43   !! * Substitutions
44#  include "domzgr_substitute.h90"
45#  include "zdfddm_substitute.h90"
46#  include "vectopt_loop_substitute.h90"
47   !!----------------------------------------------------------------------
[2528]48   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
[1152]49   !! $Id$
[2528]50   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
[456]51   !!----------------------------------------------------------------------
52
53CONTAINS
54   
55   SUBROUTINE dyn_zdf( kt )
56      !!----------------------------------------------------------------------
57      !!                  ***  ROUTINE dyn_zdf  ***
58      !!
59      !! ** Purpose :   compute the vertical ocean dynamics physics.
60      !!---------------------------------------------------------------------
[2715]61      USE wrk_nemo, ONLY:   wrk_in_use, wrk_not_released
62      USE wrk_nemo, ONLY:   ztrdu => wrk_3d_1 , ztrdv => wrk_3d_2    ! 3D workspace
[3211]63      !! DCSE_NEMO: need additional directives for renamed module variables
64!FTRANS ztrdu :I :I :z
65!FTRANS ztrdv :I :I :z
[2715]66      !!
[456]67      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index
68      !!---------------------------------------------------------------------
69
[2715]70      IF( wrk_in_use(3, 1,2) ) THEN
71         CALL ctl_stop('dyn_zdf: requested workspace arrays unavailable')   ;   RETURN
72      END IF
[456]73      !                                          ! set time step
[2528]74      IF( neuler == 0 .AND. kt == nit000     ) THEN   ;   r2dt =      rdt   ! = rdtra (restart with Euler time stepping)
75      ELSEIF(               kt <= nit000 + 1 ) THEN   ;   r2dt = 2. * rdt   ! = 2 rdttra (leapfrog)
[456]76      ENDIF
77
78      IF( l_trddyn )   THEN                      ! temporary save of ta and sa trends
79         ztrdu(:,:,:) = ua(:,:,:)
80         ztrdv(:,:,:) = va(:,:,:)
81      ENDIF
82
83      SELECT CASE ( nzdf )                       ! compute lateral mixing trend and add it to the general trend
[503]84      !
[2528]85      CASE ( 0 )   ;   CALL dyn_zdf_exp( kt, r2dt )      ! explicit scheme
86      CASE ( 1 )   ;   CALL dyn_zdf_imp( kt, r2dt )      ! implicit scheme
[503]87      !
[2715]88      CASE ( -1 )                                        ! esopa: test all possibility with control print
[2528]89                       CALL dyn_zdf_exp( kt, r2dt )
[684]90                       CALL prt_ctl( tab3d_1=ua, clinfo1=' zdf0 - Ua: ', mask1=umask,               &
[2715]91                          &          tab3d_2=va, clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' )
[2528]92                       CALL dyn_zdf_imp( kt, r2dt )
[684]93                       CALL prt_ctl( tab3d_1=ua, clinfo1=' zdf1 - Ua: ', mask1=umask,               &
[2715]94                          &          tab3d_2=va, clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' )
[456]95      END SELECT
96
[503]97      IF( l_trddyn )   THEN                      ! save the vertical diffusive trends for further diagnostics
[456]98         ztrdu(:,:,:) = ua(:,:,:) - ztrdu(:,:,:)
99         ztrdv(:,:,:) = va(:,:,:) - ztrdv(:,:,:)
[503]100         CALL trd_mod( ztrdu, ztrdv, jpdyn_trd_zdf, 'DYN', kt )
[456]101      ENDIF
102      !                                          ! print mean trends (used for debugging)
103      IF(ln_ctl)   CALL prt_ctl( tab3d_1=ua, clinfo1=' zdf  - Ua: ', mask1=umask,               &
104            &                    tab3d_2=va, clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' )
[503]105      !
[2715]106      IF( wrk_not_released(3, 1,2) )   CALL ctl_stop('dyn_zdf: failed to release workspace arrays')
107      !
[456]108   END SUBROUTINE dyn_zdf
109
110
[2528]111   SUBROUTINE dyn_zdf_init
[456]112      !!----------------------------------------------------------------------
[2528]113      !!                 ***  ROUTINE dyn_zdf_init  ***
[456]114      !!
[503]115      !! ** Purpose :   initializations of the vertical diffusion scheme
[456]116      !!
117      !! ** Method  :   implicit (euler backward) scheme (default)
118      !!                explicit (time-splitting) scheme if ln_zdfexp=T
119      !!----------------------------------------------------------------------
120      USE zdftke
[2528]121      USE zdfgls
[456]122      USE zdfkpp
[3211]123#  include "zdftke_ftrans.h90"
[456]124      !!----------------------------------------------------------------------
[2528]125      !
[456]126      ! Choice from ln_zdfexp read in namelist in zdfini
[503]127      IF( ln_zdfexp ) THEN   ;   nzdf = 0           ! use explicit scheme
128      ELSE                   ;   nzdf = 1           ! use implicit scheme
[456]129      ENDIF
[2528]130      !
[456]131      ! Force implicit schemes
[2528]132      IF( lk_zdftke .OR. lk_zdfgls .OR. lk_zdfkpp )   nzdf = 1   ! TKE, GLS or KPP physics
133      IF( ln_dynldf_iso                           )   nzdf = 1   ! iso-neutral lateral physics
134      IF( ln_dynldf_hor .AND. ln_sco              )   nzdf = 1   ! horizontal lateral physics in s-coordinate
135      !
[503]136      IF( lk_esopa )    nzdf = -1                   ! Esopa key: All schemes used
[2528]137      !
[503]138      IF(lwp) THEN                                  ! Print the choice
[456]139         WRITE(numout,*)
[2528]140         WRITE(numout,*) 'dyn_zdf_init : vertical dynamics physics scheme'
[456]141         WRITE(numout,*) '~~~~~~~~~~~'
142         IF( nzdf == -1 )   WRITE(numout,*) '              ESOPA test All scheme used'
143         IF( nzdf ==  0 )   WRITE(numout,*) '              Explicit time-splitting scheme'
144         IF( nzdf ==  1 )   WRITE(numout,*) '              Implicit (euler backward) scheme'
145      ENDIF
[503]146      !
[2528]147   END SUBROUTINE dyn_zdf_init
[456]148
149   !!==============================================================================
150END MODULE dynzdf
Note: See TracBrowser for help on using the repository browser.