Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
WriteTecplotAscii.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 grid (and solution) data to plot file in ASCII format.
26 !
27 ! Description: none.
28 !
29 ! Input: iReg = region number
30 ! iLev = grid level
31 ! plotType = 1 - grid + smoke only, = 2 - grid + all fields
32 ! region = region data (dimensions, flow variables)
33 !
34 ! Output: to plot file.
35 !
36 ! Notes: none.
37 !
38 !******************************************************************************
39 !
40 ! $Id: WriteTecplotAscii.F90,v 1.3 2008/12/06 08:45:08 mtcampbe Exp $
41 !
42 ! Copyright: (c) 2003 by the University of Illinois
43 !
44 !******************************************************************************
45 
46 SUBROUTINE writetecplotascii( iReg,iLev,plotType,region )
47 
48  USE moddatatypes
49  USE moderror
50  USE moddatastruct, ONLY : t_region
51  USE modglobal, ONLY : t_global
55  USE modmpi
56  USE modparameters
57  IMPLICIT NONE
58 
59 #include "Indexing.h"
60 
61 ! ... parameters
62  INTEGER :: ireg, ilev, plottype
63 
64  TYPE(t_region) :: region
65 
66 ! ... loop variables
67  INTEGER :: i, j, k, ipeul
68 
69 ! ... local variables
70  CHARACTER(CHRLEN+4) :: fname
71  CHARACTER(256) :: varstr
72  CHARACTER(16) :: concstr
73 
74  INTEGER :: ipnbeg, ipnend, jpnbeg, jpnend, kpnbeg, kpnend
75  INTEGER :: icoff, ijcoff, inoff, ijnoff, ijkn, cell(8), errorflag, npeul
76 
77  REAL(RFREAL) :: rho, u, v, w, press, temp, mach, c, qq
78  REAL(RFREAL), POINTER :: xyz(:,:), cv(:,:), dv(:,:), tv(:,:), gv(:,:)
79  REAL(RFREAL), POINTER :: peulcv(:,:), conc(:)
80 
81  TYPE(t_global), POINTER :: global
82 
83 !******************************************************************************
84 
85  global => region%global
86 
87  CALL registerfunction( global,'WriteTecplotAscii',&
88  'WriteTecplotAscii.F90' )
89 
90 ! set parameters --------------------------------------------------------------
91 
92  CALL rflo_getdimensphysnodes( region,ilev,ipnbeg,ipnend, &
93  jpnbeg,jpnend,kpnbeg,kpnend )
94  CALL rflo_getcelloffset( region,ilev,icoff,ijcoff )
95  CALL rflo_getnodeoffset( region,ilev,inoff,ijnoff )
96 
97  npeul = region%levels(ilev)%peul%nCv
98 
99  IF (npeul > 0) ALLOCATE( conc(npeul),stat=errorflag )
100 
101  global%error = errorflag
102  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
103 
104 ! open file and write the header ----------------------------------------------
105 
106  IF (ireg == 1) THEN
107  WRITE(fname,'(A,ES11.5,A)') &
108  trim(global%casename)//'.peul_',global%currentTime,'.dat'
109  OPEN(if_plot,file=fname,status='unknown',form='formatted',iostat=errorflag)
110  global%error = errorflag
111  IF (global%error /= 0) CALL errorstop( global,err_file_open,__line__,fname )
112 
113  IF (global%flowType == flow_steady) THEN
114  WRITE(if_plot,1000,err=10) trim(global%casename),global%currentIter
115  ELSE
116  IF (global%currentTime <= 0._rfreal) THEN
117  WRITE(if_plot,1005,err=10) trim(global%casename),global%timeStamp
118  ELSE
119  WRITE(if_plot,1005,err=10) trim(global%casename),global%currentTime
120  ENDIF
121  ENDIF
122 
123  varstr = 'x y z'
124  IF (plottype == plot_grid_flow) varstr = 'x y z rho u v w p T M'
125 
126  DO ipeul=1,npeul
127  SELECT CASE (ipeul)
128  CASE ( 0: 9)
129  WRITE(concstr,'(A,I1)') 'c_', ipeul
130  CASE (10:99)
131  WRITE(concstr,'(A,I2)') 'c_', ipeul
132  CASE default
133  WRITE(concstr,'(A)') 'c_?'
134  END SELECT ! iPeul
135  varstr = trim(varstr)//' '//trim(concstr)
136  ENDDO ! iPeul
137 
138  WRITE(if_plot,1010,err=10) trim(varstr)
139 
140  ENDIF ! iReg=1
141 
142 ! write zone header
143 
144  WRITE(if_plot,1015) ireg,ipnend-ipnbeg+1,jpnend-jpnbeg+1,kpnend-kpnbeg+1
145 
146 ! write data ------------------------------------------------------------------
147 ! pointer to variables
148 
149  xyz => region%levels(ilev)%grid%xyz
150  cv => region%levels(ilev)%mixt%cv
151  dv => region%levels(ilev)%mixt%dv
152  tv => region%levels(ilev)%mixt%tv
153  gv => region%levels(ilev)%mixt%gv
154  IF (npeul > 0) peulcv => region%levels(ilev)%peul%cv
155 
156  DO k=kpnbeg,kpnend
157  DO j=jpnbeg,jpnend
158  DO i=ipnbeg,ipnend
159  ijkn = indijk(i,j,k,inoff,ijnoff)
160  cell(1) = indijk(i ,j ,k ,icoff,ijcoff)
161  cell(2) = indijk(i-1,j ,k ,icoff,ijcoff)
162  cell(3) = indijk(i ,j-1,k ,icoff,ijcoff)
163  cell(4) = indijk(i-1,j-1,k ,icoff,ijcoff)
164  cell(5) = indijk(i ,j ,k-1,icoff,ijcoff)
165  cell(6) = indijk(i-1,j ,k-1,icoff,ijcoff)
166  cell(7) = indijk(i ,j-1,k-1,icoff,ijcoff)
167  cell(8) = indijk(i-1,j-1,k-1,icoff,ijcoff)
168 
169  DO ipeul=1,npeul
170  conc(ipeul) = aver(cell,ipeul,peulcv)
171  ENDDO
172 
173  IF (plottype == plot_grid_only) THEN
174 
175 ! ------- write grid coordinates and smoke fields only
176 
177  WRITE(if_plot,1020,err=10) xyz(xcoord,ijkn), &
178  xyz(ycoord,ijkn), &
179  xyz(zcoord,ijkn), &
180  (conc(ipeul),ipeul=1,npeul)
181 
182  ELSE
183 
184 ! ------- write grid and all fields
185 
186  rho = aver(cell,cv_mixt_dens,cv)
187  u = averdiv(cell,cv_mixt_xmom,cv,cv_mixt_dens,cv)
188  v = averdiv(cell,cv_mixt_ymom,cv,cv_mixt_dens,cv)
189  w = averdiv(cell,cv_mixt_zmom,cv,cv_mixt_dens,cv)
190  press = aver(cell,dv_mixt_pres,dv)
191  temp = aver(cell,dv_mixt_temp,dv)
192  c = aver(cell,dv_mixt_soun,dv)
193  qq = u*u + v*v + w*w
194  mach = sqrt(qq)/c
195 
196  WRITE(if_plot,1020,err=10) xyz(xcoord,ijkn), &
197  xyz(ycoord,ijkn), &
198  xyz(zcoord,ijkn), &
199  rho,u,v,w,press,temp,mach, &
200  (conc(ipeul),ipeul=1,npeul)
201 
202  ENDIF ! plotType
203 
204  ENDDO
205  ENDDO
206  ENDDO
207 
208 ! close file, handle errors ---------------------------------------------------
209 
210  IF (ireg == global%nRegions) THEN
211  CLOSE(if_plot,iostat=errorflag)
212  global%error = errorflag
213  IF (global%error /= 0) &
214  CALL errorstop( global,err_file_close,__line__,fname )
215  ENDIF
216 
217  IF (npeul > 0) DEALLOCATE( conc,stat=errorflag )
218 
219  global%error = errorflag
220  IF (global%error /= 0) CALL errorstop( global,err_deallocate,__line__ )
221 
222  CALL deregisterfunction( global )
223  goto 999
224 
225 10 CONTINUE
226  CALL errorstop( global,err_file_write,__line__,fname )
227 
228 ! formats ---------------------------------------------------------------------
229 
230 1000 FORMAT('TITLE="',a,'. Iteration: ',i8,'."')
231 1005 FORMAT('TITLE="',a,'. Time: ',es11.5,'."')
232 1010 FORMAT('VARIABLES= ',a)
233 1015 FORMAT('ZONE T="',i5.5,'", I=',i6,', J=',i6,', K=',i6,', F=POINT')
234 1020 FORMAT(999(1x,es13.6))
235 
236 999 CONTINUE
237 END SUBROUTINE writetecplotascii
238 
239 !******************************************************************************
240 !
241 ! RCS Revision history:
242 !
243 ! $Log: WriteTecplotAscii.F90,v $
244 ! Revision 1.3 2008/12/06 08:45:08 mtcampbe
245 ! Updated license.
246 !
247 ! Revision 1.2 2008/11/19 22:18:18 mtcampbe
248 ! Added Illinois Open Source License/Copyright
249 !
250 ! Revision 1.1 2004/12/01 22:29:09 fnajjar
251 ! Initial revision after changing case
252 !
253 ! Revision 1.2 2004/03/02 21:50:57 jferry
254 ! Added timestamp to name of peulpost output file
255 !
256 ! Revision 1.1 2003/09/25 15:40:22 jferry
257 ! Implented Rocsmoke post-processing
258 !
259 !******************************************************************************
260 
261 
262 
263 
264 
265 
266 
**********************************************************************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
double sqrt(double d)
Definition: double.h:73
RT c() const
Definition: Line_2.h:150
*********************************************************************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
**********************************************************************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)
subroutine writetecplotascii(iReg, region)
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
subroutine rflo_getcelloffset(region, iLev, iCellOffset, ijCellOffset)
void int int REAL * x
Definition: read.cpp: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_getdimensphysnodes(region, iLev, ipnbeg, ipnend, jpnbeg, jpnend, kpnbeg, kpnend)
j indices j
Definition: Indexing.h:6
DOUBLE PRECISION function aver(cell, iEq, var)
DOUBLE PRECISION function averdiv(cell, iEq1, var1, iEq2, var2)
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
RT a() const
Definition: Line_2.h:140