Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
RFLO_ReadGrid.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 x-,y-,z-coordinates of grid nodes.
26 !
27 ! Description: the following grid formats are supported:
28 ! - RocfloMP ASCII
29 ! - RocfloMP binary.
30 !
31 ! Input: regions = dimensions of all regions.
32 !
33 ! Output: region%levels%grid%xyz = grid coordinates
34 ! global%currentTime = physical time
35 !
36 ! Notes: additionaly, physical time is read in, which is stored at
37 ! the beginning of the file (meaningful only in the case of unsteady
38 ! flow and dynamic grids). It is the finest grid, which is read in.
39 !
40 !******************************************************************************
41 !
42 ! $Id: RFLO_ReadGrid.F90,v 1.5 2008/12/06 08:44:07 mtcampbe Exp $
43 !
44 ! Copyright: (c) 2001 by the University of Illinois
45 !
46 !******************************************************************************
47 
48 SUBROUTINE rflo_readgrid( regions )
49 
50  USE moddatatypes
51  USE moddatastruct, ONLY : t_region
52  USE modglobal, ONLY : t_global
55  USE moderror
56  USE modmpi
57  USE modparameters
58  IMPLICIT NONE
59 
60 #include "Indexing.h"
61 
62 ! ... parameters
63  TYPE(t_region), POINTER :: regions(:)
64 
65 ! ... loop variables
66  INTEGER :: ireg, i, j, k, n
67 
68 ! ... local variables
69  CHARACTER(2*CHRLEN+17) :: fname
70  CHARACTER(CHRLEN) :: msg
71 
72 #ifdef MPI
73  INTEGER :: status(mpi_status_size)
74 #endif
75  INTEGER :: iregfile, ipc, jpc, kpc, ndim
76  INTEGER :: ipnbeg, ipnend, jpnbeg, jpnend, kpnbeg, kpnend
77  INTEGER :: inoff, ijnoff, ijkn, errorflag
78  INTEGER, ALLOCATABLE :: ivar(:,:)
79 
80  LOGICAL :: movegrid
81 
82  REAL(RFREAL), POINTER :: xyz(:,:)
83  REAL(RFREAL), ALLOCATABLE :: rvar(:,:), xyzfile(:,:)
84 
85  TYPE(t_global), POINTER :: global
86 
87 !******************************************************************************
88 
89  global => regions(1)%global
90 
91  CALL registerfunction( global,'RFLO_ReadGrid',&
92  'RFLO_ReadGrid.F90' )
93 
94 ! allocate fixed-size temporary data arrays -----------------------------------
95 
96  ALLOCATE( ivar(4,1),stat=errorflag )
97  ALLOCATE( rvar(1,1),stat=errorflag )
98  global%error = errorflag
99  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
100 
101 ! open grid file (only master proc.) ------------------------------------------
102 
103  IF (global%myProcid == masterproc) THEN
104 
105  movegrid = .false.
106  DO ireg=1,global%nRegions
107  IF (regions(ireg)%mixtInput%moveGrid) movegrid = .true.
108  ENDDO
109 
110 ! - unsteady flow
111 
112  IF (global%flowType==flow_unsteady .AND. &
113  movegrid .AND. global%timeStamp>0._rfreal) THEN
114 #ifdef GENX
115  IF (global%gridFormat == format_ascii) THEN
116  WRITE(fname,'(A)') trim(global%inDir)//trim(global%casename)//'.grda'
117  OPEN(if_grid,file=fname,form='formatted',status='old',iostat=errorflag)
118  ELSE IF (global%gridFormat == format_binary) THEN
119  WRITE(fname,'(A)') trim(global%inDir)//trim(global%casename)//'.grdb'
120  OPEN(if_grid,file=fname,form='unformatted',status='old',iostat=errorflag)
121  ELSE
122  CALL errorstop( global,err_unknown_format,__line__ )
123  ENDIF
124 #else
125  IF (global%gridFormat == format_ascii) THEN
126  WRITE(fname,'(A,1PE11.5)') trim(global%inDir)//trim(global%casename)//'.grda_', &
127  global%timeStamp
128  OPEN(if_grid,file=fname,form='formatted',status='old',iostat=errorflag)
129  ELSE IF (global%gridFormat == format_binary) THEN
130  WRITE(fname,'(A,1PE11.5)') trim(global%inDir)//trim(global%casename)//'.grdb_', &
131  global%timeStamp
132  OPEN(if_grid,file=fname,form='unformatted',status='old',iostat=errorflag)
133  ELSE
134  CALL errorstop( global,err_unknown_format,__line__ )
135  ENDIF
136 #endif
137 
138 ! - steady flow
139 
140  ELSE
141  IF (global%gridFormat == format_ascii) THEN
142  WRITE(fname,'(A)') trim(global%inDir)//trim(global%casename)//'.grda'
143  OPEN(if_grid,file=fname,form='formatted',status='old',iostat=errorflag)
144  ELSE IF (global%gridFormat == format_binary) THEN
145  WRITE(fname,'(A)') trim(global%inDir)//trim(global%casename)//'.grdb'
146  OPEN(if_grid,file=fname,form='unformatted',status='old',iostat=errorflag)
147  ELSE
148  CALL errorstop( global,err_unknown_format,__line__ )
149  ENDIF
150  ENDIF
151 
152  global%error = errorflag
153  IF (global%error /= 0) &
154  CALL errorstop( global,err_file_open,__line__,'File: '//trim(fname) )
155 
156  ENDIF ! MASTERPROC
157 
158 ! read & broadcast time in file -----------------------------------------------
159 
160  IF (global%myProcid == masterproc) THEN
161  CALL rflo_readdatafilereal( global,if_grid,global%gridFormat,1,1,rvar )
162 #ifndef GENX
163  global%currentTime = rvar(1,1)
164 #endif
165  ENDIF
166 
167 #ifdef MPI
168  CALL mpi_bcast( global%currentTime,1,mpi_rfreal,masterproc, &
169  global%mpiComm,global%mpierr )
170  IF (global%mpierr /=0 ) CALL errorstop( global,err_mpi_trouble,__line__ )
171 #endif
172 
173 ! read grid data --------------------------------------------------------------
174 
175  DO ireg=1,global%nRegions
176 
177 ! - read region number and dimensions (only master)
178 
179  IF (global%myProcid == masterproc) THEN
180  CALL rflo_readdatafileint( global,if_grid,global%gridFormat,4,1,ivar )
181  iregfile = ivar(1,1)
182  ipc = ivar(2,1)
183  jpc = ivar(3,1)
184  kpc = ivar(4,1)
185 
186  IF (iregfile /= ireg) &
187  CALL errorstop( global,err_region_number,__line__,'File: '//trim(fname) )
188  IF ((ipc /= regions(ireg)%levels(1)%grid%ipc) .OR. &
189  (jpc /= regions(ireg)%levels(1)%grid%jpc) .OR. &
190  (kpc /= regions(ireg)%levels(1)%grid%kpc)) THEN
191  WRITE(msg,1000) ireg,ipc,jpc,kpc
192  CALL errorstop( global,err_grid_dimensions,__line__,msg )
193  ENDIF
194  ENDIF
195 
196 ! - master reads & sends data, others receive them
197 
198  IF (global%myProcid == masterproc) THEN
199 
200  ndim = (ipc+1)*(jpc+1)*(kpc+1)
201  ALLOCATE( xyzfile(3,ndim),stat=errorflag )
202  global%error = errorflag
203  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
204 
205  CALL rflo_readdatafilereal( global,if_grid,global%gridFormat,3,ndim, &
206  xyzfile )
207 #ifdef MPI
208  IF (regions(ireg)%procid /= masterproc) THEN
209  CALL mpi_send( xyzfile,3*ndim,mpi_rfreal,regions(ireg)%procid,ireg, &
210  global%mpiComm,global%mpierr )
211  IF (global%mpierr /=0 ) CALL errorstop( global,err_mpi_trouble,__line__ )
212  ENDIF
213 #endif
214 
215  ELSE ! not the master
216 
217  IF (regions(ireg)%procid == global%myProcid) THEN
218  ndim = (regions(ireg)%levels(1)%grid%ipc+1)* &
219  (regions(ireg)%levels(1)%grid%jpc+1)* &
220  (regions(ireg)%levels(1)%grid%kpc+1)
221  ALLOCATE( xyzfile(3,ndim),stat=errorflag )
222  global%error = errorflag
223  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
224 #ifdef MPI
225  CALL mpi_recv( xyzfile,3*ndim,mpi_rfreal,masterproc,ireg, &
226  global%mpiComm,status,global%mpierr )
227  IF (global%mpierr /=0 ) CALL errorstop( global,err_mpi_trouble,__line__ )
228 #endif
229  ENDIF
230 
231  ENDIF
232 
233 ! - copy grid into data structure
234 
235  IF (regions(ireg)%procid == global%myProcid) THEN
236  CALL rflo_getdimensphysnodes( regions(ireg),1,ipnbeg,ipnend, &
237  jpnbeg,jpnend,kpnbeg,kpnend )
238  CALL rflo_getnodeoffset( regions(ireg),1,inoff,ijnoff )
239  xyz => regions(ireg)%levels(1)%grid%xyz
240 
241  n = 0
242  DO k=kpnbeg,kpnend
243  DO j=jpnbeg,jpnend
244  DO i=ipnbeg,ipnend
245  n = n + 1
246  ijkn = indijk(i,j,k,inoff,ijnoff)
247  xyz(xcoord,ijkn) = xyzfile(1,n)
248  xyz(ycoord,ijkn) = xyzfile(2,n)
249  xyz(zcoord,ijkn) = xyzfile(3,n)
250  ENDDO
251  ENDDO
252  ENDDO
253  ENDIF
254 
255  IF (ALLOCATED(xyzfile)) THEN
256  DEALLOCATE( xyzfile,stat=errorflag )
257  global%error = errorflag
258  IF (global%error /= 0) CALL errorstop( global,err_deallocate,__line__ )
259  ENDIF
260 
261  ENDDO ! iReg
262 
263 ! finalize --------------------------------------------------------------------
264 
265  IF (global%myProcid == masterproc) THEN
266  CLOSE(if_grid,iostat=errorflag)
267  global%error = errorflag
268  IF (global%error /= 0) &
269  CALL errorstop( global,err_file_close,__line__,'File: '//trim(fname) )
270  ENDIF
271 
272  CALL deregisterfunction( global )
273 
274 1000 FORMAT('Region ',i5,', ipc= ',i6,', jpc= ',i6,', kpc= ',i6,'.')
275 
276 END SUBROUTINE rflo_readgrid
277 
278 !******************************************************************************
279 !
280 ! RCS Revision history:
281 !
282 ! $Log: RFLO_ReadGrid.F90,v $
283 ! Revision 1.5 2008/12/06 08:44:07 mtcampbe
284 ! Updated license.
285 !
286 ! Revision 1.4 2008/11/19 22:17:21 mtcampbe
287 ! Added Illinois Open Source License/Copyright
288 !
289 ! Revision 1.3 2005/06/28 21:19:24 wasistho
290 ! if GENX don't read currenttime
291 !
292 ! Revision 1.2 2005/05/27 08:04:58 wasistho
293 ! allow genx read initial grid
294 !
295 ! Revision 1.1 2004/11/29 21:25:16 wasistho
296 ! lower to upper case
297 !
298 ! Revision 1.17 2003/11/20 16:40:34 mdbrandy
299 ! Backing out RocfluidMP changes from 11-17-03
300 !
301 ! Revision 1.14 2003/05/15 02:57:01 jblazek
302 ! Inlined index function.
303 !
304 ! Revision 1.13 2002/10/23 18:43:24 jblazek
305 ! Changed temporary pointer arrays into allocatable arrays
306 ! in grid and solution I/O routines.
307 !
308 ! Revision 1.12 2002/10/12 03:20:50 jblazek
309 ! Replaced [io]stat=global%error with local errorFlag for Rocflo.
310 !
311 ! Revision 1.11 2002/09/20 22:22:35 jblazek
312 ! Finalized integration into GenX.
313 !
314 ! Revision 1.10 2002/09/05 17:40:19 jblazek
315 ! Variable global moved into regions().
316 !
317 ! Revision 1.9 2002/08/29 21:52:21 jblazek
318 ! Added I/O of grid speeds.
319 !
320 ! Revision 1.8 2002/06/07 16:40:36 jblazek
321 ! Grid & solution for all regions in one file.
322 !
323 ! Revision 1.7 2002/03/18 21:56:39 jblazek
324 ! Finished multiblock and MPI.
325 !
326 ! Revision 1.6 2002/02/21 23:25:04 jblazek
327 ! Blocks renamed as regions.
328 !
329 ! Revision 1.5 2002/01/08 22:09:16 jblazek
330 ! Added calculation of face vectors and volumes.
331 !
332 ! Revision 1.4 2001/12/22 00:09:37 jblazek
333 ! Added routines to store grid and solution.
334 !
335 ! Revision 1.3 2001/12/19 23:09:20 jblazek
336 ! Added routines to read grid and solution.
337 !
338 ! Revision 1.2 2001/12/08 00:18:41 jblazek
339 ! Added routines to read BC input file.
340 !
341 ! Revision 1.1.1.1 2001/12/03 21:44:05 jblazek
342 ! Import of RocfluidMP
343 !
344 !******************************************************************************
345 
346 
347 
348 
349 
350 
351 
**********************************************************************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 jpnbeg
j indices k indices k
Definition: Indexing.h:6
**********************************************************************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 kpnbeg
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
int status() const
Obtain the status of the attribute.
Definition: Attribute.h:240
subroutine rflo_readdatafileint(global, fileId, form, nDim1, nDim2, ivar)
**********************************************************************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 jpnend
subroutine rflo_getnodeoffset(region, iLev, iNodeOffset, ijNodeOffset)
blockLoc i
Definition: read.cpp:79
**********************************************************************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 ipnbeg
**********************************************************************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
const NT & n
subroutine rflo_getdimensphysnodes(region, iLev, ipnbeg, ipnend, jpnbeg, jpnend, kpnbeg, kpnend)
j indices j
Definition: Indexing.h:6
subroutine rflo_readgrid(regions)
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
subroutine deregisterfunction(global)
Definition: ModError.F90:469
**********************************************************************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 ipnend
subroutine rflo_readdatafilereal(global, fileId, form, nDim1, nDim2, var)