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/TAM_V3_0/NEMO/OPA_SRC – NEMO

source: branches/TAM_V3_0/NEMO/OPA_SRC/par_oce.F90 @ 1884

Last change on this file since 1884 was 1884, checked in by rblod, 14 years ago

Light adaptation of NEMO direct model routine to handle TAM

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 11.4 KB
Line 
1MODULE par_oce
2   !!======================================================================
3   !!                        ***  par_oce  ***
4   !! Ocean :   set the ocean parameters
5   !!======================================================================
6   !! History :
7   !!   4.0  !  91     (Imbard, Levy, Madec)  Original code
8   !!   9.0  !  04-01  (G. Madec, J.-M. Molines)  Free form and module
9   !!    "   !  05-11  (V. Garnier) Surface pressure gradient organization
10   !!----------------------------------------------------------------------
11   !!  OPA 9.0 , LOCEAN-IPSL (2005)
12   !! $Id$
13   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
14   !!----------------------------------------------------------------------
15   !! * Modules used
16   USE par_kind          ! kind parameters
17
18   IMPLICIT NONE
19   PUBLIC
20
21   !!----------------------------------------------------------------------
22   !!   Domain decomposition
23   !!----------------------------------------------------------------------
24   !! * if we dont use massively parallel computer (parameters jpni=jpnj=1)
25   !!      so jpiglo=jpi and jpjglo=jpj
26
27#if ! defined key_mpp_dyndist
28   INTEGER, PUBLIC, PARAMETER ::    &  !:
29      jpni   = 1,                   &  !: number of processors following i
30      jpnj   = 1,                   &  !: number of processors following j
31      jpnij  = 1                       !: nb of local domain = nb of processors
32      !                                !  ( <= jpni x jpnj )
33#else
34   INTEGER, PUBLIC ::               &  !
35      jpni      ,                   &  !: number of processors following i
36      jpnj      ,                   &  !: number of processors following j
37      jpnij                            !: nb of local domain = nb of processors
38      !                                !  ( <= jpni x jpnj )
39#endif
40 
41   INTEGER, PUBLIC, PARAMETER ::    &  !:
42      jpr2di = 0,                   &  !: number of columns for extra outer halo
43      jpr2dj = 0,                   &  !: number of rows    for extra outer halo
44      jpreci = 1,                   &  !: number of columns for overlap
45      jprecj = 1                       !: number of rows    for overlap
46
47   !! Ocean Domain sizes
48   !! ------------------
49   !!   data           domain   (jpidta,jpjdta)
50   !!   global or zoom domain   (jpiglo,jpjglo)
51   !!   local          domain   ( jpi  , jpj  )
52   
53#if   defined key_orca_r4
54   !!---------------------------------------------------------------------
55   !!   'key_orca_r4'   :                           global ocean : ORCA R4
56   !!---------------------------------------------------------------------
57#             include "par_ORCA_R4.h90"
58#elif defined key_orca_r2
59   !!---------------------------------------------------------------------
60   !!   'key_orca_r2'   :                           global ocean : ORCA R2
61   !!---------------------------------------------------------------------
62#             include "par_ORCA_R2.h90"
63#elif defined key_orca_r05
64   !!---------------------------------------------------------------------
65   !!   'key_orca_r05'  :                          global ocean : ORCA R05
66   !!---------------------------------------------------------------------
67#             include "par_ORCA_R05.h90"
68#elif defined key_orca_r025
69   !!---------------------------------------------------------------------
70   !!   'key_orca_r025' :                         global ocean : ORCA R025
71   !!---------------------------------------------------------------------
72#             include "par_ORCA_R025.h90"
73#elif defined key_eel_r2
74   !!---------------------------------------------------------------------
75   !!   'key_eel_r2'    :                                 channel : EEL R2
76   !!---------------------------------------------------------------------
77#             include "par_EEL_R2.h90"
78#elif defined key_eel_r5
79   !!---------------------------------------------------------------------
80   !!   'key_eel_r5'    :                                 channel : EEL R5
81   !!---------------------------------------------------------------------
82#             include "par_EEL_R5.h90"
83#elif defined key_eel_r6
84   !!---------------------------------------------------------------------
85   !!   'key_eel_r6'    :                                 channel : EEL R6
86   !!---------------------------------------------------------------------
87#             include "par_EEL_R6.h90"
88#elif defined key_gyre
89   !!---------------------------------------------------------------------
90   !!   'key_gyre'      :                        mid-latitude basin : GYRE
91   !!---------------------------------------------------------------------
92#             include "par_GYRE.h90"
93#elif defined key_pomme_r025 
94   !!---------------------------------------------------------------------
95   !!   'key_pomme_r025':                        regional basin : POMME025
96   !!---------------------------------------------------------------------
97#             include "par_POMME_R025.h90" 
98#else
99   !!---------------------------------------------------------------------
100   !!   default option  :                               small closed basin
101   !!---------------------------------------------------------------------
102   CHARACTER(len=16), PUBLIC, PARAMETER ::   &  !:
103      cp_cfg = "default"               !: name of the configuration
104   INTEGER, PARAMETER ::            &  !:
105      jp_cfg = 0  ,                 &  !: resolution of the configuration
106
107      ! data size                     !!! * size of all input files *
108      jpidta  = 10,                 &  !: 1st lateral dimension ( >= jpi )
109      jpjdta  = 12,                 &  !: 2nd    "         "    ( >= jpj )
110      jpkdta  = 31,                 &  !: number of levels      ( >= jpk )
111
112      ! global or zoom domain size    !!! * computational domain *
113      jpiglo  = jpidta,             &  !: 1st dimension of global domain --> i
114      jpjglo  = jpjdta,             &  !: 2nd    "                  "    --> j
115      jpk     = jpkdta,             &  !: number of vertical levels
116      ! zoom starting position
117      jpizoom =   1   ,             &  !: left bottom (i,j) indices of the zoom
118      jpjzoom =   1   ,             &  !: in data domain indices
119
120      ! Domain characteristics
121      jperio  =  0,                 &  !: lateral cond. type (between 0 and 6)
122         !                             !  = 0 closed
123         !                             !  = 1 cyclic East-West
124         !                             !  = 2 equatorial symmetric
125         !                             !  = 3 North fold T-point pivot
126         !                             !  = 4 cyclic East-West AND North fold T-point pivot
127         !                             !  = 5 North fold F-point pivot
128         !                             !  = 6 cyclic East-West AND North fold F-point pivot
129      jpisl   =  0,                 &  !: number of islands (rigid-lid only)
130      jpnisl  =  0                     !: maximum number of points per island
131
132      !!  Values set to pp_not_used indicates that this parameter is not used in THIS config.
133      !!  Values set to pp_to_be_computed  indicates that variables will be computed in domzgr
134      REAL(wp), PARAMETER ::   &  !:
135         pp_not_used       = 999999._wp , &  !:
136         pp_to_be_computed = 999999._wp      !:
137
138
139   !! Horizontal grid parameters for domhgr
140   !! =====================================
141
142   INTEGER, PUBLIC, PARAMETER   ::   &  !:
143      jphgr_msh = 0            !: type of horizontal mesh
144      !                        !  = 0 curvilinear coordinate on the sphere
145      !                        !      read in coordinate.nc file
146      !                        !  = 1 geographical mesh on the sphere
147      !                        !      with regular grid-spacing
148      !                        !  = 2 f-plane with regular grid-spacing
149      !                        !  = 3 beta-plane with regular grid-spacing
150      !                        !  = 4 Mercator grid with T/U point at the equator  with
151      !                        !      isotropic resolution (e1_deg)
152
153   REAL(wp) , PUBLIC, PARAMETER ::   &   !:
154      ppglam0  =    0.0_wp,   &  !: longitude of first raw and column T-point (jphgr_msh = 1)
155      ppgphi0  =  -35.0_wp,   &  !: latitude  of first raw and column T-point (jphgr_msh = 1)
156      !                          !  latitude for the Coriolis or Beta parameter (jphgr_msh = 2 or 3)
157      ppe1_deg =    1.0_wp,   &  !: zonal      grid-spacing (degrees)
158      ppe2_deg =    0.5_wp,   &  !: meridional grid-spacing (degrees)
159      ppe1_m   = 5000.0_wp,   &  !: zonal      grid-spacing (degrees)
160      ppe2_m   = 5000.0_wp       !: meridional grid-spacing (degrees)
161
162   !! Vertical grid parameter for domzgr
163   !! ==================================
164
165   REAL(wp), PUBLIC, PARAMETER  ::   &  !:
166      &     ppsur = -4762.96143546300_wp ,  &  !: ORCA r4, r2 and r05 coefficients
167      &     ppa0  =   255.58049070440_wp ,  &  !: (default coefficients)
168      &     ppa1  =   245.58132232490_wp ,  &  !:
169      &     ppkth =    21.43336197938_wp ,  &  !:
170      &     ppacr =     3.00000000000_wp       !:
171
172   !!  If both ppa0 ppa1 and ppsur are specified to 0, then
173   !!  they are computed from ppdzmin, pphmax , ppkth, ppacr in dom_zgr
174
175   REAL(wp), PUBLIC, PARAMETER ::   &  !:
176      &     ppdzmin = 10._wp             ,  &  !: Minimum vertical spacing
177      &     pphmax  = 5000._wp                 !: Maximum depth
178
179   !!---------------------------------------------------------------------
180#endif
181
182   !!---------------------------------------------------------------------
183   !! Domain Matrix size
184   !!---------------------------------------------------------------------
185   INTEGER  &  !:
186#if !defined key_agrif
187      ,PARAMETER  &
188#endif
189    :: &
190      jpi = ( jpiglo-2*jpreci + (jpni-1) ) / jpni + 2*jpreci ,   &  !: first  dimension
191      jpj = ( jpjglo-2*jprecj + (jpnj-1) ) / jpnj + 2*jprecj ,   &  !: second dimension
192      jpim1 = jpi-1,                                             &  !: inner domain indices
193      jpjm1 = jpj-1,                                             &  !:   "            "
194      jpkm1 = jpk-1,                                             &  !:   "            "
195      jpij  = jpi*jpj                                               !:  jpi x jpj
196
197#if defined key_agrif
198   !!---------------------------------------------------------------------
199   !! Agrif variables
200   !!---------------------------------------------------------------------
201   INTEGER, PUBLIC, PARAMETER :: nbghostcells = 1
202   INTEGER, PUBLIC :: nbcellsx = jpiglo - 2 - 2*nbghostcells
203   INTEGER, PUBLIC :: nbcellsy = jpjglo - 2 - 2*nbghostcells
204#endif
205   !!---------------------------------------------------------------------
206   !! Optimization/control flags
207   !!---------------------------------------------------------------------
208#if defined key_esopa
209   LOGICAL, PUBLIC, PARAMETER ::   lk_esopa     = .TRUE.   !: flag to activate the all options
210#else
211   LOGICAL, PUBLIC, PARAMETER ::   lk_esopa     = .FALSE.  !: flag to activate the all options
212#endif
213
214#if defined key_vectopt_memory
215   LOGICAL, PUBLIC, PARAMETER ::   lk_vopt_mem  = .TRUE.   !: vector optimization flag
216#else
217   LOGICAL, PUBLIC, PARAMETER ::   lk_vopt_mem  = .FALSE.  !: vector optimization flag
218#endif
219
220#if defined key_vectopt_loop
221   LOGICAL, PUBLIC, PARAMETER ::   lk_vopt_loop = .TRUE.   !: vector optimization flag
222#else
223   LOGICAL, PUBLIC, PARAMETER ::   lk_vopt_loop = .FALSE.  !: vector optimization flag
224#endif
225
226   !!======================================================================
227END MODULE par_oce
Note: See TracBrowser for help on using the repository browser.