Ignore:
Timestamp:
Jan 11, 2021, 11:24:08 PM (3 years ago)
Author:
lguez
Message:

Sync latest trunk changes to Ocean_skin

Location:
LMDZ6/branches/Ocean_skin
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Ocean_skin

  • LMDZ6/branches/Ocean_skin/libf/dynphy_lonlat/phylmd/etat0phys_netcdf.F90

    r3605 r3798  
    4242  USE conf_dat_m,         ONLY: conf_dat2d
    4343  USE phys_state_var_mod, ONLY: zmea, zstd, zsig, zgam, zthe, zpic, zval, z0m, &
    44           solsw, radsol, t_ancien, wake_deltat, wake_s,  rain_fall, qsol, z0h, &
     44          solsw, solswfdiff, radsol, t_ancien, wake_deltat, wake_s,  rain_fall, qsol, z0h, &
    4545          sollw,sollwdown, rugoro, q_ancien, wake_deltaq, wake_pe, snow_fall, ratqs,w01, &
    4646    sig1, ftsol, clwcon, fm_therm, wake_Cstar,  pctsrf,  entr_therm,radpas, f0,&
     
    107107  REAL, DIMENSION(SIZE(masque,1),SIZE(masque,2)) :: masque_tmp,phiso
    108108  REAL, DIMENSION(klon)               :: sn, rugmer, run_off_lic_0, fder
    109   REAL, DIMENSION(klon,nbsrf)         :: qsolsrf, snsrf
     109  REAL, DIMENSION(klon,nbsrf)         :: qsurf, snsrf
    110110  REAL, DIMENSION(klon,nsoilmx,nbsrf) :: tsoil
    111111
     
    121121  LOGICAL :: flag_aer_feedback
    122122  LOGICAL :: flag_bc_internal_mixture
    123   LOGICAL :: new_aod
    124123  REAL    :: bl95_b0, bl95_b1
    125124  INTEGER :: read_climoz                        !--- Read ozone climatology
     
    143142                   chemistry_couple, flag_aerosol, flag_aerosol_strat,  &
    144143                   flag_aer_feedback,                                   &
    145                    new_aod, flag_bc_internal_mixture, bl95_b0, bl95_b1, &
     144                   flag_bc_internal_mixture, bl95_b0, bl95_b1, &
    146145                   read_climoz, alp_offset)
    147146  CALL phys_state_var_init(read_climoz)
     
    193192  WRITE(lunout,*)'phystep =', phystep, radpas
    194193
    195 ! Init: ftsol, snsrf, qsolsrf, tsoil, rain_fall, snow_fall, solsw, sollw, z0
     194! Init: ftsol, snsrf, qsurf, tsoil, rain_fall, snow_fall, solsw, sollw, z0
    196195!*******************************************************************************
    197196  DO i=1,nbsrf; ftsol(:,i) = tsol; END DO
     
    210209
    211210  fevap(:,:) = 0.
    212   DO i=1,nbsrf; qsolsrf(:,i)=150.; END DO
     211  qsurf = 0.
    213212  DO i=1,nbsrf; DO j=1,nsoilmx; tsoil(:,j,i) = tsol; END DO; END DO
    214213  rain_fall  = 0.
    215214  snow_fall  = 0.
    216215  solsw      = 165.
     216  solswfdiff = 1.
    217217  sollw      = -53.
    218218!ym warning missing init for sollwdown => set to 0
     
    272272
    273273  CALL fonte_neige_init(run_off_lic_0)
    274   CALL pbl_surface_init( fder, snsrf, qsolsrf, tsoil )
     274  CALL pbl_surface_init( fder, snsrf, qsurf, tsoil )
    275275  CALL phyredem( "startphy.nc" )
    276276
  • LMDZ6/branches/Ocean_skin/libf/dynphy_lonlat/phylmd/iniphysiq_mod.F90

    r3605 r3798  
    2525                      indnum_fn_num,index_trac,&
    2626                      niso,ntraceurs_zone,ntraciso
     27#ifdef CPP_StratAer
     28  USE infotrac, ONLY: nbtr_bin, nbtr_sulgas, id_OCS_strat, &
     29                      id_SO2_strat, id_H2SO4_strat, id_BIN01_strat
     30
     31#endif
    2732#ifdef REPROBUS
    2833  USE CHEM_REP, ONLY : Init_chem_rep_phys
     34#ifdef CPP_PARA
     35  USE parallel_lmdz, ONLY : mpi_size, mpi_rank
     36  USE bands, ONLY : distrib_phys
     37#endif
     38  USE mod_phys_lmdz_omp_data, ONLY: klon_omp
    2939#endif
    3040  USE control_mod, ONLY: dayref,anneeref,day_step,nday,offline, iphysiq, config_inca
     
    4656  USE ioipsl_getin_p_mod, ONLY: getin_p
    4757  USE slab_heat_transp_mod, ONLY: ini_slab_transp_geom
    48 #ifdef REPROBUS
    49   USE CHEM_REP, ONLY : Init_chem_rep_phys
    50 #endif
    5158  IMPLICIT NONE
    5259
     
    147154                         iso_indnum,zone_num,phase_num,&
    148155                         indnum_fn_num,index_trac,&
    149                          niso,ntraceurs_zone,ntraciso)
     156                         niso,ntraceurs_zone,ntraciso&
     157#ifdef CPP_StratAer
     158                         ,nbtr_bin,nbtr_sulgas&
     159                         ,id_OCS_strat,id_SO2_strat,id_H2SO4_strat,id_BIN01_strat&
     160#endif
     161                         )
    150162
    151163  ! Initializations for Reprobus
    152164  IF (type_trac == 'repr') THEN
    153165#ifdef REPROBUS
    154     CALL Init_chem_rep_phys(klon_omp,nlayer)
     166    call Init_chem_rep_phys(klon_omp,nlayer)
     167    call init_reprobus_para( &
     168          nbp_lon,nbp_lat,nbp_lev,klon_glo,mpi_size, &
     169          distrib_phys,communicator)
    155170#endif
    156171  ENDIF
     
    168183#endif
    169184  END IF
     185  IF (type_trac == 'repr') THEN
     186#ifdef REPROBUS
     187    call init_reprobus_para( &
     188          nbp_lon,nbp_lat,nbp_lev,klon_glo,mpi_size, &
     189          distrib_phys,communicator)
     190#endif
     191  ENDIF
    170192
    171193!!$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/)
Note: See TracChangeset for help on using the changeset viewer.