62 INTEGER :: ireg, ilev, plottype
64 TYPE(t_region
) :: region
67 INTEGER ::
i,
j,
k, ipeul
70 CHARACTER(CHRLEN+4) :: fname
71 CHARACTER(256) :: varstr
72 CHARACTER(16) :: concstr
75 INTEGER :: icoff, ijcoff, inoff, ijnoff, ijkn, cell(8), errorflag, npeul
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(:)
85 global => region%global
88 'WriteTecplotAscii.F90' )
97 npeul = region%levels(ilev)%peul%nCv
99 IF (npeul > 0)
ALLOCATE( conc(npeul),stat=errorflag )
101 global%error = errorflag
102 IF (global%error /= 0) CALL
errorstop( global,err_allocate,__line__ )
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 )
113 IF (global%flowType == flow_steady)
THEN
114 WRITE(if_plot,1000,err=10) trim(global%casename),global%currentIter
116 IF (global%currentTime <= 0._rfreal)
THEN
117 WRITE(if_plot,1005,err=10) trim(global%casename),global%timeStamp
119 WRITE(if_plot,1005,err=10) trim(global%casename),global%currentTime
124 IF (plottype == plot_grid_flow) varstr =
'x y z rho u v w p T M'
129 WRITE(concstr,
'(A,I1)')
'c_', ipeul
131 WRITE(concstr,
'(A,I2)')
'c_', ipeul
133 WRITE(concstr,
'(A)')
'c_?'
135 varstr = trim(varstr)//
' '//trim(concstr)
138 WRITE(if_plot,1010,err=10) trim(varstr)
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
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)
170 conc(ipeul) =
aver(cell,ipeul,peulcv)
173 IF (plottype == plot_grid_only)
THEN
177 WRITE(if_plot,1020,err=10) xyz(xcoord,ijkn), &
180 (conc(ipeul),ipeul=1,npeul)
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)
196 WRITE(if_plot,1020,err=10) xyz(xcoord,ijkn), &
199 rho,u,
v,w,press,temp,mach, &
200 (conc(ipeul),ipeul=1,npeul)
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 )
217 IF (npeul > 0)
DEALLOCATE( conc,stat=errorflag )
219 global%error = errorflag
220 IF (global%error /= 0) CALL
errorstop( global,err_deallocate,__line__ )
226 CALL
errorstop( global,err_file_write,__line__,fname )
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(1
x,es13.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 jpnbeg
**********************************************************************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)
int status() const
Obtain the status of the attribute.
*********************************************************************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
**********************************************************************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)
**********************************************************************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)
**********************************************************************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)
DOUBLE PRECISION function aver(cell, iEq, var)
DOUBLE PRECISION function averdiv(cell, iEq1, var1, iEq2, var2)
subroutine errorstop(global, errorCode, errorLine, addMessage)
subroutine deregisterfunction(global)
**********************************************************************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