source: dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/geometry_mod.f90 @ 3825

Last change on this file since 3825 was 3825, checked in by ymipsl, 10 years ago

Reorganize geometry and grid modules. Prepare physics for unstructutured grid support. Simplify initialization of physics from dynamic.
Compiled only with dynd3dmem, but not tested for moment.

YM

File size: 2.1 KB
Line 
1MODULE geometry_mod
2
3
4  REAL,SAVE,ALLOCATABLE :: longitude(:) ! longitude of the cell (rad)
5!$OMP THREADPRIVATE(longitude)
6
7  REAL,SAVE,ALLOCATABLE :: latitude(:)! latitude of the cell (rad)
8!$OMP THREADPRIVATE(latitude)
9
10  REAL,SAVE,ALLOCATABLE :: lon_degrees(:) ! longitude of the cell (degree)
11!$OMP THREADPRIVATE(lon_degrees)
12
13  REAL,SAVE,ALLOCATABLE :: lat_degrees(:)! latitude of the cell (degree)
14!$OMP THREADPRIVATE(lat_degrees)
15
16  REAL,SAVE,ALLOCATABLE :: boundslon(:,:)  ! boundaries of the cell (rad)
17!$OMP THREADPRIVATE(boundslon)
18
19  REAL,SAVE,ALLOCATABLE :: boundslat(:,:) ! boundaries of the cell (rad)
20!$OMP THREADPRIVATE(boundslat)
21
22  REAL,SAVE,ALLOCATABLE :: dx(:)      ! resolution of longitude cell (valid only for 2D grid)
23!$OMP THREADPRIVATE(dx)
24 
25  REAL,SAVE,ALLOCATABLE :: dy(:)      ! resolution of latitude cell (valid only for 2D grid)
26!$OMP THREADPRIVATE(dy)
27
28  REAL,SAVE,ALLOCATABLE :: cell_area(:)      ! area of the cell
29!$OMP THREADPRIVATE(cell_area)
30
31
32CONTAINS
33
34  SUBROUTINE init_geometry(longitude_, latitude_, boundslon_, boundslat_, cell_area_, dx_, dy_)
35  USE dimphy, ONLY: klon
36  USE mod_grid_phy_lmdz, ONLY: nvertex
37  USE nrtype, ONLY : PI
38  IMPLICIT NONE
39    REAL :: longitude_(klon)
40    REAL :: latitude_(klon)
41    REAL :: boundslon_(klon,nvertex)
42    REAL :: boundslat_(klon,nvertex)
43    REAL :: cell_area_(klon)
44    REAL,OPTIONAL :: dx_(klon)
45    REAL,OPTIONAL :: dy_(klon)
46   
47    ALLOCATE(longitude(klon))
48    ALLOCATE(latitude(klon))
49    ALLOCATE(lon_degrees(klon))
50    ALLOCATE(lat_degrees(klon))
51    ALLOCATE(boundslon(klon,nvertex))
52    ALLOCATE(boundslat(klon,nvertex))
53    ALLOCATE(cell_area(klon))
54    IF (PRESENT(dx_)) ALLOCATE(dx(klon))
55    IF (PRESENT(dy_))ALLOCATE(dy(klon))
56   
57    longitude(:) = longitude_(:)
58    latitude(:) = latitude_(:)
59    lon_degrees(:) = longitude(:)*180./PI
60    lat_degrees(:) = latitude(:)*180./PI
61    boundslon(:,:) = boundslon_(:,:)
62    boundslat(:,:) = boundslat_(:,:)
63    cell_area(:) = cell_area_(:)
64    IF (PRESENT(dx_)) dx(:) = dx_(:)
65    IF (PRESENT(dy_)) dy(:) = dy_(:)
66   
67  END SUBROUTINE init_geometry
68
69
70END MODULE geometry_mod
Note: See TracBrowser for help on using the repository browser.