Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
RADI_rFLO_ReadSolution.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 radiation solution.
26 !
27 ! Description: the following solution formats are supported:
28 ! - RocfloMP ASCII
29 ! - RocfloMP binary.
30 !
31 ! Input: regions = dimensions of all regions.
32 !
33 ! Output:
34 ! global%currentTime = physical time
35 ! global%resInit = initial residual
36 !
37 ! Notes: solution is read in only for the current grid level;
38 ! solution is also read in for all dummy cells.
39 !
40 !******************************************************************************
41 !
42 ! $Id: RADI_rFLO_ReadSolution.F90,v 1.3 2008/12/06 08:44:38 mtcampbe Exp $
43 !
44 ! Copyright: (c) 2001 by the University of Illinois
45 !
46 !******************************************************************************
47 
48 SUBROUTINE radi_rflo_readsolution( regions ) ! PUBLIC
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
59  IMPLICIT NONE
60 
61 #include "Indexing.h"
62 
63 ! ... parameters
64  TYPE(t_region), POINTER :: regions(:)
65 
66 ! ... loop variables
67  INTEGER :: ireg, i, j, k, n, ifld
68 
69 ! ... local variables
70  CHARACTER(2*CHRLEN+17) :: fname
71  CHARACTER(CHRLEN) :: msg, timestring
72 
73 #ifdef MPI
74  INTEGER :: status(mpi_status_size)
75 #endif
76  INTEGER :: ilev, iregfile, ipc, jpc, kpc, ndumcells, ioff, ijoff, ijk
77  INTEGER :: idcbeg, jdcbeg, kdcbeg, idcend, jdcend, kdcend, ijkbeg, ijkend
78  INTEGER :: ndimc, nrvar, noutsol, nang, nsolcomp, errorflag
79  INTEGER, ALLOCATABLE :: ivar(:,:)
80 
81  REAL(RFREAL), POINTER :: rcv(:,:)
82  REAL(RFREAL), ALLOCATABLE :: rvar(:,:), solfile(:,:), dumfile(:,:)
83 
84  TYPE(t_global), POINTER :: global
85 
86 !******************************************************************************
87 
88  global => regions(1)%global
89 
90  CALL registerfunction( global,'RADI_RFLO_ReadSolution',&
91  'RADI_rFLO_ReadSolution.F90' )
92 
93 ! allocate fixed-size temporary data arrays -----------------------------------
94 
95  nrvar = 2
96 
97  ALLOCATE( ivar(5,1),stat=errorflag )
98  ALLOCATE( rvar(nrvar,1),stat=errorflag )
99  global%error = errorflag
100  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
101 
102 ! copy time to string ---------------------------------------------------------
103 
104  IF (global%flowType == flow_unsteady) THEN
105  WRITE(timestring,'(1PE11.5)') global%timeStamp
106  ELSE
107  WRITE(timestring,'(1PE11.5)') 0._rfreal
108  ENDIF
109 
110 ! open solution file (only master proc.) --------------------------------------
111 
112  IF (global%myProcid == masterproc) THEN
113 
114 ! - unsteady flow
115 
116  IF (global%flowType == flow_unsteady) THEN
117  IF (global%solutFormat == format_ascii) THEN
118  WRITE(fname,'(A,1PE11.5)') trim(global%inDir)//trim(global%casename)//'.radia_', &
119  global%timeStamp
120  OPEN(if_solut,file=fname,form='formatted',status='old',iostat=errorflag)
121  ELSE IF (global%solutFormat == format_binary) THEN
122  WRITE(fname,'(A,1PE11.5)') trim(global%inDir)//trim(global%casename)//'.radib_', &
123  global%timeStamp
124  OPEN(if_solut,file=fname,form='unformatted',status='old',iostat=errorflag)
125  ELSE
126  CALL errorstop( global,err_unknown_format,__line__ )
127  ENDIF
128 
129 ! - steady flow
130 
131  ELSE
132  IF (global%solutFormat == format_ascii) THEN
133  WRITE(fname,'(A,I6.6)') trim(global%inDir)//trim(global%casename)//'.radia_', &
134  global%currentIter
135  OPEN(if_solut,file=fname,form='formatted',status='old',iostat=errorflag)
136  ELSE IF (global%solutFormat == format_binary) THEN
137  WRITE(fname,'(A,I6.6)') trim(global%inDir)//trim(global%casename)//'.radib_', &
138  global%currentIter
139  OPEN(if_solut,file=fname,form='unformatted',status='old',iostat=errorflag)
140  ELSE
141  CALL errorstop( global,err_unknown_format,__line__ )
142  ENDIF
143  ENDIF
144 
145  global%error = errorflag
146  IF (global%error /= 0) &
147  CALL errorstop( global,err_file_open,__line__,'File: '//trim(fname) )
148 
149  ENDIF ! MASTERPROC
150 
151 ! read & broadcast time and initial residual in file --------------------------
152 
153  IF (global%myProcid == masterproc) THEN
154  CALL rflo_readdatafilereal( global,if_solut,global%solutFormat,nrvar,1,rvar )
155  ENDIF
156 
157 #ifdef MPI
158  CALL mpi_bcast( rvar,nrvar,mpi_rfreal,masterproc,global%mpiComm,global%mpierr )
159  IF (global%mpierr /=0 ) CALL errorstop( global,err_mpi_trouble,__line__ )
160 #endif
161 
162  IF (global%flowType==flow_unsteady .AND. global%currentTime>0._rfreal) THEN
163  IF (global%currentTime /= rvar(1,1)) THEN
164  WRITE(msg,1000) rvar(1,1),global%currentTime
165  CALL errorstop( global,err_time_solution,__line__,msg//' File: '//trim(fname) )
166  ENDIF
167  ELSE
168  global%currentTime = rvar(1,1)
169  ENDIF
170  global%resInit = rvar(2,1)
171 
172 ! read solution data ----------------------------------------------------------
173 
174 ! first define some parameters
175 
176  noutsol = 1
177  nang = regions(ireg)%radiInput%nAng
178  nsolcomp = 3+radi_coeff_ncomp+nang
179 
180  DO ireg=1,global%nRegions
181 
182 ! - get dimensions and pointers
183 
184  ilev = regions(ireg)%currLevel
185  CALL rflo_getdimensdummy( regions(ireg),ilev,idcbeg,idcend, &
186  jdcbeg,jdcend,kdcbeg,kdcend )
187  CALL rflo_getcelloffset( regions(ireg),ilev,ioff,ijoff )
188  ijkbeg = indijk(idcbeg,jdcbeg,kdcbeg,ioff,ijoff)
189  ijkend = indijk(idcend,jdcend,kdcend,ioff,ijoff)
190  ndimc = ijkend - ijkbeg + 1
191 
192 ! - read region number and dimensions (only master)
193 
194  IF (global%myProcid == masterproc) THEN
195  CALL rflo_readdatafileint( global,if_solut,global%solutFormat,5,1,ivar )
196  iregfile = ivar(1,1)
197  ipc = ivar(2,1)
198  jpc = ivar(3,1)
199  kpc = ivar(4,1)
200  ndumcells = ivar(5,1)
201 
202  IF (iregfile /= ireg) &
203  CALL errorstop( global,err_region_number,__line__,'File: '//trim(fname) )
204  IF ((ipc /= regions(ireg)%levels(ilev)%grid%ipc) .OR. &
205  (jpc /= regions(ireg)%levels(ilev)%grid%jpc) .OR. &
206  (kpc /= regions(ireg)%levels(ilev)%grid%kpc)) THEN
207  WRITE(msg,1005) ireg,ipc,jpc,kpc
208  CALL errorstop( global,err_grid_dimensions,__line__,msg )
209  ENDIF
210  IF (ndumcells /= regions(ireg)%nDumCells) THEN
211  WRITE(msg,1010) ireg,ndumcells,regions(ireg)%nDumCells
212  CALL errorstop( global,err_grid_dumcells,__line__,msg )
213  ENDIF
214  ENDIF
215 
216 ! - master reads & sends data, others receive them
217 
218  IF (global%myProcid == masterproc) THEN
219 
220  ALLOCATE( solfile(noutsol,ndimc),stat=errorflag )
221  global%error = errorflag
222  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
223 
224  ALLOCATE( dumfile(1,ndimc),stat=errorflag )
225  global%error = errorflag
226  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
227 
228  solfile(:,:) = 0._rfreal
229  IF (regions(ireg)%radiInput%radiModel == radi_model_fldtran) THEN
230  CALL rflo_readdatafilereal( global,if_solut,global%solutFormat, &
231  noutsol,ndimc,solfile )
232  ENDIF
233  DO ifld = 1,nsolcomp
234  CALL rflo_readdatafilereal( global,if_solut,global%solutFormat, &
235  1,ndimc,dumfile )
236  ENDDO
237 
238 #ifdef MPI
239  IF (regions(ireg)%procid /= masterproc) THEN
240  CALL mpi_send( noutsol,1,mpi_integer, &
241  regions(ireg)%procid,ireg, &
242  global%mpiComm,global%mpierr )
243  IF (global%mpierr /=0 ) CALL errorstop( global,err_mpi_trouble,__line__ )
244  CALL mpi_send( solfile,noutsol*ndimc,mpi_rfreal, &
245  regions(ireg)%procid,ireg, &
246  global%mpiComm,global%mpierr )
247  IF (global%mpierr /=0 ) CALL errorstop( global,err_mpi_trouble,__line__ )
248  ENDIF
249 #endif
250 
251  ELSE ! not the master
252 
253  IF (regions(ireg)%procid == global%myProcid) THEN
254 #ifdef MPI
255  CALL mpi_recv( noutsol,1,mpi_integer,masterproc,ireg, &
256  global%mpiComm,status,global%mpierr )
257  IF (global%mpierr /=0 ) CALL errorstop( global,err_mpi_trouble,__line__ )
258 #endif
259  ALLOCATE( solfile(noutsol,ndimc),stat=errorflag )
260  global%error = errorflag
261  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
262 
263 #ifdef MPI
264  CALL mpi_recv( solfile,noutsol*ndimc,mpi_rfreal,masterproc,ireg, &
265  global%mpiComm,status,global%mpierr )
266  IF (global%mpierr /=0 ) CALL errorstop( global,err_mpi_trouble,__line__ )
267 #endif
268  ENDIF
269 
270  ENDIF
271 
272 ! - copy solution into data structure
273 
274  IF (regions(ireg)%procid == global%myProcid) THEN
275  IF (regions(ireg)%radiInput%radiModel == radi_model_fldtran) THEN
276  rcv => regions(ireg)%levels(ilev)%radi%cv
277  n = 0
278  DO k=kdcbeg,kdcend
279  DO j=jdcbeg,jdcend
280  DO i=idcbeg,idcend
281  n = n + 1
282  ijk = indijk(i,j,k,ioff,ijoff)
283  rcv(tv_mixt_muet,ijk) = solfile(2,n)
284  ENDDO
285  ENDDO
286  ENDDO
287  ENDIF ! radiModel
288  ENDIF ! global%myProcid
289 
290  IF (ALLOCATED(solfile)) THEN
291  DEALLOCATE( solfile,stat=errorflag )
292  global%error = errorflag
293  IF (global%error /= 0) CALL errorstop( global,err_deallocate,__line__ )
294  ENDIF
295 
296  ENDDO ! iReg
297 
298 ! finalize --------------------------------------------------------------------
299 
300  IF (global%myProcid == masterproc) THEN
301  CLOSE(if_solut,iostat=errorflag)
302  global%error = errorflag
303  IF (global%error /= 0) &
304  CALL errorstop( global,err_file_close,__line__,'File: '//trim(fname) )
305  ENDIF
306 
307  CALL deregisterfunction( global )
308 
309 1000 FORMAT('Time in file is= ',1pe12.5,' but it should be= ',e12.5,'.')
310 1005 FORMAT('Region ',i5,', ipc= ',i6,', jpc= ',i6,', kpc= ',i6,'.')
311 1010 FORMAT('Region ',i5,', # dummy cells=',i2,' but should be= ',i1)
312 
313 END SUBROUTINE radi_rflo_readsolution
314 
315 !******************************************************************************
316 !
317 ! RCS Revision history:
318 !
319 ! $Log: RADI_rFLO_ReadSolution.F90,v $
320 ! Revision 1.3 2008/12/06 08:44:38 mtcampbe
321 ! Updated license.
322 !
323 ! Revision 1.2 2008/11/19 22:17:50 mtcampbe
324 ! Added Illinois Open Source License/Copyright
325 !
326 ! Revision 1.1 2004/09/30 17:49:10 wasistho
327 ! prepared for full FLD radiation model
328 !
329 !
330 !
331 !******************************************************************************
332 
333 
334 
335 
336 
337 
338 
339 
340 
**********************************************************************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 idcend
j indices k indices k
Definition: Indexing.h:6
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)
subroutine rflo_getdimensdummy(region, iLev, idcbeg, idcend, jdcbeg, jdcend, kdcbeg, kdcend)
**********************************************************************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 kdcbeg
blockLoc i
Definition: read.cpp:79
subroutine rflo_getcelloffset(region, iLev, iCellOffset, ijCellOffset)
**********************************************************************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 idcbeg
**********************************************************************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
**********************************************************************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 jdcend
j indices j
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 jdcbeg
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
subroutine radi_rflo_readsolution(regions)
subroutine deregisterfunction(global)
Definition: ModError.F90:469
subroutine rflo_readdatafilereal(global, fileId, form, nDim1, nDim2, var)