Ignore:
Timestamp:
Jun 15, 2021, 1:18:14 PM (3 years ago)
Author:
crisi
Message:

replace files by symbloic liks from phylmdiso towards phylmd.
Many files at once

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmdiso/phyetat0.F90

    r3927 r3940  
    1 ! $Id: phyetat0.F90 3581 2019-10-10 12:35:59Z oboucher $
     1! $Id: phyetat0.F90 3890 2021-05-05 15:15:06Z jyg $
    22
    33SUBROUTINE phyetat0 (fichnom, clesphy0, tabcntr0)
     
    1919       ftsol, pbl_tke, pctsrf, q_ancien, ql_ancien, qs_ancien, radpas, radsol, rain_fall, ratqs, &
    2020       rnebcon, rugoro, sig1, snow_fall, solaire_etat0, sollw, sollwdown, &
    21        solsw, t_ancien, u_ancien, v_ancien, w01, wake_cstar, wake_deltaq, &
    22        wake_deltat, wake_delta_pbl_TKE, delta_tsurf, wake_fip, wake_pe, &
     21       solsw, solswfdiff, t_ancien, u_ancien, v_ancien, w01, wake_cstar, wake_deltaq, &
     22       wake_deltat, wake_delta_pbl_TKE, delta_tsurf, beta_aridity, wake_fip, wake_pe, &
    2323       wake_s, wake_dens, zgam, zmax0, zmea, zpic, zsig, &
    2424#ifdef ISO
     
    2727#endif
    2828       zstd, zthe, zval, ale_bl, ale_bl_trig, alp_bl, u10m, v10m, treedrg, &
    29        ale_wake, ale_bl_stat
     29       ale_wake, ale_bl_stat, ds_ns, dt_ns, delta_sst, delta_sal, ratqs_inter
    3030!FC
    3131  USE geometry_mod, ONLY : longitude_deg, latitude_deg
     
    3838  USE ocean_slab_mod, ONLY: nslay, tslab, seaice, tice, ocean_slab_init
    3939  USE time_phylmdz_mod, ONLY: init_iteration, pdtphys, itau_phy
     40#ifdef CPP_XIOS
     41  USE wxios, ONLY: missing_val
     42#else
     43  use netcdf, only: missing_val => nf90_fill_real
     44#endif
     45  use config_ocean_skin_m, only: activate_ocean_skin
    4046#ifdef ISO
    4147  USE infotrac_phy, ONLY: ntraciso,niso,iso_num
     
    5258  ! Objet: Lecture de l'etat initial pour la physique
    5359  !======================================================================
    54   include "netcdf.inc"
    5560  include "dimsoil.h"
    5661  include "clesphys.h"
     
    330335
    331336  found=phyetat0_get(1,solsw,"solsw","net SW radiation surf",0.)
     337  found=phyetat0_get(1,solswfdiff,"solswfdiff","fraction of SW radiation surf that is diffuse",1.)
    332338  found=phyetat0_get(1,sollw,"sollw","net LW radiation surf",0.)
    333339  found=phyetat0_get(1,sollwdown,"sollwdown","down LW radiation surf",0.)
    334340  IF (.NOT. found) THEN
    335      sollwdown = 0. ;  zts=0.
    336      do nsrf=1,nbsrf
     341     sollwdown(:) = 0. ;  zts(:)=0.
     342     DO nsrf=1,nbsrf
    337343        zts(:)=zts(:)+ftsol(:,nsrf)*pctsrf(:,nsrf)
    338      enddo
     344     ENDDO
    339345     sollwdown(:)=sollw(:)+RSIGMA*zts(:)**4
    340346  ENDIF
     
    413419  IF (iflag_pbl>1 .AND. iflag_wake>=1  .AND. iflag_pbl_split >=1 ) then
    414420    found=phyetat0_srf(klev+1,wake_delta_pbl_tke,"DELTATKE","Del TKE wk/env",0.)
    415     found=phyetat0_srf(1,delta_tsurf,"DELTA_TSURF","Delta Ts wk/env ",0.)
     421!!    found=phyetat0_srf(1,delta_tsurf,"DELTA_TSURF","Delta Ts wk/env ",0.)
     422    found=phyetat0_srf(1,delta_tsurf,"DELTATS","Delta Ts wk/env ",0.)
     423!!    found=phyetat0_srf(1,beta_aridity,"BETA_S","Aridity factor ",1.)
     424    found=phyetat0_srf(1,beta_aridity,"BETAS","Aridity factor ",1.)
    416425  ENDIF   !(iflag_pbl>1 .AND. iflag_wake>=1 .AND. iflag_pbl_split >=1 )
    417426
     
    452461  found=phyetat0_get(1,ale_bl_stat,"ALE_BL_STAT","ALE_BL_STAT",0.)
    453462
     463! fisrtilp/Clouds 0.002 could be ratqsbas. But can stay like this as well
     464  found=phyetat0_get(klev,ratqs_inter,"RATQS_INTER","Relative width of the lsc sugrid scale water",0.002)
     465
     466
    454467!===========================================
    455468  ! Read and send field trs to traclmdz
     
    468481  ENDIF
    469482
    470 !--OB now this is for co2i
    471   IF (type_trac == 'co2i') THEN
     483!--OB now this is for co2i - ThL: and therefore also for inco
     484  IF (type_trac == 'co2i' .OR. type_trac == 'inco') THEN
    472485     IF (carbon_cycle_cpl) THEN
    473486        ALLOCATE(co2_send(klon), stat=ierr)
     
    564577  ENDIF ! Slab       
    565578
     579  if (activate_ocean_skin >= 1) then
     580     if (activate_ocean_skin == 2 .and. type_ocean == 'couple') then
     581        found = phyetat0_get(1, delta_sal, "delta_sal", &
     582             "ocean-air interface salinity minus bulk salinity", 0.)
     583        found = phyetat0_get(1, delta_sst, "delta_SST", &
     584             "ocean-air interface temperature minus bulk SST", 0.)
     585     end if
     586     
     587     found = phyetat0_get(1, ds_ns, "dS_ns", "delta salinity near surface", 0.)
     588     found = phyetat0_get(1, dt_ns, "dT_ns", "delta temperature near surface", &
     589          0.)
     590
     591     where (pctsrf(:, is_oce) == 0.)
     592        ds_ns = missing_val
     593        dt_ns = missing_val
     594        delta_sst = missing_val
     595        delta_sal = missing_val
     596     end where
     597  end if
     598 
     599
    566600  ! on ferme le fichier
    567601  CALL close_startphy
Note: See TracChangeset for help on using the changeset viewer.