Ignore:
Timestamp:
Jul 28, 2025, 7:23:15 PM (6 days ago)
Author:
aborella
Message:

Merge with trunk r5789

Location:
LMDZ6/branches/contrails
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/contrails

  • LMDZ6/branches/contrails/libf/phylmd/dyn1d/old_lmdz1d.f90

    r5626 r5791  
    55      SUBROUTINE old_lmdz1d
    66
    7 USE flux_arp_mod_h
     7   USE flux_arp_mod_h
    88      USE compbl_mod_h
    99         USE clesphys_mod_h
    1010      USE ioipsl, only: ju2ymds, ymds2ju, ioconf_calendar,getin
     11   USE phyetat0_get_mod, ONLY : phyetat0_get, phyetat0_srf
    1112   USE phys_state_var_mod, ONLY : phys_state_var_init, phys_state_var_end, &
    1213       clwcon, detr_therm, &
     
    219220      real :: run_off_lic_0(1)
    220221      real :: fder(1),snsrf(1,nbsrf),qsurfsrf(1,nbsrf)
     222      real :: hice(1), tice(1), bilg_cumul(1)
    221223      real :: tsoil(1,nsoilmx,nbsrf)
    222224!     real :: agesno(1,nbsrf)
     
    267269!                           <> 0, tendencies of forcing are not added
    268270      INTEGER :: flag_inhib_forcing = 0
     271      LOGICAL :: found
    269272
    270273!=====================================================================
     
    821824!       tsoil(1,11,1)=308.00
    822825!-----------------------------------------------------------------------
    823         call pbl_surface_init(fder, snsrf, qsurfsrf, tsoil)
     826  !GG
     827  ! Sea ice
     828  !IF (iflag_seaice == 2) THEN
     829
     830     hice(:)=1.0
     831     tice(:)=ftsol(:,is_sic)
     832     bilg_cumul(:)=0.0
     833
     834
     835  !END IF
     836  !GG
     837        call pbl_surface_init(fder, snsrf, qsurfsrf, tsoil, hice, tice, bilg_cumul)
    824838
    825839!------------------ prepare limit conditions for limit.nc -----------------
Note: See TracChangeset for help on using the changeset viewer.