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.F in trunk/AGRIF/AGRIF_FILES – NEMO

source: trunk/AGRIF/AGRIF_FILES/modtypes.F @ 396

Last change on this file since 396 was 396, checked in by opalod, 18 years ago

Initial revision

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 15.9 KB
Line 
1C     Agrif (Adaptive Grid Refinement In Fortran)
2C
3C     Copyright (C) 2003 Laurent Debreu (Laurent.Debreu@imag.fr)
4C                        Christophe Vouland (Christophe.Vouland@imag.fr)   
5C
6C     This program is free software; you can redistribute it and/or modify
7C     it under the terms of the GNU General Public License as published by
8C     the Free Software Foundation; either version 2 of the License, or
9C     (at your option) any later version.
10C
11C     This program is distributed in the hope that it will be useful,
12C     but WITHOUT ANY WARRANTY; without even the implied warranty of
13C     MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
14C     GNU General Public License for more details.
15C
16C     You should have received a copy of the GNU General Public License
17C     along with this program; if not, write to the Free Software
18C     Foundation, Inc., 59 Temple Place-Suite 330, Boston, MA 02111-1307, USA.
19C
20C
21C
22CCC   Module Agrif_types 
23C
24      Module Agrif_types 
25C
26CCC   Description:
27CCC   Definition of data types used in Agrif, of several variables and
28C        PARAMETERs.     
29C
30      IMPLICIT NONE
31C
32C     **************************************************************************
33CCC   TYPE Agrif_LRECTANGLE
34C     **************************************************************************
35C
36CCC   Description:
37CCC   Data TYPE allowing a grid to reach a grid on the same level or its child
38CCC   grids.
39C
40      TYPE Agrif_lrectangle 
41           TYPE(Agrif_rectangle) , Pointer :: r    ! to reach a child grid
42           TYPE(Agrif_lrectangle), Pointer :: next ! to reach a grid on the
43                                                   !    same level
44      End TYPE Agrif_lrectangle 
45C
46C     **************************************************************************
47CCC   TYPE Agrif_RECTANGLE: 
48C     **************************************************************************
49C
50CCC   Description:
51CCC   Data TYPE to define several CHARACTERistics of a grid (number,position,
52CCC   time and space refinement factors,...). 
53C
54      TYPE Agrif_rectangle
55           INTEGER                         :: number      ! Number of the grid
56           ! Number of child grids
57           INTEGER                         :: nbgridchild 
58           ! Minimal position in the x,y and z direction
59           INTEGER, DIMENSION(3)           :: imin       
60           ! Maximal position in the x,y and z direction
61           INTEGER, DIMENSION(3)           :: imax 
62           ! Space refinement factor in the x,y and z direction 
63           INTEGER, DIMENSION(3)           :: spaceref   
64           ! Time refinement factor in the x,y and z direction
65           INTEGER, DIMENSION(3)           :: timeref     
66           ! Pointer to reach a grid on  the same level or a child grid
67           TYPE(Agrif_lrectangle), Pointer :: childgrids 
68      End TYPE Agrif_rectangle 
69C
70C
71C
72C     **************************************************************************
73CCC   TYPE Agrif_PGrid
74C     **************************************************************************
75C
76CCC   Description:
77CCC   Data TYPE to go over the grid hierarchy (used for the creation of this 
78CCC   grid hierarchy and during the time integration).
79C 
80      TYPE Agrif_pgrid 
81           ! allows to reach a child grid 
82           TYPE(Agrif_grid) , Pointer :: gr
83           ! allows to reach the grids of the same level
84           TYPE(Agrif_pgrid), Pointer :: next 
85      End TYPE Agrif_pgrid 
86C
87C
88C
89C     **************************************************************************
90CCC   TYPE Agrif_PVariable
91C     **************************************************************************
92C
93CCC   Description:
94CCC   Data TYPE to define a grid variable.
95C
96      TYPE Agrif_PVariable 
97           ! This field allows to get the various CHARACTERistics
98           !   of the variable (defined by the Agrif_Variable data TYPE)
99           TYPE(Agrif_Variable) , Pointer :: var 
100           ! Pointer on the parent grid
101           TYPE(Agrif_PVariable), Pointer :: parent_var 
102      End TYPE Agrif_PVariable 
103C
104C     **************************************************************************
105CCC   TYPE Agrif_Grid
106C     **************************************************************************
107C
108CCC   Description:
109CCC   Data TYPE to define a grid (position, space and time refinement factors).
110C
111      TYPE Agrif_grid 
112           ! pointer on the parent grid
113           TYPE(Agrif_grid)                    ,Pointer :: parent     
114           ! pointer on the child grids
115           TYPE(Agrif_pgrid)                   ,Pointer :: child_grids 
116           ! List of the grid variables   
117           TYPE(Agrif_PVariable), DIMENSION(:) ,Pointer :: tabvars     
118C
119           ! Global x,y and z position
120           REAL    ,DIMENSION(3)                   :: Agrif_x   
121           ! Global space step in the x,y and z direction
122           REAL    ,DIMENSION(3)                   :: Agrif_d
123           ! number of cells in the x,y and z direction
124           INTEGER ,DIMENSION(3)                   :: nb       
125           ! minimal position in the x,y and z direction
126           INTEGER ,DIMENSION(3)                   :: ix       
127           ! Space refinement factor in the x,y and z direction
128           INTEGER ,DIMENSION(3)                   :: spaceref 
129           ! Time refinement factor in the x,y and z direction
130           INTEGER ,DIMENSION(3)                   :: timeref   
131           INTEGER ,DIMENSION(:)          ,Pointer :: restore1D   
132           INTEGER ,DIMENSION(:,:)        ,Pointer :: restore2D   
133           INTEGER ,DIMENSION(:,:,:)      ,Pointer :: restore3D 
134           INTEGER ,DIMENSION(:,:,:,:)    ,Pointer :: restore4D
135           INTEGER ,DIMENSION(:,:,:,:,:)  ,Pointer :: restore5D
136           INTEGER ,DIMENSION(:,:,:,:,:,:),Pointer :: restore6D
137           ! number of time step 
138           INTEGER                                 :: ngridstep 
139           INTEGER                                 :: rank 
140           !moving grid id
141           INTEGER                                 :: grid_id
142           ! number of the grid
143           INTEGER                                 :: fixedrank 
144           ! fixed or moving grid ? 
145           LOGICAL                                 :: fixed     
146           LOGICAL                                 :: oldgrid   
147C          LOGICALs indicating if the current grid has a common border 
148C             with the root coarse grid
149           LOGICAL ,DIMENSION(3)                   :: NearRootBorder
150           LOGICAL ,DIMENSION(3)                   :: DistantRootBorder
151C          Arrays for adaptive grid refinement
152           REAL    ,DIMENSION(:)          ,Pointer :: valtabpoint1D
153           REAL    ,DIMENSION(:,:)        ,Pointer :: valtabpoint2D
154           REAL    ,DIMENSION(:,:,:)      ,Pointer :: valtabpoint3D
155           INTEGER ,DIMENSION(:)          ,Pointer :: tabpoint1D
156           INTEGER ,DIMENSION(:,:)        ,Pointer :: tabpoint2D
157           INTEGER ,DIMENSION(:,:,:)      ,Pointer :: tabpoint3D
158      End TYPE Agrif_grid
159C
160C     **************************************************************************
161CCC   TYPE Agrif_VARIABLE
162C     **************************************************************************
163C     
164CCC   Description:
165CCC   Data TYPE to CHARACTERize a grid variable.   
166C
167      TYPE Agrif_Variable 
168C       
169         ! Pointer on the variable of the root grid
170         TYPE(Agrif_Variable), Pointer :: root_var 
171C
172         ! index of the first point in the REAL domain (x,y and z direction)
173         INTEGER     ,DIMENSION(6)          :: point
174         ! position of the variable on the cell (1 for the boarder of
175         !    the edge, 2 for the center)
176         INTEGER     ,DIMENSION(:) ,Pointer :: posvar      => NULL() 
177         ! Indication for the space interpolation (module Agrif_Boundary)
178         INTEGER                   ,Pointer :: interpIndex => NULL() 
179         ! number of DIMENSIONs of the grid variable
180         INTEGER                            :: nbdim = 0             
181         ! Array indicating the TYPE of DIMENSION (space or not) for
182         !    each of them
183         CHARACTER(6),DIMENSION(:) ,Pointer :: interptab   => NULL() 
184C        Arrays containing the values of the grid variables (REAL)
185         REAL                                    :: array0 
186         REAL   , DIMENSION(:)          ,Pointer :: array1    => NULL()
187         REAL   , DIMENSION(:,:)        ,Pointer :: array2    => NULL()
188         REAL   , DIMENSION(:,:,:)      ,Pointer :: array3    => NULL()
189         REAL   , DIMENSION(:,:,:,:)    ,Pointer :: array4    => NULL()
190         REAL   , DIMENSION(:,:,:,:,:)  ,Pointer :: array5    => NULL()
191         REAL   , DIMENSION(:,:,:,:,:,:),Pointer :: array6    => NULL()
192C        Arrays containing the values of the grid variables (REAL*8)
193         REAL(8)                                 :: darray0
194         REAL(8), DIMENSION(:)          ,Pointer :: darray1   => NULL()
195         REAL(8), DIMENSION(:,:)        ,Pointer :: darray2   => NULL()
196         REAL(8), DIMENSION(:,:,:)      ,Pointer :: darray3   => NULL()
197         REAL(8), DIMENSION(:,:,:,:)    ,Pointer :: darray4   => NULL()
198         REAL(8), DIMENSION(:,:,:,:,:)  ,Pointer :: darray5   => NULL()
199         REAL(8), DIMENSION(:,:,:,:,:,:),Pointer :: darray6   => NULL()
200C        Arrays containing the values of the grid variables (LOGICAL)
201         LOGICAL                                 :: larray0
202         LOGICAL, DIMENSION(:)          ,Pointer :: larray1   => NULL()
203         LOGICAL, DIMENSION(:,:)        ,Pointer :: larray2   => NULL()
204         LOGICAL, DIMENSION(:,:,:)      ,Pointer :: larray3   => NULL()
205         LOGICAL, DIMENSION(:,:,:,:)    ,Pointer :: larray4   => NULL()
206         LOGICAL, DIMENSION(:,:,:,:,:)  ,Pointer :: larray5   => NULL()
207         LOGICAL, DIMENSION(:,:,:,:,:,:),Pointer :: larray6   => NULL()
208C         Arrays containing the values of the grid variables (INTEGER)   
209         INTEGER                                 :: iarray0
210         INTEGER, DIMENSION(:)          ,Pointer :: iarray1   => NULL()
211         INTEGER, DIMENSION(:,:)        ,Pointer :: iarray2   => NULL()
212         INTEGER, DIMENSION(:,:,:)      ,Pointer :: iarray3   => NULL()
213         INTEGER, DIMENSION(:,:,:,:)    ,Pointer :: iarray4   => NULL()
214         INTEGER, DIMENSION(:,:,:,:,:)  ,Pointer :: iarray5   => NULL()
215         INTEGER, DIMENSION(:,:,:,:,:,:),Pointer :: iarray6   => NULL()
216C
217         INTEGER, DIMENSION(:)          ,Pointer :: restore1D => NULL()
218         INTEGER, DIMENSION(:,:)        ,Pointer :: restore2D => NULL()
219         INTEGER, DIMENSION(:,:,:)      ,Pointer :: restore3D => NULL()
220         INTEGER, DIMENSION(:,:,:,:)    ,Pointer :: restore4D => NULL()
221         INTEGER, DIMENSION(:,:,:,:,:)  ,Pointer :: restore5D => NULL()
222         INTEGER, DIMENSION(:,:,:,:,:,:),Pointer :: restore6D => NULL()
223C   
224         CHARACTER(2050)                          :: carray0
225         CHARACTER(200), DIMENSION(:)    ,Pointer :: carray1   => NULL()
226         CHARACTER(200), DIMENSION(:,:)  ,Pointer :: carray2   => NULL()
227C
228         ! Array used for the time interpolation
229         REAL   , DIMENSION(:,:)      ,Pointer :: oldvalues2D => NULL()
230
231         ! if the variable should be restore -> =1
232         LOGICAL :: restaure = .FALSE.
233         ! the interpolation should be made in any case
234         LOGICAL :: Interpolationshouldbemade = .FALSE. 
235         INTEGER :: bcinf ! option bc
236         INTEGER :: bcsup ! option bc
237         INTEGER :: updateinf ! option update
238         INTEGER :: updatesup ! option update         
239         INTEGER, DIMENSION(6) :: bcTYPEinterp ! option bcinterp
240         INTEGER, DIMENSION(6) :: TYPEinterp ! option interp
241         INTEGER, DIMENSION(6) :: TYPEupdate ! option update
242C
243      End TYPE Agrif_Variable   
244C
245C     **************************************************************************
246CCC   Different PARAMETERs
247C     **************************************************************************
248      TYPE(Agrif_PVariable), DIMENSION(:) ,Pointer :: Agrif_tabvars
249C
250      ! this pointer always points on the root grid of the grid hierarchy
251      TYPE(Agrif_grid)  ,Pointer :: Agrif_Mygrid     
252      ! Pointer used in the Agrif_regrid subroutine (Agrif_Util module).
253      !    It contains  the safeguard of the grid hierarchy.
254      TYPE(Agrif_pgrid) ,Pointer :: Agrif_oldmygrid   
255      ! pointer to the current grid (the link is done by using the
256      !    Agrif_Instance   procedure (module Agrif_Init))
257      TYPE(Agrif_grid)  ,Pointer :: Agrif_Curgrid
258      ! Pointer used in the Agrif_ChildGrid_to_ParentGrid and
259      !    Agrif_ParentGrid_to_ChildGrid subroutines
260      !    (Agrif_CurgridFunctions module). It contains the
261      !    safeguard of the current grid hierarchy.
262      TYPE(Agrif_grid)  ,Pointer :: Agrif_saveCURGRID
263C
264      ! Problem DIMENSION
265      INTEGER               :: Agrif_Probdim
266      ! number of variables
267      INTEGER               :: Agrif_NbVariables
268      ! number of fixed grids in the grid hierarchy
269      INTEGER               :: Agrif_nbfixedgrids           
270      ! space refinement factor
271      INTEGER ,DIMENSION(3) :: Agrif_coeffref
272      ! time refinement factor
273      INTEGER ,DIMENSION(3) :: Agrif_coeffreft
274      ! LOGICAL to use special values on the parent grid
275      LOGICAL               :: Agrif_UseSpecialValue
276      ! LOGICAL to use special values on the parent grid
277      LOGICAL               :: Agrif_UseSpecialValueInUpdate
278      ! LOGICAL to use special values on the current grid
279      LOGICAL               :: Agrif_UseSpecialValueFineGrid
280      ! Special values on the parent grid
281      REAL                  :: Agrif_SpecialValue
282      ! Special values on the current grid
283      REAL                  :: Agrif_SpecialValueFineGrid
284C   clustering PARAMETERs
285      INTEGER               :: Agrif_Regridding
286      INTEGER               :: Agrif_Minwidth
287      REAL                  :: Agrif_Efficiency
288      REAL    ,DIMENSION(3) :: Agrif_mind
289C     PARAMETERs for the interpolation of the child grids
290      ! linear interpolation
291      INTEGER ,PARAMETER    :: Agrif_linear=1
292      ! lagrange interpolation
293      INTEGER ,PARAMETER    :: Agrif_lagrange=2
294      ! spline interpolation
295      INTEGER ,PARAMETER    :: Agrif_eno=3
296      ! user s interpolation
297      INTEGER ,PARAMETER    :: Agrif_user_interp=4
298      ! constant interpolation
299      INTEGER ,PARAMETER    :: Agrif_constant=5
300      ! linear conservative interpolation
301      INTEGER ,PARAMETER    :: Agrif_linearconserv=6
302      ! linear conservative interpolation       
303      INTEGER ,PARAMETER    :: Agrif_linearconservlim=7
304      INTEGER ,PARAMETER    :: Agrif_ppm=8   
305C     PARAMETERs for the update of the parent grids     
306      INTEGER ,PARAMETER    :: Agrif_Update_Copy=1           ! copy
307      INTEGER ,PARAMETER    :: Agrif_Update_Average=2        ! average
308      INTEGER ,PARAMETER    :: Agrif_Update_Full_Weighting=3 ! full-weighting
309C     Raffinement grid switch definition
310      ! Agrif_USE_ONLY_FIXED_GRIDS =1 if fixed grid mode
311      INTEGER               :: Agrif_USE_ONLY_FIXED_GRIDS   
312      ! Agrif_USE_FIXED_GRIDS = 1 if AMR mode + fixed grid
313      !    else only AMR mode
314      INTEGER               :: Agrif_USE_FIXED_GRIDS         
315C
316#ifdef AGRIF_MPI
317      INTEGER :: Agrif_Nbprocs  ! Number of processors
318      INTEGER :: Agrif_ProcRank ! Rank of the current processor
319      INTEGER :: Agrif_Group    ! Group associated to MPI_COMM_WORLD
320      INTEGER :: Agrif_MPIPREC
321#endif
322C
323      contains
324C   
325      Integer Function agrif_ceiling(x)
326C             
327          Real :: x
328          Integer ::i 
329C
330          i = floor(x)
331C     
332          if( abs(x - i).le.0.0001 )then
333             agrif_ceiling = i
334          else
335             agrif_ceiling = i+1
336          endif     
337C
338      End Function
339C
340      Integer Function agrif_int(x)
341C             
342          Real :: x
343          Integer ::i 
344C
345          i = floor(x) + 1
346C     
347          if( abs(x - i).le.0.0001 )then
348             agrif_int = i
349          else
350             agrif_int = i-1
351          endif     
352C
353      End Function
354      End Module Agrif_TYPEs 
Note: See TracBrowser for help on using the repository browser.