!---------------------------------------------------------------------- ! NEMO system team, System and Interface for oceanic RElocable Nesting !---------------------------------------------------------------------- ! ! MODULE: global ! ! DESCRIPTION: !> @brief This module defines global variables, and parameters that can't !> be associated with a module ! !> @author !> J.paul ! REVISION HISTORY: !> @date Nov, 2013 - Initial Version ! !> @note Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) !---------------------------------------------------------------------- MODULE global USE kind ! F90 kind parameter USE netcdf IMPLICIT NONE PUBLIC :: dg_fill !< default fill value PUBLIC :: ig_nsep !< number of separator listed PUBLIC :: ig_ncom !< number of comment character listed PUBLIC :: cg_sep !< list of separator PUBLIC :: cg_com !< list of comment character PUBLIC :: ig_npoint PUBLIC :: jp_T PUBLIC :: jp_U PUBLIC :: jp_V PUBLIC :: jp_F PUBLIC :: ig_ndim PUBLIC :: jp_I PUBLIC :: jp_J PUBLIC :: jp_K PUBLIC :: jp_L PUBLIC :: ig_maxvar !< maximum number of variable PUBLIC :: ig_maxmtx !< matrix variable maximum dimension PUBLIC :: ig_maxseg !< maximum number of segment PUBLIC :: ig_ghost !< number of ghost cell PUBLIC :: ig_ninterp !< number of available interpolation method PUBLIC :: cg_interp_list !< list of interpolation name PUBLIC :: ig_nextrap !< number of available extrapolation method PUBLIC :: cg_extrap_list !< list of extrapolation name PUBLIC :: ig_nfilter !< number of available filter PUBLIC :: cg_filter_list !< list of filter name PRIVATE ! NOTE_avoid_public_variables_if_possible INTEGER(i4) , PARAMETER :: ig_maxvar =200 !< maximum number of variable INTEGER(i4) , PARAMETER :: ig_maxmtx =100 !< matrix variable maximum dimension (cf create_bathy) INTEGER(i4) , PARAMETER :: ig_maxseg =50 !< maximum number of segment for each boundary INTEGER(i4) , PARAMETER :: ig_nsep=2 !< number of separator listed CHARACTER(1) , DIMENSION(ig_nsep) , PARAMETER :: cg_sep = (/'.','_'/) !< list of separator INTEGER(i4) , PARAMETER :: ig_ncom=2 !< number of comment character listed CHARACTER(1) , DIMENSION(ig_ncom) , PARAMETER :: cg_com = (/'#','!'/) !< list of comment character INTEGER(i4) , PARAMETER :: ig_ghost=1 !< number of ghost cell INTEGER(i4) , PARAMETER :: ig_ninterp=3 CHARACTER(LEN=lc), DIMENSION(ig_ninterp), PARAMETER :: cg_interp_list = & & (/ 'nearest', & & 'cubic ', & & 'linear ' /) INTEGER(i4) , PARAMETER :: ig_nextrap=2 CHARACTER(LEN=lc), DIMENSION(ig_nextrap), PARAMETER :: cg_extrap_list = & & (/ 'dist_weight', & & 'min_error ' /) INTEGER(i4) , PARAMETER :: ig_nfilter=5 CHARACTER(LEN=lc), DIMENSION(ig_nfilter), PARAMETER :: cg_filter_list = & & (/ 'butterworth', & & 'blackman ', & & 'hamming ', & & 'hann ', & & 'gauss '/) REAL(dp) , PARAMETER :: dg_fill=NF90_FILL_DOUBLE !< default fill value INTEGER(i4) , PARAMETER :: ig_fill=NF90_FILL_INT !< default fill value INTEGER(i4) , PARAMETER :: ig_npoint=4 INTEGER(i4) , PARAMETER :: jp_T=1 INTEGER(i4) , PARAMETER :: jp_U=2 INTEGER(i4) , PARAMETER :: jp_V=3 INTEGER(i4) , PARAMETER :: jp_F=4 INTEGER(i4) , PARAMETER :: ig_ndim=2 INTEGER(i4) , PARAMETER :: jp_I=1 INTEGER(i4) , PARAMETER :: jp_J=2 INTEGER(i4) , PARAMETER :: jp_K=3 INTEGER(i4) , PARAMETER :: jp_L=4 END MODULE global