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 branches/UKMO/r5936_hadgem3_mct/NEMOGCM/EXTERNAL/AGRIF/AGRIF_FILES – NEMO

source: branches/UKMO/r5936_hadgem3_mct/NEMOGCM/EXTERNAL/AGRIF/AGRIF_FILES/modtypes.F90 @ 7127

Last change on this file since 7127 was 7127, checked in by jcastill, 7 years ago

Remove svn keywords

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(200), dimension(:)  , allocatable :: carray1
157    character(200), dimension(:,:), allocatable :: carray2
158!> @}
159!---------------------------------------------------------------------------------------------------
160end type Agrif_Variable_c
161!===================================================================================================
162!
163!===================================================================================================
164type Agrif_Variable_r
165!---------------------------------------------------------------------------------------------------
166!<  Data type to characterize a grid variable.
167!
168    type(Agrif_Variable_r), pointer  :: root_var   => NULL()      !< pointer on the variable of the root grid
169    type(Agrif_Variable_r), pointer  :: parent_var => NULL()      !< pointer on the parent variable
170!
171    integer                          :: nbdim = 0                 !< number of dimensions of the grid variable
172!
173!> \name Arrays containing the values of the grid variables (real)
174!> @{
175    real                                         :: array0
176    real,    dimension(:)          , allocatable :: array1
177    real,    dimension(:,:)        , allocatable :: array2
178    real,    dimension(:,:,:)      , allocatable :: array3
179    real,    dimension(:,:,:,:)    , allocatable :: array4
180    real,    dimension(:,:,:,:,:)  , allocatable :: array5
181    real,    dimension(:,:,:,:,:,:), allocatable :: array6
182!> @}
183!> \name Arrays containing the values of the grid variables (real*8)
184!> @{
185    real(8)                                      :: darray0
186    real(8), dimension(:)          , allocatable :: darray1
187    real(8), dimension(:,:)        , allocatable :: darray2
188    real(8), dimension(:,:,:)      , allocatable :: darray3
189    real(8), dimension(:,:,:,:)    , allocatable :: darray4
190    real(8), dimension(:,:,:,:,:)  , allocatable :: darray5
191    real(8), dimension(:,:,:,:,:,:), allocatable :: darray6
192!> @}
193!> \name Arrays containing the values of the grid variables (real*4)
194!> @{
195    real(4)                                      :: sarray0
196    real(4), dimension(:)          , allocatable :: sarray1
197    real(4), dimension(:,:)        , allocatable :: sarray2
198    real(4), dimension(:,:,:)      , allocatable :: sarray3
199    real(4), dimension(:,:,:,:)    , allocatable :: sarray4
200    real(4), dimension(:,:,:,:,:)  , allocatable :: sarray5
201    real(4), dimension(:,:,:,:,:,:), allocatable :: sarray6
202!> @}
203!---------------------------------------------------------------------------------------------------
204end type Agrif_Variable_r
205!===================================================================================================
206!===================================================================================================
207!
208!===================================================================================================
209type Agrif_Variable_l
210!---------------------------------------------------------------------------------------------------
211!<  Data type to characterize a grid variable.
212!
213    type(Agrif_Variable_l), pointer  :: root_var   => NULL()      !< pointer on the variable of the root grid
214    type(Agrif_Variable_l), pointer  :: parent_var => NULL()      !< pointer on the parent variable
215!
216    integer                          :: nbdim = 0                 !< number of dimensions of the grid variable
217!
218!> \name Arrays containing the values of the grid variables (logical)
219!> @{
220    logical                                      :: larray0
221    logical, dimension(:)          , allocatable :: larray1
222    logical, dimension(:,:)        , allocatable :: larray2
223    logical, dimension(:,:,:)      , allocatable :: larray3
224    logical, dimension(:,:,:,:)    , allocatable :: larray4
225    logical, dimension(:,:,:,:,:)  , allocatable :: larray5
226    logical, dimension(:,:,:,:,:,:), allocatable :: larray6
227!> @}
228!---------------------------------------------------------------------------------------------------
229end type Agrif_Variable_l
230!===================================================================================================
231!
232!===================================================================================================
233type Agrif_Variable_i
234!---------------------------------------------------------------------------------------------------
235!<  Data type to characterize a grid variable.
236!
237    type(Agrif_Variable_i), pointer  :: root_var   => NULL()      !< pointer on the variable of the root grid
238    type(Agrif_Variable_i), pointer  :: parent_var => NULL()      !< pointer on the parent variable
239!
240    integer                          :: nbdim = 0             !< number of dimensions of the grid variable
241!
242!> \name Arrays containing the values of the grid variables (integer)
243!> @{
244    integer                                      :: iarray0
245    integer, dimension(:)          , allocatable :: iarray1
246    integer, dimension(:,:)        , allocatable :: iarray2
247    integer, dimension(:,:,:)      , allocatable :: iarray3
248    integer, dimension(:,:,:,:)    , allocatable :: iarray4
249    integer, dimension(:,:,:,:,:)  , allocatable :: iarray5
250    integer, dimension(:,:,:,:,:,:), allocatable :: iarray6
251!> @}
252!---------------------------------------------------------------------------------------------------
253end type Agrif_Variable_i
254!===================================================================================================
255!
256!===================================================================================================
257type Agrif_Interp_Loc
258!---------------------------------------------------------------------------------------------------
259    integer,dimension(6)              :: pttab, petab, pttab_Child, pttab_Parent = -99
260    integer,dimension(6)              :: indmin, indmax
261    integer,dimension(6)              :: pttruetab,cetruetab
262    logical :: member, memberin
263#if !defined AGRIF_MPI
264    integer,dimension(6)              :: indminglob,indmaxglob
265#else
266    integer,dimension(6)              :: indminglob2,indmaxglob2
267    integer,dimension(6,2,2)          :: parentarray
268    integer,dimension(:,:,:), pointer :: tab4t          => NULL()
269    integer,dimension(:,:,:), pointer :: tab5t          => NULL()
270    logical, dimension(:),    pointer :: memberinall    => NULL()
271    logical, dimension(:),    pointer :: memberinall2   => NULL()
272    logical, dimension(:),    pointer :: sendtoproc1    => NULL()
273    logical, dimension(:),    pointer :: sendtoproc2    => NULL()
274    logical, dimension(:),    pointer :: recvfromproc1  => NULL()
275    logical, dimension(:),    pointer :: recvfromproc2  => NULL()
276#endif
277!---------------------------------------------------------------------------------------------------
278end type Agrif_Interp_Loc
279!===================================================================================================
280
281!===================================================================================================
282type Agrif_List_Interp_Loc
283!---------------------------------------------------------------------------------------------------
284    type(Agrif_Interp_Loc),      pointer :: interp_loc => NULL()
285    type(Agrif_List_Interp_Loc), pointer :: suiv       => NULL()
286!---------------------------------------------------------------------------------------------------
287end type Agrif_List_Interp_Loc
288!===================================================================================================
289
290!===================================================================================================
291type Agrif_Variables_List
292!---------------------------------------------------------------------------------------------------
293    type(Agrif_Variable),       pointer :: var  => NULL()
294    type(Agrif_Variables_List), pointer :: next => NULL()
295!---------------------------------------------------------------------------------------------------
296end type Agrif_Variables_List
297!===================================================================================================
298!
299!===================================================================================================
300!> Different parameters
301!
302    type(Agrif_Variable),   dimension(:), pointer :: Agrif_tabvars => NULL()
303    type(Agrif_Variable_c), dimension(:), pointer :: Agrif_tabvars_c => NULL()
304    type(Agrif_Variable_r), dimension(:), pointer :: Agrif_tabvars_r => NULL()
305    type(Agrif_Variable_l), dimension(:), pointer :: Agrif_tabvars_l => NULL()
306    type(Agrif_Variable_i), dimension(:), pointer :: Agrif_tabvars_i => NULL()
307!
308    integer               :: Agrif_Probdim          !< Problem dimension
309    integer,dimension(0:4):: Agrif_NbVariables      !< Number of variables
310    integer               :: Agrif_nbfixedgrids     !< Number of fixed grids in the grid hierarchy
311    integer, dimension(3) :: Agrif_coeffref         !< Space refinement factor
312    integer, dimension(3) :: Agrif_coeffreft        !< Time refinement factor
313    logical               :: Agrif_UseSpecialValue          !< T if use special values on the parent grid
314    logical               :: Agrif_UseSpecialValueInUpdate  !< T if use special values on the parent grid
315    logical               :: Agrif_Update_Weights = .FALSE.
316    logical               :: Agrif_UseSpecialValueFineGrid  !< T if use special values on the current grid
317    real                  :: Agrif_SpecialValue             !< Special value on the parent grid
318    real                  :: Agrif_SpecialValueFineGrid     !< Special value on the current grid
319!>
320!> \name Clustering parameters
321!> @{
322    integer               :: Agrif_Regridding = 10
323    integer               :: Agrif_Minwidth
324    real                  :: Agrif_Efficiency = 0.7
325    integer               :: MaxSearch = 5
326    real, dimension(3)    :: Agrif_mind
327!> @}
328!> \name parameters for the interpolation of the child grids
329!> @{
330    integer, parameter    :: Agrif_linear = 1           !< linear interpolation
331    integer, parameter    :: Agrif_lagrange = 2         !< lagrange interpolation
332    integer, parameter    :: Agrif_eno = 3              !< spline interpolation
333    integer, parameter    :: Agrif_user_interp = 4      !< user defined interpolation
334    integer, parameter    :: Agrif_constant = 5         !< constant interpolation
335    integer, parameter    :: Agrif_linearconserv = 6    !< linear conservative interpolation
336    integer, parameter    :: Agrif_linearconservlim = 7 !< linear conservative interpolation
337    integer, parameter    :: Agrif_ppm = 8              !< PPM interpolation
338    integer, parameter    :: Agrif_weno = 9             !< WENO5 interpolation
339    integer, parameter    :: Agrif_ppm_lim = 10         !< PPM interpolation with monotonicity
340!> @}
341!> \name parameters for the update of the parent grids
342!> @{
343    integer, parameter    :: Agrif_Update_Copy = 1              !< copy
344    integer, parameter    :: Agrif_Update_Average = 2           !< average
345    integer, parameter    :: Agrif_Update_Full_Weighting = 3    !< full-weighting
346!> @}
347!> \name Raffinement grid switches
348!> @{
349    integer               :: Agrif_USE_ONLY_FIXED_GRIDS   !< = 1 if fixed grid mode
350    integer               :: Agrif_USE_FIXED_GRIDS        !< = 1 if AMR mode + fixed grid else only AMR mode
351!> @}
352    integer               :: Agrif_Maxlevelloc
353!
354#if defined AGRIF_MPI
355    integer :: Agrif_Nbprocs  !< Number of processors
356    integer :: Agrif_ProcRank !< Rank of the current processor
357    integer :: Agrif_Group    !< Group associated to Agrif_mpi_comm
358    integer :: Agrif_mpi_comm
359#else
360    integer :: Agrif_ProcRank = 0
361#endif
362!
363    integer :: Agrif_Extra_Boundary_Cells = 3       !< When computing integration sequences, the grid rects
364                                                    !! are expanded to this number of cells.
365    logical :: Agrif_Parallel_sisters = .FALSE.     !< When TRUE, try to compute sister grids (which have the same parent)
366                                                    !! in parallel rather than sequentially.
367    logical :: agrif_regrid_has_been_done = .FALSE. !< switch to skip Agrif_Regrid call
368!
369    real, dimension(:)          , allocatable :: parray1
370    real, dimension(:,:)        , allocatable :: parray2
371    real, dimension(:,:,:)      , allocatable :: parray3
372    real, dimension(:,:,:,:)    , allocatable :: parray4
373    real, dimension(:,:,:,:,:)  , allocatable :: parray5
374    real, dimension(:,:,:,:,:,:), allocatable :: parray6
375!
376    logical :: agrif_debug = .false.    ! may be activaded in users subroutine for debugging purposes
377
378! If a grand mother grid is present
379    logical :: agrif_coarse = .false.
380    integer, dimension(3) :: coarse_spaceref = (/1,1,1/)
381    integer, dimension(3) :: coarse_timeref  = (/1,1,1/)
382!
383contains
384!
385!===================================================================================================
386!  function Agrif_Ceiling
387!---------------------------------------------------------------------------------------------------
388integer function Agrif_Ceiling ( x )
389!---------------------------------------------------------------------------------------------------
390    real,   intent(in) :: x
391!
392    integer   :: i
393!
394    i = FLOOR(x)
395!
396    if( ABS(x - i) <= 0.0001 )then
397        Agrif_Ceiling = i
398    else
399        Agrif_Ceiling = i+1
400    endif
401!---------------------------------------------------------------------------------------------------
402end function Agrif_Ceiling
403!===================================================================================================
404!
405!===================================================================================================
406!  function Agrif_Int
407!---------------------------------------------------------------------------------------------------
408    integer function Agrif_Int(x)
409!---------------------------------------------------------------------------------------------------
410    real,   intent(in) :: x
411!
412    integer :: i
413!
414    i = FLOOR(x) + 1
415!
416    if( ABS(x - i) <= 0.0001 )then
417        Agrif_Int = i
418    else
419        Agrif_Int = i-1
420    endif
421!---------------------------------------------------------------------------------------------------
422end function Agrif_Int
423!===================================================================================================
424!
425end module Agrif_Types
Note: See TracBrowser for help on using the repository browser.