Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
RFLU_InitBcDataHardCode.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: Initialize boundary-condition data using hard-coded values.
26 !
27 ! Description: None.
28 !
29 ! Input:
30 ! pRegion Pointer to region
31 !
32 ! Output: None.
33 !
34 ! Notes:
35 ! 1. This routine assumes a perfect gas.
36 !
37 ! ******************************************************************************
38 !
39 ! $Id: RFLU_InitBcDataHardCode.F90,v 1.7 2008/12/06 08:44:56 mtcampbe Exp $
40 !
41 ! Copyright: (c) 2004-2005 by the University of Illinois
42 !
43 ! ******************************************************************************
44 
45 SUBROUTINE rflu_initbcdatahardcode(pRegion)
46 
47  USE moddatatypes
48  USE moderror
49  USE modbndpatch, ONLY: t_patch
50  USE moddatastruct, ONLY: t_region
51  USE modglobal, ONLY: t_global
52  USE modgrid, ONLY: t_grid
53  USE modparameters
54 
61 
62  USE modinterfaces, ONLY: mixtperf_c_dgp, &
66 
67  IMPLICIT NONE
68 
69 ! ******************************************************************************
70 ! Declarations and definitions
71 ! ******************************************************************************
72 
73 ! ==============================================================================
74 ! Arguments
75 ! ==============================================================================
76 
77  TYPE(t_region), POINTER :: pregion
78 
79 ! ==============================================================================
80 ! Locals
81 ! ==============================================================================
82 
83  CHARACTER(CHRLEN) :: errorstring,rcsidentstring
84  INTEGER :: ifl,ipatch
85  REAL(RFREAL) :: betah,cpgas,d,dinc,ggas,height,mach,mi,minj,p,ptot,rgas, &
86  ri,t,ttot,u,v,vinj,vmag,w,x,y
87  TYPE(t_global), POINTER :: global
88  TYPE(t_grid), POINTER :: pgrid
89  TYPE(t_patch), POINTER :: ppatch
90 
91 ! ******************************************************************************
92 ! Start
93 ! ******************************************************************************
94 
95  rcsidentstring = '$RCSfile: RFLU_InitBcDataHardCode.F90,v $ $Revision: 1.7 $'
96 
97  global => pregion%global
98 
99  CALL registerfunction(global,'RFLU_InitBcDataHardCode', &
100  'RFLU_InitBcDataHardCode.F90')
101 
102  IF ( global%verbLevel > verbose_none ) THEN
103  WRITE(stdout,'(A,1X,A)') solver_name, &
104  'Initializing boundary-condition data from hard code...'
105 
106  IF ( global%verbLevel > verbose_low ) THEN
107  WRITE(stdout,'(A,3X,A,A)') solver_name,'Case: ',trim(global%casename)
108  END IF ! global%verbLevel
109  END IF ! global%verbLevel
110 
111 ! ==============================================================================
112 ! Set pointers
113 ! ==============================================================================
114 
115  pgrid => pregion%grid
116 
117 ! ==============================================================================
118 ! Set constants
119 ! ==============================================================================
120 
121  cpgas = global%refCp
122  ggas = global%refGamma
123  rgas = mixtperf_r_cpg(cpgas,ggas)
124 
125 ! ******************************************************************************
126 ! Initialize data fields based on user input
127 ! ******************************************************************************
128 
129  SELECT CASE ( global%casename )
130 
131 ! ==============================================================================
132 ! Proudman-Culick flow. NOTE this problem is two-dimensional and assumed to
133 ! lie in the x-y plane, and that the injection boundary is located at
134 ! y = -height.
135 ! ==============================================================================
136 
137  CASE ( "onera_c0", "onera_c0_2d_100x50" )
138  CALL rflu_getparamshardcodeproudman(dinc,minj,vinj,ptot)
139 
140  height = minval(pgrid%xyz(ycoord,1:pgrid%nVertTot))
141 
142  DO ipatch = 1,pgrid%nPatches
143  ppatch => pregion%patches(ipatch)
144 
145  IF ( ppatch%bcType == bc_injection ) THEN
146  IF ( ppatch%mixt%distrib == bcdat_distrib ) THEN
147  DO ifl = 1,ppatch%nBFaces
148  x = ppatch%fc(xcoord,ifl)
149  y = ppatch%fc(ycoord,ifl)
150 
151  CALL rflu_computeexactflowproudman(global,x,y,height,dinc, &
152  vinj,ptot,d,u,v,w,p)
153 
154  t = mixtperf_t_dpr(d,p,rgas)
155 
156  ppatch%mixt%vals(bcdat_inject_mfrate,ifl) = d*v
157  ppatch%mixt%vals(bcdat_inject_temp ,ifl) = t
158  END DO ! ifl
159  ELSE
160  WRITE(errorstring,'(A,1X,I3)') 'Patch:',ipatch
161  CALL errorstop(global,err_distrib_invalid,__line__, &
162  trim(errorstring))
163  END IF ! pPatch%mixt%distrib
164  ELSE IF ( ppatch%bcType == bc_outflow ) THEN
165  IF ( ppatch%mixt%distrib == bcdat_distrib ) THEN
166  DO ifl = 1,ppatch%nBFaces
167  x = ppatch%fc(xcoord,ifl)
168  y = ppatch%fc(ycoord,ifl)
169 
170  CALL rflu_computeexactflowproudman(global,x,y,height,dinc, &
171  vinj,ptot,d,u,v,w,p)
172 
173  ppatch%mixt%vals(bcdat_outflow_press,ifl) = p
174  END DO ! ifl
175  ELSE
176  WRITE(errorstring,'(A,1X,I3)') 'Patch:',ipatch
177  CALL errorstop(global,err_distrib_invalid,__line__, &
178  trim(errorstring))
179  END IF ! pPatch%mixt%distrib
180  END IF ! pPatch%bcType
181  END DO ! iPatch
182 
183 ! ==============================================================================
184 ! Ringleb flow. NOTE this problem is two-dimensional and assumed to lie in
185 ! the x-y plane and that the exact solution is restricted to gamma = 1.4.
186 ! ==============================================================================
187 
188  CASE ( "ringleb" )
189  CALL rflu_getparamshardcoderingleb(ptot,ttot)
190 
191  DO ipatch = 1,pgrid%nPatches
192  ppatch => pregion%patches(ipatch)
193 
194  IF ( ppatch%bcType == bc_inflow_totang ) THEN
195  IF ( ppatch%mixt%distrib == bcdat_distrib ) THEN
196  DO ifl = 1,ppatch%nBFaces
197  x = ppatch%fc(xcoord,ifl)
198  y = ppatch%fc(ycoord,ifl)
199 
200  CALL rflu_computeexactflowringleb(x,y,rgas,ptot,ttot,d,u,v,w,p)
201 
202  betah = atan2(v,u) ! w assumed to be zero
203 
204  ppatch%mixt%vals(bcdat_inflow_ptot ,ifl) = ptot
205  ppatch%mixt%vals(bcdat_inflow_ttot ,ifl) = ttot
206  ppatch%mixt%vals(bcdat_inflow_betah,ifl) = betah
207  ppatch%mixt%vals(bcdat_inflow_betav,ifl) = 0.0_rfreal
208  END DO ! ifl
209  ELSE
210  WRITE(errorstring,'(A,1X,I3)') 'Patch:',ipatch
211  CALL errorstop(global,err_distrib_invalid,__line__, &
212  trim(errorstring))
213  END IF ! pPatch%mixt%distrib
214  ELSE IF ( ppatch%bcType == bc_outflow ) THEN
215  IF ( ppatch%mixt%distrib == bcdat_distrib ) THEN
216  DO ifl = 1,ppatch%nBFaces
217  x = ppatch%fc(xcoord,ifl)
218  y = ppatch%fc(ycoord,ifl)
219 
220  CALL rflu_computeexactflowringleb(x,y,rgas,ptot,ttot,d,u,v,w,p)
221 
222  ppatch%mixt%vals(bcdat_outflow_press,ifl) = p
223  END DO ! ifl
224  ELSE
225  WRITE(errorstring,'(A,1X,I3)') 'Patch:',ipatch
226  CALL errorstop(global,err_distrib_invalid,__line__, &
227  trim(errorstring))
228  END IF ! pPatch%mixt%distrib
229  END IF ! pPatch%bcType
230  END DO ! iPatch
231 
232 ! ==============================================================================
233 ! Supersonic vortex flow. NOTE this problem is two-dimensional and assumed
234 ! to lie in the x-y plane.
235 ! ==============================================================================
236 
237  CASE ( "ssvorth20x5l1" ,"ssvortp20x5l1", &
238  "ssvorth20x5l3" ,"ssvortp20x5l3", &
239  "ssvorth40x10l1" ,"ssvortp40x10l1", &
240  "ssvorth40x10l3" ,"ssvortp40x10l3", &
241  "ssvorth80x20l1" ,"ssvortp80x20l1", &
242  "ssvorth80x20l3" ,"ssvortp80x20l3", &
243  "ssvorth160x40l1" ,"ssvortp160x40l1", &
244  "ssvorth160x40l3" ,"ssvortp160x40l3", &
245  "ssvorth320x80l1" ,"ssvortp320x80l1", &
246  "ssvorth320x80l3" ,"ssvortp320x80l3", &
247  "ssvorth640x160l1","ssvortp640x160l1", &
248  "ssvorth640x160l3","ssvortp640x160l3" )
249  CALL rflu_getparamshardcodessvortex(ri,mi,ptot,ttot)
250 
251  DO ipatch = 1,pgrid%nPatches
252  ppatch => pregion%patches(ipatch)
253 
254  IF ( ppatch%bcType == bc_inflow_totang ) THEN
255  IF ( ppatch%mixt%distrib == bcdat_distrib ) THEN
256  DO ifl = 1,ppatch%nBFaces
257  x = ppatch%fc(xcoord,ifl)
258  y = ppatch%fc(ycoord,ifl)
259 
260  CALL rflu_computeexactflowssvortex(x,y,ggas,rgas,ri,mi,ptot, &
261  ttot,d,u,v,w,p)
262 
263  vmag = sqrt(u*u + v*v) ! w assumed to be zero
264  betah = asin(v/vmag)
265  mach = vmag/mixtperf_c_dgp(d,ggas,p)
266 
267  ppatch%mixt%vals(bcdat_inflow_ptot ,ifl) = ptot
268  ppatch%mixt%vals(bcdat_inflow_ttot ,ifl) = ttot
269  ppatch%mixt%vals(bcdat_inflow_betah,ifl) = betah
270  ppatch%mixt%vals(bcdat_inflow_betav,ifl) = 0.0_rfreal
271  ppatch%mixt%vals(bcdat_inflow_mach ,ifl) = mach
272  END DO ! ifl
273  ELSE
274  WRITE(errorstring,'(A,1X,I3)') 'Patch:',ipatch
275  CALL errorstop(global,err_distrib_invalid,__line__, &
276  trim(errorstring))
277  END IF ! pPatch%mixt%distrib
278  END IF ! pPatch%bcType
279  END DO ! iPatch
280 
281 ! ==============================================================================
282 ! Default - must be due to input error
283 ! ==============================================================================
284 
285  CASE default
286  CALL errorstop(global,err_reached_default,__line__)
287  END SELECT ! global%casename
288 
289 ! ******************************************************************************
290 ! End
291 ! ******************************************************************************
292 
293  IF ( global%verbLevel > verbose_none ) THEN
294  WRITE(stdout,'(A,1X,A)') solver_name, &
295  'Initializing boundary-condition data from hard code done.'
296  END IF ! global%verbLevel
297 
298  CALL deregisterfunction(global)
299 
300 END SUBROUTINE rflu_initbcdatahardcode
301 
302 ! ******************************************************************************
303 !
304 ! RCS Revision history:
305 !
306 ! $Log: RFLU_InitBcDataHardCode.F90,v $
307 ! Revision 1.7 2008/12/06 08:44:56 mtcampbe
308 ! Updated license.
309 !
310 ! Revision 1.6 2008/11/19 22:18:06 mtcampbe
311 ! Added Illinois Open Source License/Copyright
312 !
313 ! Revision 1.5 2006/08/19 15:41:09 mparmar
314 ! Renamed patch variables
315 !
316 ! Revision 1.4 2006/03/08 23:39:39 haselbac
317 ! Added 1 layer ssvort cases
318 !
319 ! Revision 1.3 2005/10/09 15:40:19 haselbac
320 ! Added 2d C0 case
321 !
322 ! Revision 1.2 2005/04/27 02:14:52 haselbac
323 ! Adapted to changes in inflow treatment
324 !
325 ! Revision 1.1 2005/04/15 15:08:13 haselbac
326 ! Initial revision
327 !
328 ! Revision 1.5 2004/10/19 19:30:53 haselbac
329 ! Removed setting of relative velocity on injection boundaries
330 !
331 ! Revision 1.4 2004/07/06 15:15:53 haselbac
332 ! Adapted to changes in libflu and modflu, cosmetics
333 !
334 ! Revision 1.3 2004/02/23 23:05:10 haselbac
335 ! Added Proudman solution for ONERA C0 case
336 !
337 ! Revision 1.2 2004/02/13 03:05:54 haselbac
338 ! Added more casenames
339 !
340 ! Revision 1.1 2004/01/29 22:58:49 haselbac
341 ! Initial revision
342 !
343 ! ******************************************************************************
344 
345 
346 
347 
348 
349 
350 
subroutine, public rflu_getparamshardcodessvortex(ri, Mi, pTot, tTot)
const NT & d
void int int REAL REAL * y
Definition: read.cpp:74
real(rfreal) function mixtperf_c_dgp(D, G, P)
Definition: MixtPerf_C.F90:56
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
double sqrt(double d)
Definition: double.h:73
real(rfreal) function mixtperf_r_cpg(Cp, G)
Definition: MixtPerf_R.F90:39
*********************************************************************Illinois Open Source License ****University of Illinois NCSA **Open Source License University of Illinois All rights reserved ****Developed free of to any person **obtaining a copy of this software and associated documentation to deal with the Software without including without limitation the rights to and or **sell copies of the and to permit persons to whom the **Software is furnished to do subject to the following this list of conditions and the following disclaimers ****Redistributions in binary form must reproduce the above **copyright this list of conditions and the following **disclaimers in the documentation and or other materials **provided with the distribution ****Neither the names of the Center for Simulation of Advanced the University of nor the names of its **contributors may be used to endorse or promote products derived **from this Software without specific prior written permission ****THE SOFTWARE IS PROVIDED AS 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 v
Definition: roccomf90.h:20
void int int REAL * x
Definition: read.cpp:74
real(rfreal) function mixtperf_t_dpr(D, P, R)
Definition: MixtPerf_T.F90:85
subroutine, public rflu_getparamshardcoderingleb(pTot, tTot)
subroutine, public rflu_computeexactflowringleb(x, y, rGas, pTot, tTot, d, u, v, w, p)
subroutine, public rflu_computeexactflowssvortex(x, y, gGas, rGas, ri, Mi, pTot, tTot, d, u, v, w, p)
subroutine, public rflu_getparamshardcodeproudman(dInc, mInj, vInj, pTot)
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
subroutine rflu_initbcdatahardcode(pRegion)
subroutine deregisterfunction(global)
Definition: ModError.F90:469
CImg< T > & atan2(const CImg< t > &img)
Compute the arc-tangent of each pixel.
Definition: CImg.h:12671
real(rfreal) function mixtperf_p_drt(D, R, T)
Definition: MixtPerf_P.F90:54
subroutine, public rflu_computeexactflowproudman(global, x, y, height, dInc, vInj, pTot, d, u, v, w, p)