Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
RVAV_Main.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: Verification And Validation (VAV) Tool to compare 2 DataStreams.
26 !
27 ! Description: currently supported formats are:
28 ! - ASCII
29 ! - Binary
30 !
31 ! Input: case name from the list of arguments
32 !
33 ! Output: to Standard Output.
34 !
35 ! Notes:
36 !
37 !******************************************************************************
38 !
39 ! $Id: RVAV_Main.F90,v 1.3 2008/12/06 08:45:08 mtcampbe Exp $
40 !
41 ! Copyright: (c) 2002 by the University of Illinois
42 !
43 !******************************************************************************
44 
45 PROGRAM rocvav_post
46 
47  USE moddatatypes
48  USE moderror
49  USE moddatastruct, ONLY : t_region
50  USE modglobal, ONLY : t_global
51  USE modgrid, ONLY : t_grid
52  USE modmixture, ONLY : t_mixt
57  USE modmpi
58  USE modparameters
60  USE rvav_modglobal
67  IMPLICIT NONE
68 
69 ! ... loop variables
70  INTEGER :: ireg, ilev, i, j, k
71 
72 ! ... local variables
73  CHARACTER(CHRLEN) :: msg, verbosity, versionstring, headerstring
74 
75  TYPE(t_region) , POINTER :: regions(:)
76  TYPE(t_grid) , POINTER :: grid
77  TYPE(t_mixt) , POINTER :: mixt
78  TYPE(t_region) , POINTER :: regionss1(:), regionss2(:)
79  TYPE(t_compare), POINTER :: rvavcompare
80  TYPE(t_global) , POINTER :: global
81 
82 ! ... we are setting the indCp and indMol values here
83 ! ... if the Cp and Molecular weight changes from cell to cell you will
84 ! ... need to use the computed values of indCp and indMol in this program
85 
86  INTEGER :: indcp = 0, indmol = 0
87  INTEGER :: icompare
88  INTEGER :: ibegs1,iends1,ijumps1
89  INTEGER :: jbegs1,jends1,jjumps1
90  INTEGER :: kbegs1,kends1,kjumps1
91  INTEGER :: icoffs1,ijcoffs1
92 
93  INTEGER :: ibegs2,iends2,ijumps2
94  INTEGER :: jbegs2,jends2,jjumps2
95  INTEGER :: kbegs2,kends2,kjumps2
96  INTEGER :: icoffs2,ijcoffs2
97 
98  INTEGER :: variableindexs1, variableindexs2
99  INTEGER :: filetypes1, filetypes2
100  INTEGER :: similaritytypes2
101  INTEGER :: inodess1, jnodess1, knodess1
102  INTEGER :: inodess2, jnodess2, knodess2
103  INTEGER :: iregs1, iregs2
104  INTEGER :: margin, versionwidth, errorflag
105  INTEGER, PARAMETER :: headerwidth = 54
106 
107  REAL(RFREAL) :: evs1min, evs2min, evs1max, evs2max
108 
109 !******************************************************************************
110 
111  ALLOCATE( global )
112 
113  global%nFunTree = 0
114  CALL registerfunction( global, 'ROCVAV_Post',&
115  'RVAV_Main.F90' )
116 
117 ! initialize global parameters ------------------------------------------------
118 
119  global%verbLevel = verbose_none
120 
121  global%flowType = flow_steady ! stationary flow
122  global%currentTime = -1._rfreal ! no physical time set
123  global%currentIter = -1 ! no iteration
124 
125  global%inDir = './' ! directory path
126  global%outDir = './'
127 
128  global%nProcAlloc = 1
129  global%myProcid = masterproc ! default process number (not an MPI code)
130  global%mpierr = err_none
131  global%error = err_none
132 
133  global%pi = 4._rfreal*atan(1._rfreal)
134  global%rad = global%pi/180._rfreal
135 
136 ! print header ----------------------------------------------------------------
137 
138 #ifdef MPI
139  CALL mpi_init( global%mpierr )
140  IF (global%mpierr /=0 ) CALL errorstop( global, err_mpi_trouble,__line__ )
141 #endif
142 
143  CALL buildversionstring( versionstring )
144 
145  headerstring = ' '
146  versionwidth = len_trim(versionstring)
147  margin = (headerwidth-versionwidth)/2
148  headerstring(margin+1:margin+versionwidth) = versionstring(1:versionwidth)
149  headerstring(1:1) = '*'
150  headerstring(headerwidth:headerwidth) = '*'
151 
152  WRITE(stdout,'(/,A)') ' ******************************************************'
153  WRITE(stdout, '(A)') ' * *'
154  WRITE(stdout, '(A)') ' * ROCVAV: Verification And Validation Tool *'
155  WRITE(stdout, '(A)') ' * ======================================== *'
156  WRITE(stdout, '(A)') ' * *'
157  WRITE(stdout, '(A)') ' '//trim(headerstring)
158  WRITE(stdout, '(A)') ' * Copyright (c) by the University of Illinois *'
159  WRITE(stdout, '(A)') ' * *'
160  WRITE(stdout,'(A,/)') ' ******************************************************'
161 
162 ! read argument list ----------------------------------------------------------
163 
164  CALL getarg(1,global%casename)
165  CALL getarg(2,verbosity)
166 
167  IF (len_trim(global%casename)==0 .OR. len_trim(verbosity)==0) THEN
168  WRITE(stdout,'(/,A,//,5(A,/))') &
169  'Usage: rocvav <casename> <verbosity>', &
170  ' verbosity = 0 - no output', &
171  ' = 1 - moderate output',&
172  ' = 2 - output all'
173 #ifdef MPI
174  CALL mpi_finalize( global%mpierr )
175 #endif
176  stop
177  ENDIF
178 
179  READ(verbosity,*) global%verbLevel
180 
181 ! set MultiGrid Start Level ---------------------------------------------------
182 
183  global%startLevel = 1
184 
185 ! read region topology --------------------------------------------------------
186 
187  IF (global%verbLevel /= verbose_none) &
188  WRITE(stdout,'(/,A)') 'RFLO Reading region topology ...'
189 
190  CALL rflo_readregiontopology( global,regionss1 )
191 
192  DO ireg=1,global%nRegions
193  regionss1(ireg)%startLevel = global%startLevel
194  regionss1(ireg)%currLevel = global%startLevel
195  IF (regionss1(ireg)%nGridLevels < regionss1(ireg)%currLevel) THEN
196  WRITE(msg,1000) ireg,global%startLevel
197  CALL errorstop( global, err_grid_level,__line__,msg )
198  ENDIF
199  ENDDO ! iReg
200 
201 ! get user parameters ---------------------------------------------------------
202 
203  IF (global%verbLevel /= verbose_none) &
204  WRITE(stdout,'(/,A)') 'RFLO Reading user input ...'
205 
206  CALL rflo_initinputvalues( regionss1 )
207  CALL readinputfile( regionss1 )
208  CALL rflo_derivedinputvalues( regionss1 )
209 
210 ! reset Iteration Number or Timestamp to Zero
211 
212  IF (global%flowType == flow_steady) THEN
213  global%currentIter = 0
214  ELSE
215  global%timeStamp = 0.0_rfreal
216  ENDIF
217 
218 ! read Input File Pertinent to RocVAV
219 
220  IF (global%verbLevel /= verbose_none) &
221  WRITE(stdout,'(/,A)') 'RocVAV Reading user input ...'
222 
223  CALL rvav_readinputfile( global )
224 
225 ! read File for Stream 1
226 
227  IF (global%verbLevel /= verbose_none) &
228  WRITE(stdout,'(/,A)') 'RocVAV Reading Stream1 Data ...'
229 
230  CALL rvav_readfilestream1( regionss1 )
231 
232 ! generate Analytical Solution File
233 
234  IF (global%verbLevel /= verbose_none) &
235  WRITE(stdout,'(/,A)') 'RocVAV Compute Analytical Solution Data for Stream2...'
236 
237  CALL rvav_computeanalyticalsolution( globalrvav%similarityTypeS2, regionss1 )
238 
239 ! read File for Stream 2
240 
241  IF (global%verbLevel /= verbose_none) &
242  WRITE(stdout,'(/,A)') 'RocVAV Reading Stream2 Data ...'
243 
244  CALL rvav_readfilestream2( regionss1, regionss2 )
245 
246 ! - extraction of variables to be compared and the compute errors
247 
248  DO icompare=1,globalrvav%nComparisons
249 
250  rvavcompare => globalrvav%RVAVcompare(icompare)
251 
252  IF (global%verbLevel /= verbose_none) THEN
253  WRITE(stdout,'(/,A,I5.5,A)') 'In comparison = ',icompare,'we are comparing:'
254  WRITE(stdout,'(A,I5.5)') 'Stream1 block = ' ,rvavcompare%blockS1
255  WRITE(stdout,'(A,I5.5)') 'Stream2 block = ' ,rvavcompare%blockS2
256  WRITE(stdout,'(A,I5.5)') 'Stream1 variable = ' ,rvavcompare%variableIndexS1
257  WRITE(stdout,'(A,I5.5)') 'Stream2 variable = ' ,rvavcompare%variableIndexS2
258  END IF ! verbLevel
259 
260 ! - checking the contents of blockS1 and blockS2
261 
262  IF (globalrvav%fileTypeS1 == file_computed .AND. &
263  globalrvav%fileTypeS2 == file_computed) THEN
264 
265  IF (rvavcompare%blockS1 /= rvavcompare%blockS2)THEN
266  WRITE(stdout,'(/,A)')'Streams 1 and 2 are both Computed Results'
267  WRITE(stdout,'(A)')'Block numbers on Stream1 and Stream2 do not match'
268  WRITE(stdout,'(A)')'RocVAV will abort'
269  CALL errorstop( global, err_previous_errors,__line__ )
270  ENDIF
271 
272  ENDIF ! fileTypeS1
273 
274  IF (rvavcompare%operationS1 /= rvavcompare%operationS2) THEN
275  WRITE(stdout,'(/,A)')'Operations in Stream1 and Stream2 do not match'
276  WRITE(stdout,'(A)')'RocVAV will abort'
277  CALL errorstop( global, err_previous_errors,__line__ )
278  ENDIF
279 
280  ibegs1 = rvavcompare%ibegS1
281  iends1 = rvavcompare%iendS1
282  ijumps1 = rvavcompare%ijumpS1
283 
284  jbegs1 = rvavcompare%jbegS1
285  jends1 = rvavcompare%jendS1
286  jjumps1 = rvavcompare%jjumpS1
287 
288  kbegs1 = rvavcompare%kbegS1
289  kends1 = rvavcompare%kendS1
290  kjumps1 = rvavcompare%kjumpS1
291 
292  variableindexs1 = rvavcompare%variableIndexS1
293  filetypes1 = globalrvav%fileTypeS1
294 
295  ibegs2 = rvavcompare%ibegS2
296  iends2 = rvavcompare%iendS2
297  ijumps2 = rvavcompare%ijumpS2
298 
299  jbegs2 = rvavcompare%jbegS2
300  jends2 = rvavcompare%jendS2
301  jjumps2 = rvavcompare%jjumpS2
302 
303  kbegs2 = rvavcompare%kbegS2
304  kends2 = rvavcompare%kendS2
305  kjumps2 = rvavcompare%kjumpS2
306 
307  icoffs1 = globalrvav%iCOffS1
308  ijcoffs1 = globalrvav%iCOffS1
309 
310  icoffs2 = globalrvav%iCOffS2
311  ijcoffs2 = globalrvav%iCOffS2
312 
313  variableindexs2 = rvavcompare%variableIndexS2
314  filetypes2 = globalrvav%fileTypeS2
315  similaritytypes2 = globalrvav%similarityTypeS2
316 
317  inodess1 = int(REAL( (iends1-ibegs1)/ijumps1,kind=rfreal))+1
318  jnodess1 = int(REAL( (jends1-jbegs1)/jjumps1,kind=rfreal))+1
319  knodess1 = int(REAL( (kends1-kbegs1)/kjumps1,kind=rfreal))+1
320 
321  inodess2 = int(REAL( (iends2-ibegs2)/ijumps2,kind=rfreal))+1
322  jnodess2 = int(REAL( (jends2-jbegs2)/jjumps2,kind=rfreal))+1
323  knodess2 = int(REAL( (kends2-kbegs2)/kjumps2,kind=rfreal))+1
324 
325  IF (global%verbLevel /= verbose_none) THEN
326  WRITE(stdout,'(/,A,3(I5,3X))') 'Stream1 iNodes,jNodes,kNodes = ', &
327  inodess1,jnodess1,knodess1
328  WRITE(stdout,'(A,3(I5,3X))') 'Stream2 iNodes,jNodes,kNodes = ', &
329  inodess2,jnodess2,knodess2
330  END IF ! verbLevel
331 
332 ! - Allocate evS1 and evS2
333 
334  IF (.NOT. ASSOCIATED(globalrvav%evS1))THEN
335  ALLOCATE( globalrvav%evS1(inodess1,jnodess1,knodess1),stat=errorflag )
336  global%error = errorflag
337  IF (global%error /= 0) CALL errorstop( global, err_allocate, __line__ )
338  ENDIF
339 
340  IF (.NOT. ASSOCIATED(globalrvav%evS2))THEN
341  ALLOCATE( globalrvav%evS2(inodess2,jnodess2,knodess2),stat=errorflag )
342  global%error = errorflag
343  IF (global%error /= 0) CALL errorstop( global, err_allocate, __line__ )
344  ENDIF
345 
346 ! - initialize evS1 and evS2
347 
348  globalrvav%evS1 = 0.0_rfreal
349  globalrvav%evS2 = 0.0_rfreal
350 
351 ! - extract variables from Stream1
352 
353  iregs1 = rvavcompare%blockS1
354 
355  IF (global%verbLevel /= verbose_none) &
356  WRITE(stdout,'(/,A)') 'Entering RVAV_ExtractVariables-EVS1'
357 
358  CALL rvav_extractvariables( global, regionss1(iregs1), &
359  ibegs1,iends1,ijumps1, &
360  jbegs1,jends1,jjumps1, &
361  kbegs1,kends1,kjumps1, &
362  icoffs1, ijcoffs1, &
363  variableindexs1, &
364  filetypes1, &
365  indcp,indmol,globalrvav%evS1 )
366 
367  IF (global%verbLevel /= verbose_none) &
368  WRITE(stdout,'(/,A)') 'Exiting RVAV_ExtractVariables-EVS1'
369 
370 ! - extract variables from Stream2
371 
372  iregs2 = rvavcompare%blockS2
373 
374  IF (global%verbLevel /= verbose_none) &
375  WRITE(stdout,'(/,A)') 'Entering RVAV_ExtractVariables-EVS2'
376 
377  CALL rvav_extractvariables( global, regionss2(iregs2), &
378  ibegs2,iends2,ijumps2, &
379  jbegs2,jends2,jjumps2, &
380  kbegs2,kends2,kjumps2, &
381  icoffs2, ijcoffs2, &
382  variableindexs2, &
383  filetypes2, &
384  indcp,indmol,globalrvav%evS2 )
385 
386  IF (global%verbLevel /= verbose_none) &
387  WRITE(stdout,'(/,A)') 'Exiting RVAV_ExtractVariables-EVS2'
388 
389 ! - apply similarity analysis on evS1 if needed
390 
391  IF ( filetypes2 == file_analytical .AND. &
392  similaritytypes2 /= 0 ) THEN
393  IF ( global%verbLevel/=verbose_none ) &
394  WRITE(stdout,'(/,A)') 'Entering RVAV_ComputeSimilarField-EVS2'
395 
396  CALL rvav_computesimilarfield( global, &
397  inodess1,jnodess1,knodess1, &
398  similaritytypes2, &
399  variableindexs1, &
400  globalrvav%evS1)
401 
402  IF ( global%verbLevel/=verbose_none ) &
403  WRITE(stdout,'(/,A)') 'Entering RVAV_ComputeSimilarField-EVS2'
404 
405  END IF ! fileTypeS2
406 
407 ! - extract Min Max values from evS1, evS2
408 
409  IF (global%verbLevel /= verbose_none) THEN
410  evs1min = +1.0e+30_rfreal
411  evs1max = -1.0e+30_rfreal
412  evs2min = +1.0e+30_rfreal
413  evs2max = -1.0e+30_rfreal
414 
415  DO k=1,knodess1
416  DO j=1,jnodess1
417  DO i=1,inodess1
418  evs1min = min(globalrvav%evS1(i,j,k), evs1min)
419  evs1max = max(globalrvav%evS1(i,j,k), evs1max)
420  ENDDO ! i
421  ENDDO ! j
422  ENDDO ! k
423 
424  DO k=1,knodess2
425  DO j=1,jnodess2
426  DO i=1,inodess2
427  evs2min = min(globalrvav%evS2(i,j,k), evs2min)
428  evs2max = max(globalrvav%evS2(i,j,k), evs2max)
429  ENDDO ! i
430  ENDDO ! j
431  ENDDO ! k
432 
433  WRITE(stdout,'(A,2E14.5)') 'MIN-MAX of EVS1',evs1min,evs1max
434  WRITE(stdout,'(A,2E14.5)') 'MIN-MAX of EVS2',evs2min,evs2max
435 
436  END IF ! verbLevel
437 
438 ! - perform operations according to input flag
439 
440  inodess1 = int(REAL((iends1-ibegs1)/ijumps1,kind=rfreal)) + 1
441  jnodess1 = int(REAL((jends1-jbegs1)/jjumps1,kind=rfreal)) + 1
442  knodess1 = int(REAL((kends1-kbegs1)/kjumps1,kind=rfreal)) + 1
443 
444  inodess2 = int(REAL((iends2-ibegs2)/ijumps2,kind=rfreal)) + 1
445  jnodess2 = int(REAL((jends2-jbegs2)/jjumps2,kind=rfreal)) + 1
446  knodess2 = int(REAL((kends2-kbegs2)/kjumps2,kind=rfreal)) + 1
447 
448  IF (global%verbLevel /= verbose_none) THEN
449  WRITE(stdout,'(/,A,3(I5,3X))') 'Stream1 iNodes,jNodes,kNodes = ', &
450  inodess1,jnodess1,knodess1
451  WRITE(stdout,'(/,A,3(I5,3X))') 'Stream2 iNodes,jNodes,kNodes = ', &
452  inodess2,jnodess2,knodess2
453  END IF ! verbLevel
454 
455  IF (rvavcompare%operationS1 == compute_errors_only) THEN
456  IF (inodess1 /= inodess2) THEN
457  WRITE(stdout,'(/,A,2(I5,3X))') &
458  'Non Matching Number of I-Nodes for Streams 1 and 2: ', &
459  inodess1,inodess2
460  CALL errorstop( global, err_previous_errors,__line__ )
461  ENDIF ! iNodes
462 
463  IF (jnodess1 /= jnodess2) THEN
464  WRITE(stdout,'(/,A,2(I5,3X))') &
465  'Non Matching Number of J-Nodes for Streams 1 and 2: ', &
466  jnodess1,jnodess2
467  CALL errorstop( global, err_previous_errors,__line__ )
468  ENDIF ! jNodes
469 
470  IF (knodess1 /= knodess2) THEN
471  WRITE(stdout,'(/,A,2(I5,3X))') &
472  'Non Matching Number of K-Nodes for Streams 1 and 2: ', &
473  knodess1,knodess2
474  CALL errorstop( global, err_previous_errors,__line__ )
475  ENDIF ! kNodes
476 
477  ENDIF ! operationS1
478 
479  IF (rvavcompare%operationS1 == compute_errors_only) THEN
480  CALL rvav_computeerror( global,icompare,inodess1,jnodess1,knodess1 )
481  ENDIF ! operationsS1
482 
483 ! IF (RVAVcompare%operationS1 == PLOT_ERRORS_ONLY) THEN
484 ! CALL RVAV_PlotResults( global, iCompare,iNodesS1,jNodesS1,kNodesS1 )
485 ! ENDIF ! operationsS1
486 
487 ! - Deallocate evS1 and evS2
488 
489  DEALLOCATE( globalrvav%evS1,stat=errorflag )
490  global%error = errorflag
491  IF( global%error /= 0 ) CALL errorstop( global,err_deallocate,__line__ )
492 
493  DEALLOCATE( globalrvav%evS2,stat=errorflag )
494  global%error = errorflag
495  IF( global%error /= 0 ) CALL errorstop( global,err_deallocate,__line__ )
496 
497  ENDDO ! iCompare
498 
499 ! finalize --------------------------------------------------------------------
500 
501  CALL deregisterfunction( global )
502 
503  WRITE(stdout,'(/,A)') 'RocVAV Finished.'
504 
505 #ifdef MPI
506  CALL mpi_finalize( global%mpierr )
507 #endif
508 
509 1000 FORMAT('Region ',i5,', grid level= ',i2,'.')
510 
511 END PROGRAM rocvav_post
512 
513 !******************************************************************************
514 !
515 ! RCS Revision history:
516 !
517 ! $Log: RVAV_Main.F90,v $
518 ! Revision 1.3 2008/12/06 08:45:08 mtcampbe
519 ! Updated license.
520 !
521 ! Revision 1.2 2008/11/19 22:18:19 mtcampbe
522 ! Added Illinois Open Source License/Copyright
523 !
524 ! Revision 1.1 2004/12/01 22:43:24 fnajjar
525 ! Initial revision after changing case
526 !
527 ! Revision 1.16 2003/11/20 16:40:41 mdbrandy
528 ! Backing out RocfluidMP changes from 11-17-03
529 !
530 ! Revision 1.12 2003/05/15 02:57:08 jblazek
531 ! Inlined index function.
532 !
533 ! Revision 1.11 2002/10/12 03:20:51 jblazek
534 ! Replaced [io]stat=global%error with local errorFlag for Rocflo.
535 !
536 ! Revision 1.10 2002/09/20 22:22:37 jblazek
537 ! Finalized integration into GenX.
538 !
539 ! Revision 1.9 2002/09/11 16:20:21 jblazek
540 ! Added directory path to input/output files (needed for GENX).
541 !
542 ! Revision 1.8 2002/09/10 00:01:45 f-najjar
543 ! Variable global moved into regions()
544 !
545 ! Revision 1.7 2002/08/16 21:33:48 jblazek
546 ! Changed interface to MixtureProperties.
547 !
548 ! Revision 1.6 2002/07/12 21:50:08 jblazek
549 ! Added tool to split single grid into multiple regions.
550 !
551 ! Revision 1.5 2002/06/19 14:40:14 f-najjar
552 ! Included verbLevel calls for cleanup
553 !
554 ! Revision 1.4 2002/06/18 03:18:20 f-najjar
555 ! Included RVAV_computeAnalyticalSolution
556 !
557 ! Revision 1.3 2002/06/17 17:02:07 f-najjar
558 ! Fix Calling sequence for ExtractVariables
559 !
560 ! Revision 1.2 2002/06/14 17:00:52 jblazek
561 ! Added version string.
562 !
563 ! Revision 1.1.1.1 2002/06/03 21:41:29 f-najjar
564 ! Initial Import of RocVaV
565 !
566 !******************************************************************************
567 
568 
569 
570 
571 
572 
573 
subroutine rvav_readfilestream2(regionsS1, regionsS2)
j indices k indices k
Definition: Indexing.h:6
subroutine rvav_computeerror(global, iCompare, iNodes, jNodes, kNodes)
program rocvav_post
Definition: RVAV_Main.F90:45
Vector_n max(const Array_n_const &v1, const Array_n_const &v2)
Definition: Vector_n.h:354
subroutine rvav_extractvariables(global, region, ibeg, iend, ijump, jbeg, jend, jjump, kbeg, kend, kjump, iCOff, ijCOff, variableIndex, fileType, indCp, indMol, ev)
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
subroutine rflo_readsolutionregion(iReg, regions)
subroutine rvav_readinputfile(global)
subroutine rvav_computesimilarfield(global, iNodes, jNodes, kNodes, similarityType, variableIndex, ev)
subroutine rflo_getnodeoffset(region, iLev, iNodeOffset, ijNodeOffset)
subroutine rflo_readgridregion(iReg, regions)
subroutine rflo_getdimensdummy(region, iLev, idcbeg, idcend, jdcbeg, jdcend, kdcbeg, kdcend)
subroutine rvav_plotresults(global, iCompare, iNodes, jNodes, kNodes)
subroutine rvav_readfilestream1(regionsS1)
subroutine buildversionstring(versionString)
subroutine rvav_computeanalyticalsolution(similarityType, regionsS1)
blockLoc i
Definition: read.cpp:79
subroutine rflo_getcelloffset(region, iLev, iCellOffset, ijCellOffset)
subroutine readinputfile(regions)
subroutine rflo_derivedinputvalues(regions)
Vector_n min(const Array_n_const &v1, const Array_n_const &v2)
Definition: Vector_n.h:346
j indices j
Definition: Indexing.h:6
subroutine rflo_getdimensdummynodes(region, iLev, idnbeg, idnend, jdnbeg, jdnend, kdnbeg, kdnend)
subroutine rflo_readregiontopology(global, regions)
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
subroutine grid(bp)
Definition: setup_py.f90:257
subroutine deregisterfunction(global)
Definition: ModError.F90:469
subroutine rflo_initinputvalues(regions)