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 utils/tools_AGRIF_CMEMS_2020/DOMAINcfg/src – NEMO

source: utils/tools_AGRIF_CMEMS_2020/DOMAINcfg/src/par_oce.f90 @ 10727

Last change on this file since 10727 was 10727, checked in by rblod, 5 years ago

new nesting tools (attempt) and brutal cleaning of DOMAINcfg, see ticket #2129

File size: 6.4 KB
RevLine 
[6951]1MODULE par_oce
2   !!======================================================================
3   !!                        ***  par_oce  ***
4   !! Ocean :   set the ocean parameters
5   !!======================================================================
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
9   !!----------------------------------------------------------------------
10   USE par_kind          ! kind parameters
11
12   IMPLICIT NONE
13   PUBLIC
14
[10727]15   ! zoom starting position
16   INTEGER       ::   jpizoom          !: left bottom (i,j) indices of the zoom
17   INTEGER       ::   jpjzoom          !: in data domain indices
[6951]18
[10727]19  CHARACTER(lc) ::   cp_cfg           !: name of the configuration
[6951]20   CHARACTER(lc) ::   cp_cfz           !: name of the zoom of configuration
21   INTEGER       ::   jp_cfg           !: resolution of the configuration
22
23   ! data size                                       !!! * size of all input files *
24   INTEGER       ::   jpidta           !: 1st lateral dimension ( >= jpi )
25   INTEGER       ::   jpjdta           !: 2nd    "         "    ( >= jpj )
26   INTEGER       ::   jpkdta           !: number of levels      ( >= jpk )
[10727]27   LOGICAL       ::   ln_e3_dep        ! e3. definition flag
[6951]28   REAL(wp)      ::   pp_not_used       = 999999._wp   !: vertical grid parameter
29   REAL(wp)      ::   pp_to_be_computed = 999999._wp   !:    -      -       -
[10727]30   !!----------------------------------------------------------------------
31   !!                   namcfg namelist parameters
32   !!----------------------------------------------------------------------
33   LOGICAL       ::   ln_read_cfg      !: (=T) read the domain configuration file or (=F) not
34   CHARACTER(lc) ::      cn_domcfg        !: filename the configuration file to be read
35   LOGICAL       ::   ln_write_cfg     !: (=T) create the domain configuration file
36   CHARACTER(lc) ::      cn_domcfg_out    !: filename the configuration file to be read
37   !
38   LOGICAL       ::   ln_use_jattr     !: input file read offset
39   !                                   !  Use file global attribute: open_ocean_jstart to determine start j-row
40   !                                   !  when reading input from those netcdf files that have the
41   !                                   !  attribute defined. This is designed to enable input files associated
42   !                                   !  with the extended grids used in the under ice shelf configurations to
43   !                                   !  be used without redundant rows when the ice shelves are not in use.
44   !
[6951]45
[10727]46   !!---------------------------------------------------------------------
47   !! Domain Matrix size
48   !!---------------------------------------------------------------------
49   ! configuration name & resolution   (required only in ORCA family case)
50   CHARACTER(lc) ::   cn_cfg           !: name of the configuration
51   INTEGER       ::   nn_cfg           !: resolution of the configuration
[6951]52
[10727]53   ! global domain size               !!! * total computational domain *
54   INTEGER       ::   jpiglo           !: 1st dimension of global domain --> i-direction
55   INTEGER       ::   jpjglo           !: 2nd    -                  -    --> j-direction
56   INTEGER       ::   jpkglo           !: 3nd    -                  -    --> k levels
[6951]57
[10727]58   ! global domain size for AGRIF     !!! * total AGRIF computational domain *
59   INTEGER, PUBLIC            ::   nbug_in_agrif_conv_do_not_remove_or_modify = 1 - 1
60   INTEGER, PUBLIC, PARAMETER ::   nbghostcells = 3                             !: number of ghost cells
61   INTEGER, PUBLIC            ::   nbcellsx   ! = jpiglo - 2 - 2*nbghostcells   !: number of cells in i-direction
62   INTEGER, PUBLIC            ::   nbcellsy   ! = jpjglo - 2 - 2*nbghostcells   !: number of cells in j-direction
[6951]63
[10727]64   ! local domain size                !!! * local computational domain *
65   INTEGER, PUBLIC ::   jpi   !                                                    !: first  dimension
66   INTEGER, PUBLIC ::   jpj   !                                                    !: second dimension
67   INTEGER, PUBLIC ::   jpk   ! = jpkglo                                           !: third  dimension
68   INTEGER, PUBLIC ::   jpim1 ! = jpi-1                                            !: inner domain indices
69   INTEGER, PUBLIC ::   jpjm1 ! = jpj-1                                            !:   -     -      -
70   INTEGER, PUBLIC ::   jpkm1 ! = jpk-1                                            !:   -     -      -
71   INTEGER, PUBLIC ::   jpij  ! = jpi*jpj                                          !:  jpi x jpj
72   INTEGER, PUBLIC ::   jpimax! = ( jpiglo-2*nn_hls + (jpni-1) ) / jpni + 2*nn_hls !: maximum jpi
73   INTEGER, PUBLIC ::   jpjmax! = ( jpjglo-2*nn_hls + (jpnj-1) ) / jpnj + 2*nn_hls !: maximum jpj
74
[6951]75   !!---------------------------------------------------------------------
76   !! Active tracer parameters
77   !!---------------------------------------------------------------------
78   INTEGER, PUBLIC, PARAMETER ::   jpts   = 2    !: Number of active tracers (=2, i.e. T & S )
79   INTEGER, PUBLIC, PARAMETER ::   jp_tem = 1    !: indice for temperature
80   INTEGER, PUBLIC, PARAMETER ::   jp_sal = 2    !: indice for salinity
81
[10727]82   !!----------------------------------------------------------------------
83   !!   Domain decomposition
84   !!----------------------------------------------------------------------
85   !! if we dont use massively parallel computer (parameters jpni=jpnj=1) so jpiglo=jpi and jpjglo=jpj
86   INTEGER, PUBLIC            ::   jpni         !: number of processors following i
87   INTEGER, PUBLIC            ::   jpnj         !: number of processors following j
88   INTEGER, PUBLIC            ::   jpnij        !: nb of local domain = nb of processors ( <= jpni x jpnj )
89   INTEGER, PUBLIC, PARAMETER ::   jpr2di = 0   !: number of columns for extra outer halo
90   INTEGER, PUBLIC, PARAMETER ::   jpr2dj = 0   !: number of rows    for extra outer halo
91   INTEGER, PUBLIC, PARAMETER ::   nn_hls = 1   !: halo width (applies to both rows and columns)
[6951]92
93   !!----------------------------------------------------------------------
[9598]94   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
[10727]95   !! $Id: par_oce.F90 10068 2018-08-28 14:09:04Z nicolasmartin $
96   !! Software governed by the CeCILL license (see ./LICENSE)
[6951]97   !!======================================================================
98END MODULE par_oce
Note: See TracBrowser for help on using the repository browser.