Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
RFLO_ReadBcInflowTotAngSection.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: read in user input related to inflow boundary condition.
26 !
27 ! Description: present inflow bc is based on total pressure, total temperature
28 ! and flow angle.
29 !
30 ! Input: boundary condition file.
31 !
32 ! Output: regions = BC data.
33 !
34 ! Notes: none.
35 !
36 !******************************************************************************
37 !
38 ! $Id: RFLO_ReadBcInflowTotAngSection.F90,v 1.5 2008/12/06 08:44:07 mtcampbe Exp $
39 !
40 ! Copyright: (c) 2001 by the University of Illinois
41 !
42 !******************************************************************************
43 
44 SUBROUTINE rflo_readbcinflowtotangsection( regions )
45 
46  USE moddatatypes
47  USE modbndpatch, ONLY : t_patch
48  USE moddatastruct, ONLY : t_region
49  USE modglobal, ONLY : t_global
51  USE moderror
52  USE modparameters
53  IMPLICIT NONE
54 
55 #include "Indexing.h"
56 
57 ! ... parameters
58  TYPE(t_region), POINTER :: regions(:)
59 
60 ! ... loop variables
61  INTEGER :: ireg, ipatch
62 
63 ! ... local variables
64  CHARACTER(10) :: keys(7)
65  CHARACTER(256) :: fname
66 
67  INTEGER :: brbeg, brend, prbeg, prend, distrib, switch
68  INTEGER :: n1, n2, ioff, ijbeg, ijend, errorflag
69 
70  LOGICAL :: defined(7)
71 
72  REAL(RFREAL) :: vals(7)
73 
74  TYPE(t_patch), POINTER :: patch
75  TYPE(t_global), POINTER :: global
76 
77 !******************************************************************************
78 
79  global => regions(1)%global
80 
81  CALL registerfunction( global,'RFLO_ReadBcInflowTotAngSection',&
82  'RFLO_ReadBcInflowTotAngSection.F90' )
83 
84 ! specify keywords and search for them ----------------------------------------
85 
86  keys(1) = 'TYPE'
87  keys(2) = 'FIXED'
88  keys(3) = 'PTOT'
89  keys(4) = 'TTOT'
90  keys(5) = 'BETAH'
91  keys(6) = 'BETAV'
92  keys(7) = 'MACH'
93 
94  CALL readpatchsection( global,if_input,7,keys,vals,brbeg,brend, &
95  prbeg,prend,distrib,fname,defined )
96 
97 ! get switches & check if all necessary values defined ------------------------
98 
99  DO ireg=brbeg,brend
100  DO ipatch=prbeg,min(prend,regions(ireg)%nPatches)
101 
102  patch => regions(ireg)%levels(1)%patches(ipatch)
103 
104  IF ((patch%bcType>=bc_inflow .AND. &
105  patch%bcType<=bc_inflow+bc_range) .AND. & ! my boundary type,
106  regions(ireg)%procid==global%myProcid .AND. & ! region active and
107  regions(ireg)%active==active) THEN ! on my processor
108 
109  patch%bcType = bc_inflow_totang
110 
111  IF (patch%mixt%bcSet.eqv..true.) &
112  CALL errorstop( global,err_patch_overspec,&
113  __line__,'Inflow boundary.' )
114 
115  patch%mixt%nSwitches = 2
116  IF (patch%bcCoupled == bc_external) THEN ! data from outside
117  patch%mixt%distrib = bcdat_distrib ! => always distribution
118  ELSE
119  patch%mixt%distrib = distrib
120  ENDIF
121 
122  ALLOCATE( patch%mixt%switches(patch%mixt%nSwitches), &
123  stat=errorflag )
124  global%error = errorflag
125  IF (global%error /= 0) CALL errorstop( global,err_allocate,&
126  __line__ )
127 
128 ! ----- check if switch defined
129  IF (defined(1).eqv..true.) THEN
130  patch%mixt%switches(bcswi_inflow_type) = bcopt_subsonic
131  IF (vals(1) < 0.1) &
132  patch%mixt%switches(bcswi_inflow_type) = bcopt_supersonic
133  IF (vals(1) > 1.9) &
134  patch%mixt%switches(bcswi_inflow_type) = bcopt_mixed
135  ELSE
136  CALL errorstop( global,err_no_bcswitch,&
137  __line__,'(inflow type).' )
138  ENDIF
139 
140  IF (defined(2).eqv..true.) THEN
141  IF (vals(2) < 0.1) &
142  patch%mixt%switches(bcswi_inflow_fixed) = bcopt_fixed_no
143  IF (vals(2) > 0.9) &
144  patch%mixt%switches(bcswi_inflow_fixed) = bcopt_fixed_yes
145  ELSE
146  patch%mixt%switches(bcswi_inflow_fixed) = bcopt_fixed_no
147  ENDIF
148 
149 ! ----- check if appropriate values specified
150  IF (patch%mixt%switches(bcswi_inflow_type) == bcopt_subsonic) THEN
151  IF (patch%mixt%distrib==bcdat_constant .AND. &
152  (.NOT. (defined(3).eqv..true.) .OR. &
153  .NOT. (defined(4).eqv..true.) .OR. &
154  .NOT. (defined(5).eqv..true.) .OR. &
155  .NOT. (defined(6).eqv..true.))) CALL errorstop( global,err_bcval_missing,&
156  __line__ )
157  ENDIF
158  IF (patch%mixt%switches(bcswi_inflow_type) == bcopt_supersonic .OR. &
159  patch%mixt%switches(bcswi_inflow_type) == bcopt_mixed) THEN
160  IF (patch%mixt%distrib==bcdat_constant .AND. &
161  (.NOT. (defined(3).eqv..true.) .OR. &
162  .NOT. (defined(4).eqv..true.) .OR. &
163  .NOT. (defined(5).eqv..true.) .OR. &
164  .NOT. (defined(6).eqv..true.) .OR. &
165  .NOT. (defined(7).eqv..true.))) CALL errorstop( global,err_bcval_missing,&
166  __line__ )
167  ENDIF
168 
169 ! ----- set flag to BC specified
170  patch%mixt%bcSet = .true.
171 
172  ENDIF ! my BC & processor, active
173  ENDDO
174  ENDDO
175 
176 ! copy values/distribution to variables ---------------------------------------
177 
178  DO ireg=brbeg,brend
179  DO ipatch=prbeg,min(prend,regions(ireg)%nPatches)
180 
181  patch => regions(ireg)%levels(1)%patches(ipatch)
182 
183  IF ((patch%bcType>=bc_inflow .AND. &
184  patch%bcType<=bc_inflow+bc_range) .AND. & ! my boundary type,
185  regions(ireg)%procid==global%myProcid .AND. & ! region active and
186  regions(ireg)%active==active) THEN ! on my processor
187 
188  switch = patch%mixt%switches(bcswi_inflow_type)
189  IF (switch == bcopt_subsonic) THEN
190  patch%mixt%nData = 4
191  ELSE
192  patch%mixt%nData = 5
193  ENDIF
194 
195 ! ----- allocate memory for the values
196 
197  IF (patch%mixt%distrib == bcdat_distrib) THEN
198  n1 = abs(patch%l1end-patch%l1beg)
199  n2 = abs(patch%l2end-patch%l2beg)
200  ioff = n1 + 1
201  ijbeg = indij( 0, 0,ioff)
202  ijend = indij(n1,n2,ioff)
203  ELSE
204  ijbeg = 0
205  ijend = 1
206  ENDIF
207  ALLOCATE( patch%mixt%vals(patch%mixt%nData,ijbeg:ijend), &
208  stat=errorflag )
209  global%error = errorflag
210  IF (global%error /= 0) CALL errorstop( global,err_allocate,&
211  __line__ )
212 
213 ! ----- distribution from file
214 
215  IF (patch%mixt%distrib==bcdat_distrib .AND. &
216  patch%bcCoupled /=bc_external ) THEN
217  CALL rflo_readbcfromfile( global,fname,patch )
218 
219  IF (switch == bcopt_subsonic) THEN
220  patch%mixt%vals(bcdat_inflow_betah,:) = &
221  patch%mixt%vals(bcdat_inflow_betah,:)*global%rad
222  patch%mixt%vals(bcdat_inflow_betav,:) = &
223  patch%mixt%vals(bcdat_inflow_betav,:)*global%rad
224  ENDIF
225 
226 ! ----- distribution from external source / constant value
227 
228  ELSE
229  patch%mixt%vals(bcdat_inflow_ptot ,:) = vals(3)
230  patch%mixt%vals(bcdat_inflow_ttot ,:) = vals(4)
231  patch%mixt%vals(bcdat_inflow_betah,:) = vals(5)*global%rad
232  patch%mixt%vals(bcdat_inflow_betav,:) = vals(6)*global%rad
233  IF (switch /= bcopt_subsonic) THEN
234  patch%mixt%vals(bcdat_inflow_mach,:) = vals(7)
235  ENDIF
236  ENDIF ! distribution?
237 
238  ENDIF ! bcType, active region on my processor
239 
240  ENDDO ! iPatch
241  ENDDO ! iReg
242 
243 ! finalize --------------------------------------------------------------------
244 
245  CALL deregisterfunction( global )
246 
247 END SUBROUTINE rflo_readbcinflowtotangsection
248 
249 !******************************************************************************
250 !
251 ! RCS Revision history:
252 !
253 ! $Log: RFLO_ReadBcInflowTotAngSection.F90,v $
254 ! Revision 1.5 2008/12/06 08:44:07 mtcampbe
255 ! Updated license.
256 !
257 ! Revision 1.4 2008/11/19 22:17:20 mtcampbe
258 ! Added Illinois Open Source License/Copyright
259 !
260 ! Revision 1.3 2008/10/23 18:20:53 mtcampbe
261 ! Crazy number of changes to track and fix initialization and
262 ! restart bugs. Many improperly formed logical expressions
263 ! were fixed, and bug in allocation for data associated with
264 ! the BC_INFLOWVELTEMP boundary condition squashed in
265 ! RFLO_ReadBcInflowVelSection.F90.
266 !
267 ! Revision 1.2 2006/08/19 15:38:10 mparmar
268 ! Renamed patch variables
269 !
270 ! Revision 1.1 2005/04/28 05:48:28 wasistho
271 ! added velocity based inflow BC
272 !
273 ! Revision 1.1 2004/11/29 21:25:16 wasistho
274 ! lower to upper case
275 !
276 ! Revision 1.7 2004/01/29 22:55:30 haselbac
277 ! Read new argument
278 !
279 ! Revision 1.6 2003/11/20 16:40:34 mdbrandy
280 ! Backing out RocfluidMP changes from 11-17-03
281 !
282 ! Revision 1.3 2003/05/15 02:57:01 jblazek
283 ! Inlined index function.
284 !
285 ! Revision 1.2 2003/02/11 22:30:21 jferry
286 ! Re-worked BC and TBC input routines to add multi-physics capability
287 !
288 ! Revision 1.1 2002/10/19 00:40:30 jblazek
289 ! Added utility (rflosurf) to write out surface grids for GenX.
290 !
291 ! Revision 1.13 2002/10/12 03:20:50 jblazek
292 ! Replaced [io]stat=global%error with local errorFlag for Rocflo.
293 !
294 ! Revision 1.12 2002/09/27 00:57:10 jblazek
295 ! Changed makefiles - no makelinks needed.
296 !
297 ! Revision 1.11 2002/09/20 22:22:36 jblazek
298 ! Finalized integration into GenX.
299 !
300 ! Revision 1.10 2002/09/17 13:43:00 jferry
301 ! Added Time-dependent boundary conditions
302 !
303 ! Revision 1.9 2002/09/05 17:40:22 jblazek
304 ! Variable global moved into regions().
305 !
306 ! Revision 1.8 2002/06/22 01:13:38 jblazek
307 ! Modified interfaces to BC routines.
308 !
309 ! Revision 1.7 2002/03/29 23:15:22 jblazek
310 ! Corrected bug in MPI send.
311 !
312 ! Revision 1.6 2002/02/21 23:25:06 jblazek
313 ! Blocks renamed as regions.
314 !
315 ! Revision 1.5 2002/02/09 01:47:01 jblazek
316 ! Added multi-probe option, residual smoothing, physical time step.
317 !
318 ! Revision 1.4 2002/01/31 20:56:30 jblazek
319 ! Added basic boundary conditions.
320 !
321 ! Revision 1.3 2002/01/11 17:20:19 jblazek
322 ! Added time stamp or iteration number to file names.
323 !
324 ! Revision 1.2 2001/12/22 00:09:39 jblazek
325 ! Added routines to store grid and solution.
326 !
327 ! Revision 1.1 2001/12/08 00:18:42 jblazek
328 ! Added routines to read BC input file.
329 !
330 !******************************************************************************
331 
332 
333 
334 
335 
336 
337 
subroutine rflo_readbcfromfile(global, fname, patch)
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
**********************************************************************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 brbeg
subroutine readpatchsection(global, fileID, nvals, keys, vals, brbeg, brend, prbeg, prend, distrib, profType, fname, defined)
Definition: patch.h: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 USE ModDataTypes USE prend
**********************************************************************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 USE ModDataTypes USE prbeg
Vector_n min(const Array_n_const &v1, const Array_n_const &v2)
Definition: Vector_n.h:346
subroutine rflo_readbcinflowtotangsection(regions)
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
subroutine deregisterfunction(global)
Definition: ModError.F90:469