Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
POST_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 ! region = region data (dimensions, flow variables)
31 !
32 ! Output: to plot file.
33 !
34 ! Notes: none.
35 !
36 !******************************************************************************
37 !
38 ! $Id: POST_WriteTecplotAscii.F90,v 1.5 2008/12/06 08:44:49 mtcampbe Exp $
39 !
40 ! Copyright: (c) 2001 by the University of Illinois
41 !
42 !******************************************************************************
43 
44 SUBROUTINE writetecplotascii( iReg,region )
45 
46  USE moddatatypes
47  USE moderror
48  USE moddatastruct, ONLY : t_region
49  USE modglobal, ONLY : t_global
50  USE modmixture, ONLY : t_mixt
54  USE modmpi
55  USE modparameters
56 #ifdef TURB
57  USE modturbulence, ONLY : t_turb
59 #endif
60  IMPLICIT NONE
61 
62 #include "Indexing.h"
63 
64 ! ... parameters
65  INTEGER :: ireg
66 
67  TYPE(t_region) :: region
68 
69 ! ... loop variables
70  INTEGER :: i, j, k
71 
72 ! ... local variables
73  CHARACTER(CHRLEN+4) :: fname
74 
75  INTEGER :: ilev, ipnbeg, ipnend, jpnbeg, jpnend, kpnbeg, kpnend
76  INTEGER :: icoff, ijcoff, inoff, ijnoff, ijkn, cell(8), errorflag
77 
78  REAL(RFREAL) :: rho, u, v, w, press, temp, mach, c, qq
79  REAL(RFREAL), POINTER :: xyz(:,:), cv(:,:), dv(:,:), tv(:,:), gv(:,:)
80 #ifdef TURB
81  REAL(RFREAL) :: mut, tvort, len
82  REAL(RFREAL), POINTER :: vort(:,:), lens(:)
83 #endif
84 #ifdef STATS
85  REAL(RFREAL) :: su, sv, sw, spress, suu, svv, sww, suv, spp
86  REAL(RFREAL) :: rtime, smut, scdyn
87  LOGICAL :: statsactive
88 #endif
89 
90  TYPE(t_global), POINTER :: global
91  TYPE(t_mixt) , POINTER :: mixt
92 #ifdef TURB
93  TYPE(t_turb) , POINTER :: turb
94 #endif
95 
96 !******************************************************************************
97 
98  global => region%global
99 
100  CALL registerfunction( global,'WriteTecplotAscii',&
101  'POST_WriteTecplotAscii.F90' )
102 
103 ! set parameters --------------------------------------------------------------
104 
105  ilev = global%startLevel
106  CALL rflo_getdimensphysnodes( region,ilev,ipnbeg,ipnend, &
107  jpnbeg,jpnend,kpnbeg,kpnend )
108  CALL rflo_getcelloffset( region,ilev,icoff,ijcoff )
109  CALL rflo_getnodeoffset( region,ilev,inoff,ijnoff )
110 
111 ! statistics active?
112 
113 #ifdef STATS
114  statsactive = (global%postStatsFlag .AND. &
115  (global%flowType == flow_unsteady) .AND. &
116  (global%doStat == active))
117 
118 ! set 1/integrTime
119  rtime = 1._rfreal/global%integrTime
120 #endif
121 
122 ! open file and write the header ----------------------------------------------
123 
124  IF (ireg == 1) THEN
125  fname = trim(global%casename)//'.dat'
126  OPEN(if_plot,file=fname,status='unknown',form='formatted',iostat=errorflag)
127  global%error = errorflag
128  IF (global%error /= 0) CALL errorstop( global,err_file_open,__line__,fname )
129 
130  IF (global%flowType == flow_steady) THEN
131  WRITE(if_plot,1000,err=10) trim(global%casename),global%postIter
132  ELSE
133  WRITE(if_plot,1005,err=10) trim(global%casename),global%postTime
134  ENDIF
135  IF (global%postPlotType == plot_grid_only) THEN
136  WRITE(if_plot,1010,err=10) 'x y z'
137  ELSE
138 #ifndef TURB
139 #ifdef STATS
140  IF (statsactive) THEN
141  IF (global%mixtNStat > 0) THEN
142  WRITE(if_plot,1010,err=10) &
143  'x y z rho u v w p T M <u> <v> <w> <p> <uu> <vv> <ww> <uv> <pp>'
144  ELSE
145  WRITE(if_plot,1010,err=10) &
146  'x y z rho u v w p T M'
147  ENDIF
148  ELSE
149  WRITE(if_plot,1010,err=10) 'x y z rho u v w p T M'
150  ENDIF
151 #else
152  WRITE(if_plot,1010,err=10) 'x y z rho u v w p T M'
153 #endif
154 #endif
155 
156 #ifdef TURB
157  IF ((global%postTurbFlag .EQV. .false.) .OR. &
158  region%mixtInput%turbModel==turb_model_none) THEN
159 #ifdef STATS
160  IF (statsactive) THEN
161  IF (global%mixtNStat > 0) THEN
162  WRITE(if_plot,1010,err=10) &
163  'x y z rho u v w p T M <u> <v> <w> <p> <uu> <vv> <ww> <uv> <pp>'
164  ELSE
165  WRITE(if_plot,1010,err=10) 'x y z rho u v w p T M'
166  ENDIF
167  ELSE
168  WRITE(if_plot,1010,err=10) 'x y z rho u v w p T M'
169  ENDIF
170 #else
171  WRITE(if_plot,1010,err=10) 'x y z rho u v w p T M'
172 #endif
173  ENDIF
174  IF (global%postTurbFlag) THEN
175  IF (region%turbInput%nOutField == 1) THEN
176 #ifdef STATS
177  IF (statsactive) THEN
178  IF (global%turbNStat > 0) THEN
179  WRITE(if_plot,1010,err=10) &
180  'x y z rho u v w p T M mut <u> <v> <w> <p> <uu> <vv> <ww> <uv> <pp> <mut> <cdyn>'
181  ELSE
182  WRITE(if_plot,1010,err=10) &
183  'x y z rho u v w p T M mut <u> <v> <w> <p> <uu> <vv> <ww> <uv> <pp>'
184  ENDIF
185  ELSE
186  WRITE(if_plot,1010,err=10) 'x y z rho u v w p T M mut'
187  ENDIF
188 #else
189  WRITE(if_plot,1010,err=10) 'x y z rho u v w p T M mut'
190 #endif
191  ELSEIF (region%turbInput%nOutField == 2) THEN
192 #ifdef STATS
193  IF (statsactive) THEN
194  IF (global%turbNStat > 0) THEN
195  WRITE(if_plot,1010,err=10) &
196  'x y z rho u v w p T M mut tvort <u> <v> <w> <p> <uu> <vv> <ww> <uv> <pp> <mut> <cdyn>'
197  ELSE
198  WRITE(if_plot,1010,err=10) &
199  'x y z rho u v w p T M mut tvort <u> <v> <w> <p> <uu> <vv> <ww> <uv> <pp>'
200  ENDIF
201  ELSE
202  WRITE(if_plot,1010,err=10) 'x y z rho u v w p T M mut tvort'
203  ENDIF
204 #else
205  WRITE(if_plot,1010,err=10) 'x y z rho u v w p T M mut tvort'
206 #endif
207  ENDIF
208  IF ((region%turbInput%modelClass == model_rans) .AND. &
209  (region%turbInput%nOutField == 3)) THEN
210 #ifdef STATS
211  IF (statsactive) THEN
212  IF (global%turbNStat > 0) THEN
213  WRITE(if_plot,1010,err=10) &
214  'x y z rho u v w p T M mut tvort lens <u> <v> <w> <p> <uu> <vv> <ww> <uv> <pp> <mut> <cdyn>'
215  ELSE
216  WRITE(if_plot,1010,err=10) &
217  'x y z rho u v w p T M mut tvort lens <u> <v> <w> <p> <uu> <vv> <ww> <uv> <pp>'
218  ENDIF
219  ELSE
220  WRITE(if_plot,1010,err=10) 'x y z rho u v w p T M mut tvort lens'
221  ENDIF
222 #else
223  WRITE(if_plot,1010,err=10) 'x y z rho u v w p T M mut tvort lens'
224 #endif
225  ENDIF
226  ENDIF
227 #endif
228  ENDIF
229  ENDIF ! iReg=1
230 
231 ! write zone header
232 
233  WRITE(if_plot,1015) ireg,ipnend-ipnbeg+1,jpnend-jpnbeg+1,kpnend-kpnbeg+1
234 
235 ! write data ------------------------------------------------------------------
236 ! pointer to variables
237 
238  xyz => region%levels(ilev)%grid%xyz
239  mixt => region%levels(ilev)%mixt
240  cv => mixt%cv
241  dv => mixt%dv
242  tv => mixt%tv
243  gv => mixt%gv
244 #ifdef TURB
245  turb => region%levels(ilev)%turb
246 
247  IF (global%postTurbFlag) THEN
248  IF (region%turbInput%nOutField > 1) vort => region%levels(ilev)%turb%vort
249 
250  IF (region%turbInput%modelClass == model_rans) &
251  lens => region%levels(ilev)%turb%lens
252  ENDIF
253 #endif
254 
255 ! write grid coordinates only
256 
257  IF (global%postPlotType == plot_grid_only) THEN
258 
259  DO k=kpnbeg,kpnend
260  DO j=jpnbeg,jpnend
261  DO i=ipnbeg,ipnend
262  ijkn = indijk(i,j,k,inoff,ijnoff)
263  WRITE(if_plot,1020,err=10) xyz(xcoord,ijkn), &
264  xyz(ycoord,ijkn), &
265  xyz(zcoord,ijkn)
266  ENDDO
267  ENDDO
268  ENDDO
269 
270 ! write grid and solution
271 
272  ELSE
273 
274  DO k=kpnbeg,kpnend
275  DO j=jpnbeg,jpnend
276  DO i=ipnbeg,ipnend
277  ijkn = indijk(i,j,k,inoff,ijnoff)
278  cell(1) = indijk(i ,j ,k ,icoff,ijcoff)
279  cell(2) = indijk(i-1,j ,k ,icoff,ijcoff)
280  cell(3) = indijk(i ,j-1,k ,icoff,ijcoff)
281  cell(4) = indijk(i-1,j-1,k ,icoff,ijcoff)
282  cell(5) = indijk(i ,j ,k-1,icoff,ijcoff)
283  cell(6) = indijk(i-1,j ,k-1,icoff,ijcoff)
284  cell(7) = indijk(i ,j-1,k-1,icoff,ijcoff)
285  cell(8) = indijk(i-1,j-1,k-1,icoff,ijcoff)
286 
287  rho = aver(cell,cv_mixt_dens,cv)
288  u = averdiv(cell,cv_mixt_xmom,cv,cv_mixt_dens,cv)
289  v = averdiv(cell,cv_mixt_ymom,cv,cv_mixt_dens,cv)
290  w = averdiv(cell,cv_mixt_zmom,cv,cv_mixt_dens,cv)
291  press = aver(cell,dv_mixt_pres,dv)
292  temp = aver(cell,dv_mixt_temp,dv)
293  c = aver(cell,dv_mixt_soun,dv)
294  qq = u*u + v*v + w*w
295  mach = sqrt(qq)/c
296 #ifdef STATS
297  IF (statsactive) THEN
298  IF (global%mixtNStat > 0) THEN
299  su = aver(cell,2,mixt%tav)*rtime ! 02 mixtStatId
300  sv = aver(cell,3,mixt%tav)*rtime ! 03
301  sw = aver(cell,4,mixt%tav)*rtime ! 04
302  spress = aver(cell,5,mixt%tav)*rtime ! 06
303  suu = aver(cell,7,mixt%tav)*rtime ! 22
304  svv = aver(cell,8,mixt%tav)*rtime ! 33
305  sww = aver(cell,9,mixt%tav)*rtime ! 44
306  suv = aver(cell,10,mixt%tav)*rtime ! 23
307  spp = aver(cell,11,mixt%tav)*rtime ! 66
308  suu = suu - su*su
309  svv = svv - sv*sv
310  sww = sww - sw*sw
311  suv = suv - su*sv
312  spp = spp - spress*spress
313  ENDIF
314 #ifdef TURB
315  IF (global%turbNStat > 0) THEN
316  smut = aver(cell,1,turb%tav)*rtime ! 01 turbStatId
317  scdyn = aver(cell,2,turb%tav)*rtime ! 03
318  ENDIF
319 #endif
320  ENDIF ! statsActive
321 #endif
322 
323 #ifndef TURB
324 #ifdef STATS
325  IF (statsactive) THEN
326  IF (global%mixtNStat > 0) THEN
327  WRITE(if_plot,1030,err=10) xyz(xcoord,ijkn), &
328  xyz(ycoord,ijkn), &
329  xyz(zcoord,ijkn), &
330  rho,u,v,w,press,temp,mach, &
331  su,sv,sw,spress,suu,svv,sww,suv,spp
332  ELSE
333  WRITE(if_plot,1020,err=10) xyz(xcoord,ijkn), &
334  xyz(ycoord,ijkn), &
335  xyz(zcoord,ijkn), &
336  rho,u,v,w,press,temp,mach
337  ENDIF
338  ELSE
339  WRITE(if_plot,1020,err=10) xyz(xcoord,ijkn), &
340  xyz(ycoord,ijkn), &
341  xyz(zcoord,ijkn), &
342  rho,u,v,w,press,temp,mach
343  ENDIF
344 #else
345  WRITE(if_plot,1020,err=10) xyz(xcoord,ijkn), &
346  xyz(ycoord,ijkn), &
347  xyz(zcoord,ijkn), &
348  rho,u,v,w,press,temp,mach
349 #endif
350 #endif
351 
352 #ifdef TURB
353  IF ((global%postTurbFlag .EQV. .false.) .OR. &
354  region%turbInput%modelClass == model_none) THEN
355 #ifdef STATS
356  IF (statsactive) THEN
357  IF (global%mixtNStat > 0) THEN
358  WRITE(if_plot,1030,err=10) xyz(xcoord,ijkn), &
359  xyz(ycoord,ijkn), &
360  xyz(zcoord,ijkn), &
361  rho,u,v,w,press,temp,mach,&
362  su,sv,sw,spress,suu,svv,sww,suv,spp
363  ELSE
364  WRITE(if_plot,1020,err=10) xyz(xcoord,ijkn), &
365  xyz(ycoord,ijkn), &
366  xyz(zcoord,ijkn), &
367  rho,u,v,w,press,temp,mach
368  ENDIF
369  ELSE
370  WRITE(if_plot,1020,err=10) xyz(xcoord,ijkn), &
371  xyz(ycoord,ijkn), &
372  xyz(zcoord,ijkn), &
373  rho,u,v,w,press,temp,mach
374  ENDIF
375 #else
376  WRITE(if_plot,1020,err=10) xyz(xcoord,ijkn), &
377  xyz(ycoord,ijkn), &
378  xyz(zcoord,ijkn), &
379  rho,u,v,w,press,temp,mach
380 #endif
381  ENDIF
382  IF (global%postTurbFlag) THEN
383  mut = aver(cell,tv_mixt_muet,tv)
384  IF (region%turbInput%nOutField == 1) THEN
385 #ifdef STATS
386  IF (statsactive) THEN
387  IF (global%turbNStat > 0) THEN
388  WRITE(if_plot,1041,err=10) xyz(xcoord,ijkn), &
389  xyz(ycoord,ijkn), &
390  xyz(zcoord,ijkn), &
391  rho,u,v,w,press,temp,mach,mut, &
392  su,sv,sw,spress,suu,svv,sww,suv,spp, &
393  smut,scdyn
394  ELSE
395  WRITE(if_plot,1031,err=10) xyz(xcoord,ijkn), &
396  xyz(ycoord,ijkn), &
397  xyz(zcoord,ijkn), &
398  rho,u,v,w,press,temp,mach,mut, &
399  su,sv,sw,spress,suu,svv,sww,suv,spp
400  ENDIF
401  ELSE
402  WRITE(if_plot,1021,err=10) xyz(xcoord,ijkn), &
403  xyz(ycoord,ijkn), &
404  xyz(zcoord,ijkn), &
405  rho,u,v,w,press,temp,mach,mut
406  ENDIF
407 #else
408  WRITE(if_plot,1021,err=10) xyz(xcoord,ijkn), &
409  xyz(ycoord,ijkn), &
410  xyz(zcoord,ijkn), &
411  rho,u,v,w,press,temp,mach,mut
412 #endif
413  ELSEIF (region%turbInput%nOutField == 2) THEN
414  tvort = aver(cell,xcoord,vort)
415 #ifdef STATS
416  IF (statsactive) THEN
417  IF (global%turbNStat > 0) THEN
418  WRITE(if_plot,1042,err=10) xyz(xcoord,ijkn), &
419  xyz(ycoord,ijkn), &
420  xyz(zcoord,ijkn), &
421  rho,u,v,w,press,temp,mach,mut,tvort, &
422  su,sv,sw,spress,suu,svv,sww,suv,spp, &
423  smut,scdyn
424  ELSE
425  WRITE(if_plot,1032,err=10) xyz(xcoord,ijkn), &
426  xyz(ycoord,ijkn), &
427  xyz(zcoord,ijkn), &
428  rho,u,v,w,press,temp,mach,mut,tvort, &
429  su,sv,sw,spress,suu,svv,sww,suv,spp
430  ENDIF
431  ELSE
432  WRITE(if_plot,1022,err=10) xyz(xcoord,ijkn), &
433  xyz(ycoord,ijkn), &
434  xyz(zcoord,ijkn), &
435  rho,u,v,w,press,temp,mach,mut,tvort
436  ENDIF
437 #else
438  WRITE(if_plot,1022,err=10) xyz(xcoord,ijkn), &
439  xyz(ycoord,ijkn), &
440  xyz(zcoord,ijkn), &
441  rho,u,v,w,press,temp,mach,mut,tvort
442 #endif
443  ENDIF
444  IF ((region%turbInput%modelClass == model_rans ) .AND. &
445  (region%turbInput%nOutField == 3)) THEN
446  tvort = aver(cell,xcoord,vort)
447  len = aver1d(cell,lens)
448 #ifdef STATS
449  IF (statsactive) THEN
450  IF (global%turbNStat > 0) THEN
451  WRITE(if_plot,1043,err=10) xyz(xcoord,ijkn), &
452  xyz(ycoord,ijkn), &
453  xyz(zcoord,ijkn), &
454  rho,u,v,w,press,temp,mach,mut,tvort,len, &
455  su,sv,sw,spress,suu,svv,sww,suv,spp,smut,scdyn
456  ELSE
457  WRITE(if_plot,1033,err=10) xyz(xcoord,ijkn), &
458  xyz(ycoord,ijkn), &
459  xyz(zcoord,ijkn), &
460  rho,u,v,w,press,temp,mach,mut,tvort,len, &
461  su,sv,sw,spress,suu,svv,sww,suv,spp
462  ENDIF
463  ELSE
464  WRITE(if_plot,1023,err=10) xyz(xcoord,ijkn), &
465  xyz(ycoord,ijkn), &
466  xyz(zcoord,ijkn), &
467  rho,u,v,w,press,temp,mach,mut,tvort,len
468  ENDIF
469 #else
470  WRITE(if_plot,1023,err=10) xyz(xcoord,ijkn), &
471  xyz(ycoord,ijkn), &
472  xyz(zcoord,ijkn), &
473  rho,u,v,w,press,temp,mach,mut,tvort,len
474 #endif
475  ENDIF
476  ENDIF ! postTurbFlag
477 #endif
478  ENDDO
479  ENDDO
480  ENDDO
481 
482  ENDIF ! postPlotType
483 
484 ! close file, handle errors ---------------------------------------------------
485 
486  IF (ireg == global%nRegions) THEN
487  CLOSE(if_plot,iostat=errorflag)
488  global%error = errorflag
489  IF (global%error /= 0) CALL errorstop( global,err_file_close,__line__,fname )
490  ENDIF
491 
492  CALL deregisterfunction( global )
493  goto 999
494 
495 10 CONTINUE
496  CALL errorstop( global,err_file_write,__line__,fname )
497 
498 ! formats ---------------------------------------------------------------------
499 
500 1000 FORMAT('TITLE="',a,'. Iteration: ',i8,'."')
501 1005 FORMAT('TITLE="',a,'. Time: ',1pe11.5,'."')
502 1010 FORMAT('VARIABLES= ',a)
503 1015 FORMAT('ZONE T="',i5.5,'", I=',i6,', J=',i6,', K=',i6,', F=POINT')
504 1020 FORMAT(1p,10(1x,e13.6))
505 1021 FORMAT(1p,11(1x,e13.6))
506 1022 FORMAT(1p,12(1x,e13.6))
507 1023 FORMAT(1p,13(1x,e13.6))
508 1030 FORMAT(1p,19(1x,e13.6))
509 1031 FORMAT(1p,20(1x,e13.6))
510 1032 FORMAT(1p,21(1x,e13.6))
511 1033 FORMAT(1p,22(1x,e13.6))
512 1041 FORMAT(1p,22(1x,e13.6))
513 1042 FORMAT(1p,23(1x,e13.6))
514 1043 FORMAT(1p,24(1x,e13.6))
515 
516 999 CONTINUE
517 END SUBROUTINE writetecplotascii
518 
519 !******************************************************************************
520 !
521 ! RCS Revision history:
522 !
523 ! $Log: POST_WriteTecplotAscii.F90,v $
524 ! Revision 1.5 2008/12/06 08:44:49 mtcampbe
525 ! Updated license.
526 !
527 ! Revision 1.4 2008/11/19 22:17:59 mtcampbe
528 ! Added Illinois Open Source License/Copyright
529 !
530 ! Revision 1.3 2004/12/24 04:07:59 wasistho
531 ! put brackets when comparing logicals in if statements
532 !
533 ! Revision 1.2 2004/12/03 03:20:31 wasistho
534 ! rflo_modinterfacespost to post_modinterfaces
535 !
536 ! Revision 1.1 2004/12/03 02:03:16 wasistho
537 ! added prefix
538 !
539 ! Revision 1.1 2004/12/03 00:32:01 wasistho
540 ! lower to upper case
541 !
542 ! Revision 1.15 2004/11/16 04:20:44 wasistho
543 ! replaced extension .plt to .dat
544 !
545 ! Revision 1.14 2004/11/10 18:29:54 wasistho
546 ! put rtime within ifdef STATS
547 !
548 ! Revision 1.13 2004/11/10 02:19:46 wasistho
549 ! devided accumulated tav by integrTime
550 !
551 ! Revision 1.12 2004/11/09 12:17:30 wasistho
552 ! compute <u> = <uu>-<u><u> inside routine
553 !
554 ! Revision 1.11 2004/11/09 10:50:31 wasistho
555 ! added statistics to rflopost
556 !
557 ! Revision 1.10 2004/07/24 03:48:22 wasistho
558 ! use postSection instead of command line input
559 !
560 ! Revision 1.9 2004/02/11 03:26:16 wasistho
561 ! added feature: variable number of turbulence output fields
562 !
563 ! Revision 1.8 2004/02/07 01:19:00 wasistho
564 ! added turbulence related results in rocflo post processing
565 !
566 ! Revision 1.7 2003/05/15 02:57:07 jblazek
567 ! Inlined index function.
568 !
569 ! Revision 1.6 2003/03/20 22:23:47 haselbac
570 ! Renamed ModInterfaces
571 !
572 ! Revision 1.5 2003/03/20 19:41:26 haselbac
573 ! Corrected mistake in phased check-in
574 !
575 ! Revision 1.4 2003/03/20 19:34:37 haselbac
576 ! Modified RegFun call to avoid probs with long 'POST_WriteTecplotAscii.F90' names
577 !
578 ! Revision 1.3 2002/10/12 03:20:51 jblazek
579 ! Replaced [io]stat=global%error with local errorFlag for Rocflo.
580 !
581 ! Revision 1.2 2002/09/05 17:40:22 jblazek
582 ! Variable global moved into regions().
583 !
584 ! Revision 1.1 2002/07/20 00:42:05 jblazek
585 ! Added ASCII Tecplot format.
586 !
587 !******************************************************************************
588 
589 
590 
591 
592 
593 
594 
595 
**********************************************************************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
DOUBLE PRECISION function aver1d(cell, var)
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