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/phyetat0_mod.f90

    r5790 r5791  
    1616  USE fonte_neige_mod,  ONLY : fonte_neige_init
    1717  USE pbl_surface_mod,  ONLY : pbl_surface_init
    18   USE surface_data,     ONLY : type_ocean, version_ocean
     18!GG  USE surface_data,     ONLY : type_ocean, version_ocean
     19  USE surface_data,     ONLY : type_ocean, version_ocean, iflag_seaice, &
     20                                   iflag_seaice_alb, iflag_leads
     21!GG
    1922  USE phyetat0_get_mod, ONLY : phyetat0_get, phyetat0_srf
    2023  USE phys_state_var_mod, ONLY : ancien_ok, clwcon, detr_therm, phys_tstep, &
     
    2427       ftsol, pbl_tke, pctsrf, q_ancien, ql_ancien, qs_ancien, qbs_ancien, &
    2528       cf_ancien, qvc_ancien, qvcon, qccon, cfc_ancien, qtc_ancien, nic_ancien, &
    26        radpas, radsol, rain_fall, &
    27        ratqs, rnebcon, rugoro, sig1, snow_fall, bs_fall, solaire_etat0, sollw, sollwdown, &
     29       tke_ancien, radpas, radsol, rain_fall, ratqs, &
     30       rnebcon, rugoro, sig1, snow_fall, bs_fall, solaire_etat0, sollw, sollwdown, &
    2831       solsw, solswfdiff, t_ancien, u_ancien, v_ancien, w01, wake_cstar, wake_deltaq, &
    2932       wake_deltat, wake_delta_pbl_TKE, delta_tsurf, beta_aridity, wake_fip, wake_pe, &
     
    3134       zstd, zthe, zval, ale_bl, ale_bl_trig, alp_bl, u10m, v10m, treedrg, &
    3235       ale_wake, ale_bl_stat, ds_ns, dt_ns, delta_sst, delta_sal, dter, dser, &
    33        dt_ds, ratqs_inter_, frac_tersrf, z0m_tersrf, ratio_z0m_z0h_tersrf, &
     36!GG       dt_ds, ratqs_inter_
     37       dt_ds, ratqs_inter_, &
     38       hice, tice, bilg_cumul, &
     39!GG
     40       frac_tersrf, z0m_tersrf, ratio_z0m_z0h_tersrf, &
    3441       albedo_tersrf, beta_tersrf, inertie_tersrf, alpha_soil_tersrf, &
    3542       period_tersrf, hcond_tersrf, tsurfi_tersrf, tsoili_tersrf, tsoil_depth, &
     
    4451  USE carbon_cycle_mod, ONLY: carbon_cycle_init, carbon_cycle_cpl, carbon_cycle_tr, carbon_cycle_rad, co2_send, RCO2_glo
    4552  USE indice_sol_mod,   ONLY: nbsrf, is_ter, epsfra, is_lic, is_oce, is_sic
    46   USE ocean_slab_mod,   ONLY: nslay, tslab, seaice, tice, ocean_slab_init
     53  !GG USE ocean_slab_mod,   ONLY: nslay, tslab, seaice, tice, ocean_slab_init
     54  USE ocean_slab_mod,   ONLY: nslay, tslab, seaice, tice_slab, ocean_slab_init
     55  !GG
    4756  USE time_phylmdz_mod, ONLY: init_iteration, pdtphys, itau_phy
    4857  use wxios_mod, ONLY: missing_val_xios => missing_val, using_xios
     
    163172  IF (ok_orolf) tab_cntrl(11) =1.
    164173  IF (ok_limitvrai) tab_cntrl(12) =1.
     174  !GG
     175  tab_cntrl(18) =iflag_seaice
     176  tab_cntrl(19) =iflag_seaice_alb
     177  tab_cntrl(20) =iflag_leads
     178  !GG
    165179
    166180  itau_phy = tab_cntrl(15)
     
    536550!==================================
    537551!
    538   IF (iflag_pbl>1) then
     552  ! cas specifique de l'advection de TKE
     553  IF (ok_advtke) THEN
     554       ancien_ok=ancien_ok.AND.phyetat0_get(tke_ancien,"TKEANCIEN","TKEANCIEN",0.)
     555  ELSE
     556    tke_ancien(:,:)=0.
     557  ENDIF
     558
     559  IF (ok_advtke) THEN
     560    IF ( (maxval(tke_ancien).EQ.minval(tke_ancien))) THEN
     561       ancien_ok=.false.
     562    ENDIF
     563  ENDIF
     564
     565  IF ((iflag_pbl>1)) then
    539566     found=phyetat0_srf(pbl_tke,"TKE","Turb. Kinetic. Energ. ",1.e-8)
    540567  ENDIF
     
    659686      ! Sea ice variables
    660687      IF (version_ocean == 'sicINT') THEN
    661           found=phyetat0_get(tice,"slab_tice","slab_tice",0.)
     688          found=phyetat0_get(tice_slab,"slab_tice","slab_tice",0.)
     689  !GG        found=phyetat0_get(tice,"slab_tice","slab_tice",0.)
    662690          IF (.NOT. found) THEN
    663               PRINT*, "phyetat0: Le champ <tice> est absent"
     691  !GG            PRINT*, "phyetat0: Le champ <tice> est absent"
     692              PRINT*, "phyetat0: Le champ <tice_slab> est absent"
    664693              PRINT*, "Initialisation a tsol_sic"
    665                   tice(:)=ftsol(:,is_sic)
     694  !GG                tice(:)=ftsol(:,is_sic)
     695                  tice_slab(:)=ftsol(:,is_sic)
    666696          ENDIF
    667697          found=phyetat0_get(seaice,"seaice","seaice",0.)
     
    710740  end if
    711741
     742  !GG
     743  ! Sea ice
     744  !IF (iflag_seaice == 2) THEN
     745
     746  found=phyetat0_get(hice,"hice","Ice thickness",0.)
     747  IF (.NOT. found) THEN
     748       PRINT*, "phyetat0: Le champ <hice> est absent"
     749       PRINT*, "Initialisation a hice=1m "
     750       hice(:)=1.0
     751  END IF
     752  found=phyetat0_get(tice,"tice","Sea Ice temperature",0.)
     753  IF (.NOT. found) THEN
     754       PRINT*, "phyetat0: Le champ <tice> est absent"
     755       PRINT*, "Initialisation a tsol_sic"
     756       tice(:)=ftsol(:,is_sic)
     757  END IF
     758  found=phyetat0_get(bilg_cumul,"bilg_cumul","Flux conductivite + transmit sea-ice",0.)
     759  IF (.NOT. found) THEN
     760       PRINT*, "phyetat0: Le champ <bilg_cumul> est absent"
     761       PRINT*, "Initialisation a zero"
     762       bilg_cumul(:)=0.0
     763  END IF
     764
     765  !END IF
     766  !GG
    712767  ! on ferme le fichier
    713768  CALL close_startphy
     
    716771
    717772  if ( iflag_physiq <= 1 ) then
    718   CALL pbl_surface_init(fder, snow, qsurf, tsoil)
     773  !GG CALL pbl_surface_init(fder, snow, qsurf, tsoil)
     774  CALL pbl_surface_init(fder, snow, qsurf, tsoil, hice, tice, bilg_cumul)
     775  !GG
    719776  endif
    720777
Note: See TracChangeset for help on using the changeset viewer.