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 13662 for NEMO/branches/2019/dev_r11842_SI3-10_EAP/src/ICE/iceistate.F90 – NEMO

Ignore:
Timestamp:
2020-10-22T20:49:56+02:00 (4 years ago)
Author:
clem
Message:

update to almost r4.0.4

Location:
NEMO/branches/2019/dev_r11842_SI3-10_EAP
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r11842_SI3-10_EAP

    • Property svn:externals
      •  

        old new  
        1 ^/utils/build/arch@HEAD       arch 
        2 ^/utils/build/makenemo@HEAD   makenemo 
        3 ^/utils/build/mk@HEAD         mk 
        4 ^/utils/tools@HEAD            tools 
        5 ^/vendors/AGRIF/dev@HEAD      ext/AGRIF 
        6 ^/vendors/FCM@HEAD            ext/FCM 
        7 ^/vendors/IOIPSL@HEAD         ext/IOIPSL 
         1^/utils/build/arch@12130      arch 
         2^/utils/build/makenemo@12191  makenemo 
         3^/utils/build/mk@11662        mk 
         4^/utils/tools_r4.0-HEAD@12672 tools 
         5^/vendors/AGRIF/dev@10586     ext/AGRIF 
         6^/vendors/FCM@10134           ext/FCM 
         7^/vendors/IOIPSL@9655         ext/IOIPSL 
         8 
         9# SETTE mapping (inactive) 
         10#^/utils/CI/sette@12135        sette 
  • NEMO/branches/2019/dev_r11842_SI3-10_EAP/src/ICE/iceistate.F90

    r11536 r13662  
    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 
     
    176180            ! 
    177181            ! -- mandatory fields -- ! 
    178             zht_i_ini(:,:) = si(jp_hti)%fnow(:,:,1) 
    179             zht_s_ini(:,:) = si(jp_hts)%fnow(:,:,1) 
    180             zat_i_ini(:,:) = si(jp_ati)%fnow(:,:,1) 
     182            zht_i_ini(:,:) = si(jp_hti)%fnow(:,:,1) * tmask(:,:,1) 
     183            zht_s_ini(:,:) = si(jp_hts)%fnow(:,:,1) * tmask(:,:,1) 
     184            zat_i_ini(:,:) = si(jp_ati)%fnow(:,:,1) * tmask(:,:,1) 
    181185 
    182186            ! -- optional fields -- ! 
    183             !    if fields do not exist then set them to the values present in the namelist (except for snow and surface temperature) 
     187            !    if fields do not exist then set them to the values present in the namelist (except for temperatures) 
    184188            ! 
    185189            ! ice salinity 
    186190            IF( TRIM(si(jp_smi)%clrootname) == 'NOT USED' ) & 
    187191               &     si(jp_smi)%fnow(:,:,1) = ( rn_smi_ini_n * zswitch + rn_smi_ini_s * (1._wp - zswitch) ) * tmask(:,:,1) 
    188             zsm_i_ini(:,:) = si(jp_smi)%fnow(:,:,1) 
    189             ! 
    190             ! ice temperature 
    191             IF( TRIM(si(jp_tmi)%clrootname) == 'NOT USED' ) & 
    192                &     si(jp_tmi)%fnow(:,:,1) = ( rn_tmi_ini_n * zswitch + rn_tmi_ini_s * (1._wp - zswitch) ) * tmask(:,:,1) 
    193             ztm_i_ini(:,:) = si(jp_tmi)%fnow(:,:,1) 
    194             ! 
    195             ! surface temperature => set to ice temperature if it exists 
    196             IF    ( TRIM(si(jp_tsu)%clrootname) == 'NOT USED' .AND. TRIM(si(jp_tmi)%clrootname) == 'NOT USED' ) THEN 
    197                      si(jp_tsu)%fnow(:,:,1) = ( rn_tsu_ini_n * zswitch + rn_tsu_ini_s * (1._wp - zswitch) ) * tmask(:,:,1) 
    198             ELSEIF( TRIM(si(jp_tsu)%clrootname) == 'NOT USED' .AND. TRIM(si(jp_tmi)%clrootname) /= 'NOT USED' ) THEN 
    199                      si(jp_tsu)%fnow(:,:,1) = si(jp_tmi)%fnow(:,:,1) 
     192            ! 
     193            ! temperatures 
     194            IF    ( TRIM(si(jp_tmi)%clrootname) == 'NOT USED' .AND. TRIM(si(jp_tsu)%clrootname) == 'NOT USED' .AND. & 
     195               &    TRIM(si(jp_tms)%clrootname) == 'NOT USED' ) THEN 
     196               si(jp_tmi)%fnow(:,:,1) = ( rn_tmi_ini_n * zswitch + rn_tmi_ini_s * (1._wp - zswitch) ) * tmask(:,:,1) 
     197               si(jp_tsu)%fnow(:,:,1) = ( rn_tsu_ini_n * zswitch + rn_tsu_ini_s * (1._wp - zswitch) ) * tmask(:,:,1) 
     198               si(jp_tms)%fnow(:,:,1) = ( rn_tms_ini_n * zswitch + rn_tms_ini_s * (1._wp - zswitch) ) * tmask(:,:,1) 
    200199            ENDIF 
    201             zt_su_ini(:,:) = si(jp_tsu)%fnow(:,:,1) 
    202             ! 
    203             ! snow temperature => set to ice temperature if it exists 
    204             IF    ( TRIM(si(jp_tms)%clrootname) == 'NOT USED' .AND. TRIM(si(jp_tmi)%clrootname) == 'NOT USED' ) THEN 
    205                      si(jp_tms)%fnow(:,:,1) = ( rn_tms_ini_n * zswitch + rn_tms_ini_s * (1._wp - zswitch) ) * tmask(:,:,1) 
    206             ELSEIF( TRIM(si(jp_tms)%clrootname) == 'NOT USED' .AND. TRIM(si(jp_tmi)%clrootname) /= 'NOT USED' ) THEN 
    207                      si(jp_tms)%fnow(:,:,1) = si(jp_tmi)%fnow(:,:,1) 
    208             ENDIF 
    209             ztm_s_ini(:,:) = si(jp_tms)%fnow(:,:,1) 
     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) 
    210212            ! 
    211213            ! pond concentration 
     
    213215               &     si(jp_apd)%fnow(:,:,1) = ( rn_apd_ini_n * zswitch + rn_apd_ini_s * (1._wp - zswitch) ) * tmask(:,:,1) & ! rn_apd = pond fraction => rn_apnd * a_i = pond conc. 
    214216               &                              * si(jp_ati)%fnow(:,:,1)  
    215             zapnd_ini(:,:) = si(jp_apd)%fnow(:,:,1) 
    216217            ! 
    217218            ! pond depth 
    218219            IF( TRIM(si(jp_hpd)%clrootname) == 'NOT USED' ) & 
    219220               &     si(jp_hpd)%fnow(:,:,1) = ( rn_hpd_ini_n * zswitch + rn_hpd_ini_s * (1._wp - zswitch) ) * tmask(:,:,1) 
    220             zhpnd_ini(:,:) = si(jp_hpd)%fnow(:,:,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) 
     225            ! 
     226            zsm_i_ini(:,:) = si(jp_smi)%fnow(:,:,1) * tmask(:,:,1) 
     227            ztm_i_ini(:,:) = si(jp_tmi)%fnow(:,:,1) * tmask(:,:,1) 
     228            zt_su_ini(:,:) = si(jp_tsu)%fnow(:,:,1) * tmask(:,:,1) 
     229            ztm_s_ini(:,:) = si(jp_tms)%fnow(:,:,1) * tmask(:,:,1) 
     230            zapnd_ini(:,:) = si(jp_apd)%fnow(:,:,1) * tmask(:,:,1) 
     231            zhpnd_ini(:,:) = si(jp_hpd)%fnow(:,:,1) * tmask(:,:,1) 
     232            zhlid_ini(:,:) = si(jp_hld)%fnow(:,:,1) * tmask(:,:,1) 
    221233            ! 
    222234            ! change the switch for the following 
     
    243255               zapnd_ini(:,:) = rn_apd_ini_n * zswitch(:,:) * zat_i_ini(:,:) ! rn_apd = pond fraction => rn_apd * a_i = pond conc.  
    244256               zhpnd_ini(:,:) = rn_hpd_ini_n * zswitch(:,:) 
     257               zhlid_ini(:,:) = rn_hld_ini_n * zswitch(:,:) 
    245258            ELSEWHERE 
    246259               zht_i_ini(:,:) = rn_hti_ini_s * zswitch(:,:) 
     
    253266               zapnd_ini(:,:) = rn_apd_ini_s * zswitch(:,:) * zat_i_ini(:,:) ! rn_apd = pond fraction => rn_apd * a_i = pond conc. 
    254267               zhpnd_ini(:,:) = rn_hpd_ini_s * zswitch(:,:) 
     268               zhlid_ini(:,:) = rn_hld_ini_s * zswitch(:,:) 
    255269            END WHERE 
    256270            ! 
     
    261275            zapnd_ini(:,:) = 0._wp 
    262276            zhpnd_ini(:,:) = 0._wp 
     277            zhlid_ini(:,:) = 0._wp 
     278         ENDIF 
     279 
     280         IF ( .NOT.ln_pnd_lids ) THEN 
     281            zhlid_ini(:,:) = 0._wp 
    263282         ENDIF 
    264283          
    265          !-------------! 
    266          ! fill fields ! 
    267          !-------------! 
     284         !----------------! 
     285         ! 3) fill fields ! 
     286         !----------------! 
    268287         ! select ice covered grid points 
    269288         npti = 0 ; nptidx(:) = 0 
     
    287306         CALL tab_2d_1d( npti, nptidx(1:npti), a_ip_1d(1:npti)  , zapnd_ini ) 
    288307         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 ) 
    289309 
    290310         ! allocate temporary arrays 
    291          ALLOCATE( zhi_2d(npti,jpl), zhs_2d(npti,jpl), zai_2d (npti,jpl), & 
    292             &      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) ) 
    293314          
    294315         ! distribute 1-cat into jpl-cat: (jpi*jpj) -> (jpi*jpj,jpl) 
    295          CALL ice_var_itd( h_i_1d(1:npti)  , h_s_1d(1:npti)  , at_i_1d(1:npti),                                                   & 
    296             &              zhi_2d          , zhs_2d          , zai_2d         ,                                                   & 
    297             &              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), & 
    298             &              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 ) 
    299322 
    300323         ! move to 3D arrays: (jpi*jpj,jpl) -> (jpi,jpj,jpl) 
     
    312335         CALL tab_2d_3d( npti, nptidx(1:npti), zaip_2d  , a_ip   ) 
    313336         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   ) 
    314338 
    315339         ! deallocate temporary arrays 
    316340         DEALLOCATE( zhi_2d, zhs_2d, zai_2d , & 
    317             &        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 ) 
    318342 
    319343         ! calculate extensive and intensive variables 
     
    357381 
    358382         ! Melt ponds 
    359          WHERE( a_i > epsi10 ) 
    360             a_ip_frac(:,:,:) = a_ip(:,:,:) / a_i(:,:,:) 
    361          ELSEWHERE 
    362             a_ip_frac(:,:,:) = 0._wp 
     383         WHERE( a_i > epsi10 )   ;   a_ip_eff(:,:,:) = a_ip(:,:,:) / a_i(:,:,:) 
     384         ELSEWHERE               ;   a_ip_eff(:,:,:) = 0._wp 
    363385         END WHERE 
    364386         v_ip(:,:,:) = h_ip(:,:,:) * a_ip(:,:,:) 
     387         v_il(:,:,:) = h_il(:,:,:) * a_ip(:,:,:) 
    365388           
    366389         ! specific temperatures for coupled runs 
     
    368391         t1_ice(:,:,:) = t_i (:,:,1,:) 
    369392         ! 
     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         ! 
    370400      ENDIF ! ln_iceini 
    371401      ! 
    372       at_i(:,:) = SUM( a_i, dim=3 ) 
    373       ! 
    374402      !---------------------------------------------- 
    375       ! 3) Snow-ice mass (case ice is fully embedded) 
     403      ! 4) Snow-ice mass (case ice is fully embedded) 
    376404      !---------------------------------------------- 
    377405      snwice_mass  (:,:) = tmask(:,:,1) * SUM( rhos * v_s(:,:,:) + rhoi * v_i(:,:,:), dim=3  )   ! snow+ice mass 
     
    423451         ENDIF 
    424452      ENDIF 
    425        
    426       !------------------------------------ 
    427       ! 4) store fields at before time-step 
    428       !------------------------------------ 
    429       ! it is only necessary for the 1st interpolation by Agrif 
    430       a_i_b  (:,:,:)   = a_i  (:,:,:) 
    431       e_i_b  (:,:,:,:) = e_i  (:,:,:,:) 
    432       v_i_b  (:,:,:)   = v_i  (:,:,:) 
    433       v_s_b  (:,:,:)   = v_s  (:,:,:) 
    434       e_s_b  (:,:,:,:) = e_s  (:,:,:,:) 
    435       sv_i_b (:,:,:)   = sv_i (:,:,:) 
    436       oa_i_b (:,:,:)   = oa_i (:,:,:) 
    437       u_ice_b(:,:)     = u_ice(:,:) 
    438       v_ice_b(:,:)     = v_ice(:,:) 
    439       ! total concentration is needed for Lupkes parameterizations 
    440       at_i_b (:,:)     = at_i (:,:)  
    441453 
    442454!!clem: output of initial state should be written here but it is impossible because 
     
    463475      ! 
    464476      CHARACTER(len=256) ::  cn_dir          ! Root directory for location of ice files 
    465       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 
    466478      TYPE(FLD_N), DIMENSION(jpfldi) ::   slf_i                 ! array of namelist informations on the fields to read 
    467479      ! 
    468       NAMELIST/namini/ ln_iceini, ln_iceini_file, rn_thres_sst, & 
     480      NAMELIST/namini/ ln_iceini, nn_iceini_file, rn_thres_sst, & 
    469481         &             rn_hti_ini_n, rn_hti_ini_s, rn_hts_ini_n, rn_hts_ini_s, & 
    470482         &             rn_ati_ini_n, rn_ati_ini_s, rn_smi_ini_n, rn_smi_ini_s, & 
    471483         &             rn_tmi_ini_n, rn_tmi_ini_s, rn_tsu_ini_n, rn_tsu_ini_s, rn_tms_ini_n, rn_tms_ini_s, & 
    472          &             rn_apd_ini_n, rn_apd_ini_s, rn_hpd_ini_n, rn_hpd_ini_s, & 
    473          &             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 
    474486      !!----------------------------------------------------------------------------- 
    475487      ! 
     
    485497      slf_i(jp_ati) = sn_ati  ;  slf_i(jp_smi) = sn_smi 
    486498      slf_i(jp_tmi) = sn_tmi  ;  slf_i(jp_tsu) = sn_tsu   ;   slf_i(jp_tms) = sn_tms 
    487       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 
    488500      ! 
    489501      IF(lwp) THEN                          ! control print 
     
    493505         WRITE(numout,*) '   Namelist namini:' 
    494506         WRITE(numout,*) '      ice initialization (T) or not (F)                ln_iceini      = ', ln_iceini 
    495          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 
    496508         WRITE(numout,*) '      max ocean temp. above Tfreeze with initial ice   rn_thres_sst   = ', rn_thres_sst 
    497          IF( ln_iceini .AND. .NOT.ln_iceini_file ) THEN 
     509         IF( ln_iceini .AND. nn_iceini_file == 0 ) THEN 
    498510            WRITE(numout,*) '      initial snw thickness in the north-south         rn_hts_ini     = ', rn_hts_ini_n,rn_hts_ini_s  
    499511            WRITE(numout,*) '      initial ice thickness in the north-south         rn_hti_ini     = ', rn_hti_ini_n,rn_hti_ini_s 
     
    505517            WRITE(numout,*) '      initial pnd fraction  in the north-south         rn_apd_ini     = ', rn_apd_ini_n,rn_apd_ini_s 
    506518            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 
    507520         ENDIF 
    508521      ENDIF 
    509522      ! 
    510       IF( ln_iceini_file ) THEN                      ! Ice initialization using input file 
     523      IF( nn_iceini_file == 1 ) THEN                      ! Ice initialization using input file 
    511524         ! 
    512525         ! set si structure 
     
    529542         rn_apd_ini_n = 0. ; rn_apd_ini_s = 0. 
    530543         rn_hpd_ini_n = 0. ; rn_hpd_ini_s = 0. 
    531          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. 
    532550      ENDIF 
    533551      ! 
Note: See TracChangeset for help on using the changeset viewer.