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 13472 for NEMO/trunk/src/ICE/iceistate.F90 – NEMO

Ignore:
Timestamp:
2020-09-16T15:05:19+02:00 (4 years ago)
Author:
smasson
Message:

trunk: commit changes from r4.0-HEAD from 13284 to 13449, see #2523

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/trunk/src/ICE/iceistate.F90

    r13429 r13472  
    4747   !                             !! ** namelist (namini) ** 
    4848   LOGICAL, PUBLIC  ::   ln_iceini        !: Ice initialization or not 
    49    LOGICAL, PUBLIC  ::   ln_iceini_file   !: Ice initialization from 2D netcdf file 
     49   INTEGER, PUBLIC  ::   nn_iceini_file   !: Ice initialization: 
     50                                  !        0 = Initialise sea ice based on SSTs 
     51                                  !        1 = Initialise sea ice from single category netcdf file 
     52                                  !        2 = Initialise sea ice from multi category restart file 
    5053   REAL(wp) ::   rn_thres_sst 
    5154   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 
    5255   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 
    53    REAL(wp) ::   rn_apd_ini_n, rn_hpd_ini_n 
    54    REAL(wp) ::   rn_apd_ini_s, rn_hpd_ini_s 
     56   REAL(wp) ::   rn_apd_ini_n, rn_hpd_ini_n, rn_hld_ini_n 
     57   REAL(wp) ::   rn_apd_ini_s, rn_hpd_ini_s, rn_hld_ini_s 
    5558   ! 
    56    !                              ! if ln_iceini_file = T 
    57    INTEGER , PARAMETER ::   jpfldi = 9           ! maximum number of files to read 
     59   !                              ! if nn_iceini_file = 1 
     60   INTEGER , PARAMETER ::   jpfldi = 10          ! maximum number of files to read 
    5861   INTEGER , PARAMETER ::   jp_hti = 1           ! index of ice thickness    (m) 
    5962   INTEGER , PARAMETER ::   jp_hts = 2           ! index of snw thickness    (m) 
     
    6568   INTEGER , PARAMETER ::   jp_apd = 8           ! index of pnd fraction     (-) 
    6669   INTEGER , PARAMETER ::   jp_hpd = 9           ! index of pnd depth        (m) 
     70   INTEGER , PARAMETER ::   jp_hld = 10          ! index of pnd lid depth    (m) 
    6771   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   si  ! structure of input fields (file informations, fields read) 
    6872 
     
    8993      !! ** Steps   :   1) Set initial surface and basal temperatures 
    9094      !!                2) Recompute or read sea ice state variables 
    91       !!                3) Fill in the ice thickness distribution using gaussian 
    92       !!                4) Fill in space-dependent arrays for state variables 
    93       !!                5) snow-ice mass computation 
    94       !!                6) store before fields 
     95      !!                3) Fill in space-dependent arrays for state variables 
     96      !!                4) snow-ice mass computation 
    9597      !! 
    9698      !! ** Notes   : o_i, t_su, t_s, t_i, sz_i must be filled everywhere, even 
     
    107109      REAL(wp), DIMENSION(jpi,jpj)     ::   zht_i_ini, zat_i_ini, ztm_s_ini            !data from namelist or nc file 
    108110      REAL(wp), DIMENSION(jpi,jpj)     ::   zt_su_ini, zht_s_ini, zsm_i_ini, ztm_i_ini !data from namelist or nc file 
    109       REAL(wp), DIMENSION(jpi,jpj)     ::   zapnd_ini, zhpnd_ini                       !data from namelist or nc file 
    110       REAL(wp), DIMENSION(jpi,jpj,jpl) ::   zti_3d , zts_3d                            !locak arrays 
    111       !! 
    112       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::   zhi_2d, zhs_2d, zai_2d, zti_2d, zts_2d, ztsu_2d, zsi_2d, zaip_2d, zhip_2d 
     111      REAL(wp), DIMENSION(jpi,jpj)     ::   zapnd_ini, zhpnd_ini, zhlid_ini            !data from namelist or nc file 
     112      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   zti_3d , zts_3d                            !temporary arrays 
     113      !! 
     114      REAL(wp), DIMENSION(:,:), ALLOCATABLE ::   zhi_2d, zhs_2d, zai_2d, zti_2d, zts_2d, ztsu_2d, zsi_2d, zaip_2d, zhip_2d, zhil_2d 
    113115      !-------------------------------------------------------------------- 
    114116 
     
    164166      a_ip     (:,:,:) = 0._wp 
    165167      v_ip     (:,:,:) = 0._wp 
    166       a_ip_frac(:,:,:) = 0._wp 
     168      v_il     (:,:,:) = 0._wp 
     169      a_ip_eff (:,:,:) = 0._wp 
    167170      h_ip     (:,:,:) = 0._wp 
     171      h_il     (:,:,:) = 0._wp 
    168172      ! 
    169173      ! ice velocities 
     
    174178      ! 2) overwrite some of the fields with namelist parameters or netcdf file 
    175179      !------------------------------------------------------------------------ 
    176  
    177  
    178180      IF( ln_iceini ) THEN 
    179          !                             !---------------! 
    180           
     181         ! 
    181182         IF( Agrif_Root() ) THEN 
    182  
    183             IF( ln_iceini_file )THEN      ! Read a file   ! 
     183            !                             !---------------! 
     184            IF( nn_iceini_file == 1 )THEN ! Read a file   ! 
    184185               !                          !---------------! 
    185186               WHERE( ff_t(:,:) >= 0._wp )   ;   zswitch(:,:) = 1._wp 
     
    195196 
    196197               ! -- optional fields -- ! 
    197                !    if fields do not exist then set them to the values present in the namelist (except for snow and surface temperature) 
     198               !    if fields do not exist then set them to the values present in the namelist (except for temperatures) 
    198199               ! 
    199200               ! ice salinity 
     
    207208                  si(jp_tsu)%fnow(:,:,1) = ( rn_tsu_ini_n * zswitch + rn_tsu_ini_s * (1._wp - zswitch) ) * tmask(:,:,1) 
    208209                  si(jp_tms)%fnow(:,:,1) = ( rn_tms_ini_n * zswitch + rn_tms_ini_s * (1._wp - zswitch) ) * tmask(:,:,1) 
    209                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 
    210                   si(jp_tmi)%fnow(:,:,1) = 0.5_wp * ( si(jp_tms)%fnow(:,:,1) + 271.15 ) 
    211                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 
    212                   si(jp_tmi)%fnow(:,:,1) = 0.5_wp * ( si(jp_tsu)%fnow(:,:,1) + 271.15 ) 
    213                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 
    214                   si(jp_tsu)%fnow(:,:,1) = si(jp_tms)%fnow(:,:,1) 
    215                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 
    216                   si(jp_tsu)%fnow(:,:,1) = si(jp_tmi)%fnow(:,:,1) 
    217                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 
    218                   si(jp_tms)%fnow(:,:,1) = si(jp_tsu)%fnow(:,:,1) 
    219                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 
    220                   si(jp_tms)%fnow(:,:,1) = si(jp_tmi)%fnow(:,:,1) 
    221210               ENDIF 
     211               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 
     212                  &     si(jp_tmi)%fnow(:,:,1) = 0.5_wp * ( si(jp_tms)%fnow(:,:,1) + 271.15 ) 
     213               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 
     214                  &     si(jp_tmi)%fnow(:,:,1) = 0.5_wp * ( si(jp_tsu)%fnow(:,:,1) + 271.15 ) 
     215               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 
     216                  &     si(jp_tsu)%fnow(:,:,1) = si(jp_tms)%fnow(:,:,1) 
     217               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 
     218                  &     si(jp_tsu)%fnow(:,:,1) = si(jp_tmi)%fnow(:,:,1) 
     219               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 
     220                  &     si(jp_tms)%fnow(:,:,1) = si(jp_tsu)%fnow(:,:,1) 
     221               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 
     222                  &     si(jp_tms)%fnow(:,:,1) = si(jp_tmi)%fnow(:,:,1) 
    222223               ! 
    223224               ! pond concentration 
     
    229230               IF( TRIM(si(jp_hpd)%clrootname) == 'NOT USED' ) & 
    230231                  &     si(jp_hpd)%fnow(:,:,1) = ( rn_hpd_ini_n * zswitch + rn_hpd_ini_s * (1._wp - zswitch) ) * tmask(:,:,1) 
     232               ! 
     233               ! pond lid depth 
     234               IF( TRIM(si(jp_hld)%clrootname) == 'NOT USED' ) & 
     235                  &     si(jp_hld)%fnow(:,:,1) = ( rn_hld_ini_n * zswitch + rn_hld_ini_s * (1._wp - zswitch) ) * tmask(:,:,1) 
    231236               ! 
    232237               zsm_i_ini(:,:) = si(jp_smi)%fnow(:,:,1) * tmask(:,:,1) 
     
    236241               zapnd_ini(:,:) = si(jp_apd)%fnow(:,:,1) * tmask(:,:,1) 
    237242               zhpnd_ini(:,:) = si(jp_hpd)%fnow(:,:,1) * tmask(:,:,1) 
     243               zhlid_ini(:,:) = si(jp_hld)%fnow(:,:,1) * tmask(:,:,1) 
    238244               ! 
    239245               ! change the switch for the following 
     
    261267                  zapnd_ini(:,:) = rn_apd_ini_n * zswitch(:,:) * zat_i_ini(:,:) ! rn_apd = pond fraction => rn_apd * a_i = pond conc.  
    262268                  zhpnd_ini(:,:) = rn_hpd_ini_n * zswitch(:,:) 
     269                  zhlid_ini(:,:) = rn_hld_ini_n * zswitch(:,:) 
    263270               ELSEWHERE 
    264271                  zht_i_ini(:,:) = rn_hti_ini_s * zswitch(:,:) 
     
    271278                  zapnd_ini(:,:) = rn_apd_ini_s * zswitch(:,:) * zat_i_ini(:,:) ! rn_apd = pond fraction => rn_apd * a_i = pond conc. 
    272279                  zhpnd_ini(:,:) = rn_hpd_ini_s * zswitch(:,:) 
     280                  zhlid_ini(:,:) = rn_hld_ini_s * zswitch(:,:) 
    273281               END WHERE 
    274282               ! 
     
    281289               zapnd_ini(:,:) = 0._wp 
    282290               zhpnd_ini(:,:) = 0._wp 
     291               zhlid_ini(:,:) = 0._wp 
    283292            ENDIF 
    284293             
    285             !-------------! 
    286             ! fill fields ! 
    287             !-------------! 
     294            IF ( .NOT.ln_pnd_lids ) THEN 
     295               zhlid_ini(:,:) = 0._wp 
     296            ENDIF 
     297             
     298            !----------------! 
     299            ! 3) fill fields ! 
     300            !----------------! 
    288301            ! select ice covered grid points 
    289302            npti = 0 ; nptidx(:) = 0 
     
    305318            CALL tab_2d_1d( npti, nptidx(1:npti), a_ip_1d(1:npti)  , zapnd_ini ) 
    306319            CALL tab_2d_1d( npti, nptidx(1:npti), h_ip_1d(1:npti)  , zhpnd_ini ) 
    307  
     320            CALL tab_2d_1d( npti, nptidx(1:npti), h_il_1d(1:npti)  , zhlid_ini ) 
     321             
    308322            ! allocate temporary arrays 
    309             ALLOCATE( zhi_2d(npti,jpl), zhs_2d(npti,jpl), zai_2d (npti,jpl), & 
    310                &      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              
     323            ALLOCATE( zhi_2d (npti,jpl), zhs_2d (npti,jpl), zai_2d (npti,jpl), & 
     324               &      zti_2d (npti,jpl), zts_2d (npti,jpl), ztsu_2d(npti,jpl), zsi_2d(npti,jpl), & 
     325               &      zaip_2d(npti,jpl), zhip_2d(npti,jpl), zhil_2d(npti,jpl) ) 
     326 
    312327            ! distribute 1-cat into jpl-cat: (jpi*jpj) -> (jpi*jpj,jpl) 
    313             CALL ice_var_itd( h_i_1d(1:npti)  , h_s_1d(1:npti)  , at_i_1d(1:npti),                                                   & 
    314                &              zhi_2d          , zhs_2d          , zai_2d         ,                                                   & 
    315                &              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), & 
    316                &              zti_2d          , zts_2d          , ztsu_2d        , zsi_2d        , zaip_2d        , zhip_2d ) 
     328            CALL ice_var_itd( h_i_1d(1:npti)  , h_s_1d(1:npti)  , at_i_1d(1:npti),                  & 
     329               &              zhi_2d          , zhs_2d          , zai_2d         ,                  & 
     330               &              t_i_1d(1:npti,1), t_s_1d(1:npti,1), t_su_1d(1:npti),                  & 
     331               &              s_i_1d(1:npti)  , a_ip_1d(1:npti) , h_ip_1d(1:npti), h_il_1d(1:npti), & 
     332               &              zti_2d          , zts_2d          , ztsu_2d        ,                  & 
     333               &              zsi_2d          , zaip_2d         , zhip_2d        , zhil_2d ) 
    317334 
    318335            ! move to 3D arrays: (jpi*jpj,jpl) -> (jpi,jpj,jpl) 
     
    330347            CALL tab_2d_3d( npti, nptidx(1:npti), zaip_2d  , a_ip   ) 
    331348            CALL tab_2d_3d( npti, nptidx(1:npti), zhip_2d  , h_ip   ) 
     349            CALL tab_2d_3d( npti, nptidx(1:npti), zhil_2d  , h_il   ) 
    332350 
    333351            ! deallocate temporary arrays 
    334352            DEALLOCATE( zhi_2d, zhs_2d, zai_2d , & 
    335                &        zti_2d, zts_2d, ztsu_2d, zsi_2d, zaip_2d, zhip_2d ) 
     353               &        zti_2d, zts_2d, ztsu_2d, zsi_2d, zaip_2d, zhip_2d, zhil_2d ) 
    336354 
    337355            ! calculate extensive and intensive variables 
     
    363381               END_3D 
    364382            END DO 
    365  
    366             ! Melt ponds 
    367             WHERE( a_i > epsi10 ) 
    368                a_ip_frac(:,:,:) = a_ip(:,:,:) / a_i(:,:,:) 
    369             ELSEWHERE 
    370                a_ip_frac(:,:,:) = 0._wp 
    371             END WHERE 
    372             v_ip(:,:,:) = h_ip(:,:,:) * a_ip(:,:,:) 
    373               
    374             ! specific temperatures for coupled runs 
    375             tn_ice(:,:,:) = t_su(:,:,:) 
    376             t1_ice(:,:,:) = t_i (:,:,1,:) 
    377             ! 
    378           
     383             
    379384#if  defined key_agrif 
    380385         ELSE 
     
    391396            Agrif_UseSpecialValue = .FALSE. 
    392397        ! lbc ????  
    393    ! Here we know : a_i, v_i, v_s, sv_i, oa_i, a_ip, v_ip, t_su, e_s, e_i 
     398   ! Here we know : a_i, v_i, v_s, sv_i, oa_i, a_ip, v_ip, v_il, t_su, e_s, e_i 
    394399            CALL ice_var_glo2eqv 
    395400            CALL ice_var_zapsmall 
    396401            CALL ice_var_agg(2) 
    397  
    398             ! Melt ponds 
    399             WHERE( a_i > epsi10 ) 
    400                a_ip_frac(:,:,:) = a_ip(:,:,:) / a_i(:,:,:) 
    401             ELSEWHERE 
    402                a_ip_frac(:,:,:) = 0._wp 
    403             END WHERE 
    404             WHERE( a_ip > 0._wp )       ! ???????     
    405                h_ip(:,:,:) = v_ip(:,:,:) / a_ip(:,:,:) 
    406             ELSEWHERE 
    407                h_ip(:,:,:) = 0._wp 
    408             END WHERE    
    409  
    410             tn_ice(:,:,:) = t_su(:,:,:) 
    411             t1_ice(:,:,:) = t_i (:,:,1,:) 
    412402#endif 
    413           ENDIF ! Agrif_Root 
     403         ENDIF ! Agrif_Root 
     404         ! 
     405         ! Melt ponds 
     406         WHERE( a_i > epsi10 )   ;   a_ip_eff(:,:,:) = a_ip(:,:,:) / a_i(:,:,:) 
     407         ELSEWHERE               ;   a_ip_eff(:,:,:) = 0._wp 
     408         END WHERE 
     409         v_ip(:,:,:) = h_ip(:,:,:) * a_ip(:,:,:) 
     410         v_il(:,:,:) = h_il(:,:,:) * a_ip(:,:,:) 
     411          
     412         ! specific temperatures for coupled runs 
     413         tn_ice(:,:,:) = t_su(:,:,:) 
     414         t1_ice(:,:,:) = t_i (:,:,1,:) 
     415         ! 
     416         ! ice concentration should not exceed amax 
     417         at_i(:,:) = SUM( a_i, dim=3 ) 
     418         DO jl = 1, jpl 
     419            WHERE( at_i(:,:) > rn_amax_2d(:,:) )   a_i(:,:,jl) = a_i(:,:,jl) * rn_amax_2d(:,:) / at_i(:,:) 
     420         END DO 
     421         at_i(:,:) = SUM( a_i, dim=3 ) 
     422         ! 
    414423      ENDIF ! ln_iceini 
    415424      ! 
    416       at_i(:,:) = SUM( a_i, dim=3 ) 
    417       ! 
    418425      !---------------------------------------------- 
    419       ! 3) Snow-ice mass (case ice is fully embedded) 
     426      ! 4) Snow-ice mass (case ice is fully embedded) 
    420427      !---------------------------------------------- 
    421428      snwice_mass  (:,:) = tmask(:,:,1) * SUM( rhos * v_s(:,:,:) + rhoi * v_i(:,:,:), dim=3  )   ! snow+ice mass 
     
    469476!          ENDIF 
    470477      ENDIF 
    471        
    472       !------------------------------------ 
    473       ! 4) store fields at before time-step 
    474       !------------------------------------ 
    475       ! it is only necessary for the 1st interpolation by Agrif 
    476       a_i_b  (:,:,:)   = a_i  (:,:,:) 
    477       e_i_b  (:,:,:,:) = e_i  (:,:,:,:) 
    478       v_i_b  (:,:,:)   = v_i  (:,:,:) 
    479       v_s_b  (:,:,:)   = v_s  (:,:,:) 
    480       e_s_b  (:,:,:,:) = e_s  (:,:,:,:) 
    481       sv_i_b (:,:,:)   = sv_i (:,:,:) 
    482       oa_i_b (:,:,:)   = oa_i (:,:,:) 
    483       u_ice_b(:,:)     = u_ice(:,:) 
    484       v_ice_b(:,:)     = v_ice(:,:) 
    485       ! total concentration is needed for Lupkes parameterizations 
    486       at_i_b (:,:)     = at_i (:,:)  
    487  
    488 !!clem: output of initial state should be written here but it is impossible because 
    489 !!      the ocean and ice are in the same file 
    490 !!      CALL dia_wri_state( Kmm, 'output.init' ) 
     478 
     479      !!clem: output of initial state should be written here but it is impossible because 
     480      !!      the ocean and ice are in the same file 
     481      !!      CALL dia_wri_state( 'output.init' ) 
    491482      ! 
    492483   END SUBROUTINE ice_istate 
     
    505496      !! 
    506497      !!----------------------------------------------------------------------------- 
    507       INTEGER ::   ios, ifpr, ierror   ! Local integers 
    508  
     498      INTEGER ::   ios   ! Local integer output status for namelist read 
     499      INTEGER ::   ifpr, ierror 
    509500      ! 
    510501      CHARACTER(len=256) ::  cn_dir          ! Root directory for location of ice files 
    511       TYPE(FLD_N)                    ::   sn_hti, sn_hts, sn_ati, sn_smi, sn_tmi, sn_tsu, sn_tms, sn_apd, sn_hpd 
     502      TYPE(FLD_N)                    ::   sn_hti, sn_hts, sn_ati, sn_smi, sn_tmi, sn_tsu, sn_tms, sn_apd, sn_hpd, sn_hld 
    512503      TYPE(FLD_N), DIMENSION(jpfldi) ::   slf_i                 ! array of namelist informations on the fields to read 
    513504      ! 
    514       NAMELIST/namini/ ln_iceini, ln_iceini_file, rn_thres_sst, & 
     505      NAMELIST/namini/ ln_iceini, nn_iceini_file, rn_thres_sst, & 
    515506         &             rn_hti_ini_n, rn_hti_ini_s, rn_hts_ini_n, rn_hts_ini_s, & 
    516507         &             rn_ati_ini_n, rn_ati_ini_s, rn_smi_ini_n, rn_smi_ini_s, & 
    517508         &             rn_tmi_ini_n, rn_tmi_ini_s, rn_tsu_ini_n, rn_tsu_ini_s, rn_tms_ini_n, rn_tms_ini_s, & 
    518          &             rn_apd_ini_n, rn_apd_ini_s, rn_hpd_ini_n, rn_hpd_ini_s, & 
    519          &             sn_hti, sn_hts, sn_ati, sn_tsu, sn_tmi, sn_smi, sn_tms, sn_apd, sn_hpd, cn_dir 
     509         &             rn_apd_ini_n, rn_apd_ini_s, rn_hpd_ini_n, rn_hpd_ini_s, rn_hld_ini_n, rn_hld_ini_s, & 
     510         &             sn_hti, sn_hts, sn_ati, sn_tsu, sn_tmi, sn_smi, sn_tms, sn_apd, sn_hpd, sn_hld, cn_dir 
    520511      !!----------------------------------------------------------------------------- 
    521512      ! 
     
    529520      slf_i(jp_ati) = sn_ati  ;  slf_i(jp_smi) = sn_smi 
    530521      slf_i(jp_tmi) = sn_tmi  ;  slf_i(jp_tsu) = sn_tsu   ;   slf_i(jp_tms) = sn_tms 
    531       slf_i(jp_apd) = sn_apd  ;  slf_i(jp_hpd) = sn_hpd 
     522      slf_i(jp_apd) = sn_apd  ;  slf_i(jp_hpd) = sn_hpd   ;   slf_i(jp_hld) = sn_hld 
    532523      ! 
    533524      IF(lwp) THEN                          ! control print 
     
    537528         WRITE(numout,*) '   Namelist namini:' 
    538529         WRITE(numout,*) '      ice initialization (T) or not (F)                ln_iceini      = ', ln_iceini 
    539          WRITE(numout,*) '      ice initialization from a netcdf file            ln_iceini_file = ', ln_iceini_file 
     530         WRITE(numout,*) '      ice initialization from a netcdf file            nn_iceini_file = ', nn_iceini_file 
    540531         WRITE(numout,*) '      max ocean temp. above Tfreeze with initial ice   rn_thres_sst   = ', rn_thres_sst 
    541          IF( ln_iceini .AND. .NOT.ln_iceini_file ) THEN 
     532         IF( ln_iceini .AND. nn_iceini_file == 0 ) THEN 
    542533            WRITE(numout,*) '      initial snw thickness in the north-south         rn_hts_ini     = ', rn_hts_ini_n,rn_hts_ini_s  
    543534            WRITE(numout,*) '      initial ice thickness in the north-south         rn_hti_ini     = ', rn_hti_ini_n,rn_hti_ini_s 
     
    549540            WRITE(numout,*) '      initial pnd fraction  in the north-south         rn_apd_ini     = ', rn_apd_ini_n,rn_apd_ini_s 
    550541            WRITE(numout,*) '      initial pnd depth     in the north-south         rn_hpd_ini     = ', rn_hpd_ini_n,rn_hpd_ini_s 
     542            WRITE(numout,*) '      initial pnd lid depth in the north-south         rn_hld_ini     = ', rn_hld_ini_n,rn_hld_ini_s 
    551543         ENDIF 
    552544      ENDIF 
    553545      ! 
    554       IF( ln_iceini_file ) THEN                      ! Ice initialization using input file 
     546      IF( nn_iceini_file == 1 ) THEN                      ! Ice initialization using input file 
    555547         ! 
    556548         ! set si structure 
     
    573565         rn_apd_ini_n = 0. ; rn_apd_ini_s = 0. 
    574566         rn_hpd_ini_n = 0. ; rn_hpd_ini_s = 0. 
    575          CALL ctl_warn( 'rn_apd_ini & rn_hpd_ini = 0 when no ponds' ) 
     567         rn_hld_ini_n = 0. ; rn_hld_ini_s = 0. 
     568         CALL ctl_warn( 'rn_apd_ini & rn_hpd_ini = 0 & rn_hld_ini = 0 when no ponds' ) 
     569      ENDIF 
     570      ! 
     571      IF( .NOT.ln_pnd_lids ) THEN 
     572         rn_hld_ini_n = 0. ; rn_hld_ini_s = 0. 
    576573      ENDIF 
    577574      ! 
Note: See TracChangeset for help on using the changeset viewer.