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 5038 for branches/2014/dev_r4621_NOC4_BDY_VERT_INTERP/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfmxl.F90 – NEMO

Ignore:
Timestamp:
2015-01-20T15:26:13+01:00 (9 years ago)
Author:
jamesharle
Message:

Merging branch with HEAD of the trunk

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2014/dev_r4621_NOC4_BDY_VERT_INTERP/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfmxl.F90

    r4245 r5038  
    66   !! History :  1.0  ! 2003-08  (G. Madec)  original code 
    77   !!            3.2  ! 2009-07  (S. Masson, G. Madec)  IOM + merge of DO-loop 
     8   !!            3.7  ! 2012-03  (G. Madec)  make public the density criteria for trdmxl  
     9   !!             -   ! 2014-02  (F. Roquet)  mixed layer depth calculated using N2 instead of rhop  
    810   !!---------------------------------------------------------------------- 
    911   !!   zdf_mxl      : Compute the turbocline and mixed layer depths. 
     
    1416   USE in_out_manager  ! I/O manager 
    1517   USE prtctl          ! Print control 
     18   USE phycst          ! physical constants 
    1619   USE iom             ! I/O library 
    1720   USE lib_mpp         ! MPP library 
     
    2528   PUBLIC   zdf_mxl       ! called by step.F90 
    2629 
    27    REAL(wp), PUBLIC ::   rho_c = 0.01_wp    ! density criterion for mixed layer depth 
    28    REAL(wp), PUBLIC ::   avt_c = 5.e-4_wp   ! Kz criterion for the turbocline depth 
    29  
    3030   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   nmln    !: number of level in the mixed layer (used by TOP) 
    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] 
    3333   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hmlpt   !: mixed layer depth at t-points        [m] 
     34 
     35   REAL(wp), PUBLIC ::   rho_c = 0.01_wp    !: density criterion for mixed layer depth 
     36   REAL(wp)         ::   avt_c = 5.e-4_wp   ! Kz criterion for the turbocline depth 
    3437 
    3538   !! * Substitutions 
     
    7073      !!      eddy diffusivity coefficient (resulting from the vertical physics 
    7174      !!      alone, not the isopycnal part, see trazdf.F) fall below a given 
    72       !!      value defined locally (avt_c here taken equal to 5 cm/s2) 
     75      !!      value defined locally (avt_c here taken equal to 5 cm/s2 by default) 
    7376      !! 
    7477      !! ** Action  :   nmln, hmld, hmlp, hmlpt 
    7578      !!---------------------------------------------------------------------- 
    7679      INTEGER, INTENT(in) ::   kt   ! ocean time-step index 
    77       !! 
    78       INTEGER  ::   ji, jj, jk          ! dummy loop indices 
    79       INTEGER  ::   iikn, iiki          ! temporary integer within a do loop 
    80       INTEGER, POINTER, DIMENSION(:,:) ::   imld                ! temporary workspace 
     80      ! 
     81      INTEGER  ::   ji, jj, jk   ! dummy loop indices 
     82      INTEGER  ::   iikn, iiki, ikt, imkt   ! local integer 
     83      REAL(wp) ::   zN2_c        ! local scalar 
     84      INTEGER, POINTER, DIMENSION(:,:) ::   imld   ! 2D workspace 
    8185      !!---------------------------------------------------------------------- 
    8286      ! 
     
    9498 
    9599      ! w-level of the mixing and mixed layers 
    96       nmln(:,:) = mbkt(:,:) + 1        ! Initialization to the number of w ocean point 
    97       imld(:,:) = mbkt(:,:) + 1 
    98       DO jk = jpkm1, nlb10, -1         ! from the bottom to nlb10 
     100      nmln(:,:)  = nlb10               ! Initialization to the number of w ocean point 
     101      hmlp(:,:)  = 0._wp               ! here hmlp used as a dummy variable, integrating vertically N^2 
     102      zN2_c = grav * rho_c * r1_rau0   ! convert density criteria into N^2 criteria 
     103      DO jk = nlb10, jpkm1 
     104         DO jj = 1, jpj                ! Mixed layer level: w-level  
     105            DO ji = 1, jpi 
     106               ikt = mbkt(ji,jj) 
     107               hmlp(ji,jj) = hmlp(ji,jj) + MAX( rn2b(ji,jj,jk) , 0._wp ) * fse3w(ji,jj,jk) 
     108               IF( hmlp(ji,jj) < zN2_c )   nmln(ji,jj) = MIN( jk , ikt ) + 1   ! Mixed layer level 
     109            END DO 
     110         END DO 
     111      END DO 
     112      ! 
     113      ! w-level of the turbocline 
     114      imld(:,:) = mbkt(:,:) + 1        ! Initialization to the number of w ocean point 
     115      DO jk = jpkm1, nlb10, -1         ! from the bottom to nlb10  
    99116         DO jj = 1, jpj 
    100117            DO ji = 1, jpi 
    101                IF( rhop(ji,jj,jk) > rhop(ji,jj,nla10) + rho_c )   nmln(ji,jj) = jk      ! Mixed layer 
    102                IF( avt (ji,jj,jk) < avt_c                     )   imld(ji,jj) = jk      ! Turbocline  
     118               imkt = mikt(ji,jj) 
     119               IF( avt (ji,jj,jk) < avt_c )   imld(ji,jj) = MAX( imkt, jk )      ! Turbocline  
    103120            END DO 
    104121         END DO 
     
    109126            iiki = imld(ji,jj) 
    110127            iikn = nmln(ji,jj) 
    111             hmld (ji,jj) = fsdepw(ji,jj,iiki  ) * tmask(ji,jj,1)    ! Turbocline depth  
    112             hmlp (ji,jj) = fsdepw(ji,jj,iikn  ) * tmask(ji,jj,1)    ! Mixed layer depth 
    113             hmlpt(ji,jj) = fsdept(ji,jj,iikn-1)                     ! depth of the last T-point inside the mixed layer 
     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 
    114132         END DO 
    115133      END DO 
Note: See TracChangeset for help on using the changeset viewer.