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.
Changeset 3085 for branches/2011/dev_MERCATOR_INGV_2011_MERGE/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfric.F90 – NEMO

Ignore:
Timestamp:
2011-11-14T14:13:32+01:00 (12 years ago)
Author:
cbricaud
Message:

commit changes from dev_INGV_2011

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2011/dev_MERCATOR_INGV_2011_MERGE/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfric.F90

    r2715 r3085  
    77   !! History :  OPA  ! 1987-09  (P. Andrich)  Original code 
    88   !!            4.0  ! 1991-11  (G. Madec) 
    9    !!            7.0  ! 1996-01  (G. Madec)  complet rewriting of multitasking suppression of common work arrays 
    10    !!            8.0  ! 1997-06 (G. Madec)  complete rewriting of zdfmix 
     9   !!            7.0  ! 1996-01  (G. Madec)  complete rewriting of multitasking suppression of common work arrays 
     10   !!            8.0  ! 1997-06  (G. Madec)  complete rewriting of zdfmix 
    1111   !!   NEMO     1.0  ! 2002-06  (G. Madec)  F90: Free form and module 
    1212   !!            3.3  ! 2010-10  (C. Ethe, G. Madec) reorganisation of initialisation phase 
     13   !!            3.3.1! 2011-09  (P. Oddo) Mixed layer depth parameterization 
    1314   !!---------------------------------------------------------------------- 
    1415#if defined key_zdfric   ||   defined key_esopa 
     
    2021   !!   zdf_ric_init : initialization, namelist read, & parameters control 
    2122   !!---------------------------------------------------------------------- 
    22    USE oce             ! ocean dynamics and tracers variables 
    23    USE dom_oce         ! ocean space and time domain variables 
    24    USE zdf_oce         ! ocean vertical physics 
    25    USE in_out_manager  ! I/O manager 
    26    USE lbclnk          ! ocean lateral boundary condition (or mpp link) 
    27    USE lib_mpp         ! MPP library 
     23   USE oce                   ! ocean dynamics and tracers variables 
     24   USE dom_oce               ! ocean space and time domain variables 
     25   USE zdf_oce               ! ocean vertical physics 
     26   USE in_out_manager        ! I/O manager 
     27   USE lbclnk                ! ocean lateral boundary condition (or mpp link) 
     28   USE lib_mpp               ! MPP library 
     29   USE eosbn2, ONLY : nn_eos 
    2830 
    2931   IMPLICIT NONE 
     
    3941   REAL(wp) ::   rn_avmri = 100.e-4_wp   ! maximum value of the vertical eddy viscosity 
    4042   REAL(wp) ::   rn_alp   =   5._wp      ! coefficient of the parameterization 
     43   REAL(wp) ::   rn_ekmfc =   0.7_wp     ! Ekman Factor Coeff 
     44   REAL(wp) ::   rn_mldmin=   1.0_wp     ! minimum mixed layer (ML) depth     
     45   REAL(wp) ::   rn_mldmax=1000.0_wp     ! maximum mixed layer depth 
     46   REAL(wp) ::   rn_wtmix =  10.0_wp     ! Vertical eddy Diff. in the ML 
     47   REAL(wp) ::   rn_wvmix =  10.0_wp     ! Vertical eddy Visc. in the ML 
     48   LOGICAL  ::   ln_mldw  = .TRUE.       ! Use or not the MLD parameters 
    4149 
    4250   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   tmric   !: coef. for the horizontal mean at t-point 
     
    6775      !!                     
    6876      !! ** Purpose :   Compute the before eddy viscosity and diffusivity as 
    69       !!              a function of the local richardson number. 
     77      !!                a function of the local richardson number. 
    7078      !! 
    7179      !! ** Method  :   Local richardson number dependent formulation of the  
    72       !!              vertical eddy viscosity and diffusivity coefficients.  
     80      !!                vertical eddy viscosity and diffusivity coefficients.  
    7381      !!                The eddy coefficients are given by: 
    7482      !!                    avm = avm0 + avmb 
    7583      !!                    avt = avm0 / (1 + rn_alp*ri) 
    76       !!              with ri  = N^2 / dz(u)**2 
    77       !!                       = e3w**2 * rn2/[ mi( dk(ub) )+mj( dk(vb) ) ] 
    78       !!                   avm0= rn_avmri / (1 + rn_alp*ri)**nn_ric 
     84      !!                with ri  = N^2 / dz(u)**2 
     85      !!                         = e3w**2 * rn2/[ mi( dk(ub) )+mj( dk(vb) ) ] 
     86      !!                    avm0= rn_avmri / (1 + rn_alp*ri)**nn_ric 
    7987      !!      Where ri is the before local Richardson number, 
    8088      !!            rn_avmri is the maximum value reaches by avm and avt  
     
    8492      !!      avtb=1.e-7 m2/s, rn_alp=5. and nn_ric=2. 
    8593      !!      a numerical threshold is impose on the vertical shear (1.e-20) 
     94      !!      As second step compute Ekman depth from wind stress forcing 
     95      !!      and apply namelist provided vertical coeff within this depth. 
     96      !!      The Ekman depth is: 
     97      !!              Ustar = SQRT(Taum/rho0) 
     98      !!              ekd= rn_ekmfc * Ustar / f0 
     99      !!      Large et al. (1994, eq.29) suggest rn_ekmfc=0.7; however, the derivation 
     100      !!      of the above equation indicates the value is somewhat arbitrary; therefore 
     101      !!      we allow the freedom to increase or decrease this value, if the 
     102      !!      Ekman depth estimate appears too shallow or too deep, respectively. 
     103      !!      Ekd is then limited by rn_mldmin and rn_mldmax provided in the 
     104      !!      namelist 
    86105      !!        N.B. the mask are required for implicit scheme, and surface 
    87106      !!      and bottom value already set in zdfini.F90 
    88107      !! 
    89108      !! References : Pacanowski & Philander 1981, JPO, 1441-1451. 
     109      !!              PFJ Lermusiaux 2001. 
    90110      !!---------------------------------------------------------------------- 
    91111      USE wrk_nemo, ONLY:   wrk_in_use, wrk_not_released 
    92       USE wrk_nemo, ONLY:   zwx => wrk_2d_1     ! 2D workspace 
    93       !! 
    94       INTEGER, INTENT( in ) ::   kt         ! ocean time-step indexocean time step 
    95       !! 
    96       INTEGER  ::   ji, jj, jk               ! dummy loop indices 
    97       REAL(wp) ::   zcoef, zdku, zdkv, zri, z05alp     ! temporary scalars 
    98       !!---------------------------------------------------------------------- 
    99  
    100       IF( wrk_in_use(2, 1) ) THEN 
     112      USE wrk_nemo, ONLY:   zwx => wrk_2d_1         ! 2D workspace 
     113      USE wrk_nemo, ONLY:   ekm_dep => wrk_2d_2     ! 2D workspace 
     114      USE phycst,   ONLY:   rsmall,rau0 
     115      USE sbc_oce,  ONLY:   taum 
     116      !! 
     117      INTEGER, INTENT( in ) ::   kt                           ! ocean time-step 
     118      !! 
     119      INTEGER  ::   ji, jj, jk                                ! dummy loop indices 
     120      REAL(wp) ::   zcoef, zdku, zdkv, zri, z05alp, zflageos  ! temporary scalars 
     121      REAL(wp) ::   zrhos, zustar 
     122      !!---------------------------------------------------------------------- 
     123 
     124      IF( wrk_in_use(2, 1,2) ) THEN 
    101125         CALL ctl_stop('zdf_ric : requested workspace array unavailable')   ;   RETURN 
    102126      ENDIF 
     
    145169      !                                                ! =============== 
    146170      ! 
     171      IF( ln_mldw ) THEN 
     172 
     173      !  Compute Ekman depth from wind stress forcing. 
     174      ! ------------------------------------------------------- 
     175      zflageos = ( 0.5 + SIGN( 0.5, nn_eos - 1. ) ) * rau0 
     176      DO jj = 1, jpj 
     177         DO ji = 1, jpi 
     178            zrhos          = rhop(ji,jj,1) + zflageos * ( 1. - tmask(ji,jj,1) ) 
     179            zustar         = SQRT( taum(ji,jj) / ( zrhos +  rsmall ) ) 
     180            ekm_dep(ji,jj) = rn_ekmfc * zustar / ( ABS( ff(ji,jj) ) + rsmall ) 
     181            ekm_dep(ji,jj) = MAX(ekm_dep(ji,jj),rn_mldmin) ! Minimun allowed 
     182            ekm_dep(ji,jj) = MIN(ekm_dep(ji,jj),rn_mldmax) ! Maximum allowed 
     183         END DO 
     184      END DO 
     185 
     186      ! In the first model level vertical diff/visc coeff.s  
     187      ! are always equal to the namelist values rn_wtmix/rn_wvmix 
     188      ! ------------------------------------------------------- 
     189      DO jj = 1, jpj 
     190         DO ji = 1, jpi 
     191            avmv(ji,jj,1) = MAX( avmv(ji,jj,1), rn_wvmix ) 
     192            avmu(ji,jj,1) = MAX( avmu(ji,jj,1), rn_wvmix ) 
     193            avt( ji,jj,1) = MAX(  avt(ji,jj,1), rn_wtmix ) 
     194         END DO 
     195      END DO 
     196 
     197      !  Force the vertical mixing coef within the Ekman depth 
     198      ! ------------------------------------------------------- 
     199      DO jk = 2, jpkm1 
     200         DO jj = 1, jpj 
     201            DO ji = 1, jpi 
     202               IF( fsdept(ji,jj,jk) < ekm_dep(ji,jj) ) THEN 
     203                  avmv(ji,jj,jk) = MAX( avmv(ji,jj,jk), rn_wvmix ) 
     204                  avmu(ji,jj,jk) = MAX( avmu(ji,jj,jk), rn_wvmix ) 
     205                  avt( ji,jj,jk) = MAX(  avt(ji,jj,jk), rn_wtmix ) 
     206               ENDIF 
     207            END DO 
     208         END DO 
     209      END DO 
     210 
     211      DO jk = 1, jpkm1                 
     212         DO jj = 1, jpj 
     213            DO ji = 1, jpi 
     214               avmv(ji,jj,jk) = avmv(ji,jj,jk) * vmask(ji,jj,jk) 
     215               avmu(ji,jj,jk) = avmu(ji,jj,jk) * umask(ji,jj,jk) 
     216               avt( ji,jj,jk) = avt( ji,jj,jk) * tmask(ji,jj,jk) 
     217            END DO 
     218         END DO 
     219      END DO 
     220 
     221     ENDIF 
     222 
    147223      CALL lbc_lnk( avt , 'W', 1. )                         ! Boundary conditions   (unchanged sign) 
    148224      CALL lbc_lnk( avmu, 'U', 1. )   ;   CALL lbc_lnk( avmv, 'V', 1. ) 
    149225      ! 
    150       IF( wrk_not_released(2, 1) )   CALL ctl_stop('zdf_ric: failed to release workspace array') 
     226      IF( wrk_not_released(2, 1,2) )   CALL ctl_stop('zdf_ric: failed to release workspace array') 
    151227      ! 
    152228   END SUBROUTINE zdf_ric 
     
    168244      INTEGER :: ji, jj, jk   ! dummy loop indices 
    169245      !! 
    170       NAMELIST/namzdf_ric/ rn_avmri, rn_alp, nn_ric 
     246      NAMELIST/namzdf_ric/ rn_avmri, rn_alp   , nn_ric  , rn_ekmfc,  & 
     247         &                rn_mldmin, rn_mldmax, rn_wtmix, rn_wvmix, ln_mldw 
    171248      !!---------------------------------------------------------------------- 
    172249      ! 
     
    179256         WRITE(numout,*) '~~~~~~~' 
    180257         WRITE(numout,*) '   Namelist namzdf_ric : set Kz(Ri) parameters' 
    181          WRITE(numout,*) '      maximum vertical viscosity     rn_avmri = ', rn_avmri 
    182          WRITE(numout,*) '      coefficient                    rn_alp   = ', rn_alp 
    183          WRITE(numout,*) '      coefficient                    nn_ric   = ', nn_ric 
     258         WRITE(numout,*) '      maximum vertical viscosity     rn_avmri  = ', rn_avmri 
     259         WRITE(numout,*) '      coefficient                    rn_alp    = ', rn_alp 
     260         WRITE(numout,*) '      coefficient                    nn_ric    = ', nn_ric 
     261         WRITE(numout,*) '      Ekman Factor Coeff             rn_ekmfc  = ', rn_ekmfc 
     262         WRITE(numout,*) '      minimum mixed layer depth      rn_mldmin = ', rn_mldmin 
     263         WRITE(numout,*) '      maximum mixed layer depth      rn_mldmax = ', rn_mldmax 
     264         WRITE(numout,*) '      Vertical eddy Diff. in the ML  rn_wtmix  = ', rn_wtmix 
     265         WRITE(numout,*) '      Vertical eddy Visc. in the ML  rn_wvmix  = ', rn_wvmix 
     266         WRITE(numout,*) '      Use the MLD parameterization   ln_mldw   = ', ln_mldw 
    184267      ENDIF 
    185268      ! 
Note: See TracChangeset for help on using the changeset viewer.