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 6072 – NEMO

Changeset 6072


Ignore:
Timestamp:
2015-12-16T17:12:13+01:00 (8 years ago)
Author:
hadcv
Message:

Changes to allow up to 5 separate MLD definitions in the namelist.

  • Altered the namzdf_mldzint namelist to allow up to 5 MLD definitions
    • The namelist parameters have been converted to a Fortran structure format
    • The zdfmxl module has been restructured to work with this
    • A new parameter in namzdf_mldzint controls the number of these diagnostics to calculate
    • The XIOS field_def file has been updated with new definitions
  • A heat content diagnostic integrated over each defined MLD has been added
  • An additional MLD criterion type has been added for density (nn_mld_type = 0)
Location:
branches/UKMO/dev_r5107_mld_zint/NEMOGCM
Files:
3 edited

Legend:

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

    r5534 r6072  
    5353         <field id="mldr10_1max"  long_name="Max of Mixed Layer Depth (dsigma = 0.01 wrt 10m)"   field_ref="mldr10_1"   operation="maximum"                                                                          /> 
    5454         <field id="mldr10_1min"  long_name="Min of Mixed Layer Depth (dsigma = 0.01 wrt 10m)"   field_ref="mldr10_1"   operation="minimum"                                                                          /> 
    55          <field id="mldzint"      long_name="Mixed Layer Depth interpolated"                     standard_name="ocean_mixed_layer_thickness_defined_by_sigma_theta"                                unit="m"          /> 
     55         <field id="mldzint_1"    long_name="Mixed Layer Depth interpolated"                     standard_name="ocean_mixed_layer_thickness"                                                       unit="m"          /> 
     56         <field id="mldzint_2"     field_ref="mldzint_1" /> 
     57         <field id="mldzint_3"     field_ref="mldzint_1" /> 
     58         <field id="mldzint_4"     field_ref="mldzint_1" /> 
     59         <field id="mldzint_5"     field_ref="mldzint_1" /> 
     60         <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"       /> 
     61         <field id="mldhtc_2"      field_ref="mldhtc_1"  /> 
     62         <field id="mldhtc_3"      field_ref="mldhtc_1"  /> 
     63         <field id="mldhtc_4"      field_ref="mldhtc_1"  /> 
     64         <field id="mldhtc_5"      field_ref="mldhtc_1"  /> 
    5665         <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"       /> 
    5766         <field id="saltc"        long_name="Salt content vertically integrated"                                                                                                                   unit="1e-3*kg/m2" /> 
  • branches/UKMO/dev_r5107_mld_zint/NEMOGCM/CONFIG/SHARED/namelist_ref

    r5534 r6072  
    10141014&namzdf_mldzint    !   Parameters for vertically-interpolated mixed-layer depth diagnostic 
    10151015!------------------------------------------------------------------------------------------ 
    1016          nn_mld_type   = 1      ! mixed layer type 
    1017          rn_zref       = 10.0   ! depth of initial reference temperature 
    1018          rn_dT_crit    = 0.2    ! critical temperature difference 
    1019          rn_iso_frac   = 0.1    ! fraction of critical temperature difference used 
     1016   nn_mld_diag = 0         !  Number of MLD diagnostics to use from below 
     1017 
     1018!              ! MLD criterion ! Reference ! Finite difference ! Gradient layer ! 
     1019!              ! type          ! depth     ! criterion         ! criterion      ! 
     1020   sn_mld1     =       1       ,    10.0   ,        0.2        ,       0.1 
     1021   sn_mld2     =       ''      ,      ''   ,         ''        ,        '' 
     1022   sn_mld3     =       ''      ,      ''   ,         ''        ,        '' 
     1023   sn_mld4     =       ''      ,      ''   ,         ''        ,        '' 
     1024   sn_mld5     =       ''      ,      ''   ,         ''        ,        '' 
    10201025/ 
    10211026 
  • branches/UKMO/dev_r5107_mld_zint/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfmxl.F90

    r5249 r6072  
    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_zint  !: vertically-interpolated mixed layer depth   [m]  
     35   REAL(wp), PUBLIC, ALLOCATABLE,       DIMENSION(:,:) ::   hmld_zint  !: vertically-interpolated mixed layer depth   [m]  
     36   REAL(wp), PUBLIC, ALLOCATABLE,       DIMENSION(:,:) ::   htc_mld    ! Heat content of hmld_zint 
    3637   LOGICAL, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)    :: ll_found   ! Is T_b to be found by interpolation ?  
    3738   LOGICAL, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)  :: ll_belowml ! Flag points below mixed layer when ll_found=F 
     
    4041   REAL(wp)         ::   avt_c = 5.e-4_wp   ! Kz criterion for the turbocline depth 
    4142 
    42    ! Namelist variables for  namzdf_mldzint 
    43    INTEGER          :: nn_mld_type         ! mixed layer type             
    44    REAL(wp)         :: rn_zref            ! depth of initial T_ref 
    45    REAL(wp)         :: rn_dT_crit          ! Critical temp diff  
    46    REAL(wp)         :: rn_iso_frac         ! Fraction of rn_dT_crit used  
     43   TYPE, PUBLIC :: MXL_ZINT   !: Structure for MLD defs 
     44      INTEGER   :: mld_type   ! mixed layer type      
     45      REAL(wp)  :: zref       ! depth of initial T_ref 
     46      REAL(wp)  :: dT_crit    ! Critical temp diff 
     47      REAL(wp)  :: iso_frac   ! Fraction of rn_dT_crit used 
     48   END TYPE MXL_ZINT 
    4749 
    4850   !! * Substitutions 
     
    6264      IF( .NOT. ALLOCATED( nmln ) ) THEN 
    6365         ALLOCATE( nmln(jpi,jpj), hmld(jpi,jpj), hmlp(jpi,jpj), hmlpt(jpi,jpj), hmld_zint(jpi,jpj),       & 
     66        &          htc_mld(jpi,jpj),                                                                    & 
    6467        &          ll_found(jpi,jpj), ll_belowml(jpi,jpj,jpk), STAT= zdf_mxl_alloc ) 
    6568         ! 
     
    149152       
    150153      ! Vertically-interpolated mixed-layer depth diagnostic 
    151       IF( iom_use( "mldzint" ) ) THEN 
    152          CALL zdf_mxl_zint( kt ) 
    153          CALL iom_put( "mldzint" , hmld_zint ) 
    154       ENDIF 
     154      CALL zdf_mxl_zint( kt ) 
    155155 
    156156      IF(ln_ctl)   CALL prt_ctl( tab2d_1=REAL(nmln,wp), clinfo1=' nmln : ', tab2d_2=hmlp, clinfo2=' hmlp : ', ovlap=1 ) 
     
    162162   END SUBROUTINE zdf_mxl 
    163163 
    164    SUBROUTINE zdf_mxl_zint( kt )  
     164   SUBROUTINE zdf_mxl_zint_mld( sf )  
    165165      !!----------------------------------------------------------------------------------  
    166       !!                    ***  ROUTINE zdf_mxl_zint  ***  
     166      !!                    ***  ROUTINE zdf_mxl_zint_mld  ***  
    167167      !                                                                         
    168168      !   Calculate vertically-interpolated mixed layer depth diagnostic.  
     
    184184      !!-----------------------------------------------------------------------------------  
    185185 
    186       INTEGER, INTENT(in) ::   kt   ! ocean time-step index 
    187       ! 
     186      TYPE(MXL_ZINT), INTENT(in)  :: sf 
     187 
     188      ! Diagnostic criteria 
     189      INTEGER   :: nn_mld_type   ! mixed layer type      
     190      REAL(wp)  :: rn_zref       ! depth of initial T_ref 
     191      REAL(wp)  :: rn_dT_crit    ! Critical temp diff 
     192      REAL(wp)  :: rn_iso_frac   ! Fraction of rn_dT_crit used 
     193 
    188194      ! Local variables 
    189195      INTEGER, POINTER, DIMENSION(:,:) :: ikmt          ! number of active tracer levels  
     
    201207      REAL, POINTER, DIMENSION(:,:)    :: zRHO1, zRHO2  ! Densities  
    202208      INTEGER :: ji, jj, jk                             ! loop counter  
    203       INTEGER :: ios 
    204  
    205       NAMELIST/namzdf_mldzint/ nn_mld_type, rn_zref, rn_dT_crit, rn_iso_frac 
    206209 
    207210      !!-------------------------------------------------------------------------------------  
     
    210213      CALL wrk_alloc( jpi, jpj, ppzdep, zT_ref, zdelta_T, zRHO1, zRHO2 )  
    211214      CALL wrk_alloc( jpi, jpj, jpk, zT, zdTdz, zmoddT )  
    212   
    213       IF( kt == nit000 ) THEN 
    214          REWIND( numnam_ref )              ! Namelist namzdf_mldzint in reference namelist  
    215          READ  ( numnam_ref, namzdf_mldzint, IOSTAT = ios, ERR = 901) 
    216 901      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzdf_mldzint in reference namelist', lwp ) 
    217  
    218          REWIND( numnam_cfg )              ! Namelist namzdf_mldzint in configuration namelist  
    219          READ  ( numnam_cfg, namzdf_mldzint, IOSTAT = ios, ERR = 902 ) 
    220 902      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzdf_mldzint in configuration namelist', lwp ) 
    221          IF(lwm) WRITE ( numond, namzdf_mldzint ) 
    222  
    223          WRITE(numout,*) '===== Vertically-interpolated mixed layer =====' 
    224          WRITE(numout,*) 'nn_mld_type = ',nn_mld_type 
    225          WRITE(numout,*) 'rn_zref = ',rn_zref 
    226          WRITE(numout,*) 'rn_dT_crit = ',rn_dT_crit 
    227          WRITE(numout,*) 'rn_iso_frac = ',rn_iso_frac 
    228          WRITE(numout,*) '===============================================' 
    229       ENDIF 
    230   
     215 
     216      ! Unpack structure 
     217      nn_mld_type = sf%mld_type 
     218      rn_zref     = sf%zref 
     219      rn_dT_crit  = sf%dT_crit 
     220      rn_iso_frac = sf%iso_frac 
     221 
    231222      ! Set the mixed layer depth criterion at each grid point  
    232       IF (nn_mld_type == 1) THEN                                          
     223      IF( nn_mld_type == 0 ) THEN 
     224         zdelta_T(:,:) = rn_dT_crit 
     225         zT(:,:,:) = rhop(:,:,:) 
     226      ELSE IF( nn_mld_type == 1 ) THEN 
    233227         ppzdep(:,:)=0.0  
    234228         call eos ( tsn(:,:,1,:), ppzdep(:,:), zRHO1(:,:) )  
     
    345339      CALL wrk_dealloc( jpi,jpj, jpk, zT, zdTdz, zmoddT )  
    346340      !  
     341   END SUBROUTINE zdf_mxl_zint_mld 
     342 
     343   SUBROUTINE zdf_mxl_zint_htc( kt ) 
     344      !!---------------------------------------------------------------------- 
     345      !!                  ***  ROUTINE zdf_mxl_zint_htc  *** 
     346      !!  
     347      !! ** Purpose :    
     348      !! 
     349      !! ** Method  :    
     350      !!---------------------------------------------------------------------- 
     351 
     352      INTEGER, INTENT(in) ::   kt   ! ocean time-step index 
     353 
     354      INTEGER :: ji, jj, jk 
     355      INTEGER :: ikmax 
     356      REAL(wp) :: zc, zcoef 
     357      ! 
     358      INTEGER,  ALLOCATABLE, DIMENSION(:,:) ::   ilevel 
     359      REAL(wp), ALLOCATABLE, DIMENSION(:,:) ::   zthick_0, zthick 
     360 
     361      !!---------------------------------------------------------------------- 
     362 
     363      IF( .NOT. ALLOCATED(ilevel) ) THEN 
     364         ALLOCATE( ilevel(jpi,jpj), zthick_0(jpi,jpj), & 
     365         &         zthick(jpi,jpj), STAT=ji ) 
     366         IF( lk_mpp  )   CALL mpp_sum(ji) 
     367         IF( ji /= 0 )   CALL ctl_stop( 'STOP', 'zdf_mxl_zint_htc : unable to allocate arrays' ) 
     368      ENDIF 
     369 
     370      ! Find last whole model T level above the MLD 
     371      ilevel(:,:)   = 0 
     372      zthick_0(:,:) = 0._wp 
     373 
     374      DO jk = 1, jpkm1   
     375         DO jj = 1, jpj 
     376            DO ji = 1, jpi                     
     377               zthick_0(ji,jj) = zthick_0(ji,jj) + fse3t(ji,jj,jk) 
     378               IF( zthick_0(ji,jj) < hmld_zint(ji,jj) )   ilevel(ji,jj) = jk 
     379            END DO 
     380         END DO 
     381         WRITE(numout,*) 'zthick_0(jk =',jk,') =',zthick_0(2,2) 
     382         WRITE(numout,*) 'fsdepw(jk+1 =',jk+1,') =',fsdepw(2,2,jk+1) 
     383      END DO 
     384 
     385      ! Surface boundary condition 
     386      IF( lk_vvl ) THEN   ;   zthick(:,:) = 0._wp       ;   htc_mld(:,:) = 0._wp                                    
     387      ELSE                ;   zthick(:,:) = sshn(:,:)   ;   htc_mld(:,:) = tsn(:,:,1,jp_tem) * sshn(:,:) * tmask(:,:,1)    
     388      ENDIF 
     389 
     390      ! Deepest whole T level above the MLD 
     391      ikmax = MIN( MAXVAL( ilevel(:,:) ), jpkm1 ) 
     392 
     393      ! Integration down to last whole model T level 
     394      DO jk = 1, ikmax 
     395         DO jj = 1, jpj 
     396            DO ji = 1, jpi 
     397               zc = fse3t(ji,jj,jk) * REAL( MIN( MAX( 0, ilevel(ji,jj) - jk + 1 ) , 1  )  )    ! 0 below ilevel 
     398               zthick(ji,jj) = zthick(ji,jj) + zc 
     399               htc_mld(ji,jj) = htc_mld(ji,jj) + zc * tsn(ji,jj,jk,jp_tem) * tmask(ji,jj,jk) 
     400            END DO 
     401         END DO 
     402      END DO 
     403 
     404      ! Subsequent partial T level 
     405      zthick(:,:) = hmld_zint(:,:) - zthick(:,:)   !   remaining thickness to reach MLD 
     406 
     407      DO jj = 1, jpj 
     408         DO ji = 1, jpi 
     409            htc_mld(ji,jj) = htc_mld(ji,jj) + tsn(ji,jj,ilevel(ji,jj)+1,jp_tem)  &  
     410      &                      * MIN( fse3t(ji,jj,ilevel(ji,jj)+1), zthick(ji,jj) ) * tmask(ji,jj,ilevel(ji,jj)+1) 
     411         END DO 
     412      END DO 
     413 
     414      WRITE(numout,*) 'htc_mld(after) =',htc_mld(2,2) 
     415 
     416      ! Convert to heat content 
     417      zcoef = rau0 * rcp 
     418      htc_mld(:,:) = zcoef * htc_mld(:,:) 
     419 
     420   END SUBROUTINE zdf_mxl_zint_htc 
     421 
     422   SUBROUTINE zdf_mxl_zint( kt ) 
     423      !!---------------------------------------------------------------------- 
     424      !!                  ***  ROUTINE zdf_mxl_zint  *** 
     425      !!  
     426      !! ** Purpose :    
     427      !! 
     428      !! ** Method  :    
     429      !!---------------------------------------------------------------------- 
     430 
     431      INTEGER, INTENT(in) ::   kt   ! ocean time-step index 
     432 
     433      INTEGER :: ios 
     434      INTEGER :: jn 
     435 
     436      INTEGER :: nn_mld_diag = 0    ! number of diagnostics 
     437 
     438      CHARACTER(len=1) :: cmld 
     439 
     440      TYPE(MXL_ZINT) :: sn_mld1, sn_mld2, sn_mld3, sn_mld4, sn_mld5 
     441      TYPE(MXL_ZINT), SAVE, DIMENSION(5) ::   mld_diags 
     442 
     443      NAMELIST/namzdf_mldzint/ nn_mld_diag, sn_mld1, sn_mld2, sn_mld3, sn_mld4, sn_mld5 
     444 
     445      !!---------------------------------------------------------------------- 
     446       
     447      IF( kt == nit000 ) THEN 
     448         REWIND( numnam_ref )              ! Namelist namzdf_mldzint in reference namelist  
     449         READ  ( numnam_ref, namzdf_mldzint, IOSTAT = ios, ERR = 901) 
     450901      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzdf_mldzint in reference namelist', lwp ) 
     451 
     452         REWIND( numnam_cfg )              ! Namelist namzdf_mldzint in configuration namelist  
     453         READ  ( numnam_cfg, namzdf_mldzint, IOSTAT = ios, ERR = 902 ) 
     454902      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzdf_mldzint in configuration namelist', lwp ) 
     455         IF(lwm) WRITE ( numond, namzdf_mldzint ) 
     456 
     457         IF( nn_mld_diag > 5 )   CALL ctl_stop( 'STOP', 'zdf_mxl_ini: Specify no more than 5 MLD definitions' ) 
     458 
     459         mld_diags(1) = sn_mld1 
     460         mld_diags(2) = sn_mld2 
     461         mld_diags(3) = sn_mld3 
     462         mld_diags(4) = sn_mld4 
     463         mld_diags(5) = sn_mld5 
     464 
     465         IF( nn_mld_diag > 0 ) THEN 
     466            WRITE(numout,*) '=============== Vertically-interpolated mixed layer ================' 
     467            WRITE(numout,*) '(Diagnostic number, nn_mld_type, rn_zref, rn_dT_crit, rn_iso_frac)' 
     468            DO jn = 1, nn_mld_diag 
     469               WRITE(numout,*) 'MLD criterion',jn,':' 
     470               WRITE(numout,*) '    nn_mld_type =', mld_diags(jn)%mld_type 
     471               WRITE(numout,*) '    rn_zref ='    , mld_diags(jn)%zref 
     472               WRITE(numout,*) '    rn_dT_crit =' , mld_diags(jn)%dT_crit 
     473               WRITE(numout,*) '    rn_iso_frac =', mld_diags(jn)%iso_frac 
     474            END DO 
     475            WRITE(numout,*) '====================================================================' 
     476         ENDIF 
     477      ENDIF 
     478 
     479      IF( nn_mld_diag > 0 ) THEN 
     480         DO jn = 1, nn_mld_diag 
     481            WRITE(cmld,'(I1)') jn 
     482            IF( iom_use( "mldzint_"//cmld ) .OR. iom_use( "mldhtc_"//cmld ) ) THEN 
     483               CALL zdf_mxl_zint_mld( mld_diags(jn) ) 
     484 
     485               IF( iom_use( "mldzint_"//cmld ) ) THEN 
     486                  CALL iom_put( "mldzint_"//cmld, hmld_zint(:,:) ) 
     487               ENDIF 
     488 
     489               IF( iom_use( "mldhtc_"//cmld ) )  THEN 
     490                  CALL zdf_mxl_zint_htc( kt ) 
     491                  CALL iom_put( "mldhtc_"//cmld , htc_mld(:,:)   ) 
     492               ENDIF 
     493            ENDIF 
     494         END DO 
     495      ENDIF 
     496 
    347497   END SUBROUTINE zdf_mxl_zint 
    348498 
Note: See TracChangeset for help on using the changeset viewer.