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.
zdfevd.F90 in branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/ZDF – NEMO

source: branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfevd.F90 @ 4460

Last change on this file since 4460 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: 6.5 KB
RevLine 
[3]1MODULE zdfevd
2   !!======================================================================
3   !!                       ***  MODULE  zdfevd  ***
4   !! Ocean physics: parameterization of convection through an enhancement
5   !!                of vertical eddy mixing coefficient
6   !!======================================================================
[1438]7   !! History :  OPA  !  1997-06  (G. Madec, A. Lazar)  Original code
8   !!   NEMO     1.0  !  2002-06  (G. Madec)  F90: Free form and module
9   !!             -   !  2005-06  (C. Ethe) KPP parameterization
10   !!            3.2  !  2009-03  (M. Leclair, G. Madec, R. Benshila) test on both before & after
11   !!----------------------------------------------------------------------
[3]12
13   !!----------------------------------------------------------------------
[1438]14   !!   zdf_evd      : increase the momentum and tracer Kz at the location of
15   !!                  statically unstable portion of the water column (ln_zdfevd=T)
[3]16   !!----------------------------------------------------------------------
17   USE oce             ! ocean dynamics and tracers variables
18   USE dom_oce         ! ocean space and time domain variables
19   USE zdf_oce         ! ocean vertical physics variables
[255]20   USE zdfkpp          ! KPP vertical mixing
[3]21   USE in_out_manager  ! I/O manager
[1482]22   USE iom             ! for iom_put
[3]23   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
24
25   IMPLICIT NONE
26   PRIVATE
27
[1438]28   PUBLIC   zdf_evd    ! called by step.F90
[3]29
[3211]30   !! * Control permutation of array indices
31#  include "oce_ftrans.h90"
32#  include "dom_oce_ftrans.h90"
33#  include "zdf_oce_ftrans.h90"
34
[255]35   !! * Substitutions
36#  include "domzgr_substitute.h90"
[3]37   !!----------------------------------------------------------------------
[2715]38   !! NEMO/OPA 4.0 , NEMO Consortium (2011)
[1438]39   !! $Id$
[2715]40   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
[3]41   !!----------------------------------------------------------------------
42CONTAINS
43
44   SUBROUTINE zdf_evd( kt )
45      !!----------------------------------------------------------------------
46      !!                  ***  ROUTINE zdf_evd  ***
47      !!                   
48      !! ** Purpose :   Local increased the vertical eddy viscosity and diffu-
49      !!      sivity coefficients when a static instability is encountered.
50      !!
[1546]51      !! ** Method  :   avt, avm, and the 4 neighbouring avmu, avmv coefficients
[3]52      !!      are set to avevd (namelist parameter) if the water column is
53      !!      statically unstable (i.e. if rn2 < -1.e-12 )
54      !!
[1546]55      !! ** Action  :   avt, avm, avmu, avmv updted in static instability cases
56      !!
[1438]57      !! References :   Lazar, A., these de l'universite Paris VI, France, 1997
[3]58      !!----------------------------------------------------------------------
[2715]59      USE oce,   zavt_evd => ua , zavm_evd => va  ! (ua,va) used ua workspace
[3211]60
61      !! DCSE_NEMO: need additional directives for renamed module variables
62!FTRANS ua va :I :I :z
63
[2715]64      !
65      INTEGER, INTENT( in ) ::   kt   ! ocean time-step indexocean time step
66      !
67      INTEGER ::   ji, jj, jk   ! dummy loop indices
[3]68      !!----------------------------------------------------------------------
69
70      IF( kt == nit000 ) THEN
71         IF(lwp) WRITE(numout,*)
72         IF(lwp) WRITE(numout,*) 'zdf_evd : Enhanced Vertical Diffusion (evd)'
73         IF(lwp) WRITE(numout,*) '~~~~~~~ '
74         IF(lwp) WRITE(numout,*)
75      ENDIF
76
[1681]77      zavt_evd(:,:,:) = avt(:,:,:)           ! set avt prior to evd application
[255]78
[1537]79      SELECT CASE ( nn_evdm )
[2715]80      !
[3]81      CASE ( 1 )           ! enhance vertical eddy viscosity and diffusivity (if rn2<-1.e-12)
[2715]82         !
[1681]83         zavm_evd(:,:,:) = avm(:,:,:)           ! set avm prior to evd application
84         !
[3211]85#if defined key_z_first
86         DO jj = 2, jpj
87            DO ji = 2, jpi
88               DO jk = 1, jpkm1
89#else
[1546]90         DO jk = 1, jpkm1 
[1438]91#if defined key_vectopt_loop
92            DO jj = 1, 1                     ! big loop forced
93               DO ji = jpi+2, jpij   
94#else
[3]95            DO jj = 2, jpj             ! no vector opt.
96               DO ji = 2, jpi
[1438]97#endif
[3211]98#endif
99
[1438]100#if defined key_zdfkpp
[1546]101                  ! no evd mixing in the boundary layer with KPP
[2715]102                  IF(  MIN( rn2(ji,jj,jk), rn2b(ji,jj,jk) ) <= -1.e-12  .AND.  fsdepw(ji,jj,jk) > hkpp(ji,jj)  ) THEN
[1438]103#else
[2715]104                  IF(  MIN( rn2(ji,jj,jk), rn2b(ji,jj,jk) ) <= -1.e-12 ) THEN
[1438]105#endif
[1537]106                     avt (ji  ,jj  ,jk) = rn_avevd * tmask(ji  ,jj  ,jk)
107                     avm (ji  ,jj  ,jk) = rn_avevd * tmask(ji  ,jj  ,jk)
108                     avmu(ji  ,jj  ,jk) = rn_avevd * umask(ji  ,jj  ,jk)
109                     avmu(ji-1,jj  ,jk) = rn_avevd * umask(ji-1,jj  ,jk)
110                     avmv(ji  ,jj  ,jk) = rn_avevd * vmask(ji  ,jj  ,jk)
111                     avmv(ji  ,jj-1,jk) = rn_avevd * vmask(ji  ,jj-1,jk)
[3]112                  ENDIF
113               END DO
114            END DO
[1546]115         END DO
[2715]116         CALL lbc_lnk( avt , 'W', 1. )   ;   CALL lbc_lnk( avm , 'W', 1. )   ! Lateral boundary conditions
[1546]117         CALL lbc_lnk( avmu, 'U', 1. )   ;   CALL lbc_lnk( avmv, 'V', 1. )
118         !
[1681]119         zavm_evd(:,:,:) = avm(:,:,:) - zavm_evd(:,:,:)   ! change in avm due to evd
120         CALL iom_put( "avm_evd", zavm_evd )              ! output this change
121         !
[3]122      CASE DEFAULT         ! enhance vertical eddy diffusivity only (if rn2<-1.e-12)
[3211]123#if defined key_z_first
124         DO jj = 1, jpj
125            DO ji = 1, jpi
126               DO jk = 1, jpkm1
127#else
[1546]128         DO jk = 1, jpkm1
129!!!         WHERE( rn2(:,:,jk) <= -1.e-12 ) avt(:,:,jk) = tmask(:,:,jk) * avevd   ! agissant sur T SEUL!
[1438]130#if defined key_vectopt_loop
131            DO jj = 1, 1                     ! big loop forced
132               DO ji = 1, jpij   
133#else
[3]134            DO jj = 1, jpj             ! loop over the whole domain (no lbc_lnk call)
135               DO ji = 1, jpi
[1438]136#endif
[3211]137#endif
138
[1438]139#if defined key_zdfkpp
[1546]140                  ! no evd mixing in the boundary layer with KPP
[2715]141                  IF(  MIN( rn2(ji,jj,jk), rn2b(ji,jj,jk) ) <= -1.e-12  .AND.  fsdepw(ji,jj,jk) > hkpp(ji,jj)  )   &         
[1438]142#else
[2715]143                  IF(  MIN( rn2(ji,jj,jk), rn2b(ji,jj,jk) ) <= -1.e-12 )   &
[1438]144#endif
[1537]145                     avt(ji,jj,jk) = rn_avevd * tmask(ji,jj,jk)
[3]146               END DO
147            END DO
[1546]148         END DO
149         !
[3]150      END SELECT
151
[1681]152      zavt_evd(:,:,:) = avt(:,:,:) - zavt_evd(:,:,:)   ! change in avt due to evd
153      CALL iom_put( "avt_evd", zavt_evd )              ! output this change
[1546]154      !
[3]155   END SUBROUTINE zdf_evd
156
157   !!======================================================================
158END MODULE zdfevd
Note: See TracBrowser for help on using the repository browser.