Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
RFLU_ModTimeZoom.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: Collection of routines related to solution zooming..
26 !
27 ! Description: None.
28 !
29 ! Notes: None.
30 !**********************************************************************
31 
33 
34  USE moddatatypes !add use list
35  USE modparameters
36  USE moderror
37  USE moddatastruct, ONLY: t_region
38  USE modglobal, ONLY: t_global
39  USE modgrid, ONLY: t_grid
40  USE modbndpatch, ONLY: t_patch
41  USE modmpi
42 
43  IMPLICIT NONE
44 
46  REAL(RFREAL),Dimension(CV_MIXT_DENS:CV_MIXT_ENER) :: CvBulk,resbar_Qbulk,&
47  CvdVdtBulk
48  END TYPE t_timezoom
49 
50  PRIVATE
51  PUBLIC :: rflu_timezoomdriver,t_timezoom,timezoom, &
53 
54 
55 !Module Local varaibles
56  TYPE (t_timezoom) :: TimeZoom
57 
58 ! ******************************************************************************
59 ! Declarations and definitions
60 ! ******************************************************************************
61 
62  CHARACTER(CHRLEN) :: &
63  RCSIdentString = '$RCSfile: RFLU_ModTimeZoom.F90,v $'
64 
65 ! ******************************************************************************
66 ! Routines
67 ! ******************************************************************************
68 
69 CONTAINS
70 
71 
72  SUBROUTINE rflu_timezoomdriver(regions)
73  IMPLICIT NONE
74 
75 !---Dummy
76  TYPE(t_region), POINTER :: regions(:)
77 
78  CALL rflu_timezoomcomputebulkvars(regions)
79  CALL rflu_timezoomsumaddsource(regions)
80 
81  RETURN
82  END SUBROUTINE rflu_timezoomdriver
83 
84 
85  SUBROUTINE rflu_timezoomcomputebulkvars(regions)
86  IMPLICIT NONE
87 
88 !---Dummy
89  TYPE(t_region), POINTER :: regions(:)
90 !---Local
91  TYPE(t_region), POINTER :: pregion
92  TYPE(t_global), POINTER :: global
93  REAL(RFREAL), DIMENSION(:), POINTER :: vol,volold
94  REAL(RFREAL), DIMENSION(:,:), POINTER :: cv
95  INTEGER :: ireg,icell,i,nvars,ncvvars
96  REAL(RFREAL) ::x, localintegvol,globalintegvol,dvdt_i, volbulkold
97  REAL(RFREAL),DIMENSION(2*(CV_MIXT_ENER-CV_MIXT_DENS+1)+2) :: bulkvarslocal,bulkvarsglobal
98 !---For submerged nozzles
99  REAL(RFREAL) :: y, z
100  REAL(RFREAL) :: rnozzleinlet2
101 
102  global => regions(1)%global
103 
104  rnozzleinlet2 = global%tzNozRad**2
105 
106  nvars = ubound(bulkvarslocal,1)-lbound(bulkvarslocal,1)+1
107  ncvvars = cv_mixt_ener-cv_mixt_dens+1
108  bulkvarslocal = 0_rfreal
109 
110  DO ireg = 1,global%nRegionsLocal
111 
112 ! Region Pointers
113  pregion => regions(ireg)
114  vol => pregion%grid%vol
115  volold => pregion%gridOld%vol
116  cv => pregion%mixt%cv
117 
118 ! Sum over Cells
119  IF (.NOT. global%tzSubNoz) THEN
120  DO icell = 1,pregion%grid%nCells
121  x = pregion%grid%cofg(global%tzCoordLong,icell)
122  IF(x > global%tzMinPlane .AND. x < global%tzMaxPlane) THEN
123  dvdt_i = (vol(icell)-volold(icell))/max(global%dtMin, &
124  tiny(1.0_rfreal))
125  bulkvarslocal = bulkvarslocal + (/ (cv(i,icell)*vol(icell), &
126  i=cv_mixt_dens,cv_mixt_ener),vol(icell),volold(icell), &
127  (cv(i,icell)*dvdt_i,i=cv_mixt_dens,cv_mixt_ener)/)
128  ENDIF
129  END DO !iCell
130  ELSE
131 ! Exclude submerged nozzle
132  DO icell = 1,pregion%grid%nCells
133  x = pregion%grid%cofg(global%tzCoordLong,icell)
134  y = pregion%grid%cofg(global%tzCoordTrans1,icell)
135  z = pregion%grid%cofg(global%tzCoordTrans2,icell)
136  IF((x > global%tzMinPlane .AND. x < global%tzNozInlet) .OR. &
137  ((x >= global%tzNozInlet .AND. x < global%tzMaxPlane) .AND. &
138  (y**2 + z**2 > rnozzleinlet2) ) ) THEN
139  dvdt_i = (vol(icell)-volold(icell))/max(global%dtMin, &
140  tiny(1.0_rfreal))
141  bulkvarslocal = bulkvarslocal + (/ (cv(i,icell)*vol(icell), &
142  i=cv_mixt_dens,cv_mixt_ener),vol(icell),volold(icell), &
143  (cv(i,icell)*dvdt_i,i=cv_mixt_dens,cv_mixt_ener)/)
144  ENDIF ! In zoomed volume
145  END DO !iCell
146  ENDIF ! submerged
147  END DO !iReg
148 
149  CALL mpi_allreduce(bulkvarslocal, bulkvarsglobal,nvars, &
150  mpi_rfreal,mpi_sum,global%mpiComm,global%error)
151  IF ( global%error /= err_none ) THEN
152  CALL errorstop(global,err_mpi_trouble,__line__)
153  END IF ! global%errorFlag
154 
155  global%tzVolBulk = bulkvarsglobal(ncvvars+1)
156  volbulkold = bulkvarsglobal(ncvvars+2)
157  timezoom%CvBulk(cv_mixt_dens:cv_mixt_ener) = bulkvarsglobal(1:ncvvars)/global%tzVolBulk
158  timezoom%CvdVdtBulk(cv_mixt_dens:cv_mixt_ener) = bulkvarsglobal(ncvvars+3:nvars)
159 
160  global%tzRadChamber = sqrt(global%tzVolBulk/global%tzLenChamb/global%pi)
161  global%tzEpsNozz = (global%tzThroatRad/global%tzRadChamber)**2.0d0
162 
163 ! is the time difference between pRegion%gridOld and pRegion%grid = global%dtMin !???ZOOM???
164  global%tzDvolBulkDt = (global%tzVolBulk-volbulkold)/max(global%dtMin,tiny(1.0_rfreal))
165 
166 
167  return
168  End Subroutine rflu_timezoomcomputebulkvars
169 
170 
171 
172  Subroutine rflu_timezoomsumaddsource(regions)
175 
176  IMPLICIT NONE
177 
178 !---Dummy
179  TYPE(t_region), POINTER :: regions(:)
180 !---Local
181  TYPE(t_global), POINTER :: global
182  TYPE(t_region), POINTER :: pregion
183  REAL(RFREAL), DIMENSION(:,:), POINTER :: res !use res to conform to Q1D code
184  REAL(RFREAL), DIMENSION(:), POINTER :: vol,volold
185  INTEGER :: ireg,icell,nvars,ivar
186  REAL(RFREAL) :: x,betafill,volbulk,ddt_volbulk,termr1,termr2,termr3,terml1
187 !---For submerged nozzles
188  REAL(RFREAL) :: y, z
189  REAL(RFREAL) :: rnozzleinlet2
190 
191  global => regions(1)%global
192 
193  rnozzleinlet2 = global%tzNozRad**2
194 
195  nvars = cv_mixt_ener-cv_mixt_dens+1
196 
197  betafill = global%zoomFactor
198  volbulk = global%tzVolBulk
199  ddt_volbulk = global%tzDvolBulkDt
200 
201 
202 !sum Residuals
203  call rflu_timezoomsumresiduals(regions)
204 
205 !Add R1
206  DO ireg = 1,global%nRegionsLocal
207  pregion => regions(ireg)
208  res => pregion%mixt%rhs
209  vol => pregion%grid%vol
210  volold => pregion%gridOld%vol
211 
212  IF (.NOT. global%tzSubNoz) THEN
213  DO icell = 1,pregion%grid%nCells
214  x = pregion%grid%cofg(global%tzCoordLong,icell)
215 
216  if(x > global%tzMinPlane .and. x < global%tzMaxPlane) then
217  termr1 = (1_rfreal-betafill)/betafill/max(global%dtMin,tiny(1.0_rfreal))
218  termr1 = rflu_scalegridspeed(pregion,termr1)
219  do ivar = cv_mixt_dens,cv_mixt_ener
220  res(ivar,icell) = res(ivar,icell) + termr1*pregion%mixt%Cv(ivar,icell)*&
221  &(vol(icell)-volold(icell))
222  end do
223  end if ! if x > Xmin & x < Xmax
224 
225  End DO !ic
226  ELSE
227 ! Exclude submerged nozzle
228  DO icell = 1,pregion%grid%nCells
229  x = pregion%grid%cofg(global%tzCoordLong,icell)
230  y = pregion%grid%cofg(global%tzCoordTrans1,icell)
231  z = pregion%grid%cofg(global%tzCoordTrans2,icell)
232  IF((x > global%tzMinPlane .AND. x < global%tzNozInlet) .OR. &
233  ((x >= global%tzNozInlet .AND. x < global%tzMaxPlane) .AND. &
234  (y**2 + z**2 > rnozzleinlet2) ) ) THEN
235 
236  termr1 = (1_rfreal-betafill)/betafill/max(global%dtMin,tiny(1.0_rfreal))
237  termr1 = rflu_scalegridspeed(pregion,termr1)
238  do ivar = cv_mixt_dens,cv_mixt_ener
239  res(ivar,icell) = res(ivar,icell) + termr1*pregion%mixt%Cv(ivar,icell)*&
240  &(vol(icell)-volold(icell))
241  end do
242  ENDIF ! In zoomed volume
243 
244  End DO !ic
245  ENDIF ! submerged
246  End Do !iReg
247 
248 ! Add R2 and R3
249  DO ireg = 1,global%nRegionsLocal
250  pregion => regions(ireg)
251  res => pregion%mixt%rhs
252  vol => pregion%grid%vol
253 
254  IF (.NOT. global%tzSubNoz) THEN
255  DO icell = 1,pregion%grid%nCells
256  x = pregion%grid%cofg(global%tzCoordLong,icell)
257 
258  if(x > global%tzMinPlane .and. x < global%tzMaxPlane) then
259  !---R2
260  termr2 = (betafill-1_rfreal)*vol(icell)/volbulk
261  do ivar = cv_mixt_dens,cv_mixt_ener
262  res(ivar,icell) = res(ivar,icell) + termr2*timezoom%resbar_Qbulk(ivar)
263  end do
264  !---R3
265  termr3 = (betafill-1_rfreal)/betafill*vol(icell)/volbulk*ddt_volbulk
266  termr3 = rflu_scalegridspeed(pregion,termr3)
267  do ivar = cv_mixt_dens,cv_mixt_ener
268  res(ivar,icell) = res(ivar,icell) + termr3*timezoom%CvBulk(ivar)
269  end do
270 
271  end if ! if x > Xmin & x < Xmax
272 
273  End DO !ic
274  ELSE
275 ! Exclude submerged nozzle
276  DO icell = 1,pregion%grid%nCells
277  x = pregion%grid%cofg(global%tzCoordLong,icell)
278  y = pregion%grid%cofg(global%tzCoordTrans1,icell)
279  z = pregion%grid%cofg(global%tzCoordTrans2,icell)
280  IF((x > global%tzMinPlane .AND. x < global%tzNozInlet) .OR. &
281  ((x >= global%tzNozInlet .AND. x < global%tzMaxPlane) .AND. &
282  (y**2 + z**2 > rnozzleinlet2) ) ) THEN
283 
284 !---R2
285  termr2 = (betafill-1_rfreal)*vol(icell)/volbulk
286  do ivar = cv_mixt_dens,cv_mixt_ener
287  res(ivar,icell) = res(ivar,icell) + termr2*timezoom%resbar_Qbulk(ivar)
288  end do
289 !---R3
290  termr3 = (betafill-1_rfreal)/betafill*vol(icell)/volbulk*ddt_volbulk
291  termr3 = rflu_scalegridspeed(pregion,termr3)
292  do ivar = cv_mixt_dens,cv_mixt_ener
293  res(ivar,icell) = res(ivar,icell) + termr3*timezoom%CvBulk(ivar)
294  end do
295  ENDIF ! In zoomed volume
296 
297  End DO !ic
298 
299  ENDIF ! submerged
300 
301  End Do !iReg
302 
303  return
304  End Subroutine rflu_timezoomsumaddsource
305 
306 
307 
308 
309  Subroutine rflu_timezoomsumresiduals(Regions)
310  IMPLICIT NONE
311 
312 !---Dummy
313  TYPE(t_global), POINTER :: global
314 !---Local
315  TYPE(t_region), POINTER :: pregion, regions(:)
316  REAL(RFREAL), DIMENSION(:,:), POINTER :: res !use res to conform to Q1D code
317  INTEGER :: ireg,icell,nvars
318  REAL(RFREAL) ::x, localintegvol,globalintegvol
319  REAL(RFREAL),DIMENSION(CV_MIXT_ENER-CV_MIXT_DENS+1) :: resbarveclocal,resbarvecglobal
320 !---For submerged nozzles
321  REAL(RFREAL) :: y, z
322  REAL(RFREAL) :: rnozzleinlet2
323 
324  global => regions(1)%global
325 
326  rnozzleinlet2 = global%tzNozRad**2
327 
328  nvars = cv_mixt_ener-cv_mixt_dens+1
329 
330  resbarveclocal = 0_rfreal
331  DO ireg = 1,global%nRegionsLocal
332 
333  pregion => regions(ireg)
334  res => pregion%mixt%rhs
335 
336  IF (.NOT. global%tzSubNoz) THEN
337  DO icell = 1,pregion%grid%nCells
338  x = pregion%grid%cofg(global%tzCoordLong,icell)
339  if(x > global%tzMinPlane .and. x < global%tzMaxPlane) then
340  resbarveclocal = resbarveclocal + res(cv_mixt_dens:cv_mixt_ener,icell)
341  end if
342  End DO !iCell
343  ELSE
344 ! Exclude submerged nozzle
345  DO icell = 1,pregion%grid%nCells
346  x = pregion%grid%cofg(global%tzCoordLong,icell)
347  y = pregion%grid%cofg(global%tzCoordTrans1,icell)
348  z = pregion%grid%cofg(global%tzCoordTrans2,icell)
349  IF((x > global%tzMinPlane .AND. x < global%tzNozInlet) .OR. &
350  ((x >= global%tzNozInlet .AND. x < global%tzMaxPlane) .AND. &
351  (y**2 + z**2 > rnozzleinlet2) ) ) THEN
352  resbarveclocal = resbarveclocal + res(cv_mixt_dens:cv_mixt_ener,icell)
353  ENDIF ! In zoomed volume
354  End DO !iCell
355  ENDIF ! submerged
356  End DO
357 
358  CALL mpi_allreduce(resbarveclocal, resbarvecglobal,nvars, &
359  mpi_rfreal,mpi_sum,global%mpiComm,global%error)
360  IF ( global%error /= err_none ) THEN
361  CALL errorstop(global,err_mpi_trouble,__line__)
362  END IF ! global%errorFlag
363 
364  timezoom%resbar_Qbulk(cv_mixt_dens:cv_mixt_ener) = resbarvecglobal(1:nvars)
365 
366 
367 
368  return
369  END SUBROUTINE rflu_timezoomsumresiduals
370 
371 
372 
373 ! ******************************************************************************
374 !
375 ! Purpose: Time UnZoom grid speeds for faces and boundary patches.
376 !
377 ! Description: None.
378 !
379 ! Input:
380 ! pRegion Pointer to region data
381 !
382 ! Output: None.
383 !
384 ! Notes: None.
385 !
386 ! ******************************************************************************
387 
388  SUBROUTINE rflu_unzoomgridspeeds(pRegion)
389 
390  IMPLICIT NONE
391 
392 ! ******************************************************************************
393 ! Declarations and definitions
394 ! ******************************************************************************
395 
396 ! ==============================================================================
397 ! Arguments
398 ! ==============================================================================
399 
400  TYPE(t_region), POINTER :: pregion
401 
402 ! ==============================================================================
403 ! Locals
404 ! ==============================================================================
405 
406  INTEGER :: ifg,ifl,ipatch
407  REAL(RFREAL) :: scalefactor
408  TYPE(t_grid), POINTER :: pgrid
409  TYPE(t_patch), POINTER :: ppatch
410  TYPE(t_global), POINTER :: global
411 
412 ! *****************************************************************************
413 ! Set pointers and variables
414 ! *****************************************************************************
415 
416  global => pregion%global
417  pgrid => pregion%grid
418 
419  scalefactor = 1_rfreal/global%Zoomfactor
420 
421 ! ******************************************************************************
422 ! Scale grid speeds
423 ! ******************************************************************************
424 
425  DO ifg = lbound(pgrid%gs,1),ubound(pgrid%gs,1)
426  pgrid%gs(ifg) = scalefactor*pgrid%gs(ifg)
427  END DO ! ifg
428 
429  DO ipatch = 1,pgrid%nPatches
430  ppatch => pregion%patches(ipatch)
431 
432  DO ifl = lbound(ppatch%gs,1),ubound(ppatch%gs,1)
433  ppatch%gs(ifl) = scalefactor*ppatch%gs(ifl)
434  END DO ! ifl
435  END DO ! iPatch
436 
437 ! ******************************************************************************
438 ! End
439 ! ******************************************************************************
440 
441  END SUBROUTINE rflu_unzoomgridspeeds
442 
443 
444 
445 
446 ! ******************************************************************************
447 !
448 ! Purpose: Time Zoom grid speeds for faces and boundary patches.
449 !
450 ! Description: None.
451 !
452 ! Input:
453 ! pRegion Pointer to region data
454 !
455 ! Output: None.
456 !
457 ! Notes: None.
458 !
459 ! ******************************************************************************
460 
461  SUBROUTINE rflu_zoomgridspeeds(pRegion)
462 
463  IMPLICIT NONE
464 
465 ! ******************************************************************************
466 ! Declarations and definitions
467 ! ******************************************************************************
468 
469 ! ==============================================================================
470 ! Arguments
471 ! ==============================================================================
472 
473  TYPE(t_region), POINTER :: pregion
474 
475 ! ==============================================================================
476 ! Locals
477 ! ==============================================================================
478 
479  INTEGER :: ifg,ifl,ipatch
480  REAL(RFREAL) :: scalefactor
481  TYPE(t_grid), POINTER :: pgrid
482  TYPE(t_patch), POINTER :: ppatch
483  TYPE(t_global), POINTER :: global
484 
485 ! *****************************************************************************
486 ! Set pointers and variables
487 ! *****************************************************************************
488 
489  global => pregion%global
490  pgrid => pregion%grid
491 
492  scalefactor = global%Zoomfactor
493 
494 ! ******************************************************************************
495 ! Scale grid speeds
496 ! ******************************************************************************
497 
498  DO ifg = lbound(pgrid%gs,1),ubound(pgrid%gs,1)
499  pgrid%gs(ifg) = scalefactor*pgrid%gs(ifg)
500  END DO ! ifg
501 
502  DO ipatch = 1,pgrid%nPatches
503  ppatch => pregion%patches(ipatch)
504 
505  DO ifl = lbound(ppatch%gs,1),ubound(ppatch%gs,1)
506  ppatch%gs(ifl) = scalefactor*ppatch%gs(ifl)
507  END DO ! ifl
508  END DO ! iPatch
509 
510 ! ******************************************************************************
511 ! End
512 ! ******************************************************************************
513 
514  END SUBROUTINE rflu_zoomgridspeeds
515 
516 
517 
518 ! ******************************************************************************
519 ! End
520 ! ******************************************************************************
521 
522 END MODULE rflu_modtimezoom
523 
524 
525 ! ******************************************************************************
526 !
527 ! RCS Revision history:
528 !
529 !
530 ! ******************************************************************************
531 
532 
533 
534 
535 
536 
537 
subroutine rflu_timezoomcomputebulkvars(regions)
void int int REAL REAL * y
Definition: read.cpp:74
Vector_n max(const Array_n_const &v1, const Array_n_const &v2)
Definition: Vector_n.h:354
subroutine, public rflu_zoomgridspeeds(pRegion)
real(rfreal) function, public rflu_scalegridspeed(pRegion, fs)
double sqrt(double d)
Definition: double.h:73
subroutine rflu_timezoomsumaddsource(regions)
real(rfreal) function, public rflu_descalegridspeed(pRegion, fs)
void int int int REAL REAL REAL * z
Definition: write.cpp:76
blockLoc i
Definition: read.cpp:79
void int int REAL * x
Definition: read.cpp:74
**********************************************************************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 icell
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
subroutine rflu_timezoomsumresiduals(Regions)
subroutine, public rflu_timezoomdriver(regions)
subroutine, public rflu_unzoomgridspeeds(pRegion)