source: codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/dyn3dpar/initialize_physics.F90 @ 245

Last change on this file since 245 was 245, checked in by ymipsl, 10 years ago
  • One call for initialize physics from dynamico
  • mpi_root renamed into mpi_master due to conflict with an existaing symbol from the mpi library

==> mpi_root => mpi_master, is_mpi_root => is_mpi_master, is_omp_root => is_omp_master

YM

File size: 2.9 KB
Line 
1SUBROUTINE initialize_unstructured_physics(nbp, nlayer, communicator, nb_proc, distrib, &
2                                           punjours, pdayref,ptimestep, lat,lon,area, &
3                                           prad,pg,pr,pcpp, preff,ap,bp )
4USE mod_phys_lmdz_para
5USE mod_grid_phy_lmdz
6USE dimphy
7USE comgeomphy, only :   initcomgeomphy, &
8                         airephy, & ! physics grid area (m2)
9                         rlond, & ! longitudes
10                         rlatd ! latitudes
11USE infotrac, only : nqtot ! number of advected tracers
12USE planete_mod, only: ini_planete_mod
13IMPLICIT NONE
14
15                                           
16    INTEGER,INTENT(in) :: nbp     ! nb point for the current mpi process
17    INTEGER,INTENT(in) :: nlayer  ! number of atmospheric layers
18    INTEGER,INTENT(in) :: communicator ! current MPI communicataor
19    INTEGER,INTENT(in) :: nb_proc      ! nb processor in the current communicator
20    INTEGER,INTENT(in) :: distrib(0:nb_proc-1)  ! nb point for alll mpi_process
21    REAL,INTENT(in)    :: prad ! radius of the planet (m)
22    REAL,INTENT(in)    :: pg ! gravitational acceleration (m/s2)
23    REAL,INTENT(in)    :: pr ! ! reduced gas constant R/mu
24    REAL,INTENT(in)    :: pcpp ! specific heat Cp
25    REAL,INTENT(in)    :: punjours ! length (in s) of a standard day
26    REAL,INTENT(in)    :: lat(nbp) ! latitudes of the physics grid
27    REAL,INTENT(in)    :: lon(nbp) ! longitudes of the physics grid
28    REAL,INTENT(in)    :: area(nbp) ! area (m2)
29    INTEGER,INTENT(in) :: pdayref ! reference day of for the simulation
30    REAL,INTENT(in)    :: ptimestep ! physics time step (s)
31    REAL,INTENT(in)    :: preff      ! reference surface pressure (Pa)
32    REAL,INTENT(in)    :: ap(nlayer+1) ! hybrid coordinate at interfaces
33    REAL,INTENT(in)    :: bp(nlayer+1) ! hybrid coordinate at interfaces
34
35    INTEGER :: offset
36    REAL,SAVE,ALLOCATABLE    :: plat(:) ! latitudes of the physics grid
37    REAL,SAVE,ALLOCATABLE    :: plon(:) ! longitudes of the physics grid
38    REAL,SAVE,ALLOCATABLE    :: parea(:) ! area (m2)
39
40    ALLOCATE(plat(nbp),plon(nbp),parea(nbp))
41    plat(:)=lat(:)
42    plon(:)=lon(:)
43    parea(:)=area(:)
44   
45    CALL init_grid_phy_lmdz(nbp,1,sum(distrib),nlayer)
46    CALL init_phys_lmdz_para(nbp,1,communicator,nb_proc,distrib)
47
48
49!$OMP PARALLEL
50    CALL init_dimphy(klon_omp,nbp_lev)
51    CALL initcomgeomphy
52   
53    offset=0
54    airephy(1:klon_omp)=parea(offset+klon_omp_begin:offset+klon_omp_end)
55    rlond(1:klon_omp)=plon(offset+klon_omp_begin:offset+klon_omp_end)
56    rlatd(1:klon_omp)=plat(offset+klon_omp_begin:offset+klon_omp_end)
57
58! copy over preff , ap() and bp()
59    CALL ini_planete_mod(nlayer,preff,ap,bp)
60
61! copy some fundamental parameters to physics
62! and do some initializations
63    CALL inifis(klon_omp,nlayer,nqtot,pdayref,punjours,ptimestep, &
64                rlatd,rlond,airephy,prad,pg,pr,pcpp)
65           
66!$OMP END PARALLEL
67
68END SUBROUTINE initialize_unstructured_physics
Note: See TracBrowser for help on using the repository browser.