Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
ExplicitMultistage.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: calculate solution at a new time level/iteration.
26 !
27 ! Description: the governing equations are integrated in time using
28 ! an explicit, multistage (Runge-Kutta type) temporal scheme.
29 ! Spatial and temporal discretizations are independent of
30 ! each other based on the method of lines.
31 !
32 ! Input: regions = data of all regions
33 ! ftermNew = compute new forcing term (true/false)
34 ! residFterm = add forcing term to residual (true/false).
35 !
36 ! Output: regions%levels%mixt = new solution (and forcing term) after
37 ! one time step/iteration.
38 !
39 ! Notes: none.
40 !
41 ! ******************************************************************************
42 !
43 ! $Id: ExplicitMultistage.F90,v 1.15 2008/12/06 08:44:09 mtcampbe Exp $
44 !
45 ! Copyright: (c) 2001-2005 by the University of Illinois
46 !
47 ! ******************************************************************************
48 
49 SUBROUTINE explicitmultistage( regions,ftermNew,residFterm )
50 
51  USE moddatatypes
52  USE moddatastruct, ONLY : t_region
53  USE modglobal, ONLY : t_global
54  USE moderror
55  USE modmpi
56  USE modparameters
57 #ifdef RFLO
67 #include "Indexing.h"
68 #endif
69 #ifdef RFLU
73  USE rflu_modmpi
74  USE modinterfaces, ONLY: convectivefluxes, &
79  rflu_setvars, &
83  sourceterms, &
84  updatetbc, &
86 #endif
87 #ifdef PEUL
91 #endif
92 #ifdef INRT
94 #endif
95 #ifdef RADI
97 #endif
98 #ifdef PERI
100 !#ifdef RFLO
101 ! USE PERI_ModHybridDES, ONLY : PERI_CoMeanCorrection
102 !#endif
103 #endif
104 #ifdef TURB
108 #ifdef RFLO
113 #endif
114 #endif
115 
116  IMPLICIT NONE
117 
118 #ifdef GENX
119  include 'roccomf90.h'
120 #endif
121 
122 ! ... parameters
123  TYPE(t_region), POINTER :: regions(:)
124 
125  LOGICAL :: ftermnew, residfterm
126 
127 ! ... loop variables
128  INTEGER :: ireg, ireglocal, ic, istage
129 
130 ! ... local variables
131 #ifdef RFLO
132  INTEGER :: idcbeg, idcend, jdcbeg, jdcend, kdcbeg, kdcend
133  INTEGER :: ilev, icoff, ijcoff
134 #endif
135  INTEGER :: ibc, iec, iectot, ldiss(5), flowmodel, gasmodel
136 
137  LOGICAL :: movegrid
138 
139 #ifdef RFLO
140  REAL(RFREAL) :: smoocf
141 #endif
142 
143  REAL(RFREAL) :: cfl, ark(5), betrk(5), blend1, fac, adtv
144  REAL(RFREAL) :: alpha, time
145  REAL(RFREAL), POINTER :: cv(:,:), cvold(:,:), dt(:), diss(:,:), rhs(:,:)
146  REAL(RFREAL), POINTER :: vol(:), fterm(:,:)
147 
148  TYPE(t_global), POINTER :: global
149 #ifdef RFLU
150  TYPE(t_region), POINTER :: pregion
151 #endif
152 
153 !******************************************************************************
154 
155  global => regions(1)%global
156 
157  CALL registerfunction( global,'ExplicitMultistage',&
158  'ExplicitMultistage.F90' )
159 
160 #ifdef RFLO
161 ! set time for time-dependent BC data (for dual-time stepping)-----------------
162 
163  time = global%currentTime + global%dtMin
164  alpha = (time-global%timeStamp)/global%dTimeSystem
165 #endif
166 
167 ! loop over stages and regions ------------------------------------------------
168 
169  DO istage=1,regions(1)%global%nrkSteps
170 #ifdef RFLO
171  DO ireg=1,global%nRegions
172  IF (regions(ireg)%procid==global%myProcid .AND. & ! region active and
173  regions(ireg)%active==active) THEN ! on my processor
174 #endif
175 #ifdef RFLU
176  DO ireglocal = 1,global%nRegionsLocal
177  ireg = ireglocal
178 #endif
179  regions(ireg)%irkStep = istage
180 
181 ! ----- get dimensions and pointers
182 
183  ldiss(:) = regions(ireg)%mixtInput%ldiss(:)
184  cfl = regions(ireg)%mixtInput%cfl
185  ark(:) = regions(ireg)%mixtInput%ark(:)
186  betrk(:) = regions(ireg)%mixtInput%betrk(:)
187  flowmodel = regions(ireg)%mixtInput%flowModel
188  gasmodel = regions(ireg)%mixtInput%gasModel
189  movegrid = regions(ireg)%mixtInput%moveGrid
190 
191 #ifdef RFLO
192  ilev = regions(ireg)%currLevel
193 
194  CALL rflo_getdimensdummy( regions(ireg),ilev,idcbeg,idcend, &
195  jdcbeg,jdcend,kdcbeg,kdcend )
196  CALL rflo_getcelloffset( regions(ireg),ilev,icoff,ijcoff )
197  ibc = indijk(idcbeg,jdcbeg,kdcbeg,icoff,ijcoff)
198  iec = indijk(idcend,jdcend,kdcend,icoff,ijcoff)
199  iectot = iec
200 
201  smoocf = regions(ireg)%mixtInput%smoocf
202 
203  cv => regions(ireg)%levels(ilev)%mixt%cv
204  cvold => regions(ireg)%levels(ilev)%mixt%cvOld
205  diss => regions(ireg)%levels(ilev)%mixt%diss
206  rhs => regions(ireg)%levels(ilev)%mixt%rhs
207  vol => regions(ireg)%levels(ilev)%grid%vol
208  dt => regions(ireg)%levels(ilev)%dt
209  IF (residfterm) fterm => regions(ireg)%levels(ilev)%mixt%fterm
210 #endif
211 
212 #ifdef RFLU
213  pregion => regions(ireg)
214 
215  ibc = 1
216  iec = pregion%grid%nCells
217  iectot = pregion%grid%nCellsTot
218 
219  cv => pregion%mixt%cv
220  cvold => pregion%mixt%cvOld
221  diss => pregion%mixt%diss
222  rhs => pregion%mixt%rhs
223  vol => pregion%grid%vol
224  dt => pregion%dt
225  IF (residfterm) fterm => pregion%mixt%fterm
226 #endif
227 
228 #ifdef RFLO
229 ! ----- compute local time step (first stage only)
230 
231  IF (istage == 1) THEN
232  IF (flowmodel == flow_euler) THEN
233  CALL rflo_timestepinviscid( regions(ireg) )
234  ELSE
235  CALL rflo_timestepviscous( regions(ireg) )
236  ENDIF
237  IF (smoocf > 0._rfreal) THEN
238  CALL rflo_residualsmoothingcoeffs( regions(ireg) )
239  END IF ! smoocf
240 #ifdef PEUL
241  IF (global%peulUsed) THEN
242  CALL peul_spectralradii( regions(ireg) )
243 
244  IF (regions(ireg)%peulInput%smoocf > 0._rfreal) THEN
245  CALL peul_residualsmoothingcoeffs( regions(ireg) )
246  ENDIF ! smoocf
247  ENDIF ! peulUsed
248 #endif
249 #ifdef TURB
250  IF (flowmodel == flow_navst .AND. &
251  regions(ireg)%mixtInput%turbModel /= turb_model_none) THEN
252  CALL turb_rflo_ransspectralradii( regions(ireg) )
253 
254  IF (regions(ireg)%turbInput%smoocf > 0._rfreal) THEN
255  CALL turb_rflo_ransressmoothingcoeff( regions(ireg) )
256  ENDIF ! smoocf
257  ENDIF ! flowModel
258 #endif
259  ENDIF
260 #endif
261 
262 ! ----- store previous solution; set dissipation to zero (first stage)
263 
264  IF (istage == 1) THEN
265  DO ic=ibc,iectot
266  cvold(cv_mixt_dens,ic) = cv(cv_mixt_dens,ic)
267  cvold(cv_mixt_xmom,ic) = cv(cv_mixt_xmom,ic)
268  cvold(cv_mixt_ymom,ic) = cv(cv_mixt_ymom,ic)
269  cvold(cv_mixt_zmom,ic) = cv(cv_mixt_zmom,ic)
270  cvold(cv_mixt_ener,ic) = cv(cv_mixt_ener,ic)
271  diss(cv_mixt_dens,ic) = 0._rfreal
272  diss(cv_mixt_xmom,ic) = 0._rfreal
273  diss(cv_mixt_ymom,ic) = 0._rfreal
274  diss(cv_mixt_zmom,ic) = 0._rfreal
275  diss(cv_mixt_ener,ic) = 0._rfreal
276  ENDDO
277  ENDIF
278 
279 ! ----- initialize dissipation (later stages)
280 
281  IF (istage>1 .AND. ldiss(istage)/=0) THEN
282  blend1 = 1._rfreal - betrk(istage)
283  DO ic=ibc,iectot
284  diss(cv_mixt_dens,ic) = blend1*diss(cv_mixt_dens,ic)
285  diss(cv_mixt_xmom,ic) = blend1*diss(cv_mixt_xmom,ic)
286  diss(cv_mixt_ymom,ic) = blend1*diss(cv_mixt_ymom,ic)
287  diss(cv_mixt_zmom,ic) = blend1*diss(cv_mixt_zmom,ic)
288  diss(cv_mixt_ener,ic) = blend1*diss(cv_mixt_ener,ic)
289  ENDDO
290  ENDIF
291 
292 #ifdef RFLU
293 ! ----- Compute cell gradients for higher-order scheme
294 
295  IF ( regions(ireg)%mixtInput%spaceOrder > 1 ) THEN
296  pregion => regions(ireg)
297  CALL rflu_convertcvcons2prim(pregion,cv_mixt_state_duvwp)
298  CALL rflu_computegradcells(pregion,cv_mixt_dens,cv_mixt_pres, &
299  grc_mixt_dens,grc_mixt_pres, &
300  pregion%mixt%cv,pregion%mixt%gradCell)
301  CALL rflu_computegradcellseno(pregion,grc_mixt_dens,grc_mixt_pres, &
302  pregion%mixt%gradCell)
303  CALL rflu_limitgradcellssimple(pregion,cv_mixt_dens,cv_mixt_pres, &
304  grc_mixt_dens,grc_mixt_pres, &
305  pregion%mixt%cv,pregion%mixt%cvInfo, &
306  pregion%mixt%gradCell)
307  CALL rflu_convertcvprim2cons(pregion,cv_mixt_state_cons)
308  END IF ! regions
309 #endif
310 
311 #ifdef TURB
312  IF (flowmodel == flow_navst .AND. &
313  regions(ireg)%mixtInput%turbModel /= turb_model_none) &
314  CALL turb_emsinit( regions(ireg),istage )
315 #endif
316 
317 ! ----- compute numerical dissipation
318 
319  IF (ldiss(istage) /= 0) THEN
320  CALL numericaldissipation( regions(ireg) )
321  ENDIF
322 
323 #ifdef TURB
324  IF (ldiss(istage) /= 0 .AND. flowmodel == flow_navst .AND. &
325  regions(ireg)%mixtInput%turbModel /= turb_model_none) THEN
326  CALL turb_ransnumericaldissipation( regions(ireg) )
327  ENDIF
328 #endif
329 
330 ! ----- compute viscous fluxes
331 
332  IF (flowmodel==flow_navst .AND. ldiss(istage)/=0) THEN
333  CALL viscousfluxes( regions(ireg) )
334  ENDIF
335 
336 ! ----- compute convective fluxes; form residual
337 
338  CALL convectivefluxes( regions(ireg) )
339 
340 #ifdef TURB
341  IF (flowmodel == flow_navst .AND. &
342  regions(ireg)%mixtInput%turbModel /= turb_model_none) THEN
343  CALL turb_ransconvectivefluxes( regions(ireg) )
344  ENDIF
345 #endif
346 
347 ! ----- add source terms
348 
349  CALL sourceterms( regions(ireg) )
350 
351 #ifdef INRT
352  IF (global%inrtUsed) THEN
353  CALL inrt_sourceterms( regions(ireg) )
354  ENDIF
355 #endif
356 #ifdef RADI
357  CALL radi_sourceterms( regions(ireg) )
358 #endif
359 #ifdef PERI
360  CALL peri_sourceterms( regions(ireg) )
361 #endif
362 #ifdef TURB
363  IF (flowmodel == flow_navst .AND. &
364  regions(ireg)%mixtInput%turbModel /= turb_model_none) THEN
365  CALL turb_ranssourceterms( regions(ireg) )
366  ENDIF
367 #endif
368 
369 ! ----- zero out residuals in dummy cells
370 
371 #ifdef RFLO
372  CALL rflo_zerodummycells( regions(ireg),rhs )
373 #endif
374 #ifdef RFLU
375  pregion => regions(ireg)
376  CALL rflu_zerovirtualcellvars(pregion,rhs)
377 #endif
378 #ifdef TURB
379  IF (flowmodel == flow_navst .AND. &
380  regions(ireg)%mixtInput%turbModel /= turb_model_none) THEN
381  CALL turb_ranszerodummycells( regions(ireg) )
382  ENDIF
383 #endif
384 
385 ! ----- compute new forcing term
386 
387  IF (ftermnew) THEN
388  DO ic=ibc,iectot
389  fterm(cv_mixt_dens,ic) = fterm(cv_mixt_dens,ic) - &
390  rhs(cv_mixt_dens,ic)
391  fterm(cv_mixt_xmom,ic) = fterm(cv_mixt_xmom,ic) - &
392  rhs(cv_mixt_xmom,ic)
393  fterm(cv_mixt_ymom,ic) = fterm(cv_mixt_ymom,ic) - &
394  rhs(cv_mixt_ymom,ic)
395  fterm(cv_mixt_zmom,ic) = fterm(cv_mixt_zmom,ic) - &
396  rhs(cv_mixt_zmom,ic)
397  fterm(cv_mixt_ener,ic) = fterm(cv_mixt_ener,ic) - &
398  rhs(cv_mixt_ener,ic)
399  ENDDO
400  ENDIF
401 
402  ftermnew = .false.
403 
404 ! ----- residual (+ forcing term) * time step / volume
405 
406  fac = ark(istage)*cfl
407 
408  IF (residfterm) THEN
409  DO ic=ibc,iec
410  adtv = fac*dt(ic)/vol(ic)
411  rhs(cv_mixt_dens,ic) = adtv*(rhs(cv_mixt_dens,ic)+ &
412  fterm(cv_mixt_dens,ic))
413  rhs(cv_mixt_xmom,ic) = adtv*(rhs(cv_mixt_xmom,ic)+ &
414  fterm(cv_mixt_xmom,ic))
415  rhs(cv_mixt_ymom,ic) = adtv*(rhs(cv_mixt_ymom,ic)+ &
416  fterm(cv_mixt_ymom,ic))
417  rhs(cv_mixt_zmom,ic) = adtv*(rhs(cv_mixt_zmom,ic)+ &
418  fterm(cv_mixt_zmom,ic))
419  rhs(cv_mixt_ener,ic) = adtv*(rhs(cv_mixt_ener,ic)+ &
420  fterm(cv_mixt_ener,ic))
421  ENDDO
422  ELSE
423  DO ic=ibc,iec
424  adtv = fac*dt(ic)/vol(ic)
425  rhs(cv_mixt_dens,ic) = adtv*rhs(cv_mixt_dens,ic)
426  rhs(cv_mixt_xmom,ic) = adtv*rhs(cv_mixt_xmom,ic)
427  rhs(cv_mixt_ymom,ic) = adtv*rhs(cv_mixt_ymom,ic)
428  rhs(cv_mixt_zmom,ic) = adtv*rhs(cv_mixt_zmom,ic)
429  rhs(cv_mixt_ener,ic) = adtv*rhs(cv_mixt_ener,ic)
430  ENDDO
431  ENDIF
432 
433 #ifdef RFLO
434 ! ----- implicit residual smoothing
435 
436  IF (smoocf > 0._rfreal) THEN
437  CALL rflo_zerodummycells( regions(ireg),rhs )
438  CALL rflo_residualsmoothing( regions(ireg) )
439  ENDIF
440 #ifdef PEUL
441  IF (global%peulUsed .AND. &
442  regions(ireg)%peulInput%smoocf > 0._rfreal) THEN
443  CALL rflo_zerodummycells( regions(ireg), &
444  regions(ireg)%levels(ilev)%peul%rhs )
445  CALL peul_residualsmoothingcoeffs( regions(ireg) )
446  ENDIF
447 #endif
448 #ifdef TURB
449  IF (flowmodel == flow_navst .AND. &
450  regions(ireg)%mixtInput%turbModel /= turb_model_none .AND. &
451  regions(ireg)%turbInput%smoocf > 0._rfreal) THEN
452  CALL turb_ranszerodummycells( regions(ireg) )
453  CALL turb_rflo_ransressmoothing( regions(ireg) )
454  ENDIF
455 #endif
456 #endif
457 
458 ! ----- update solution
459 
460  IF (global%solverType == solv_implicit) THEN
461  fac = 1.5_rfreal*ark(istage)*cfl/global%dtMin
462  DO ic=ibc,iec
463  adtv = 1._rfreal/(1._rfreal+fac*dt(ic))
464  cv(cv_mixt_dens,ic) = cvold(cv_mixt_dens,ic) - &
465  adtv*rhs(cv_mixt_dens,ic)
466  cv(cv_mixt_xmom,ic) = cvold(cv_mixt_xmom,ic) - &
467  adtv*rhs(cv_mixt_xmom,ic)
468  cv(cv_mixt_ymom,ic) = cvold(cv_mixt_ymom,ic) - &
469  adtv*rhs(cv_mixt_ymom,ic)
470  cv(cv_mixt_zmom,ic) = cvold(cv_mixt_zmom,ic) - &
471  adtv*rhs(cv_mixt_zmom,ic)
472  cv(cv_mixt_ener,ic) = cvold(cv_mixt_ener,ic) - &
473  adtv*rhs(cv_mixt_ener,ic)
474  ENDDO
475  ELSE
476  DO ic=ibc,iec
477  cv(cv_mixt_dens,ic) = cvold(cv_mixt_dens,ic) - rhs(cv_mixt_dens,ic)
478  cv(cv_mixt_xmom,ic) = cvold(cv_mixt_xmom,ic) - rhs(cv_mixt_xmom,ic)
479  cv(cv_mixt_ymom,ic) = cvold(cv_mixt_ymom,ic) - rhs(cv_mixt_ymom,ic)
480  cv(cv_mixt_zmom,ic) = cvold(cv_mixt_zmom,ic) - rhs(cv_mixt_zmom,ic)
481  cv(cv_mixt_ener,ic) = cvold(cv_mixt_ener,ic) - rhs(cv_mixt_ener,ic)
482  ENDDO
483  ENDIF
484 
485 #ifdef PERI
486  IF (regions(ireg)%periInput%flowKind /= off) THEN
487  CALL peri_solutionupdate( regions(ireg) )
488  ENDIF
489 #endif
490 #ifdef TURB
491  IF (flowmodel == flow_navst .AND. &
492  regions(ireg)%mixtInput%turbModel /= turb_model_none) THEN
493  CALL turb_solutionupdate( regions(ireg),istage,ibc,iec )
494  ENDIF
495 #endif
496 
497 ! ----- check for positivity/validity -----------------------------------------
498 
499 #ifdef RFLO
500  CALL rflo_checkvalidity( regions(ireg) )
501 #endif
502 
503 #ifdef RFLU
504  pregion => regions(ireg)
505  CALL rflu_checkvaliditywrapper(pregion)
506  CALL rflu_checkpositivitywrapper(pregion)
507 #endif
508 
509 #ifdef RFLO
510 ! ----- send conservative variables to other processors
511 
512  CALL rflo_boundaryconditionssend( regions,ireg )
513 
514 #ifdef TURB
515  IF (flowmodel == flow_navst .AND. &
516  regions(ireg)%mixtInput%turbModel /= turb_model_none) THEN
517  CALL turb_rflo_ransbndconditionssend( regions,ireg )
518  ENDIF
519 #endif
520 #endif
521 #ifdef RFLU
522 ! ----- exchange conservative variables with other processors
523 
524  pregion => regions(ireg)
525  CALL rflu_mpi_isendwrapper(pregion)
526  CALL rflu_setvars(pregion,1,pregion%grid%nCells)
527 #endif
528 
529 ! ----- update dependent variables
530 
531 #ifdef RFLO
532  IF (gasmodel == gas_model_tcperf) THEN ! cp, Mol=const.
533  CALL mixtureproperties( regions(ireg),ibc,iec,.false. )
534  ELSE
535  CALL mixtureproperties( regions(ireg),ibc,iec,.true. )
536  ENDIF
537 #endif
538 
539 #ifdef RFLO
540  ENDIF ! region on this processor and active
541 #endif
542  ENDDO ! iReg
543 
544 #ifdef RFLO
545 ! - facilitate global non-dummy communication ---------------------------------
546 
547  CALL globalcommunicationmp( regions )
548 
549 #ifdef GENX
550 ! - send fluids density at interface
551 
552  CALL com_call_function( global%genxHandleBc,2,alpha,1 )
553 
554  DO ireg=1,global%nRegions
555  IF (regions(ireg)%procid==global%myProcid .AND. & ! region active and
556  regions(ireg)%active==active) THEN ! on my processor
557  IF (regions(ireg)%mixtInput%externalBc) THEN
558  CALL rflo_sendboundaryvaluesalpha( regions(ireg) )
559  ENDIF
560  ENDIF
561  ENDDO
562 
563 ! - get BC values at the interface; set BC values in dummy cells
564 
565  CALL com_call_function( global%genxHandleBc,2,alpha,2 )
566 #endif
567 
568  DO ireg=1,global%nRegions
569  IF (regions(ireg)%procid==global%myProcid .AND. & ! region active and
570  regions(ireg)%active==active) THEN ! on my processor
571  IF (regions(ireg)%mixtInput%externalBc) THEN
572  CALL rflo_getboundaryvalues( regions(ireg) )
573  ENDIF
574  IF (global%solverType == solv_implicit) THEN
575  CALL updatetbc( regions(ireg),time,global%dtMin,.true. )
576  ENDIF
577  CALL rflo_boundaryconditionsset( regions,ireg )
578 #ifdef TURB
579  IF (flowmodel == flow_navst .AND. &
580  regions(ireg)%mixtInput%turbModel /= turb_model_none) THEN
581  CALL turb_rflo_ransbndconditionsset( regions,ireg )
582  ENDIF
583 #endif
584  ENDIF
585  ENDDO
586 
587 ! - receive variables from other processors; send BC values to external code
588 
589  DO ireg=1,global%nRegions
590  IF (regions(ireg)%procid==global%myProcid .AND. & ! region active and
591  regions(ireg)%active==active) THEN ! on my processor
592  CALL rflo_boundaryconditionsrecv( regions,ireg )
593 #ifdef TURB
594  IF (flowmodel == flow_navst .AND. &
595  regions(ireg)%mixtInput%turbModel /= turb_model_none) THEN
596  CALL turb_rflo_ransbndconditionsrecv( regions,ireg )
597  ENDIF
598 #endif
599  ENDIF
600  ENDDO
601 
602 ! - clear send requests
603 
604  DO ireg=1,global%nRegions
605  IF (regions(ireg)%procid==global%myProcid .AND. & ! region active and
606  regions(ireg)%active==active) THEN ! on my processor
607  CALL rflo_clearsendrequests( regions,ireg,.false. )
608 #ifdef TURB
609  IF (flowmodel == flow_navst .AND. &
610  regions(ireg)%mixtInput%turbModel /= turb_model_none) THEN
611  CALL turb_rflo_ransclearsendrequests( regions,ireg )
612  ENDIF
613 #endif
614  ENDIF
615  ENDDO
616 
617 #ifdef PERI
618 ! DO iReg=1,global%nRegions
619 ! IF (regions(iReg)%procid==global%myProcid .AND. & ! region active and
620 ! regions(iReg)%active==ACTIVE) THEN ! on my processor
621 ! IF (regions(iReg)%periInput%flowKind /= OFF) THEN
622 ! CALL PERI_CoMeanCorrection( regions(iReg) )
623 ! ENDIF
624 ! ENDIF
625 ! ENDDO
626 #endif
627 
628 #endif
629 
630 
631 
632 #ifdef RFLU
633  CALL rflu_mpi_copywrapper(regions)
634 
635  DO ireg = 1,global%nRegionsLocal
636  pregion => regions(ireg)
637 
638  CALL rflu_mpi_recvwrapper(pregion)
639  CALL rflu_setvars(pregion,pregion%grid%nCells+1,pregion%grid%nCellsTot)
640  END DO ! iReg
641 
642  DO ireg = 1,global%nRegionsLocal
643  pregion => regions(ireg)
644 
645  CALL rflu_mpi_clearrequestwrapper(pregion)
646  END DO ! iReg
647 #endif
648 
649 
650  ENDDO ! istage
651 
652 ! finalize --------------------------------------------------------------------
653 
654  CALL deregisterfunction( global )
655 
656 END SUBROUTINE explicitmultistage
657 
658 !******************************************************************************
659 !
660 ! RCS Revision history:
661 !
662 ! $Log: ExplicitMultistage.F90,v $
663 ! Revision 1.15 2008/12/06 08:44:09 mtcampbe
664 ! Updated license.
665 !
666 ! Revision 1.14 2008/11/19 22:17:22 mtcampbe
667 ! Added Illinois Open Source License/Copyright
668 !
669 ! Revision 1.13 2006/03/26 20:21:14 haselbac
670 ! Changed to wrappers bcos of GL model
671 !
672 ! Revision 1.12 2005/12/03 19:45:05 haselbac
673 ! Apparent bug fix: Separated call to RFLU_MPI_ClearRequestWrapper into separate loop
674 !
675 ! Revision 1.11 2005/10/31 21:09:34 haselbac
676 ! Changed specModel and SPEC_MODEL_NONE
677 !
678 ! Revision 1.10 2005/10/05 13:47:23 haselbac
679 ! Adapted to new module for cell grads
680 !
681 ! Revision 1.9 2005/07/13 17:26:20 haselbac
682 ! Bug fix: Adapted to changes to RFLU_LimitGradCells
683 !
684 ! Revision 1.8 2005/05/16 20:38:42 haselbac
685 ! Renamed RFLU_ZeroDummyCells, moved computation of dt into RFLU_TimeStepping
686 !
687 ! Revision 1.7 2005/04/29 00:06:09 haselbac
688 ! Added routines to clear send requests
689 !
690 ! Revision 1.6 2005/04/15 15:06:01 haselbac
691 ! Converted to MPI
692 !
693 ! Revision 1.5 2005/04/06 01:59:42 wasistho
694 ! mv call to PERI_CoMeanCorrection to after BC treatment, commented for now
695 !
696 ! Revision 1.4 2005/03/10 02:08:25 wasistho
697 ! commented PERI_coMeanCorrection temporarily for testing
698 !
699 ! Revision 1.3 2005/03/07 05:05:18 wasistho
700 ! install hybrid DESSA turbulence model
701 !
702 ! Revision 1.2 2004/12/28 22:49:15 wasistho
703 ! moved RFLO_Bcond* and RFLO_BoundaryCond* routines into RFLO_ModBoundaryConditions
704 !
705 ! Revision 1.1 2004/12/01 16:48:30 haselbac
706 ! Initial revision after changing case
707 !
708 ! Revision 1.68 2004/11/17 23:44:33 wasistho
709 ! used generic RK-update for rocturb
710 !
711 ! Revision 1.67 2004/11/14 19:34:26 haselbac
712 ! Replaced call to mixtureProperties by RFLU_SetVars
713 !
714 ! Revision 1.66 2004/10/19 19:25:34 haselbac
715 ! Adapted calls to time step routines
716 !
717 ! Revision 1.65 2004/07/26 19:08:59 wasistho
718 ! add RFLO_CheckValidity
719 !
720 ! Revision 1.64 2004/03/27 03:02:15 wasistho
721 ! added ifdef RFLO within ifdef TURB
722 !
723 ! Revision 1.63 2004/03/20 00:26:35 wasistho
724 ! set turb_rflo_ransNumericalDiss to turb_ransNumerical..
725 !
726 ! Revision 1.62 2004/03/19 02:39:55 wasistho
727 ! renamed TURB_RFLO_RansZeroDummyCells to TURB_RansZeroDummyCells
728 !
729 ! Revision 1.61 2004/03/11 03:32:13 wasistho
730 ! changed rocturb nomenclature
731 !
732 ! Revision 1.60 2004/03/05 22:09:00 jferry
733 ! created global variables for peul, plag, and inrt use
734 !
735 ! Revision 1.59 2004/03/02 21:49:21 jferry
736 ! Added inrtUsed flag to mixture data structure
737 !
738 ! Revision 1.58 2004/02/26 21:13:55 wasistho
739 ! changed TURB_ransEmsInit to TURB_emsInit
740 !
741 ! Revision 1.57 2004/01/29 22:52:41 haselbac
742 ! Added info argument to cell-gradient routine call
743 !
744 ! Revision 1.56 2003/12/04 03:22:59 haselbac
745 ! Added second-order scheme, viscous fluxes, validity check
746 !
747 ! Revision 1.55 2003/11/25 21:01:39 haselbac
748 ! Added routine to update dummy cells
749 !
750 ! Revision 1.54 2003/11/20 16:40:35 mdbrandy
751 ! Backing out RocfluidMP changes from 11-17-03
752 !
753 ! Revision 1.51 2003/10/27 04:49:29 wasistho
754 ! replace ransCentralDiss by ransNumericalDiss.
755 !
756 ! Revision 1.50 2003/10/21 03:57:42 wasistho
757 ! put turb and peul spectralradii before its smoothingcoef
758 !
759 ! Revision 1.49 2003/10/16 20:12:27 wasistho
760 ! completed incorporation of RaNS/DES
761 !
762 ! Revision 1.48 2003/10/03 20:12:11 wasistho
763 ! initial installation of turbModel SA and DES
764 !
765 ! Revision 1.47 2003/09/26 21:45:34 fnajjar
766 ! Modified ModInterfaces calls to proper physical modules
767 !
768 ! Revision 1.46 2003/08/28 20:32:48 wasistho
769 ! excluced ModInterfacesTurbulence,Radiation,Periodic from ModInterfaces
770 !
771 ! Revision 1.45 2003/08/13 02:19:42 wasistho
772 ! added call to radiation source term routine
773 !
774 ! Revision 1.44 2003/07/22 01:52:40 haselbac
775 ! Bug fix: dual-time stepping only for RFLO, lead to core dump
776 !
777 ! Revision 1.43 2003/07/03 21:48:44 jblazek
778 ! Implemented dual-time stepping.
779 !
780 ! Revision 1.42 2003/05/15 02:57:02 jblazek
781 ! Inlined index function.
782 !
783 ! Revision 1.41 2003/05/09 17:01:03 jiao
784 ! Renamed the COM_call_function_handlers to COM_call_function.
785 !
786 ! Revision 1.40 2003/04/05 02:01:08 wasistho
787 ! regions to region in PERI_solutionUpdate
788 !
789 ! Revision 1.39 2003/03/29 03:26:21 wasistho
790 ! install ROCPERI
791 !
792 ! Revision 1.38 2003/03/15 16:17:58 haselbac
793 ! Added zeroing of dummies (?) and changed FEM to IDXL
794 !
795 ! Revision 1.37 2003/03/05 20:41:21 jiao
796 ! ACH: Split update inbuff calls into get correct dependency of rhof on mdot
797 !
798 ! Revision 1.36 2003/03/04 22:12:34 jferry
799 ! Initial import of Rocinteract
800 !
801 ! Revision 1.35 2003/02/11 22:52:50 jferry
802 ! Initial import of Rocsmoke
803 !
804 ! Revision 1.34 2002/12/06 22:29:25 jblazek
805 ! Corrected bug for geometry exchange between minimal patches.
806 !
807 ! Revision 1.33 2002/10/27 18:47:32 haselbac
808 ! Added call to RFLU_CheckPositivity
809 !
810 ! Revision 1.32 2002/10/17 06:50:42 jiao
811 ! Changed 0. to 0._RFREAL.
812 !
813 ! Revision 1.31 2002/10/12 20:21:25 jblazek
814 ! Rearranged UpdateTbc (after getting values from GenX);
815 ! corrected bug in externalBc.
816 !
817 ! Revision 1.30 2002/10/05 18:34:08 haselbac
818 ! Moved ifdef CHARM inside ifdef RFLU
819 !
820 ! Revision 1.29 2002/09/20 22:22:35 jblazek
821 ! Finalized integration into GenX.
822 !
823 ! Revision 1.27 2002/09/09 13:57:49 haselbac
824 ! added viscous routines, bug fix for iec, mixtInput under regions
825 !
826 ! Revision 1.26 2002/09/05 17:40:20 jblazek
827 ! Variable global moved into regions().
828 !
829 ! Revision 1.25 2002/08/29 21:53:18 jblazek
830 ! Added support for moving grids.
831 !
832 ! Revision 1.24 2002/08/16 21:33:47 jblazek
833 ! Changed interface to MixtureProperties.
834 !
835 ! Revision 1.23 2002/08/15 19:48:05 jblazek
836 ! Implemented grid deformation capability.
837 !
838 ! Revision 1.22 2002/07/25 14:50:52 haselbac
839 ! Added RFLU_ModFEM and call for update of dummy cells
840 !
841 ! Revision 1.21 2002/07/23 20:28:19 wasistho
842 ! #ifdef RFLO around ViscousFluxes removed
843 !
844 ! Revision 1.20 2002/07/22 17:01:23 jblazek
845 ! Removed MPI_Barrier at the end of stage loop.
846 !
847 ! Revision 1.19 2002/07/05 23:20:46 jblazek
848 ! Corrected bug in perfgasDependentVars.F90; did some cosmetics.
849 !
850 ! Revision 1.18 2002/06/27 15:46:27 haselbac
851 ! Added FEM calls for communication - not activated yet
852 !
853 ! Revision 1.17 2002/06/14 20:11:48 haselbac
854 ! Deleted ModLocal, renamed local%nRegions to global%nRegionsLocal
855 !
856 ! Revision 1.16 2002/06/07 16:40:36 jblazek
857 ! Grid & solution for all regions in one file.
858 !
859 ! Revision 1.15 2002/05/28 14:14:39 haselbac
860 ! Enclosed viscous fluxes within RFLO conditional statement
861 !
862 ! Revision 1.14 2002/05/28 13:44:05 haselbac
863 ! Cosmetic changes only?
864 !
865 ! Revision 1.13 2002/05/21 01:51:56 wasistho
866 ! add viscous terms
867 !
868 ! Revision 1.12 2002/05/04 16:31:49 haselbac
869 ! Added RFLU statements
870 !
871 ! Revision 1.11 2002/04/12 17:36:23 jblazek
872 ! Added timer.
873 !
874 ! Revision 1.10 2002/04/01 19:36:07 jblazek
875 ! Added routine to clear send requests.
876 !
877 ! Revision 1.9 2002/03/30 00:50:49 jblazek
878 ! Cleaned up with flint.
879 !
880 ! Revision 1.8 2002/03/29 23:15:22 jblazek
881 ! Corrected bug in MPI send.
882 !
883 ! Revision 1.7 2002/03/18 22:25:45 jblazek
884 ! Finished multiblock and MPI.
885 !
886 ! Revision 1.6 2002/02/21 23:25:05 jblazek
887 ! Blocks renamed as regions.
888 !
889 ! Revision 1.5 2002/02/09 01:47:01 jblazek
890 ! Added multi-probe option, residual smoothing, physical time step.
891 !
892 ! Revision 1.4 2002/01/28 23:55:22 jblazek
893 ! Added flux computation (central scheme).
894 !
895 ! Revision 1.3 2002/01/23 23:37:32 jblazek
896 ! All blocks passed to time integration routines.
897 !
898 ! Revision 1.2 2002/01/23 03:51:24 jblazek
899 ! Added low-level time-stepping routines.
900 !
901 ! Revision 1.1 2002/01/16 22:03:34 jblazek
902 ! Added time-stepping routines.
903 !
904 !******************************************************************************
905 
906 
907 
908 
909 
910 
911 
subroutine rflu_setvars(pRegion, icgBeg, icgEnd)
subroutine rflu_timestepviscous(pRegion)
subroutine turb_emsinit(region, istage)
**********************************************************************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 idcend
subroutine radi_sourceterms(region)
subroutine turb_ranszerodummycells(region)
subroutine rflu_timestepinviscid(pRegion)
subroutine peul_spectralradii(region)
subroutine peri_sourceterms(region)
NT rhs
subroutine turb_rflo_ransspectralradii(region)
subroutine, public rflu_mpi_isendwrapper(pRegion)
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
subroutine rflu_zerovirtualcellvars(pRegion, var)
**********************************************************************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 ic
subroutine, public rflu_mpi_clearrequestwrapper(pRegion)
subroutine turb_ransconvectivefluxes(region)
subroutine turb_rflo_ransressmoothing(region)
subroutine, public rflu_limitgradcellssimple(pRegion, iBegVar, iEndVar, iBegGrad, iEndGrad, var, varInfo, grad)
subroutine explicitmultistage(regions, ftermNew, residFterm)
subroutine, public rflu_convertcvcons2prim(pRegion, cvStateFuture)
subroutine rflo_getdimensdummy(region, iLev, idcbeg, idcend, jdcbeg, jdcend, kdcbeg, kdcend)
subroutine turb_rflo_ransbndconditionsrecv(regions, iReg)
**********************************************************************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 kdcbeg
subroutine rflu_checkpositivitywrapper(pRegion)
subroutine rflo_sendboundaryvaluesalpha(region)
subroutine, public rflo_boundaryconditionssend(regions, iReg)
subroutine updatetbc(region, t, dt, final)
Definition: UpdateTbc.F90:43
subroutine, public rflu_convertcvprim2cons(pRegion, cvStateFuture)
subroutine, public rflu_mpi_recvwrapper(pRegion)
subroutine, public rflo_boundaryconditionsrecv(regions, iReg)
subroutine rflo_getcelloffset(region, iLev, iCellOffset, ijCellOffset)
**********************************************************************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 idcbeg
subroutine peul_residualsmoothing(region)
subroutine rflo_zerodummycells(region, var)
subroutine turb_solutionupdate(region, istage, ibc, iec)
subroutine rflo_sendboundaryvalues(region, initialize)
subroutine peri_solutionupdate(region)
subroutine rflo_residualsmoothing(region)
subroutine inrt_sourceterms(region)
subroutine peul_residualsmoothingcoeffs(region)
subroutine rflo_getboundaryvalues(region)
subroutine rflo_checkvalidity(region)
subroutine rflo_clearsendrequests(regions, iReg, geometry)
subroutine turb_rflo_ransbndconditionssend(regions, iReg)
**********************************************************************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 jdcend
subroutine viscousfluxes(region)
subroutine convectivefluxes(region)
subroutine globalcommunicationmp(regions)
subroutine, public rflo_boundaryconditionsset(regions, iReg)
**********************************************************************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 jdcbeg
subroutine turb_rflo_ransressmoothingcoeff(region)
subroutine turb_ranssourceterms(region)
subroutine turb_rflo_ransclearsendrequests(regions, iReg)
subroutine rflo_timestepviscous(region)
subroutine, public rflu_mpi_copywrapper(regions)
subroutine mixtureproperties(region, inBeg, inEnd, gasUpdate)
unsigned char alpha() const
Definition: Color.h:75
subroutine turb_ransnumericaldissipation(region)
subroutine deregisterfunction(global)
Definition: ModError.F90:469
subroutine rflo_residualsmoothingcoeffs(region)
subroutine sourceterms(region)
Definition: SourceTerms.F90:44
subroutine rflu_checkvaliditywrapper(pRegion)
subroutine rflo_timestepinviscid(region)
subroutine numericaldissipation(region)
subroutine turb_rflo_ransbndconditionsset(regions, iReg)