Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
WriteProbe.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 data of a probe into a file.
26 !
27 ! Description: none.
28 !
29 ! Input: regions%levels%mixt = flow variables
30 ! iReg = current region number
31 ! global%probePos = list of probes
32 !
33 ! Output: into file.
34 !
35 ! Notes: none.
36 !
37 !******************************************************************************
38 !
39 ! $Id: WriteProbe.F90,v 1.5 2009/01/06 21:29:46 mdbrandy Exp $
40 !
41 ! Copyright: (c) 2001 by the University of Illinois
42 !
43 !******************************************************************************
44 
45 SUBROUTINE writeprobe( regions,iReg )
46 
47  USE moddatatypes
48  USE moddatastruct, ONLY : t_region
49  USE modglobal, ONLY : t_global
50  USE moderror
51  USE modparameters
52 #ifdef RFLO
54 
55 #include "Indexing.h"
56 #endif
57  IMPLICIT NONE
58 
59 ! ... parameters
60  TYPE(t_region), POINTER :: regions(:)
61 
62  INTEGER :: ireg
63 
64 ! ... loop variables
65  INTEGER :: iprobe
66 
67 ! ... local variables
68  CHARACTER(CHRLEN+9) :: fname
69 
70  INTEGER :: errorflag,ipcbeg, ipcend, jpcbeg, jpcend, kpcbeg, kpcend
71  INTEGER :: ilev, icoff, ijcoff, icell, npeul, i, j, k
72 
73  LOGICAL :: wrtprobe
74 
75  REAL(RFREAL) :: rho, u, v, w, press, temp
76  REAL(RFREAL), POINTER :: cv(:,:), dv(:,:), peulcv(:,:)
77 
78  TYPE(t_global), POINTER :: global
79 
80 !******************************************************************************
81 
82  global => regions(ireg)%global
83 
84  CALL registerfunction( global,'WriteProbe',&
85  'WriteProbe.F90' )
86 
87 ! determine number of smoke/species types that exist (if any)
88 
89  npeul = 0
90 
91 #ifdef RFLO
92 #ifdef PEUL
93  IF (global%peulUsed) npeul = regions(ireg)%peulInput%nPtypes
94 #endif
95 #endif
96 
97 #ifdef RFLU
98 #ifdef SPEC
99  IF (global%specUsed) npeul = regions(ireg)%specInput%nSpecies
100 #endif
101 #endif
102 
103 ! loop over all specified probes ----------------------------------------------
104 
105  DO iprobe=1,global%nProbes
106 
107  wrtprobe = .false.
108 
109 #ifdef RFLO
110 ! - check if region number within range
111 
112  IF (global%probePos(iprobe,1)<1 .OR. &
113  global%probePos(iprobe,1)>global%nRegions) &
114  CALL errorstop( global,err_probe_location,__line__ )
115 
116 ! - prepare data
117 
118  IF (regions(global%probePos(iprobe,1))%procid==global%myProcid .AND. &
119  regions(global%probePos(iprobe,1))%active==active .AND. &
120  ireg==global%probePos(iprobe,1)) THEN
121 
122 ! --- get dimensions
123 
124  ilev = regions(ireg)%currLevel
125 
126  CALL rflo_getdimensphys( regions(ireg),ilev,ipcbeg,ipcend, &
127  jpcbeg,jpcend,kpcbeg,kpcend )
128  CALL rflo_getcelloffset( regions(ireg),ilev,icoff,ijcoff )
129 
130 ! --- check if probe within index range; get cell pointer
131 
132  IF ((global%probePos(iprobe,2)<ipcbeg .OR. &
133  global%probePos(iprobe,2)>ipcend) .OR. &
134  (global%probePos(iprobe,3)<jpcbeg .OR. &
135  global%probePos(iprobe,3)>jpcend) .OR. &
136  (global%probePos(iprobe,4)<kpcbeg .OR. &
137  global%probePos(iprobe,4)>kpcend)) &
138  CALL errorstop( global,err_probe_location,__line__ )
139 
140  i = global%probePos(iprobe,2)
141  j = global%probePos(iprobe,3)
142  k = global%probePos(iprobe,4)
143  icell = indijk(i,j,k,icoff,ijcoff)
144 
145  cv => regions(ireg)%levels(ilev)%mixt%cv
146  dv => regions(ireg)%levels(ilev)%mixt%dv
147 #ifdef PEUL
148  IF (npeul > 0) peulcv => regions(ireg)%levels(ilev)%peul%cv
149 #endif
150  wrtprobe = .true.
151  ENDIF
152 #endif
153 #ifdef RFLU
154  IF ( global%probePos(iprobe,probe_region) == &
155  regions(ireg)%iRegionGlobal ) THEN
156 
157  icell = global%probePos(iprobe,probe_cell)
158 
159  cv => regions(ireg)%mixt%cv
160  dv => regions(ireg)%mixt%dv
161  IF (npeul > 0) peulcv => regions(ireg)%spec%cv
162 
163  wrtprobe = .true.
164  END IF ! global%probePos
165 #endif
166 
167 ! - write probe data to file
168 
169  IF (wrtprobe) THEN
170  rho = cv(cv_mixt_dens,icell)
171  u = cv(cv_mixt_xmom,icell)/rho
172  v = cv(cv_mixt_ymom,icell)/rho
173  w = cv(cv_mixt_zmom,icell)/rho
174  press = dv(dv_mixt_pres,icell)
175  temp = dv(dv_mixt_temp,icell)
176 
177  IF (npeul == 0) THEN
178  IF (global%flowType == flow_steady) THEN
179  WRITE(if_probe+iprobe-1,1000,iostat=errorflag) global%currentIter, &
180  rho,u,v,w,press,temp
181  ELSE
182  WRITE(if_probe+iprobe-1,1005,iostat=errorflag) global%currentTime, &
183  rho,u,v,w,press,temp
184  ENDIF
185  ELSE
186 #ifdef RFLO
187 #ifdef PEUL
188  IF (global%flowType == flow_steady) THEN
189  WRITE(if_probe+iprobe-1,1000,iostat=errorflag) global%currentIter, &
190  rho,u,v,w,press,temp,&
191  peulcv(1:npeul,icell)
192  ELSE
193  WRITE(if_probe+iprobe-1,1005,iostat=errorflag) global%currentTime, &
194  rho,u,v,w,press,temp,&
195  peulcv(1:npeul,icell)
196  ENDIF
197 #endif
198 #endif
199 #ifdef RFLU
200  IF (global%flowType == flow_steady) THEN
201  WRITE(if_probe+iprobe-1,1000,iostat=errorflag) global%currentIter, &
202  rho,u,v,w,press,temp,&
203  peulcv(1:npeul,icell)
204  ELSE
205  WRITE(if_probe+iprobe-1,1005,iostat=errorflag) global%currentTime, &
206  rho,u,v,w,press,temp,&
207  peulcv(1:npeul,icell)
208  ENDIF
209 #endif
210  ENDIF
211 
212  global%error = errorflag
213  IF (global%error /= 0) THEN
214  CALL errorstop( global,err_file_write,__line__,'Probe file' )
215  ENDIF
216 
217 ! --- close and open probe file (instead of fflush)
218 
219  IF (global%probeOpenClose) THEN
220  WRITE(fname,'(A,I4.4)') &
221  trim(global%outDir)//trim(global%casename)//'.prb_',iprobe
222  CLOSE(if_probe+iprobe-1)
223  OPEN(if_probe+iprobe-1,file=fname,form='FORMATTED',status='OLD', &
224  position='APPEND')
225  ENDIF
226  ENDIF ! wrtProbe
227 
228  ENDDO ! iprobe
229 
230 ! finalize --------------------------------------------------------------------
231 
232  CALL deregisterfunction( global )
233 
234 !Modified by Mark Brandyberry to have more Decimal Places for Acoustics
235 1000 FORMAT(i6,1p,99e24.15)
236 1005 FORMAT(1pe14.7,99e24.15)
237 
238 END SUBROUTINE writeprobe
239 
240 !******************************************************************************
241 !
242 ! RCS Revision history:
243 !
244 ! $Log: WriteProbe.F90,v $
245 ! Revision 1.5 2009/01/06 21:29:46 mdbrandy
246 ! Added More Decm
247 !
248 ! Revision 1.4 2008/12/06 08:44:10 mtcampbe
249 ! Updated license.
250 !
251 ! Revision 1.3 2008/11/19 22:17:24 mtcampbe
252 ! Added Illinois Open Source License/Copyright
253 !
254 ! Revision 1.2 2006/02/13 21:01:05 wasistho
255 ! added ifdef PEUL
256 !
257 ! Revision 1.1 2004/12/01 16:52:25 haselbac
258 ! Initial revision after changing case
259 !
260 ! Revision 1.21 2004/07/28 15:29:18 jferry
261 ! created global variable for spec use
262 !
263 ! Revision 1.20 2004/07/23 22:43:15 jferry
264 ! Integrated rocspecies into rocinteract
265 !
266 ! Revision 1.19 2004/03/05 22:09:00 jferry
267 ! created global variables for peul, plag, and inrt use
268 !
269 ! Revision 1.18 2003/11/20 16:40:36 mdbrandy
270 ! Backing out RocfluidMP changes from 11-17-03
271 !
272 ! Revision 1.15 2003/05/15 16:40:57 jblazek
273 ! Changed index function call to fit into single line.
274 !
275 ! Revision 1.14 2003/05/15 02:57:02 jblazek
276 ! Inlined index function.
277 !
278 ! Revision 1.13 2003/04/07 18:25:09 jferry
279 ! added smoke concentrations to output
280 !
281 ! Revision 1.12 2003/04/07 14:19:33 haselbac
282 ! Removed ifdefs - now also used for RFLU
283 !
284 ! Revision 1.11 2003/01/23 17:48:53 jblazek
285 ! Changed algorithm to dump convergence, solution and probe data.
286 !
287 ! Revision 1.10 2003/01/10 17:58:43 jblazek
288 ! Added missing explicit interfaces.
289 !
290 ! Revision 1.9 2002/10/07 19:24:28 haselbac
291 ! Change use of IOSTAT, cures problem on SGIs
292 !
293 ! Revision 1.8 2002/10/05 18:42:09 haselbac
294 ! Added RFLU functionality
295 !
296 ! Revision 1.7 2002/09/05 17:40:20 jblazek
297 ! Variable global moved into regions().
298 !
299 ! Revision 1.6 2002/02/21 23:25:05 jblazek
300 ! Blocks renamed as regions.
301 !
302 ! Revision 1.5 2002/02/16 07:16:00 jblazek
303 ! Added implicit residual smoothing.
304 !
305 ! Revision 1.4 2002/02/09 01:47:01 jblazek
306 ! Added multi-probe option, residual smoothing, physical time step.
307 !
308 ! Revision 1.3 2002/02/01 00:00:24 jblazek
309 ! Edge and corner cells defined for each level.
310 !
311 ! Revision 1.2 2002/01/31 20:56:30 jblazek
312 ! Added basic boundary conditions.
313 !
314 ! Revision 1.1 2002/01/31 00:39:23 jblazek
315 ! Probe output moved to common library.
316 !
317 !******************************************************************************
318 
319 
320 
321 
322 
323 
324 
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 kpcbeg
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
int status() const
Obtain the status of the attribute.
Definition: Attribute.h:240
**********************************************************************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 jpcbeg
**********************************************************************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 ipcend
*********************************************************************Illinois Open Source License ****University of Illinois NCSA **Open Source License University of Illinois All rights reserved ****Developed free of to any person **obtaining a copy of this software and associated documentation to deal with the Software without including without limitation the rights to and or **sell copies of the and to permit persons to whom the **Software is furnished to do subject to the following this list of conditions and the following disclaimers ****Redistributions in binary form must reproduce the above **copyright this list of conditions and the following **disclaimers in the documentation and or other materials **provided with the distribution ****Neither the names of the Center for Simulation of Advanced the University of nor the names of its **contributors may be used to endorse or promote products derived **from this Software without specific prior written permission ****THE SOFTWARE IS PROVIDED AS 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 v
Definition: roccomf90.h:20
subroutine writeprobe(regions, iReg)
Definition: WriteProbe.F90:45
**********************************************************************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 ipcbeg
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 form
**********************************************************************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 icell
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 jpcend
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
subroutine deregisterfunction(global)
Definition: ModError.F90:469
subroutine rflo_getdimensphys(region, iLev, ipcbeg, ipcend, jpcbeg, jpcend, kpcbeg, kpcend)