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 @ 10725

Last change on this file since 10725 was 10725, checked in by rblod, 5 years ago

Update agrif library and conv see ticket #2129

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