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.
Changeset 10727 for utils/tools_AGRIF_CMEMS_2020/DOMAINcfg/src/par_oce.f90 – NEMO

Ignore:
Timestamp:
2019-02-27T17:02:02+01:00 (5 years ago)
Author:
rblod
Message:

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

File:
1 edited

Legend:

Unmodified
Added
Removed
  • utils/tools_AGRIF_CMEMS_2020/DOMAINcfg/src/par_oce.f90

    r9598 r10727  
    1313   PUBLIC 
    1414 
     15   ! zoom starting position 
     16   INTEGER       ::   jpizoom          !: left bottom (i,j) indices of the zoom 
     17   INTEGER       ::   jpjzoom          !: in data domain indices 
     18 
     19  CHARACTER(lc) ::   cp_cfg           !: name of the configuration 
     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 ) 
     27   LOGICAL       ::   ln_e3_dep        ! e3. definition flag 
     28   REAL(wp)      ::   pp_not_used       = 999999._wp   !: vertical grid parameter 
     29   REAL(wp)      ::   pp_to_be_computed = 999999._wp   !:    -      -       - 
     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   !  
     45 
     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  
     52 
     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 
     57 
     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 
     63 
     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 
     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 
    1582   !!---------------------------------------------------------------------- 
    1683   !!   Domain decomposition 
     
    2289   INTEGER, PUBLIC, PARAMETER ::   jpr2di = 0   !: number of columns for extra outer halo  
    2390   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  
    26  
    27    !!---------------------------------------------------------------------- 
    28    !!                   namcfg namelist parameters 
    29    !!---------------------------------------------------------------------- 
    30    ! 
    31    LOGICAL       ::   ln_e3_dep        ! e3. definition flag 
    32    ! 
    33    CHARACTER(lc) ::   cp_cfg           !: name of the configuration 
    34    CHARACTER(lc) ::   cp_cfz           !: name of the zoom of configuration 
    35    INTEGER       ::   jp_cfg           !: resolution of the configuration 
    36  
    37    ! data size                                       !!! * size of all input files * 
    38    INTEGER       ::   jpidta           !: 1st lateral dimension ( >= jpi ) 
    39    INTEGER       ::   jpjdta           !: 2nd    "         "    ( >= jpj ) 
    40    INTEGER       ::   jpkdta           !: number of levels      ( >= jpk ) 
    41  
    42    ! global or zoom domain size                      !!! * computational domain * 
    43    INTEGER       ::   jpiglo           !: 1st dimension of global domain --> i 
    44    INTEGER       ::   jpjglo           !: 2nd    -                  -    --> j 
    45  
    46    ! zoom starting position  
    47    INTEGER       ::   jpizoom          !: left bottom (i,j) indices of the zoom 
    48    INTEGER       ::   jpjzoom          !: in data domain indices 
    49  
    50    ! Domain characteristics 
    51    INTEGER       ::   jperio           !: lateral cond. type (between 0 and 6) 
    52    !                                       !  = 0 closed                 ;   = 1 cyclic East-West 
    53    !                                       !  = 2 equatorial symmetric   ;   = 3 North fold T-point pivot 
    54    !                                       !  = 4 cyclic East-West AND North fold T-point pivot 
    55    !                                       !  = 5 North fold F-point pivot 
    56    !                                       !  = 6 cyclic East-West AND North fold F-point pivot 
    57  
    58    ! Input file read offset 
    59    LOGICAL       ::   ln_use_jattr     !: Use file global attribute: open_ocean_jstart to determine start j-row  
    60                                            ! when reading input from those netcdf files that have the  
    61                                            ! attribute defined. This is designed to enable input files associated  
    62                                            ! with the extended grids used in the under ice shelf configurations to  
    63                                            ! be used without redundant rows when the ice shelves are not in use. 
    64  
    65    !!  Values set to pp_not_used indicates that this parameter is not used in THIS config. 
    66    !!  Values set to pp_to_be_computed  indicates that variables will be computed in domzgr 
    67    REAL(wp)      ::   pp_not_used       = 999999._wp   !: vertical grid parameter 
    68    REAL(wp)      ::   pp_to_be_computed = 999999._wp   !:    -      -       - 
    69  
    70  
    71  
    72  
    73    !!--------------------------------------------------------------------- 
    74    !! Active tracer parameters 
    75    !!--------------------------------------------------------------------- 
    76    INTEGER, PUBLIC, PARAMETER ::   jpts   = 2    !: Number of active tracers (=2, i.e. T & S ) 
    77    INTEGER, PUBLIC, PARAMETER ::   jp_tem = 1    !: indice for temperature 
    78    INTEGER, PUBLIC, PARAMETER ::   jp_sal = 2    !: indice for salinity 
    79  
    80    !!--------------------------------------------------------------------- 
    81    !! Domain Matrix size  (if AGRIF, they are not all parameters) 
    82    !!--------------------------------------------------------------------- 
    83  
    84  
    85  
    86  
    87  
    88  
    89    INTEGER, PUBLIC  ::   jpi   ! = ( jpiglo-2*jpreci + (jpni-1) ) / jpni + 2*jpreci   !: first  dimension 
    90    INTEGER, PUBLIC  ::   jpj   ! = ( jpjglo-2*jprecj + (jpnj-1) ) / jpnj + 2*jprecj   !: second dimension 
    91    INTEGER, PUBLIC  ::   jpk   ! = jpkdta 
    92    INTEGER, PUBLIC  ::   jpim1 ! = jpi-1                                            !: inner domain indices 
    93    INTEGER, PUBLIC  ::   jpjm1 ! = jpj-1                                            !:   -     -      - 
    94    INTEGER, PUBLIC  ::   jpkm1 ! = jpk-1                                            !:   -     -      - 
    95    INTEGER, PUBLIC  ::   jpij  ! = jpi*jpj                                          !:  jpi x jpj 
     91   INTEGER, PUBLIC, PARAMETER ::   nn_hls = 1   !: halo width (applies to both rows and columns) 
    9692 
    9793   !!---------------------------------------------------------------------- 
    9894   !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
    99    !! $Id: par_oce.F90 5836 2015-10-26 14:49:40Z cetlod $  
    100    !! Software governed by the CeCILL licence (./LICENSE) 
     95   !! $Id: par_oce.F90 10068 2018-08-28 14:09:04Z nicolasmartin $  
     96   !! Software governed by the CeCILL license (see ./LICENSE) 
    10197   !!====================================================================== 
    10298END MODULE par_oce 
Note: See TracChangeset for help on using the changeset viewer.