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

Last change on this file was 313, checked in by ymipsl, 10 years ago
  • implement splitting of XIOS file for lmdz physics
  • Termination is done properly in parallel by calling MPI_ABORT instead of abort or stop

YM

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