46 REAL(RFREAL),
Dimension(CV_MIXT_DENS:CV_MIXT_ENER) :: CvBulk,resbar_Qbulk,&
62 CHARACTER(CHRLEN) :: &
63 RCSIdentString =
'$RCSfile: RFLU_ModTimeZoom.F90,v $'
76 TYPE(t_region
),
POINTER :: regions(:)
89 TYPE(t_region
),
POINTER :: regions(:)
91 TYPE(t_region
),
POINTER :: pregion
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
100 REAL(RFREAL) :: rnozzleinlet2
102 global => regions(1)%global
104 rnozzleinlet2 = global%tzNozRad**2
106 nvars = ubound(bulkvarslocal,1)-lbound(bulkvarslocal,1)+1
107 ncvvars = cv_mixt_ener-cv_mixt_dens+1
108 bulkvarslocal = 0_rfreal
110 DO ireg = 1,global%nRegionsLocal
113 pregion => regions(ireg)
114 vol => pregion%grid%vol
115 volold => pregion%gridOld%vol
116 cv => pregion%mixt%cv
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
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)/)
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
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)/)
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__)
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)
160 global%tzRadChamber =
sqrt(global%tzVolBulk/global%tzLenChamb/global%pi)
161 global%tzEpsNozz = (global%tzThroatRad/global%tzRadChamber)**2.0d0
164 global%tzDvolBulkDt = (global%tzVolBulk-volbulkold)/
max(global%dtMin,tiny(1.0_rfreal))
179 TYPE(t_region
),
POINTER :: regions(:)
182 TYPE(t_region
),
POINTER :: pregion
183 REAL(RFREAL),
DIMENSION(:,:),
POINTER :: res
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
189 REAL(RFREAL) :: rnozzleinlet2
191 global => regions(1)%global
193 rnozzleinlet2 = global%tzNozRad**2
195 nvars = cv_mixt_ener-cv_mixt_dens+1
197 betafill = global%zoomFactor
198 volbulk = global%tzVolBulk
199 ddt_volbulk = global%tzDvolBulkDt
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
212 IF (.NOT. global%tzSubNoz)
THEN
213 DO icell = 1,pregion%grid%nCells
214 x = pregion%grid%cofg(global%tzCoordLong,
icell)
216 if(
x > global%tzMinPlane .and.
x < global%tzMaxPlane)
then
217 termr1 = (1_rfreal-betafill)/betafill/
max(global%dtMin,tiny(1.0_rfreal))
219 do ivar = cv_mixt_dens,cv_mixt_ener
220 res(ivar,
icell) = res(ivar,
icell) + termr1*pregion%mixt%Cv(ivar,
icell)*&
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
236 termr1 = (1_rfreal-betafill)/betafill/
max(global%dtMin,tiny(1.0_rfreal))
238 do ivar = cv_mixt_dens,cv_mixt_ener
239 res(ivar,
icell) = res(ivar,
icell) + termr1*pregion%mixt%Cv(ivar,
icell)*&
249 DO ireg = 1,global%nRegionsLocal
250 pregion => regions(ireg)
251 res => pregion%mixt%rhs
252 vol => pregion%grid%vol
254 IF (.NOT. global%tzSubNoz)
THEN
255 DO icell = 1,pregion%grid%nCells
256 x = pregion%grid%cofg(global%tzCoordLong,
icell)
258 if(
x > global%tzMinPlane .and.
x < global%tzMaxPlane)
then
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)
265 termr3 = (betafill-1_rfreal)/betafill*vol(
icell)/volbulk*ddt_volbulk
267 do ivar = cv_mixt_dens,cv_mixt_ener
268 res(ivar,
icell) = res(ivar,
icell) + termr3*timezoom%CvBulk(ivar)
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
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)
290 termr3 = (betafill-1_rfreal)/betafill*vol(
icell)/volbulk*ddt_volbulk
292 do ivar = cv_mixt_dens,cv_mixt_ener
293 res(ivar,
icell) = res(ivar,
icell) + termr3*timezoom%CvBulk(ivar)
315 TYPE(t_region
),
POINTER :: pregion, regions(:)
316 REAL(RFREAL),
DIMENSION(:,:),
POINTER :: res
317 INTEGER :: ireg,
icell,nvars
318 REAL(RFREAL) ::
x, localintegvol,globalintegvol
319 REAL(RFREAL),
DIMENSION(CV_MIXT_ENER-CV_MIXT_DENS+1) :: resbarveclocal,resbarvecglobal
322 REAL(RFREAL) :: rnozzleinlet2
324 global => regions(1)%global
326 rnozzleinlet2 = global%tzNozRad**2
328 nvars = cv_mixt_ener-cv_mixt_dens+1
330 resbarveclocal = 0_rfreal
331 DO ireg = 1,global%nRegionsLocal
333 pregion => regions(ireg)
334 res => pregion%mixt%rhs
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)
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)
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__)
364 timezoom%resbar_Qbulk(cv_mixt_dens:cv_mixt_ener) = resbarvecglobal(1:nvars)
400 TYPE(t_region
),
POINTER :: pregion
406 INTEGER :: ifg,ifl,ipatch
407 REAL(RFREAL) :: scalefactor
408 TYPE(t_grid),
POINTER :: pgrid
409 TYPE(t_patch),
POINTER :: ppatch
416 global => pregion%global
417 pgrid => pregion%grid
419 scalefactor = 1_rfreal/global%Zoomfactor
425 DO ifg = lbound(pgrid%gs,1),ubound(pgrid%gs,1)
426 pgrid%gs(ifg) = scalefactor*pgrid%gs(ifg)
429 DO ipatch = 1,pgrid%nPatches
430 ppatch => pregion%patches(ipatch)
432 DO ifl = lbound(ppatch%gs,1),ubound(ppatch%gs,1)
433 ppatch%gs(ifl) = scalefactor*ppatch%gs(ifl)
473 TYPE(t_region
),
POINTER :: pregion
479 INTEGER :: ifg,ifl,ipatch
480 REAL(RFREAL) :: scalefactor
481 TYPE(t_grid),
POINTER :: pgrid
482 TYPE(t_patch),
POINTER :: ppatch
489 global => pregion%global
490 pgrid => pregion%grid
492 scalefactor = global%Zoomfactor
498 DO ifg = lbound(pgrid%gs,1),ubound(pgrid%gs,1)
499 pgrid%gs(ifg) = scalefactor*pgrid%gs(ifg)
502 DO ipatch = 1,pgrid%nPatches
503 ppatch => pregion%patches(ipatch)
505 DO ifl = lbound(ppatch%gs,1),ubound(ppatch%gs,1)
506 ppatch%gs(ifl) = scalefactor*ppatch%gs(ifl)
subroutine rflu_timezoomcomputebulkvars(regions)
void int int REAL REAL * y
Vector_n max(const Array_n_const &v1, const Array_n_const &v2)
subroutine, public rflu_zoomgridspeeds(pRegion)
real(rfreal) function, public rflu_scalegridspeed(pRegion, fs)
subroutine rflu_timezoomsumaddsource(regions)
real(rfreal) function, public rflu_descalegridspeed(pRegion, fs)
void int int int REAL REAL REAL * z
**********************************************************************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)
subroutine rflu_timezoomsumresiduals(Regions)
subroutine, public rflu_timezoomdriver(regions)
subroutine, public rflu_unzoomgridspeeds(pRegion)