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/iceistate.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/iceistate.F90

    r13732 r13998  
    5151   !                             !! ** namelist (namini) ** 
    5252   LOGICAL, PUBLIC  ::   ln_iceini        !: Ice initialization or not 
    53    LOGICAL, PUBLIC  ::   ln_iceini_file   !: Ice initialization from 2D netcdf file 
     53   INTEGER, PUBLIC  ::   nn_iceini_file   !: Ice initialization: 
     54                                  !        0 = Initialise sea ice based on SSTs 
     55                                  !        1 = Initialise sea ice from single category netcdf file 
     56                                  !        2 = Initialise sea ice from multi category restart file 
    5457   REAL(wp) ::   rn_thres_sst 
    5558   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 
    5659   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 
    57    REAL(wp) ::   rn_apd_ini_n, rn_hpd_ini_n 
    58    REAL(wp) ::   rn_apd_ini_s, rn_hpd_ini_s 
     60   REAL(wp) ::   rn_apd_ini_n, rn_hpd_ini_n, rn_hld_ini_n 
     61   REAL(wp) ::   rn_apd_ini_s, rn_hpd_ini_s, rn_hld_ini_s 
    5962   ! 
    60    !                              ! if ln_iceini_file = T 
    61    INTEGER , PARAMETER ::   jpfldi = 9           ! maximum number of files to read 
     63   !                              ! if nn_iceini_file = 1 
     64   INTEGER , PARAMETER ::   jpfldi = 10          ! maximum number of files to read 
    6265   INTEGER , PARAMETER ::   jp_hti = 1           ! index of ice thickness    (m) 
    6366   INTEGER , PARAMETER ::   jp_hts = 2           ! index of snw thickness    (m) 
     
    6972   INTEGER , PARAMETER ::   jp_apd = 8           ! index of pnd fraction     (-) 
    7073   INTEGER , PARAMETER ::   jp_hpd = 9           ! index of pnd depth        (m) 
     74   INTEGER , PARAMETER ::   jp_hld = 10          ! index of pnd lid depth    (m) 
    7175   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   si  ! structure of input fields (file informations, fields read) 
    7276 
     
    9397      !! ** Steps   :   1) Set initial surface and basal temperatures 
    9498      !!                2) Recompute or read sea ice state variables 
    95       !!                3) Fill in the ice thickness distribution using gaussian 
    96       !!                4) Fill in space-dependent arrays for state variables 
    97       !!                5) snow-ice mass computation 
    98       !!                6) store before fields 
     99      !!                3) Fill in space-dependent arrays for state variables 
     100      !!                4) snow-ice mass computation 
    99101      !! 
    100102      !! ** Notes   : o_i, t_su, t_s, t_i, sz_i must be filled everywhere, even 
     
    111113      REAL(wp), DIMENSION(jpi,jpj)     ::   zht_i_ini, zat_i_ini, ztm_s_ini            !data from namelist or nc file 
    112114      REAL(wp), DIMENSION(jpi,jpj)     ::   zt_su_ini, zht_s_ini, zsm_i_ini, ztm_i_ini !data from namelist or nc file 
    113       REAL(wp), DIMENSION(jpi,jpj)     ::   zapnd_ini, zhpnd_ini                       !data from namelist or nc file 
    114       REAL(wp), DIMENSION(jpi,jpj,jpl) ::   zti_3d , zts_3d                            !locak arrays 
    115       !! 
    116       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::   zhi_2d, zhs_2d, zai_2d, zti_2d, zts_2d, ztsu_2d, zsi_2d, zaip_2d, zhip_2d 
     115      REAL(wp), DIMENSION(jpi,jpj)     ::   zapnd_ini, zhpnd_ini, zhlid_ini            !data from namelist or nc file 
     116      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   zti_3d , zts_3d                            !temporary arrays 
     117      !! 
     118      REAL(wp), DIMENSION(:,:), ALLOCATABLE ::   zhi_2d, zhs_2d, zai_2d, zti_2d, zts_2d, ztsu_2d, zsi_2d, zaip_2d, zhip_2d, zhil_2d 
    117119      !-------------------------------------------------------------------- 
    118120 
     
    168170      a_ip     (:,:,:) = 0._wp 
    169171      v_ip     (:,:,:) = 0._wp 
    170       a_ip_frac(:,:,:) = 0._wp 
     172      v_il     (:,:,:) = 0._wp 
     173      a_ip_eff (:,:,:) = 0._wp 
    171174      h_ip     (:,:,:) = 0._wp 
     175      h_il     (:,:,:) = 0._wp 
    172176      ! 
    173177      ! ice velocities 
     
    178182      ! 2) overwrite some of the fields with namelist parameters or netcdf file 
    179183      !------------------------------------------------------------------------ 
    180  
    181  
    182184      IF( ln_iceini ) THEN 
    183          !                             !---------------! 
    184           
     185         ! 
    185186         IF( Agrif_Root() ) THEN 
    186  
    187             IF( ln_iceini_file )THEN      ! Read a file   ! 
     187            !                             !---------------! 
     188            IF( nn_iceini_file == 1 )THEN ! Read a file   ! 
    188189               !                          !---------------! 
    189190               WHERE( ff_t(:,:) >= 0._wp )   ;   zswitch(:,:) = 1._wp 
     
    199200 
    200201               ! -- optional fields -- ! 
    201                !    if fields do not exist then set them to the values present in the namelist (except for snow and surface temperature) 
     202               !    if fields do not exist then set them to the values present in the namelist (except for temperatures) 
    202203               ! 
    203204               ! ice salinity 
     
    211212                  si(jp_tsu)%fnow(:,:,1) = ( rn_tsu_ini_n * zswitch + rn_tsu_ini_s * (1._wp - zswitch) ) * tmask(:,:,1) 
    212213                  si(jp_tms)%fnow(:,:,1) = ( rn_tms_ini_n * zswitch + rn_tms_ini_s * (1._wp - zswitch) ) * tmask(:,:,1) 
    213                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 
    214                   si(jp_tmi)%fnow(:,:,1) = 0.5_wp * ( si(jp_tms)%fnow(:,:,1) + 271.15 ) 
    215                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 
    216                   si(jp_tmi)%fnow(:,:,1) = 0.5_wp * ( si(jp_tsu)%fnow(:,:,1) + 271.15 ) 
    217                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 
    218                   si(jp_tsu)%fnow(:,:,1) = si(jp_tms)%fnow(:,:,1) 
    219                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 
    220                   si(jp_tsu)%fnow(:,:,1) = si(jp_tmi)%fnow(:,:,1) 
    221                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 
    222                   si(jp_tms)%fnow(:,:,1) = si(jp_tsu)%fnow(:,:,1) 
    223                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 
    224                   si(jp_tms)%fnow(:,:,1) = si(jp_tmi)%fnow(:,:,1) 
    225214               ENDIF 
     215               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 
     216                  &     si(jp_tmi)%fnow(:,:,1) = 0.5_wp * ( si(jp_tms)%fnow(:,:,1) + 271.15 ) 
     217               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 
     218                  &     si(jp_tmi)%fnow(:,:,1) = 0.5_wp * ( si(jp_tsu)%fnow(:,:,1) + 271.15 ) 
     219               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 
     220                  &     si(jp_tsu)%fnow(:,:,1) = si(jp_tms)%fnow(:,:,1) 
     221               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 
     222                  &     si(jp_tsu)%fnow(:,:,1) = si(jp_tmi)%fnow(:,:,1) 
     223               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 
     224                  &     si(jp_tms)%fnow(:,:,1) = si(jp_tsu)%fnow(:,:,1) 
     225               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 
     226                  &     si(jp_tms)%fnow(:,:,1) = si(jp_tmi)%fnow(:,:,1) 
    226227               ! 
    227228               ! pond concentration 
     
    233234               IF( TRIM(si(jp_hpd)%clrootname) == 'NOT USED' ) & 
    234235                  &     si(jp_hpd)%fnow(:,:,1) = ( rn_hpd_ini_n * zswitch + rn_hpd_ini_s * (1._wp - zswitch) ) * tmask(:,:,1) 
     236               ! 
     237               ! pond lid depth 
     238               IF( TRIM(si(jp_hld)%clrootname) == 'NOT USED' ) & 
     239                  &     si(jp_hld)%fnow(:,:,1) = ( rn_hld_ini_n * zswitch + rn_hld_ini_s * (1._wp - zswitch) ) * tmask(:,:,1) 
    235240               ! 
    236241               zsm_i_ini(:,:) = si(jp_smi)%fnow(:,:,1) * tmask(:,:,1) 
     
    240245               zapnd_ini(:,:) = si(jp_apd)%fnow(:,:,1) * tmask(:,:,1) 
    241246               zhpnd_ini(:,:) = si(jp_hpd)%fnow(:,:,1) * tmask(:,:,1) 
     247               zhlid_ini(:,:) = si(jp_hld)%fnow(:,:,1) * tmask(:,:,1) 
    242248               ! 
    243249               ! change the switch for the following 
     
    265271                  zapnd_ini(:,:) = rn_apd_ini_n * zswitch(:,:) * zat_i_ini(:,:) ! rn_apd = pond fraction => rn_apd * a_i = pond conc.  
    266272                  zhpnd_ini(:,:) = rn_hpd_ini_n * zswitch(:,:) 
     273                  zhlid_ini(:,:) = rn_hld_ini_n * zswitch(:,:) 
    267274               ELSEWHERE 
    268275                  zht_i_ini(:,:) = rn_hti_ini_s * zswitch(:,:) 
     
    275282                  zapnd_ini(:,:) = rn_apd_ini_s * zswitch(:,:) * zat_i_ini(:,:) ! rn_apd = pond fraction => rn_apd * a_i = pond conc. 
    276283                  zhpnd_ini(:,:) = rn_hpd_ini_s * zswitch(:,:) 
     284                  zhlid_ini(:,:) = rn_hld_ini_s * zswitch(:,:) 
    277285               END WHERE 
    278286               ! 
     
    285293               zapnd_ini(:,:) = 0._wp 
    286294               zhpnd_ini(:,:) = 0._wp 
     295               zhlid_ini(:,:) = 0._wp 
    287296            ENDIF 
    288297             
    289             !-------------! 
    290             ! fill fields ! 
    291             !-------------! 
     298            IF ( .NOT.ln_pnd_lids ) THEN 
     299               zhlid_ini(:,:) = 0._wp 
     300            ENDIF 
     301             
     302            !----------------! 
     303            ! 3) fill fields ! 
     304            !----------------! 
    292305            ! select ice covered grid points 
    293306            npti = 0 ; nptidx(:) = 0 
     
    309322            CALL tab_2d_1d( npti, nptidx(1:npti), a_ip_1d(1:npti)  , zapnd_ini ) 
    310323            CALL tab_2d_1d( npti, nptidx(1:npti), h_ip_1d(1:npti)  , zhpnd_ini ) 
    311  
     324            CALL tab_2d_1d( npti, nptidx(1:npti), h_il_1d(1:npti)  , zhlid_ini ) 
     325             
    312326            ! allocate temporary arrays 
    313             ALLOCATE( zhi_2d(npti,jpl), zhs_2d(npti,jpl), zai_2d (npti,jpl), & 
    314                &      zti_2d(npti,jpl), zts_2d(npti,jpl), ztsu_2d(npti,jpl), zsi_2d(npti,jpl), zaip_2d(npti,jpl), zhip_2d(npti,jpl) ) 
    315              
     327            ALLOCATE( zhi_2d (npti,jpl), zhs_2d (npti,jpl), zai_2d (npti,jpl), & 
     328               &      zti_2d (npti,jpl), zts_2d (npti,jpl), ztsu_2d(npti,jpl), zsi_2d(npti,jpl), & 
     329               &      zaip_2d(npti,jpl), zhip_2d(npti,jpl), zhil_2d(npti,jpl) ) 
     330 
    316331            ! distribute 1-cat into jpl-cat: (jpi*jpj) -> (jpi*jpj,jpl) 
    317             CALL ice_var_itd( h_i_1d(1:npti)  , h_s_1d(1:npti)  , at_i_1d(1:npti),                                                   & 
    318                &              zhi_2d          , zhs_2d          , zai_2d         ,                                                   & 
    319                &              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), & 
    320                &              zti_2d          , zts_2d          , ztsu_2d        , zsi_2d        , zaip_2d        , zhip_2d ) 
     332            CALL ice_var_itd( h_i_1d(1:npti)  , h_s_1d(1:npti)  , at_i_1d(1:npti),                  & 
     333               &              zhi_2d          , zhs_2d          , zai_2d         ,                  & 
     334               &              t_i_1d(1:npti,1), t_s_1d(1:npti,1), t_su_1d(1:npti),                  & 
     335               &              s_i_1d(1:npti)  , a_ip_1d(1:npti) , h_ip_1d(1:npti), h_il_1d(1:npti), & 
     336               &              zti_2d          , zts_2d          , ztsu_2d        ,                  & 
     337               &              zsi_2d          , zaip_2d         , zhip_2d        , zhil_2d ) 
    321338 
    322339            ! move to 3D arrays: (jpi*jpj,jpl) -> (jpi,jpj,jpl) 
     
    334351            CALL tab_2d_3d( npti, nptidx(1:npti), zaip_2d  , a_ip   ) 
    335352            CALL tab_2d_3d( npti, nptidx(1:npti), zhip_2d  , h_ip   ) 
     353            CALL tab_2d_3d( npti, nptidx(1:npti), zhil_2d  , h_il   ) 
    336354 
    337355            ! deallocate temporary arrays 
    338356            DEALLOCATE( zhi_2d, zhs_2d, zai_2d , & 
    339                &        zti_2d, zts_2d, ztsu_2d, zsi_2d, zaip_2d, zhip_2d ) 
     357               &        zti_2d, zts_2d, ztsu_2d, zsi_2d, zaip_2d, zhip_2d, zhil_2d ) 
    340358 
    341359            ! calculate extensive and intensive variables 
     
    367385               END_3D 
    368386            END DO 
    369  
    370             ! Melt ponds 
    371             WHERE( a_i > epsi10 ) 
    372                a_ip_frac(:,:,:) = a_ip(:,:,:) / a_i(:,:,:) 
    373             ELSEWHERE 
    374                a_ip_frac(:,:,:) = 0._wp 
    375             END WHERE 
    376             v_ip(:,:,:) = h_ip(:,:,:) * a_ip(:,:,:) 
    377               
    378             ! specific temperatures for coupled runs 
    379             tn_ice(:,:,:) = t_su(:,:,:) 
    380             t1_ice(:,:,:) = t_i (:,:,1,:) 
    381             ! 
    382           
     387             
    383388#if  defined key_agrif 
    384389         ELSE 
     
    395400            Agrif_UseSpecialValue = .FALSE. 
    396401        ! lbc ????  
    397    ! Here we know : a_i, v_i, v_s, sv_i, oa_i, a_ip, v_ip, t_su, e_s, e_i 
     402   ! 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 
    398403            CALL ice_var_glo2eqv 
    399404            CALL ice_var_zapsmall 
    400405            CALL ice_var_agg(2) 
    401  
    402             ! Melt ponds 
    403             WHERE( a_i > epsi10 ) 
    404                a_ip_frac(:,:,:) = a_ip(:,:,:) / a_i(:,:,:) 
    405             ELSEWHERE 
    406                a_ip_frac(:,:,:) = 0._wp 
    407             END WHERE 
    408             WHERE( a_ip > 0._wp )       ! ???????     
    409                h_ip(:,:,:) = v_ip(:,:,:) / a_ip(:,:,:) 
    410             ELSEWHERE 
    411                h_ip(:,:,:) = 0._wp 
    412             END WHERE    
    413  
    414             tn_ice(:,:,:) = t_su(:,:,:) 
    415             t1_ice(:,:,:) = t_i (:,:,1,:) 
    416406#endif 
    417           ENDIF ! Agrif_Root 
     407         ENDIF ! Agrif_Root 
     408         ! 
     409         ! Melt ponds 
     410         WHERE( a_i > epsi10 )   ;   a_ip_eff(:,:,:) = a_ip(:,:,:) / a_i(:,:,:) 
     411         ELSEWHERE               ;   a_ip_eff(:,:,:) = 0._wp 
     412         END WHERE 
     413         v_ip(:,:,:) = h_ip(:,:,:) * a_ip(:,:,:) 
     414         v_il(:,:,:) = h_il(:,:,:) * a_ip(:,:,:) 
     415          
     416         ! specific temperatures for coupled runs 
     417         tn_ice(:,:,:) = t_su(:,:,:) 
     418         t1_ice(:,:,:) = t_i (:,:,1,:) 
     419         ! 
     420         ! ice concentration should not exceed amax 
     421         at_i(:,:) = SUM( a_i, dim=3 ) 
     422         DO jl = 1, jpl 
     423            WHERE( at_i(:,:) > rn_amax_2d(:,:) )   a_i(:,:,jl) = a_i(:,:,jl) * rn_amax_2d(:,:) / at_i(:,:) 
     424         END DO 
     425         at_i(:,:) = SUM( a_i, dim=3 ) 
     426         ! 
    418427      ENDIF ! ln_iceini 
    419428      ! 
    420       at_i(:,:) = SUM( a_i, dim=3 ) 
    421       ! 
    422429      !---------------------------------------------- 
    423       ! 3) Snow-ice mass (case ice is fully embedded) 
     430      ! 4) Snow-ice mass (case ice is fully embedded) 
    424431      !---------------------------------------------- 
    425432      snwice_mass  (:,:) = tmask(:,:,1) * SUM( rhos * v_s(:,:,:) + rhoi * v_i(:,:,:), dim=3  )   ! snow+ice mass 
     
    438445 
    439446      ENDIF 
    440        
    441       !------------------------------------ 
    442       ! 4) store fields at before time-step 
    443       !------------------------------------ 
    444       ! it is only necessary for the 1st interpolation by Agrif 
    445       a_i_b  (:,:,:)   = a_i  (:,:,:) 
    446       e_i_b  (:,:,:,:) = e_i  (:,:,:,:) 
    447       v_i_b  (:,:,:)   = v_i  (:,:,:) 
    448       v_s_b  (:,:,:)   = v_s  (:,:,:) 
    449       e_s_b  (:,:,:,:) = e_s  (:,:,:,:) 
    450       sv_i_b (:,:,:)   = sv_i (:,:,:) 
    451       oa_i_b (:,:,:)   = oa_i (:,:,:) 
    452       u_ice_b(:,:)     = u_ice(:,:) 
    453       v_ice_b(:,:)     = v_ice(:,:) 
    454       ! total concentration is needed for Lupkes parameterizations 
    455       at_i_b (:,:)     = at_i (:,:)  
    456  
    457 !!clem: output of initial state should be written here but it is impossible because 
    458 !!      the ocean and ice are in the same file 
    459 !!      CALL dia_wri_state( Kmm, 'output.init' ) 
     447 
     448      !!clem: output of initial state should be written here but it is impossible because 
     449      !!      the ocean and ice are in the same file 
     450      !!      CALL dia_wri_state( 'output.init' ) 
    460451      ! 
    461452   END SUBROUTINE ice_istate 
     
    474465      !! 
    475466      !!----------------------------------------------------------------------------- 
    476       INTEGER ::   ios, ifpr, ierror   ! Local integers 
    477  
     467      INTEGER ::   ios   ! Local integer output status for namelist read 
     468      INTEGER ::   ifpr, ierror 
    478469      ! 
    479470      CHARACTER(len=256) ::  cn_dir          ! Root directory for location of ice files 
    480       TYPE(FLD_N)                    ::   sn_hti, sn_hts, sn_ati, sn_smi, sn_tmi, sn_tsu, sn_tms, sn_apd, sn_hpd 
     471      TYPE(FLD_N)                    ::   sn_hti, sn_hts, sn_ati, sn_smi, sn_tmi, sn_tsu, sn_tms, sn_apd, sn_hpd, sn_hld 
    481472      TYPE(FLD_N), DIMENSION(jpfldi) ::   slf_i                 ! array of namelist informations on the fields to read 
    482473      ! 
    483       NAMELIST/namini/ ln_iceini, ln_iceini_file, rn_thres_sst, & 
     474      NAMELIST/namini/ ln_iceini, nn_iceini_file, rn_thres_sst, & 
    484475         &             rn_hti_ini_n, rn_hti_ini_s, rn_hts_ini_n, rn_hts_ini_s, & 
    485476         &             rn_ati_ini_n, rn_ati_ini_s, rn_smi_ini_n, rn_smi_ini_s, & 
    486477         &             rn_tmi_ini_n, rn_tmi_ini_s, rn_tsu_ini_n, rn_tsu_ini_s, rn_tms_ini_n, rn_tms_ini_s, & 
    487          &             rn_apd_ini_n, rn_apd_ini_s, rn_hpd_ini_n, rn_hpd_ini_s, & 
    488          &             sn_hti, sn_hts, sn_ati, sn_tsu, sn_tmi, sn_smi, sn_tms, sn_apd, sn_hpd, cn_dir 
     478         &             rn_apd_ini_n, rn_apd_ini_s, rn_hpd_ini_n, rn_hpd_ini_s, rn_hld_ini_n, rn_hld_ini_s, & 
     479         &             sn_hti, sn_hts, sn_ati, sn_tsu, sn_tmi, sn_smi, sn_tms, sn_apd, sn_hpd, sn_hld, cn_dir 
    489480      !!----------------------------------------------------------------------------- 
    490481      ! 
     
    498489      slf_i(jp_ati) = sn_ati  ;  slf_i(jp_smi) = sn_smi 
    499490      slf_i(jp_tmi) = sn_tmi  ;  slf_i(jp_tsu) = sn_tsu   ;   slf_i(jp_tms) = sn_tms 
    500       slf_i(jp_apd) = sn_apd  ;  slf_i(jp_hpd) = sn_hpd 
     491      slf_i(jp_apd) = sn_apd  ;  slf_i(jp_hpd) = sn_hpd   ;   slf_i(jp_hld) = sn_hld 
    501492      ! 
    502493      IF(lwp) THEN                          ! control print 
     
    506497         WRITE(numout,*) '   Namelist namini:' 
    507498         WRITE(numout,*) '      ice initialization (T) or not (F)                ln_iceini      = ', ln_iceini 
    508          WRITE(numout,*) '      ice initialization from a netcdf file            ln_iceini_file = ', ln_iceini_file 
     499         WRITE(numout,*) '      ice initialization from a netcdf file            nn_iceini_file = ', nn_iceini_file 
    509500         WRITE(numout,*) '      max ocean temp. above Tfreeze with initial ice   rn_thres_sst   = ', rn_thres_sst 
    510          IF( ln_iceini .AND. .NOT.ln_iceini_file ) THEN 
     501         IF( ln_iceini .AND. nn_iceini_file == 0 ) THEN 
    511502            WRITE(numout,*) '      initial snw thickness in the north-south         rn_hts_ini     = ', rn_hts_ini_n,rn_hts_ini_s  
    512503            WRITE(numout,*) '      initial ice thickness in the north-south         rn_hti_ini     = ', rn_hti_ini_n,rn_hti_ini_s 
     
    518509            WRITE(numout,*) '      initial pnd fraction  in the north-south         rn_apd_ini     = ', rn_apd_ini_n,rn_apd_ini_s 
    519510            WRITE(numout,*) '      initial pnd depth     in the north-south         rn_hpd_ini     = ', rn_hpd_ini_n,rn_hpd_ini_s 
     511            WRITE(numout,*) '      initial pnd lid depth in the north-south         rn_hld_ini     = ', rn_hld_ini_n,rn_hld_ini_s 
    520512         ENDIF 
    521513      ENDIF 
    522514      ! 
    523       IF( ln_iceini_file ) THEN                      ! Ice initialization using input file 
     515      IF( nn_iceini_file == 1 ) THEN                      ! Ice initialization using input file 
    524516         ! 
    525517         ! set si structure 
     
    542534         rn_apd_ini_n = 0. ; rn_apd_ini_s = 0. 
    543535         rn_hpd_ini_n = 0. ; rn_hpd_ini_s = 0. 
    544          CALL ctl_warn( 'rn_apd_ini & rn_hpd_ini = 0 when no ponds' ) 
     536         rn_hld_ini_n = 0. ; rn_hld_ini_s = 0. 
     537         CALL ctl_warn( 'rn_apd_ini & rn_hpd_ini = 0 & rn_hld_ini = 0 when no ponds' ) 
     538      ENDIF 
     539      ! 
     540      IF( .NOT.ln_pnd_lids ) THEN 
     541         rn_hld_ini_n = 0. ; rn_hld_ini_s = 0. 
    545542      ENDIF 
    546543      ! 
Note: See TracChangeset for help on using the changeset viewer.