MODULE dynzdf !!============================================================================== !! *** MODULE dynzdf *** !! Ocean dynamics : vertical component of the momentum mixing trend !!============================================================================== !! History : 9.0 ! 05-11 (G. Madec) Original code !!---------------------------------------------------------------------- !!---------------------------------------------------------------------- !! dyn_zdf : Update the momentum trend with the vertical diffusion !! zdf_ctl : initializations of the vertical diffusion scheme !!---------------------------------------------------------------------- USE oce ! ocean dynamics and tracers variables USE dom_oce ! ocean space and time domain variables USE zdf_oce ! ocean vertical physics variables USE dynzdf_exp ! vertical diffusion: explicit (dyn_zdf_exp routine) USE dynzdf_imp ! vertical diffusion: implicit (dyn_zdf_imp routine) USE ldfdyn_oce ! ocean dynamics: lateral physics USE trdmod ! ocean active dynamics and tracers trends USE trdmod_oce ! ocean variables trends USE in_out_manager ! I/O manager USE prtctl ! Print control IMPLICIT NONE PRIVATE PUBLIC dyn_zdf ! routine called by step.F90 INTEGER :: nzdf = 0 ! type vertical diffusion algorithm used ! ! defined from ln_zdf... namlist logicals) REAL(wp) :: r2dt ! time-step, = 2 rdttra ! ! except at nit000 (=rdttra) if neuler=0 !! * Substitutions # include "domzgr_substitute.h90" # include "zdfddm_substitute.h90" # include "vectopt_loop_substitute.h90" !!---------------------------------------------------------------------- !! OPA 9.0 , LOCEAN-IPSL (2005) !! $Id: dynzdf.F90 1533 2009-07-24 09:54:48Z ctlod $ !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) !!---------------------------------------------------------------------- CONTAINS SUBROUTINE dyn_zdf( kt ) !!---------------------------------------------------------------------- !! *** ROUTINE dyn_zdf *** !! !! ** Purpose : compute the vertical ocean dynamics physics. !!--------------------------------------------------------------------- INTEGER, INTENT( in ) :: kt ! ocean time-step index !! REAL(wp), DIMENSION(jpi,jpj,jpk) :: ztrdu, ztrdv ! 3D workspace !!--------------------------------------------------------------------- IF( kt == nit000 ) CALL zdf_ctl ! initialisation & control of options ! ! set time step IF( neuler == 0 .AND. kt == nit000 ) THEN ; r2dt = rdt ! = rdtra (restarting with Euler time stepping) ELSEIF( kt <= nit000 + 1) THEN ; r2dt = 2. * rdt ! = 2 rdttra (leapfrog) ENDIF IF( l_trddyn ) THEN ! temporary save of ta and sa trends ztrdu(:,:,:) = ua(:,:,:) ztrdv(:,:,:) = va(:,:,:) ENDIF SELECT CASE ( nzdf ) ! compute lateral mixing trend and add it to the general trend ! CASE ( 0 ) ; CALL dyn_zdf_exp ( kt, r2dt ) ! explicit scheme CASE ( 1 ) ; CALL dyn_zdf_imp ( kt, r2dt ) ! implicit scheme ! CASE ( -1 ) ! esopa: test all possibility with control print CALL dyn_zdf_exp ( kt, r2dt ) CALL prt_ctl( tab3d_1=ua, clinfo1=' zdf0 - Ua: ', mask1=umask, & & tab3d_2=va, clinfo2= ' Va: ', mask2=vmask, clinfo3='dyn' ) CALL dyn_zdf_imp ( kt, r2dt ) CALL prt_ctl( tab3d_1=ua, clinfo1=' zdf1 - Ua: ', mask1=umask, & & tab3d_2=va, clinfo2= ' Va: ', mask2=vmask, clinfo3='dyn' ) END SELECT IF( l_trddyn ) THEN ! save the vertical diffusive trends for further diagnostics ztrdu(:,:,:) = ua(:,:,:) - ztrdu(:,:,:) ztrdv(:,:,:) = va(:,:,:) - ztrdv(:,:,:) CALL trd_mod( ztrdu, ztrdv, jpdyn_trd_zdf, 'DYN', kt ) ENDIF ! ! print mean trends (used for debugging) IF(ln_ctl) CALL prt_ctl( tab3d_1=ua, clinfo1=' zdf - Ua: ', mask1=umask, & & tab3d_2=va, clinfo2= ' Va: ', mask2=vmask, clinfo3='dyn' ) ! END SUBROUTINE dyn_zdf SUBROUTINE zdf_ctl !!---------------------------------------------------------------------- !! *** ROUTINE zdf_ctl *** !! !! ** Purpose : initializations of the vertical diffusion scheme !! !! ** Method : implicit (euler backward) scheme (default) !! explicit (time-splitting) scheme if ln_zdfexp=T !!---------------------------------------------------------------------- USE zdftke_old USE zdftke USE zdfkpp !!---------------------------------------------------------------------- ! Choice from ln_zdfexp read in namelist in zdfini IF( ln_zdfexp ) THEN ; nzdf = 0 ! use explicit scheme ELSE ; nzdf = 1 ! use implicit scheme ENDIF ! Force implicit schemes IF( lk_zdftke_old .OR. lk_zdftke .OR. lk_zdfkpp ) nzdf = 1 ! TKE or KPP physics IF( ln_dynldf_iso ) nzdf = 1 ! iso-neutral lateral physics IF( ln_dynldf_hor .AND. ln_sco ) nzdf = 1 ! horizontal lateral physics in s-coordinate IF( lk_esopa ) nzdf = -1 ! Esopa key: All schemes used IF(lwp) THEN ! Print the choice WRITE(numout,*) WRITE(numout,*) 'dyn:zdf_ctl : vertical dynamics physics scheme' WRITE(numout,*) '~~~~~~~~~~~' IF( nzdf == -1 ) WRITE(numout,*) ' ESOPA test All scheme used' IF( nzdf == 0 ) WRITE(numout,*) ' Explicit time-splitting scheme' IF( nzdf == 1 ) WRITE(numout,*) ' Implicit (euler backward) scheme' ENDIF ! END SUBROUTINE zdf_ctl !!============================================================================== END MODULE dynzdf