Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
RFLO_TimeStepping.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: integrate the governing equations in time;
26 ! move/regenerate the grid.
27 !
28 ! Description: none.
29 !
30 ! Input: dTimeSystem = total solution time (unsteady flow)
31 ! dIterSystem = total number of iterations (steady flow)
32 ! regions = data for all grid regions
33 !
34 ! Output: regions = flow variables and grid for all grid regions.
35 !
36 ! Notes: none.
37 !
38 !******************************************************************************
39 !
40 ! $Id: RFLO_TimeStepping.F90,v 1.25 2009/08/27 14:04:52 mtcampbe Exp $
41 !
42 ! Copyright: (c) 2001 by the University of Illinois
43 !
44 !******************************************************************************
45 
46 SUBROUTINE rflo_timestepping( dTimeSystem,dIterSystem,regions )
47 
48  USE moddatatypes
49  USE moddatastruct, ONLY : t_region
50  USE modglobal, ONLY : t_global
68 #ifdef PLAG
70 #endif
71 #ifdef PEUL
73 #endif
74 #ifdef RADI
76 #endif
77 #ifdef SPEC
78  USE modinterfacesspecies, ONLY : spec_writesolution
79 #endif
80 #ifdef TURB
83 #endif
84 #ifdef PERI
85  USE peri_modhybriddes, ONLY : peri_comeancorrection
86 #endif
87 #ifdef STATS
89 #endif
90  USE moderror
91  USE modmpi
92  USE modparameters
93  IMPLICIT NONE
94 
95 ! ... parameters
96  INTEGER :: ditersystem
97 
98  REAL(RFREAL) :: dtimesystem
99 
100  TYPE(t_region), POINTER :: regions(:)
101 
102 ! ... loop variables
103  INTEGER :: ireg
104 
105 ! ... local variables
106  INTEGER, SAVE :: iter = 0
107 
108  LOGICAL :: stopexists, finished, ftermnew, residfterm, &
109  doprint, dowrite, doprobe, dothrust, movegrid
110 
111  REAL(RFREAL), SAVE :: timeprint=0._rfreal, timewrite =0._rfreal, &
112  timeprobe=0._rfreal, timethrust=0._rfreal
113  REAL(RFREAL) :: time, totalmass
114 
115  TYPE(t_global), POINTER :: global
116 
117  INTEGER :: original_format
118 
119 !******************************************************************************
120 
121  global => regions(1)%global
122 
123  CALL registerfunction( global,'RFLO_TimeStepping',&
124  'RFLO_TimeStepping.F90' )
125 
126 ! initialize ------------------------------------------------------------------
127 
128 #ifdef GENX
129  IF (global%predCorrIter) THEN
130  iter = 0
131  global%predCorrIter = .false.
132  ENDIF
133 ! write header for convergence history
134 
135  IF (global%myProcid==masterproc .AND. global%verbLevel/=verbose_none) THEN
136  WRITE(stdout,'(A)') solver_name
137  IF (global%flowType == flow_steady) &
138  WRITE(stdout,1010) solver_name,solver_name
139  IF (global%flowType == flow_unsteady) &
140  WRITE(stdout,1015) solver_name,solver_name
141  ENDIF
142 #endif
143 
144  time = 0._rfreal
145 
146  finished = .false. ! run not finished yet
147  global%stopRun = 0._rfreal
148 
149 ! no multigrid here
150 
151  ftermnew = .false. ! no new forcing term
152  residfterm = .false. ! do not add forcing term to residual
153 
154 ! got some moving grid?
155 
156  movegrid = .false.
157  DO ireg=1,global%nRegions
158  IF (regions(ireg)%mixtInput%moveGrid) movegrid = .true.
159  ENDDO
160 
161 ! time steps / iterations -----------------------------------------------------
162 
163  DO
164 
165 ! - min. time step (unsteady flow)
166 
167  IF (global%flowType == flow_unsteady) THEN
168  global%dtMin = 1.e+30_rfreal
169  DO ireg=1,global%nRegions
170  IF (regions(ireg)%procid==global%myProcid .AND. & ! region active and
171  regions(ireg)%active==active) THEN ! on my processor
172  IF (regions(ireg)%mixtInput%flowModel == flow_euler) THEN
173  CALL rflo_timestepinviscid( regions(ireg) )
174  ELSE
175  CALL rflo_timestepviscous( regions(ireg) )
176  ENDIF
177 #ifdef PEUL
178  IF (global%peulUsed) &
179  CALL peul_spectralradii( regions(ireg) )
180 #endif
181 #ifdef TURB
182  IF (regions(ireg)%mixtInput%turbModel /= turb_model_none) &
183  CALL turb_rflo_ransspectralradii( regions(ireg) )
184 #endif
185  ENDIF ! region on this processor and active
186  ENDDO ! iReg
187  CALL rflo_minimumtimestep( regions )
188  IF (time+global%dtMin > dtimesystem) THEN ! do not run over max. time
189  global%dtMin = dtimesystem - time
190  finished = .true.
191  ENDIF
192  ENDIF
193 
194 ! - move grid
195 
196  IF (global%flowType==flow_unsteady .AND. movegrid) THEN
197  IF (global%moveGridScheme == movegrid_blocks) THEN
198  CALL rflo_movegridblocks( regions )
199  ELSEIF (global%moveGridScheme == movegrid_global) THEN
200  CALL rflo_movegridglobal( regions )
201  ELSEIF (global%moveGridScheme == movegrid_frame .OR. &
202  global%moveGridScheme == movegrid_foms) THEN
203  CALL rflo_movegridframe( regions )
204  ELSEIF (global%moveGridScheme == movegrid_elglobal) THEN
205  CALL rflo_movegridelliptglo( regions )
206  ELSEIF (global%moveGridScheme == movegrid_elframe) THEN
207  CALL rflo_movegridelliptfra( regions )
208  ELSE
209  CALL rflo_movegridvms( regions )
210  ENDIF
211  ENDIF
212 
213 ! - new grid needed?
214 
215  IF (global%flowType==flow_unsteady .AND. movegrid) THEN
216  CALL rflo_newgrid( regions )
217  ENDIF
218 
219 ! - recompute metrics of MP modules due to moving grid
220 #ifndef PROPONLY
221  IF (global%flowType==flow_unsteady .AND. movegrid) THEN
222 #ifdef TURB
223  IF (global%turbActive) CALL turb_calcmetrics( regions, 0 )
224 #endif
225 #ifdef PLAG
226  CALL plag_rflo_setmetrics( regions )
227 #endif
228  ENDIF
229 
230 ! - new solution
231 
232  IF (global%flowType == flow_unsteady) THEN
233  CALL rungekuttamp( regions )
234  DO ireg=1,global%nRegions
235  IF (regions(ireg)%procid==global%myProcid .AND. & ! region active,
236  regions(ireg)%active==active .AND. & ! on my processor
237  regions(ireg)%mixtInput%moveGrid) THEN ! and moving
238  CALL descalegridspeeds( regions(ireg) )
239  ENDIF ! region on this processor and active
240  ENDDO ! iReg
241  ELSE
242  IF (global%solverType == solv_explicit) THEN
243  CALL explicitmultistage( regions,ftermnew,residfterm )
244  ELSE
245  ! implicit scheme
246  CALL errorstop( global,err_unknown_option,__line__ )
247  ENDIF
248  ENDIF
249 
250 #ifdef PERI
251 ! - hybrid (guided) DES
252 
253  DO ireg=1,global%nRegions
254  IF (regions(ireg)%procid==global%myProcid .AND. & ! region active and
255  regions(ireg)%active==active) THEN ! on my processor
256  IF ( regions(ireg)%periInput%flowKind /= off ) THEN
257  CALL peri_comeancorrection( regions(ireg) )
258  ENDIF ! flowKind
259  ENDIF ! region on this processor and active
260  ENDDO ! iReg
261 #endif
262 
263 #ifdef STATS
264 ! - get statistics
265 
266  CALL getstatistics( regions )
267 #endif
268 #endif ! PROPONLY
269 
270 ! - update time / iteration number
271 
272  IF (global%flowType == flow_unsteady) THEN
273  global%currentTime = global%currentTime + global%dtMin
274  time = time + global%dtMin
275  iter = iter + 1
276  ELSE
277  global%currentIter = global%currentIter + 1
278  iter = iter + 1
279  ENDIF
280 
281 #ifndef PROPONLY
282 ! - print/write convergence, data, probe or thrust?
283 
284  IF (global%flowType==flow_unsteady .AND. iter==1) THEN
285  timeprint = global%timeStamp + global%printTime
286  timewrite = global%timeStamp + global%writeTime
287  timeprobe = global%timeStamp + global%probeSaveTime
288  timethrust = global%timeStamp + global%thrustSaveTime
289 ! IF (global%myProcid==MASTERPROC .AND. &
290 ! global%verbLevel/=VERBOSE_NONE) THEN
291 ! WRITE(STDOUT,*) SOLVER_NAME//'S:timeWrite,timeStamp,writeTime =',timeWrite,global%timeStamp, &
292 ! global%writeTime
293 ! ENDIF
294 
295  ENDIF
296 
297  IF (global%flowType == flow_unsteady) THEN
298  doprint = .false.
299  dowrite = .false.
300  doprobe = .false.
301  dothrust = .false.
302  ! IF (global%myProcid==MASTERPROC .AND. &
303  ! global%verbLevel/=VERBOSE_NONE) THEN
304  ! WRITE(STDOUT,*) SOLVER_NAME//'timeWrite,timeStamp,writeTime =',timeWrite,global%timeStamp, &
305  ! global%writeTime
306  ! WRITE(STDOUT,*) SOLVER_NAME//'currentTime =',global%currentTime
307  ! ENDIF
308  IF (abs(timeprint-global%currentTime)<global%dtMin/10._rfreal .OR. &
309  timeprint<global%currentTime .OR. iter==1) THEN
310  doprint = .true.
311  IF (iter > 1) timeprint = timeprint + global%printTime
312  ENDIF
313  IF (abs(timewrite-global%currentTime)<global%dtMin/10._rfreal .OR. &
314  timewrite<global%currentTime) THEN
315  dowrite = .true.
316  timewrite = timewrite + global%writeTime
317  ENDIF
318  IF (abs(timeprobe-global%currentTime)<global%dtMin/10._rfreal .OR. &
319  timeprobe<global%currentTime .OR. iter==1) THEN
320  doprobe = .true.
321  IF (iter > 1) timeprobe = timeprobe + global%probeSaveTime
322  ENDIF
323  IF (abs(timethrust-global%currentTime)<global%dtMin/10._rfreal .OR. &
324  timethrust<global%currentTime .OR. iter==1) THEN
325  dothrust = .true.
326  IF (iter > 1) timethrust = timethrust + global%thrustSaveTime
327  ENDIF
328  ELSE
329  doprint = (mod(global%currentIter,global%printIter ) == 0)
330  dowrite = (mod(global%currentIter,global%writeIter ) == 0)
331  doprobe = (mod(global%currentIter,global%probeSaveIter ) == 0)
332  dothrust = (mod(global%currentIter,global%thrustSaveIter) == 0)
333  ENDIF
334 #endif ! PROPONLY
335 ! - check for stop file
336 
337 #ifndef GENX
338  INQUIRE(file="STOP",exist=stopexists)
339  IF (stopexists) global%stopRun = 1.1_rfreal
340 #endif
341 
342 ! - check for end of time stepping
343 
344  IF (global%flowType == flow_unsteady) THEN
345  IF (time>=dtimesystem) finished = .true.
346  ELSE
347 #ifndef PROPONLY
348  CALL rflo_residualnorm( regions )
349  IF (iter==ditersystem .OR. &
350  global%residual/global%resInit<=global%resTol) finished = .true.
351 #endif
352  ENDIF
353 
354 ! - compute forces, mass flow & thrust;
355 ! - store probe data, thrust and flow solution
356 
357  global%forceX = 0._rfreal
358  global%forceY = 0._rfreal
359  global%forceZ = 0._rfreal
360  global%massIn = 0._rfreal
361  global%massOut = 0._rfreal
362  global%thrustMom = 0._rfreal
363  global%thrustPress = 0._rfreal
364  totalmass = 0._rfreal
365 
366 #ifndef PROPONLY
367  DO ireg=1,global%nRegions
368  IF (regions(ireg)%procid==global%myProcid .AND. & ! region active and
369  regions(ireg)%active==active) THEN ! on my processor
370 
371 ! ----- store probe, aero-coeffs. and thrust data
372 #ifdef GENX
373  IF (global%nProbes>0 .AND. (doprobe .eqv. .true.)) &
374  CALL writeprobe( regions,ireg )
375 
376  IF (global%aeroCoeffs==active .AND. (doprobe .eqv. .true.)) &
377  CALL rflo_computepatchforcemomco( regions(ireg) )
378 
379  IF (global%thrustType/=thrust_none .AND. (dothrust .eqv. .true.)) &
380  CALL rflo_calcthrust( regions(ireg) )
381 #else
382  IF (global%nProbes>0 .AND. ((doprobe.eqv..true.).OR.(finished.eqv..true.))) &
383  CALL writeprobe( regions,ireg )
384 
385  IF (global%aeroCoeffs==active .AND. (doprobe.OR.finished)) &
386  CALL rflo_computepatchforcemomco( regions(ireg) )
387 
388  IF (global%thrustType/=thrust_none .AND. (dothrust.OR.finished)) &
389  CALL rflo_calcthrust( regions(ireg) )
390 #endif
391 
392 ! ----- get forces, mass flow
393  IF ((doprint .eqv. .true.) .OR. (finished .eqv. .true.)) THEN
394  CALL rflo_calcmassflow( regions(ireg) )
395  CALL rflo_calcforces( regions(ireg) )
396  ENDIF
397  ENDIF ! region on this processor and active
398  ENDDO ! iReg
399 
400 ! - compute and write global aero-coeffs. to file
401 #ifdef GENX
402  IF (global%aeroCoeffs==active .AND. (doprobe .eqv. .true.)) THEN
403  CALL rflo_computeintegralforcemomco( global )
404  CALL rflo_writeintegralforcemomco( global )
405  ENDIF
406 #else
407  IF (global%aeroCoeffs==active .AND. ((doprobe .eqv. .true.).OR.(finished.eqv..true.))) THEN
408  CALL rflo_computeintegralforcemomco( global )
409  CALL rflo_writeintegralforcemomco( global )
410  ENDIF
411 #endif
412 
413 ! - write thrust to file
414 #ifdef GENX
415  IF (global%thrustType/=thrust_none .AND. (dothrust .eqv. .true.)) &
416  CALL writethrust( global )
417 #else
418  IF (global%thrustType/=thrust_none .AND. ((dothrust .eqv. .true.).OR.(finished .eqv. .true.))) &
419  CALL writethrust( global )
420 #endif
421 
422 ! - write convergence history (file & screen)
423 
424  IF ((doprint .eqv. .true.) .OR. (finished .eqv. .true.)) THEN
425 #ifdef MASS
426  CALL rflo_computeintegralvalues( regions )
427  WRITE(stdout,*) 'Total mass = ',global%totalMass
428 #endif
429  CALL writeconvergence( global )
430 #ifndef GENX
431  IF (global%stopRun > 1._rfreal) THEN
432  finished = .true.
433  ENDIF
434 #endif
435  ENDIF
436 
437 #ifndef GENX
438 ! - store flow field (and grid if moving)
439 
440  IF ((dowrite .eqv. .true.) .OR. (finished .eqv. .true.)) THEN
441  IF (movegrid) THEN
442  IF (global%myProcid==masterproc .AND. &
443  global%verbLevel/=verbose_none) THEN
444  WRITE(stdout,'(/,A)') solver_name//' Saving grid ...'
445  ENDIF
446  CALL rflo_writegrid( regions )
447  ENDIF
448  IF (global%myProcid==masterproc .AND. &
449  global%verbLevel/=verbose_none) THEN
450  WRITE(stdout,'(/,A)') solver_name//' Saving flow solution ...'
451  ENDIF
452  IF (global%myProcid==masterproc .AND. &
453  global%verbLevel>=verbose_high) THEN
454  WRITE(stdout,'(A)') solver_name//' - mixture'
455  ENDIF
456  CALL rflo_writesolution( regions )
457  CALL rflo_writerandomstate( regions )
458 
459  IF (global%aeroCoeffs == active) THEN
460  IF (global%myProcid==masterproc .AND. &
461  global%verbLevel>=verbose_high) THEN
462  WRITE(stdout,'(A)') solver_name//' - patch ac'
463  ENDIF
464  CALL rflo_writepatchaerocoeffs( regions )
465  ENDIF
466 #ifdef STATS
467  IF (global%doStat==active) THEN
468  IF (global%myProcid==masterproc .AND. &
469  global%verbLevel/=verbose_none) THEN
470  WRITE(stdout,'(/,A)') solver_name,' Saving statistics ...'
471  ENDIF
472  CALL statwritemp( regions )
473  ENDIF
474 #endif
475 #endif ! ndef GENX
476 
477 #ifdef GENX
478 #ifdef NATIVE_MP_IO
479  IF (dowrite .eqv. .true.) THEN
480  original_format = global%solutFormat
481  global%gridFormat = format_ascii
482  global%solutFormat = format_ascii
483 #ifdef PLAG
484  IF (global%myProcid==masterproc .AND. &
485  global%verbLevel/=verbose_none) THEN
486  WRITE(stdout,'(/,A)') solver_name,' Saving Lagrangian particle solution ...'
487  ENDIF
488  CALL plag_writesolution( regions )
489 #endif
490 #ifdef PEUL
491  CALL peul_writesolution( regions )
492 #endif
493 #ifdef RADI
494  IF (global%radiActive) THEN
495  IF (global%myProcid==masterproc .AND. &
496  global%verbLevel/=verbose_none) THEN
497  WRITE(stdout,'(/,A)') solver_name,' Saving radiation solution ...'
498  ENDIF
499  CALL radi_rflo_writesolution( regions )
500  ENDIF
501 #endif
502 #ifdef SPEC
503  CALL spec_writesolution( regions )
504 #endif
505 #ifdef TURB
506  IF (global%turbActive) THEN
507  IF (global%myProcid==masterproc .AND. &
508  global%verbLevel/=verbose_none) THEN
509  WRITE(stdout,'(/,A)') solver_name,' Saving turbulence solution ...'
510  ENDIF
511  CALL turb_rflo_writesolution( regions )
512  ENDIF
513 #endif
514  global%gridFormat = original_format
515  global%solutFormat = original_format
516  ENDIF
517 #endif ! NATIVE_MP_IO
518 #endif ! GENX
519 
520 #ifndef GENX
521 #ifdef PLAG
522  CALL plag_writesolution( regions )
523 #endif
524 #ifdef PEUL
525  CALL peul_writesolution( regions )
526 #endif
527 #ifdef RADI
528  IF (global%radiActive) THEN
529  IF (global%myProcid==masterproc .AND. &
530  global%verbLevel/=verbose_none) THEN
531  WRITE(stdout,'(/,A)') solver_name,' Saving radiation solution ...'
532  ENDIF
533  CALL radi_rflo_writesolution( regions )
534  ENDIF
535 #endif
536 #ifdef SPEC
537  CALL spec_writesolution( regions )
538 #endif
539 #ifdef TURB
540  IF (global%turbActive) THEN
541  IF (global%myProcid==masterproc .AND. &
542  global%verbLevel/=verbose_none) THEN
543  WRITE(stdout,'(/,A)') solver_name,' Saving turbulence solution ...'
544  ENDIF
545  CALL turb_rflo_writesolution( regions )
546  ENDIF
547 #endif
548  CALL rflo_writerestartinfo( global )
549 
550  ENDIF ! doWrite
551 #endif ! Not GENX
552 #endif ! NOT PROPONLY
553 ! - run finished?
554 
555  IF (finished) THEN
556  DO ireg=1,global%nRegions
557  IF (regions(ireg)%procid==global%myProcid .AND. & ! region active and
558  regions(ireg)%active==active) THEN ! on my processor
559  CALL rflo_sendboundaryvalues( regions(ireg),.false. )
560  ENDIF ! region on this processor and active
561  ENDDO ! iReg
562  global%timeStamp = global%currentTime
563  EXIT
564  ENDIF
565 
566 ! - check if to proceed to next finer grid
567 
568  IF (global%flowType==flow_steady .AND. mod(iter,global%refineIter)==0) THEN
569  DO ireg=1,global%nRegions
570  regions(ireg)%currLevel = regions(ireg)%currLevel - 1
571  CALL rflo_interpoltofinerlevel( regions(ireg) )
572  ENDDO
573  ENDIF
574 
575  ENDDO ! loop over time / iter
576 
577 ! formats
578 
579 1010 FORMAT(a,' iter',4x,'res-norm',5x,'force-x',6x,'force-y',6x,'force-z', &
580  6x,'mass-in',6x,'mass-out',/,a,1x,84('-'))
581 1015 FORMAT(a,' time',10x,'delta-t',6x,'force-x',6x,'force-y',6x,'force-z', &
582  6x,'mass-in',6x,'mass-out'/,a,1x,90('-'))
583 
584 ! finalize --------------------------------------------------------------------
585 
586  CALL deregisterfunction( global )
587 
588 END SUBROUTINE rflo_timestepping
589 
590 !******************************************************************************
591 !
592 ! RCS Revision history:
593 !
594 ! $Log: RFLO_TimeStepping.F90,v $
595 ! Revision 1.25 2009/08/27 14:04:52 mtcampbe
596 ! Updated to enable burning motion with symmetry boundaries and enhanced
597 ! burnout code.
598 !
599 ! Revision 1.24 2009/08/12 04:15:58 mtcampbe
600 ! Major update, bugfix from Abe development, more propagation compatibility,
601 ! some Rocstar IO changes, Ju's temporary clipping fix for turbulence. A bug
602 ! fix for initialization IO.
603 !
604 ! Revision 1.23 2009/04/07 14:53:57 mtcampbe
605 ! Switch to FORMAT_ASCII for native mp io
606 !
607 ! Revision 1.22 2009/03/05 13:00:23 mtcampbe
608 ! Added NATIVEMPIO and PROPONLY options for Rocflo
609 !
610 ! Revision 1.21 2008/12/06 08:44:28 mtcampbe
611 ! Updated license.
612 !
613 ! Revision 1.20 2008/11/19 22:17:39 mtcampbe
614 ! Added Illinois Open Source License/Copyright
615 !
616 ! Revision 1.19 2006/03/24 23:29:23 wasistho
617 ! added forceMomentCoeffs computation and output
618 !
619 ! Revision 1.18 2006/03/22 03:03:25 wasistho
620 ! added call to RFLO_WritePatchAeroCoeffs
621 !
622 ! Revision 1.17 2006/03/02 01:27:58 wasistho
623 ! split movegrid_epde to elglobal and elframe
624 !
625 ! Revision 1.16 2006/02/11 03:55:44 wasistho
626 ! added MOVEGRID_EPDE
627 !
628 ! Revision 1.15 2006/02/01 20:02:18 wasistho
629 ! added WriteRestartInfo
630 !
631 ! Revision 1.14 2005/11/11 07:32:47 wasistho
632 ! removed commented call to moveGridGlobal
633 !
634 ! Revision 1.13 2005/11/11 07:27:05 wasistho
635 ! removed obsolete file
636 !
637 ! Revision 1.12 2005/10/27 05:12:41 wasistho
638 ! added moveGridFoms
639 !
640 ! Revision 1.11 2005/06/02 03:21:17 wasistho
641 ! shuffle MoveGridVms with MoveGridFrame
642 !
643 ! Revision 1.10 2005/05/28 08:08:18 wasistho
644 ! added moveGridFrame
645 !
646 ! Revision 1.9 2005/05/21 01:43:17 wasistho
647 ! added statWriteMP
648 !
649 ! Revision 1.8 2005/05/21 00:18:33 wasistho
650 ! added moveGridVms
651 !
652 ! Revision 1.7 2005/04/17 05:09:58 wasistho
653 ! mv guided DES treatment to before statistics
654 !
655 ! Revision 1.6 2005/03/11 04:24:23 wasistho
656 ! added mean correction for PERI flows with hybrid DES
657 !
658 ! Revision 1.5 2005/02/26 04:05:29 wasistho
659 ! added RFLO_ComputeIntegralValues
660 !
661 ! Revision 1.4 2005/02/16 14:43:08 fnajjar
662 ! Included PLAG call to communicate statistics buffers during IO stage
663 !
664 ! Revision 1.3 2005/01/08 20:38:39 fnajjar
665 ! Added PLAG_RFLO_WriteStat call for IO
666 !
667 ! Revision 1.2 2004/12/28 20:27:52 wasistho
668 ! moved statistics routines into module ModStatsRoutines
669 !
670 ! Revision 1.1 2004/11/29 20:51:40 wasistho
671 ! lower to upper case
672 !
673 ! Revision 1.58 2004/11/29 17:15:57 wasistho
674 ! use ModInterfacesStatistics
675 !
676 ! Revision 1.57 2004/09/23 03:49:29 wasistho
677 ! changed RADI_WriteSol.. to RADI_RFLO_WriteSol..
678 !
679 ! Revision 1.56 2004/03/11 03:31:09 wasistho
680 ! changed rocturb nomenclature
681 !
682 ! Revision 1.55 2004/03/05 22:09:02 jferry
683 ! created global variables for peul, plag, and inrt use
684 !
685 ! Revision 1.54 2004/02/11 03:27:57 wasistho
686 ! get rid of argument numVar in TURB_WriteSolution
687 !
688 ! Revision 1.53 2004/02/07 01:12:43 wasistho
689 ! modified TURB_WriteSolution
690 !
691 ! Revision 1.51 2003/11/21 22:35:51 fnajjar
692 ! Update Random Number Generator
693 !
694 ! Revision 1.50 2003/11/20 16:40:40 mdbrandy
695 ! Backing out RocfluidMP changes from 11-17-03
696 !
697 ! Revision 1.46 2003/11/12 21:21:06 fnajjar
698 ! Added Corner-Edge cells routine to communicate metrics for PLAG
699 !
700 ! Revision 1.45 2003/10/15 03:38:41 wasistho
701 ! added call to turbulence spectralRadii routine
702 !
703 ! Revision 1.44 2003/10/03 20:18:57 wasistho
704 ! initial installation of turbModel SA and DES
705 !
706 ! Revision 1.43 2003/10/01 23:52:10 jblazek
707 ! Corrected bug in moving noslip wall BC and grid speeds.
708 !
709 ! Revision 1.42 2003/09/26 21:44:28 fnajjar
710 ! Modified ModInterfaces calls to proper physical modules
711 !
712 ! Revision 1.41 2003/08/28 20:35:34 wasistho
713 ! excluced ModInterfacesTurbulence,Radiation,Periodic from ModInterfaces
714 !
715 ! Revision 1.40 2003/08/15 21:15:17 jblazek
716 ! Corrected bug in output of thrust in case of GENX.
717 !
718 ! Revision 1.39 2003/08/11 21:51:18 jblazek
719 ! Added basic global grid smoothing scheme.
720 !
721 ! Revision 1.38 2003/08/01 22:14:08 wasistho
722 ! radiWrite/turbWrite to radiActive/turbActive
723 !
724 ! Revision 1.37 2003/07/22 02:57:42 wasistho
725 ! prepare more accurate rocturb restart
726 !
727 ! Revision 1.36 2003/07/17 01:03:28 wasistho
728 ! initial activation rocrad
729 !
730 ! Revision 1.35 2003/07/08 21:21:37 jblazek
731 ! Modified start up procedure for dual-time stepping.
732 !
733 ! Revision 1.34 2003/07/03 21:48:45 jblazek
734 ! Implemented dual-time stepping.
735 !
736 ! Revision 1.33 2003/06/02 17:12:01 jblazek
737 ! Added computation of thrust.
738 !
739 ! Revision 1.32 2003/05/15 02:57:04 jblazek
740 ! Inlined index function.
741 !
742 ! Revision 1.31 2003/04/10 01:22:41 jblazek
743 ! Got rid of pRegion in ViscousFluxesMP.
744 !
745 ! Revision 1.30 2003/04/04 21:05:00 jblazek
746 ! Corrected bug in dumping out the solution.
747 !
748 ! Revision 1.29 2003/03/28 19:35:06 fnajjar
749 ! include RungeKuttaMP routine
750 !
751 ! Revision 1.28 2003/03/11 16:04:19 jferry
752 ! Enclosed USE statements for multi-physics routines within ifdefs
753 !
754 ! Revision 1.27 2003/02/11 22:53:19 jferry
755 ! Initial import of Rocsmoke
756 !
757 ! Revision 1.26 2003/02/05 21:07:30 jblazek
758 ! Coordinated stop of a run works now for MPI.
759 !
760 ! Revision 1.25 2003/01/23 17:48:53 jblazek
761 ! Changed algorithm to dump convergence, solution and probe data.
762 !
763 ! Revision 1.24 2003/01/10 17:58:43 jblazek
764 ! Added missing explicit interfaces.
765 !
766 ! Revision 1.23 2002/11/02 01:58:14 wasistho
767 ! Added TURB statistics
768 !
769 ! Revision 1.22 2002/10/02 22:21:59 jiao
770 ! Debugged GenX restart.
771 !
772 ! Revision 1.21 2002/09/20 22:22:36 jblazek
773 ! Finalized integration into GenX.
774 !
775 ! Revision 1.20 2002/09/17 22:51:23 jferry
776 ! Removed Fast Eulerian particle type
777 !
778 ! Revision 1.19 2002/09/05 17:40:22 jblazek
779 ! Variable global moved into regions().
780 !
781 ! Revision 1.18 2002/08/30 01:47:58 jblazek
782 ! Added support for moving grids.
783 !
784 ! Revision 1.17 2002/07/18 22:51:57 jblazek
785 ! Reduce time step to match max. physical time.
786 !
787 ! Revision 1.16 2002/07/16 21:34:37 jblazek
788 ! Prefixed screen output with SOLVER_NAME.
789 !
790 ! Revision 1.15 2002/07/12 21:50:07 jblazek
791 ! Added tool to split single grid into multiple regions.
792 !
793 ! Revision 1.14 2002/06/18 00:33:57 wasistho
794 ! Added prefix SOLVER NAME to satistics STDOutput
795 !
796 ! Revision 1.13 2002/06/14 21:38:45 wasistho
797 ! Added time avg statistics
798 !
799 ! Revision 1.12 2002/06/12 21:56:29 jblazek
800 ! Added read/write solution for physical modules.
801 !
802 ! Revision 1.11 2002/06/07 16:40:37 jblazek
803 ! Grid & solution for all regions in one file.
804 !
805 ! Revision 1.10 2002/04/11 21:10:27 jblazek
806 ! Set correct time when writing grid only for Tecplot.
807 !
808 ! Revision 1.9 2002/03/18 23:11:33 jblazek
809 ! Finished multiblock and MPI.
810 !
811 ! Revision 1.8 2002/02/21 23:25:06 jblazek
812 ! Blocks renamed as regions.
813 !
814 ! Revision 1.7 2002/02/09 01:47:01 jblazek
815 ! Added multi-probe option, residual smoothing, physical time step.
816 !
817 ! Revision 1.6 2002/02/01 21:04:26 jblazek
818 ! Streamlined time stepping routine.
819 !
820 ! Revision 1.5 2002/01/31 20:56:30 jblazek
821 ! Added basic boundary conditions.
822 !
823 ! Revision 1.4 2002/01/28 23:55:22 jblazek
824 ! Added flux computation (central scheme).
825 !
826 ! Revision 1.3 2002/01/23 23:36:37 jblazek
827 ! All blocks passed to time integration routines.
828 !
829 ! Revision 1.2 2002/01/23 03:51:25 jblazek
830 ! Added low-level time-stepping routines.
831 !
832 ! Revision 1.1 2002/01/16 22:03:35 jblazek
833 ! Added time-stepping routines.
834 !
835 !******************************************************************************
836 
837 
838 
839 
840 
841 
842 
subroutine rflo_writerandomstate(regions)
subroutine, public rflo_movegridelliptfra(regions)
subroutine plag_rflo_setmetrics(regions)
subroutine peul_spectralradii(region)
subroutine, public rflo_writeintegralforcemomco(global)
subroutine turb_rflo_ransspectralradii(region)
subroutine peul_writesolution(regions)
subroutine rflo_calcforces(region)
subroutine rflo_residualnorm(regions)
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
subroutine, public rflo_movegridframe(regions)
subroutine, public rflo_writerestartinfo(global)
subroutine rflo_calcmassflow(region)
subroutine rflo_newgrid(regions)
subroutine, public rflo_computepatchforcemomco(region)
subroutine explicitmultistage(regions, ftermNew, residFterm)
subroutine, public rflo_writepatchaerocoeffs(regions)
subroutine, public rflo_computeintegralforcemomco(global)
subroutine rflo_timestepping(dTimeSystem, dIterSystem, regions)
subroutine writeprobe(regions, iReg)
Definition: WriteProbe.F90:45
subroutine rflo_computeintegralvalues(regions)
subroutine, public getstatistics(regions)
subroutine rungekuttamp(regions)
subroutine turb_rflo_writesolution(regions)
subroutine rflo_minimumtimestep(regions)
void int int REAL * x
Definition: read.cpp:74
subroutine, public statwritemp(regions)
subroutine turb_calcmetrics(regions, isInit)
subroutine radi_rflo_writesolution(regions)
subroutine rflo_sendboundaryvalues(region, initialize)
subroutine rflo_writegrid(regions)
subroutine rflo_interpoltofinerlevel(region)
subroutine, public rflo_movegridelliptglo(regions)
subroutine rflo_movegridglobal(regions)
subroutine rflo_writesolution(regions)
subroutine rflo_timestepviscous(region)
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
subroutine plag_writesolution(regions)
subroutine writeconvergence(global)
subroutine, public rflo_movegridvms(regions)
subroutine deregisterfunction(global)
Definition: ModError.F90:469
subroutine descalegridspeeds(region)
subroutine rflo_calcthrust(region)
RT a() const
Definition: Line_2.h:140
subroutine rflo_timestepinviscid(region)
subroutine rflo_movegridblocks(regions)
subroutine writethrust(global)
Definition: WriteThrust.F90:43