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 12439 for NEMO/branches – NEMO

Changeset 12439 for NEMO/branches


Ignore:
Timestamp:
2020-02-21T15:43:59+01:00 (4 years ago)
Author:
dancopsey
Message:
  • Provide maximum limits to how big ponds can get. If they exceep this they leak water into the ocean.
  • Water going into melt ponds does not affect ice thickness until it leaks inot the ocean.
  • Deep snow on sea ice can cover up the ponds by forming a lid.
Location:
NEMO/branches/UKMO/NEMO_4.0_add_pond_lids_prints
Files:
9 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/UKMO/NEMO_4.0_add_pond_lids_prints/cfgs/SHARED/field_def_nemo-ice.xml

    r12394 r12439  
    224224          <field id="dmisub"       long_name="snow mass change through evaporation or sublimation"     standard_name="surface_snow_sublimation_flux"                                           unit="kg/m2/s" /> 
    225225          <field id="dmisum"       long_name="sea-ice mass change through surface melting"             standard_name="tendency_of_sea_ice_amount_due_to_surface_melting"                       unit="kg/m2/s" /> 
     226          <field id="dmipnd"       long_name="sea-ice mass change through pond overflow"               standard_name="tendency_of_sea_ice_amount_due_to_pond_overflow"                         unit="kg/m2/s" /> 
    226227          <field id="dmibom"       long_name="sea-ice mass change through bottom melting"              standard_name="tendency_of_sea_ice_amount_due_to_basal_melting"                         unit="kg/m2/s" /> 
    227228          <field id="dmsspr"       long_name="snow mass change through snow fall"                      standard_name="snowfall_flux"                                                           unit="kg/m2/s" /> 
     
    396397          <field field_ref="dmisub"           name="sidmassevapsubl"  /> 
    397398          <field field_ref="dmisum"           name="sidmassmelttop"   /> 
     399          <field field_ref="dmipnd"           name="sidmasspondleak"  /> 
    398400          <field field_ref="dmibom"           name="sidmassmeltbot"   /> 
    399401          <field field_ref="dmsspr"           name="sndmasssnf"       /> 
  • NEMO/branches/UKMO/NEMO_4.0_add_pond_lids_prints/src/ICE/ice.F90

    r12379 r12439  
    414414         &      wfx_bog    (jpi,jpj) , wfx_dyn   (jpi,jpj) , wfx_bom(jpi,jpj) , wfx_sum(jpi,jpj) ,           & 
    415415         &      wfx_res    (jpi,jpj) , wfx_sni   (jpi,jpj) , wfx_opw(jpi,jpj) , wfx_spr(jpi,jpj) ,           & 
    416          &      afx_tot    (jpi,jpj) , rn_amax_2d(jpi,jpj),                                                  & 
     416         &      afx_tot    (jpi,jpj) , rn_amax_2d(jpi,jpj) ,                                                 & 
    417417         &      qsb_ice_bot(jpi,jpj) , qlead     (jpi,jpj) ,                                                 & 
    418418         &      sfx_res    (jpi,jpj) , sfx_bri   (jpi,jpj) , sfx_dyn(jpi,jpj) , sfx_sub(jpi,jpj) , sfx_lam(jpi,jpj) ,  & 
  • NEMO/branches/UKMO/NEMO_4.0_add_pond_lids_prints/src/ICE/ice1d.F90

    r12379 r12439  
    111111   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   h_s_1d 
    112112   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   dh_s_tot      !: Snow accretion/ablation        [m] 
    113    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   dh_i_sum      !: Ice surface ablation [m] 
     113   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   dh_i_sum      !: Ice surface ablation into ocean [m] 
     114   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   dh_i_pnd      !: Ice surface adlation into ponds [m] 
     115   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   dh_s_pnd      !: Snow surface adlation into ponds [m] 
    114116   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   dh_i_itm      !: Ice internal ablation [m] 
    115117   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   dh_i_bom      !: Ice bottom ablation  [m] 
     
    130132   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   a_ip_frac_1d  !: 
    131133   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   lh_ip_1d      !: Ice pond lid thickness   [m] 
     134   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   a_pnd_avail_1d !: Fraction of sea ice available for melt ponding 
    132135 
    133136   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   t_s_1d      !: corresponding to the 2D var  t_s 
     
    212215         &      dh_i_sub(jpij) , dh_s_mlt(jpij) , dh_snowice(jpij) , s_i_1d  (jpij) , s_i_new (jpij) ,  & 
    213216         &      a_ip_1d (jpij) , v_ip_1d (jpij) , v_i_1d    (jpij) , v_s_1d  (jpij) , lh_ip_1d(jpij) ,  & 
    214          &      h_ip_1d (jpij) , a_ip_frac_1d(jpij) ,                                                   & 
     217         &      h_ip_1d (jpij) , a_ip_frac_1d(jpij) , dh_i_pnd(jpij) , a_pnd_avail_1d(jpij) ,           & 
    215218         &      sv_i_1d (jpij) , oa_i_1d (jpij) , o_i_1d    (jpij) , STAT=ierr(ii) ) 
    216219      ! 
  • NEMO/branches/UKMO/NEMO_4.0_add_pond_lids_prints/src/ICE/icealb.F90

    r12382 r12439  
    1717   USE phycst         ! physical constants 
    1818   USE dom_oce        ! domain: ocean 
     19   USE icethd_pnd, only: pnd_lid_max, pnd_lid_min 
    1920   ! 
    2021   USE in_out_manager ! I/O manager 
     
    100101      REAL(wp), INTENT(  out), DIMENSION(:,:,:) ::   palb_cs      !  albedo of ice under clear    sky 
    101102      REAL(wp), INTENT(  out), DIMENSION(:,:,:) ::   palb_os      !  albedo of ice under overcast sky 
    102       ! 
    103       REAL(wp), PARAMETER :: pnd_lid_max = 0.015                  !  pond lid thickness above which the ponds disappear from the albedo calculation 
    104       REAL(wp), PARAMETER :: pnd_lid_min = 0.005                  !  pond lid thickness below which the full pond area is used in the albedo calculation 
    105                                                                   ! Note: these two variables are mirrored in sbccpl.F90 (maybe put them in one place...) 
    106103      ! 
    107104      INTEGER  ::   ji, jj, jl                ! dummy loop indices 
  • NEMO/branches/UKMO/NEMO_4.0_add_pond_lids_prints/src/ICE/icethd.F90

    r12379 r12439  
    275275            dh_i_sub  (1:npti) = 0._wp ; dh_i_bog(1:npti) = 0._wp 
    276276            dh_snowice(1:npti) = 0._wp ; dh_s_mlt(1:npti) = 0._wp 
     277            dh_i_pnd  (1:npti) = 0._wp 
     278            dh_s_pnd  (1:npti) = 0._wp 
    277279            !                                       
    278280                              CALL ice_thd_zdf                      ! --- Ice-Snow temperature --- ! 
  • NEMO/branches/UKMO/NEMO_4.0_add_pond_lids_prints/src/ICE/icethd_dh.F90

    r12369 r12439  
    2424   USE lib_mpp        ! MPP library 
    2525   USE lib_fortran    ! fortran utilities (glob_sum + no signed zero) 
     26   USE icethd_pnd, ONLY : a_pnd_avail 
    2627    
    2728   IMPLICIT NONE 
     
    113114      END SELECT 
    114115 
     116      ! Initialise fraction of sea ice available for melt ponding 
     117      DO ji = 1, npti 
     118         a_pnd_avail_1d(ji) = a_pnd_avail * at_i_1d(ji) 
     119      END DO 
     120 
    115121      ! initialize layer thicknesses and enthalpies 
    116122      h_i_old (1:npti,0:nlay_i+1) = 0._wp 
     
    281287               ! updates available heat + thickness 
    282288               dh_s_mlt(ji)    = dh_s_mlt(ji) + zdeltah(ji,jk) 
     289               dh_s_pnd(ji)    = dh_s_pnd(ji) + zdeltah(ji,jk) * a_pnd_avail_1d(ji)                   ! Cumulate surface melt on areas contributing to melt ponds 
    283290               zq_top  (ji)    = MAX( 0._wp , zq_top(ji) + zdeltah(ji,jk) * e_s_1d(ji,jk) ) 
    284291               h_s_1d  (ji)    = MAX( 0._wp , h_s_1d(ji) + zdeltah(ji,jk) ) 
     292               h_i_1d  (ji)    = MAX( 0._wp , h_i_1d(ji) - zdeltah(ji,jk) * a_pnd_avail_1d(ji) * rhos * r1_rhoi )   ! Snow melt trapped in ponds contrbutes to ice thickness 
    285293               zh_s    (ji,jk) = MAX( 0._wp , zh_s(ji,jk) + zdeltah(ji,jk) ) 
    286294               ! 
     
    400408               zq_top(ji)      = MAX( 0._wp , zq_top(ji) - zdeltah(ji,jk) * rhoi * zdE ) ! update available heat 
    401409                
    402                dh_i_sum(ji)   = dh_i_sum(ji) + zdeltah(ji,jk)         ! Cumulate surface melt 
     410               dh_i_sum(ji)   = dh_i_sum(ji) + zdeltah(ji,jk) * (1._wp - a_pnd_avail_1d(ji))         ! Cumulate surface melt on areas not contributing to melt ponds 
     411               dh_i_pnd(ji)   = dh_i_pnd(ji) + zdeltah(ji,jk) * a_pnd_avail_1d(ji)                   ! Cumulate surface melt on areas contributing to melt ponds 
    403412                
    404413               zfmdt          = - rhoi * zdeltah(ji,jk)               ! Recompute mass flux [kg/m2, >0] 
  • NEMO/branches/UKMO/NEMO_4.0_add_pond_lids_prints/src/ICE/icethd_pnd.F90

    r12423 r12439  
    3737   INTEGER, PARAMETER ::   np_pndCST = 1   ! Constant pond scheme 
    3838   INTEGER, PARAMETER ::   np_pndH12 = 2   ! Evolutive pond scheme (Holland et al. 2012) 
     39 
     40   REAL(wp), PUBLIC, PARAMETER :: a_pnd_avail = 0.7_wp   ! Fraction of sea ice available for melt ponding 
     41   REAL(wp), PUBLIC, PARAMETER :: pnd_lid_max = 0.015    !  pond lid thickness above which the ponds disappear from the albedo calculation 
     42   REAL(wp), PUBLIC, PARAMETER :: pnd_lid_min = 0.005    !  pond lid thickness below which the full pond area is used in the albedo calculation 
     43 
     44   REAL(wp), PARAMETER :: snow_lid_min = 0.15  ! Snow thickness above which form a lid of size pnd_lid_min on the melt ponds 
     45   REAL(wp), PARAMETER :: snow_lid_max = 0.25  ! Snow thickness above which form a lid of size pnd_lid_max on the melt ponds 
    3946 
    4047   !! * Substitutions 
     
    135142      REAL(wp) ::   z1_rhow          ! inverse freshwater density 
    136143      REAL(wp) ::   z1_zpnd_aspect   ! inverse pond aspect ratio 
     144      REAL(wp) ::   z1_rhoi          ! inverse ice density 
    137145      REAL(wp) ::   zfac, zdum 
    138146      REAL(wp) ::   t_grad           ! Temperature deficit for refreezing 
     
    140148      REAL(wp) ::   lh_ip_end        ! Lid thickness at end of timestep (temporary variable) 
    141149      REAL(wp) ::   zdh_frz          ! Amount of melt pond that freezes (m) 
     150      REAL(wp) ::   v_ip_old         ! Pond volume before leaking back to the ocean 
     151      REAL(wp) ::   dh_i_pndleak     ! Grid box mean change in water depth due to leaking back to the ocean 
     152      REAL(wp) ::   weighted_lid_snow ! Lid to go on ponds under snow if snow thickness exceeds snow_lid_min 
    142153      ! 
    143154      INTEGER  ::   ji   ! loop indices 
     
    146157      z1_zpnd_aspect = 1._wp / zpnd_aspect 
    147158      z1_Tp          = 1._wp / zTp  
     159      z1_rhoi        = 1._wp / rhoi 
    148160 
    149161      ! Define time-independent field for use in refreezing 
     
    175187            ! This is the change in ice thickness due to melt scaled up by the realive areas of the meltpond 
    176188            ! and the area of sea ice feeding the melt ponds. 
    177             zdh_mlt = -( dh_i_sum(ji)*rhoi + dh_s_mlt(ji)*rhos ) * z1_rhow * (zrmax * a_i_1d(ji)) / a_ip_1d(ji) 
     189            zdh_mlt = -(dh_i_pnd(ji)*rhoi + dh_s_pnd(ji)*rhos) * z1_rhow * a_i_1d(ji) / a_ip_1d(ji) 
    178190            ! 
    179191            !--- Pond gowth ---! 
     
    208220            END IF 
    209221 
    210             ! melt pond mass flux (<0) 
    211             IF( zdh_mlt > 0._wp ) THEN 
    212                zfac = zdh_mlt * zrmax * a_i_1d(ji) * rhow * r1_rdtice 
    213                wfx_pnd_1d(ji) = wfx_pnd_1d(ji) - zfac 
    214                ! 
    215                ! adjust ice/snow melting flux to balance melt pond flux (>0) 
    216                zdum = zfac / ( wfx_snw_sum_1d(ji) + wfx_sum_1d(ji) ) 
    217                wfx_snw_sum_1d(ji) = wfx_snw_sum_1d(ji) * (1._wp + zdum) 
    218                wfx_sum_1d(ji)     = wfx_sum_1d(ji)     * (1._wp + zdum) 
    219             ENDIF 
    220222            ! 
    221223            ! Make sure pond volume or lid thickness has not gone negative 
     
    237239                v_ip_1d(ji)      = 0._wp 
    238240            END IF 
     241 
     242            ! If pond area exceeds a_pnd_avail_1d(ji) * a_i_1d(ji) then reduce the pond volume 
     243            IF ( a_ip_1d(ji) > a_pnd_avail_1d(ji) * a_i_1d(ji) ) THEN 
     244                v_ip_old = v_ip_1d(ji)   ! Save original volume before leak for future use 
     245                h_ip_1d(ji) = zpnd_aspect * a_pnd_avail_1d(ji) 
     246                a_ip_1d(ji) = a_pnd_avail_1d(ji) * a_i_1d(ji) 
     247                v_ip_1d(ji) = h_ip_1d(ji) * a_ip_1d(ji) 
     248                a_ip_frac_1d(ji) = a_ip_1d(ji) / a_i_1d(ji) 
     249 
     250                ! A change in volume of a melt pond is equivalent to a change in water depth in the grid box mean. 
     251                ! Scale this up to make water depth meaned over sea ice. 
     252                dh_i_pndleak = (v_ip_1d(ji) - v_ip_old) / a_i_1d(ji)   ! This will be a negative number 
     253 
     254                ! Output this water loss as a mass flux diagnostic 
     255                wfx_pnd_1d(ji) = wfx_pnd_1d(ji) - rhow * a_i_1d(ji) * dh_i_pndleak * r1_rdtice 
     256 
     257                ! Reduce the ice thickness using densities to convert from a water depth difference to a sea ice thickness difference 
     258                h_i_1d(ji) =  MAX( 0._wp , h_i_1d(ji) + dh_i_pndleak * rhow * z1_rhoi ) 
     259            ENDIF 
     260 
     261            ! If pond depth exceeds half the ice thickness then reduce the pond volume 
     262            IF ( h_ip_1d(ji) > 0.5_wp * h_i_1d(ji) ) THEN 
     263                v_ip_old = v_ip_1d(ji)   ! Save original volume before leak for future use 
     264                h_ip_1d(ji) = 0.5_wp * h_i_1d(ji) 
     265                a_ip_frac_1d(ji) = h_ip_1d(ji) / zpnd_aspect 
     266                a_ip_1d(ji) = a_ip_frac_1d(ji) * a_i_1d(ji) 
     267                v_ip_1d(ji) = h_ip_1d(ji) * a_ip_1d(ji) 
     268 
     269                ! A change in volume of a melt pond is equivalent to a change in water depth in the grid box mean. 
     270                ! Scale this up to make water depth meaned over sea ice. 
     271                dh_i_pndleak = (v_ip_1d(ji) - v_ip_old) / a_i_1d(ji)   ! This will be a negative number 
     272 
     273                ! Output this water loss as a mass flux diagnostic 
     274                wfx_pnd_1d(ji) = wfx_pnd_1d(ji) - rhow * a_i_1d(ji) * dh_i_pndleak * r1_rdtice 
     275 
     276                ! Reduce the ice thickness using densities to convert from a water depth difference to a sea ice thickness difference 
     277                h_i_1d(ji) =  MAX( 0._wp , h_i_1d(ji) + dh_i_pndleak * rhow * z1_rhoi ) 
     278            ENDIF 
     279 
     280            ! If any of the previous two IF tests has removed all the ice thickness then remove ice area. 
     281            IF ( h_i_1d(ji) == 0._wp ) THEN 
     282                a_i_1d(ji) = 0._wp 
     283                h_s_1d(ji) = 0._wp 
     284            ENDIF 
     285 
     286            ! If snow thickness exceeds snow_lid_min then form a very thin lid (so snow can go over the top) 
     287            IF ( h_s_1d(ji) > snow_lid_min .AND. h_s_1d(ji) < snow_lid_max ) THEN 
     288               weighted_lid_snow = (snow_lid_max - h_s_1d(ji))/(snow_lid_max-snow_lid_min) * pnd_lid_min +             & 
     289                                   (h_s_1d(ji) - snow_lid_min)/(snow_lid_max-snow_lid_min) * pnd_lid_max 
     290               lh_ip_1d(ji) = MAX(lh_ip_1d(ji), weighted_lid_snow) 
     291            ENDIF 
     292            IF ( h_s_1d(ji) >= snow_lid_max ) THEN 
     293               lh_ip_1d(ji) = MAX(lh_ip_1d(ji), pnd_lid_max) 
     294            ENDIF 
     295 
    239296            ! 
    240297         ENDIF 
     
    245302            write(numout,*)'icethd_pnd: meltt = ', -( dh_i_sum(ji)*rhoi + dh_s_mlt(ji)*rhos ) / rhoi 
    246303            write(numout,*)'icethd_pnd: lh_ip_1d(ji), zdh_mlt, zdh_frz, t_su_1d(ji) = ',lh_ip_1d(ji), ' ', zdh_mlt, ' ', zdh_frz, ' ', t_su_1d(ji) 
     304            write(numout,*)'icethd_pnd: a_pnd_avail_1d(ji), at_i_1d(ji), wfx_pnd_1d(ji), h_i_1d(ji) = ', a_pnd_avail_1d(ji), ' ', at_i_1d(ji), ' ', wfx_pnd_1d(ji), ' ', h_i_1d(ji) 
    247305         END IF 
    248306 
  • NEMO/branches/UKMO/NEMO_4.0_add_pond_lids_prints/src/ICE/icewri.F90

    r12394 r12439  
    172172      !------------------ 
    173173      ! trends 
    174       IF( iom_use('dmithd') )   CALL iom_put( "dmithd", - wfx_bog - wfx_bom - wfx_sum - wfx_sni - wfx_opw - wfx_lam - wfx_res ) ! Sea-ice mass change from thermodynamics 
     174      IF( iom_use('dmithd') )   CALL iom_put( "dmithd", - wfx_bog - wfx_bom - wfx_sum - wfx_sni - wfx_opw - wfx_lam - wfx_res - wfx_pnd ) ! Sea-ice mass change from thermodynamics 
    175175      IF( iom_use('dmidyn') )   CALL iom_put( "dmidyn", - wfx_dyn + rhoi * diag_trp_vi      )   ! Sea-ice mass change from dynamics(kg/m2/s) 
    176176      IF( iom_use('dmiopw') )   CALL iom_put( "dmiopw", - wfx_opw                           )   ! Sea-ice mass change through growth in open water 
     
    178178      IF( iom_use('dmisni') )   CALL iom_put( "dmisni", - wfx_sni                           )   ! Sea-ice mass change through snow-to-ice conversion 
    179179      IF( iom_use('dmisum') )   CALL iom_put( "dmisum", - wfx_sum                           )   ! Sea-ice mass change through surface melting 
     180      IF( iom_use('dmipnd') )   CALL iom_put( "dmipnd", - wfx_pnd                           )   ! Sea-ice mass change through meltponds overflowing to ocean 
    180181      IF( iom_use('dmibom') )   CALL iom_put( "dmibom", - wfx_bom                           )   ! Sea-ice mass change through bottom melting 
    181182      IF( iom_use('dmtsub') )   CALL iom_put( "dmtsub", - wfx_sub                           )   ! Sea-ice mass change through evaporation and sublimation 
  • NEMO/branches/UKMO/NEMO_4.0_add_pond_lids_prints/src/OCE/SBC/sbccpl.F90

    r12394 r12439  
    2929#if defined key_si3 
    3030   USE ice            ! ice variables 
     31   USE icethd_pnd, only: pnd_lid_max, pnd_lid_min 
    3132#endif 
    3233   USE cpl_oasis3     ! OASIS3 coupling 
     
    21222123      INTEGER, INTENT(in) ::   kt 
    21232124      ! 
    2124       REAL(wp), PARAMETER :: pnd_lid_max = 0.015                  !  pond lid thickness above which the ponds disappear from the albedo calculation 
    2125       REAL(wp), PARAMETER :: pnd_lid_min = 0.005                  !  pond lid thickness below which the full pond area is used in the albedo calculation 
    2126                                                                   ! Note: these two variables are mirrored in icealb.F90 (maybe put them in one place...) 
    21272125      ! 
    21282126      INTEGER ::   ji, jj, jl   ! dummy loop indices 
Note: See TracChangeset for help on using the changeset viewer.