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 13998 for NEMO/branches/2020/dev_r13327_KERNEL-06_2_techene_e3/src/ICE/icethd_pnd.F90 – NEMO

Ignore:
Timestamp:
2020-12-02T14:55:21+01:00 (3 years ago)
Author:
techene
Message:

branch updated with trunk 13787

Location:
NEMO/branches/2020/dev_r13327_KERNEL-06_2_techene_e3
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/dev_r13327_KERNEL-06_2_techene_e3

    • Property svn:externals
      •  

        old new  
        88 
        99# SETTE 
        10 ^/utils/CI/sette@13292        sette 
         10^/utils/CI/sette@13559        sette 
  • NEMO/branches/2020/dev_r13327_KERNEL-06_2_techene_e3/src/ICE/icethd_pnd.F90

    r12489 r13998  
    3535   !                                   ! associated indices: 
    3636   INTEGER, PARAMETER ::   np_pndNO  = 0   ! No pond scheme 
    37    INTEGER, PARAMETER ::   np_pndCST = 1   ! Constant pond scheme 
    38    INTEGER, PARAMETER ::   np_pndH12 = 2   ! Evolutive pond scheme (Holland et al. 2012) 
     37   INTEGER, PARAMETER ::   np_pndCST = 1   ! Constant ice pond scheme 
     38   INTEGER, PARAMETER ::   np_pndLEV = 2   ! Level ice pond scheme 
    3939 
    4040   !!---------------------------------------------------------------------- 
     
    4949      !!               ***  ROUTINE ice_thd_pnd   *** 
    5050      !!                
    51       !! ** Purpose :   change melt pond fraction 
     51      !! ** Purpose :   change melt pond fraction and thickness 
    5252      !!                 
    53       !! ** Method  :   brut force 
    5453      !!------------------------------------------------------------------- 
    5554      ! 
     
    5857      CASE (np_pndCST)   ;   CALL pnd_CST    !==  Constant melt ponds  ==! 
    5958         ! 
    60       CASE (np_pndH12)   ;   CALL pnd_H12    !==  Holland et al 2012 melt ponds  ==! 
     59      CASE (np_pndLEV)   ;   CALL pnd_LEV    !==  Level ice melt ponds  ==! 
    6160         ! 
    6261      END SELECT 
     
    8685         ! 
    8786         IF( a_i_1d(ji) > 0._wp .AND. t_su_1d(ji) >= rt0 ) THEN 
    88             a_ip_frac_1d(ji) = rn_apnd 
    8987            h_ip_1d(ji)      = rn_hpnd     
    90             a_ip_1d(ji)      = a_ip_frac_1d(ji) * a_i_1d(ji) 
     88            a_ip_1d(ji)      = rn_apnd * a_i_1d(ji) 
     89            h_il_1d(ji)      = 0._wp    ! no pond lids whatsoever 
    9190         ELSE 
    92             a_ip_frac_1d(ji) = 0._wp 
    9391            h_ip_1d(ji)      = 0._wp     
    9492            a_ip_1d(ji)      = 0._wp 
     93            h_il_1d(ji)      = 0._wp 
    9594         ENDIF 
    9695         ! 
     
    10099 
    101100 
    102    SUBROUTINE pnd_H12 
    103       !!------------------------------------------------------------------- 
    104       !!                ***  ROUTINE pnd_H12  *** 
    105       !! 
    106       !! ** Purpose    : Compute melt pond evolution 
    107       !! 
    108       !! ** Method     : Empirical method. A fraction of meltwater is accumulated in ponds  
    109       !!                 and sent to ocean when surface is freezing 
    110       !! 
    111       !!                 pond growth:      Vp = Vp + dVmelt 
    112       !!                    with dVmelt = R/rhow * ( rhoi*dh_i + rhos*dh_s ) * a_i 
    113       !!                 pond contraction: Vp = Vp * exp(0.01*MAX(Tp-Tsu,0)/Tp) 
    114       !!                    with Tp = -2degC 
    115       !!   
    116       !! ** Tunable parameters : (no real expertise yet, ideas?) 
     101   SUBROUTINE pnd_LEV 
     102      !!------------------------------------------------------------------- 
     103      !!                ***  ROUTINE pnd_LEV  *** 
     104      !! 
     105      !! ** Purpose : Compute melt pond evolution 
     106      !! 
     107      !! ** Method  : A fraction of meltwater is accumulated in ponds and sent to ocean when surface is freezing 
     108      !!              We  work with volumes and then redistribute changes into thickness and concentration 
     109      !!              assuming linear relationship between the two.  
     110      !! 
     111      !! ** Action  : - pond growth:      Vp = Vp + dVmelt                                          --- from Holland et al 2012 --- 
     112      !!                                     dVmelt = (1-r)/rhow * ( rhoi*dh_i + rhos*dh_s ) * a_i 
     113      !!                                        dh_i  = meltwater from ice surface melt 
     114      !!                                        dh_s  = meltwater from snow melt 
     115      !!                                        (1-r) = fraction of melt water that is not flushed 
     116      !! 
     117      !!              - limtations:       a_ip must not exceed (1-r)*a_i 
     118      !!                                  h_ip must not exceed 0.5*h_i 
     119      !! 
     120      !!              - pond shrinking: 
     121      !!                       if lids:   Vp = Vp -dH * a_ip 
     122      !!                                     dH = lid thickness change. Retrieved from this eq.:    --- from Flocco et al 2010 --- 
     123      !! 
     124      !!                                                                   rhoi * Lf * dH/dt = ki * MAX(Tp-Tsu,0) / H  
     125      !!                                                                      H = lid thickness 
     126      !!                                                                      Lf = latent heat of fusion 
     127      !!                                                                      Tp = -2C 
     128      !! 
     129      !!                                                                And solved implicitely as: 
     130      !!                                                                   H(t+dt)**2 -H(t) * H(t+dt) -ki * (Tp-Tsu) * dt / (rhoi*Lf) = 0 
     131      !! 
     132      !!                    if no lids:   Vp = Vp * exp(0.01*MAX(Tp-Tsu,0)/Tp)                      --- from Holland et al 2012 --- 
     133      !! 
     134      !!              - Flushing:         w = -perm/visc * rho_oce * grav * Hp / Hi                 --- from Flocco et al 2007 --- 
     135      !!                                     perm = permability of sea-ice 
     136      !!                                     visc = water viscosity 
     137      !!                                     Hp   = height of top of the pond above sea-level 
     138      !!                                     Hi   = ice thickness thru which there is flushing 
     139      !! 
     140      !!              - Corrections:      remove melt ponds when lid thickness is 10 times the pond thickness 
     141      !! 
     142      !!              - pond thickness and area is retrieved from pond volume assuming a linear relationship between h_ip and a_ip: 
     143      !!                                  a_ip/a_i = a_ip_frac = h_ip / zaspect 
     144      !! 
     145      !! ** Tunable parameters : ln_pnd_lids, rn_apnd_max, rn_apnd_min 
    117146      !!  
    118       !! ** Note       : Stolen from CICE for quick test of the melt pond 
    119       !!                 radiation and freshwater interfaces 
    120       !!                 Coupling can be radiative AND freshwater 
    121       !!                 Advection, ridging, rafting are called 
    122       !! 
    123       !! ** References : Holland, M. M. et al (J Clim 2012) 
    124       !!------------------------------------------------------------------- 
    125       REAL(wp), PARAMETER ::   zrmin       = 0.15_wp  ! minimum fraction of available meltwater retained for melt ponding 
    126       REAL(wp), PARAMETER ::   zrmax       = 0.70_wp  ! maximum     -           -         -         -            - 
    127       REAL(wp), PARAMETER ::   zpnd_aspect = 0.8_wp   ! pond aspect ratio 
    128       REAL(wp), PARAMETER ::   zTp         = -2._wp   ! reference temperature 
    129       ! 
    130       REAL(wp) ::   zfr_mlt          ! fraction of available meltwater retained for melt ponding 
    131       REAL(wp) ::   zdv_mlt          ! available meltwater for melt ponding 
    132       REAL(wp) ::   z1_Tp            ! inverse reference temperature 
    133       REAL(wp) ::   z1_rhow          ! inverse freshwater density 
    134       REAL(wp) ::   z1_zpnd_aspect   ! inverse pond aspect ratio 
    135       REAL(wp) ::   zfac, zdum 
    136       ! 
    137       INTEGER  ::   ji   ! loop indices 
    138       !!------------------------------------------------------------------- 
    139       z1_rhow        = 1._wp / rhow  
    140       z1_zpnd_aspect = 1._wp / zpnd_aspect 
    141       z1_Tp          = 1._wp / zTp  
     147      !! ** Note       :   mostly stolen from CICE 
     148      !! 
     149      !! ** References :   Flocco and Feltham (JGR, 2007) 
     150      !!                   Flocco et al       (JGR, 2010) 
     151      !!                   Holland et al      (J. Clim, 2012) 
     152      !!------------------------------------------------------------------- 
     153      REAL(wp), DIMENSION(nlay_i) ::   ztmp           ! temporary array 
     154      !! 
     155      REAL(wp), PARAMETER ::   zaspect =  0.8_wp      ! pond aspect ratio 
     156      REAL(wp), PARAMETER ::   zTp     = -2._wp       ! reference temperature 
     157      REAL(wp), PARAMETER ::   zvisc   =  1.79e-3_wp  ! water viscosity 
     158      !! 
     159      REAL(wp) ::   zfr_mlt, zdv_mlt                  ! fraction and volume of available meltwater retained for melt ponding 
     160      REAL(wp) ::   zdv_frz, zdv_flush                ! Amount of melt pond that freezes, flushes 
     161      REAL(wp) ::   zhp                               ! heigh of top of pond lid wrt ssh 
     162      REAL(wp) ::   zv_ip_max                         ! max pond volume allowed 
     163      REAL(wp) ::   zdT                               ! zTp-t_su 
     164      REAL(wp) ::   zsbr                              ! Brine salinity 
     165      REAL(wp) ::   zperm                             ! permeability of sea ice 
     166      REAL(wp) ::   zfac, zdum                        ! temporary arrays 
     167      REAL(wp) ::   z1_rhow, z1_aspect, z1_Tp         ! inverse 
     168      !! 
     169      INTEGER  ::   ji, jk                            ! loop indices 
     170      !!------------------------------------------------------------------- 
     171      z1_rhow   = 1._wp / rhow  
     172      z1_aspect = 1._wp / zaspect 
     173      z1_Tp     = 1._wp / zTp  
    142174 
    143175      DO ji = 1, npti 
    144          !                                                        !--------------------------------! 
    145          IF( h_i_1d(ji) < rn_himin) THEN                          ! Case ice thickness < rn_himin ! 
    146             !                                                     !--------------------------------! 
    147             !--- Remove ponds on thin ice 
     176         !                                                            !----------------------------------------------------! 
     177         IF( h_i_1d(ji) < rn_himin .OR. a_i_1d(ji) < epsi10 ) THEN    ! Case ice thickness < rn_himin or tiny ice fraction ! 
     178            !                                                         !----------------------------------------------------! 
     179            !--- Remove ponds on thin ice or tiny ice fractions 
    148180            a_ip_1d(ji)      = 0._wp 
    149             a_ip_frac_1d(ji) = 0._wp 
    150181            h_ip_1d(ji)      = 0._wp 
    151             !                                                     !--------------------------------! 
    152          ELSE                                                     ! Case ice thickness >= rn_himin ! 
    153             !                                                     !--------------------------------! 
    154             v_ip_1d(ji) = h_ip_1d(ji) * a_ip_1d(ji)   ! record pond volume at previous time step 
    155             ! 
    156             ! available meltwater for melt ponding [m, >0] and fraction 
    157             zdv_mlt = -( dh_i_sum(ji)*rhoi + dh_s_mlt(ji)*rhos ) * z1_rhow * a_i_1d(ji) 
    158             zfr_mlt = zrmin + ( zrmax - zrmin ) * a_i_1d(ji)  ! from CICE doc 
    159             !zfr_mlt = zrmin + zrmax * a_i_1d(ji)             ! from Holland paper  
    160             ! 
    161             !--- Pond gowth ---! 
    162             ! v_ip should never be negative, otherwise code crashes 
    163             v_ip_1d(ji) = MAX( 0._wp, v_ip_1d(ji) + zfr_mlt * zdv_mlt ) 
    164             ! 
    165             ! melt pond mass flux (<0) 
     182            h_il_1d(ji)      = 0._wp 
     183            !                                                         !--------------------------------! 
     184         ELSE                                                         ! Case ice thickness >= rn_himin ! 
     185            !                                                         !--------------------------------! 
     186            v_ip_1d(ji) = h_ip_1d(ji) * a_ip_1d(ji)   ! retrieve volume from thickness 
     187            v_il_1d(ji) = h_il_1d(ji) * a_ip_1d(ji) 
     188            ! 
     189            !------------------! 
     190            ! case ice melting ! 
     191            !------------------! 
     192            ! 
     193            !--- available meltwater for melt ponding ---! 
     194            zdum    = -( dh_i_sum(ji)*rhoi + dh_s_mlt(ji)*rhos ) * z1_rhow * a_i_1d(ji) 
     195            zfr_mlt = rn_apnd_min + ( rn_apnd_max - rn_apnd_min ) * at_i_1d(ji) !  = ( 1 - r ) = fraction of melt water that is not flushed 
     196            zdv_mlt = MAX( 0._wp, zfr_mlt * zdum ) ! max for roundoff errors?  
     197            ! 
     198            !--- overflow ---! 
     199            ! If pond area exceeds zfr_mlt * a_i_1d(ji) then reduce the pond volume 
     200            !    a_ip_max = zfr_mlt * a_i 
     201            !    => from zaspect = h_ip / (a_ip / a_i), set v_ip_max as:  
     202            zv_ip_max = zfr_mlt**2 * a_i_1d(ji) * zaspect 
     203            zdv_mlt = MAX( 0._wp, MIN( zdv_mlt, zv_ip_max - v_ip_1d(ji) ) ) 
     204 
     205            ! If pond depth exceeds half the ice thickness then reduce the pond volume 
     206            !    h_ip_max = 0.5 * h_i 
     207            !    => from zaspect = h_ip / (a_ip / a_i), set v_ip_max as:  
     208            zv_ip_max = z1_aspect * a_i_1d(ji) * 0.25 * h_i_1d(ji) * h_i_1d(ji) 
     209            zdv_mlt = MAX( 0._wp, MIN( zdv_mlt, zv_ip_max - v_ip_1d(ji) ) ) 
     210             
     211            !--- Pond growing ---! 
     212            v_ip_1d(ji) = v_ip_1d(ji) + zdv_mlt 
     213            ! 
     214            !--- Lid melting ---! 
     215            IF( ln_pnd_lids )   v_il_1d(ji) = MAX( 0._wp, v_il_1d(ji) - zdv_mlt ) ! must be bounded by 0 
     216            ! 
     217            !--- mass flux ---! 
    166218            IF( zdv_mlt > 0._wp ) THEN 
    167                zfac = zfr_mlt * zdv_mlt * rhow * r1_Dt_ice 
     219               zfac = zdv_mlt * rhow * r1_Dt_ice                        ! melt pond mass flux < 0 [kg.m-2.s-1] 
    168220               wfx_pnd_1d(ji) = wfx_pnd_1d(ji) - zfac 
    169221               ! 
    170                ! adjust ice/snow melting flux to balance melt pond flux (>0) 
    171                zdum = zfac / ( wfx_snw_sum_1d(ji) + wfx_sum_1d(ji) ) 
     222               zdum = zfac / ( wfx_snw_sum_1d(ji) + wfx_sum_1d(ji) )    ! adjust ice/snow melting flux > 0 to balance melt pond flux 
    172223               wfx_snw_sum_1d(ji) = wfx_snw_sum_1d(ji) * (1._wp + zdum) 
    173224               wfx_sum_1d(ji)     = wfx_sum_1d(ji)     * (1._wp + zdum) 
    174225            ENDIF 
     226 
     227            !-------------------! 
     228            ! case ice freezing ! i.e. t_su_1d(ji) < (zTp+rt0) 
     229            !-------------------! 
     230            ! 
     231            zdT = MAX( zTp+rt0 - t_su_1d(ji), 0._wp ) 
    175232            ! 
    176233            !--- Pond contraction (due to refreezing) ---! 
    177             v_ip_1d(ji) = v_ip_1d(ji) * EXP( 0.01_wp * MAX( zTp+rt0 - t_su_1d(ji), 0._wp ) * z1_Tp ) 
    178             ! 
    179             ! Set new pond area and depth assuming linear relation between h_ip and a_ip_frac 
    180             !    h_ip = zpnd_aspect * a_ip_frac = zpnd_aspect * a_ip/a_i 
    181             a_ip_1d(ji)      = SQRT( v_ip_1d(ji) * z1_zpnd_aspect * a_i_1d(ji) ) 
    182             a_ip_frac_1d(ji) = a_ip_1d(ji) / a_i_1d(ji) 
    183             h_ip_1d(ji)      = zpnd_aspect * a_ip_frac_1d(ji) 
     234            IF( ln_pnd_lids ) THEN 
     235               ! 
     236               !--- Lid growing and subsequent pond shrinking ---!  
     237               zdv_frz = 0.5_wp * MAX( 0._wp, -v_il_1d(ji) + & ! Flocco 2010 (eq. 5) solved implicitly as aH**2 + bH + c = 0 
     238                  &                    SQRT( v_il_1d(ji)**2 + a_ip_1d(ji)**2 * 4._wp * rcnd_i * zdT * rdt_ice / (rLfus * rhow) ) ) ! max for roundoff errors 
     239                
     240               ! Lid growing 
     241               v_il_1d(ji) = MAX( 0._wp, v_il_1d(ji) + zdv_frz ) 
     242                
     243               ! Pond shrinking 
     244               v_ip_1d(ji) = MAX( 0._wp, v_ip_1d(ji) - zdv_frz ) 
     245 
     246            ELSE 
     247               ! Pond shrinking 
     248               v_ip_1d(ji) = v_ip_1d(ji) * EXP( 0.01_wp * zdT * z1_Tp ) ! Holland 2012 (eq. 6) 
     249            ENDIF 
     250            ! 
     251            !--- Set new pond area and depth ---! assuming linear relation between h_ip and a_ip_frac 
     252            ! v_ip     = h_ip * a_ip 
     253            ! a_ip/a_i = a_ip_frac = h_ip / zaspect (cf Holland 2012, fitting SHEBA so that knowing v_ip we can distribute it to a_ip and h_ip) 
     254            a_ip_1d(ji)      = MIN( a_i_1d(ji), SQRT( v_ip_1d(ji) * z1_aspect * a_i_1d(ji) ) ) ! make sure a_ip < a_i 
     255            h_ip_1d(ji)      = zaspect * a_ip_1d(ji) / a_i_1d(ji) 
     256 
     257            !---------------!             
     258            ! Pond flushing ! 
     259            !---------------! 
     260            ! height of top of the pond above sea-level 
     261            zhp = ( h_i_1d(ji) * ( rho0 - rhoi ) + h_ip_1d(ji) * ( rho0 - rhow * a_ip_1d(ji) / a_i_1d(ji) ) ) * r1_rho0 
     262             
     263            ! Calculate the permeability of the ice (Assur 1958, see Flocco 2010) 
     264            DO jk = 1, nlay_i 
     265               zsbr = - 1.2_wp                                  & 
     266                  &   - 21.8_wp    * ( t_i_1d(ji,jk) - rt0 )    & 
     267                  &   - 0.919_wp   * ( t_i_1d(ji,jk) - rt0 )**2 & 
     268                  &   - 0.0178_wp  * ( t_i_1d(ji,jk) - rt0 )**3 
     269               ztmp(jk) = sz_i_1d(ji,jk) / zsbr 
     270            END DO 
     271            zperm = MAX( 0._wp, 3.e-08_wp * MINVAL(ztmp)**3 ) 
     272             
     273            ! Do the drainage using Darcy's law 
     274            zdv_flush   = -zperm * rho0 * grav * zhp * rdt_ice / (zvisc * h_i_1d(ji)) * a_ip_1d(ji) 
     275            zdv_flush   = MAX( zdv_flush, -v_ip_1d(ji) ) 
     276            v_ip_1d(ji) = v_ip_1d(ji) + zdv_flush 
     277             
     278            !--- Set new pond area and depth ---! assuming linear relation between h_ip and a_ip_frac 
     279            a_ip_1d(ji)      = MIN( a_i_1d(ji), SQRT( v_ip_1d(ji) * z1_aspect * a_i_1d(ji) ) ) ! make sure a_ip < a_i 
     280            h_ip_1d(ji)      = zaspect * a_ip_1d(ji) / a_i_1d(ji) 
     281 
     282            !--- Corrections and lid thickness ---! 
     283            IF( ln_pnd_lids ) THEN 
     284               !--- retrieve lid thickness from volume ---! 
     285               IF( a_ip_1d(ji) > epsi10 ) THEN   ;   h_il_1d(ji) = v_il_1d(ji) / a_ip_1d(ji) 
     286               ELSE                              ;   h_il_1d(ji) = 0._wp 
     287               ENDIF 
     288               !--- remove ponds if lids are much larger than ponds ---! 
     289               IF ( h_il_1d(ji) > h_ip_1d(ji) * 10._wp ) THEN 
     290                  a_ip_1d(ji)      = 0._wp 
     291                  h_ip_1d(ji)      = 0._wp 
     292                  h_il_1d(ji)      = 0._wp 
     293               ENDIF 
     294            ENDIF 
    184295            ! 
    185296         ENDIF 
     297          
    186298      END DO 
    187299      ! 
    188    END SUBROUTINE pnd_H12 
     300   END SUBROUTINE pnd_LEV 
    189301 
    190302 
     
    203315      INTEGER  ::   ios, ioptio   ! Local integer 
    204316      !! 
    205       NAMELIST/namthd_pnd/  ln_pnd, ln_pnd_H12, ln_pnd_CST, rn_apnd, rn_hpnd, ln_pnd_alb 
     317      NAMELIST/namthd_pnd/  ln_pnd, ln_pnd_LEV , rn_apnd_min, rn_apnd_max, & 
     318         &                          ln_pnd_CST , rn_apnd, rn_hpnd,         & 
     319         &                          ln_pnd_lids, ln_pnd_alb 
    206320      !!------------------------------------------------------------------- 
    207321      ! 
     
    217331         WRITE(numout,*) '~~~~~~~~~~~~~~~~' 
    218332         WRITE(numout,*) '   Namelist namicethd_pnd:' 
    219          WRITE(numout,*) '      Melt ponds activated or not                                     ln_pnd     = ', ln_pnd 
    220          WRITE(numout,*) '         Evolutive  melt pond fraction and depth (Holland et al 2012) ln_pnd_H12 = ', ln_pnd_H12 
    221          WRITE(numout,*) '         Prescribed melt pond fraction and depth                      ln_pnd_CST = ', ln_pnd_CST 
    222          WRITE(numout,*) '            Prescribed pond fraction                                  rn_apnd    = ', rn_apnd 
    223          WRITE(numout,*) '            Prescribed pond depth                                     rn_hpnd    = ', rn_hpnd 
    224          WRITE(numout,*) '         Melt ponds affect albedo or not                              ln_pnd_alb = ', ln_pnd_alb 
     333         WRITE(numout,*) '      Melt ponds activated or not                                 ln_pnd       = ', ln_pnd 
     334         WRITE(numout,*) '         Level ice melt pond scheme                               ln_pnd_LEV   = ', ln_pnd_LEV 
     335         WRITE(numout,*) '            Minimum ice fraction that contributes to melt ponds   rn_apnd_min  = ', rn_apnd_min 
     336         WRITE(numout,*) '            Maximum ice fraction that contributes to melt ponds   rn_apnd_max  = ', rn_apnd_max 
     337         WRITE(numout,*) '         Constant ice melt pond scheme                            ln_pnd_CST   = ', ln_pnd_CST 
     338         WRITE(numout,*) '            Prescribed pond fraction                              rn_apnd      = ', rn_apnd 
     339         WRITE(numout,*) '            Prescribed pond depth                                 rn_hpnd      = ', rn_hpnd 
     340         WRITE(numout,*) '         Frozen lids on top of melt ponds                         ln_pnd_lids  = ', ln_pnd_lids 
     341         WRITE(numout,*) '         Melt ponds affect albedo or not                          ln_pnd_alb   = ', ln_pnd_alb 
    225342      ENDIF 
    226343      ! 
     
    229346      IF( .NOT.ln_pnd ) THEN   ;   ioptio = ioptio + 1   ;   nice_pnd = np_pndNO     ;   ENDIF 
    230347      IF( ln_pnd_CST  ) THEN   ;   ioptio = ioptio + 1   ;   nice_pnd = np_pndCST    ;   ENDIF 
    231       IF( ln_pnd_H12  ) THEN   ;   ioptio = ioptio + 1   ;   nice_pnd = np_pndH12    ;   ENDIF 
     348      IF( ln_pnd_LEV  ) THEN   ;   ioptio = ioptio + 1   ;   nice_pnd = np_pndLEV    ;   ENDIF 
    232349      IF( ioptio /= 1 )   & 
    233          & CALL ctl_stop( 'ice_thd_pnd_init: choose either none (ln_pnd=F) or only one pond scheme (ln_pnd_H12 or ln_pnd_CST)' ) 
     350         & CALL ctl_stop( 'ice_thd_pnd_init: choose either none (ln_pnd=F) or only one pond scheme (ln_pnd_LEV or ln_pnd_CST)' ) 
    234351      ! 
    235352      SELECT CASE( nice_pnd ) 
    236353      CASE( np_pndNO )          
    237          IF( ln_pnd_alb ) THEN ; ln_pnd_alb = .FALSE. ; CALL ctl_warn( 'ln_pnd_alb=false when no ponds' ) ; ENDIF 
     354         IF( ln_pnd_alb  ) THEN ; ln_pnd_alb  = .FALSE. ; CALL ctl_warn( 'ln_pnd_alb=false when no ponds' )  ; ENDIF 
     355         IF( ln_pnd_lids ) THEN ; ln_pnd_lids = .FALSE. ; CALL ctl_warn( 'ln_pnd_lids=false when no ponds' ) ; ENDIF 
     356      CASE( np_pndCST )          
     357         IF( ln_pnd_lids ) THEN ; ln_pnd_lids = .FALSE. ; CALL ctl_warn( 'ln_pnd_lids=false when constant ponds' ) ; ENDIF 
    238358      END SELECT 
    239359      ! 
Note: See TracChangeset for help on using the changeset viewer.