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.
par_oce.F90 in branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC – NEMO

source: branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/par_oce.F90 @ 3989

Last change on this file since 3989 was 3989, checked in by clevy, 11 years ago

Configuration setting/Step3 and doc, see ticket:#1074

  • Property svn:keywords set to Id
File size: 8.2 KB
RevLine 
[3]1MODULE par_oce
2   !!======================================================================
3   !!                        ***  par_oce  ***
4   !! Ocean :   set the ocean parameters
5   !!======================================================================
[2528]6   !! History :  OPA  !  1991     (Imbard, Levy, Madec)  Original code
7   !!   NEMO     1.0  !  2004-01  (G. Madec, J.-M. Molines)  Free form and module
8   !!            3.3  !  2010-09  (C. Ethe) TRA-TRC merge: add jpts, jp_tem & jp_sal
[3]9   !!----------------------------------------------------------------------
[15]10   USE par_kind          ! kind parameters
[3]11
12   IMPLICIT NONE
13   PUBLIC
14
15   !!----------------------------------------------------------------------
16   !!   Domain decomposition
17   !!----------------------------------------------------------------------
[2528]18   !! if we dont use massively parallel computer (parameters jpni=jpnj=1) so jpiglo=jpi and jpjglo=jpj
19   INTEGER, PUBLIC            ::   jpni         !: number of processors following i
20   INTEGER, PUBLIC            ::   jpnj         !: number of processors following j
21   INTEGER, PUBLIC            ::   jpnij        !: nb of local domain = nb of processors ( <= jpni x jpnj )
22   INTEGER, PUBLIC, PARAMETER ::   jpr2di = 0   !: number of columns for extra outer halo
23   INTEGER, PUBLIC, PARAMETER ::   jpr2dj = 0   !: number of rows    for extra outer halo
24   INTEGER, PUBLIC, PARAMETER ::   jpreci = 1   !: number of columns for overlap
25   INTEGER, PUBLIC, PARAMETER ::   jprecj = 1   !: number of rows    for overlap
[635]26
[3973]27   !!----------------------------------------------------------------------
28   !!                   namcfg namelist parameters
29   !!----------------------------------------------------------------------
30   CHARACTER(lc) ::   cp_cfg           !: name of the configuration
[3989]31   CHARACTER(lc) ::   cp_cfz           !: name of the zoom of configuration
[3973]32   INTEGER       ::   jp_cfg           !: resolution of the configuration
[3]33
[2528]34   ! data size                                       !!! * size of all input files *
[3973]35   INTEGER       ::   jpidta           !: 1st lateral dimension ( >= jpi )
36   INTEGER       ::   jpjdta           !: 2nd    "         "    ( >= jpj )
37   INTEGER       ::   jpkdta           !: number of levels      ( >= jpk )
[3]38
[2528]39   ! global or zoom domain size                      !!! * computational domain *
[3973]40   INTEGER       ::   jpiglo           !: 1st dimension of global domain --> i
41   INTEGER       ::   jpjglo           !: 2nd    -                  -    --> j
[3294]42
[2528]43   ! zoom starting position
[3973]44   INTEGER       ::   jpizoom          !: left bottom (i,j) indices of the zoom
45   INTEGER       ::   jpjzoom          !: in data domain indices
[3]46
[2528]47   ! Domain characteristics
[3973]48   INTEGER       ::   jperio           !: lateral cond. type (between 0 and 6)
49   !                                       !  = 0 closed                 ;   = 1 cyclic East-West
50   !                                       !  = 2 equatorial symmetric   ;   = 3 North fold T-point pivot
51   !                                       !  = 4 cyclic East-West AND North fold T-point pivot
52   !                                       !  = 5 North fold F-point pivot
53   !                                       !  = 6 cyclic East-West AND North fold F-point pivot
[3]54
[2528]55   !!  Values set to pp_not_used indicates that this parameter is not used in THIS config.
56   !!  Values set to pp_to_be_computed  indicates that variables will be computed in domzgr
[3973]57   REAL(wp)      ::   pp_not_used       = 999999._wp   !: vertical grid parameter
58   REAL(wp)      ::   pp_to_be_computed = 999998._wp   !:    -      -       -
[15]59
60
[3]61   !! Horizontal grid parameters for domhgr
62   !! =====================================
[3973]63   INTEGER       ::   jphgr_msh        !: type of horizontal mesh
64   !                                       !  = 0 curvilinear coordinate on the sphere read in coordinate.nc
65   !                                       !  = 1 geographical mesh on the sphere with regular grid-spacing
66   !                                       !  = 2 f-plane with regular grid-spacing
67   !                                       !  = 3 beta-plane with regular grid-spacing
68   !                                       !  = 4 Mercator grid with T/U point at the equator
[3]69
[3973]70   REAL(wp)      ::   ppglam0              !: longitude of first raw and column T-point (jphgr_msh = 1)
71   REAL(wp)      ::   ppgphi0              !: latitude  of first raw and column T-point (jphgr_msh = 1)
[2528]72   !                                                        !  used for Coriolis & Beta parameters (jphgr_msh = 2 or 3)
[3973]73   REAL(wp)      ::   ppe1_deg             !: zonal      grid-spacing (degrees)
74   REAL(wp)      ::   ppe2_deg             !: meridional grid-spacing (degrees)
75   REAL(wp)      ::   ppe1_m               !: zonal      grid-spacing (degrees)
76   REAL(wp)      ::   ppe2_m               !: meridional grid-spacing (degrees)
[3]77
78   !! Vertical grid parameter for domzgr
79   !! ==================================
[3973]80   REAL(wp)      ::   ppsur                !: ORCA r4, r2 and r05 coefficients
81   REAL(wp)      ::   ppa0                 !: (default coefficients)
82   REAL(wp)      ::   ppa1                 !:
83   REAL(wp)      ::   ppkth                !:
84   REAL(wp)      ::   ppacr                !:
[2528]85   !
86   !  If both ppa0 ppa1 and ppsur are specified to 0, then
87   !  they are computed from ppdzmin, pphmax , ppkth, ppacr in dom_zgr
[3973]88   REAL(wp)      ::   ppdzmin              !: Minimum vertical spacing
89   REAL(wp)      ::   pphmax               !: Maximum depth
[2528]90   !
[3973]91   LOGICAL       ::   ldbletanh            !: Use/do not use double tanf function for vertical coordinates
92   REAL(wp)      ::   ppa2                 !: Double tanh function parameters
93   REAL(wp)      ::   ppkth2               !:
94   REAL(wp)      ::   ppacr2               !:
[3]95
96   !!---------------------------------------------------------------------
[2528]97   !! Active tracer parameters
98   !!---------------------------------------------------------------------
99   INTEGER, PUBLIC, PARAMETER ::   jpts   = 2    !: Number of active tracers (=2, i.e. T & S )
100   INTEGER, PUBLIC, PARAMETER ::   jp_tem = 1    !: indice for temperature
101   INTEGER, PUBLIC, PARAMETER ::   jp_sal = 2    !: indice for salinity
[3]102
103   !!---------------------------------------------------------------------
[2528]104   !! Domain Matrix size  (if AGRIF, they are not all parameters)
[3]105   !!---------------------------------------------------------------------
[2528]106#if defined key_agrif
107   INTEGER, PUBLIC, PARAMETER ::   nbghostcells = 1                             !: number of ghost cells
108   INTEGER, PUBLIC            ::   nbcellsx     = jpiglo - 2 - 2*nbghostcells   !: number of cells in i-direction
109   INTEGER, PUBLIC            ::   nbcellsy     = jpjglo - 2 - 2*nbghostcells   !: number of cells in j-direction
110   !
[389]111#endif
[2715]112   INTEGER, PUBLIC  ::   jpi   ! = ( jpiglo-2*jpreci + (jpni-1) ) / jpni + 2*jpreci   !: first  dimension
113   INTEGER, PUBLIC  ::   jpj   ! = ( jpjglo-2*jprecj + (jpnj-1) ) / jpnj + 2*jprecj   !: second dimension
[3294]114   INTEGER, PUBLIC  ::   jpk   ! = jpkdta
[2715]115   INTEGER, PUBLIC  ::   jpim1 ! = jpi-1                                            !: inner domain indices
116   INTEGER, PUBLIC  ::   jpjm1 ! = jpj-1                                            !:   -     -      -
117   INTEGER, PUBLIC  ::   jpkm1 ! = jpk-1                                            !:   -     -      -
118   INTEGER, PUBLIC  ::   jpij  ! = jpi*jpj                                          !:  jpi x jpj
[3]119
120   !!---------------------------------------------------------------------
[15]121   !! Optimization/control flags
[3]122   !!---------------------------------------------------------------------
123#if defined key_esopa
[15]124   LOGICAL, PUBLIC, PARAMETER ::   lk_esopa     = .TRUE.   !: flag to activate the all options
[3]125#else
[15]126   LOGICAL, PUBLIC, PARAMETER ::   lk_esopa     = .FALSE.  !: flag to activate the all options
[3]127#endif
128
[15]129#if defined key_vectopt_loop
130   LOGICAL, PUBLIC, PARAMETER ::   lk_vopt_loop = .TRUE.   !: vector optimization flag
131#else
132   LOGICAL, PUBLIC, PARAMETER ::   lk_vopt_loop = .FALSE.  !: vector optimization flag
133#endif
134
[2528]135   !!----------------------------------------------------------------------
136   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
137   !! $Id$
138   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
[3]139   !!======================================================================
140END MODULE par_oce
Note: See TracBrowser for help on using the repository browser.