Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
RFLO_InitFlowSolver.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: initialize all global variables and regions.
26 !
27 ! Description: none.
28 !
29 ! Input: casename = name of the case
30 ! verbLevel = verbosity level (VERBOSE_NONE/LOW/HIGH).
31 !
32 ! Output: global = global variables
33 ! regions = dimensions and initial values for all regions
34 !
35 ! Notes: none.
36 !
37 !******************************************************************************
38 !
39 ! $Id: RFLO_InitFlowSolver.F90,v 1.18 2009/08/12 04:15:58 mtcampbe Exp $
40 !
41 ! Copyright: (c) 2001 by the University of Illinois
42 !
43 !******************************************************************************
44 
45 #ifdef GENX
46 SUBROUTINE rflo_initflowsolver( globalGenx,initialTime,communicator, &
47  genxhandle,insurf,invol,obtain_attribute )
48 #else
49 SUBROUTINE rflo_initflowsolver( casename,verbLevel,global,regions )
50 #endif
51 
52  USE moddatatypes
53 #ifdef GENX
54  USE modrocstar, ONLY : t_globalgenx
56 #endif
57  USE modglobal, ONLY : t_global
58  USE moddatastruct, ONLY : t_region
71 
72 #ifdef STATS
75 #endif
76 #ifdef TURB
79 #endif
80 #ifdef RADI
82 #endif
83 #ifdef PERI
85 #endif
86 #ifdef SPEC
88 #endif
89 #ifdef PLAG
92 #endif
93 #ifdef PEUL
95 #endif
96 #ifdef INRT
98 #endif
99  USE moderror
100  USE modmpi
101  USE modparameters
102  IMPLICIT NONE
103 #ifdef GENX
104  include "roccomf90.h"
105 #endif
106 
107 ! ... parameters
108 #ifdef GENX
109  CHARACTER(*), INTENT(in) :: insurf, invol
110  DOUBLE PRECISION, INTENT(in) :: initialtime
111  INTEGER, INTENT(in) :: communicator, genxhandle, obtain_attribute
112 
113  TYPE(t_globalgenx), POINTER :: globalgenx
114 #else
115  CHARACTER(*) :: casename
116 
117  INTEGER :: verblevel
118 #endif
119  TYPE(t_global), POINTER :: global
120  TYPE(t_region), POINTER :: regions(:)
121 
122 ! ... local variables
123  CHARACTER(CHRLEN) :: msg, versionstring, headerstring, fname
124 
125  INTEGER :: headerwidth
126  INTEGER :: solver, error, margin, versionwidth, ireg, errorflag
127 
128  LOGICAL :: fileexists,dummylogical
129 
130  INTEGER :: dummy
131 
132 !******************************************************************************
133 ! initialize some global variables --------------------------------------------
134 
135 #ifdef GENX
136  global => globalgenx%global
137 
138  global%timeStamp = initialtime
139  global%currentTime = initialtime
140  global%currentIter = -1 ! no iteration
141 #else
142  global%winName = ''
143  global%casename = casename
144  global%verbLevel = verblevel
145  global%inDir = './'
146  global%outDir = './'
147  global%currentTime = -1._rfreal ! no physical time set
148  global%currentIter = -1 ! no iteration
149 #endif
150 
151  global%nFunTree = 0
152  CALL registerfunction( global,'RFLO_InitFlowSolver',&
153  'RFLO_InitFlowSolver.F90' )
154 
155  global%nProcAlloc = 1
156  global%myProcid = masterproc ! default process number (if not MPI)
157  global%mpierr = err_none
158  global%error = err_none
159 
160  global%pi = 4._rfreal*atan(1._rfreal)
161  global%rad = global%pi/180._rfreal
162  global%calcCellCtr = .false.
163  global%calcFaceCtr = .false.
164 
165 ! global grid motion
166 
167  global%moveGridNbour = 6
168 
169 #ifdef GENX
170 ! read GenX control file ------------------------------------------------------
171 
172  fname = trim(global%winName)//'/RocfloControl.txt'
173 
174  OPEN(if_control,file=fname,form='formatted',status='old',iostat=errorflag)
175  global%error = errorflag
176  IF (global%error /= 0) &
177  CALL errorstop( global,err_file_open,__line__,'File: '//trim(fname) )
178 
179  READ(if_control,'(A)',iostat=errorflag) global%casename
180  global%error = errorflag
181  IF (global%error /= 0) &
182  CALL errorstop( global,err_file_read,__line__,'File: '//trim(fname) )
183 
184  READ(if_control,*,iostat=errorflag) global%verbLevel
185  global%error = errorflag
186  IF (global%error /= 0) global%verbLevel = 1
187 
188  READ(if_control,'(A)',iostat=errorflag) global%inDir
189  global%error = errorflag
190  IF (global%error /= 0) THEN
191  global%inDir = trim(global%winName)//'/'
192  ELSE
193  IF (global%inDir(len_trim(global%inDir):len_trim(global%inDir)) /= '/') &
194  global%inDir = trim(global%inDir)//'/'
195  ENDIF
196 
197  READ(if_control,'(A)',iostat=errorflag) global%outDir
198  global%error = errorflag
199  IF (global%error /= 0) THEN
200  global%outDir = trim(global%winName)//'/'
201  ELSE
202  IF (global%outDir(len_trim(global%outDir):len_trim(global%outDir)) /= '/') &
203  global%outDir = trim(global%outDir)//'/'
204  ENDIF
205  global%error = err_none
206  CLOSE(if_control)
207 #endif
208 
209 ! start up solver and MPI -----------------------------------------------------
210 
211 #ifdef MPI
212 #ifndef GENX
213  global%mpiComm = mpi_comm_world
214  CALL mpi_init( global%mpierr )
215  IF (global%mpierr /= 0) CALL errorstop( global,err_mpi_trouble,__line__ )
216  global%mpiTagMax = 32768
217 #else
218  global%mpiComm = communicator
219 #endif
220  dummy = 0
221  dummylogical = .true.
222  CALL mpi_attr_get(mpi_comm_world,mpi_tag_ub,global%mpiTagMax,dummylogical,dummy)
223 ! IF (global%myProcid==MASTERPROC .AND. global%verbLevel/=VERBOSE_NONE) THEN
224 ! WRITE(STDOUT,*) SOLVER_NAME//' Maximum MPI Tag: ',global%mpiTagMax
225 ! ENDIF
226  CALL mpi_comm_size( global%mpiComm,global%nProcAlloc,global%mpierr )
227  IF (global%mpierr /= 0) CALL errorstop( global,err_mpi_trouble,__line__ )
228 
229  CALL mpi_comm_rank( global%mpiComm,global%myProcid,global%mpierr )
230  IF (global%mpierr /= 0) CALL errorstop( global,err_mpi_trouble,__line__ )
231 #endif
232 
233  IF (global%myProcid==masterproc .AND. global%verbLevel/=verbose_none) THEN
234  CALL buildversionstring( versionstring )
235  headerwidth = 53
236  headerstring = ' '
237  versionwidth = len_trim(versionstring)
238  margin = (headerwidth-versionwidth)/2
239  headerstring(margin+1:margin+versionwidth) = versionstring(1:versionwidth)
240  headerstring(1:1) = '*'
241  headerstring(headerwidth:headerwidth) = '*'
242 
243  WRITE(stdout,'(/,A)') solver_name//' *****************************************************'
244  WRITE(stdout, '(A)') solver_name//' * *'
245  WRITE(stdout, '(A)') solver_name//' * RocfloMP *'
246  WRITE(stdout, '(A)') solver_name//' * *'
247 ! WRITE(STDOUT, '(A)') SOLVER_NAME//' '//TRIM(headerString)
248  WRITE(stdout, '(A)') solver_name//' * Copyright (C) 2015 Illinois Rocstar LLC. *'
249  WRITE(stdout, '(A)') solver_name//' * *'
250  WRITE(stdout,'(A,/)') solver_name//' *****************************************************'
251  ENDIF
252 
253 ! write out messages from conditional compilation -----------------------------
254 
255  IF (global%myProcid==masterproc .AND. global%verbLevel/=verbose_low) THEN
256  headerwidth = 32
257  headerstring = ' '
258 
259 #ifdef CHECK_GRAD
260  WRITE(stdout,'(A)' ) solver_name//' -----------------------------------------------'
261  WRITE(stdout,'(A)' ) solver_name//' WARNING '
262  WRITE(stdout,'(A)' ) solver_name//' Compiled to check for gradients of u,v,w and T '
263  WRITE(stdout,'(A,/)') solver_name//' -----------------------------------------------'
264 #endif
265 
266 #ifdef STATS
267  CALL statbuildversionstring( versionstring )
268  versionwidth = len_trim(versionstring)
269  margin = (headerwidth-versionwidth)/2
270  headerstring(margin+1:margin+versionwidth) = versionstring(1:versionwidth)
271  WRITE(stdout,'(A)' ) solver_name//' --------------------------------'
272  WRITE(stdout,'(A)' ) solver_name//' Compiled with Statistics module '
273  WRITE(stdout,'(A)' ) solver_name//' '//trim(headerstring)
274  WRITE(stdout,'(A,/)') solver_name//' --------------------------------'
275 #endif
276 
277 #ifdef PLAG
278  CALL plag_buildversionstring( versionstring )
279  versionwidth = len_trim(versionstring)
280  margin = (headerwidth-versionwidth)/2
281  headerstring(margin+1:margin+versionwidth) = versionstring(1:versionwidth)
282  WRITE(stdout,'(A)' ) solver_name//' --------------------------------'
283  WRITE(stdout,'(A)' ) solver_name//' Compiled with Lagrangian module '
284  WRITE(stdout,'(A)' ) solver_name//' '//trim(headerstring)
285  WRITE(stdout,'(A,/)') solver_name//' --------------------------------'
286 #endif
287 
288 #ifdef PEUL
289  CALL peul_buildversionstring( versionstring )
290  versionwidth = len_trim(versionstring)
291  margin = (headerwidth-versionwidth)/2
292  headerstring(margin+1:margin+versionwidth) = versionstring(1:versionwidth)
293  WRITE(stdout,'(A)' ) solver_name//' --------------------------------'
294  WRITE(stdout,'(A)' ) solver_name//' Compiled with Eulerian module '
295  WRITE(stdout,'(A)' ) solver_name//' '//trim(headerstring)
296  WRITE(stdout,'(A,/)') solver_name//' --------------------------------'
297 #endif
298 
299 #ifdef RADI
300  CALL radi_buildversionstring( versionstring )
301  versionwidth = len_trim(versionstring)
302  margin = (headerwidth-versionwidth)/2
303  headerstring(margin+1:margin+versionwidth) = versionstring(1:versionwidth)
304  WRITE(stdout,'(A)' ) solver_name//' --------------------------------'
305  WRITE(stdout,'(A)' ) solver_name//' Compiled with Radiation module '
306  WRITE(stdout,'(A)' ) solver_name//' '//trim(headerstring)
307  WRITE(stdout,'(A,/)') solver_name//' --------------------------------'
308 #endif
309 
310 #ifdef SPEC
311  CALL spec_buildversionstring( versionstring )
312  versionwidth = len_trim(versionstring)
313  margin = (headerwidth-versionwidth)/2
314  headerstring(margin+1:margin+versionwidth) = versionstring(1:versionwidth)
315  WRITE(stdout,'(A)' ) solver_name//' --------------------------------'
316  WRITE(stdout,'(A)' ) solver_name//' Compiled with Species module '
317  WRITE(stdout,'(A)' ) solver_name//' '//trim(headerstring)
318  WRITE(stdout,'(A,/)') solver_name//' --------------------------------'
319 #endif
320 
321 #ifdef TURB
322  CALL turb_buildversionstring( versionstring )
323  versionwidth = len_trim(versionstring)
324  margin = (headerwidth-versionwidth)/2
325  headerstring(margin+1:margin+versionwidth) = versionstring(1:versionwidth)
326  WRITE(stdout,'(A)' ) solver_name//' --------------------------------'
327  WRITE(stdout,'(A)' ) solver_name//' Compiled with Turbulence module '
328  WRITE(stdout,'(A)' ) solver_name//' '//trim(headerstring)
329  WRITE(stdout,'(A,/)') solver_name//' --------------------------------'
330 #endif
331 
332 #ifdef INRT
333  CALL inrt_buildversionstring( versionstring )
334  versionwidth = len_trim(versionstring)
335  margin = (headerwidth-versionwidth)/2
336  headerstring(margin+1:margin+versionwidth) = versionstring(1:versionwidth)
337  WRITE(stdout,'(A)' ) solver_name//' --------------------------------'
338  WRITE(stdout,'(A)' ) solver_name//' Compiled with Interaction module'
339  WRITE(stdout,'(A)' ) solver_name//' '//trim(headerstring)
340  WRITE(stdout,'(A,/)') solver_name//' --------------------------------'
341 #endif
342 
343 #ifdef PERI
344  CALL peri_buildversionstring( versionstring )
345  versionwidth = len_trim(versionstring)
346  margin = (headerwidth-versionwidth)/2
347  headerstring(margin+1:margin+versionwidth) = versionstring(1:versionwidth)
348  WRITE(stdout,'(A)' ) solver_name//' --------------------------------'
349  WRITE(stdout,'(A)' ) solver_name//' Compiled with Periodic module '
350  WRITE(stdout,'(A)' ) solver_name//' '//trim(headerstring)
351  WRITE(stdout,'(A,/)') solver_name//' --------------------------------'
352 #endif
353  ENDIF
354 
355 ! check for stop file - delete it if there ------------------------------------
356 
357  INQUIRE(file="STOP",exist=fileexists)
358  IF (fileexists) THEN
359 #ifdef GENX
360  errorflag = com_call_system( "rm -f STOP")
361  global%error = errorflag
362  IF (global%error /= 0) &
363  CALL errorstop( global,err_system_command,__line__,'rm -f STOP' )
364 #else
365  CALL system( 'rm -f STOP' )
366 #endif
367  ENDIF
368 
369 ! read region topology --------------------------------------------------------
370 
371  IF (global%myProcid==masterproc .AND. global%verbLevel>=verbose_low) THEN
372  WRITE(stdout,'(A,A,A,/)') solver_name//' Case <', &
373  trim(global%casename),'> running'
374  ENDIF
375  IF (global%myProcid==masterproc .AND. global%verbLevel>=verbose_high) THEN
376  WRITE(stdout,'(A)') solver_name//' Reading region topology ...'
377  ENDIF
378 
379 #ifdef GENX
380  CALL rflo_readregiontopology( global,regions )
381  globalgenx%regions => regions
382 #else
383  CALL rflo_readregiontopology( global,regions )
384 #endif
385 
386 #ifdef MPI
387  global%nProcAlloc = min(global%nProcAlloc,global%nRegions)
388 #endif
389 
390 ! find source patches on adjacent regions
391 
392  CALL rflo_findsourcepatches( regions )
393 
394 ! get user parameters ---------------------------------------------------------
395 
396  IF (global%myProcid==masterproc .AND. global%verbLevel>=verbose_low) &
397  WRITE(stdout,'(A)') solver_name//' Reading user input ...'
398 
399  CALL rflo_getuserinput( regions )
400 
401 ! initialize random number generator ------------------------------------------
402 
403  CALL rflo_randominit( regions )
404 
405 ! read restart info -----------------------------------------------------------
406 
407 #ifndef GENX
408  CALL rflo_readrestartinfo( global )
409 #endif
410 
411 ! find out solver type (Euler/Navier-Stokes) for GenX -------------------------
412 
413 #ifdef GENX
414  solver = 0
415  DO ireg=1,global%nRegions
416  IF (regions(ireg)%mixtInput%flowModel == flow_navst) solver = 1
417  ENDDO
418 #endif
419 
420 ! check if BCs defined for all boundary faces ---------------------------------
421 
422 #ifdef MPI
423  CALL mpi_barrier( global%mpiComm,global%mpierr )
424 #endif
425  IF (global%myProcid==masterproc .AND. global%verbLevel>=verbose_high) &
426  WRITE(stdout,'(A)') solver_name//' Checking BCs of regions ...'
427 
428  CALL rflo_checkregionfaces( regions )
429 
430 ! check if enough cells to provide data to adjacent region
431 
432  CALL rflo_checkminimumcells( regions )
433 
434 ! find source regions for edge & corner cells ---------------------------------
435 #ifdef MPI
436  CALL mpi_barrier( global%mpiComm,global%mpierr )
437 #endif
438 
439  IF (global%myProcid==masterproc .AND. global%verbLevel>=verbose_high) &
440  WRITE(stdout,'(A)') solver_name// &
441  ' Searching source regions for edge & corner cells ...'
442 
443  CALL rflo_findsourceregions( regions )
444 
445 ! allocate memory -------------------------------------------------------------
446 
447 
448 #ifdef MPI
449  CALL mpi_barrier( global%mpiComm,global%mpierr )
450 #endif
451  IF (global%myProcid==masterproc .AND. global%verbLevel>=verbose_high) &
452  WRITE(stdout,'(A)') solver_name//' Allocating memory ...'
453 
454  CALL rflo_domemoryallocation( regions )
455 
456 ! write degenerate edges & corners if exist, and mark them --------------------
457 
458 #ifdef MPI
459  CALL mpi_barrier( global%mpiComm,global%mpierr )
460 #endif
461  IF (global%degenrtEc .AND. global%myProcid==masterproc) THEN
462  IF (global%verbLevel>=verbose_high) &
463  WRITE(stdout,'(A)') solver_name// &
464  ' Write degenerated edges and corners into file ...'
465 
466  CALL rflo_writedegeneratec( regions )
467  ENDIF
468  CALL rflo_markdegeneratvert( regions )
469 
470 #ifdef STATS
471 ! statistics mapping (must be done before initGenxInterface) ------------------
472 
473 #ifdef MPI
474  CALL mpi_barrier( global%mpiComm,global%mpierr )
475 #endif
476  IF (global%flowType == flow_unsteady .AND. global%doStat==active) THEN
477  IF (global%myProcid==masterproc .AND. global%verbLevel>=verbose_high) &
478  WRITE(stdout,'(A)') solver_name// &
479  ' Doing stat mapping ...'
480  CALL statmapping( global )
481  ENDIF
482 #endif
483 
484 ! get initial grid data -------------------------------------------------------
485 
486 #ifdef MPI
487  CALL mpi_barrier( global%mpiComm,global%mpierr )
488 #endif
489  IF (global%myProcid==masterproc .AND. global%verbLevel>=verbose_high) &
490  WRITE(stdout,'(A)') solver_name// &
491  ' Reading grid file, exchanging geometry ...'
492 
493  CALL rflo_getgeometry( regions,1 )
494 
495 #ifdef GENX
496 ! initial grid procedures -----------------------------------------------------
497 
498 #ifdef MPI
499  CALL mpi_barrier( global%mpiComm,global%mpierr )
500 #endif
501  IF (global%myProcid==masterproc .AND. global%verbLevel>=verbose_high) &
502  WRITE(stdout,'(A)') solver_name// &
503  ' Initializing Grid Procedures ...'
504  CALL rflo_initgridprocedures( regions )
505 
506 ! init. interface; restore grid and flow solution if restart ------------------
507 
508 #ifdef MPI
509  CALL mpi_barrier( global%mpiComm,global%mpierr )
510 #endif
511  IF (global%myProcid==masterproc .AND. global%verbLevel>=verbose_high) &
512  WRITE(stdout,'(A)') solver_name//' Preparing GenX interface ...'
513 
514  CALL rflo_initgenxinterface( regions,genxhandle,solver,insurf,invol, &
516 
517 ! exchange geometry between regions -------------------------------------------
518 
519 #ifdef MPI
520  CALL mpi_barrier( global%mpiComm,global%mpierr )
521 #endif
522  IF (global%myProcid==masterproc .AND. global%verbLevel>=verbose_high) &
523  WRITE(stdout,'(A)') solver_name// &
524  ' Getting geometry ...'
525  CALL rflo_getgeometry( regions,0 )
526 #endif
527 
528 ! calculate & check grid metrics ----------------------------------------------
529 
530 #ifdef MPI
531  CALL mpi_barrier( global%mpiComm,global%mpierr )
532 #endif
533  IF (global%myProcid==masterproc .AND. global%verbLevel>=verbose_high) &
534  WRITE(stdout,'(A)') solver_name//' Calculating & checking grid metrics ...'
535 
536  CALL rflo_calcgridmetrics( regions )
537 
538 ! calculate metrics of MP modules
539 
540 #ifdef TURB
541 #ifdef MPI
542  CALL mpi_barrier( global%mpiComm,global%mpierr )
543 #endif
544  IF (global%myProcid==masterproc .AND. global%verbLevel>=verbose_high) &
545  WRITE(stdout,'(A)') solver_name//' Calculating & checking turbulence metrics ...'
546  IF (global%turbActive) CALL turb_calcmetrics( regions, 1 )
547 #endif
548 
549 #ifdef PLAG
550 #ifdef MPI
551  CALL mpi_barrier( global%mpiComm,global%mpierr )
552 #endif
553  IF (global%myProcid==masterproc .AND. global%verbLevel>=verbose_high) &
554  WRITE(stdout,'(A)') solver_name//' Setting metrics for lagrangian particles ...'
555  CALL plag_rflo_setmetrics( regions )
556 #endif
557 
558 ! read flow solution ----------------------------------------------------------
559 
560 #ifdef MPI
561  CALL mpi_barrier( global%mpiComm,global%mpierr )
562 #endif
563  IF (global%myProcid==masterproc .AND. global%verbLevel>=verbose_high) &
564  WRITE(stdout,'(A)') solver_name//' Reading flow solution ...'
565 
566  CALL rflo_getflowsolution( regions )
567 
568 ! find patches for thrust integration -----------------------------------------
569 
570 #ifdef MPI
571  CALL mpi_barrier( global%mpiComm,global%mpierr )
572 #endif
573  IF (global%thrustType /= thrust_none) THEN
574  IF (global%myProcid==masterproc .AND. global%verbLevel>=verbose_high) &
575  WRITE(stdout,'(A)') solver_name//' Searching for thrust patches ...'
576 #ifdef MPI
577  CALL mpi_barrier( global%mpiComm,global%mpierr )
578 #endif
579  DO ireg=1,global%nRegions
580  IF (regions(ireg)%procid==global%myProcid .AND. & ! region active and
581  regions(ireg)%active==active) THEN ! on my processor
582  CALL rflo_findthrustpatches( regions(ireg),ireg )
583  ENDIF
584  ENDDO
585  ENDIF
586 
587 #ifdef STATS
588 ! statistics initialization ---------------------------------------------------
589 
590 #ifdef MPI
591  CALL mpi_barrier( global%mpiComm,global%mpierr )
592 #endif
593  IF (global%myProcid==masterproc .AND. global%verbLevel>=verbose_high) &
594  WRITE(stdout,'(A)') solver_name//' Initializing statistics ...'
595  CALL initstatistics( regions )
596 #endif
597 
598 ! open files for convergence history and time evolution data ------------------
599 
600 #ifdef MPI
601  CALL mpi_barrier( global%mpiComm,global%mpierr )
602 #endif
603  IF (global%myProcid==masterproc .AND. global%verbLevel>=verbose_high) &
604  WRITE(stdout,'(A)') solver_name//' Opening native output files ...'
605  CALL rflo_openconverfile( global )
606 
607  CALL rflo_openprobefile( regions )
608 
609  IF (global%thrustType /= thrust_none) &
610  CALL rflo_openthrustfile( global )
611 
612  IF (global%aeroCoeffs == active .AND. global%myProcid==masterproc) &
613  CALL rflo_openforcemomcofile( global )
614 #ifndef GENX
615  IF (global%myProcid==masterproc .AND. global%verbLevel/=verbose_none) &
616  WRITE(stdout,'(//,A,/,A,/,A)') solver_name//' Time stepping', &
617  solver_name//' =============', &
618  solver_name
619 
620 ! write header for convergence history
621 
622  IF (global%myProcid==masterproc .AND. global%verbLevel/=verbose_none) THEN
623  WRITE(stdout,'(A)') solver_name
624  IF (global%flowType == flow_steady) &
625  WRITE(stdout,1010) solver_name,solver_name
626  IF (global%flowType == flow_unsteady) &
627  WRITE(stdout,1015) solver_name,solver_name
628  ENDIF
629 #endif
630 #ifdef GENX
631 ! send initial data to GenX ---------------------------------------------------
632 
633 #ifdef MPI
634  CALL mpi_barrier( global%mpiComm,global%mpierr )
635 #endif
636  IF (global%myProcid==masterproc .AND. global%verbLevel>=verbose_high) &
637  WRITE(stdout,'(A)') solver_name//' Sending boundary values to Rocstar ...'
638  DO ireg=1,global%nRegions
639  IF (regions(ireg)%procid==global%myProcid .AND. & ! region active and
640  regions(ireg)%active==active) THEN ! on my processor
641  CALL rflo_sendboundaryvalues( regions(ireg),global%timeStamp<=0)
642  ENDIF ! region on this processor and active
643  ENDDO ! iReg
644 #endif
645 
646 #ifdef MPI
647  CALL mpi_barrier( global%mpiComm,global%mpierr )
648 #endif
649  IF (global%myProcid==masterproc .AND. global%verbLevel>=verbose_high) &
650  WRITE(stdout,'(A)') solver_name//' All processors initialized ...'
651 ! finalize --------------------------------------------------------------------
652 
653  CALL deregisterfunction( global )
654 
655 ! formats
656 
657 1010 FORMAT(a,' iter',4x,'res-norm',5x,'force-x',6x,'force-y',6x,'force-z', &
658  6x,'mass-in',6x,'mass-out',/,a,1x,84('-'))
659 1015 FORMAT(a,' time',10x,'delta-t',6x,'force-x',6x,'force-y',6x,'force-z', &
660  6x,'mass-in',6x,'mass-out'/,a,1x,90('-'))
661 
662 END SUBROUTINE rflo_initflowsolver
663 
664 !******************************************************************************
665 !
666 ! RCS Revision history:
667 !
668 ! $Log: RFLO_InitFlowSolver.F90,v $
669 ! Revision 1.18 2009/08/12 04:15:58 mtcampbe
670 ! Major update, bugfix from Abe development, more propagation compatibility,
671 ! some Rocstar IO changes, Ju's temporary clipping fix for turbulence. A bug
672 ! fix for initialization IO.
673 !
674 ! Revision 1.17 2009/03/02 00:19:35 mtcampbe
675 ! Added some ifdefs around Rocflo to disable particle injection on INFLOW
676 ! boundaries and added some checks around MPI tags utilizing a new global
677 ! data item, global%mpiTagMax.
678 !
679 ! Revision 1.16 2008/12/06 08:44:27 mtcampbe
680 ! Updated license.
681 !
682 ! Revision 1.15 2008/11/19 22:17:38 mtcampbe
683 ! Added Illinois Open Source License/Copyright
684 !
685 ! Revision 1.14 2006/03/25 01:14:30 wasistho
686 ! open forceMomCoeff file only by masterproc
687 !
688 ! Revision 1.13 2006/03/24 23:30:54 wasistho
689 ! added RFLO_OpenForceMomCoFile
690 !
691 ! Revision 1.12 2006/03/04 04:29:08 wasistho
692 ! moved calcGridMetrics to a rocflo module
693 !
694 ! Revision 1.11 2006/02/01 20:01:59 wasistho
695 ! added ReadRestartInfo
696 !
697 ! Revision 1.10 2005/11/11 07:19:52 wasistho
698 ! added RFLO_MarkDegeneratVert
699 !
700 ! Revision 1.9 2005/10/20 06:50:25 wasistho
701 ! initialize calcFaceCtr
702 !
703 ! Revision 1.8 2005/06/28 08:51:22 rfiedler
704 ! Remove local currentTime; use timeStamp in place of currentTime to open probes.
705 !
706 ! Revision 1.7 2005/06/23 01:38:25 wasistho
707 ! initialize global%moveGridNbour to 6
708 !
709 ! Revision 1.6 2005/05/28 21:24:43 wasistho
710 ! move second getGeometry within ifdef GENX
711 !
712 ! Revision 1.5 2005/05/28 08:09:04 wasistho
713 ! activate RFLO_InitGridProcedures
714 !
715 ! Revision 1.4 2005/05/27 08:06:16 wasistho
716 ! allow genx read initial grid
717 !
718 ! Revision 1.3 2004/12/28 20:27:22 wasistho
719 ! moved statistics routines into module ModStatsRoutines
720 !
721 ! Revision 1.2 2004/12/01 00:20:58 wasistho
722 ! added phys. modules version strings
723 !
724 ! Revision 1.1 2004/11/29 20:51:39 wasistho
725 ! lower to upper case
726 !
727 ! Revision 1.44 2004/11/29 17:15:46 wasistho
728 ! use ModInterfacesStatistics
729 !
730 ! Revision 1.43 2004/08/21 00:32:59 wasistho
731 ! added write file degenerated edge/corners
732 !
733 ! Revision 1.42 2004/07/23 23:26:47 wasistho
734 ! separate system command btw genx and standalone
735 !
736 ! Revision 1.41 2004/07/06 23:24:00 jiao
737 ! Jiao: Changed to call RFLO_SendBoundaryValues only at time 0.
738 !
739 ! Revision 1.40 2004/06/29 23:57:17 wasistho
740 ! migrated to Roccom-3
741 !
742 ! Revision 1.39 2004/06/07 23:09:35 wasistho
743 ! moved statistics mapping from initStatistics to before initGenxInterfaces
744 !
745 ! Revision 1.38 2004/02/04 22:29:43 wasistho
746 ! add integer argument isInit to TURB_calcMetrics
747 !
748 ! Revision 1.37 2003/12/07 04:52:21 jiao
749 ! Changed the call to RFLO_ReadRegionTopology to work with PGI compilers.
750 !
751 ! Revision 1.36 2003/11/21 22:35:51 fnajjar
752 ! Update Random Number Generator
753 !
754 ! Revision 1.35 2003/11/20 16:40:39 mdbrandy
755 ! Backing out RocfluidMP changes from 11-17-03
756 !
757 ! Revision 1.31 2003/11/12 21:21:06 fnajjar
758 ! Added Corner-Edge cells routine to communicate metrics for PLAG
759 !
760 ! Revision 1.30 2003/10/03 20:18:43 wasistho
761 ! initial installation of turbModel SA and DES
762 !
763 ! Revision 1.29 2003/10/01 23:52:10 jblazek
764 ! Corrected bug in moving noslip wall BC and grid speeds.
765 !
766 ! Revision 1.28 2003/06/02 17:12:01 jblazek
767 ! Added computation of thrust.
768 !
769 ! Revision 1.27 2003/05/15 02:57:04 jblazek
770 ! Inlined index function.
771 !
772 ! Revision 1.26 2003/04/15 20:57:53 jiao
773 ! Jiri: Added close statement for the genx-control file.
774 !
775 ! Revision 1.25 2003/03/04 22:12:34 jferry
776 ! Initial import of Rocinteract
777 !
778 ! Revision 1.24 2003/02/17 19:31:10 jferry
779 ! Implemented portable random number generator ModRandom
780 !
781 ! Revision 1.23 2003/02/14 22:32:37 jblazek
782 ! Finished implementation of corener and edge cells.
783 !
784 ! Revision 1.22 2003/02/03 19:20:47 jblazek
785 ! Added treatment of edge and corner cells for one processor.
786 !
787 ! Revision 1.21 2002/10/16 18:30:38 jblazek
788 ! Within GenX, BC data at t=0 are updated in FlowSolver before calling
789 ! the time-stepping routine.
790 !
791 ! Revision 1.20 2002/10/12 03:20:50 jblazek
792 ! Replaced [io]stat=global%error with local errorFlag for Rocflo.
793 !
794 ! Revision 1.19 2002/10/02 22:21:59 jiao
795 ! Debugged GenX restart.
796 !
797 ! Revision 1.18 2002/09/27 22:42:41 jferry
798 ! removed PFEU reference
799 !
800 ! Revision 1.17 2002/09/20 22:22:36 jblazek
801 ! Finalized integration into GenX.
802 !
803 ! Revision 1.16 2002/09/05 17:40:21 jblazek
804 ! Variable global moved into regions().
805 !
806 ! Revision 1.15 2002/07/24 17:30:06 wasistho
807 ! Added Rocturb header
808 !
809 ! Revision 1.14 2002/07/16 21:34:37 jblazek
810 ! Prefixed screen output with SOLVER_NAME.
811 !
812 ! Revision 1.13 2002/06/22 01:13:38 jblazek
813 ! Modified interfaces to BC routines.
814 !
815 ! Revision 1.12 2002/06/18 00:34:32 wasistho
816 ! Added prefix SOLVER NAME to satistics STDOutput
817 !
818 ! Revision 1.11 2002/06/17 16:09:17 wasistho
819 ! Added STATS compilation message
820 !
821 ! Revision 1.10 2002/06/14 21:38:45 wasistho
822 ! Added time avg statistics
823 !
824 ! Revision 1.9 2002/06/13 23:06:20 jblazek
825 ! Added version string.
826 !
827 ! Revision 1.8 2002/06/07 16:40:37 jblazek
828 ! Grid & solution for all regions in one file.
829 !
830 ! Revision 1.7 2002/04/12 17:36:23 jblazek
831 ! Added timer.
832 !
833 ! Revision 1.6 2002/04/03 02:28:52 jblazek
834 ! Added x,y,z location to probe file header.
835 !
836 ! Revision 1.5 2002/04/01 19:36:08 jblazek
837 ! Added routine to clear send requests.
838 !
839 ! Revision 1.4 2002/03/30 00:50:49 jblazek
840 ! Cleaned up with flint.
841 !
842 ! Revision 1.3 2002/03/18 23:11:33 jblazek
843 ! Finished multiblock and MPI.
844 !
845 ! Revision 1.2 2002/02/27 18:38:20 jblazek
846 ! Changed extrapol. to dummy cells at injection boundaries and slip walls.
847 !
848 ! Revision 1.1 2002/02/25 22:36:53 jblazek
849 ! Simplified solver initialization routine.
850 !
851 !******************************************************************************
852 
853 
854 
855 
856 
857 
858 
subroutine, public statbuildversionstring(versionString)
subroutine turb_buildversionstring(versionString)
subroutine peul_buildversionstring(versionString)
subroutine rflo_openthrustfile(global)
subroutine plag_rflo_setmetrics(regions)
subroutine, public initstatistics(regions)
subroutine, public rflo_markdegeneratvert(regions)
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
int status() const
Obtain the status of the attribute.
Definition: Attribute.h:240
subroutine inrt_buildversionstring(versionString)
subroutine radi_buildversionstring(versionString)
subroutine peri_buildversionstring(versionString)
subroutine rflo_getflowsolution(regions)
MPI_Comm communicator() const
Definition: Function.h:119
subroutine rflo_openconverfile(global)
subroutine buildversionstring(versionString)
subroutine, public statmapping(global)
void int int REAL * x
Definition: read.cpp:74
subroutine turb_calcmetrics(regions, isInit)
subroutine spec_buildversionstring(versionString)
subroutine rflo_initgridprocedures(regions)
**********************************************************************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_checkminimumcells(regions)
subroutine rflo_sendboundaryvalues(region, initialize)
subroutine, public rflo_openforcemomcofile(global)
subroutine, public rflo_readrestartinfo(global)
subroutine rflo_initflowsolver(casename, verbLevel, global, regions)
subroutine rflo_openprobefile(regions)
subroutine rflo_randominit(regions)
subroutine rflo_findsourceregions(regions)
subroutine rflo_findthrustpatches(region, iReg)
Vector_n min(const Array_n_const &v1, const Array_n_const &v2)
Definition: Vector_n.h:346
subroutine rflo_findsourcepatches(regions)
void obtain_attribute(const COM::Attribute *attribute_in, COM::Attribute *user_attribute, int *pane_id=NULL)
Fill the destination (second) attribute from files using the data corresponding to the source (first)...
Definition: Rocin.C:2431
subroutine rflo_readregiontopology(global, regions)
subroutine rflo_getgeometry(regions, iread)
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
subroutine, public rflo_writedegeneratec(regions)
subroutine, public rflo_calcgridmetrics(regions)
subroutine rflo_getuserinput(regions)
subroutine deregisterfunction(global)
Definition: ModError.F90:469
subroutine rflo_initgenxinterface(regions, handle, solver, inSurf, inVolPlag, obtain_attribute)
subroutine rflo_checkregionfaces(regions)
subroutine plag_buildversionstring(versionString)
RT a() const
Definition: Line_2.h:140
subroutine rflo_domemoryallocation(regions)