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.
modtypes.F90 in vendors/AGRIF/dev_r11615_ENHANCE-04_namelists_as_internalfiles_agrif/AGRIF_FILES – NEMO

source: vendors/AGRIF/dev_r11615_ENHANCE-04_namelists_as_internalfiles_agrif/AGRIF_FILES/modtypes.F90 @ 11998

Last change on this file since 11998 was 11668, checked in by acc, 5 years ago

Branch dev_r11615_ENHANCE-04_namelists_as_internalfiles_agrif. Changes to support 2019/dev_r11615_ENHANCE-04_namelists_as_internalfiles developments.
These changes enable sufficient support for allocatable, zero-dimension character variables defined using the:

CHARACTER(LEN=:), ALLOCATABLE :: cstr

syntax. This is supported by:

  1. Adding : as a valid length identifier at line 1028 in fortran.y (and then rebuilding fortran.c and main.c via make -f Makefile.lex)
  2. Adding a carrayu entry to Agrif_Variable_c type in AGRIF_FILES/modtypes.F90 where carrayu is declared as:
character(:) , allocatable
carrayu
Ensuring correct deallocation of carrayu in AGRIF_FILES/modsauv.F90 and AGRIF_FILES/modutil.F90
  • Substituting carrayu in place of carray0 declarations when character length matches : for zero-dimension variables. This occurs twice in LIB/toamr.c, e.g:
  • if (!strcasecmp(var->v_dimchar ,":") && var->v_nbdim == 0 )
    {
    sprintf (tname_2, "%% carrayu");
    } else {
    sprintf (tname_2, "%% carray%d", var->v_nbdim);
    }

    Any such character variables must be allocated by the user. Typically this is done with lines such as:

    IF ( .NOT. ALLOCATED(cdnambuff) ) ALLOCATE( CHARACTER(LEN=kleng)
    cdnambuff )

    making AGRIF accept the CHARACTER(LEN=kleng) :: construct within the ALLOCATE statement was beyond my skills. Fortunately, for the current purpose, this
    isn't necessary since such allocations only occur within utility routines in which the appropriate tabvar has been passed down. So:

    !$AGRIF_DO_NOT_TREAT

    IF ( .NOT. ALLOCATED(cdnambuff) ) ALLOCATE( CHARACTER(LEN=kleng)
    cdnambuff )
    !$AGRIF_END_DO_NOT_TREAT

    avoids the issue.

    • Property svn:keywords set to Id
    File size: 22.2 KB
    Line 
    1!     Agrif (Adaptive Grid Refinement In Fortran)
    2!
    3!     Copyright (C) 2003 Laurent Debreu (Laurent.Debreu@imag.fr)
    4!                        Christophe Vouland (Christophe.Vouland@imag.fr)
    5!
    6!     This program is free software; you can redistribute it and/or modify
    7!     it under the terms of the GNU General Public License as published by
    8!     the Free Software Foundation; either version 2 of the License, or
    9!     (at your option) any later version.
    10!
    11!     This program is distributed in the hope that it will be useful,
    12!     but WITHOUT ANY WARRANTY; without even the implied warranty of
    13!     MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
    14!     GNU General Public License for more details.
    15!
    16!     You should have received a copy of the GNU General Public License
    17!     along with this program; if not, write to the Free Software
    18!     Foundation, Inc., 59 Temple Place-Suite 330, Boston, MA 02111-1307, USA.
    19!
    20!
    21!
    22!
    23!> Definition of data types used in AGRIF, of several variables and parameters
    24!
    25module Agrif_Types
    26!
    27use Agrif_Procs
    28!
    29implicit none
    30!
    31integer, parameter :: Agrif_MaxRaff = 7       !< Maximum refinement ratio
    32integer, parameter :: Agrif_NbMaxGrids = 10   !< Maximum number of grids of the hierarchy
    33!
    34!===================================================================================================
    35type Agrif_LRectangle
    36!---------------------------------------------------------------------------------------------------
    37!<  Data type allowing a grid to reach a grid on the same level or its child grids
    38!
    39    type(Agrif_Rectangle) , pointer :: r    => NULL()   !< to reach a child grid
    40    type(Agrif_LRectangle), pointer :: next => NULL()   !< to reach a grid on the same level
    41!
    42!---------------------------------------------------------------------------------------------------
    43end type Agrif_LRectangle
    44!===================================================================================================
    45!
    46!===================================================================================================
    47type Agrif_Rectangle
    48!---------------------------------------------------------------------------------------------------
    49!<  Data type to define several characteristics of a grid (number, position, time and space
    50!<  refinement factors, etc).
    51!
    52    integer                         :: number       !< Number of the grid
    53    integer, dimension(3)           :: imin         !< Minimal position in the x,y and z direction
    54    integer, dimension(3)           :: imax         !< Maximal position in the x,y and z direction
    55    integer, dimension(3)           :: spaceref     !< Space refinement factor in the x,y and z direction
    56    integer, dimension(3)           :: timeref      !< Time refinement factor in the x,y and z direction
    57    type(Agrif_LRectangle), pointer :: childgrids => NULL()   !< Pointer to reach a grid on the same level or a child grid
    58!
    59!---------------------------------------------------------------------------------------------------
    60end type Agrif_Rectangle
    61!===================================================================================================
    62!
    63!===================================================================================================
    64type Agrif_Variable
    65!---------------------------------------------------------------------------------------------------
    66!<  Data type to characterize a grid variable.
    67!
    68    type(Agrif_Variable), pointer  :: root_var   => NULL()  !< pointer on the variable of the root grid
    69    type(Agrif_Variable), pointer  :: parent_var => NULL()  !< pointer on the parent variable
    70!
    71    integer,   dimension(6)              :: point           !< index of the first point in the
    72                                                            !<    real domain (x,y and z direction)
    73    integer,   dimension(:), allocatable :: posvar          !< position of the variable on the cell
    74                                                            !<   (1 for the boarder of the edge, 2 for the center)
    75    integer                            :: interpIndex = -1  !< Indication for the space interpolation (module Agrif_Boundary)
    76    integer                            :: nbdim = 0         !< number of dimensions of the grid variable
    77    character(1), dimension(:), allocatable :: interptab    !< Array indicating the type of dimension (space or not)
    78                                                            !!   for each of them
    79    integer,   dimension(:), allocatable :: coords          !< Array indicating the coordinate for each dimension
    80                                                            !!   of the array that is refined :
    81                                                            !!  'x' -> 1 ; 'y' -> 2 ; 'z' -> 3 ; 'N' -> 0
    82
    83!> @}
    84!> \name Arrays containing the values of the grid variables (real)
    85!> @{
    86    real,    dimension(:)          , allocatable :: array1
    87    real,    dimension(:,:)        , allocatable :: array2
    88    real,    dimension(:,:,:)      , allocatable :: array3
    89    real,    dimension(:,:,:,:)    , allocatable :: array4
    90    real,    dimension(:,:,:,:,:)  , allocatable :: array5
    91    real,    dimension(:,:,:,:,:,:), allocatable :: array6
    92!> @}
    93!> \name Arrays containing the values of the grid variables (real*8)
    94!> @{
    95    real(8), dimension(:)          , allocatable :: darray1
    96    real(8), dimension(:,:)        , allocatable :: darray2
    97    real(8), dimension(:,:,:)      , allocatable :: darray3
    98    real(8), dimension(:,:,:,:)    , allocatable :: darray4
    99    real(8), dimension(:,:,:,:,:)  , allocatable :: darray5
    100    real(8), dimension(:,:,:,:,:,:), allocatable :: darray6
    101!> @}
    102!> \name Arrays containing the values of the grid variables (real*4)
    103!> @{
    104    real(4), dimension(:)          , allocatable :: sarray1
    105    real(4), dimension(:,:)        , allocatable :: sarray2
    106    real(4), dimension(:,:,:)      , allocatable :: sarray3
    107    real(4), dimension(:,:,:,:)    , allocatable :: sarray4
    108    real(4), dimension(:,:,:,:,:)  , allocatable :: sarray5
    109    real(4), dimension(:,:,:,:,:,:), allocatable :: sarray6
    110!> @}
    111!> \name Arrays used to restore the values
    112!> @{
    113    integer, dimension(:)          , pointer :: restore1D => NULL()
    114    integer, dimension(:,:)        , pointer :: restore2D => NULL()
    115    integer, dimension(:,:,:)      , pointer :: restore3D => NULL()
    116    integer, dimension(:,:,:,:)    , pointer :: restore4D => NULL()
    117    integer, dimension(:,:,:,:,:)  , pointer :: restore5D => NULL()
    118    integer, dimension(:,:,:,:,:,:), pointer :: restore6D => NULL()
    119!> @}
    120
    121    real, dimension(:,:), pointer :: oldvalues2D => NULL() !< Array used for the time interpolation
    122
    123    logical :: restore = .FALSE. !< =1 if the variable should be restored
    124    logical :: Interpolationshouldbemade = .FALSE. !< TRUE if the interpolation should be made in any case
    125    integer                 :: bcinf !< option bc
    126    integer                 :: bcsup !< option bc
    127    integer, dimension(6)   :: type_interp    !< option interp
    128    integer, dimension(6,6) :: type_interp_bc !< option bcinterp
    129    integer, dimension(6)   :: type_update    !< option update
    130
    131    integer, dimension(6)   :: lb
    132    integer, dimension(6)   :: ub
    133
    134    logical,dimension(6,2) :: memberin
    135    integer,dimension(6,2,2,6,2) :: childarray
    136
    137    type(Agrif_List_Interp_Loc), pointer :: list_interp => NULL()
    138    type(Agrif_List_Interp_Loc), pointer :: list_update => NULL()
    139!---------------------------------------------------------------------------------------------------
    140end type Agrif_Variable
    141!===================================================================================================
    142!
    143!===================================================================================================
    144type Agrif_Variable_c
    145!---------------------------------------------------------------------------------------------------
    146!<  Data type to characterize a grid variable.
    147!
    148    type(Agrif_Variable_c), pointer  :: root_var   => NULL()      !< pointer on the variable of the root grid
    149    type(Agrif_Variable_c), pointer  :: parent_var => NULL()      !< pointer on the parent variable
    150!
    151    integer                          :: nbdim = 0                 !< number of dimensions of the grid variable
    152!
    153!> \name Arrays containing the values of the grid variables (character)
    154!> @{
    155    character(2400)                             :: carray0
    156    character(:)  ,                 allocatable :: carrayu
    157    character(200), dimension(:)  , allocatable :: carray1
    158    character(200), dimension(:,:), allocatable :: carray2
    159!> @}
    160!---------------------------------------------------------------------------------------------------
    161end type Agrif_Variable_c
    162!===================================================================================================
    163!
    164!===================================================================================================
    165type Agrif_Variable_r
    166!---------------------------------------------------------------------------------------------------
    167!<  Data type to characterize a grid variable.
    168!
    169    type(Agrif_Variable_r), pointer  :: root_var   => NULL()      !< pointer on the variable of the root grid
    170    type(Agrif_Variable_r), pointer  :: parent_var => NULL()      !< pointer on the parent variable
    171!
    172    integer                          :: nbdim = 0                 !< number of dimensions of the grid variable
    173!
    174!> \name Arrays containing the values of the grid variables (real)
    175!> @{
    176    real                                         :: array0
    177    real,    dimension(:)          , allocatable :: array1
    178    real,    dimension(:,:)        , allocatable :: array2
    179    real,    dimension(:,:,:)      , allocatable :: array3
    180    real,    dimension(:,:,:,:)    , allocatable :: array4
    181    real,    dimension(:,:,:,:,:)  , allocatable :: array5
    182    real,    dimension(:,:,:,:,:,:), allocatable :: array6
    183!> @}
    184!> \name Arrays containing the values of the grid variables (real*8)
    185!> @{
    186    real(8)                                      :: darray0
    187    real(8), dimension(:)          , allocatable :: darray1
    188    real(8), dimension(:,:)        , allocatable :: darray2
    189    real(8), dimension(:,:,:)      , allocatable :: darray3
    190    real(8), dimension(:,:,:,:)    , allocatable :: darray4
    191    real(8), dimension(:,:,:,:,:)  , allocatable :: darray5
    192    real(8), dimension(:,:,:,:,:,:), allocatable :: darray6
    193!> @}
    194!> \name Arrays containing the values of the grid variables (real*4)
    195!> @{
    196    real(4)                                      :: sarray0
    197    real(4), dimension(:)          , allocatable :: sarray1
    198    real(4), dimension(:,:)        , allocatable :: sarray2
    199    real(4), dimension(:,:,:)      , allocatable :: sarray3
    200    real(4), dimension(:,:,:,:)    , allocatable :: sarray4
    201    real(4), dimension(:,:,:,:,:)  , allocatable :: sarray5
    202    real(4), dimension(:,:,:,:,:,:), allocatable :: sarray6
    203!> @}
    204!---------------------------------------------------------------------------------------------------
    205end type Agrif_Variable_r
    206!===================================================================================================
    207!===================================================================================================
    208!
    209!===================================================================================================
    210type Agrif_Variable_l
    211!---------------------------------------------------------------------------------------------------
    212!<  Data type to characterize a grid variable.
    213!
    214    type(Agrif_Variable_l), pointer  :: root_var   => NULL()      !< pointer on the variable of the root grid
    215    type(Agrif_Variable_l), pointer  :: parent_var => NULL()      !< pointer on the parent variable
    216!
    217    integer                          :: nbdim = 0                 !< number of dimensions of the grid variable
    218!
    219!> \name Arrays containing the values of the grid variables (logical)
    220!> @{
    221    logical                                      :: larray0
    222    logical, dimension(:)          , allocatable :: larray1
    223    logical, dimension(:,:)        , allocatable :: larray2
    224    logical, dimension(:,:,:)      , allocatable :: larray3
    225    logical, dimension(:,:,:,:)    , allocatable :: larray4
    226    logical, dimension(:,:,:,:,:)  , allocatable :: larray5
    227    logical, dimension(:,:,:,:,:,:), allocatable :: larray6
    228!> @}
    229!---------------------------------------------------------------------------------------------------
    230end type Agrif_Variable_l
    231!===================================================================================================
    232!
    233!===================================================================================================
    234type Agrif_Variable_i
    235!---------------------------------------------------------------------------------------------------
    236!<  Data type to characterize a grid variable.
    237!
    238    type(Agrif_Variable_i), pointer  :: root_var   => NULL()      !< pointer on the variable of the root grid
    239    type(Agrif_Variable_i), pointer  :: parent_var => NULL()      !< pointer on the parent variable
    240!
    241    integer                          :: nbdim = 0             !< number of dimensions of the grid variable
    242!
    243!> \name Arrays containing the values of the grid variables (integer)
    244!> @{
    245    integer                                      :: iarray0
    246    integer, dimension(:)          , allocatable :: iarray1
    247    integer, dimension(:,:)        , allocatable :: iarray2
    248    integer, dimension(:,:,:)      , allocatable :: iarray3
    249    integer, dimension(:,:,:,:)    , allocatable :: iarray4
    250    integer, dimension(:,:,:,:,:)  , allocatable :: iarray5
    251    integer, dimension(:,:,:,:,:,:), allocatable :: iarray6
    252!> @}
    253!---------------------------------------------------------------------------------------------------
    254end type Agrif_Variable_i
    255!===================================================================================================
    256!
    257!===================================================================================================
    258type Agrif_Interp_Loc
    259!---------------------------------------------------------------------------------------------------
    260    integer,dimension(6)              :: pttab, petab, pttab_Child, pttab_Parent = -99
    261    integer,dimension(6)              :: indmin, indmax
    262    integer,dimension(6)              :: pttruetab,cetruetab
    263    logical :: member, memberin
    264#if !defined AGRIF_MPI
    265    integer,dimension(6)              :: indminglob,indmaxglob
    266#else
    267    integer,dimension(6)              :: indminglob2,indmaxglob2
    268    integer,dimension(6,2,2)          :: parentarray
    269    integer,dimension(:,:,:), pointer :: tab4t          => NULL()
    270    integer,dimension(:,:,:), pointer :: tab5t          => NULL()
    271    logical, dimension(:),    pointer :: memberinall    => NULL()
    272    logical, dimension(:),    pointer :: memberinall2   => NULL()
    273    logical, dimension(:),    pointer :: sendtoproc1    => NULL()
    274    logical, dimension(:),    pointer :: sendtoproc2    => NULL()
    275    logical, dimension(:),    pointer :: recvfromproc1  => NULL()
    276    logical, dimension(:),    pointer :: recvfromproc2  => NULL()
    277#endif
    278!---------------------------------------------------------------------------------------------------
    279end type Agrif_Interp_Loc
    280!===================================================================================================
    281
    282!===================================================================================================
    283type Agrif_List_Interp_Loc
    284!---------------------------------------------------------------------------------------------------
    285    type(Agrif_Interp_Loc),      pointer :: interp_loc => NULL()
    286    type(Agrif_List_Interp_Loc), pointer :: suiv       => NULL()
    287!---------------------------------------------------------------------------------------------------
    288end type Agrif_List_Interp_Loc
    289!===================================================================================================
    290
    291!===================================================================================================
    292type Agrif_Variables_List
    293!---------------------------------------------------------------------------------------------------
    294    type(Agrif_Variable),       pointer :: var  => NULL()
    295    type(Agrif_Variables_List), pointer :: next => NULL()
    296!---------------------------------------------------------------------------------------------------
    297end type Agrif_Variables_List
    298!===================================================================================================
    299!
    300!===================================================================================================
    301!> Different parameters
    302!
    303    type(Agrif_Variable),   dimension(:), pointer :: Agrif_tabvars => NULL()
    304    type(Agrif_Variable_c), dimension(:), pointer :: Agrif_tabvars_c => NULL()
    305    type(Agrif_Variable_r), dimension(:), pointer :: Agrif_tabvars_r => NULL()
    306    type(Agrif_Variable_l), dimension(:), pointer :: Agrif_tabvars_l => NULL()
    307    type(Agrif_Variable_i), dimension(:), pointer :: Agrif_tabvars_i => NULL()
    308!
    309    integer               :: Agrif_Probdim          !< Problem dimension
    310    integer,dimension(0:4):: Agrif_NbVariables      !< Number of variables
    311    integer               :: Agrif_nbfixedgrids     !< Number of fixed grids in the grid hierarchy
    312    integer, dimension(3) :: Agrif_coeffref         !< Space refinement factor
    313    integer, dimension(3) :: Agrif_coeffreft        !< Time refinement factor
    314    logical               :: Agrif_UseSpecialValue          !< T if use special values on the parent grid
    315    logical               :: Agrif_UseSpecialValueInUpdate  !< T if use special values on the parent grid
    316    logical               :: Agrif_Update_Weights = .FALSE.
    317    logical               :: Agrif_UseSpecialValueFineGrid  !< T if use special values on the current grid
    318    real                  :: Agrif_SpecialValue             !< Special value on the parent grid
    319    real                  :: Agrif_SpecialValueFineGrid     !< Special value on the current grid
    320!>
    321!> \name Clustering parameters
    322!> @{
    323    integer               :: Agrif_Regridding = 10
    324    integer               :: Agrif_Minwidth
    325    real                  :: Agrif_Efficiency = 0.7
    326    integer               :: MaxSearch = 5
    327    real, dimension(3)    :: Agrif_mind
    328!> @}
    329!> \name parameters for the interpolation of the child grids
    330!> @{
    331    integer, parameter    :: Agrif_linear = 1           !< linear interpolation
    332    integer, parameter    :: Agrif_lagrange = 2         !< lagrange interpolation
    333    integer, parameter    :: Agrif_eno = 3              !< spline interpolation
    334    integer, parameter    :: Agrif_user_interp = 4      !< user defined interpolation
    335    integer, parameter    :: Agrif_constant = 5         !< constant interpolation
    336    integer, parameter    :: Agrif_linearconserv = 6    !< linear conservative interpolation
    337    integer, parameter    :: Agrif_linearconservlim = 7 !< linear conservative interpolation
    338    integer, parameter    :: Agrif_ppm = 8              !< PPM interpolation
    339    integer, parameter    :: Agrif_weno = 9             !< WENO5 interpolation
    340    integer, parameter    :: Agrif_ppm_lim = 10         !< PPM interpolation with monotonicity
    341!> @}
    342!> \name parameters for the update of the parent grids
    343!> @{
    344    integer, parameter    :: Agrif_Update_Copy = 1              !< copy
    345    integer, parameter    :: Agrif_Update_Average = 2           !< average
    346    integer, parameter    :: Agrif_Update_Full_Weighting = 3    !< full-weighting
    347!> @}
    348!> \name Raffinement grid switches
    349!> @{
    350    integer               :: Agrif_USE_ONLY_FIXED_GRIDS   !< = 1 if fixed grid mode
    351    integer               :: Agrif_USE_FIXED_GRIDS        !< = 1 if AMR mode + fixed grid else only AMR mode
    352!> @}
    353    integer               :: Agrif_Maxlevelloc
    354!
    355#if defined AGRIF_MPI
    356    integer :: Agrif_Nbprocs  !< Number of processors
    357    integer :: Agrif_ProcRank !< Rank of the current processor
    358    integer :: Agrif_Group    !< Group associated to Agrif_mpi_comm
    359    integer :: Agrif_mpi_comm
    360#else
    361    integer :: Agrif_ProcRank = 0
    362#endif
    363!
    364    integer :: Agrif_Extra_Boundary_Cells = 3       !< When computing integration sequences, the grid rects
    365                                                    !! are expanded to this number of cells.
    366    logical :: Agrif_Parallel_sisters = .FALSE.     !< When TRUE, try to compute sister grids (which have the same parent)
    367                                                    !! in parallel rather than sequentially.
    368    logical :: agrif_regrid_has_been_done = .FALSE. !< switch to skip Agrif_Regrid call
    369!
    370    real, dimension(:)          , allocatable :: parray1
    371    real, dimension(:,:)        , allocatable :: parray2
    372    real, dimension(:,:,:)      , allocatable :: parray3
    373    real, dimension(:,:,:,:)    , allocatable :: parray4
    374    real, dimension(:,:,:,:,:)  , allocatable :: parray5
    375    real, dimension(:,:,:,:,:,:), allocatable :: parray6
    376!
    377    logical :: agrif_debug = .false.    ! may be activaded in users subroutine for debugging purposes
    378
    379! If a grand mother grid is present
    380    logical :: agrif_coarse = .false.
    381    integer, dimension(3) :: coarse_spaceref = (/1,1,1/)
    382    integer, dimension(3) :: coarse_timeref  = (/1,1,1/)
    383!
    384contains
    385!
    386!===================================================================================================
    387!  function Agrif_Ceiling
    388!---------------------------------------------------------------------------------------------------
    389integer function Agrif_Ceiling ( x )
    390!---------------------------------------------------------------------------------------------------
    391    real,   intent(in) :: x
    392!
    393    integer   :: i
    394!
    395    i = FLOOR(x)
    396!
    397    if( ABS(x - i) <= 0.0001 )then
    398        Agrif_Ceiling = i
    399    else
    400        Agrif_Ceiling = i+1
    401    endif
    402!---------------------------------------------------------------------------------------------------
    403end function Agrif_Ceiling
    404!===================================================================================================
    405!
    406!===================================================================================================
    407!  function Agrif_Int
    408!---------------------------------------------------------------------------------------------------
    409    integer function Agrif_Int(x)
    410!---------------------------------------------------------------------------------------------------
    411    real,   intent(in) :: x
    412!
    413    integer :: i
    414!
    415    i = FLOOR(x) + 1
    416!
    417    if( ABS(x - i) <= 0.0001 )then
    418        Agrif_Int = i
    419    else
    420        Agrif_Int = i-1
    421    endif
    422!---------------------------------------------------------------------------------------------------
    423end function Agrif_Int
    424!===================================================================================================
    425!
    426end module Agrif_Types
    Note: See TracBrowser for help on using the repository browser.