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 6630 for branches/UKMO/dev_r5518_v3.4_asm_nemovar_community/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfmxl.F90 – NEMO

Ignore:
Timestamp:
2016-05-26T18:28:12+02:00 (8 years ago)
Author:
kingr
Message:

Adpated changes required to apply 2D surft increments in AMM7 from NEMO3.4 branch /branches/dev/frwe/vn3.4_ASM_NEMOVAR_community.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/dev_r5518_v3.4_asm_nemovar_community/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfmxl.F90

    r6626 r6630  
    3333   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hmlp    !: mixed layer depth  (rho=rho0+zdcrit) [m] 
    3434   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hmlpt   !: mixed layer depth at t-points        [m] 
     35   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hmld_tref  !: mixed layer depth at t-points - temperature criterion [m] 
    3536 
    3637   REAL(wp), PUBLIC ::   rho_c = 0.01_wp    !: density criterion for mixed layer depth 
     
    5253      zdf_mxl_alloc = 0      ! set to zero if no array to be allocated 
    5354      IF( .NOT. ALLOCATED( nmln ) ) THEN 
    54          ALLOCATE( nmln(jpi,jpj), hmld(jpi,jpj), hmlp(jpi,jpj), hmlpt(jpi,jpj), STAT= zdf_mxl_alloc ) 
     55         ALLOCATE( nmln(jpi,jpj), hmld(jpi,jpj), hmlp(jpi,jpj), hmlpt(jpi,jpj), & 
     56         &                           hmld_tref(jpi,jpj), STAT= zdf_mxl_alloc ) 
    5557         ! 
    5658         IF( lk_mpp             )   CALL mpp_sum ( zdf_mxl_alloc ) 
     
    8486      REAL(wp) ::   zN2_c        ! local scalar 
    8587      INTEGER, POINTER, DIMENSION(:,:) ::   imld   ! 2D workspace 
     88      REAL(wp) ::   t_ref               ! Reference temperature   
     89      REAL(wp) ::   temp_c = 0.2        ! temperature criterion for mixed layer depth   
    8690      !!---------------------------------------------------------------------- 
    8791      ! 
     
    137141         CALL iom_put( "mldkz5"  , hmld )   ! turbocline depth 
    138142      ENDIF 
     143 
     144      !For the AMM model assimiation uses a temperature based mixed layer depth   
     145      !This is defined here   
     146      DO jj = 1, jpj   
     147         DO ji = 1, jpi   
     148           hmld_tref(ji,jj)=fsdept(ji,jj,1  )    
     149           IF(ssmask(ji,jj) > 0.)THEN   
     150             t_ref=tsn(ji,jj,1,jp_tem)  
     151             DO jk=2,jpk   
     152               IF(ssmask(ji,jj)==0.)THEN   
     153                  hmld_tref(ji,jj)=fsdept(ji,jj,jk )   
     154                  EXIT   
     155               ELSEIF( ABS(tsn(ji,jj,jk,jp_tem)-t_ref) < temp_c)THEN   
     156                  hmld_tref(ji,jj)=fsdept(ji,jj,jk )   
     157               ELSE   
     158                  EXIT   
     159               ENDIF   
     160             ENDDO   
     161           ENDIF   
     162         ENDDO   
     163      ENDDO 
    139164       
    140165      IF(ln_ctl)   CALL prt_ctl( tab2d_1=REAL(nmln,wp), clinfo1=' nmln : ', tab2d_2=hmlp, clinfo2=' hmlp : ', ovlap=1 ) 
Note: See TracChangeset for help on using the changeset viewer.