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 6533 for branches/UKMO/dev_r5518_GO6_package/NEMOGCM – NEMO

Ignore:
Timestamp:
2016-05-13T15:22:14+02:00 (8 years ago)
Author:
davestorkey
Message:

Update mixed-layer depth diagnostic code in UKMO/dev_r5518_GO6_package branch.
Custom merge into /branches/UKMO/dev_r5518_GO6_package/NEMOGCM: r6335 cf. r5534 of /branches/UKMO/dev_r5107_mld_zint/NEMOGCM@6532

Location:
branches/UKMO/dev_r5518_GO6_package/NEMOGCM
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/dev_r5518_GO6_package/NEMOGCM/CONFIG/SHARED/field_def.xml

    r6501 r6533  
    5454         <field id="mldr10_1max"  long_name="Max of Mixed Layer Depth (dsigma = 0.01 wrt 10m)"   field_ref="mldr10_1"   operation="maximum"                                                                          /> 
    5555         <field id="mldr10_1min"  long_name="Min of Mixed Layer Depth (dsigma = 0.01 wrt 10m)"   field_ref="mldr10_1"   operation="minimum"                                                                          /> 
    56          <field id="mldzint"      long_name="Mixed Layer Depth interpolated"                     standard_name="ocean_mixed_layer_thickness_defined_by_sigma_theta"                                unit="m"          /> 
     56         <field id="mldzint_1"    long_name="Mixed Layer Depth interpolated"                     standard_name="ocean_mixed_layer_thickness"                                                       unit="m"          /> 
     57         <field id="mldzint_2"    long_name="Mixed Layer Depth interpolated"                     standard_name="ocean_mixed_layer_thickness"                                                       unit="m"          /> 
     58         <field id="mldzint_3"    long_name="Mixed Layer Depth interpolated"                     standard_name="ocean_mixed_layer_thickness"                                                       unit="m"          /> 
     59         <field id="mldzint_4"    long_name="Mixed Layer Depth interpolated"                     standard_name="ocean_mixed_layer_thickness"                                                       unit="m"          /> 
     60         <field id="mldzint_5"    long_name="Mixed Layer Depth interpolated"                     standard_name="ocean_mixed_layer_thickness"                                                       unit="m"          /> 
     61         <field id="mldhtc_1"     long_name="Mixed Layer Depth integrated heat content"          standard_name="integral_of_sea_water_potential_temperature_wrt_depth_expressed_as_heat_content"   unit="J/m2"       /> 
     62         <field id="mldhtc_2"     long_name="Mixed Layer Depth integrated heat content"          standard_name="integral_of_sea_water_potential_temperature_wrt_depth_expressed_as_heat_content"   unit="J/m2"       /> 
     63         <field id="mldhtc_3"     long_name="Mixed Layer Depth integrated heat content"          standard_name="integral_of_sea_water_potential_temperature_wrt_depth_expressed_as_heat_content"   unit="J/m2"       /> 
     64         <field id="mldhtc_4"     long_name="Mixed Layer Depth integrated heat content"          standard_name="integral_of_sea_water_potential_temperature_wrt_depth_expressed_as_heat_content"   unit="J/m2"       /> 
     65         <field id="mldhtc_5"     long_name="Mixed Layer Depth integrated heat content"          standard_name="integral_of_sea_water_potential_temperature_wrt_depth_expressed_as_heat_content"   unit="J/m2"       /> 
    5766         <field id="heatc"        long_name="Heat content vertically integrated"                 standard_name="integral_of_sea_water_potential_temperature_wrt_depth_expressed_as_heat_content"   unit="J/m2"       /> 
    5867         <field id="saltc"        long_name="Salt content vertically integrated"                                                                                                                   unit="1e-3*kg/m2" /> 
  • branches/UKMO/dev_r5518_GO6_package/NEMOGCM/CONFIG/SHARED/namelist_ref

    r6498 r6533  
    883883!!             Tracers & Dynamics vertical physics namelists 
    884884!!====================================================================== 
    885 !!    namzdf            vertical physics 
    886 !!    namzdf_ric        richardson number dependent vertical mixing     ("key_zdfric") 
    887 !!    namzdf_tke        TKE dependent vertical mixing                   ("key_zdftke") 
    888 !!    namzdf_kpp        KPP dependent vertical mixing                   ("key_zdfkpp") 
    889 !!    namzdf_ddm        double diffusive mixing parameterization        ("key_zdfddm") 
    890 !!    namzdf_tmx        tidal mixing parameterization                   ("key_zdftmx") 
     885!!    namzdf        vertical physics 
     886!!    namzdf_ric    richardson number dependent vertical mixing         ("key_zdfric") 
     887!!    namzdf_tke    TKE dependent vertical mixing                       ("key_zdftke") 
     888!!    namzdf_kpp    KPP dependent vertical mixing                       ("key_zdfkpp") 
     889!!    namzdf_ddm    double diffusive mixing parameterization            ("key_zdfddm") 
     890!!    namzdf_tmx    tidal mixing parameterization                       ("key_zdftmx") 
    891891!!    namzdf_tmx_new    new tidal mixing parameterization               ("key_zdftmx_new") 
     892!!    namzdf_mldzint vertically-interpolated mixed-layer depth parameters 
    892893!!====================================================================== 
    893894! 
     
    10031004   ln_tsdiff   = .true.    !  account for differential T/S mixing (T) or not (F) 
    10041005/ 
     1006!------------------------------------------------------------------------------------------ 
     1007&namzdf_mldzint    !   Parameters for vertically-interpolated mixed-layer depth diagnostic 
     1008!------------------------------------------------------------------------------------------ 
     1009   nn_mld_diag = 0         !  Number of MLD diagnostics to use from below 
     1010 
     1011!              ! MLD criterion ! Reference ! Finite difference ! Gradient layer ! 
     1012!              ! type          ! depth     ! criterion         ! criterion      ! 
     1013   sn_mld1     =       1       ,    10.0   ,        0.2        ,       0.1 
     1014   sn_mld2     =       ''      ,      ''   ,         ''        ,        '' 
     1015   sn_mld3     =       ''      ,      ''   ,         ''        ,        '' 
     1016   sn_mld4     =       ''      ,      ''   ,         ''        ,        '' 
     1017   sn_mld5     =       ''      ,      ''   ,         ''        ,        '' 
     1018/ 
     1019 
    10051020!!====================================================================== 
    10061021!!                  ***  Miscellaneous namelists  *** 
  • branches/UKMO/dev_r5518_GO6_package/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfmxl.F90

    r6498 r6533  
    3434   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hmlp    !: mixed layer depth  (rho=rho0+zdcrit) [m] 
    3535   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hmlpt   !: mixed layer depth at t-points        [m] 
    36    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hmld_zint  !: vertically-interpolated mixed layer depth   [m]  
     36   REAL(wp), PUBLIC, ALLOCATABLE,       DIMENSION(:,:) ::   hmld_zint  !: vertically-interpolated mixed layer depth   [m]  
     37   REAL(wp), PUBLIC, ALLOCATABLE,       DIMENSION(:,:) ::   htc_mld    ! Heat content of hmld_zint 
    3738   LOGICAL, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)    :: ll_found   ! Is T_b to be found by interpolation ?  
    3839   LOGICAL, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)  :: ll_belowml ! Flag points below mixed layer when ll_found=F 
     
    4142   REAL(wp)         ::   avt_c = 5.e-4_wp   ! Kz criterion for the turbocline depth 
    4243 
    43    ! Namelist variables for  namzdf_mldzint 
    44    INTEGER          :: nn_mld_type         ! mixed layer type             
    45    REAL(wp)         :: rn_zref            ! depth of initial T_ref 
    46    REAL(wp)         :: rn_dT_crit          ! Critical temp diff  
    47    REAL(wp)         :: rn_iso_frac         ! Fraction of rn_dT_crit used  
     44   TYPE, PUBLIC :: MXL_ZINT   !: Structure for MLD defs 
     45      INTEGER   :: mld_type   ! mixed layer type      
     46      REAL(wp)  :: zref       ! depth of initial T_ref 
     47      REAL(wp)  :: dT_crit    ! Critical temp diff 
     48      REAL(wp)  :: iso_frac   ! Fraction of rn_dT_crit used 
     49   END TYPE MXL_ZINT 
    4850 
    4951   !! * Substitutions 
     
    6365      IF( .NOT. ALLOCATED( nmln ) ) THEN 
    6466         ALLOCATE( nmln(jpi,jpj), hmld(jpi,jpj), hmlp(jpi,jpj), hmlpt(jpi,jpj), hmld_zint(jpi,jpj),       & 
     67        &          htc_mld(jpi,jpj),                                                                    & 
    6568        &          ll_found(jpi,jpj), ll_belowml(jpi,jpj,jpk), STAT= zdf_mxl_alloc ) 
    6669         ! 
     
    163166       
    164167      ! Vertically-interpolated mixed-layer depth diagnostic 
    165       IF( iom_use( "mldzint" ) ) THEN 
    166          CALL zdf_mxl_zint( kt ) 
    167          CALL iom_put( "mldzint" , hmld_zint ) 
    168       ENDIF 
     168      CALL zdf_mxl_zint( kt ) 
    169169 
    170170      IF(ln_ctl)   CALL prt_ctl( tab2d_1=REAL(nmln,wp), clinfo1=' nmln : ', tab2d_2=hmlp, clinfo2=' hmlp : ', ovlap=1 ) 
     
    176176   END SUBROUTINE zdf_mxl 
    177177 
    178    SUBROUTINE zdf_mxl_zint( kt )  
     178   SUBROUTINE zdf_mxl_zint_mld( sf )  
    179179      !!----------------------------------------------------------------------------------  
    180       !!                    ***  ROUTINE zdf_mxl_zint  ***  
     180      !!                    ***  ROUTINE zdf_mxl_zint_mld  ***  
    181181      !                                                                         
    182182      !   Calculate vertically-interpolated mixed layer depth diagnostic.  
     
    198198      !!-----------------------------------------------------------------------------------  
    199199 
    200       INTEGER, INTENT(in) ::   kt   ! ocean time-step index 
    201       ! 
     200      TYPE(MXL_ZINT), INTENT(in)  :: sf 
     201 
     202      ! Diagnostic criteria 
     203      INTEGER   :: nn_mld_type   ! mixed layer type      
     204      REAL(wp)  :: rn_zref       ! depth of initial T_ref 
     205      REAL(wp)  :: rn_dT_crit    ! Critical temp diff 
     206      REAL(wp)  :: rn_iso_frac   ! Fraction of rn_dT_crit used 
     207 
    202208      ! Local variables 
     209      REAL(wp), PARAMETER :: zepsilon = 1.e-30          ! local small value 
    203210      INTEGER, POINTER, DIMENSION(:,:) :: ikmt          ! number of active tracer levels  
    204211      INTEGER, POINTER, DIMENSION(:,:) :: ik_ref        ! index of reference level  
     
    215222      REAL, POINTER, DIMENSION(:,:)    :: zRHO1, zRHO2  ! Densities  
    216223      INTEGER :: ji, jj, jk                             ! loop counter  
    217       INTEGER :: ios 
    218  
    219       NAMELIST/namzdf_mldzint/ nn_mld_type, rn_zref, rn_dT_crit, rn_iso_frac 
    220224 
    221225      !!-------------------------------------------------------------------------------------  
     
    224228      CALL wrk_alloc( jpi, jpj, ppzdep, zT_ref, zdelta_T, zRHO1, zRHO2 )  
    225229      CALL wrk_alloc( jpi, jpj, jpk, zT, zdTdz, zmoddT )  
    226   
    227       IF( kt == nit000 ) THEN 
    228          REWIND( numnam_ref )              ! Namelist namzdf_mldzint in reference namelist  
    229          READ  ( numnam_ref, namzdf_mldzint, IOSTAT = ios, ERR = 901) 
    230 901      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzdf_mldzint in reference namelist', lwp ) 
    231  
    232          REWIND( numnam_cfg )              ! Namelist namzdf_mldzint in configuration namelist  
    233          READ  ( numnam_cfg, namzdf_mldzint, IOSTAT = ios, ERR = 902 ) 
    234 902      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzdf_mldzint in configuration namelist', lwp ) 
    235          IF(lwm) WRITE ( numond, namzdf_mldzint ) 
    236  
    237          WRITE(numout,*) '===== Vertically-interpolated mixed layer =====' 
    238          WRITE(numout,*) 'nn_mld_type = ',nn_mld_type 
    239          WRITE(numout,*) 'rn_zref = ',rn_zref 
    240          WRITE(numout,*) 'rn_dT_crit = ',rn_dT_crit 
    241          WRITE(numout,*) 'rn_iso_frac = ',rn_iso_frac 
    242          WRITE(numout,*) '===============================================' 
    243       ENDIF 
    244   
     230 
     231      ! Unpack structure 
     232      nn_mld_type = sf%mld_type 
     233      rn_zref     = sf%zref 
     234      rn_dT_crit  = sf%dT_crit 
     235      rn_iso_frac = sf%iso_frac 
     236 
    245237      ! Set the mixed layer depth criterion at each grid point  
    246       IF (nn_mld_type == 1) THEN                                          
     238      IF( nn_mld_type == 0 ) THEN 
     239         zdelta_T(:,:) = rn_dT_crit 
     240         zT(:,:,:) = rhop(:,:,:) 
     241      ELSE IF( nn_mld_type == 1 ) THEN 
    247242         ppzdep(:,:)=0.0  
    248243         call eos ( tsn(:,:,1,:), ppzdep(:,:), zRHO1(:,:) )  
     
    288283      ikmt(:,:) = mbathy(:,:) - 1  
    289284 
    290       ! Search for a uniform density/temperature region where adjacent levels           
    291       ! differ by less than rn_iso_frac * deltaT.                                       
    292       ! ik_iso is the index of the last level in the uniform layer   
    293       ! ll_found indicates whether the mixed layer depth can be found by interpolation  
    294       ik_iso(:,:)   = ik_ref(:,:)  
    295       ll_found(:,:) = .false.  
    296       DO jj = 1, nlcj  
    297          DO ji = 1, nlci  
     285      ! Initialize / reset 
     286      ll_found(:,:) = .false. 
     287 
     288      IF ( rn_iso_frac - zepsilon > 0. ) THEN 
     289         ! Search for a uniform density/temperature region where adjacent levels           
     290         ! differ by less than rn_iso_frac * deltaT.                                       
     291         ! ik_iso is the index of the last level in the uniform layer   
     292         ! ll_found indicates whether the mixed layer depth can be found by interpolation  
     293         ik_iso(:,:)   = ik_ref(:,:)  
     294         DO jj = 1, nlcj  
     295            DO ji = 1, nlci  
    298296!CDIR NOVECTOR  
    299             DO jk = ik_ref(ji,jj), ikmt(ji,jj)-1  
    300                IF ( zmoddT(ji,jj,jk) > ( rn_iso_frac * zdelta_T(ji,jj) ) ) THEN  
    301                   ik_iso(ji,jj)   = jk  
    302                   ll_found(ji,jj) = ( zmoddT(ji,jj,jk) > zdelta_T(ji,jj) )  
    303                   EXIT  
     297               DO jk = ik_ref(ji,jj), ikmt(ji,jj)-1  
     298                  IF ( zmoddT(ji,jj,jk) > ( rn_iso_frac * zdelta_T(ji,jj) ) ) THEN  
     299                     ik_iso(ji,jj)   = jk  
     300                     ll_found(ji,jj) = ( zmoddT(ji,jj,jk) > zdelta_T(ji,jj) )  
     301                     EXIT  
     302                  END IF  
     303               END DO  
     304            END DO  
     305         END DO  
     306 
     307         ! Use linear interpolation to find depth of mixed layer base where possible  
     308         hmld_zint(:,:) = rn_zref  
     309         DO jj = 1, jpj  
     310            DO ji = 1, jpi  
     311               IF (ll_found(ji,jj) .and. tmask(ji,jj,1) == 1.0) THEN  
     312                  zdz =  abs( zdelta_T(ji,jj) / zdTdz(ji,jj,ik_iso(ji,jj)) )  
     313                  hmld_zint(ji,jj) = fsdept(ji,jj,ik_iso(ji,jj)) + zdz  
    304314               END IF  
    305315            END DO  
    306316         END DO  
    307       END DO  
    308  
    309       ! Use linear interpolation to find depth of mixed layer base where possible  
    310       hmld_zint(:,:) = rn_zref  
    311       DO jj = 1, jpj  
    312          DO ji = 1, jpi  
    313             IF (ll_found(ji,jj) .and. tmask(ji,jj,1) == 1.0) THEN  
    314                zdz =  abs( zdelta_T(ji,jj) / zdTdz(ji,jj,ik_iso(ji,jj)) )  
    315                hmld_zint(ji,jj) = fsdept(ji,jj,ik_iso(ji,jj)) + zdz  
    316             END IF  
    317          END DO  
    318       END DO  
     317      END IF 
    319318 
    320319      ! If ll_found = .false. then calculate MLD using difference of zdelta_T     
     
    359358      CALL wrk_dealloc( jpi,jpj, jpk, zT, zdTdz, zmoddT )  
    360359      !  
     360   END SUBROUTINE zdf_mxl_zint_mld 
     361 
     362   SUBROUTINE zdf_mxl_zint_htc( kt ) 
     363      !!---------------------------------------------------------------------- 
     364      !!                  ***  ROUTINE zdf_mxl_zint_htc  *** 
     365      !!  
     366      !! ** Purpose :    
     367      !! 
     368      !! ** Method  :    
     369      !!---------------------------------------------------------------------- 
     370 
     371      INTEGER, INTENT(in) ::   kt   ! ocean time-step index 
     372 
     373      INTEGER :: ji, jj, jk 
     374      INTEGER :: ikmax 
     375      REAL(wp) :: zc, zcoef 
     376      ! 
     377      INTEGER,  ALLOCATABLE, DIMENSION(:,:) ::   ilevel 
     378      REAL(wp), ALLOCATABLE, DIMENSION(:,:) ::   zthick_0, zthick 
     379 
     380      !!---------------------------------------------------------------------- 
     381 
     382      IF( .NOT. ALLOCATED(ilevel) ) THEN 
     383         ALLOCATE( ilevel(jpi,jpj), zthick_0(jpi,jpj), & 
     384         &         zthick(jpi,jpj), STAT=ji ) 
     385         IF( lk_mpp  )   CALL mpp_sum(ji) 
     386         IF( ji /= 0 )   CALL ctl_stop( 'STOP', 'zdf_mxl_zint_htc : unable to allocate arrays' ) 
     387      ENDIF 
     388 
     389      ! Find last whole model T level above the MLD 
     390      ilevel(:,:)   = 0 
     391      zthick_0(:,:) = 0._wp 
     392 
     393      DO jk = 1, jpkm1   
     394         DO jj = 1, jpj 
     395            DO ji = 1, jpi                     
     396               zthick_0(ji,jj) = zthick_0(ji,jj) + fse3t(ji,jj,jk) 
     397               IF( zthick_0(ji,jj) < hmld_zint(ji,jj) )   ilevel(ji,jj) = jk 
     398            END DO 
     399         END DO 
     400         WRITE(numout,*) 'zthick_0(jk =',jk,') =',zthick_0(2,2) 
     401         WRITE(numout,*) 'fsdepw(jk+1 =',jk+1,') =',fsdepw(2,2,jk+1) 
     402      END DO 
     403 
     404      ! Surface boundary condition 
     405      IF( lk_vvl ) THEN   ;   zthick(:,:) = 0._wp       ;   htc_mld(:,:) = 0._wp                                    
     406      ELSE                ;   zthick(:,:) = sshn(:,:)   ;   htc_mld(:,:) = tsn(:,:,1,jp_tem) * sshn(:,:) * tmask(:,:,1)    
     407      ENDIF 
     408 
     409      ! Deepest whole T level above the MLD 
     410      ikmax = MIN( MAXVAL( ilevel(:,:) ), jpkm1 ) 
     411 
     412      ! Integration down to last whole model T level 
     413      DO jk = 1, ikmax 
     414         DO jj = 1, jpj 
     415            DO ji = 1, jpi 
     416               zc = fse3t(ji,jj,jk) * REAL( MIN( MAX( 0, ilevel(ji,jj) - jk + 1 ) , 1  )  )    ! 0 below ilevel 
     417               zthick(ji,jj) = zthick(ji,jj) + zc 
     418               htc_mld(ji,jj) = htc_mld(ji,jj) + zc * tsn(ji,jj,jk,jp_tem) * tmask(ji,jj,jk) 
     419            END DO 
     420         END DO 
     421      END DO 
     422 
     423      ! Subsequent partial T level 
     424      zthick(:,:) = hmld_zint(:,:) - zthick(:,:)   !   remaining thickness to reach MLD 
     425 
     426      DO jj = 1, jpj 
     427         DO ji = 1, jpi 
     428            htc_mld(ji,jj) = htc_mld(ji,jj) + tsn(ji,jj,ilevel(ji,jj)+1,jp_tem)  &  
     429      &                      * MIN( fse3t(ji,jj,ilevel(ji,jj)+1), zthick(ji,jj) ) * tmask(ji,jj,ilevel(ji,jj)+1) 
     430         END DO 
     431      END DO 
     432 
     433      WRITE(numout,*) 'htc_mld(after) =',htc_mld(2,2) 
     434 
     435      ! Convert to heat content 
     436      zcoef = rau0 * rcp 
     437      htc_mld(:,:) = zcoef * htc_mld(:,:) 
     438 
     439   END SUBROUTINE zdf_mxl_zint_htc 
     440 
     441   SUBROUTINE zdf_mxl_zint( kt ) 
     442      !!---------------------------------------------------------------------- 
     443      !!                  ***  ROUTINE zdf_mxl_zint  *** 
     444      !!  
     445      !! ** Purpose :    
     446      !! 
     447      !! ** Method  :    
     448      !!---------------------------------------------------------------------- 
     449 
     450      INTEGER, INTENT(in) ::   kt   ! ocean time-step index 
     451 
     452      INTEGER :: ios 
     453      INTEGER :: jn 
     454 
     455      INTEGER :: nn_mld_diag = 0    ! number of diagnostics 
     456 
     457      CHARACTER(len=1) :: cmld 
     458 
     459      TYPE(MXL_ZINT) :: sn_mld1, sn_mld2, sn_mld3, sn_mld4, sn_mld5 
     460      TYPE(MXL_ZINT), SAVE, DIMENSION(5) ::   mld_diags 
     461 
     462      NAMELIST/namzdf_mldzint/ nn_mld_diag, sn_mld1, sn_mld2, sn_mld3, sn_mld4, sn_mld5 
     463 
     464      !!---------------------------------------------------------------------- 
     465       
     466      IF( kt == nit000 ) THEN 
     467         REWIND( numnam_ref )              ! Namelist namzdf_mldzint in reference namelist  
     468         READ  ( numnam_ref, namzdf_mldzint, IOSTAT = ios, ERR = 901) 
     469901      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzdf_mldzint in reference namelist', lwp ) 
     470 
     471         REWIND( numnam_cfg )              ! Namelist namzdf_mldzint in configuration namelist  
     472         READ  ( numnam_cfg, namzdf_mldzint, IOSTAT = ios, ERR = 902 ) 
     473902      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzdf_mldzint in configuration namelist', lwp ) 
     474         IF(lwm) WRITE ( numond, namzdf_mldzint ) 
     475 
     476         IF( nn_mld_diag > 5 )   CALL ctl_stop( 'STOP', 'zdf_mxl_ini: Specify no more than 5 MLD definitions' ) 
     477 
     478         mld_diags(1) = sn_mld1 
     479         mld_diags(2) = sn_mld2 
     480         mld_diags(3) = sn_mld3 
     481         mld_diags(4) = sn_mld4 
     482         mld_diags(5) = sn_mld5 
     483 
     484         IF( nn_mld_diag > 0 ) THEN 
     485            WRITE(numout,*) '=============== Vertically-interpolated mixed layer ================' 
     486            WRITE(numout,*) '(Diagnostic number, nn_mld_type, rn_zref, rn_dT_crit, rn_iso_frac)' 
     487            DO jn = 1, nn_mld_diag 
     488               WRITE(numout,*) 'MLD criterion',jn,':' 
     489               WRITE(numout,*) '    nn_mld_type =', mld_diags(jn)%mld_type 
     490               WRITE(numout,*) '    rn_zref ='    , mld_diags(jn)%zref 
     491               WRITE(numout,*) '    rn_dT_crit =' , mld_diags(jn)%dT_crit 
     492               WRITE(numout,*) '    rn_iso_frac =', mld_diags(jn)%iso_frac 
     493            END DO 
     494            WRITE(numout,*) '====================================================================' 
     495         ENDIF 
     496      ENDIF 
     497 
     498      IF( nn_mld_diag > 0 ) THEN 
     499         DO jn = 1, nn_mld_diag 
     500            WRITE(cmld,'(I1)') jn 
     501            IF( iom_use( "mldzint_"//cmld ) .OR. iom_use( "mldhtc_"//cmld ) ) THEN 
     502               CALL zdf_mxl_zint_mld( mld_diags(jn) ) 
     503 
     504               IF( iom_use( "mldzint_"//cmld ) ) THEN 
     505                  CALL iom_put( "mldzint_"//cmld, hmld_zint(:,:) ) 
     506               ENDIF 
     507 
     508               IF( iom_use( "mldhtc_"//cmld ) )  THEN 
     509                  CALL zdf_mxl_zint_htc( kt ) 
     510                  CALL iom_put( "mldhtc_"//cmld , htc_mld(:,:)   ) 
     511               ENDIF 
     512            ENDIF 
     513         END DO 
     514      ENDIF 
     515 
    361516   END SUBROUTINE zdf_mxl_zint 
    362517 
Note: See TracChangeset for help on using the changeset viewer.