Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
RFLO_DualTimeStepping.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 using
26 ! dual time-stepping; move/regenerate the grid.
27 !
28 ! Description: none.
29 !
30 ! Input: dTimeSystem = total solution time
31 ! regions = data for all grid regions
32 !
33 ! Output: regions = flow variables and grid for all grid regions.
34 !
35 ! Notes: scheme also applicable for small time steps.
36 !
37 !******************************************************************************
38 !
39 ! $Id: RFLO_DualTimeStepping.F90,v 1.30 2008/12/06 08:44:26 mtcampbe Exp $
40 !
41 ! Copyright: (c) 2003 by the University of Illinois
42 !
43 !******************************************************************************
44 
45 SUBROUTINE rflo_dualtimestepping( dTimeSystem,regions )
46 
47  USE moddatatypes
48  USE moddatastruct, ONLY : t_region
49  USE modglobal, ONLY : t_global
58 
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
88  USE modinterfaces, ONLY : rflo_writestat
91 #endif
92  USE moderror
93  USE modmpi
94  USE modparameters
95  IMPLICIT NONE
96 
97 ! ... parameters
98  REAL(RFREAL) :: dtimesystem
99 
100  TYPE(t_region), POINTER :: regions(:)
101 
102 ! ... loop variables
103  INTEGER :: ireg, subiter
104 
105 ! ... local variables
106  INTEGER, SAVE :: iter=0
107  INTEGER, ALLOCATABLE :: timescheme(:)
108 
109  LOGICAL :: stopexists, finished, ftermnew, residfterm, &
110  doprint, dowrite, doprobe, dothrust, movegrid
111 
112  REAL(RFREAL), SAVE :: timeprint=0._rfreal, timewrite =0._rfreal, &
113  timeprobe=0._rfreal, timethrust=0._rfreal
114  REAL(RFREAL) :: time, subtime, timebc, alphabc, residrat
115  REAL(RFREAL), ALLOCATABLE :: cfl(:), smoocf(:)
116  REAL(RFREAL), POINTER :: cv(:,:), cvn(:,:), cvn1(:,:), cvn2(:,:)
117 
118  TYPE(t_global), POINTER :: global
119 
120 !******************************************************************************
121 
122  global => regions(1)%global
123 
124  CALL registerfunction( global,'RFLO_DualTimeStepping',&
125  'RFLO_DualTimeStepping.F90' )
126 
127 ! initialize parameters -------------------------------------------------------
128 
129 #ifdef GENX
130  IF (global%predCorrIter) THEN
131  iter = 0
132  global%predCorrIter = .false.
133  ENDIF
134 #endif
135 
136  time = 0._rfreal
137 
138  IF (global%dtFixed) THEN
139  IF (global%currentTime <= epsilon( 1._rfreal )) THEN ! more accurate
140  global%dtMin = global%dtImposed ! but slower
141  ENDIF
142  ELSE
143  global%dtMin = global%dtImposed ! for more speed
144  ENDIF
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 ! initialize solutions --------------------------------------------------------
162 
163  IF (iter == 0) THEN
164 
165  global%dualTstSource = .false. ! ordinary Runge-Kutta here
166 
167 ! - solution at level n-2
168 
169  CALL rflo_dualtstinit( regions,2 )
170 
171 ! - store scheme, CFL, epsIRS (overwritten for Runge-Kutta!)
172 
173  ALLOCATE( timescheme(global%nRegions) )
174  ALLOCATE( cfl(global%nRegions) )
175  ALLOCATE( smoocf(global%nRegions) )
176  DO ireg=1,global%nRegions ! commented since all
177 ! IF (regions(iReg)%procid==global%myProcid .AND. & ! procs need trk from
178 ! regions(iReg)%active==ACTIVE) THEN ! ireg=1 (see ExpMS)
179  timescheme(ireg) = regions(ireg)%mixtInput%timeScheme
180  cfl(ireg) = regions(ireg)%mixtInput%cfl
181  smoocf(ireg) = regions(ireg)%mixtInput%smoocf
182  regions(ireg)%mixtInput%timeScheme = tst_std4rk
183  regions(ireg)%mixtInput%cfl = 3._rfreal
184  CALL rflo_setmstagecoeffs( global,regions(ireg)%mixtInput,global%nrkSteps )
185 ! ENDIF ! region on this processor and active
186  ENDDO ! iReg
187 
188 ! - solutions at levels n-1 and n
189 
190  subtime = 0._rfreal
191 
192  DO subiter=1,0,-1
193  global%dtMin = 1.e+30_rfreal
194  DO ireg=1,global%nRegions
195  IF (regions(ireg)%procid==global%myProcid .AND. & ! region active and
196  regions(ireg)%active==active) THEN ! on my processor
197  IF (regions(ireg)%mixtInput%flowModel == flow_euler) THEN
198  CALL rflo_timestepinviscid( regions(ireg) )
199  ELSE
200  CALL rflo_timestepviscous( regions(ireg) )
201  ENDIF
202  ENDIF ! region on this processor and active
203  ENDDO ! iReg
204  CALL rflo_minimumtimestep( regions )
205  IF (time+global%dtMin > dtimesystem) THEN ! do not run over max. time
206  global%dtMin = dtimesystem - time
207  ENDIF
208 
209  IF (movegrid) CALL rflo_movegridblocks( regions )
210 
211  CALL rungekuttamp( regions )
212  CALL rflo_dualtstinit( regions,subiter )
213 
214  global%currentTime = global%currentTime + global%dtMin
215  time = time + global%dtMin
216  subtime = subtime + global%dtMin
217  ENDDO ! subIter
218 
219 ! - restore scheme, CFL, epsIRS again
220 
221  DO ireg=1,global%nRegions
222  IF (regions(ireg)%procid==global%myProcid .AND. & ! region active and
223  regions(ireg)%active==active) THEN ! on my processor
224  regions(ireg)%mixtInput%timeScheme = timescheme(ireg)
225  regions(ireg)%mixtInput%cfl = cfl(ireg)
226  regions(ireg)%mixtInput%smoocf = smoocf(ireg)
227  CALL rflo_setmstagecoeffs( global,regions(ireg)%mixtInput,global%nrkSteps )
228  ENDIF ! region on this processor and active
229  ENDDO ! iReg
230  DEALLOCATE( timescheme )
231  DEALLOCATE( cfl )
232  DEALLOCATE( smoocf )
233 
234 ! - substract subTime from the first implicit time step
235 
236  IF (global%dtImposed <= subtime) THEN
237  global%dtMin = 0._rfreal
238  DO
239  global%dtMin = global%dtMin + global%dtImposed
240  IF (global%dtMin > subtime) EXIT
241  ENDDO
242  global%dtMin = global%dtMin - subtime
243  ELSE
244  global%dtMin = global%dtImposed - subtime
245  ENDIF
246  global%dualTstSource = .true.
247 
248  ENDIF ! iter=0
249 
250 ! time steps ------------------------------------------------------------------
251 
252  DO
253 
254  IF (global%dtFixed) THEN
255 
256 ! --- Fixed dt for speed (default)
257  IF (iter > 0) global%dtMin = global%dtImposed
258 
259  ELSE
260 
261 ! --- Adjustable dt for higher accuracy, but slower
262  residrat = global%residual/(global%resInit*global%tolSubIter)
263  IF (iter == 0) THEN
264  global%dtMin = 0.01_rfreal * global%dtMin
265  ELSEIF (iter == 1) THEN
266  IF (global%currentTime < global%dtImposed) & ! even more accrt bt slwer
267  global%dtMin = global%dtImposed
268  ELSEIF (iter > 1) THEN
269  IF (residrat > 1._rfreal) THEN
270  global%dtMin = 0.75_rfreal*global%dtMin
271  ELSE
272  IF (global%dtMin < global%dtImposed) &
273  global%dtMin = min( 1.25_rfreal*global%dtMin, global%dtImposed )
274  ENDIF ! residRat
275  ENDIF ! iter
276 
277  ENDIF ! dtFixed
278 
279  IF (time+global%dtMin > dtimesystem) THEN ! do not run over max. time
280  global%dtMin = dtimesystem - time
281  finished = .true.
282  ENDIF
283 
284 ! - move grid
285 
286  IF (movegrid) THEN
287  IF (global%moveGridScheme == movegrid_blocks) THEN
288  CALL rflo_movegridblocks( regions )
289  ELSEIF (global%moveGridScheme == movegrid_global) THEN
290  CALL rflo_movegridglobal( regions )
291  ELSEIF (global%moveGridScheme == movegrid_frame .OR. &
292  global%moveGridScheme == movegrid_foms) THEN
293  CALL rflo_movegridframe( regions )
294  ELSEIF (global%moveGridScheme == movegrid_elglobal) THEN
295  CALL rflo_movegridelliptglo( regions )
296  ELSEIF (global%moveGridScheme == movegrid_elframe) THEN
297  CALL rflo_movegridelliptfra( regions )
298  ELSE
299  CALL rflo_movegridvms( regions )
300  ENDIF
301  ENDIF
302 
303 ! - new grid needed?
304 
305  IF (movegrid) THEN
306  CALL rflo_newgrid( regions )
307  ENDIF
308 
309 ! - recompute metrics of MP modules due to moving grid
310 
311  IF (movegrid) THEN
312 #ifdef TURB
313  IF (global%turbActive) CALL turb_calcmetrics( regions, 0 )
314 #endif
315  ENDIF
316 
317 ! - compute source term for implicit scheme; guess start solution
318 
319  DO ireg=1,global%nRegions
320  IF (regions(ireg)%procid==global%myProcid .AND. & ! region active and
321  regions(ireg)%active==active) THEN ! on my processor
322  CALL rflo_dualtststerm( regions(ireg) )
323  IF (global%predictSol .OR. iter==0) &
324  CALL rflo_dualtstpredict( regions(ireg) )
325  ENDIF ! region on this processor and active
326  ENDDO ! iReg
327 
328 ! - new solution (do subiterations)
329 
330  subiter = 0
331  global%flowType = flow_steady
332 
333  DO
334  subiter = subiter + 1
335  global%currentIter = subiter
336  CALL explicitmultistage( regions,ftermnew,residfterm )
337  CALL rflo_residualnorm( regions )
338  IF (global%myProcid==masterproc .AND. global%verbLevel>=verbose_high) THEN
339  WRITE(stdout,'(A,1X,2I6,1PE13.4,E13.4)') &
340  solver_name,iter,subiter,global%residual/global%resInit,global%residual
341  ENDIF
342  IF (subiter==global%maxSubIter .OR. &
343  global%residual/global%resInit<=global%tolSubIter .OR. &
344  global%residual<100._rfreal*epsilon(1.0_rfreal)) EXIT
345  ENDDO
346  IF (global%myProcid == masterproc .AND. global%verbLevel>=verbose_low) THEN
347  WRITE(stdout,'(A,1X,I6,1PE13.4,E13.4)') &
348  solver_name,subiter,global%residual/global%resInit,global%residual
349  ENDIF
350 
351  global%flowType = flow_unsteady
352 
353 ! - shift time levels
354 
355  DO ireg=1,global%nRegions
356  IF (regions(ireg)%procid==global%myProcid .AND. & ! region active and
357  regions(ireg)%active==active) THEN ! on my processor
358  CALL rflo_dualtstshift( regions(ireg) )
359  ENDIF ! region on this processor and active
360  ENDDO ! iReg
361 
362 #ifdef PERI
363 ! - hybrid (guided) DES
364 
365  DO ireg=1,global%nRegions
366  IF (regions(ireg)%procid==global%myProcid .AND. & ! region active and
367  regions(ireg)%active==active) THEN ! on my processor
368  IF ( regions(ireg)%periInput%flowKind /= off ) THEN
369  CALL peri_comeancorrection( regions(ireg) )
370  ENDIF ! flowKind
371  ENDIF ! region on this processor and active
372  ENDDO ! iReg
373 #endif
374 
375 #ifdef STATS
376 ! - get statistics
377 
378  CALL getstatistics( regions )
379 #endif
380 
381 ! - update physical time
382 
383  global%currentTime = global%currentTime + global%dtMin
384  time = time + global%dtMin
385  iter = iter + 1
386 
387 ! - print/write convergence, data, probe or thrust?
388 
389  IF (iter == 1) THEN
390  timeprint = global%timeStamp + global%printTime
391  timewrite = global%timeStamp + global%writeTime
392  timeprobe = global%timeStamp + global%probeSaveTime
393  timethrust = global%timeStamp + global%thrustSaveTime
394  ENDIF
395 
396  doprint = .false.
397  dowrite = .false.
398  doprobe = .false.
399  dothrust = .false.
400  IF (abs(timeprint-global%currentTime)<global%dtMin/10._rfreal .OR. &
401  timeprint<global%currentTime .OR. iter==1) THEN
402  doprint = .true.
403  IF (iter > 1) timeprint = timeprint + global%printTime
404  ENDIF
405  IF (abs(timewrite-global%currentTime)<global%dtMin/10._rfreal .OR. &
406  timewrite<global%currentTime) THEN
407  dowrite = .true.
408  timewrite = timewrite + global%writeTime
409  ENDIF
410  IF (abs(timeprobe-global%currentTime)<global%dtMin/10._rfreal .OR. &
411  timeprobe<global%currentTime .OR. iter==1) THEN
412  doprobe = .true.
413  IF (iter > 1) timeprobe = timeprobe + global%probeSaveTime
414  ENDIF
415  IF (abs(timethrust-global%currentTime)<global%dtMin/10._rfreal .OR. &
416  timethrust<global%currentTime .OR. iter==1) THEN
417  dothrust = .true.
418  IF (iter > 1) timethrust = timethrust + global%thrustSaveTime
419  ENDIF
420 
421 ! - check for stop file
422 
423 #ifndef GENX
424  INQUIRE(file="STOP",exist=stopexists)
425  IF (stopexists) global%stopRun = 1.1_rfreal
426 #endif
427 
428 ! - check for end of time stepping
429 
430  IF (time >= dtimesystem) finished = .true.
431 
432 ! - compute forces, mass flow & thrust;
433 ! - store probe data, thrust and flow solution
434 
435  global%forceX = 0._rfreal
436  global%forceY = 0._rfreal
437  global%forceZ = 0._rfreal
438  global%massIn = 0._rfreal
439  global%massOut = 0._rfreal
440  global%thrustMom = 0._rfreal
441  global%thrustPress = 0._rfreal
442 
443  DO ireg=1,global%nRegions
444  IF (regions(ireg)%procid==global%myProcid .AND. & ! region active and
445  regions(ireg)%active==active) THEN ! on my processor
446 
447 ! ----- store probe, aero-coeffs. and thrust data
448 #ifdef GENX
449  IF (global%nProbes>0 .AND. doprobe) &
450  CALL writeprobe( regions,ireg )
451 
452  IF (global%aeroCoeffs==active .AND. doprobe) &
453  CALL rflo_computepatchforcemomco( regions(ireg) )
454 
455  IF (global%thrustType/=thrust_none .AND. dothrust) &
456  CALL rflo_calcthrust( regions(ireg) )
457 #else
458  IF (global%nProbes>0 .AND. (doprobe.OR.finished)) &
459  CALL writeprobe( regions,ireg )
460 
461  IF (global%aeroCoeffs==active .AND. (doprobe.OR.finished)) &
462  CALL rflo_computepatchforcemomco( regions(ireg) )
463 
464  IF (global%thrustType/=thrust_none .AND. (dothrust.OR.finished)) &
465  CALL rflo_calcthrust( regions(ireg) )
466 #endif
467 
468 ! ----- get forces, mass flow
469  IF (doprint .OR. finished) THEN
470  CALL rflo_calcmassflow( regions(ireg) )
471  CALL rflo_calcforces( regions(ireg) )
472  ENDIF
473  ENDIF ! region on this processor and active
474  ENDDO ! iReg
475 
476 ! - compute and write global aero-coeffs. to file
477 #ifdef GENX
478  IF (global%aeroCoeffs==active .AND. doprobe) THEN
479  CALL rflo_computeintegralforcemomco( global )
480  CALL rflo_writeintegralforcemomco( global )
481  ENDIF
482 #else
483  IF (global%aeroCoeffs==active .AND. (doprobe.OR.finished)) THEN
484  CALL rflo_computeintegralforcemomco( global )
485  CALL rflo_writeintegralforcemomco( global )
486  ENDIF
487 #endif
488 
489 ! - write thrust to file
490 #ifdef GENX
491  IF (global%thrustType/=thrust_none .AND. dothrust) &
492  CALL writethrust( global )
493 #else
494  IF (global%thrustType/=thrust_none .AND. (dothrust.OR.finished)) &
495  CALL writethrust( global )
496  IF (movegrid) CALL rflo_computeintegralvalues( regions )
497 #endif
498 
499 ! - write convergence history (file & screen)
500 
501  IF (doprint .OR. finished) THEN
502 #ifdef MASS
503  CALL rflo_computeintegralvalues( regions )
504  WRITE(stdout,*) 'Total mass = ',global%totalMass
505 #endif
506  CALL writeconvergence( global )
507 #ifndef GENX
508  IF (global%stopRun > 1._rfreal) THEN
509  finished = .true.
510  ENDIF
511 #endif
512  ENDIF
513 
514 #ifndef GENX
515 ! - store flow field (and grid if moving)
516 
517  IF (dowrite .OR. finished) THEN
518  IF (movegrid) THEN
519  IF (global%myProcid==masterproc .AND. &
520  global%verbLevel/=verbose_none) THEN
521  WRITE(stdout,'(/,A)') solver_name//' Saving grid ...'
522  ENDIF
523  CALL rflo_writegrid( regions )
524  ENDIF
525  IF (global%myProcid==masterproc .AND. &
526  global%verbLevel/=verbose_none) THEN
527  WRITE(stdout,'(/,A)') solver_name//' Saving flow solution ...'
528  ENDIF
529  IF (global%myProcid==masterproc .AND. &
530  global%verbLevel>=verbose_high) THEN
531  WRITE(stdout,'(A)') solver_name//' - mixture'
532  ENDIF
533  CALL rflo_writesolution( regions )
534  CALL rflo_writerandomstate( regions )
535 
536  IF (global%aeroCoeffs == active) THEN
537  IF (global%myProcid==masterproc .AND. &
538  global%verbLevel>=verbose_high) THEN
539  WRITE(stdout,'(A)') solver_name//' - patch ac'
540  ENDIF
541  CALL rflo_writepatchaerocoeffs( regions )
542  ENDIF
543 #ifdef STATS
544  IF (global%doStat==active) THEN
545  IF (global%myProcid==masterproc .AND. &
546  global%verbLevel/=verbose_none) THEN
547  WRITE(stdout,'(/,A)') solver_name,' Saving statistics ...'
548  ENDIF
549  CALL rflo_statboundaryconditionsset( regions )
550  CALL rflo_writestat( regions )
551  ENDIF
552 #endif
553 #ifdef PLAG
554  CALL plag_writesolution( regions )
555 #endif
556 #ifdef PEUL
557  CALL peul_writesolution( regions )
558 #endif
559 #ifdef RADI
560  IF (global%radiActive) THEN
561  IF (global%myProcid==masterproc .AND. &
562  global%verbLevel/=verbose_none) THEN
563  WRITE(stdout,'(/,A)') solver_name,' Saving radiation solution ...'
564  ENDIF
565  CALL radi_rflo_writesolution( regions )
566  ENDIF
567 #endif
568 #ifdef SPEC
569  CALL spec_writesolution( regions )
570 #endif
571 #ifdef TURB
572  IF (global%turbActive) THEN
573  IF (global%myProcid==masterproc .AND. &
574  global%verbLevel/=verbose_none) THEN
575  WRITE(stdout,'(/,A)') solver_name,' Saving turbulence solution ...'
576  ENDIF
577  CALL turb_rflo_writesolution( regions )
578  ENDIF
579 #endif
580  CALL rflo_writerestartinfo( global )
581 
582  ENDIF ! doWrite
583 #endif
584 
585 ! - run finished?
586 
587  IF (finished) THEN
588  DO ireg=1,global%nRegions
589  IF (regions(ireg)%procid==global%myProcid .AND. & ! region active and
590  regions(ireg)%active==active) THEN ! on my processor
591  CALL rflo_sendboundaryvalues( regions(ireg),.false. )
592  ENDIF ! region on this processor and active
593  ENDDO ! iReg
594  global%timeStamp = global%currentTime
595  EXIT
596  ENDIF
597 
598  ENDDO ! loop over physical time
599 
600 ! finalize --------------------------------------------------------------------
601 
602  CALL deregisterfunction( global )
603 
604 END SUBROUTINE rflo_dualtimestepping
605 
606 !******************************************************************************
607 !
608 ! RCS Revision history:
609 !
610 ! $Log: RFLO_DualTimeStepping.F90,v $
611 ! Revision 1.30 2008/12/06 08:44:26 mtcampbe
612 ! Updated license.
613 !
614 ! Revision 1.29 2008/11/19 22:17:37 mtcampbe
615 ! Added Illinois Open Source License/Copyright
616 !
617 ! Revision 1.28 2006/05/09 23:32:06 wasistho
618 ! added fixed-or-free dt options in implicit dtst
619 !
620 ! Revision 1.27 2006/05/05 17:35:27 wasistho
621 ! commented back region-split for parallel, all procs need trk
622 !
623 ! Revision 1.26 2006/04/15 00:23:28 wasistho
624 ! set constant dt as default timestepping
625 !
626 ! Revision 1.25 2006/03/24 23:29:01 wasistho
627 ! added forceMomentCoeffs computation and output
628 !
629 ! Revision 1.24 2006/03/22 03:03:32 wasistho
630 ! added call to RFLO_WritePatchAeroCoeffs
631 !
632 ! Revision 1.23 2006/03/06 08:07:45 wasistho
633 ! set to more agressive stepping
634 !
635 ! Revision 1.22 2006/03/02 01:26:40 wasistho
636 ! split movegrid_epde to elglobal and elframe
637 !
638 ! Revision 1.21 2006/02/11 03:55:58 wasistho
639 ! added MOVEGRID_EPDE
640 !
641 ! Revision 1.20 2006/02/01 20:10:13 wasistho
642 ! added WriteRestartInfo
643 !
644 ! Revision 1.19 2006/01/28 03:12:45 wasistho
645 ! set adjustable timestep to more accurate option
646 !
647 ! Revision 1.18 2006/01/27 07:32:04 wasistho
648 ! adjustable timestep for stability
649 !
650 ! Revision 1.17 2006/01/26 08:25:23 wasistho
651 ! bug fixed: invert the dtMin adjuster
652 !
653 ! Revision 1.16 2006/01/26 08:10:58 wasistho
654 ! relate dtMin to previous residual
655 !
656 ! Revision 1.15 2006/01/13 00:08:28 wasistho
657 ! bound global%dtMin within max.time
658 !
659 ! Revision 1.14 2005/11/07 19:49:11 wasistho
660 ! added MOVEGRID_FOMS
661 !
662 ! Revision 1.13 2005/06/16 03:52:40 wasistho
663 ! activated RFLO_ModStatsBc
664 !
665 ! Revision 1.12 2005/06/02 03:21:25 wasistho
666 ! shuffle MoveGridVms with MoveGridFrame
667 !
668 ! Revision 1.11 2005/05/28 08:08:28 wasistho
669 ! added moveGridFrame
670 !
671 ! Revision 1.10 2005/05/21 07:08:18 wasistho
672 ! backout RFLO_ModStatsBoundaryConditions temporarily
673 !
674 ! Revision 1.9 2005/05/21 01:43:54 wasistho
675 ! added rflo_StatBcSet
676 !
677 ! Revision 1.8 2005/05/21 00:18:52 wasistho
678 ! added moveGridVms
679 !
680 ! Revision 1.7 2005/04/17 05:09:50 wasistho
681 ! mv guided DES treatment to before statistics
682 !
683 ! Revision 1.6 2005/03/10 02:03:23 wasistho
684 ! test calling PERI_coMeanCorrection from DualTsT i.o.EMS
685 !
686 ! Revision 1.5 2005/02/26 04:05:38 wasistho
687 ! added RFLO_ComputeIntegralValues
688 !
689 ! Revision 1.4 2004/12/28 20:27:12 wasistho
690 ! moved statistics routines into module ModStatsRoutines
691 !
692 ! Revision 1.3 2004/12/15 09:20:14 wasistho
693 ! fixed dual tst for Rocstar
694 !
695 ! Revision 1.2 2004/12/09 22:16:55 wasistho
696 ! added data turbulence Metric computation
697 !
698 ! Revision 1.1 2004/11/29 20:51:39 wasistho
699 ! lower to upper case
700 !
701 ! Revision 1.17 2004/11/29 17:15:38 wasistho
702 ! use ModInterfacesStatistics
703 !
704 ! Revision 1.16 2004/11/17 16:30:25 haselbac
705 ! Adapted interface of RFLO_SetMStageCoeffs
706 !
707 ! Revision 1.15 2004/09/23 03:50:04 wasistho
708 ! changed RADI_WriteSol.. to RADI_RFLO_WriteSol..
709 !
710 ! Revision 1.14 2004/03/11 03:31:33 wasistho
711 ! changed rocturb nomenclature
712 !
713 ! Revision 1.13 2004/02/11 03:28:09 wasistho
714 ! get rid of argument numVar in TURB_WriteSolution
715 !
716 ! Revision 1.12 2004/02/07 01:12:56 wasistho
717 ! modified TURB_WriteSolution
718 !
719 ! Revision 1.11 2003/11/21 22:35:51 fnajjar
720 ! Update Random Number Generator
721 !
722 ! Revision 1.10 2003/11/20 16:40:39 mdbrandy
723 ! Backing out RocfluidMP changes from 11-17-03
724 !
725 ! Revision 1.6 2003/09/26 21:44:28 fnajjar
726 ! Modified ModInterfaces calls to proper physical modules
727 !
728 ! Revision 1.5 2003/08/28 20:35:46 wasistho
729 ! excluced ModInterfacesTurbulence,Radiation,Periodic from ModInterfaces
730 !
731 ! Revision 1.4 2003/08/15 21:15:17 jblazek
732 ! Corrected bug in output of thrust in case of GENX.
733 !
734 ! Revision 1.3 2003/08/11 21:51:18 jblazek
735 ! Added basic global grid smoothing scheme.
736 !
737 ! Revision 1.2 2003/07/08 21:21:37 jblazek
738 ! Modified start up procedure for dual-time stepping.
739 !
740 ! Revision 1.1 2003/07/03 21:48:45 jblazek
741 ! Implemented dual-time stepping.
742 !
743 !******************************************************************************
744 
745 
746 
747 
748 
749 
750 
subroutine rflo_writerandomstate(regions)
subroutine rflo_dualtststerm(region)
subroutine, public rflo_movegridelliptfra(regions)
subroutine, public rflo_writeintegralforcemomco(global)
subroutine peul_writesolution(regions)
subroutine rflo_calcforces(region)
subroutine rflo_residualnorm(regions)
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
subroutine rflo_dualtstpredict(region)
subroutine, public rflo_movegridframe(regions)
subroutine, public rflo_writerestartinfo(global)
subroutine rflo_calcmassflow(region)
subroutine rflo_writestat(regions)
subroutine rflo_newgrid(regions)
subroutine, public rflo_statboundaryconditionsset(regions)
subroutine rflo_setmstagecoeffs(global, input, nrkSteps)
subroutine, public rflo_computepatchforcemomco(region)
subroutine explicitmultistage(regions, ftermNew, residFterm)
subroutine, public rflo_writepatchaerocoeffs(regions)
subroutine, public rflo_computeintegralforcemomco(global)
subroutine writeprobe(regions, iReg)
Definition: WriteProbe.F90:45
subroutine rflo_computeintegralvalues(regions)
subroutine, public getstatistics(regions)
subroutine rungekuttamp(regions)
subroutine rflo_dualtstshift(region)
subroutine turb_rflo_writesolution(regions)
subroutine rflo_minimumtimestep(regions)
subroutine turb_calcmetrics(regions, isInit)
subroutine radi_rflo_writesolution(regions)
subroutine rflo_sendboundaryvalues(region, initialize)
subroutine rflo_writegrid(regions)
subroutine rflo_dualtstinit(regions, timeLevel)
Vector_n min(const Array_n_const &v1, const Array_n_const &v2)
Definition: Vector_n.h:346
subroutine, public rflo_movegridelliptglo(regions)
subroutine rflo_movegridglobal(regions)
subroutine rflo_writesolution(regions)
subroutine rflo_timestepviscous(region)
subroutine plag_writesolution(regions)
subroutine writeconvergence(global)
subroutine, public rflo_movegridvms(regions)
subroutine deregisterfunction(global)
Definition: ModError.F90:469
subroutine rflo_dualtimestepping(dTimeSystem, regions)
subroutine rflo_calcthrust(region)
subroutine rflo_timestepinviscid(region)
subroutine rflo_movegridblocks(regions)
subroutine writethrust(global)
Definition: WriteThrust.F90:43