source: branches/publications/ORCHIDEE_DFv1.0_site/src_global/grid_var.f90 @ 6715

Last change on this file since 6715 was 5386, checked in by josefine.ghattas, 6 years ago

Corrections for running with unstructured grid (dynamico).
Done by Y. Meurdesoif

  • Property svn:keywords set to Date Revision HeadURL
File size: 3.3 KB
Line 
1! ===============================================================================================================================
2! MODULE       : grid_var
3!
4! CONTACT      : orchidee-help _at_ listes.ipsl.fr
5!
6! LICENCE      : IPSL (2006)
7! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF
10!!
11!! \n DESCRIPTION : This module define variables for the grid module.
12!!                The module is already USE in module grid. Therefor no need to use it seperatly if use grid is already done.
13
14!!
15!! RECENT CHANGE(S): These variables were previously in grid module. They have been moved here to avoid dependency
16!!                   problems when the variables are needed in the parallelization modules.
17!!
18!!
19!! SVN
20!! $HeadURL$
21!! $Date$
22!! $Revision$
23!! \n
24!_ ================================================================================================================================
25
26MODULE grid_var
27
28  USE defprec
29  IMPLICIT NONE
30
31  !=================================================================================
32  ! Horizontal grid information
33  !=================================================================================
34  CHARACTER(LEN=20), SAVE                           :: GridType    !! Describes the grid it can be RegLonLat, RegXY or UnStruct
35!$OMP THREADPRIVATE(GridType)
36  INTEGER, SAVE                                     :: NbSegments  !! Number of segments in the polygone defining the grid box
37!$OMP THREADPRIVATE(NbSegments)
38  INTEGER, SAVE                                     :: NbNeighb    !! Number of neighbours
39!$OMP THREADPRIVATE(NbNeighb)
40 
41
42  !=================================================================================
43  ! Following variables were introduce for use of unstructred grid
44  ! such as when using DYNAMICO. Same variables are used for all type of grids.
45  !=================================================================================
46  INTEGER,PARAMETER                                  :: regular_lonlat=1 !! Index for regular longitude-latitude grid
47  INTEGER,PARAMETER                                  :: unstructured=0   !! Index for unstructured grid
48  INTEGER,SAVE                                       :: grid_type        !! grid type : regular_lonlat or unstructured
49!$OMP THREADPRIVATE(grid_type)
50  INTEGER(i_std), SAVE                               :: ncells           !! numbers of cells (including masked cells)
51!$OMP THREADPRIVATE(ncells)
52  INTEGER(i_std), SAVE                               :: nvertex          !! numbers of vertex by cells
53!$OMP THREADPRIVATE(nvertex)
54  REAL(r_std), ALLOCATABLE, DIMENSION(:), SAVE       :: longitude        !! longitude for all cells (including masked cells)
55!$OMP THREADPRIVATE(longitude)
56  REAL(r_std), ALLOCATABLE, DIMENSION(:), SAVE       :: latitude         !! latitude for all cells (including masked cells)
57!$OMP THREADPRIVATE(latitude)
58  REAL(r_std), ALLOCATABLE, DIMENSION(:,:), SAVE     :: bounds_lon       !! longitude boundairies for all cells (including masked cells)
59!$OMP THREADPRIVATE(bounds_lon)
60  REAL(r_std), ALLOCATABLE, DIMENSION(:,:), SAVE     :: bounds_lat       !! latitude boundairies for all cells (including masked cells)
61!$OMP THREADPRIVATE(bounds_lat)
62  INTEGER(i_std), ALLOCATABLE, DIMENSION(:), SAVE    :: ind_cell_glo     !! Cells order give by indice form global grid reference
63!$OMP THREADPRIVATE(ind_cell_glo)
64
65
66END MODULE grid_var
Note: See TracBrowser for help on using the repository browser.