Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
RFLO_ReadRegionTopology.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: read in topology of all regions (done on all processors);
26 ! figure out which l1,l2 directions are aligned on adjacent regions.
27 !
28 ! Description: none.
29 !
30 ! Input: none.
31 !
32 ! Output: global%nRegions = number of regions
33 ! regions = region dimensions and topology
34 !
35 ! Notes: none.
36 !
37 !******************************************************************************
38 !
39 ! $Id: RFLO_ReadRegionTopology.F90,v 1.12 2009/08/27 14:04:49 mtcampbe Exp $
40 !
41 ! Copyright: (c) 2001 by the University of Illinois
42 !
43 !******************************************************************************
44 
45 SUBROUTINE rflo_readregiontopology( global,regions )
46 
47  USE moddatatypes
48  USE modbndpatch, ONLY : t_patch
49  USE moddatastruct, ONLY : t_region
50  USE modglobal, ONLY : t_global
51  USE moderror
52  USE modmpi
53  USE modparameters
54  IMPLICIT NONE
55 
56 ! ... parameters
57  TYPE(t_global), POINTER :: global
58  TYPE(t_region), POINTER :: regions(:)
59 
60 ! ... loop variables
61  INTEGER :: ireg, ipatch
62 
63 ! ... local variables
64  CHARACTER(2*CHRLEN+4) :: fname
65  CHARACTER(CHRLEN) :: msg
66 
67  INTEGER :: regionnum, nlevels, npatches, ipc, jpc, kpc, bctype, align
68  INTEGER :: ncellstot, errorflag
69 
70  TYPE(t_patch), POINTER :: patch
71 
72 !******************************************************************************
73 
74  CALL registerfunction( global,'RFLO_ReadRegionTopology',&
75  'RFLO_ReadRegionTopology.F90' )
76 
77 ! open file & read number of regions
78 
79  fname = trim(global%inDir)//trim(global%casename)//'.top'
80  OPEN(if_topol,file=fname,form='formatted',status='old',iostat=errorflag)
81  global%error = errorflag
82  IF (global%error /= 0) &
83  CALL errorstop( global,err_file_open,&
84  __line__,'File: '//trim(fname) )
85 
86  READ(if_topol,'(1X)',err=10,end=10)
87  READ(if_topol,'(1X)',err=10,end=10)
88  READ(if_topol, * ,err=10,end=10) global%nRegions
89 
90 ! allocate memory for region structure
91 
92  ALLOCATE( regions(global%nRegions),stat=errorflag )
93  global%error = errorflag
94  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
95 
96 ! read topology of each region; store data at grid level 1 (finest grid)
97 
98  ncellstot = 0
99 
100  DO ireg=1,global%nRegions
101  READ(if_topol,*,err=10,end=10) regionnum,nlevels
102  READ(if_topol,*,err=10,end=10) npatches,ipc,jpc,kpc
103 
104  ALLOCATE( regions(regionnum)%levels(nlevels),stat=errorflag )
105  ALLOCATE( regions(regionnum)%levels(1)%patches(npatches),stat=errorflag )
106  global%error = errorflag
107  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
108 
109  regions(regionnum)%iRegionGlobal = regionnum
110  regions(regionnum)%nGridLevels = nlevels
111  regions(regionnum)%nPatches = npatches
112  regions(regionnum)%levels(1)%grid%ipc = ipc
113  regions(regionnum)%levels(1)%grid%jpc = jpc
114  regions(regionnum)%levels(1)%grid%kpc = kpc
115  regions(regionnum)%active = active
116  regions(regionnum)%mixtInput%externalBc = .false.
117 
118  ncellstot = ncellstot + ipc*jpc*kpc
119 
120 ! - set pointer "global" within regions
121 
122  regions(regionnum)%global => global
123 
124 ! - loop over all patches of a region
125 
126  DO ipatch=1,npatches
127  patch => regions(regionnum)%levels(1)%patches(ipatch)
128  READ(if_topol,*,err=10,end=10) &
129  patch%bcType ,patch%lbound , &
130  patch%l1beg ,patch%l1end , &
131  patch%l2beg ,patch%l2end , &
132  patch%srcRegion,patch%srcLbound, &
133  patch%srcL1beg ,patch%srcL1end , &
134  patch%srcL2beg ,patch%srcL2end , &
135  patch%bcCoupled
136 
137  IF (patch%bcCoupled <= 0) THEN
138  patch%bcCoupled = bc_internal
139  patch%bcMotion = bc_internal
140  ELSE
141  patch%bcCoupled = bc_external
142  patch%bcMotion = bc_external
143  ENDIF
144  IF (patch%bcType == bc_slipwall_free .OR. &
145  patch%bcType == bc_slipwall_fixed .OR. &
146  patch%bcType == bc_slipwall_xslide .OR. &
147  patch%bcType == bc_slipwall_yslide .OR. &
148  patch%bcType == bc_slipwall_zslide .OR. &
149  patch%bcType == bc_slipwall_xyslide .OR. &
150  patch%bcType == bc_slipwall_xzslide .OR. &
151  patch%bcType == bc_slipwall_yzslide) THEN
152  patch%bcMotion = bc_external
153  ENDIF
154  IF (patch%bcType == bc_symmetry_free .OR. &
155  patch%bcType == bc_symmetry_fixed .OR. &
156  patch%bcType == bc_symmetry_xslide .OR. &
157  patch%bcType == bc_symmetry_yslide .OR. &
158  patch%bcType == bc_symmetry_zslide .OR. &
159  patch%bcType == bc_symmetry_xyslide .OR. &
160  patch%bcType == bc_symmetry_xzslide .OR. &
161  patch%bcType == bc_symmetry_yzslide) THEN
162  patch%bcMotion = bc_external
163  ENDIF
164  IF (patch%bcType == bc_noslipwall_free .OR. &
165  patch%bcType == bc_noslipwall_fixed .OR. &
166  patch%bcType == bc_noslipwall_xslide .OR. &
167  patch%bcType == bc_noslipwall_yslide .OR. &
168  patch%bcType == bc_noslipwall_zslide .OR. &
169  patch%bcType == bc_noslipwall_xyslide .OR. &
170  patch%bcType == bc_noslipwall_xzslide .OR. &
171  patch%bcType == bc_noslipwall_yzslide) THEN
172  patch%bcMotion = bc_external
173  ENDIF
174  IF (patch%bcType == bc_outflow_free .OR. &
175  patch%bcType == bc_outflow_fixed .OR. &
176  patch%bcType == bc_outflow_xslide .OR. &
177  patch%bcType == bc_outflow_yslide .OR. &
178  patch%bcType == bc_outflow_zslide .OR. &
179  patch%bcType == bc_outflow_xyslide .OR. &
180  patch%bcType == bc_outflow_xzslide .OR. &
181  patch%bcType == bc_outflow_yzslide) THEN
182  patch%bcMotion = bc_external
183  ENDIF
184  IF (patch%bcCoupled == bc_external) &
185  regions(regionnum)%mixtInput%externalBc = .true.
186 
187 ! --- check if BC type within range
188  IF (patch%bcType<bc_code_min .OR. patch%bcType>bc_code_max) THEN
189  WRITE(msg,'(A,I5,A)') 'Boundary code ',patch%bcType," ???"
190  CALL errorstop( global,err_unknown_bc,__line__,msg )
191  ENDIF
192 
193 ! --- check if region face between 1 and 6
194  IF (patch%lbound<1 .OR. patch%lbound>6) &
195  CALL errorstop( global,err_wrong_regionface,__line__ )
196 
197 ! --- initialize patch data
198  patch%mixt%bcSet = .true. ! defaults: BC set
199  patch%mixt%distrib = bcdat_constant ! no distribution
200  patch%mixt%nData = 0 ! no data
201  patch%mixt%nSwitches = 0 ! no switches
202 
203  patch%turb%bcSet = .true. ! defaults: BC set
204  patch%turb%distrib = bcdat_constant ! no distribution
205  patch%turb%nData = 0 ! no data
206  patch%turb%nSwitches = 0 ! no switches
207 
208  patch%spec%bcSet = .true. ! defaults: BC set
209  patch%spec%distrib = bcdat_constant ! no distribution
210  patch%spec%nData = 0 ! no data
211  patch%spec%nSwitches = 0 ! no switches
212 
213  patch%peul%bcSet = .true. ! defaults: BC set
214  patch%peul%distrib = bcdat_constant ! no distribution
215  patch%peul%nData = 0 ! no data
216  patch%peul%nSwitches = 0 ! no switches
217 
218  patch%valRadi%bcSet = .true. ! defaults: BC set
219  patch%valRadi%distrib = bcdat_constant ! no distribution
220  patch%valRadi%nData = 0 ! no data
221  patch%valRadi%nSwitches = 0 ! no switches
222 
223 ! --- unset BCs for certain types (where user input required)
224  bctype = patch%bcType
225 
226  IF ((bctype>=bc_slipwall .AND. bctype<=bc_slipwall +bc_range) .OR. &
227  (bctype>=bc_noslipwall .AND. bctype<=bc_noslipwall+bc_range) .OR. &
228  (bctype>=bc_inflow .AND. bctype<=bc_inflow +bc_range) .OR. &
229  (bctype>=bc_outflow .AND. bctype<=bc_outflow +bc_range) .OR. &
230  (bctype>=bc_farfield .AND. bctype<=bc_farfield +bc_range) .OR. &
231  (bctype>=bc_injection .AND. bctype<=bc_injection +bc_range)) THEN
232  patch%mixt%bcSet = .false. ! will be set to true if BC defined
233  ENDIF
234 
235  IF ((bctype>=bc_inflow .AND. bctype<=bc_inflow +bc_range) .OR. &
236  (bctype>=bc_farfield .AND. bctype<=bc_farfield +bc_range) .OR. &
237  (bctype>=bc_injection .AND. bctype<=bc_injection +bc_range)) THEN
238  patch%peul%bcSet = .false. ! will be set to true if BC defined
239  ENDIF
240 
241  ENDDO ! iPatch
242  ENDDO ! iReg
243 
244  CLOSE(if_topol,iostat=errorflag)
245  global%error = errorflag
246  IF (global%error /= 0) &
247  CALL errorstop( global,err_file_close,__line__,'File: '//trim(fname) )
248 
249 ! find aligned l1,l2 coordinates ----------------------------------------------
250 
251  DO ireg=1,global%nRegions
252  DO ipatch=1,regions(ireg)%nPatches
253 
254  patch => regions(ireg)%levels(1)%patches(ipatch)
255 
256 ! --- patch with a neighbor
257 
258  bctype = patch%bcType
259  IF ((bctype>=bc_regionconf .AND. bctype<=bc_regionconf+bc_range) .OR. &
260  (bctype>=bc_regionint .AND. bctype<=bc_regionint +bc_range) .OR. &
261  (bctype>=bc_regnonconf .AND. bctype<=bc_regnonconf+bc_range) .OR. &
262  (bctype>=bc_tra_peri .AND. bctype<=bc_tra_peri +bc_range) .OR. &
263  (bctype>=bc_rot_peri .AND. bctype<=bc_rot_peri +bc_range)) THEN
264 
265 ! ----- check if source region within possible range
266 
267  IF (patch%srcRegion > global%nRegions) &
268  CALL errorstop( global,err_region_range,__line__ )
269 
270 ! ----- check number of source region face
271 
272  IF (patch%srcLbound<1 .OR. patch%srcLbound>6) &
273  CALL errorstop( global,err_wrong_regionface,__line__,'(source region).' )
274 
275 ! ----- present patch
276  IF (patch%l1beg<0 .OR. patch%l1end<0 ) THEN ! 1st direction
277  align = 10
278  patch%l1beg = abs(patch%l1beg)
279  patch%l1end = abs(patch%l1end)
280  IF (patch%l2beg<0 .OR. patch%l2end<0 ) &
281  CALL errorstop( global,err_patch_2align,__line__ )
282  ELSE IF (patch%l2beg<0 .OR. patch%l2end<0 ) THEN ! 2nd direction
283  align = 20
284  patch%l2beg = abs(patch%l2beg)
285  patch%l2end = abs(patch%l2end)
286  ELSE
287  CALL errorstop( global,err_patch_noalign,__line__ )
288  ENDIF
289 
290 ! ----- source patch
291  IF (patch%srcL1beg<0 .OR. patch%srcL1end<0 ) THEN ! 1st direction
292  align = align + 1
293  patch%srcL1beg = abs(patch%srcL1beg)
294  patch%srcL1end = abs(patch%srcL1end)
295  IF (patch%srcL2beg<0 .OR. patch%srcL2end<0 ) &
296  CALL errorstop( global,err_patch_2align,__line__ )
297  ELSE IF (patch%srcL2beg<0 .OR. patch%srcL2end<0 ) THEN ! 2nd dir.
298  align = align + 2
299  patch%srcL2beg = abs(patch%srcL2beg)
300  patch%srcL2end = abs(patch%srcL2end)
301  ELSE
302  CALL errorstop( global,err_patch_noalign,__line__ )
303  ENDIF
304 
305 ! ----- set alignment flag (1=yes, 0=no)
306  IF (align==11 .OR. align==22) THEN
307  patch%align = .true.
308  ELSE
309  patch%align = .false.
310  ENDIF
311 
312 ! --- no neighbor
313 
314  ELSE
315  patch%srcRegion = -999
316  patch%srcPatch = -999
317  patch%align = .true.
318  patch%srcLbound = -999
319  patch%srcL1beg = -999
320  patch%srcL1end = -999
321  patch%srcL2beg = -999
322  patch%srcL2end = -999
323  ENDIF
324 
325  ENDDO ! iPatch
326  ENDDO ! iReg
327 
328 ! print some info -------------------------------------------------------------
329 
330  IF (global%myProcid==masterproc .AND. global%verbLevel>=verbose_med) THEN
331  WRITE(stdout,'(/,A,I8)') solver_name//' total no. of cells = ',ncellstot
332  WRITE(stdout,'(A,I8,/)') solver_name//' no. of grid regions = ', &
333  global%nRegions
334  ENDIF
335 
336 ! error handling --------------------------------------------------------------
337 
338  CALL deregisterfunction( global )
339  goto 999
340 
341 10 CONTINUE
342  CALL errorstop( global,err_file_read,__line__,'File: '//trim(fname) )
343 
344 999 CONTINUE
345 
346 END SUBROUTINE rflo_readregiontopology
347 
348 !******************************************************************************
349 !
350 ! RCS Revision history:
351 !
352 ! $Log: RFLO_ReadRegionTopology.F90,v $
353 ! Revision 1.12 2009/08/27 14:04:49 mtcampbe
354 ! Updated to enable burning motion with symmetry boundaries and enhanced
355 ! burnout code.
356 !
357 ! Revision 1.11 2008/12/06 08:44:07 mtcampbe
358 ! Updated license.
359 !
360 ! Revision 1.10 2008/11/19 22:17:21 mtcampbe
361 ! Added Illinois Open Source License/Copyright
362 !
363 ! Revision 1.9 2006/08/28 11:42:12 rfiedler
364 ! Add grid motion constraint types for outflow BC.
365 !
366 ! Revision 1.8 2006/08/24 13:15:36 rfiedler
367 ! Rocflo now supports XYSLIDE, XZSLIDE, and YZSLIDE instead of TANGEN constraint.
368 !
369 ! Revision 1.7 2006/08/19 15:38:22 mparmar
370 ! Renamed patch variables
371 !
372 ! Revision 1.6 2006/05/08 22:30:40 wasistho
373 ! added prop-NS capability
374 !
375 ! Revision 1.5 2006/05/04 04:24:28 wasistho
376 ! include BC_SLIPWALL_FIXED in bcMotion externals
377 !
378 ! Revision 1.4 2005/06/20 20:24:25 wasistho
379 ! changed bcType to patch%bcType since bcType wasn't defined yet
380 !
381 ! Revision 1.3 2005/06/19 05:31:16 wasistho
382 ! shift index rocprop slipwalls
383 !
384 ! Revision 1.2 2005/06/13 21:44:44 wasistho
385 ! added new patch variable patch%bcMotion
386 !
387 ! Revision 1.1 2004/11/29 21:25:16 wasistho
388 ! lower to upper case
389 !
390 ! Revision 1.14 2004/07/02 23:01:28 wasistho
391 ! filled iRegionGlobal for Rocflo
392 !
393 ! Revision 1.13 2003/05/15 02:57:01 jblazek
394 ! Inlined index function.
395 !
396 ! Revision 1.12 2003/02/11 22:52:50 jferry
397 ! Initial import of Rocsmoke
398 !
399 ! Revision 1.11 2002/10/12 03:20:50 jblazek
400 ! Replaced [io]stat=global%error with local errorFlag for Rocflo.
401 !
402 ! Revision 1.10 2002/09/27 03:34:04 jblazek
403 ! BH seems to need "" around ??? in line 122.
404 !
405 ! Revision 1.9 2002/09/27 00:57:09 jblazek
406 ! Changed makefiles - no makelinks needed.
407 !
408 ! Revision 1.8 2002/09/20 22:22:35 jblazek
409 ! Finalized integration into GenX.
410 !
411 ! Revision 1.7 2002/09/05 17:40:19 jblazek
412 ! Variable global moved into regions().
413 !
414 ! Revision 1.6 2002/08/15 19:48:05 jblazek
415 ! Implemented grid deformation capability.
416 !
417 ! Revision 1.5 2002/07/16 21:34:37 jblazek
418 ! Prefixed screen output with SOLVER_NAME.
419 !
420 ! Revision 1.4 2002/07/12 21:50:07 jblazek
421 ! Added tool to split single grid into multiple regions.
422 !
423 ! Revision 1.3 2002/03/18 21:56:39 jblazek
424 ! Finished multiblock and MPI.
425 !
426 ! Revision 1.2 2002/02/27 18:38:19 jblazek
427 ! Changed extrapol. to dummy cells at injection boundaries and slip walls.
428 !
429 ! Revision 1.1 2002/02/21 23:25:04 jblazek
430 ! Blocks renamed as regions.
431 !
432 ! Revision 1.6 2002/02/01 00:00:24 jblazek
433 ! Edge and corner cells defined for each level.
434 !
435 ! Revision 1.5 2002/01/11 17:13:30 jblazek
436 ! Added time stamp or iteration number to file names.
437 !
438 ! Revision 1.4 2001/12/22 00:09:36 jblazek
439 ! Added routines to store grid and solution.
440 !
441 ! Revision 1.3 2001/12/19 23:09:20 jblazek
442 ! Added routines to read grid and solution.
443 !
444 ! Revision 1.2 2001/12/08 00:18:41 jblazek
445 ! Added routines to read BC input file.
446 !
447 ! Revision 1.1.1.1 2001/12/03 21:44:05 jblazek
448 ! Import of RocfluidMP
449 !
450 !******************************************************************************
451 
452 
453 
454 
455 
456 
457 
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
int status() const
Obtain the status of the attribute.
Definition: Attribute.h:240
Definition: patch.h:74
**********************************************************************Rocstar Simulation Suite Illinois Rocstar LLC All rights reserved ****Illinois Rocstar LLC IL **www illinoisrocstar com **sales illinoisrocstar com WITHOUT WARRANTY OF ANY **EXPRESS OR INCLUDING BUT NOT LIMITED TO THE WARRANTIES **OF FITNESS FOR A PARTICULAR PURPOSE AND **NONINFRINGEMENT IN NO EVENT SHALL THE CONTRIBUTORS OR **COPYRIGHT HOLDERS BE LIABLE FOR ANY DAMAGES OR OTHER WHETHER IN AN ACTION OF TORT OR **Arising OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE **USE OR OTHER DEALINGS WITH THE SOFTWARE **********************************************************************INTERFACE SUBROUTINE form
subroutine rflo_readregiontopology(global, regions)
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
subroutine deregisterfunction(global)
Definition: ModError.F90:469