Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
RFLU_TimeStepViscous.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 max. allowable local/global time step in the case
26 ! of viscous flow.
27 !
28 ! Description: None.
29 !
30 ! Input:
31 ! pRegion Pointer to region data
32 !
33 ! Output: None.
34 !
35 ! Notes: None.
36 !
37 ! ******************************************************************************
38 !
39 ! $Id: RFLU_TimeStepViscous.F90,v 1.16 2008/12/06 08:44:30 mtcampbe Exp $
40 !
41 ! Copyright: (c) 2002-2004 by the University of Illinois
42 !
43 ! ******************************************************************************
44 
45 SUBROUTINE rflu_timestepviscous(pRegion)
46 
47  USE moddatatypes
48  USE moddatastruct, ONLY: t_region
49  USE modglobal, ONLY: t_global
50  USE modgrid, ONLY: t_grid
51  USE modbndpatch, ONLY: t_patch
52  USE moderror
53  USE modparameters
54 
57 
58  USE modinterfaces, ONLY: mixtperf_c_grt, &
59  mixtperf_g_cpr, &
61 
62  IMPLICIT NONE
63 
64 ! ******************************************************************************
65 ! Declarations and definitions
66 ! ******************************************************************************
67 
68 ! ==============================================================================
69 ! Arguments
70 ! ==============================================================================
71 
72  TYPE(t_region), POINTER :: pregion
73 
74 ! ==============================================================================
75 ! Locals
76 ! ==============================================================================
77 
78  CHARACTER(CHRLEN) :: rcsidentstring
79  INTEGER :: c1,c2,distrib,gasmodel,icg,ifg,ifl,indcp,indgs,indmol,ipatch, &
80  turbmodel
81  INTEGER :: dtminloc(1)
82  INTEGER, DIMENSION(:), POINTER :: bf2c
83  INTEGER, DIMENSION(:,:), POINTER :: f2c
84  REAL(RFREAL) :: as,a1,a2,cp1,cp2,cp,dn,dtmin,dummyrealout,dx,dy,dz,fmue,fs, &
85  fsu,gam,hl,ir1,ir2,minj,mm,mm1,mm2,nm,nx,ny,nz,pl,pr,prlam, &
86  prturb,rgas,rl,rr,r1,r2,srad,tinj,uinj,ul,u1,u2,vinj,vl,v1, &
87  v2,winj,wl,w1,w2,vc
88  REAL(RFREAL), DIMENSION(:,:), POINTER :: pcv,pdv,pgv,ptv,pvals
89  TYPE(t_global), POINTER :: global
90  TYPE(t_grid), POINTER :: pgrid
91  TYPE(t_patch), POINTER :: ppatch
92 
93 ! ******************************************************************************
94 ! Start
95 ! ******************************************************************************
96 
97  rcsidentstring = '$RCSfile: RFLU_TimeStepViscous.F90,v $ $Revision: 1.16 $'
98 
99  global => pregion%global
100 
101  CALL registerfunction(global,'RFLU_TimeStepViscous',&
102  'RFLU_TimeStepViscous.F90')
103 
104 ! ******************************************************************************
105 ! Get dimensions and pointers
106 ! ******************************************************************************
107 
108  pgrid => pregion%grid
109 
110  indgs = pgrid%indGs
111 
112  pcv => pregion%mixt%cv
113  pdv => pregion%mixt%dv
114  pgv => pregion%mixt%gv
115  ptv => pregion%mixt%tv
116 
117  prlam = pregion%mixtInput%prLam
118  prturb = pregion%mixtInput%prTurb
119 
120  indcp = pregion%mixtInput%indCp
121  indmol = pregion%mixtInput%indMol
122 
123  turbmodel = pregion%mixtInput%turbModel
124  gasmodel = pregion%mixtInput%gasModel
125 
126 ! ******************************************************************************
127 ! Initialize time step
128 ! ******************************************************************************
129 
130  DO icg = 1,pgrid%nCellsTot ! Explicit loop to avoid Frost problem
131  pregion%dt(icg) = 0.0_rfreal
132  END DO ! icg
133 
134 ! ******************************************************************************
135 ! Local time step
136 ! ******************************************************************************
137 
138 ! ==============================================================================
139 ! Interior faces
140 ! ==============================================================================
141 
142  DO ifg = 1,pgrid%nFaces
143  c1 = pgrid%f2c(1,ifg)
144  c2 = pgrid%f2c(2,ifg)
145 
146  nx = pgrid%fn(xcoord,ifg)
147  ny = pgrid%fn(ycoord,ifg)
148  nz = pgrid%fn(zcoord,ifg)
149  nm = pgrid%fn(xyzmag,ifg)
150 
151  dx = pgrid%cofg(xcoord,c2) - pgrid%cofg(xcoord,c1)
152  dy = pgrid%cofg(ycoord,c2) - pgrid%cofg(ycoord,c1)
153  dz = pgrid%cofg(zcoord,c2) - pgrid%cofg(zcoord,c1)
154  dn = sqrt(dx*dx + dy*dy + dz*dz)
155 
156  fs = pgrid%gs(indgs*ifg)
157 
158  r1 = pcv(cv_mixt_dens,c1)
159  r2 = pcv(cv_mixt_dens,c2)
160 
161  ir1 = 1.0_rfreal/r1
162  ir2 = 1.0_rfreal/r2
163 
164  u1 = pcv(cv_mixt_xmom,c1)*ir1
165  v1 = pcv(cv_mixt_ymom,c1)*ir1
166  w1 = pcv(cv_mixt_zmom,c1)*ir1
167  a1 = pdv(dv_mixt_soun,c1)
168 
169  u2 = pcv(cv_mixt_xmom,c2)*ir2
170  v2 = pcv(cv_mixt_ymom,c2)*ir2
171  w2 = pcv(cv_mixt_zmom,c2)*ir2
172  a2 = pdv(dv_mixt_soun,c2)
173 
174  vc = 0.5_rfreal*((u1+u2)*nx + (v1+v2)*ny + (w1+w2)*nz)
175  as = 0.5_rfreal*(a1+a2)
176 
177 #ifdef TURB
178  IF ( turbmodel == active ) THEN
179  fmue = 0.5_rfreal*(ptv(tv_mixt_muel,c1) + ptv(tv_mixt_muel,c2))/prlam &
180  + 0.5*rfreal*(ptv(tv_mixt_muet,c1) + ptv(tv_mixt_muet,c2))/prturb
181  ELSE
182  fmue = 0.5_rfreal*(ptv(tv_mixt_muel,c1) + ptv(tv_mixt_muel,c2))/prlam
183  END IF ! turbModel
184 #else
185  fmue = 0.5_rfreal*(ptv(tv_mixt_muel,c1) + ptv(tv_mixt_muel,c2))/prlam
186 #endif
187 
188  srad = (abs(vc - fs) + as)*nm &
189  + 4.0_rfreal*fmue/(0.5_rfreal*(r1 + r2))*nm/dn
190 
191  pregion%dt(c1) = pregion%dt(c1) + srad
192  pregion%dt(c2) = pregion%dt(c2) + srad
193  END DO ! ifg
194 
195 ! ==============================================================================
196 ! Boundary faces
197 ! ==============================================================================
198 
199  DO ipatch = 1,pgrid%nPatches
200  ppatch => pregion%patches(ipatch)
201 
202  SELECT CASE ( ppatch%bcType )
203 
204 ! ------------------------------------------------------------------------------
205 ! Injection boundary
206 ! ------------------------------------------------------------------------------
207 
208  CASE ( bc_injection:bc_injection+bc_range )
209  pvals => ppatch%mixt%vals
210 
211  distrib = ppatch%mixt%distrib
212 
213  DO ifl = 1,ppatch%nBFaces
214  c1 = ppatch%bf2c(ifl)
215 
216  nx = ppatch%fn(xcoord,ifl)
217  ny = ppatch%fn(ycoord,ifl)
218  nz = ppatch%fn(zcoord,ifl)
219  nm = ppatch%fn(xyzmag,ifl)
220 
221  dx = pgrid%cofg(xcoord,c1) - ppatch%fc(xcoord,ifl)
222  dy = pgrid%cofg(ycoord,c1) - ppatch%fc(ycoord,ifl)
223  dz = pgrid%cofg(zcoord,c1) - ppatch%fc(zcoord,ifl)
224  dn = sqrt(dx*dx + dy*dy + dz*dz)
225 
226  fs = ppatch%gs(indgs*ifl)
227  fsu = rflu_descalegridspeed(pregion,fs)
228 
229  rl = pcv(cv_mixt_dens,c1)
230  pl = pdv(dv_mixt_pres,c1)
231 
232  minj = pvals(bcdat_inject_mfrate,distrib*ifl)
233 
234  IF ( minj > 0.0_rfreal ) THEN ! Surface burning
235  tinj = pvals(bcdat_inject_temp,distrib*ifl)
236 
237  IF ( gasmodel == gas_model_tcperf ) THEN
238  cp = pgv(gv_mixt_cp ,indcp *c1)
239  mm = pgv(gv_mixt_mol,indmol*c1)
240 
241  CALL rflu_setrindstateinjectperf(cp,mm,nx,ny,nz,minj,tinj,pl, &
242  fsu,rl,ul,vl,wl,hl)
243 
244  r1 = rl
245  vc = ul*nx + vl*ny + wl*nz
246  rgas = mixtperf_r_m(mm)
247  gam = mixtperf_g_cpr(cp,rgas)
248  a1 = mixtperf_c_grt(gam,rgas,tinj)
249  ELSE ! Defensive programming
250  CALL errorstop(global,err_reached_default,__line__)
251  END IF ! gasModel
252  ELSE ! Surface NOT burning
253  r1 = rl
254  vc = 0.0_rfreal
255  a1 = pdv(dv_mixt_soun,c1)
256  END IF ! minj
257 
258 #ifdef TURB
259  IF ( turbmodel == active ) THEN
260  fmue = ptv(tv_mixt_muel,c1)/prlam + ptv(tv_mixt_muet,c1)/prturb
261  ELSE
262  fmue = ptv(tv_mixt_muel,c1)/prlam
263  END IF ! turbModel
264 #else
265  fmue = ptv(tv_mixt_muel,c1)/prlam
266 #endif
267 
268  pregion%dt(c1) = pregion%dt(c1) &
269  + (abs(vc - fsu) + a1)*nm + 4.0_rfreal*fmue/r1*nm/dn
270  END DO ! ifl
271 
272 ! ------------------------------------------------------------------------------
273 ! All other boundaries
274 ! ------------------------------------------------------------------------------
275 
276  CASE default
277  DO ifl = 1,ppatch%nBFaces
278  c1 = ppatch%bf2c(ifl)
279 
280  nx = ppatch%fn(xcoord,ifl)
281  ny = ppatch%fn(ycoord,ifl)
282  nz = ppatch%fn(zcoord,ifl)
283  nm = ppatch%fn(xyzmag,ifl)
284 
285  dx = pgrid%cofg(xcoord,c1) - ppatch%fc(xcoord,ifl)
286  dy = pgrid%cofg(ycoord,c1) - ppatch%fc(ycoord,ifl)
287  dz = pgrid%cofg(zcoord,c1) - ppatch%fc(zcoord,ifl)
288  dn = sqrt(dx*dx + dy*dy + dz*dz)
289 
290  fs = ppatch%gs(indgs*ifl)
291  fsu = rflu_descalegridspeed(pregion,fs)
292 
293  r1 = pcv(cv_mixt_dens,c1)
294 
295  ir1 = 1.0_rfreal/r1
296 
297  u1 = pcv(cv_mixt_xmom,c1)*ir1
298  v1 = pcv(cv_mixt_ymom,c1)*ir1
299  w1 = pcv(cv_mixt_zmom,c1)*ir1
300  a1 = pdv(dv_mixt_soun,c1)
301 
302  vc = u1*nx + v1*ny + w1*nz
303 
304 #ifdef TURB
305  IF ( turbmodel == active ) THEN
306  fmue = ptv(tv_mixt_muel,c1)/prlam + ptv(tv_mixt_muet,c1)/prturb
307  ELSE
308  fmue = ptv(tv_mixt_muel,c1)/prlam
309  END IF ! turbModel
310 #else
311  fmue = ptv(tv_mixt_muel,c1)/prlam
312 #endif
313 
314  pregion%dt(c1) = pregion%dt(c1) &
315  + (abs(vc - fsu) + a1)*nm + 4.0_rfreal*fmue/r1*nm/dn
316  END DO ! ifl
317  END SELECT ! pPatch%bcType
318  END DO ! iPatch
319 
320 ! ******************************************************************************
321 ! Finalize computation of local time step. NOTE set time step in dummy cells
322 ! to crazy value, that way code will blow up immediately should it be used by
323 ! accident.
324 ! ******************************************************************************
325 
326  DO icg = 1,pgrid%nCells
327  pregion%dt(icg) = pgrid%vol(icg)/pregion%dt(icg)
328  END DO ! icg
329 
330  DO icg = pgrid%nCells+1,pgrid%nCellsTot
331  pregion%dt(icg) = REAL(ABS(CRAZY_VALUE_INT),kind=rfreal)
332  END DO ! icg
333 
334 ! ******************************************************************************
335 ! For unsteady flows, determine minimum step
336 ! ******************************************************************************
337 
338  IF ( global%flowType == flow_unsteady ) THEN
339  dtmin = minval(pregion%dt(1:pgrid%nCells))
340  dtminloc = minloc(pregion%dt(1:pgrid%nCells))
341 
342  pregion%dtMin = dtmin
343  pregion%dtMinLoc = dtminloc(1)
344  END IF ! global%flowType
345 
346 ! ******************************************************************************
347 ! Finalize
348 ! ******************************************************************************
349 
350  CALL deregisterfunction(global)
351 
352 END SUBROUTINE rflu_timestepviscous
353 
354 ! ******************************************************************************
355 !
356 ! RCS Revision history:
357 !
358 ! $Log: RFLU_TimeStepViscous.F90,v $
359 ! Revision 1.16 2008/12/06 08:44:30 mtcampbe
360 ! Updated license.
361 !
362 ! Revision 1.15 2008/11/19 22:17:43 mtcampbe
363 ! Added Illinois Open Source License/Copyright
364 !
365 ! Revision 1.14 2006/08/19 15:40:02 mparmar
366 ! Renamed patch variables
367 !
368 ! Revision 1.13 2006/04/07 15:19:22 haselbac
369 ! Removed tabs
370 !
371 ! Revision 1.12 2005/10/31 21:09:37 haselbac
372 ! Changed specModel and SPEC_MODEL_NONE
373 !
374 ! Revision 1.11 2005/05/28 18:03:56 haselbac
375 ! Removed unnecessary setting of rgas and gamma
376 !
377 ! Revision 1.10 2004/10/19 19:29:34 haselbac
378 ! Now receive pRegion, partial rewrite, cosmetics
379 !
380 ! Revision 1.9 2004/01/11 02:17:34 jiao
381 ! Eliminated some redundant trailing spaces that made some lines too long.
382 ! This changed was necessary to compile with NAG F90 compiler.
383 !
384 ! Revision 1.8 2003/12/04 03:30:08 haselbac
385 ! Changed timestep computation for viscous flows
386 !
387 ! Revision 1.7 2003/10/15 02:43:57 haselbac
388 ! Added code to determine location of minimum dt
389 !
390 ! Revision 1.6 2003/08/28 00:58:43 haselbac
391 ! Fixed bug in TURB section for timestep
392 !
393 ! Revision 1.5 2003/04/18 20:00:09 haselbac
394 ! Clean-up, added explicit initialization (prevent Frost-problem)
395 !
396 ! Revision 1.4 2003/01/28 14:50:33 haselbac
397 ! Use parameters in fn
398 !
399 ! Revision 1.3 2002/11/27 20:27:45 haselbac
400 ! Proper contribution from injecting boundaries
401 !
402 ! Revision 1.2 2002/11/08 21:35:36 haselbac
403 ! Fixed bug in use of grid speed
404 !
405 ! Revision 1.1 2002/09/09 16:28:02 haselbac
406 ! Initial revision
407 !
408 ! ******************************************************************************
409 
410 
411 
412 
413 
414 
415 
subroutine, public rflu_setrindstateinjectperf(cpGas, mmGas, nx, ny, nz, mInj, tInj, pl, fs, rl, ul, vl, wl, Hl)
subroutine rflu_timestepviscous(pRegion)
real(rfreal) function mixtperf_r_m(M)
Definition: MixtPerf_R.F90:54
NT dx
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
double sqrt(double d)
Definition: double.h:73
real(rfreal) function, public rflu_descalegridspeed(pRegion, fs)
RT dz() const
Definition: Direction_3.h:133
real(rfreal) function mixtperf_c_grt(G, R, T)
Definition: MixtPerf_C.F90:86
NT dy
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
subroutine deregisterfunction(global)
Definition: ModError.F90:469
real(rfreal) function mixtperf_g_cpr(Cp, R)
Definition: MixtPerf_G.F90:39