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 branches/2011/dev_r2802_MERCATOR10_diadct/NEMOGCM/TOOLS/SECTIONS_DIADCT/src – NEMO

source: branches/2011/dev_r2802_MERCATOR10_diadct/NEMOGCM/TOOLS/SECTIONS_DIADCT/src/declarations.f90 @ 2858

Last change on this file since 2858 was 2858, checked in by cbricaud, 13 years ago

cleanning, minor modifications

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