New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
declarations.f90 in trunk/NEMOGCM/TOOLS/SECTIONS_DIADCT/src – NEMO

source: trunk/NEMOGCM/TOOLS/SECTIONS_DIADCT/src/declarations.f90 @ 4990

Last change on this file since 4990 was 3680, checked in by rblod, 11 years ago

First commit of the final branch for 2012 (future nemo_3_5), see ticket #1028

  • Property svn:executable set to *
File size: 3.6 KB
Line 
1MODULE declarations 
2  !!----------------------------------------------------------------------------
3  !!             *** declarations global varibles
4  !!
5  !! History: 2011: Clement Bricaud, Mercator-Ocean
6  !!
7  !!----------------------------------------------------------------------------
8
9  IMPLICIT NONE
10  PUBLIC
11
12  !! * Shared module variables
13  INTEGER, PUBLIC, PARAMETER   :: dp=8 , sp=4, wp=dp
14  INTEGER, PUBLIC, PARAMETER   :: nb_class_max  = 10            ! Max number of classes
15  INTEGER, PUBLIC, PARAMETER   :: nb_sec_max    = 150           ! Max number of sections
16  INTEGER, PUBLIC, PARAMETER   :: nb_point_max  = 2000          ! Max number of segments per section
17  INTEGER, PUBLIC, PARAMETER   :: nb_type_class = 10            ! Max number of types of classes
18  INTEGER, PUBLIC, PARAMETER   :: numnam=3                      ! Unit for namelist
19  INTEGER, PUBLIC, PARAMETER   :: numdctin=1                    ! Unit for input file
20  INTEGER, PUBLIC, PARAMETER   :: numdctout=2                   ! Unit for output file
21
22  INTEGER, PUBLIC              :: jpi,jpj                       ! domain dimensions
23  INTEGER, PUBLIC              :: nb_sec                        ! Number of sections read from input file
24  INTEGER, PUBLIC              :: nsecdebug = 0                 ! Number of the section to debug
25
26  REAL(wp), PUBLIC ,DIMENSION(:,:)  , ALLOCATABLE :: glamf,gphif,glamt,gphit,e1t
27  INTEGER,  PUBLIC ,DIMENSION(nb_sec_max)         :: num_sec_debug
28
29  TYPE POINT_SECTION
30     INTEGER :: I,J
31  END TYPE POINT_SECTION
32
33  TYPE COORD_SECTION
34     REAL(wp) :: lon,lat
35  END TYPE COORD_SECTION
36
37  TYPE SECTION
38     CHARACTER(len=60)                              :: name                ! name of the sec
39     LOGICAL                                        :: llstrpond           ! true if you want the computation of salt
40                                                                           ! and heat transport
41     LOGICAL                                        :: ll_ice_section      ! ice surface and icevolume transport computation
42     LOGICAL                                        :: ll_date_line        ! = T if the section crosses the date-line
43     TYPE(COORD_SECTION), DIMENSION(2)              :: coordSec            ! longitude and latitude of the extremities of the section
44     INTEGER                                        :: nb_class            ! number of boundaries for density classes
45     INTEGER, DIMENSION(nb_point_max)               :: direction           ! vector direction of the point in the section
46     CHARACTER(len=40),DIMENSION(nb_class_max)      :: classname           ! characteristics of the class
47     REAL(wp), DIMENSION(nb_class_max)              :: zsigi             ,&! insitu density classes    (99 if you don't want)
48                                                       zsigp             ,&! potential density classes    (99 if you don't want)
49                                                       zsal              ,&! salinity classes   (99 if you don't want)
50                                                       ztem              ,&! temperature classes(99 if you don't want)
51                                                       zlay                ! depth level classes      (99 if you don't want)
52     REAL(wp)                                       :: slopeSection        ! slope of the section
53     INTEGER                                        :: nb_point            ! number of points in the section
54     TYPE(POINT_SECTION),DIMENSION(nb_point_max)    :: listPoint           ! list of points in the section
55  END TYPE SECTION
56
57  TYPE(SECTION),DIMENSION(nb_sec_max) :: secs ! Array of sections
58
59
60
61END MODULE declarations
Note: See TracBrowser for help on using the repository browser.