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 5240 for branches/UKMO/dev_r5021_nn_etau_revision/NEMOGCM/TOOLS/SIREN/src/global.f90 – NEMO

Ignore:
Timestamp:
2015-04-29T12:17:12+02:00 (9 years ago)
Author:
davestorkey
Message:

Update UKMO nn_etau_revision branch with trunk changes to rev 5107.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/dev_r5021_nn_etau_revision/NEMOGCM/TOOLS/SIREN/src/global.f90

    r4213 r5240  
    66! 
    77! DESCRIPTION: 
    8 !> @brief This module defines global variables, and parameters that can't  
    9 !> be associated with a module 
     8!> @brief This module defines global variables and parameters. 
    109! 
    1110!> @author 
    1211!> J.paul 
    1312! REVISION HISTORY: 
    14 !> @date Nov, 2013 - Initial Version 
     13!> @date November, 2013 - Initial Version 
    1514! 
    1615!> @note Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     
    2221   IMPLICIT NONE 
    2322 
    24    PUBLIC :: dg_fill !< default fill value 
    25    PUBLIC :: ig_nsep !< number of separator listed 
    26    PUBLIC :: ig_ncom !< number of comment character listed 
    27    PUBLIC :: cg_sep  !< list of separator 
    28    PUBLIC :: cg_com  !< list of comment character 
     23   PUBLIC :: dp_fill        !< default fill value 
     24   PUBLIC :: ip_nsep        !< number of separator listed 
     25   PUBLIC :: ip_ncom        !< number of comment character listed 
     26   PUBLIC :: cp_sep          !< list of separator 
     27   PUBLIC :: cp_com          !< list of comment character 
    2928 
    30    PUBLIC :: ig_npoint 
    31    PUBLIC :: jp_T 
    32    PUBLIC :: jp_U 
    33    PUBLIC :: jp_V 
    34    PUBLIC :: jp_F 
     29   PUBLIC :: ip_npoint       !< number of point on ARAKAWA C-grid  
     30   PUBLIC :: jp_T            !< indice for T-point on ARAKAWA C-grid 
     31   PUBLIC :: jp_U            !< indice for U-point on ARAKAWA C-grid 
     32   PUBLIC :: jp_V            !< indice for V-point on ARAKAWA C-grid 
     33   PUBLIC :: jp_F            !< indice for F-point on ARAKAWA C-grid 
     34   PUBLIC :: cp_grid_point   !< list of grid_point character 
    3535 
    36    PUBLIC :: ig_ndim 
    37    PUBLIC :: jp_I 
    38    PUBLIC :: jp_J 
    39    PUBLIC :: jp_K 
    40    PUBLIC :: jp_L 
     36   PUBLIC :: ip_maxdim       !< maximum number of dimension to be used 
     37   PUBLIC :: jp_I            !< indice for I-direction 
     38   PUBLIC :: jp_J            !< indice for J-direction 
     39   PUBLIC :: jp_K            !< indice for K-direction 
     40   PUBLIC :: jp_L            !< indice for L-direction 
     41   PUBLIC :: cp_dimorder     !< dimension order 
    4142 
    42    PUBLIC :: ig_maxvar  !< maximum number of variable 
    43    PUBLIC :: ig_maxmtx  !< matrix variable maximum dimension 
    44    PUBLIC :: ig_maxseg  !< maximum number of segment 
    45    PUBLIC :: ig_ghost   !< number of ghost cell 
     43   PUBLIC :: ip_maxvar       !< maximum number of variable 
     44   PUBLIC :: ip_maxmtx       !< matrix variable maximum dimension 
     45   PUBLIC :: ip_maxseg       !< maximum number of segment 
     46   PUBLIC :: ip_ghost        !< number of ghost cell 
    4647 
    47    PUBLIC :: ig_ninterp      !< number of available interpolation method 
    48    PUBLIC :: cg_interp_list  !< list of interpolation name 
     48   PUBLIC :: ip_ninterp      !< number of available interpolation method 
     49   PUBLIC :: cp_interp_list  !< list of interpolation name 
    4950    
    50    PUBLIC :: ig_nextrap      !< number of available extrapolation method 
    51    PUBLIC :: cg_extrap_list  !< list of extrapolation name 
     51   PUBLIC :: ip_nextrap      !< number of available extrapolation method 
     52   PUBLIC :: cp_extrap_list  !< list of extrapolation name 
    5253    
    53    PUBLIC :: ig_nfilter      !< number of available filter 
    54    PUBLIC :: cg_filter_list  !< list of filter name 
     54   PUBLIC :: ip_nfilter      !< number of available filter 
     55   PUBLIC :: cp_filter_list  !< list of filter name 
    5556 
    56    PRIVATE 
     57   PUBLIC :: ip_ncard        !< number of cardinal point 
     58   PUBLIC :: cp_card         !< array of cardinal point 
     59   PUBLIC :: jp_north        !< indice for north boundary 
     60   PUBLIC :: jp_south        !< indice for south boundary 
     61   PUBLIC :: jp_east         !< indice for east  boundary 
     62   PUBLIC :: jp_west         !< indice for west  boundary 
     63 
    5764   ! NOTE_avoid_public_variables_if_possible 
    5865 
    59    INTEGER(i4)                             , PARAMETER :: ig_maxvar =200   !< maximum number of variable 
    60    INTEGER(i4)                             , PARAMETER :: ig_maxmtx =100   !< matrix variable maximum dimension (cf create_bathy) 
    61    INTEGER(i4)                             , PARAMETER :: ig_maxseg =50    !< maximum number of segment for each boundary 
     66   INTEGER(i4)                             , PARAMETER :: ip_maxvar =200   !< maximum number of variable 
     67   INTEGER(i4)                             , PARAMETER :: ip_maxmtx =100   !< matrix variable maximum dimension (cf create_bathy) 
     68   INTEGER(i4)                             , PARAMETER :: ip_maxseg =50    !< maximum number of segment for each boundary 
    6269 
    63    INTEGER(i4)                             , PARAMETER :: ig_nsep=2  !< number of separator listed 
    64    CHARACTER(1)     , DIMENSION(ig_nsep)   , PARAMETER :: cg_sep = (/'.','_'/) !< list of separator  
     70   INTEGER(i4)                             , PARAMETER :: ip_nsep=2        !< number of separator listed 
     71   CHARACTER(1)     , DIMENSION(ip_nsep)   , PARAMETER :: cp_sep = (/'.','_'/) !< list of separator  
    6572 
    66    INTEGER(i4)                             , PARAMETER :: ig_ncom=2  !< number of comment character listed 
    67    CHARACTER(1)     , DIMENSION(ig_ncom)   , PARAMETER :: cg_com = (/'#','!'/) !< list of comment character  
     73   INTEGER(i4)                             , PARAMETER :: ip_ncom=2        !< number of comment character listed 
     74   CHARACTER(1)     , DIMENSION(ip_ncom)   , PARAMETER :: cp_com = (/'#','!'/) !< list of comment character  
    6875     
    69    INTEGER(i4)                             , PARAMETER :: ig_ghost=1    !< number of ghost cell 
     76   INTEGER(i4)                             , PARAMETER :: ip_ghost=1       !< number of ghost cell 
    7077 
    71    INTEGER(i4)                             , PARAMETER :: ig_ninterp=3 
    72    CHARACTER(LEN=lc), DIMENSION(ig_ninterp), PARAMETER :: cg_interp_list = & 
     78   INTEGER(i4)                             , PARAMETER :: ip_ninterp=3 
     79   CHARACTER(LEN=lc), DIMENSION(ip_ninterp), PARAMETER :: cp_interp_list = & 
    7380   &  (/ 'nearest', & 
    7481   &     'cubic  ', & 
    7582   &     'linear '  /) 
    7683 
    77    INTEGER(i4)                             , PARAMETER :: ig_nextrap=2 
    78    CHARACTER(LEN=lc), DIMENSION(ig_nextrap), PARAMETER :: cg_extrap_list = & 
     84   INTEGER(i4)                             , PARAMETER :: ip_nextrap=2 
     85   CHARACTER(LEN=lc), DIMENSION(ip_nextrap), PARAMETER :: cp_extrap_list = & 
    7986   &  (/ 'dist_weight', & 
    8087   &     'min_error  ' /) 
    8188 
    82    INTEGER(i4)                             , PARAMETER :: ig_nfilter=5 
    83    CHARACTER(LEN=lc), DIMENSION(ig_nfilter), PARAMETER :: cg_filter_list = & 
     89   INTEGER(i4)                             , PARAMETER :: ip_nfilter=5 
     90   CHARACTER(LEN=lc), DIMENSION(ip_nfilter), PARAMETER :: cp_filter_list = & 
    8491   &  (/ 'butterworth', & 
    8592   &     'blackman   ', & 
     
    8895   &     'gauss      '/) 
    8996 
    90    REAL(dp)                                , PARAMETER :: dg_fill=NF90_FILL_DOUBLE !< default fill value 
    91    INTEGER(i4)                             , PARAMETER :: ig_fill=NF90_FILL_INT    !< default fill value 
     97   REAL(dp)                                , PARAMETER :: dp_fill=NF90_FILL_DOUBLE !< default fill value 
    9298 
    93    INTEGER(i4)                             , PARAMETER :: ig_npoint=4 
     99   INTEGER(i4)                             , PARAMETER :: ip_npoint=4 
    94100   INTEGER(i4)                             , PARAMETER :: jp_T=1 
    95101   INTEGER(i4)                             , PARAMETER :: jp_U=2 
    96102   INTEGER(i4)                             , PARAMETER :: jp_V=3 
    97103   INTEGER(i4)                             , PARAMETER :: jp_F=4 
     104   CHARACTER(LEN=1), DIMENSION(ip_npoint)  , PARAMETER :: cp_grid_point = & 
     105   &  (/ 'T', 'U', 'V', 'F' /) 
    98106 
    99    INTEGER(i4)                             , PARAMETER :: ig_ndim=2 
     107 
     108   INTEGER(i4)                             , PARAMETER :: ip_maxdim=4 
    100109   INTEGER(i4)                             , PARAMETER :: jp_I=1 
    101110   INTEGER(i4)                             , PARAMETER :: jp_J=2 
    102111   INTEGER(i4)                             , PARAMETER :: jp_K=3 
    103112   INTEGER(i4)                             , PARAMETER :: jp_L=4 
     113   CHARACTER(LEN=ip_maxdim)                , PARAMETER :: cp_dimorder = 'xyzt' !< dimension order to output 
     114 
     115   INTEGER(i4), PARAMETER :: ip_ncard=4 
     116   CHARACTER(LEN=lc), DIMENSION(ip_ncard), PARAMETER :: cp_card = & 
     117   &  (/ 'north', & 
     118   &     'south', & 
     119   &     'east ', & 
     120   &     'west ' /) 
     121 
     122   INTEGER(i4), PARAMETER :: jp_north=1 
     123   INTEGER(i4), PARAMETER :: jp_south=2 
     124   INTEGER(i4), PARAMETER :: jp_east =3 
     125   INTEGER(i4), PARAMETER :: jp_west =4 
     126 
     127 
    104128 
    105129END MODULE global 
Note: See TracChangeset for help on using the changeset viewer.