SUBROUTINE initialize_unstructured_physics(nbp, nlayer, communicator, nb_proc, distrib, & punjours, pdayref,ptimestep, lat,lon,area, & prad,pg,pr,pcpp, preff,ap,bp ) USE mod_phys_lmdz_para USE mod_grid_phy_lmdz USE dimphy USE comgeomphy, only : initcomgeomphy, & airephy, & ! physics grid area (m2) rlond, & ! longitudes rlatd ! latitudes USE infotrac, only : nqtot ! number of advected tracers USE planete_mod, only: ini_planete_mod IMPLICIT NONE INTEGER,INTENT(in) :: nbp ! nb point for the current mpi process INTEGER,INTENT(in) :: nlayer ! number of atmospheric layers INTEGER,INTENT(in) :: communicator ! current MPI communicataor INTEGER,INTENT(in) :: nb_proc ! nb processor in the current communicator INTEGER,INTENT(in) :: distrib(0:nb_proc-1) ! nb point for alll mpi_process REAL,INTENT(in) :: prad ! radius of the planet (m) REAL,INTENT(in) :: pg ! gravitational acceleration (m/s2) REAL,INTENT(in) :: pr ! ! reduced gas constant R/mu REAL,INTENT(in) :: pcpp ! specific heat Cp REAL,INTENT(in) :: punjours ! length (in s) of a standard day REAL,INTENT(in) :: lat(nbp) ! latitudes of the physics grid REAL,INTENT(in) :: lon(nbp) ! longitudes of the physics grid REAL,INTENT(in) :: area(nbp) ! area (m2) INTEGER,INTENT(in) :: pdayref ! reference day of for the simulation REAL,INTENT(in) :: ptimestep ! physics time step (s) REAL,INTENT(in) :: preff ! reference surface pressure (Pa) REAL,INTENT(in) :: ap(nlayer+1) ! hybrid coordinate at interfaces REAL,INTENT(in) :: bp(nlayer+1) ! hybrid coordinate at interfaces INTEGER :: offset REAL,SAVE,ALLOCATABLE :: plat(:) ! latitudes of the physics grid REAL,SAVE,ALLOCATABLE :: plon(:) ! longitudes of the physics grid REAL,SAVE,ALLOCATABLE :: parea(:) ! area (m2) ALLOCATE(plat(nbp),plon(nbp),parea(nbp)) plat(:)=lat(:) plon(:)=lon(:) parea(:)=area(:) CALL init_grid_phy_lmdz(nbp,1,sum(distrib),nlayer) CALL init_phys_lmdz_para(nbp,1,communicator,nb_proc,distrib) !$OMP PARALLEL CALL init_dimphy(klon_omp,nbp_lev) CALL initcomgeomphy offset=0 airephy(1:klon_omp)=parea(offset+klon_omp_begin:offset+klon_omp_end) rlond(1:klon_omp)=plon(offset+klon_omp_begin:offset+klon_omp_end) rlatd(1:klon_omp)=plat(offset+klon_omp_begin:offset+klon_omp_end) ! copy over preff , ap() and bp() CALL ini_planete_mod(nlayer,preff,ap,bp) ! copy some fundamental parameters to physics ! and do some initializations CALL inifis(klon_omp,nlayer,nqtot,pdayref,punjours,ptimestep, & rlatd,rlond,airephy,prad,pg,pr,pcpp) !$OMP END PARALLEL END SUBROUTINE initialize_unstructured_physics