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 13466 for NEMO/branches/2020/temporary_r4_trunk/src/ICE/iceistate.F90 – NEMO

Ignore:
Timestamp:
2020-09-15T09:27:47+02:00 (4 years ago)
Author:
smasson
Message:

r4_trunk: merge r4 13280:13310, see #2523

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/temporary_r4_trunk/src/ICE/iceistate.F90

    r12735 r13466  
    4141   !                             !! ** namelist (namini) ** 
    4242   LOGICAL, PUBLIC  ::   ln_iceini        !: Ice initialization or not 
    43    LOGICAL, PUBLIC  ::   ln_iceini_file   !: Ice initialization from 2D netcdf file 
     43   INTEGER, PUBLIC  ::   nn_iceini_file   !: Ice initialization: 
     44                                  !        0 = Initialise sea ice based on SSTs 
     45                                  !        1 = Initialise sea ice from single category netcdf file 
     46                                  !        2 = Initialise sea ice from multi category restart file 
    4447   REAL(wp) ::   rn_thres_sst 
    4548   REAL(wp) ::   rn_hti_ini_n, rn_hts_ini_n, rn_ati_ini_n, rn_smi_ini_n, rn_tmi_ini_n, rn_tsu_ini_n, rn_tms_ini_n 
    4649   REAL(wp) ::   rn_hti_ini_s, rn_hts_ini_s, rn_ati_ini_s, rn_smi_ini_s, rn_tmi_ini_s, rn_tsu_ini_s, rn_tms_ini_s 
    47    REAL(wp) ::   rn_apd_ini_n, rn_hpd_ini_n 
    48    REAL(wp) ::   rn_apd_ini_s, rn_hpd_ini_s 
     50   REAL(wp) ::   rn_apd_ini_n, rn_hpd_ini_n, rn_hld_ini_n 
     51   REAL(wp) ::   rn_apd_ini_s, rn_hpd_ini_s, rn_hld_ini_s 
    4952   ! 
    50    !                              ! if ln_iceini_file = T 
    51    INTEGER , PARAMETER ::   jpfldi = 9           ! maximum number of files to read 
     53   !                              ! if nn_iceini_file = 1 
     54   INTEGER , PARAMETER ::   jpfldi = 10          ! maximum number of files to read 
    5255   INTEGER , PARAMETER ::   jp_hti = 1           ! index of ice thickness    (m) 
    5356   INTEGER , PARAMETER ::   jp_hts = 2           ! index of snw thickness    (m) 
     
    5962   INTEGER , PARAMETER ::   jp_apd = 8           ! index of pnd fraction     (-) 
    6063   INTEGER , PARAMETER ::   jp_hpd = 9           ! index of pnd depth        (m) 
     64   INTEGER , PARAMETER ::   jp_hld = 10          ! index of pnd lid depth    (m) 
    6165   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   si  ! structure of input fields (file informations, fields read) 
    6266   !    
     
    8185      !! ** Steps   :   1) Set initial surface and basal temperatures 
    8286      !!                2) Recompute or read sea ice state variables 
    83       !!                3) Fill in the ice thickness distribution using gaussian 
    84       !!                4) Fill in space-dependent arrays for state variables 
    85       !!                5) snow-ice mass computation 
    86       !!                6) store before fields 
     87      !!                3) Fill in space-dependent arrays for state variables 
     88      !!                4) snow-ice mass computation 
    8789      !! 
    8890      !! ** Notes   : o_i, t_su, t_s, t_i, sz_i must be filled everywhere, even 
     
    98100      REAL(wp), DIMENSION(jpi,jpj)     ::   zht_i_ini, zat_i_ini, ztm_s_ini            !data from namelist or nc file 
    99101      REAL(wp), DIMENSION(jpi,jpj)     ::   zt_su_ini, zht_s_ini, zsm_i_ini, ztm_i_ini !data from namelist or nc file 
    100       REAL(wp), DIMENSION(jpi,jpj)     ::   zapnd_ini, zhpnd_ini                       !data from namelist or nc file 
     102      REAL(wp), DIMENSION(jpi,jpj)     ::   zapnd_ini, zhpnd_ini, zhlid_ini            !data from namelist or nc file 
    101103      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   zti_3d , zts_3d                            !temporary arrays 
    102104      !! 
    103       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::   zhi_2d, zhs_2d, zai_2d, zti_2d, zts_2d, ztsu_2d, zsi_2d, zaip_2d, zhip_2d 
     105      REAL(wp), DIMENSION(:,:), ALLOCATABLE ::   zhi_2d, zhs_2d, zai_2d, zti_2d, zts_2d, ztsu_2d, zsi_2d, zaip_2d, zhip_2d, zhil_2d 
    104106      !-------------------------------------------------------------------- 
    105107 
     
    155157      a_ip     (:,:,:) = 0._wp 
    156158      v_ip     (:,:,:) = 0._wp 
    157       a_ip_frac(:,:,:) = 0._wp 
     159      v_il     (:,:,:) = 0._wp 
     160      a_ip_eff (:,:,:) = 0._wp 
    158161      h_ip     (:,:,:) = 0._wp 
     162      h_il     (:,:,:) = 0._wp 
    159163      ! 
    160164      ! ice velocities 
     
    167171      IF( ln_iceini ) THEN 
    168172         !                             !---------------! 
    169          IF( ln_iceini_file )THEN      ! Read a file   ! 
     173         IF( nn_iceini_file == 1 )THEN ! Read a file   ! 
    170174            !                          !---------------! 
    171175            WHERE( ff_t(:,:) >= 0._wp )   ;   zswitch(:,:) = 1._wp 
     
    193197               si(jp_tsu)%fnow(:,:,1) = ( rn_tsu_ini_n * zswitch + rn_tsu_ini_s * (1._wp - zswitch) ) * tmask(:,:,1) 
    194198               si(jp_tms)%fnow(:,:,1) = ( rn_tms_ini_n * zswitch + rn_tms_ini_s * (1._wp - zswitch) ) * tmask(:,:,1) 
    195             ELSEIF( TRIM(si(jp_tmi)%clrootname) == 'NOT USED' .AND. TRIM(si(jp_tms)%clrootname) /= 'NOT USED' ) THEN ! if T_s is read and not T_i, set T_i = (T_s + T_freeze)/2 
    196                si(jp_tmi)%fnow(:,:,1) = 0.5_wp * ( si(jp_tms)%fnow(:,:,1) + 271.15 ) 
    197             ELSEIF( TRIM(si(jp_tmi)%clrootname) == 'NOT USED' .AND. TRIM(si(jp_tsu)%clrootname) /= 'NOT USED' ) THEN ! if T_su is read and not T_i, set T_i = (T_su + T_freeze)/2 
    198                si(jp_tmi)%fnow(:,:,1) = 0.5_wp * ( si(jp_tsu)%fnow(:,:,1) + 271.15 ) 
    199             ELSEIF( TRIM(si(jp_tsu)%clrootname) == 'NOT USED' .AND. TRIM(si(jp_tms)%clrootname) /= 'NOT USED' ) THEN ! if T_s is read and not T_su, set T_su = T_s 
    200                si(jp_tsu)%fnow(:,:,1) = si(jp_tms)%fnow(:,:,1) 
    201             ELSEIF( TRIM(si(jp_tsu)%clrootname) == 'NOT USED' .AND. TRIM(si(jp_tmi)%clrootname) /= 'NOT USED' ) THEN ! if T_i is read and not T_su, set T_su = T_i 
    202                si(jp_tsu)%fnow(:,:,1) = si(jp_tmi)%fnow(:,:,1) 
    203             ELSEIF( TRIM(si(jp_tms)%clrootname) == 'NOT USED' .AND. TRIM(si(jp_tsu)%clrootname) /= 'NOT USED' ) THEN ! if T_su is read and not T_s, set T_s = T_su 
    204                si(jp_tms)%fnow(:,:,1) = si(jp_tsu)%fnow(:,:,1) 
    205             ELSEIF( TRIM(si(jp_tms)%clrootname) == 'NOT USED' .AND. TRIM(si(jp_tmi)%clrootname) /= 'NOT USED' ) THEN ! if T_i is read and not T_s, set T_s = T_i 
    206                si(jp_tms)%fnow(:,:,1) = si(jp_tmi)%fnow(:,:,1) 
    207199            ENDIF 
     200            IF( TRIM(si(jp_tmi)%clrootname) == 'NOT USED' .AND. TRIM(si(jp_tms)%clrootname) /= 'NOT USED' ) & ! if T_s is read and not T_i, set T_i = (T_s + T_freeze)/2 
     201               &     si(jp_tmi)%fnow(:,:,1) = 0.5_wp * ( si(jp_tms)%fnow(:,:,1) + 271.15 ) 
     202            IF( TRIM(si(jp_tmi)%clrootname) == 'NOT USED' .AND. TRIM(si(jp_tsu)%clrootname) /= 'NOT USED' ) & ! if T_su is read and not T_i, set T_i = (T_su + T_freeze)/2 
     203               &     si(jp_tmi)%fnow(:,:,1) = 0.5_wp * ( si(jp_tsu)%fnow(:,:,1) + 271.15 ) 
     204            IF( TRIM(si(jp_tsu)%clrootname) == 'NOT USED' .AND. TRIM(si(jp_tms)%clrootname) /= 'NOT USED' ) & ! if T_s is read and not T_su, set T_su = T_s 
     205               &     si(jp_tsu)%fnow(:,:,1) = si(jp_tms)%fnow(:,:,1) 
     206            IF( TRIM(si(jp_tsu)%clrootname) == 'NOT USED' .AND. TRIM(si(jp_tmi)%clrootname) /= 'NOT USED' ) & ! if T_i is read and not T_su, set T_su = T_i 
     207               &     si(jp_tsu)%fnow(:,:,1) = si(jp_tmi)%fnow(:,:,1) 
     208            IF( TRIM(si(jp_tms)%clrootname) == 'NOT USED' .AND. TRIM(si(jp_tsu)%clrootname) /= 'NOT USED' ) & ! if T_su is read and not T_s, set T_s = T_su 
     209               &     si(jp_tms)%fnow(:,:,1) = si(jp_tsu)%fnow(:,:,1) 
     210            IF( TRIM(si(jp_tms)%clrootname) == 'NOT USED' .AND. TRIM(si(jp_tmi)%clrootname) /= 'NOT USED' ) & ! if T_i is read and not T_s, set T_s = T_i 
     211               &     si(jp_tms)%fnow(:,:,1) = si(jp_tmi)%fnow(:,:,1) 
    208212            ! 
    209213            ! pond concentration 
     
    215219            IF( TRIM(si(jp_hpd)%clrootname) == 'NOT USED' ) & 
    216220               &     si(jp_hpd)%fnow(:,:,1) = ( rn_hpd_ini_n * zswitch + rn_hpd_ini_s * (1._wp - zswitch) ) * tmask(:,:,1) 
     221            ! 
     222            ! pond lid depth 
     223            IF( TRIM(si(jp_hld)%clrootname) == 'NOT USED' ) & 
     224               &     si(jp_hld)%fnow(:,:,1) = ( rn_hld_ini_n * zswitch + rn_hld_ini_s * (1._wp - zswitch) ) * tmask(:,:,1) 
    217225            ! 
    218226            zsm_i_ini(:,:) = si(jp_smi)%fnow(:,:,1) * tmask(:,:,1) 
     
    222230            zapnd_ini(:,:) = si(jp_apd)%fnow(:,:,1) * tmask(:,:,1) 
    223231            zhpnd_ini(:,:) = si(jp_hpd)%fnow(:,:,1) * tmask(:,:,1) 
     232            zhlid_ini(:,:) = si(jp_hld)%fnow(:,:,1) * tmask(:,:,1) 
    224233            ! 
    225234            ! change the switch for the following 
     
    246255               zapnd_ini(:,:) = rn_apd_ini_n * zswitch(:,:) * zat_i_ini(:,:) ! rn_apd = pond fraction => rn_apd * a_i = pond conc.  
    247256               zhpnd_ini(:,:) = rn_hpd_ini_n * zswitch(:,:) 
     257               zhlid_ini(:,:) = rn_hld_ini_n * zswitch(:,:) 
    248258            ELSEWHERE 
    249259               zht_i_ini(:,:) = rn_hti_ini_s * zswitch(:,:) 
     
    256266               zapnd_ini(:,:) = rn_apd_ini_s * zswitch(:,:) * zat_i_ini(:,:) ! rn_apd = pond fraction => rn_apd * a_i = pond conc. 
    257267               zhpnd_ini(:,:) = rn_hpd_ini_s * zswitch(:,:) 
     268               zhlid_ini(:,:) = rn_hld_ini_s * zswitch(:,:) 
    258269            END WHERE 
    259270            ! 
     
    264275            zapnd_ini(:,:) = 0._wp 
    265276            zhpnd_ini(:,:) = 0._wp 
     277            zhlid_ini(:,:) = 0._wp 
     278         ENDIF 
     279 
     280         IF ( .NOT.ln_pnd_lids ) THEN 
     281            zhlid_ini(:,:) = 0._wp 
    266282         ENDIF 
    267283          
    268          !-------------! 
    269          ! fill fields ! 
    270          !-------------! 
     284         !----------------! 
     285         ! 3) fill fields ! 
     286         !----------------! 
    271287         ! select ice covered grid points 
    272288         npti = 0 ; nptidx(:) = 0 
     
    290306         CALL tab_2d_1d( npti, nptidx(1:npti), a_ip_1d(1:npti)  , zapnd_ini ) 
    291307         CALL tab_2d_1d( npti, nptidx(1:npti), h_ip_1d(1:npti)  , zhpnd_ini ) 
     308         CALL tab_2d_1d( npti, nptidx(1:npti), h_il_1d(1:npti)  , zhlid_ini ) 
    292309 
    293310         ! allocate temporary arrays 
    294          ALLOCATE( zhi_2d(npti,jpl), zhs_2d(npti,jpl), zai_2d (npti,jpl), & 
    295             &      zti_2d(npti,jpl), zts_2d(npti,jpl), ztsu_2d(npti,jpl), zsi_2d(npti,jpl), zaip_2d(npti,jpl), zhip_2d(npti,jpl) ) 
     311         ALLOCATE( zhi_2d (npti,jpl), zhs_2d (npti,jpl), zai_2d (npti,jpl), & 
     312            &      zti_2d (npti,jpl), zts_2d (npti,jpl), ztsu_2d(npti,jpl), zsi_2d(npti,jpl), & 
     313            &      zaip_2d(npti,jpl), zhip_2d(npti,jpl), zhil_2d(npti,jpl) ) 
    296314          
    297315         ! distribute 1-cat into jpl-cat: (jpi*jpj) -> (jpi*jpj,jpl) 
    298          CALL ice_var_itd( h_i_1d(1:npti)  , h_s_1d(1:npti)  , at_i_1d(1:npti),                                                   & 
    299             &              zhi_2d          , zhs_2d          , zai_2d         ,                                                   & 
    300             &              t_i_1d(1:npti,1), t_s_1d(1:npti,1), t_su_1d(1:npti), s_i_1d(1:npti), a_ip_1d(1:npti), h_ip_1d(1:npti), & 
    301             &              zti_2d          , zts_2d          , ztsu_2d        , zsi_2d        , zaip_2d        , zhip_2d ) 
     316         CALL ice_var_itd( h_i_1d(1:npti)  , h_s_1d(1:npti)  , at_i_1d(1:npti),                  & 
     317            &              zhi_2d          , zhs_2d          , zai_2d         ,                  & 
     318            &              t_i_1d(1:npti,1), t_s_1d(1:npti,1), t_su_1d(1:npti),                  & 
     319            &              s_i_1d(1:npti)  , a_ip_1d(1:npti) , h_ip_1d(1:npti), h_il_1d(1:npti), & 
     320            &              zti_2d          , zts_2d          , ztsu_2d        ,                  & 
     321            &              zsi_2d          , zaip_2d         , zhip_2d        , zhil_2d ) 
    302322 
    303323         ! move to 3D arrays: (jpi*jpj,jpl) -> (jpi,jpj,jpl) 
     
    315335         CALL tab_2d_3d( npti, nptidx(1:npti), zaip_2d  , a_ip   ) 
    316336         CALL tab_2d_3d( npti, nptidx(1:npti), zhip_2d  , h_ip   ) 
     337         CALL tab_2d_3d( npti, nptidx(1:npti), zhil_2d  , h_il   ) 
    317338 
    318339         ! deallocate temporary arrays 
    319340         DEALLOCATE( zhi_2d, zhs_2d, zai_2d , & 
    320             &        zti_2d, zts_2d, ztsu_2d, zsi_2d, zaip_2d, zhip_2d ) 
     341            &        zti_2d, zts_2d, ztsu_2d, zsi_2d, zaip_2d, zhip_2d, zhil_2d ) 
    321342 
    322343         ! calculate extensive and intensive variables 
     
    360381 
    361382         ! Melt ponds 
    362          WHERE( a_i > epsi10 ) 
    363             a_ip_frac(:,:,:) = a_ip(:,:,:) / a_i(:,:,:) 
    364          ELSEWHERE 
    365             a_ip_frac(:,:,:) = 0._wp 
     383         WHERE( a_i > epsi10 )   ;   a_ip_eff(:,:,:) = a_ip(:,:,:) / a_i(:,:,:) 
     384         ELSEWHERE               ;   a_ip_eff(:,:,:) = 0._wp 
    366385         END WHERE 
    367386         v_ip(:,:,:) = h_ip(:,:,:) * a_ip(:,:,:) 
     387         v_il(:,:,:) = h_il(:,:,:) * a_ip(:,:,:) 
    368388           
    369389         ! specific temperatures for coupled runs 
     
    371391         t1_ice(:,:,:) = t_i (:,:,1,:) 
    372392         ! 
     393         ! ice concentration should not exceed amax 
     394         at_i(:,:) = SUM( a_i, dim=3 ) 
     395         DO jl = 1, jpl 
     396            WHERE( at_i(:,:) > rn_amax_2d(:,:) )   a_i(:,:,jl) = a_i(:,:,jl) * rn_amax_2d(:,:) / at_i(:,:) 
     397         END DO 
     398         at_i(:,:) = SUM( a_i, dim=3 ) 
     399         ! 
    373400      ENDIF ! ln_iceini 
    374401      ! 
    375       at_i(:,:) = SUM( a_i, dim=3 ) 
    376       ! 
    377402      !---------------------------------------------- 
    378       ! 3) Snow-ice mass (case ice is fully embedded) 
     403      ! 4) Snow-ice mass (case ice is fully embedded) 
    379404      !---------------------------------------------- 
    380405      snwice_mass  (:,:) = tmask(:,:,1) * SUM( rhos * v_s(:,:,:) + rhoi * v_i(:,:,:), dim=3  )   ! snow+ice mass 
     
    426451         ENDIF 
    427452      ENDIF 
    428        
    429       !------------------------------------ 
    430       ! 4) store fields at before time-step 
    431       !------------------------------------ 
    432       ! it is only necessary for the 1st interpolation by Agrif 
    433       a_i_b  (:,:,:)   = a_i  (:,:,:) 
    434       e_i_b  (:,:,:,:) = e_i  (:,:,:,:) 
    435       v_i_b  (:,:,:)   = v_i  (:,:,:) 
    436       v_s_b  (:,:,:)   = v_s  (:,:,:) 
    437       e_s_b  (:,:,:,:) = e_s  (:,:,:,:) 
    438       sv_i_b (:,:,:)   = sv_i (:,:,:) 
    439       oa_i_b (:,:,:)   = oa_i (:,:,:) 
    440       u_ice_b(:,:)     = u_ice(:,:) 
    441       v_ice_b(:,:)     = v_ice(:,:) 
    442       ! total concentration is needed for Lupkes parameterizations 
    443       at_i_b (:,:)     = at_i (:,:)  
    444453 
    445454!!clem: output of initial state should be written here but it is impossible because 
     
    466475      ! 
    467476      CHARACTER(len=256) ::  cn_dir          ! Root directory for location of ice files 
    468       TYPE(FLD_N)                    ::   sn_hti, sn_hts, sn_ati, sn_smi, sn_tmi, sn_tsu, sn_tms, sn_apd, sn_hpd 
     477      TYPE(FLD_N)                    ::   sn_hti, sn_hts, sn_ati, sn_smi, sn_tmi, sn_tsu, sn_tms, sn_apd, sn_hpd, sn_hld 
    469478      TYPE(FLD_N), DIMENSION(jpfldi) ::   slf_i                 ! array of namelist informations on the fields to read 
    470479      ! 
    471       NAMELIST/namini/ ln_iceini, ln_iceini_file, rn_thres_sst, & 
     480      NAMELIST/namini/ ln_iceini, nn_iceini_file, rn_thres_sst, & 
    472481         &             rn_hti_ini_n, rn_hti_ini_s, rn_hts_ini_n, rn_hts_ini_s, & 
    473482         &             rn_ati_ini_n, rn_ati_ini_s, rn_smi_ini_n, rn_smi_ini_s, & 
    474483         &             rn_tmi_ini_n, rn_tmi_ini_s, rn_tsu_ini_n, rn_tsu_ini_s, rn_tms_ini_n, rn_tms_ini_s, & 
    475          &             rn_apd_ini_n, rn_apd_ini_s, rn_hpd_ini_n, rn_hpd_ini_s, & 
    476          &             sn_hti, sn_hts, sn_ati, sn_tsu, sn_tmi, sn_smi, sn_tms, sn_apd, sn_hpd, cn_dir 
     484         &             rn_apd_ini_n, rn_apd_ini_s, rn_hpd_ini_n, rn_hpd_ini_s, rn_hld_ini_n, rn_hld_ini_s, & 
     485         &             sn_hti, sn_hts, sn_ati, sn_tsu, sn_tmi, sn_smi, sn_tms, sn_apd, sn_hpd, sn_hld, cn_dir 
    477486      !!----------------------------------------------------------------------------- 
    478487      ! 
     
    488497      slf_i(jp_ati) = sn_ati  ;  slf_i(jp_smi) = sn_smi 
    489498      slf_i(jp_tmi) = sn_tmi  ;  slf_i(jp_tsu) = sn_tsu   ;   slf_i(jp_tms) = sn_tms 
    490       slf_i(jp_apd) = sn_apd  ;  slf_i(jp_hpd) = sn_hpd 
     499      slf_i(jp_apd) = sn_apd  ;  slf_i(jp_hpd) = sn_hpd   ;   slf_i(jp_hld) = sn_hld 
    491500      ! 
    492501      IF(lwp) THEN                          ! control print 
     
    496505         WRITE(numout,*) '   Namelist namini:' 
    497506         WRITE(numout,*) '      ice initialization (T) or not (F)                ln_iceini      = ', ln_iceini 
    498          WRITE(numout,*) '      ice initialization from a netcdf file            ln_iceini_file = ', ln_iceini_file 
     507         WRITE(numout,*) '      ice initialization from a netcdf file            nn_iceini_file = ', nn_iceini_file 
    499508         WRITE(numout,*) '      max ocean temp. above Tfreeze with initial ice   rn_thres_sst   = ', rn_thres_sst 
    500          IF( ln_iceini .AND. .NOT.ln_iceini_file ) THEN 
     509         IF( ln_iceini .AND. nn_iceini_file == 0 ) THEN 
    501510            WRITE(numout,*) '      initial snw thickness in the north-south         rn_hts_ini     = ', rn_hts_ini_n,rn_hts_ini_s  
    502511            WRITE(numout,*) '      initial ice thickness in the north-south         rn_hti_ini     = ', rn_hti_ini_n,rn_hti_ini_s 
     
    508517            WRITE(numout,*) '      initial pnd fraction  in the north-south         rn_apd_ini     = ', rn_apd_ini_n,rn_apd_ini_s 
    509518            WRITE(numout,*) '      initial pnd depth     in the north-south         rn_hpd_ini     = ', rn_hpd_ini_n,rn_hpd_ini_s 
     519            WRITE(numout,*) '      initial pnd lid depth in the north-south         rn_hld_ini     = ', rn_hld_ini_n,rn_hld_ini_s 
    510520         ENDIF 
    511521      ENDIF 
    512522      ! 
    513       IF( ln_iceini_file ) THEN                      ! Ice initialization using input file 
     523      IF( nn_iceini_file == 1 ) THEN                      ! Ice initialization using input file 
    514524         ! 
    515525         ! set si structure 
     
    532542         rn_apd_ini_n = 0. ; rn_apd_ini_s = 0. 
    533543         rn_hpd_ini_n = 0. ; rn_hpd_ini_s = 0. 
    534          CALL ctl_warn( 'rn_apd_ini & rn_hpd_ini = 0 when no ponds' ) 
     544         rn_hld_ini_n = 0. ; rn_hld_ini_s = 0. 
     545         CALL ctl_warn( 'rn_apd_ini & rn_hpd_ini = 0 & rn_hld_ini = 0 when no ponds' ) 
     546      ENDIF 
     547      ! 
     548      IF( .NOT.ln_pnd_lids ) THEN 
     549         rn_hld_ini_n = 0. ; rn_hld_ini_s = 0. 
    535550      ENDIF 
    536551      ! 
Note: See TracChangeset for help on using the changeset viewer.