Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
RFLO_MoveGridGlobal.F90
Go to the documentation of this file.
1 ! *********************************************************************
2 ! * Rocstar Simulation Suite *
3 ! * Copyright@2015, Illinois Rocstar LLC. All rights reserved. *
4 ! * *
5 ! * Illinois Rocstar LLC *
6 ! * Champaign, IL *
7 ! * www.illinoisrocstar.com *
8 ! * sales@illinoisrocstar.com *
9 ! * *
10 ! * License: See LICENSE file in top level of distribution package or *
11 ! * http://opensource.org/licenses/NCSA *
12 ! *********************************************************************
13 ! *********************************************************************
14 ! * THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, *
15 ! * EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES *
16 ! * OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND *
17 ! * NONINFRINGEMENT. IN NO EVENT SHALL THE CONTRIBUTORS OR *
18 ! * COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER *
19 ! * LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, *
20 ! * Arising FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE *
21 ! * USE OR OTHER DEALINGS WITH THE SOFTWARE. *
22 ! *********************************************************************
23 !******************************************************************************
24 !
25 ! Purpose: redistribute grid nodes according to the movement of the
26 ! boundaries. This function smoothes the grid globally by
27 ! solving the Laplace equation for node coordinates.
28 !
29 ! Description: none.
30 !
31 ! Input: regions = data of all grid regions.
32 !
33 ! Output: regions%levels%grid%xyz = new grid coordinates.
34 !
35 ! Notes: grid%xyz temporarily stores nodal displacements. The deformation
36 ! is applied to the finest grid first.
37 !
38 !******************************************************************************
39 !
40 ! $Id: RFLO_MoveGridGlobal.F90,v 1.9 2008/12/06 08:44:27 mtcampbe Exp $
41 !
42 ! Copyright: (c) 2003 by the University of Illinois
43 !
44 !******************************************************************************
45 
46 SUBROUTINE rflo_movegridglobal( regions )
47 
48  USE moddatatypes
49  USE modbndpatch, ONLY : t_patch
50  USE modglobal, ONLY : t_global
51  USE moddatastruct, ONLY : t_region
52  USE modgrid, ONLY : t_grid
61  USE moderror
62  USE modmpi
63  USE modparameters
64  IMPLICIT NONE
65 
66 #ifdef GENX
67  include 'roccomf90.h'
68 #endif
69 
70 ! ... parameters
71  TYPE(t_region), POINTER :: regions(:)
72 
73 ! ... loop variables
74  INTEGER :: ireg, iter, ipatch, ijk
75 
76 ! ... local variables
77  LOGICAL :: somemoved, someremesh
78 
79  INTEGER :: bctype, iremesh, jremesh, nremesh
80 
81  REAL(RFREAL) :: resid, globalresid
82  REAL(RFREAL), POINTER :: xyz(:,:), xyzold(:,:)
83 
84  TYPE(t_grid), POINTER :: grid, gridold
85  TYPE(t_global), POINTER :: global
86  TYPE(t_patch), POINTER :: patch
87 #ifdef GENX
88  DOUBLE PRECISION :: dalpha
89 #endif
90 
91 !******************************************************************************
92 
93  global => regions(1)%global
94 
95  CALL registerfunction( global,'RFLO_MoveGridGlobal',&
96  'RFLO_MoveGridGlobal.F90' )
97 
98 #ifdef GENX
99 ! update geometry buffers -----------------------------------------------------
100 
101  dalpha = global%dtMin/global%dTimeSystem
102  CALL com_call_function( global%genxHandleGm,1,dalpha )
103 #endif
104 
105 ! receive and distribute deformations for each region -------------------------
106 
107  CALL rflo_movegridsurfaces( regions,somemoved )
108 
109 ! fix interfaces between regions ----------------------------------------------
110 
111  IF (somemoved) THEN
112  CALL rflo_movegridinterfaces( regions )
113  ENDIF
114 
115 ! update grid, dummy, corner and edge cells -----------------------------------
116 
117  IF (somemoved) THEN
118  DO ireg=1,global%nRegions
119  IF (regions(ireg)%procid==global%myProcid .AND. & ! region active and
120  regions(ireg)%active==active .AND. & ! on my processor
121  regions(ireg)%mixtInput%moveGrid) THEN ! and moving
122 
123 ! ----- change the interior grid
124 
125  grid => regions(ireg)%levels(1)%grid
126  gridold => regions(ireg)%levels(1)%gridOld
127  CALL rflo_changeinteriorgrid( regions(ireg),grid%boundMoved, &
128  grid%edgeMoved,grid%arcLen12, &
129  grid%arcLen34,grid%arcLen56, &
130  gridold%xyzOld,grid%xyz )
131 
132 ! ----- update coarse grids and dummy cells
133 
134  CALL rflo_generatecoarsegrids( regions(ireg) ) ! coarsen finest grid
135  CALL rflo_copygeometrydummy( regions(ireg) ) ! copy to dummy nodes
136  CALL rflo_extrapolategeometry( regions(ireg) ) ! extrapolate
137  ENDIF ! region on this processor and active, grid moving
138  ENDDO ! iReg
139  CALL rflo_exchangegeometry( regions ) ! exchange geometry
140  ENDIF
141 
142 ! smooth grid by solving Laplace equation -------------------------------------
143 
144  IF (somemoved) THEN
145  DO iter=1,global%moveGridNiter
146  CALL rflo_laplacegridsmoo( regions,resid )
147  ENDDO
148 
149  IF (global%verbLevel /= verbose_none) THEN
150 #ifdef MPI
151  CALL mpi_reduce( resid,globalresid,1,mpi_rfreal,mpi_sum, &
152  masterproc,global%mpiComm,global%mpierr )
153  IF (global%mpierr /= 0) CALL errorstop( global,err_mpi_trouble,__line__ )
154 #else
155  globalresid = resid
156 #endif
157  IF (global%myProcid == masterproc) THEN
158  WRITE(stdout,1000) solver_name,global%moveGridNiter,sqrt(globalresid)
159  ENDIF
160  ENDIF ! verbLevel
161  ENDIF ! someMoved
162 
163 ! update grid, dummy, corner and edge cells -----------------------------------
164 
165  DO ireg=1,global%nRegions
166  IF (regions(ireg)%procid==global%myProcid .AND. & ! region active and
167  regions(ireg)%active==active .AND. & ! on my processor
168  regions(ireg)%mixtInput%moveGrid) THEN ! and moving
169 
170 ! --- change xyz from coordinates to deformations
171 
172  xyz => regions(ireg)%levels(1)%grid%xyz
173  xyzold => regions(ireg)%levels(1)%gridOld%xyz
174 
175  DO ijk=lbound(xyz,2),ubound(xyz,2)
176  xyz(xcoord,ijk) = xyz(xcoord,ijk) - xyzold(xcoord,ijk)
177  xyz(ycoord,ijk) = xyz(ycoord,ijk) - xyzold(ycoord,ijk)
178  xyz(zcoord,ijk) = xyz(zcoord,ijk) - xyzold(zcoord,ijk)
179  ENDDO
180 
181 ! --- redistribute deformations at boundaries
182 
183  grid => regions(ireg)%levels(1)%grid
184  gridold => regions(ireg)%levels(1)%gridOld
185  grid%boundMoved(:) = .true.
186  grid%edgeMoved(:) = .true.
187  DO ipatch=1,regions(ireg)%nPatches
188  patch => regions(ireg)%levels(1)%patches(ipatch)
189  bctype = patch%bcType
190  IF ((bctype>=bc_symmetry .AND. bctype<=bc_symmetry+bc_range)) THEN
191  grid%boundMoved(patch%lbound) = .false.
192  ENDIF ! bcType
193  ENDDO ! iPatch
194  CALL rflo_boundarydeformation( regions(ireg),grid%boundMoved, &
195  grid%edgeMoved,grid%arcLen12, &
196  grid%arcLen34,grid%arcLen56, &
197  gridold%xyzOld,grid%xyz )
198 
199 ! --- change xyz from deformations to coordinates
200 
201  CALL rflo_changeinteriorgrid( regions(ireg),grid%boundMoved, &
202  grid%edgeMoved,grid%arcLen12, &
203  grid%arcLen34,grid%arcLen56, &
204  gridold%xyzOld,grid%xyz )
205 
206 ! --- update coarse grids and dummy cells
207 
208  CALL rflo_generatecoarsegrids( regions(ireg) ) ! coarsen finest grid
209  CALL rflo_copygeometrydummy( regions(ireg) ) ! copy to dummy nodes
210  CALL rflo_extrapolategeometry( regions(ireg) ) ! extrapolate
211  ENDIF ! region on this processor and active, grid moving
212  ENDDO ! iReg
213 
214  CALL rflo_exchangegeometry( regions ) ! exchange geometry
215 
216 ! calculate new metrics and grid speeds ---------------------------------------
217 
218  someremesh = .false.
219  iremesh = 0
220  DO ireg=1,global%nRegions
221  IF (regions(ireg)%procid==global%myProcid .AND. & ! region active and
222  regions(ireg)%active==active .AND. & ! on my processor
223  regions(ireg)%mixtInput%moveGrid) THEN ! and moving
224  CALL rflo_calcfacevectors( regions(ireg) ) ! faces
225  CALL rflo_calccontrolvolumes( regions(ireg) ) ! volumes
226  CALL rflo_calccellcentroids( regions(ireg) ) ! cell centroids
227  IF (regions(ireg)%mixtInput%faceEdgeAvg==fe_avg_linear) &
228  CALL rflo_c2favgcoeffs( regions(ireg) ) ! cell2face averaging
229  CALL rflo_c2eavgcoeffs( regions(ireg) ) ! cell2edge averaging
230  CALL rflo_checkmetrics( ireg,regions(ireg) ) ! check metrics
231 ! IF (regions(iReg)%levels(1)%grid%remesh==1) THEN
232 ! CALL RFLO_GridRemesh( regions(iReg) ) ! grid remeshing
233 ! iRemesh=1
234 ! ENDIF
235  CALL rflo_calcgridspeeds( regions(ireg) ) ! grid speeds
236  ENDIF ! region on this processor and active, grid moving
237  ENDDO ! iReg
238 
239 #ifdef MPI
240  CALL mpi_allreduce( iremesh, nremesh, 1, mpi_integer, mpi_sum, &
241  global%mpiComm, global%mpierr )
242  IF (global%mpierr /=0 ) CALL errorstop( global,err_mpi_trouble,__line__ )
243  IF (nremesh > 0) someremesh = .true.
244 #endif
245 
246  IF (someremesh) THEN
247  CALL rflo_exchangegeometry( regions ) ! exchange geometry
248  DO ireg=1,global%nRegions
249  IF (regions(ireg)%procid==global%myProcid .AND. & ! region active and
250  regions(ireg)%active==active .AND. & ! on my processor
251  iremesh==1) THEN ! and remeshing
252  CALL rflo_calcfacevectors( regions(ireg) ) ! faces
253  CALL rflo_calccontrolvolumes( regions(ireg) ) ! volumes
254  CALL rflo_calccellcentroids( regions(ireg) ) ! cell centroids
255  IF (regions(ireg)%mixtInput%faceEdgeAvg==fe_avg_linear) &
256  CALL rflo_c2favgcoeffs( regions(ireg) ) ! cell2face averaging
257  CALL rflo_c2eavgcoeffs( regions(ireg) ) ! cell2edge averaging
258  ENDIF ! region on this processor and active, grid moving
259  ENDDO ! iReg
260  ENDIF
261 
262 ! finalize --------------------------------------------------------------------
263 
264  CALL deregisterfunction( global )
265 
266 1000 FORMAT(a,1x,'Block Laplacian grid motion: ',i6,1pe13.4)
267 
268 END SUBROUTINE rflo_movegridglobal
269 
270 !******************************************************************************
271 !
272 ! RCS Revision history:
273 !
274 ! $Log: RFLO_MoveGridGlobal.F90,v $
275 ! Revision 1.9 2008/12/06 08:44:27 mtcampbe
276 ! Updated license.
277 !
278 ! Revision 1.8 2008/11/19 22:17:38 mtcampbe
279 ! Added Illinois Open Source License/Copyright
280 !
281 ! Revision 1.7 2006/03/05 19:13:57 wasistho
282 ! set computational space coordinates from initial grid
283 !
284 ! Revision 1.6 2006/03/03 00:48:28 wasistho
285 ! renamed global grid motion to block laplacian motion
286 !
287 ! Revision 1.5 2005/11/03 02:40:28 wasistho
288 ! activate boundaryDeformation and chngInteriorGrid
289 !
290 ! Revision 1.4 2005/10/27 05:51:48 wasistho
291 ! added USE RFLO_ModLaplaceSmoothing
292 !
293 ! Revision 1.3 2005/05/28 05:52:32 wasistho
294 ! refrain from grid remeshing
295 !
296 ! Revision 1.2 2005/05/27 01:51:17 wasistho
297 ! added remeshing
298 !
299 ! Revision 1.1 2004/11/29 20:51:39 wasistho
300 ! lower to upper case
301 !
302 ! Revision 1.10 2004/09/02 02:35:26 wasistho
303 ! added face-edge averaging input-option parameter in Rocflo
304 !
305 ! Revision 1.9 2004/08/03 22:46:18 wasistho
306 ! added RFLO_c2eAvgCoeffs
307 !
308 ! Revision 1.8 2004/07/30 17:26:12 wasistho
309 ! provide cell2face averaging coefficients
310 !
311 ! Revision 1.7 2003/11/20 16:40:39 mdbrandy
312 ! Backing out RocfluidMP changes from 11-17-03
313 !
314 ! Revision 1.3 2003/08/27 23:58:10 jblazek
315 ! Removed 2nd interface to RFLO_ChangeInteriorGrid.
316 !
317 ! Revision 1.2 2003/08/25 21:51:24 jblazek
318 ! Full version of global grid motion scheme.
319 !
320 ! Revision 1.1 2003/08/11 21:51:18 jblazek
321 ! Added basic global grid smoothing scheme.
322 !
323 !******************************************************************************
324 
325 
326 
327 
328 
329 
330 
subroutine rflo_copygeometrydummy(region)
subroutine rflo_calccellcentroids(region)
subroutine rflo_c2eavgcoeffs(region)
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
subroutine rflo_extrapolategeometry(region)
subroutine rflo_c2favgcoeffs(region)
double sqrt(double d)
Definition: double.h:73
subroutine rflo_changeinteriorgrid(region, boundMoved, edgeMoved, arcLen12, arcLen34, arcLen56, xyzOld, xyz)
subroutine rflo_movegridinterfaces(regions)
subroutine rflo_calccontrolvolumes(region)
Definition: patch.h:74
subroutine rflo_calcfacevectors(region)
subroutine rflo_exchangegeometry(regions)
subroutine rflo_movegridsurfaces(regions, someMoved)
subroutine rflo_generatecoarsegrids(region)
void int int REAL * x
Definition: read.cpp:74
subroutine rflo_calcgridspeeds(region)
subroutine rflo_gridremesh(region)
subroutine rflo_movegridglobal(regions)
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
subroutine rflo_boundarydeformation(region, boundMoved, edgeMoved, arcLen12, arcLen34, arcLen56, xyzOld, dNode)
subroutine grid(bp)
Definition: setup_py.f90:257
subroutine deregisterfunction(global)
Definition: ModError.F90:469
subroutine rflo_checkmetrics(iReg, region)
RT a() const
Definition: Line_2.h:140
subroutine rflo_laplacegridsmoo(regions, resid)