Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
RFLU_ModRindStates.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 for setting rind states.
26 !
27 ! Description: None
28 !
29 ! Notes: None.
30 !
31 ! ******************************************************************************
32 !
33 ! $Id: RFLU_ModRindStates.F90,v 1.6 2008/12/06 08:44:24 mtcampbe Exp $
34 !
35 ! Copyright: (c) 2004 by the University of Illinois
36 !
37 ! ******************************************************************************
38 
40 
41  USE moddatatypes
42  USE modparameters
43  USE modglobal, ONLY: t_global
44 
45  USE modinterfaces, ONLY: mixtperf_c_dgp, &
46  mixtperf_c_grt, &
47  mixtperf_d_prt, &
51  mixtperf_g_cpr, &
54 
55  IMPLICIT NONE
56 
57 ! ******************************************************************************
58 ! Declarations and definitions
59 ! ******************************************************************************
60 
61 ! ==============================================================================
62 ! Procedures
63 ! ==============================================================================
64 
65  PUBLIC :: rflu_setrindstatefarfieldperf, &
68 
69 ! ==============================================================================
70 ! Data
71 ! ==============================================================================
72 
73  CHARACTER(CHRLEN), PRIVATE :: &
74  RCSIdentString = '$RCSfile: RFLU_ModRindStates.F90,v $ $Revision: 1.6 $'
75 
76 ! ******************************************************************************
77 ! Procedures
78 ! ******************************************************************************
79 
80  CONTAINS
81 
82 
83 
84 
85 
86 
87 
88 
89 ! ******************************************************************************
90 !
91 ! Purpose: Set rind state for farfield boundaries and perfect gas.
92 !
93 ! Description: None.
94 !
95 ! Input:
96 ! global Pointer to global data
97 ! cpGas Specific heat at constant pressure
98 ! mmGas Molecular mass
99 ! nx,ny,nz Components of unit normal vector
100 ! machInf Mach number at infinity
101 ! pInf Pressure at infinity
102 ! tInf Temperature at infinity
103 ! alphaInf Angle of attack
104 ! betaInf Sideslip angle
105 ! corrFlag Flag for vortex-correction
106 ! liftCoef Lift coefficient
107 ! xc x-coordinate
108 ! yc y-coordinate
109 ! zc z-coordinate
110 ! rl Density at boundary
111 ! rul x-momentum component at boundary
112 ! rvl y-momentum component at boundary
113 ! rwl z-momentum component at boundary
114 ! rel Total internal energy at boundary
115 !
116 ! Output:
117 ! rr Density
118 ! rur x-momentum component
119 ! rvr y-momentum component
120 ! rwr z-momentum component
121 ! rer Total internal energy
122 ! pr Pressure
123 !
124 ! Notes:
125 ! 1. Valid only for thermally and calorically perfect gas.
126 ! 2. Valid only for two-dimensional flows.
127 !
128 ! ******************************************************************************
129 
130  SUBROUTINE rflu_setrindstatefarfieldperf(global,cpGas,mmGas,nx,ny,nz, &
131  machinf,pinf,tinf,alphainf, &
132  betainf,corrflag,liftcoef,xc,yc, &
133  zc,rl,rul,rvl,rwl,rel,rr,rur,rvr, &
134  rwr,rer,pr)
135 
136  IMPLICIT NONE
137 
138 ! ******************************************************************************
139 ! Declarations and definitions
140 ! ******************************************************************************
141 
142 ! ==============================================================================
143 ! Arguments
144 ! ==============================================================================
145 
146  LOGICAL, INTENT(IN) :: corrflag
147  REAL(RFREAL), INTENT(IN) :: alphainf,betainf,cpgas,liftcoef,machinf, &
148  mmgas,nx,ny,nz,pinf,rl,rel,rul,rvl,rwl, &
149  tinf,xc,yc,zc
150  REAL(RFREAL), INTENT(OUT) :: pr,rer,rr,rur,rvr,rwr
151  TYPE(t_global), POINTER :: global
152 
153 ! ==============================================================================
154 ! Locals
155 ! ==============================================================================
156 
157  REAL(RFREAL) :: al,corr,corrterm,denom,dist,dq2,dx,dy,el,ggas,gm1og, &
158  gogm1,ggasterm3,numer,pb,pi,pl,qi,ql,rb,rgas,ri,sl2, &
159  term,theta,ub,ui,ul,vb,vi,vl,wb,wi,wl
160 
161 ! ******************************************************************************
162 ! Compute gas properties
163 ! ******************************************************************************
164 
165  rgas = mixtperf_r_m(mmgas)
166  ggas = mixtperf_g_cpr(cpgas,rgas)
167 
168  gm1og = (ggas-1.0_rfreal)/ggas
169  gogm1 = 1.0_rfreal/gm1og
170 
171  corrterm = global%forceRefLength/(4.0_rfreal*global%pi)
172 
173 ! ******************************************************************************
174 ! Interior state at boundary
175 ! ******************************************************************************
176 
177  ul = rul/rl
178  vl = rvl/rl
179  wl = rwl/rl
180  ql = ul*nx + vl*ny + wl*nz
181 
182  el = rel/rl
183  sl2 = ul*ul + vl*vl + wl*wl
184  pl = mixtperf_p_deogvm2(rl,el,ggas,sl2)
185 
186 ! ******************************************************************************
187 ! Compute state at infinity without vortex correction
188 ! ******************************************************************************
189 
190  ri = mixtperf_d_prt(pinf,rgas,tinf)
191  pi = pinf
192 
193  qi = machinf*mixtperf_c_grt(ggas,rgas,tinf)
194  ui = qi*cos(alphainf)*cos(betainf)
195  vi = qi*sin(alphainf)*cos(betainf)
196  wi = qi* sin(betainf)
197 
198 ! ******************************************************************************
199 ! Compute state at infinity with vortex correction. NOTE the correction is
200 ! assumed to be two-dimensional and the aerofoil center of pressure is assumed
201 ! to be located at (x,y) = (0.25,0.0).
202 ! ******************************************************************************
203 
204  IF ( corrflag .EQV. .true. ) THEN
205  dx = xc - 0.25_rfreal
206  dy = yc
207 
208  dist = sqrt(dx**2 + dy**2)
209  theta = atan2(dy,dx)
210 
211  numer = liftcoef*qi*sqrt(1.0_rfreal-machinf**2)
212  denom = dist*(1.0_rfreal - (machinf*sin(theta-alphainf))**2)
213  corr = corrterm*numer/denom
214 
215  ui = ui + corr*sin(theta)
216  vi = vi - corr*cos(theta)
217 
218  dq2 = qi*qi - (ui*ui + vi*vi)
219  pi = (pi**gm1og + 0.5_rfreal*gm1og*ri/pi**(1.0_rfreal/ggas)*dq2)**gogm1
220  ri = ri*(pi/pinf)**ggas
221  END IF ! corrFlag
222 
223 ! ******************************************************************************
224 ! Compute right state at boundary
225 ! ******************************************************************************
226 
227 ! ==============================================================================
228 ! Subsonic flow
229 ! ==============================================================================
230 
231  IF ( machinf < 1.0_rfreal ) THEN
232  al = mixtperf_c_dgp(rl,ggas,pl)
233 
234 ! ------------------------------------------------------------------------------
235 ! Subsonic inflow
236 ! ------------------------------------------------------------------------------
237 
238  IF ( ql < 0.0_rfreal ) THEN
239  pb = 0.5_rfreal*(pi+pl-rl*al*((ui-ul)*nx+(vi-vl)*ny+(wi-wl)*nz))
240 
241  rb = ri - (pi - pb)/(al*al)
242  ub = ui - nx*(pi - pb)/(rl*al)
243  vb = vi - ny*(pi - pb)/(rl*al)
244  wb = wi - nz*(pi - pb)/(rl*al)
245 
246 ! ------------------------------------------------------------------------------
247 ! Subsonic outflow
248 ! ------------------------------------------------------------------------------
249 
250  ELSE
251  pb = pi
252 
253  rb = rl - (pl-pi)/(al*al)
254  ub = ul + nx*(pl-pi)/(rl*al)
255  vb = vl + ny*(pl-pi)/(rl*al)
256  wb = wl + nz*(pl-pi)/(rl*al)
257  END IF ! ql
258 
259  rr = rb
260  rur = rb*ub
261  rvr = rb*vb
262  rwr = rb*wb
263  rer = rb*mixtperf_eo_dgpuvw(rb,ggas,pb,ub,vb,wb)
264  pr = pb
265 
266 ! ==============================================================================
267 ! Supersonic flow
268 ! ==============================================================================
269 
270  ELSE
271 
272 ! ------------------------------------------------------------------------------
273 ! Supersonic inflow
274 ! ------------------------------------------------------------------------------
275 
276  IF ( ql < 0.0_rfreal ) THEN
277  rr = ri
278  rur = ri*ui
279  rvr = ri*vi
280  rwr = ri*wi
281  rer = ri*mixtperf_eo_dgpvm(ri,ggas,pi,qi)
282  pr = pi
283 
284 ! ------------------------------------------------------------------------------
285 ! Supersonic outflow
286 ! ------------------------------------------------------------------------------
287 
288  ELSE
289  rr = rl
290  rur = rul
291  rvr = rvl
292  rwr = rwl
293  rer = rel
294  pr = pl
295  END IF ! ql
296  END IF ! machInf
297 
298 ! ******************************************************************************
299 ! End
300 ! ******************************************************************************
301 
302  END SUBROUTINE rflu_setrindstatefarfieldperf
303 
304 
305 
306 
307 
308 
309 
310 
311 
312 
313 
314 ! ******************************************************************************
315 !
316 ! Purpose: Set rind state for injection boundaries and perfect gas.
317 !
318 ! Description: None.
319 !
320 ! Input:
321 ! cpGas Specific heat at constant pressure
322 ! mmGas Molecular mass
323 ! nx,ny,nz Components of unit normal vector
324 ! mInj Injection mass flux
325 ! tInj Injection temperature
326 ! pl Pressure
327 ! fs Grid speed
328 !
329 ! Output:
330 ! rl Density
331 ! ul x-velocity component
332 ! vl y-velocity component
333 ! wl z-velocity component
334 ! Hl Stagnation enthalpy per unit mass
335 !
336 ! Notes:
337 ! 1. Valid only for thermally and calorically perfect gas.
338 !
339 ! ******************************************************************************
340 
341  SUBROUTINE rflu_setrindstateinjectperf(cpGas,mmGas,nx,ny,nz,mInj,tInj,pl, &
342  fs,rl,ul,vl,wl,hl)
343 
344  IMPLICIT NONE
345 
346 ! ******************************************************************************
347 ! Declarations and definitions
348 ! ******************************************************************************
349 
350 ! ==============================================================================
351 ! Arguments
352 ! ==============================================================================
353 
354  REAL(RFREAL), INTENT(IN) :: cpgas,fs,minj,mmgas,nx,ny,nz,pl,tinj
355  REAL(RFREAL), INTENT(OUT) :: hl,rl,ul,vl,wl
356 
357 ! ==============================================================================
358 ! Locals
359 ! ==============================================================================
360 
361  REAL(RFREAL) :: ggas,ql,rgas
362 
363 ! ******************************************************************************
364 ! Compute wall pressure
365 ! ******************************************************************************
366 
367  rgas = mixtperf_r_m(mmgas)
368  ggas = mixtperf_g_cpr(cpgas,rgas)
369 
370  rl = mixtperf_d_prt(pl,rgas,tinj)
371 
372  ql = -minj/rl + fs
373  ul = ql*nx
374  vl = ql*ny
375  wl = ql*nz
376 
377  hl = mixtperf_ho_cptuvw(cpgas,tinj,ul,vl,wl)
378 
379 ! ******************************************************************************
380 ! End
381 ! ******************************************************************************
382 
383  END SUBROUTINE rflu_setrindstateinjectperf
384 
385 
386 
387 
388 
389 
390 
391 
392 ! ******************************************************************************
393 !
394 ! Purpose: Set rind state for slip-wall boundaries and perfect gas.
395 !
396 ! Description: None.
397 !
398 ! Input:
399 ! cpGas Specific heat at constant pressure
400 ! mmGas Molecular mass
401 ! nx,ny,nz Components of unit normal vector
402 ! rl Density
403 ! rul x-momentum component
404 ! rvl y-momentum component
405 ! rwl z-momentum component
406 ! fs Grid speed
407 ! pl Pressure
408 !
409 ! Output:
410 ! pl Pressure
411 !
412 ! Notes:
413 ! 1. Valid only for thermally and calorically perfect gas.
414 !
415 ! ******************************************************************************
416 
417  SUBROUTINE rflu_setrindstateslipwallperf(cpGas,mmGas,nx,ny,nz,rl,rul,rvl, &
418  rwl,fs,pl)
419 
420  IMPLICIT NONE
421 
422 ! ******************************************************************************
423 ! Declarations and definitions
424 ! ******************************************************************************
425 
426 ! ==============================================================================
427 ! Arguments
428 ! ==============================================================================
429 
430  REAL(RFREAL), INTENT(IN) :: cpgas,fs,mmgas,nx,ny,nz,rl,rul,rvl,rwl
431  REAL(RFREAL), INTENT(INOUT) :: pl
432 
433 ! ==============================================================================
434 ! Locals
435 ! ==============================================================================
436 
437  REAL(RFREAL) :: al,ggas,irl,ql,rgas,term,ul,vl,wl
438 
439 ! ******************************************************************************
440 ! Compute wall pressure
441 ! ******************************************************************************
442 
443  rgas = mixtperf_r_m(mmgas)
444  ggas = mixtperf_g_cpr(cpgas,rgas)
445 
446  irl = 1.0_rfreal/rl
447  ul = irl*rul
448  vl = irl*rvl
449  wl = irl*rwl
450  ql = ul*nx + vl*ny + wl*nz - fs
451 
452  al = mixtperf_c_dgp(rl,ggas,pl)
453 
454  IF ( ql < 0.0_rfreal ) THEN
455  term = 1.0_rfreal + 0.5_rfreal*(ggas-1.0_rfreal)*ql/al
456  pl = pl*term**(2.0_rfreal*ggas/(ggas-1.0_rfreal))
457  ELSE
458  term = (ggas+1.0_rfreal)/4.0_rfreal
459  pl = pl + term*rl*ql*(ql + sqrt(al*al + term*term*ql*ql)/term)
460  END IF ! ql
461 
462 ! ******************************************************************************
463 ! End
464 ! ******************************************************************************
465 
466  END SUBROUTINE rflu_setrindstateslipwallperf
467 
468 
469 
470 
471 
472 END MODULE rflu_modrindstates
473 
474 ! ******************************************************************************
475 !
476 ! RCS Revision history:
477 !
478 ! $Log: RFLU_ModRindStates.F90,v $
479 ! Revision 1.6 2008/12/06 08:44:24 mtcampbe
480 ! Updated license.
481 !
482 ! Revision 1.5 2008/11/19 22:17:35 mtcampbe
483 ! Added Illinois Open Source License/Copyright
484 !
485 ! Revision 1.4 2006/04/07 15:19:20 haselbac
486 ! Removed tabs
487 !
488 ! Revision 1.3 2004/12/27 23:29:50 haselbac
489 ! Added setting of rind state for farf bc
490 !
491 ! Revision 1.2 2004/10/19 19:28:31 haselbac
492 ! Added procedure to set rind state for injecting boundaries
493 !
494 ! Revision 1.1 2004/04/14 02:05:11 haselbac
495 ! Initial revision
496 !
497 ! ******************************************************************************
498 
499 
500 
501 
502 
503 
subroutine, public rflu_setrindstateinjectperf(cpGas, mmGas, nx, ny, nz, mInj, tInj, pl, fs, rl, ul, vl, wl, Hl)
real(rfreal) function mixtperf_eo_dgpvm(D, G, P, Vm)
Definition: MixtPerf_E.F90:55
real(rfreal) function mixtperf_p_deogvm2(D, Eo, G, Vm2)
Definition: MixtPerf_P.F90:39
real(rfreal) function mixtperf_r_m(M)
Definition: MixtPerf_R.F90:54
NT dx
subroutine, public rflu_setrindstateslipwallperf(cpGas, mmGas, nx, ny, nz, rl, rul, rvl, rwl, fs, pl)
real(rfreal) function mixtperf_c_dgp(D, G, P)
Definition: MixtPerf_C.F90:56
real(rfreal) function mixtperf_d_prt(P, R, T)
Definition: MixtPerf_D.F90:71
double sqrt(double d)
Definition: double.h:73
static const double pi
Definition: smooth_medial.C:43
real(rfreal) function mixtperf_ho_cptuvw(Cp, T, U, V, W)
Definition: MixtPerf_H.F90:39
NT & sin
subroutine, public rflu_setrindstatefarfieldperf(global, cpGas, mmGas, nx, ny, nz, machInf, pInf, tInf, alphaInf, betaInf, corrFlag, liftCoef, xc, yc, zc, rl, rul, rvl, rwl, rel, rr, rur, rvr, rwr, rer, pr)
real(rfreal) function mixtperf_c_grt(G, R, T)
Definition: MixtPerf_C.F90:86
NT dy
real(rfreal) function mixtperf_eo_dgpuvw(D, G, P, U, V, W)
Definition: MixtPerf_E.F90:40
long double dist(long double *coord1, long double *coord2, int size)
real(rfreal) function mixtperf_g_cpr(Cp, R)
Definition: MixtPerf_G.F90:39
CGAL_BEGIN_NAMESPACE void const NT NT NT NT & denom
NT & cos
CImg< T > & atan2(const CImg< t > &img)
Compute the arc-tangent of each pixel.
Definition: CImg.h:12671