source: trunk/LMDZ.COMMON/libf/phy_common/geometry_mod.F90 @ 3452

Last change on this file since 3452 was 3242, checked in by emillour, 9 months ago

Common physics:
Undo previous commit: revert geometry_mod to previous state.
EM

File size: 3.5 KB
Line 
1MODULE geometry_mod
2
3! Store informations concerning the local (to MPI/OpenMP core) geometry
4
5  REAL,SAVE,ALLOCATABLE :: longitude(:) ! longitude of the cell (rad)
6!$OMP THREADPRIVATE(longitude)
7
8  REAL,SAVE,ALLOCATABLE :: latitude(:)! latitude of the cell (rad)
9!$OMP THREADPRIVATE(latitude)
10
11  REAL,SAVE,ALLOCATABLE :: longitude_deg(:) ! longitude of the cell (degree)
12!$OMP THREADPRIVATE(longitude_deg)
13
14  REAL,SAVE,ALLOCATABLE :: latitude_deg(:)! latitude of the cell (degree)
15!$OMP THREADPRIVATE(latitude_deg)
16
17  REAL,SAVE,ALLOCATABLE :: boundslon(:,:)  ! boundaries of the cell (rad)
18!$OMP THREADPRIVATE(boundslon)
19
20  REAL,SAVE,ALLOCATABLE :: boundslat(:,:) ! boundaries of the cell (rad)
21!$OMP THREADPRIVATE(boundslat)
22
23  REAL,SAVE,ALLOCATABLE :: dx(:)      ! resolution of longitude cell (valid only for 2D grid)
24!$OMP THREADPRIVATE(dx)
25 
26  REAL,SAVE,ALLOCATABLE :: dy(:)      ! resolution of latitude cell (valid only for 2D grid)
27!$OMP THREADPRIVATE(dy)
28
29  REAL,SAVE,ALLOCATABLE :: cell_area(:) ! area of the cell (m2)
30!$OMP THREADPRIVATE(cell_area)
31
32  REAL,SAVE,ALLOCATABLE :: cell_area_for_lonlat_outputs(:)
33                           ! for lon-lat outputs only: area of the cell
34                           ! but with polar values as in dyn grid
35                           ! (with replicated polar grid point)
36!$OMP THREADPRIVATE(cell_area_for_lonlat_outputs)
37
38  INTEGER,SAVE,ALLOCATABLE :: ind_cell_glo(:)      ! global index of a local cell
39!$OMP THREADPRIVATE(ind_cell_glo)
40
41CONTAINS
42
43  SUBROUTINE init_geometry(klon,longitude_,latitude_, &
44                           boundslon_,boundslat_, &
45                           cell_area_,ind_cell_glo_,dx_,dy_)
46  USE mod_grid_phy_lmdz, ONLY: nvertex
47  USE nrtype, ONLY : PI
48  IMPLICIT NONE
49    INTEGER,INTENT(IN) :: klon ! number of columns for this MPI/OpenMP domain
50    REAL,INTENT(IN) :: longitude_(klon)
51    REAL,INTENT(IN) :: latitude_(klon)
52    REAL,INTENT(IN) :: boundslon_(klon,nvertex)
53    REAL,INTENT(IN) :: boundslat_(klon,nvertex)
54    REAL,INTENT(IN) :: cell_area_(klon)
55    INTEGER,OPTIONAL,INTENT(IN) :: ind_cell_glo_(klon)
56    REAL,OPTIONAL,INTENT(IN) :: dx_(klon)
57    REAL,OPTIONAL,INTENT(IN) :: dy_(klon)
58   
59    ALLOCATE(longitude(klon))
60    ALLOCATE(latitude(klon))
61    ALLOCATE(longitude_deg(klon))
62    ALLOCATE(latitude_deg(klon))
63    ALLOCATE(boundslon(klon,nvertex))
64    ALLOCATE(boundslat(klon,nvertex))
65    ALLOCATE(cell_area(klon))
66    IF (PRESENT(ind_cell_glo_)) ALLOCATE(ind_cell_glo(klon))
67    IF (PRESENT(dx_)) ALLOCATE(dx(klon))
68    IF (PRESENT(dy_))ALLOCATE(dy(klon))
69   
70    longitude(:) = longitude_(:)
71    latitude(:) = latitude_(:)
72    longitude_deg(:) = longitude(:)*180./PI
73    latitude_deg(:) = latitude(:)*180./PI
74    boundslon(:,:) = boundslon_(:,:)
75    boundslat(:,:) = boundslat_(:,:)
76    cell_area(:) = cell_area_(:)
77    IF (PRESENT(ind_cell_glo_)) ind_cell_glo(:) = ind_cell_glo_(:)
78    IF (PRESENT(dx_)) dx(:) = dx_(:)
79    IF (PRESENT(dy_)) dy(:) = dy_(:)
80   
81  END SUBROUTINE init_geometry
82
83
84  SUBROUTINE init_geometry_cell_area_for_outputs(klon, &
85                                                 cell_area_for_lonlat_outputs_)
86  IMPLICIT NONE
87  INTEGER,INTENT(IN) :: klon ! number of columns for this MPI/OpenMP domain
88  REAL,INTENT(IN) :: cell_area_for_lonlat_outputs_(klon) ! tweaked lon-lat mesh
89                     ! cell areas where polar values are as on dyn lon-lat grid
90                     ! for outputs
91 
92  ALLOCATE(cell_area_for_lonlat_outputs(klon))
93  cell_area_for_lonlat_outputs(1:klon)=cell_area_for_lonlat_outputs_(1:klon)
94 
95  END SUBROUTINE init_geometry_cell_area_for_outputs
96
97END MODULE geometry_mod
98
Note: See TracBrowser for help on using the repository browser.