source: branches/publications/ORCHIDEE_2.2_r7266/ORCHIDEE/src_global/grid_var.f90 @ 7541

Last change on this file since 7541 was 7541, checked in by fabienne.maignan, 2 years ago
  1. Zhang publication on coupling factor
File size: 3.2 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: svn://forge.ipsl.jussieu.fr/orchidee/branches/ORCHIDEE_2_2/ORCHIDEE/src_global/grid_var.f90 $
21!! $Date: 2018-11-08 12:04:00 +0100 (Thu, 08 Nov 2018) $
22!! $Revision: 5559 $
23!! \n
24!_ ================================================================================================================================
25
26MODULE grid_var
27
28  USE defprec
29  IMPLICIT NONE
30
31  !=================================================================================
32  ! Horizontal grid information
33  !=================================================================================
34  INTEGER,PARAMETER                                  :: unstructured=0   !! Index for unstructured grid
35  INTEGER,PARAMETER                                  :: regular_lonlat=1 !! Index for regular longitude-latitude grid
36  INTEGER,PARAMETER                                  :: regular_xy=2     !! Index for regular grid projected on X-Y
37  INTEGER,SAVE                                       :: grid_type        !! grid type : unstructured, regular_lonlat or regular_xy
38!$OMP THREADPRIVATE(grid_type)
39  INTEGER(i_std), SAVE                               :: ncells           !! numbers of cells (including masked cells)
40!$OMP THREADPRIVATE(ncells)
41  INTEGER(i_std), SAVE                               :: nvertex          !! numbers of vertex by cells
42!$OMP THREADPRIVATE(nvertex)
43  INTEGER, SAVE                                      :: NbSegments       !! Number of segments in the polygone defining the grid box, same as nvertex
44!$OMP THREADPRIVATE(NbSegments)
45  INTEGER, SAVE                                      :: NbNeighb         !! Number of neighbours for each grid box
46!$OMP THREADPRIVATE(NbNeighb)
47  REAL(r_std), ALLOCATABLE, DIMENSION(:), SAVE       :: longitude        !! longitude for all cells (including masked cells)
48!$OMP THREADPRIVATE(longitude)
49  REAL(r_std), ALLOCATABLE, DIMENSION(:), SAVE       :: latitude         !! latitude for all cells (including masked cells)
50!$OMP THREADPRIVATE(latitude)
51  REAL(r_std), ALLOCATABLE, DIMENSION(:,:), SAVE     :: bounds_lon       !! longitude boundairies for all cells (including masked cells)
52!$OMP THREADPRIVATE(bounds_lon)
53  REAL(r_std), ALLOCATABLE, DIMENSION(:,:), SAVE     :: bounds_lat       !! latitude boundairies for all cells (including masked cells)
54!$OMP THREADPRIVATE(bounds_lat)
55  INTEGER(i_std), ALLOCATABLE, DIMENSION(:), SAVE    :: ind_cell_glo     !! Cells order give by indice form global grid reference
56!$OMP THREADPRIVATE(ind_cell_glo)
57
58
59END MODULE grid_var
Note: See TracBrowser for help on using the repository browser.