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 8239 for branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/limwri.F90 – NEMO

Ignore:
Timestamp:
2017-06-28T17:55:50+02:00 (7 years ago)
Author:
clem
Message:

merge with v3_6_CMIP6_ice_diagnostics@r8238

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/limwri.F90

    r8233 r8239  
    5454      ! 
    5555      INTEGER  ::  ji, jj, jk, jl  ! dummy loop indices 
    56       REAL(wp) ::  z1_365 
    57       REAL(wp) ::  z2da, z2db, ztmp 
     56      REAL(wp) ::  z2da, z2db, ztmp, zrho1, zrho2 
    5857      REAL(wp), POINTER, DIMENSION(:,:,:) ::  zswi2 
    5958      REAL(wp), POINTER, DIMENSION(:,:)   ::  z2d, zswi    ! 2D workspace 
     59      REAL(wp), POINTER, DIMENSION(:,:)   ::  zfb          ! ice freeboard 
     60      REAL(wp), POINTER, DIMENSION(:,:)   ::  zamask, zamask15 ! 15% concentration mask 
     61 
     62      ! Global ice diagnostics (SIMIP) 
     63      REAL(wp) ::  zdiag_area_nh, &   ! area, extent, volume 
     64         &         zdiag_extt_nh, & 
     65         &         zdiag_area_sh, &  
     66         &         zdiag_extt_sh, &  
     67         &         zdiag_volu_nh, &  
     68         &         zdiag_volu_sh  
     69 
    6070      !!------------------------------------------------------------------- 
    6171 
     
    6474      CALL wrk_alloc( jpi,jpj,jpl, zswi2 ) 
    6575      CALL wrk_alloc( jpi,jpj    , z2d, zswi ) 
    66  
     76      CALL wrk_alloc( jpi,jpj    , zfb, zamask, zamask15 ) 
    6777      !----------------------------- 
    6878      ! Mean category values 
    6979      !----------------------------- 
    70       z1_365 = 1._wp / 365._wp 
    7180 
    7281      ! brine volume 
     
    7685      DO jj = 1, jpj 
    7786         DO ji = 1, jpi 
    78             zswi(ji,jj)  = MAX( 0._wp , SIGN( 1._wp , at_i(ji,jj) - epsi06 ) ) 
     87            zswi(ji,jj)      = MAX( 0._wp , SIGN( 1._wp , at_i(ji,jj) - epsi06 ) ) ! 1 if ice, 0 if no ice 
     88            zamask(ji,jj)    = MAX( 0._wp , SIGN( 1._wp , at_i(ji,jj) - 0.05   ) ) ! 1 if 5% ice, 0 if less - required to mask thickness and snow depth 
     89            zamask15(ji,jj)  = MAX( 0._wp , SIGN( 1._wp , at_i(ji,jj) - 0.15   ) ) ! 1 if 15% ice, 0 if less 
    7990         END DO 
    8091      END DO 
     
    119130      IF ( iom_use( "tau_icebfr" ) )    CALL iom_put( "tau_icebfr"  , tau_icebfr             )  ! ice friction with ocean bottom (landfast ice)   
    120131      ! 
    121       IF ( iom_use( "miceage" ) )       CALL iom_put( "miceage"     , om_i * zswi * z1_365   )  ! mean ice age 
    122       IF ( iom_use( "icethic_cea" ) )   CALL iom_put( "icethic_cea" , htm_i * zswi           )  ! ice thickness mean 
    123       IF ( iom_use( "snowthic_cea" ) )  CALL iom_put( "snowthic_cea", htm_s * zswi           )  ! snow thickness mean 
     132      IF ( iom_use( "miceage" ) )       CALL iom_put( "miceage"     , om_i * zswi * zamask15 )  ! mean ice age 
    124133      IF ( iom_use( "micet" ) )         CALL iom_put( "micet"       , ( tm_i  - rt0 ) * zswi )  ! ice mean    temperature 
    125134      IF ( iom_use( "icest" ) )         CALL iom_put( "icest"       , ( tm_su - rt0 ) * zswi )  ! ice surface temperature 
     
    133142      CALL iom_put( "isnowhc"     , et_s  * zswi        )        ! snow total heat content 
    134143      CALL iom_put( "ibrinv"      , bvm_i * zswi * 100. )        ! brine volume 
    135       CALL iom_put( "utau_ice"    , utau_ice            )        ! wind stress over ice along i-axis at I-point 
    136       CALL iom_put( "vtau_ice"    , vtau_ice            )        ! wind stress over ice along j-axis at I-point 
     144      CALL iom_put( "utau_ice"    , utau_ice*zswi       )        ! wind stress over ice along i-axis at I-point 
     145      CALL iom_put( "vtau_ice"    , vtau_ice*zswi       )        ! wind stress over ice along j-axis at I-point 
    137146      CALL iom_put( "snowpre"     , sprecip * 86400.    )        ! snow precipitation  
    138147      CALL iom_put( "micesalt"    , smt_i   * zswi      )        ! mean ice salinity 
    139148 
    140       CALL iom_put( "icestr"      , strength * zswi )    ! ice strength 
    141       CALL iom_put( "idive"       , divu_i * 1.0e8      )    ! divergence 
    142       CALL iom_put( "ishear"      , shear_i * 1.0e8     )    ! shear 
     149      CALL iom_put( "icestr"      , strength * zswi )            ! ice strength 
     150      CALL iom_put( "idive"       , divu_i              )        ! divergence 
     151      CALL iom_put( "ishear"      , shear_i             )        ! shear 
    143152      CALL iom_put( "snowvol"     , vt_s   * zswi       )        ! snow volume 
    144153       
     
    186195      CALL iom_put( "vfxsnw"     , wfx_snw * ztmp       )        ! total snw growth/melt  
    187196      CALL iom_put( "vfxsub"     , wfx_sub * ztmp       )        ! sublimation (snow/ice)  
    188       CALL iom_put( "vfxsub_err" , wfx_err_sub * ztmp   )        ! "excess" of sublimation sent to ocean  
    189        
    190       CALL iom_put( "afxtot"     , afx_tot * rday       )        ! concentration tendency (total) 
    191       CALL iom_put( "afxdyn"     , afx_dyn * rday       )        ! concentration tendency (dynamics) 
    192       CALL iom_put( "afxthd"     , afx_thd * rday       )        ! concentration tendency (thermo) 
     197      CALL iom_put( "vfxsub_err" , wfx_err_sub * ztmp   )        ! "excess" of sublimation sent to ocean       
     198  
     199      CALL iom_put( "afxtot"     , afx_tot              )        ! concentration tendency (total) 
     200      CALL iom_put( "afxdyn"     , afx_dyn              )        ! concentration tendency (dynamics) 
     201      CALL iom_put( "afxthd"     , afx_thd              )        ! concentration tendency (thermo) 
    193202 
    194203      CALL iom_put ('hfxthd'     , hfx_thd(:,:)         )   !   
     
    218227      ! END MV MP 2016 
    219228 
    220        
    221       !-------------------------------- 
    222       ! Output values for each category 
    223       !-------------------------------- 
     229      !---------------------------------- 
     230      ! Output category-dependent fields 
     231      !---------------------------------- 
    224232      IF ( iom_use( "iceconc_cat"  ) )  CALL iom_put( "iceconc_cat"      , a_i   * zswi2   )        ! area for categories 
    225233      IF ( iom_use( "icethic_cat"  ) )  CALL iom_put( "icethic_cat"      , ht_i  * zswi2   )        ! thickness for categories 
     
    231239      IF ( iom_use( "snwtemp_cat"  ) )  CALL iom_put( "snwtemp_cat", ( SUM( t_s(:,:,:,:), dim=3 ) * r1_nlay_s - rt0 ) * zswi2 ) 
    232240      ! ice age 
    233       IF ( iom_use( "iceage_cat"   ) )  CALL iom_put( "iceage_cat" , o_i * zswi2 * z1_365 ) 
     241      IF ( iom_use( "iceage_cat"   ) )  CALL iom_put( "iceage_cat" , o_i * zswi2 )  
    234242      ! brine volume 
    235243      IF ( iom_use( "brinevol_cat" ) )  CALL iom_put( "brinevol_cat", bv_i * 100. * zswi2 ) 
     
    244252      ! END MV MP 2016 
    245253 
     254      !-------------------------------- 
     255      ! Add-ons for SIMIP 
     256      !-------------------------------- 
     257      zrho1 = ( rau0 - rhoic ) / rau0; zrho2 = rhosn / rau0 
     258 
     259      IF  ( iom_use( "icethic"  ) ) CALL iom_put( "icethic"     , htm_i * zamask             )          ! Ice thickness  
     260      IF  ( iom_use( "icepres"  ) ) CALL iom_put( "icepres"     , zswi                       )          ! Ice presence (1 or 0)  
     261      IF  ( iom_use( "snowthic" ) ) CALL iom_put( "snowthic"    , htm_s * zamask             )          ! Snow thickness        
     262      IF  ( iom_use( "icemass"  ) ) CALL iom_put( "icemass"     , rhoic * vt_i(:,:) * zswi   )          ! Ice mass per cell area  
     263      IF  ( iom_use( "snomass"  ) ) CALL iom_put( "snomass"     , rhosn * vt_s(:,:) * zswi   )          ! Snow mass per cell area 
     264      IF  ( iom_use( "icesnt"   ) ) CALL iom_put( "icesnt"      , ( tm_si - rt0 ) * zswi     )          ! Snow-ice interface temperature 
     265      IF  ( iom_use( "icebot"   ) ) CALL iom_put( "icebot"      , ( t_bo  - rt0 ) * zswi     )          ! Ice bottom temperature 
     266      IF  ( iom_use( "icesmass" ) ) CALL iom_put( "icesmass"    , SUM( smv_i, DIM = 3 ) * rhoic * 1.0e-3 * zswi )   ! Mass of salt in sea ice per cell area 
     267      IF  ( iom_use( "icefb"    ) ) THEN 
     268         zfb(:,:) = ( zrho1 * htm_i(:,:) - zrho2 * htm_s(:,:) ) * zswi(:,:)                              
     269         WHERE( zfb < 0._wp ) ;   zfb = 0._wp ;   END WHERE 
     270                                    CALL iom_put( "icefb"       , zfb                        )          ! Ice freeboard 
     271      ENDIF 
     272      IF  ( iom_use( "dmithd"   ) ) CALL iom_put( "dmithd"      , - wfx_bog - wfx_bom - wfx_sum   &     ! Sea-ice mass change from thermodynamics 
     273              &                     - wfx_sni - wfx_opw - wfx_res ) 
     274      IF  ( iom_use( "dmidyn"   ) ) CALL iom_put( "dmidyn"      ,   diag_dmi_dyn             )          ! Sea-ice mass change from dynamics 
     275      IF  ( iom_use( "dmiopw"   ) ) CALL iom_put( "dmiopw"      , - wfx_opw                  )          ! Sea-ice mass change through growth in open water 
     276      IF  ( iom_use( "dmibog"   ) ) CALL iom_put( "dmibog"      , - wfx_bog                  )          ! Sea-ice mass change through basal growth 
     277      IF  ( iom_use( "dmisni"   ) ) CALL iom_put( "dmisni"      , - wfx_sni                  )          ! Sea-ice mass change through snow-to-ice conversion 
     278      IF  ( iom_use( "dmisum"   ) ) CALL iom_put( "dmisum"      , - wfx_sum                  )          ! Sea-ice mass change through surface melting 
     279      IF  ( iom_use( "dmibom"   ) ) CALL iom_put( "dmibom"      , - wfx_bom                  )          ! Sea-ice mass change through bottom melting 
     280 
     281      IF  ( iom_use( "dmtsub"   ) ) CALL iom_put( "dmtsub"      , - wfx_sub                  )          ! Sea-ice mass change through evaporation and sublimation 
     282      IF  ( iom_use( "dmssub"   ) ) CALL iom_put( "dmssub"      , - wfx_snw_sub              )          ! Snow mass change through sublimation 
     283      IF  ( iom_use( "dmisub"   ) ) CALL iom_put( "dmisub"      , - wfx_ice_sub              )          ! Sea-ice mass change through sublimation 
     284 
     285      IF  ( iom_use( "dmsspr"   ) ) CALL iom_put( "dmsspr"      , - wfx_spr                  )          ! Snow mass change through snow fall 
     286      IF  ( iom_use( "dmsssi"   ) ) CALL iom_put( "dmsssi"      ,   wfx_sni*rhosn/rhoic      )          ! Snow mass change through snow-to-ice conversion 
     287 
     288      IF  ( iom_use( "dmsmel"   ) ) CALL iom_put( "dmsmel"      , - wfx_snw_sum              )          ! Snow mass change through melt 
     289      IF  ( iom_use( "dmsdyn"   ) ) CALL iom_put( "dmsdyn"      ,   diag_dms_dyn             )          ! Snow mass change through dynamics 
     290 
     291      IF  ( iom_use( "hfxconbo" ) ) CALL iom_put( "hfxconbo"    ,   diag_fc_bo               )          ! Bottom conduction flux 
     292      IF  ( iom_use( "hfxconsu" ) ) CALL iom_put( "hfxconsu"    ,   diag_fc_su               )          ! Surface conduction flux 
     293 
     294      IF  ( iom_use( "wfxtot"   ) ) CALL iom_put( "wfxtot"      ,   wfx_ice                  )          ! Total freshwater flux from sea ice 
     295      IF  ( iom_use( "wfxsum"   ) ) CALL iom_put( "wfxsum"      ,   wfx_sum                  )          ! Freshwater flux from sea-ice surface 
     296 
     297      IF  ( iom_use( "utau_oi"  ) ) CALL iom_put( "utau_oi"     ,   diag_utau_oi*zswi        )          ! X-component of ocean stress on sea ice 
     298      IF  ( iom_use( "vtau_oi"  ) ) CALL iom_put( "vtau_oi"     ,   diag_vtau_oi*zswi        )          ! Y-component of ocean stress on sea ice 
     299 
     300      IF  ( iom_use( "dssh_dx"  ) ) CALL iom_put( "dssh_dx"     ,   diag_dssh_dx*zswi        )          ! Sea-surface tilt term in force balance (x-component) 
     301      IF  ( iom_use( "dssh_dy"  ) ) CALL iom_put( "dssh_dy"     ,   diag_dssh_dy*zswi        )          ! Sea-surface tilt term in force balance (y-component) 
     302 
     303      IF  ( iom_use( "corstrx"  ) ) CALL iom_put( "corstrx"     ,   diag_corstrx*zswi        )          ! Coriolis force term in force balance (x-component) 
     304      IF  ( iom_use( "corstry"  ) ) CALL iom_put( "corstry"     ,   diag_corstry*zswi        )          ! Coriolis force term in force balance (y-component) 
     305 
     306      IF  ( iom_use( "intstrx"  ) ) CALL iom_put( "intstrx"     ,   diag_intstrx*zswi        )          ! Internal force term in force balance (x-component) 
     307      IF  ( iom_use( "intstry"  ) ) CALL iom_put( "intstry"     ,   diag_intstry*zswi        )          ! Internal force term in force balance (y-component) 
     308 
     309      IF  ( iom_use( "normstr"  ) ) CALL iom_put( "normstr"     ,   diag_sig1   *zswi        )          ! Normal stress 
     310      IF  ( iom_use( "sheastr"  ) ) CALL iom_put( "sheastr"     ,   diag_sig2   *zswi        )          ! Shear stress 
     311 
     312      IF  ( iom_use( "xmtrpice" ) ) CALL iom_put( "xmtrpice"     ,  diag_xmtrp_ice           )          ! X-component of sea-ice mass transport 
     313      IF  ( iom_use( "ymtrpice" ) ) CALL iom_put( "ymtrpice"     ,  diag_ymtrp_ice           )          ! Y-component of sea-ice mass transport 
     314 
     315      IF  ( iom_use( "xmtrpsnw" ) ) CALL iom_put( "xmtrpsnw"     ,  diag_xmtrp_snw           )          ! X-component of snow mass transport 
     316      IF  ( iom_use( "ymtrpsnw" ) ) CALL iom_put( "ymtrpsnw"     ,  diag_ymtrp_snw           )          ! Y-component of snow mass transport 
     317 
     318      IF  ( iom_use( "xatrp"    ) ) CALL iom_put( "xatrp"        ,  diag_xatrp               )          ! X-component of ice area transport 
     319      IF  ( iom_use( "yatrp"    ) ) CALL iom_put( "yatrp"        ,  diag_yatrp               )          ! Y-component of ice area transport 
     320 
     321      !-------------------------------- 
     322      ! Global ice diagnostics (SIMIP) 
     323      !-------------------------------- 
     324 
     325      IF ( iom_use( "NH_icearea" ) .OR. iom_use( "NH_icevolu" ) .OR. iom_use( "NH_iceextt" ) )   THEN   ! NH integrated diagnostics 
     326  
     327         WHERE( fcor > 0._wp ); zswi(:,:) = 1.0e-12 
     328         ELSEWHERE            ; zswi(:,:) = 0. 
     329         END WHERE  
     330 
     331         zdiag_area_nh = glob_sum( at_i(:,:) * zswi(:,:) * e12t(:,:) ) 
     332         zdiag_volu_nh = glob_sum( vt_i(:,:) * zswi(:,:) * e12t(:,:) ) 
     333 
     334         WHERE( fcor > 0._wp .AND. at_i > 0.15 ); zswi(:,:) = 1.0e-12 
     335         ELSEWHERE                              ; zswi(:,:) = 0. 
     336         END WHERE  
     337 
     338         zdiag_extt_nh = glob_sum( zswi(:,:) * e12t(:,:) ) 
     339 
     340         IF ( iom_use( "NH_icearea" ) ) CALL iom_put( "NH_icearea" ,  zdiag_area_nh  ) 
     341         IF ( iom_use( "NH_icevolu" ) ) CALL iom_put( "NH_icevolu" ,  zdiag_volu_nh  ) 
     342         IF ( iom_use( "NH_iceextt" ) ) CALL iom_put( "NH_iceextt" ,  zdiag_extt_nh  ) 
     343 
     344      ENDIF 
     345 
     346      IF ( iom_use( "SH_icearea" ) .OR. iom_use( "SH_icevolu" ) .OR. iom_use( "SH_iceextt" ) )   THEN   ! SH integrated diagnostics 
     347 
     348         WHERE( fcor < 0._wp ); zswi(:,:) = 1.0e-12;  
     349         ELSEWHERE            ; zswi(:,:) = 0. 
     350         END WHERE  
     351 
     352         zdiag_area_sh = glob_sum( at_i(:,:) * zswi(:,:) * e12t(:,:) )  
     353         zdiag_volu_sh = glob_sum( vt_i(:,:) * zswi(:,:) * e12t(:,:) ) 
     354 
     355         WHERE( fcor < 0._wp .AND. at_i > 0.15 ); zswi(:,:) = 1.0e-12 
     356         ELSEWHERE                              ; zswi(:,:) = 0. 
     357         END WHERE  
     358 
     359         zdiag_extt_sh = glob_sum( zswi(:,:) * e12t(:,:) ) 
     360 
     361         IF ( iom_use( "SH_icearea" ) ) CALL iom_put( "SH_icearea", zdiag_area_sh ) 
     362         IF ( iom_use( "SH_icevolu" ) ) CALL iom_put( "SH_icevolu", zdiag_volu_sh ) 
     363         IF ( iom_use( "SH_iceextt" ) ) CALL iom_put( "SH_iceextt", zdiag_extt_sh ) 
     364 
     365      ENDIF  
     366 
    246367      !     !  Create an output files (output.lim.abort.nc) if S < 0 or u > 20 m/s 
    247368      !     IF( kindic < 0 )   CALL lim_wri_state( 'output.abort' ) 
     
    250371      CALL wrk_dealloc( jpi, jpj, jpl, zswi2 ) 
    251372      CALL wrk_dealloc( jpi, jpj     , z2d, zswi ) 
     373      CALL wrk_dealloc( jpi, jpj     , zfb, zamask, zamask15 ) 
    252374 
    253375      IF( nn_timing == 1 )  CALL timing_stop('limwri') 
Note: See TracChangeset for help on using the changeset viewer.