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/CMEMS_2020/AGRIF_FILES – NEMO

source: vendors/AGRIF/CMEMS_2020/AGRIF_FILES/modtypes.F90 @ 10098

Last change on this file since 10098 was 10098, checked in by rblod, 6 years ago

Initialisation of GArif structures

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