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 7351 for branches/2016/dev_INGV_UKMO_2016/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfmxl.F90 – NEMO

Ignore:
Timestamp:
2016-11-28T17:04:10+01:00 (7 years ago)
Author:
emanuelaclementi
Message:

ticket #1805 step 3: /2016/dev_INGV_UKMO_2016 aligned to the trunk at revision 7161

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2016/dev_INGV_UKMO_2016/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfmxl.F90

    r4990 r7351  
    3131   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hmld    !: mixing layer depth (turbocline)      [m] 
    3232   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hmlp    !: mixed layer depth  (rho=rho0+zdcrit) [m] 
    33    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hmlpt   !: mixed layer depth at t-points        [m] 
     33   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hmlpt   !: depth of the last T-point inside the mixed layer [m] 
    3434 
    3535   REAL(wp), PUBLIC ::   rho_c = 0.01_wp    !: density criterion for mixed layer depth 
    3636   REAL(wp)         ::   avt_c = 5.e-4_wp   ! Kz criterion for the turbocline depth 
    3737 
    38    !! * Substitutions 
    39 #  include "domzgr_substitute.h90" 
    4038   !!---------------------------------------------------------------------- 
    4139   !! NEMO/OPA 4.0 , NEMO Consortium (2011) 
     
    7977      INTEGER, INTENT(in) ::   kt   ! ocean time-step index 
    8078      ! 
    81       INTEGER  ::   ji, jj, jk   ! dummy loop indices 
    82       INTEGER  ::   iikn, iiki, ikt, imkt  ! local integer 
    83       REAL(wp) ::   zN2_c        ! local scalar 
     79      INTEGER  ::   ji, jj, jk      ! dummy loop indices 
     80      INTEGER  ::   iikn, iiki, ikt ! local integer 
     81      REAL(wp) ::   zN2_c           ! local scalar 
    8482      INTEGER, POINTER, DIMENSION(:,:) ::   imld   ! 2D workspace 
    8583      !!---------------------------------------------------------------------- 
     
    105103            DO ji = 1, jpi 
    106104               ikt = mbkt(ji,jj) 
    107                hmlp(ji,jj) = hmlp(ji,jj) + MAX( rn2b(ji,jj,jk) , 0._wp ) * fse3w(ji,jj,jk) 
     105               hmlp(ji,jj) = hmlp(ji,jj) + MAX( rn2b(ji,jj,jk) , 0._wp ) * e3w_n(ji,jj,jk) 
    108106               IF( hmlp(ji,jj) < zN2_c )   nmln(ji,jj) = MIN( jk , ikt ) + 1   ! Mixed layer level 
    109107            END DO 
     
    111109      END DO 
    112110      ! 
    113       ! w-level of the turbocline 
     111      ! w-level of the turbocline and mixing layer (iom_use) 
    114112      imld(:,:) = mbkt(:,:) + 1        ! Initialization to the number of w ocean point 
    115113      DO jk = jpkm1, nlb10, -1         ! from the bottom to nlb10  
    116114         DO jj = 1, jpj 
    117115            DO ji = 1, jpi 
    118                imkt = mikt(ji,jj) 
    119                IF( avt (ji,jj,jk) < avt_c )   imld(ji,jj) = MAX( imkt, jk )      ! Turbocline  
     116               IF( avt (ji,jj,jk) < avt_c * wmask(ji,jj,jk) )   imld(ji,jj) = jk      ! Turbocline  
    120117            END DO 
    121118         END DO 
     
    126123            iiki = imld(ji,jj) 
    127124            iikn = nmln(ji,jj) 
    128             imkt = mikt(ji,jj) 
    129             hmld (ji,jj) = ( fsdepw(ji,jj,iiki  ) - fsdepw(ji,jj,imkt )            )   * ssmask(ji,jj)    ! Turbocline depth  
    130             hmlp (ji,jj) = ( fsdepw(ji,jj,iikn  ) - fsdepw(ji,jj,MAX( imkt,nla10 ) ) ) * ssmask(ji,jj)    ! Mixed layer depth 
    131             hmlpt(ji,jj) = ( fsdept(ji,jj,iikn-1) - fsdepw(ji,jj,imkt )            )   * ssmask(ji,jj)    ! depth of the last T-point inside the mixed layer 
     125            hmld (ji,jj) = gdepw_n(ji,jj,iiki  ) * ssmask(ji,jj)    ! Turbocline depth  
     126            hmlp (ji,jj) = gdepw_n(ji,jj,iikn  ) * ssmask(ji,jj)    ! Mixed layer depth 
     127            hmlpt(ji,jj) = gdept_n(ji,jj,iikn-1) * ssmask(ji,jj)    ! depth of the last T-point inside the mixed layer 
    132128         END DO 
    133129      END DO 
    134       IF( .NOT.lk_offline ) THEN            ! no need to output in offline mode 
    135          CALL iom_put( "mldr10_1", hmlp )   ! mixed layer depth 
    136          CALL iom_put( "mldkz5"  , hmld )   ! turbocline depth 
     130      ! no need to output in offline mode 
     131      IF( .NOT.lk_offline ) THEN    
     132         IF ( iom_use("mldr10_1") ) THEN 
     133            IF( ln_isfcav ) THEN 
     134               CALL iom_put( "mldr10_1", hmlp - risfdep)   ! mixed layer thickness 
     135            ELSE 
     136               CALL iom_put( "mldr10_1", hmlp )            ! mixed layer depth 
     137            END IF 
     138         END IF 
     139         IF ( iom_use("mldkz5") ) THEN 
     140            IF( ln_isfcav ) THEN 
     141               CALL iom_put( "mldkz5"  , hmld - risfdep )   ! turbocline thickness 
     142            ELSE 
     143               CALL iom_put( "mldkz5"  , hmld )             ! turbocline depth 
     144            END IF 
     145         END IF 
    137146      ENDIF 
    138147       
Note: See TracChangeset for help on using the changeset viewer.