Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
RFLO_WriteStat.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: write time averaged solution to file for mixture
26 !
27 ! Description: the following solution formats are supported:
28 ! - RocfloMP ASCII
29 ! - RocfloMP binary
30 !
31 ! Input: regions = dimensions and cons. variables of all regions
32 ! global%currentTime = physical time
33 ! global%integrTime = integrated time during time averaging process
34 ! mixtNStat, mixtStatId= number of mixture statistics variables and IDs
35 ! mixttav = time averaged mixture variables
36 ! turbNStat, turbStatId= number of TURB statistics variables and IDs
37 ! turbtav = time averaged TURB variables
38 !
39 ! Output: to file
40 !
41 ! Notes: solution is stored only for the current grid level; it is also
42 ! stored for all dummy cells; all regions are written into one file
43 !
44 !******************************************************************************
45 !
46 ! $Id: RFLO_WriteStat.F90,v 1.3 2008/12/06 08:44:07 mtcampbe Exp $
47 !
48 ! Copyright: (c) 2001 by the University of Illinois
49 !
50 !******************************************************************************
51 
52 SUBROUTINE rflo_writestat( regions )
53 
54  USE moddatatypes
55  USE moddatastruct, ONLY : t_region
56  USE modglobal, ONLY : t_global
59  USE moderror
60  USE modmpi
61  USE modparameters
62  IMPLICIT NONE
63 
64 #include "Indexing.h"
65 
66 ! ... parameters
67  TYPE(t_region), POINTER :: regions(:)
68 
69 ! ... loop variables
70  INTEGER :: ireg, i, j, k, l, n
71 
72 ! ... local variables
73  CHARACTER(2*CHRLEN+17) :: fname
74 
75 #ifdef MPI
76  INTEGER :: status(mpi_status_size)
77 #endif
78  INTEGER :: ilev, iregfile, ipc, jpc, kpc, ndumcells, ndim, ioff, ijoff, ijk
79  INTEGER :: idcbeg, jdcbeg, kdcbeg, idcend, jdcend, kdcend, ijkbeg, ijkend
80  INTEGER :: maxnstat, allnstat, errorflag
81  INTEGER :: mixtstatid(regions(1)%global%mixtnstat)
82  INTEGER :: turbstatid(regions(1)%global%turbnstat)
83  INTEGER, ALLOCATABLE :: ivar(:,:), jvar(:,:)
84 
85  REAL(RFREAL), POINTER :: mixttav(:,:), turbtav(:,:)
86  REAL(RFREAL), ALLOCATABLE :: rvar(:,:), tavfile(:,:)
87  LOGICAL :: zeroturb
88 
89  TYPE(t_global), POINTER :: global
90 
91 !******************************************************************************
92 
93  global => regions(1)%global
94 
95  CALL registerfunction( global,'RFLO_WriteStat',&
96  'RFLO_WriteStat.F90' )
97 
98 ! allocate temporary data arrays ---------------------------------------------
99 
100  ALLOCATE( ivar(5,1),stat=errorflag )
101  ALLOCATE( rvar(2,1),stat=errorflag )
102  maxnstat = max( global%mixtNStat,global%turbNStat )
103  ALLOCATE( jvar(maxnstat+1,1),stat=errorflag )
104  global%error = errorflag
105  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
106 
107 ! open statistics file (only master proc.) -----------------------------------
108 
109  IF (global%myProcid == masterproc) THEN
110 
111  IF (global%solutFormat == format_ascii) THEN
112  WRITE(fname,'(A,1PE11.5)') trim(global%outDir)//trim(global%casename)//'.stata_', &
113  global%currentTime
114  OPEN(if_stat,file=fname,form='formatted',status='unknown', &
115  iostat=errorflag)
116  ELSE IF (global%solutFormat == format_binary) THEN
117  WRITE(fname,'(A,1PE11.5)') trim(global%outDir)//trim(global%casename)//'.statb_', &
118  global%currentTime
119  OPEN(if_stat,file=fname,form='unformatted',status='unknown', &
120  iostat=errorflag)
121  ELSE
122  CALL errorstop( global,err_unknown_format,__line__ )
123  ENDIF
124  rvar(1,1) = global%currentTime
125  rvar(2,1) = global%integrTime
126 
127  global%error = errorflag
128  IF (global%error /= 0) &
129  CALL errorstop( global,err_file_open,__line__,'File: '//trim(fname) )
130 
131 ! write current and integrated time to file ----------------------------------
132 
133  CALL rflo_writedatafilereal( global,if_stat,global%solutFormat,2,1,rvar )
134 
135 ! mixture statistics NSTATS and ID
136 
137  IF (global%mixtNStat > 0) THEN
138  jvar(1,1) = global%mixtNStat
139  mixtstatid(:)= global%mixtStatId(1,:)*10 + global%mixtStatId(2,:)
140  jvar(2:global%mixtNStat+1,1) = mixtstatid(1:global%mixtNStat)
141  CALL rflo_writedatafileint( global,if_stat,global%solutFormat, &
142  global%mixtNStat+1,1,jvar )
143  ENDIF
144 
145 ! turbulence statistics NSTATS and ID
146 
147 #ifdef TURB
148  IF (global%turbNStat > 0) THEN
149  jvar(1,1) = global%turbNStat
150  turbstatid(:)= global%turbStatId(1,:)*10 + global%turbStatId(2,:)
151  jvar(2:global%turbNStat+1,1) = turbstatid(1:global%turbNStat)
152  CALL rflo_writedatafileint( global,if_stat,global%solutFormat, &
153  global%turbNStat+1,1,jvar )
154  ENDIF
155 #endif
156  ENDIF
157 
158 ! write statistics data ------------------------------------------------------
159 
160  allnstat = global%mixtNStat+global%turbNStat
161 
162  DO ireg=1,global%nRegions
163 
164 ! - get dimensions and pointers
165 
166  ilev = regions(ireg)%currLevel
167  CALL rflo_getdimensdummy( regions(ireg),ilev,idcbeg,idcend, &
168  jdcbeg,jdcend,kdcbeg,kdcend )
169  CALL rflo_getcelloffset( regions(ireg),ilev,ioff,ijoff )
170  ijkbeg = indijk(idcbeg,jdcbeg,kdcbeg,ioff,ijoff)
171  ijkend = indijk(idcend,jdcend,kdcend,ioff,ijoff)
172  ndim = ijkend - ijkbeg + 1
173 
174 ! - allocate memory for data field
175 
176  IF (regions(ireg)%procid==global%myProcid .OR. &
177  global%myProcid==masterproc) THEN
178  ALLOCATE( tavfile(allnstat,ndim),stat=errorflag )
179  global%error = errorflag
180  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
181  ENDIF
182 
183 ! - copy statistics into data structure
184 
185  zeroturb = .false.
186 
187  IF (regions(ireg)%procid == global%myProcid) THEN
188  IF (global%mixtNStat > 0) mixttav => regions(ireg)%levels(ilev)%mixt%tav
189 #ifdef TURB
190  IF (global%turbNStat > 0) THEN
191  IF ((regions(ireg)%mixtInput%flowModel == flow_navst) .AND. &
192  (regions(ireg)%mixtInput%turbModel /= turb_model_none)) THEN
193  turbtav => regions(ireg)%levels(ilev)%turb%tav
194  ELSE
195  ALLOCATE( turbtav(global%turbNStat,ndim) )
196  turbtav = 0._rfreal
197  zeroturb = .true.
198  ENDIF
199  ENDIF
200 #endif
201  n = 0
202  DO k=kdcbeg,kdcend
203  DO j=jdcbeg,jdcend
204  DO i=idcbeg,idcend
205  n = n + 1
206  ijk = indijk(i,j,k,ioff,ijoff)
207  DO l=1,global%mixtNStat
208  tavfile(l,n) = mixttav(l,ijk)
209  ENDDO
210 #ifdef TURB
211  DO l=1,global%turbNStat
212  tavfile(global%mixtNStat+l,n) = turbtav(l,ijk)
213  ENDDO
214 #endif
215  ENDDO
216  ENDDO
217  ENDDO
218  ENDIF
219 
220  IF (zeroturb) DEALLOCATE( turbtav )
221 
222 ! - write region number and dimensions (only master)
223 
224  IF (global%myProcid == masterproc) THEN
225  ivar(1,1) = ireg
226  ivar(2,1) = regions(ireg)%levels(ilev)%grid%ipc
227  ivar(3,1) = regions(ireg)%levels(ilev)%grid%jpc
228  ivar(4,1) = regions(ireg)%levels(ilev)%grid%kpc
229  ivar(5,1) = regions(ireg)%nDumCells
230  CALL rflo_writedatafileint( global,if_stat,global%solutFormat,5,1,ivar )
231  ENDIF
232 
233 ! - master receives and writes data, others send them
234 
235  IF (global%myProcid == masterproc) THEN
236 #ifdef MPI
237  IF (regions(ireg)%procid /= masterproc) THEN
238  CALL mpi_recv( tavfile,allnstat*ndim,mpi_rfreal, &
239  regions(ireg)%procid,ireg, &
240  global%mpiComm,status,global%mpierr )
241  IF (global%mpierr /=0 ) CALL errorstop( global,err_mpi_trouble,__line__ )
242  ENDIF
243 #endif
244  CALL rflo_writedatafilereal( global,if_stat,global%solutFormat, &
245  allnstat,ndim,tavfile )
246 
247  ELSE ! not the master
248 #ifdef MPI
249  IF (regions(ireg)%procid == global%myProcid) THEN
250  CALL mpi_send( tavfile,allnstat*ndim,mpi_rfreal,masterproc, &
251  ireg,global%mpiComm,global%mpierr )
252  IF (global%mpierr /=0 ) CALL errorstop( global,err_mpi_trouble,__line__ )
253  ENDIF
254 #endif
255  ENDIF ! global%myProcid
256 
257  IF (ALLOCATED(tavfile)) THEN
258  DEALLOCATE( tavfile,stat=errorflag )
259  global%error = errorflag
260  IF (global%error /= 0) CALL errorstop( global,err_deallocate,__line__ )
261  ENDIF
262 
263  ENDDO ! iReg
264 
265 ! finalize -----------------------------------------------------------------
266 
267  IF (global%myProcid == masterproc) THEN
268  CLOSE(if_stat,iostat=errorflag)
269  global%error = errorflag
270  IF (global%error /= 0) &
271  CALL errorstop( global,err_file_close,__line__,'File: '//trim(fname) )
272  ENDIF
273 
274  CALL deregisterfunction( global )
275 
276 END SUBROUTINE rflo_writestat
277 
278 !******************************************************************************
279 !
280 ! RCS Revision history:
281 !
282 ! $Log: RFLO_WriteStat.F90,v $
283 ! Revision 1.3 2008/12/06 08:44:07 mtcampbe
284 ! Updated license.
285 !
286 ! Revision 1.2 2008/11/19 22:17:21 mtcampbe
287 ! Added Illinois Open Source License/Copyright
288 !
289 ! Revision 1.1 2004/11/29 21:25:17 wasistho
290 ! lower to upper case
291 !
292 ! Revision 1.13 2003/11/20 16:40:35 mdbrandy
293 ! Backing out RocfluidMP changes from 11-17-03
294 !
295 ! Revision 1.10 2003/05/15 02:57:01 jblazek
296 ! Inlined index function.
297 !
298 ! Revision 1.9 2002/12/12 03:39:37 wasistho
299 ! facilitate the possibility of NO TURB statistics
300 !
301 ! Revision 1.8 2002/11/04 18:42:08 wasistho
302 ! Modified statistics restart
303 !
304 ! Revision 1.7 2002/11/02 01:47:48 wasistho
305 ! Added TURB statistics
306 !
307 ! Revision 1.6 2002/10/23 18:43:24 jblazek
308 ! Changed temporary pointer arrays into allocatable arrays
309 ! in grid and solution I/O routines.
310 !
311 ! Revision 1.5 2002/10/12 03:20:50 jblazek
312 ! Replaced [io]stat=global%error with local errorFlag for Rocflo.
313 !
314 ! Revision 1.4 2002/09/20 22:22:35 jblazek
315 ! Finalized integration into GenX.
316 !
317 ! Revision 1.3 2002/09/05 17:40:19 jblazek
318 ! Variable global moved into regions().
319 !
320 ! Revision 1.2 2002/07/22 15:44:24 wasistho
321 ! Cleaned-up conforming Coding Rule
322 !
323 ! Revision 1.1 2002/06/14 20:53:05 wasistho
324 ! add time avg statistics
325 !
326 !******************************************************************************
327 
328 
329 
330 
331 
332 
333 
**********************************************************************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
subroutine rflo_writedatafileint(global, fileId, form, nDim1, nDim2, ivar)
j indices k indices k
Definition: Indexing.h:6
Vector_n max(const Array_n_const &v1, const Array_n_const &v2)
Definition: Vector_n.h:354
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
int status() const
Obtain the status of the attribute.
Definition: Attribute.h:240
subroutine rflo_writestat(regions)
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 rflo_writedatafilereal(global, fileId, form, nDim1, nDim2, var)
subroutine deregisterfunction(global)
Definition: ModError.F90:469