Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
RFLU_ScalarSecondPatch.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: Compute second-order accurate discretization of scalar inviscid flux
26 ! through boundary faces.
27 !
28 ! Description: None.
29 !
30 ! Input:
31 ! pRegion Pointer to data of current region
32 ! pPatch Pointer to data of current patch
33 ! nVarScal Number of scalars
34 ! cvScal Vector of conserved scalar variables
35 ! gradCellScal Cell gradients of scalar variables
36 ! valScal Boundary values of scalar variables
37 !
38 ! Output:
39 ! resScal Residual of scalar variables
40 !
41 ! Notes: None.
42 !
43 ! ******************************************************************************
44 !
45 ! $Id: RFLU_ScalarSecondPatch.F90,v 1.8 2008/12/06 08:44:13 mtcampbe Exp $
46 !
47 ! Copyright: (c) 2004-2006 by the University of Illinois
48 !
49 ! ******************************************************************************
50 
51 SUBROUTINE rflu_scalarsecondpatch(pRegion,pPatch,nVarScal,cvScal, &
52  gradcellscal,valscal,resscal)
53 
54  USE modglobal, ONLY: t_global
55  USE moddatatypes
56  USE modbndpatch, ONLY: t_bcvalues,t_patch
57  USE moddatastruct, ONLY: t_region
58  USE modgrid, ONLY: t_grid
59  USE moderror
60  USE modparameters
61 
62  IMPLICIT NONE
63 
64 ! ******************************************************************************
65 ! Definitions and declarations
66 ! ******************************************************************************
67 
68 ! ==============================================================================
69 ! Arguments
70 ! ==============================================================================
71 
72  INTEGER, INTENT(IN) :: nvarscal
73  REAL(RFREAL), DIMENSION(:,:), INTENT(IN) :: cvscal
74  REAL(RFREAL), DIMENSION(:,:), INTENT(INOUT) :: resscal
75  REAL(RFREAL), DIMENSION(:,:,:), INTENT(IN) :: gradcellscal
76  TYPE(t_bcvalues) :: valscal
77  TYPE(t_patch), POINTER :: ppatch
78  TYPE(t_region), POINTER :: pregion
79 
80 ! ==============================================================================
81 ! Locals
82 ! ==============================================================================
83 
84  CHARACTER(CHRLEN) :: rcsidentstring
85  INTEGER :: c1,bctype,distscal,ifc,ivarscal
86  REAL(RFREAL) :: dx,dy,dz,flx,mf,sl
87  REAL(RFREAL), DIMENSION(:), POINTER :: pmfmixt
88  REAL(RFREAL), DIMENSION(:,:), POINTER :: rhs
89  TYPE(t_global), POINTER :: global
90  TYPE(t_grid), POINTER :: pgrid
91 
92 ! ******************************************************************************
93 ! Start
94 ! ******************************************************************************
95 
96  rcsidentstring = '$RCSfile: RFLU_ScalarSecondPatch.F90,v $ $Revision: 1.8 $'
97 
98  global => pregion%global
99 
100  CALL registerfunction(global,'RFLU_ScalarSecondPatch',&
101  'RFLU_ScalarSecondPatch.F90')
102 
103 ! ******************************************************************************
104 ! Checks: Defensive coding, should never occur
105 ! ******************************************************************************
106 
107  IF ( pregion%mixtInput%indMfMixt /= 1 ) THEN
108  CALL errorstop(global,err_indmfmixt_invalid,__line__)
109  END IF ! pRegion%mixtInput%indMfMixt
110 
111 ! ******************************************************************************
112 ! Set pointers and variables
113 ! ******************************************************************************
114 
115  pgrid => pregion%grid
116  pmfmixt => ppatch%mfMixt
117 
118  bctype = ppatch%bcType
119  distscal = valscal%distrib
120 
121 ! ******************************************************************************
122 ! Select boundary type
123 ! ******************************************************************************
124 
125  SELECT CASE ( bctype )
126 
127 ! ==============================================================================
128 ! Inflow
129 ! ==============================================================================
130 
131  CASE ( bc_inflow_totang,bc_inflow_veltemp )
132  DO ifc = 1,ppatch%nBFaces
133  c1 = ppatch%bf2c(ifc)
134 
135  mf = pmfmixt(ifc)
136 
137  DO ivarscal = 1,nvarscal
138  flx = mf*valscal%vals(ivarscal,distscal*ifc)
139 
140  resscal(ivarscal,c1) = resscal(ivarscal,c1) + flx
141  END DO ! iVarScal
142  END DO ! ifc
143 
144 ! ==============================================================================
145 ! Outflow
146 ! ==============================================================================
147 
148  CASE ( bc_outflow )
149  DO ifc = 1,ppatch%nBFaces
150  c1 = ppatch%bf2c(ifc)
151 
152  dx = ppatch%fc(xcoord,ifc) - pgrid%cofg(xcoord,c1)
153  dy = ppatch%fc(ycoord,ifc) - pgrid%cofg(ycoord,c1)
154  dz = ppatch%fc(zcoord,ifc) - pgrid%cofg(zcoord,c1)
155 
156  mf = pmfmixt(ifc)
157 
158  DO ivarscal = 1,nvarscal
159  sl = cvscal(ivarscal,c1)
160 
161  sl = sl + gradcellscal(xcoord,ivarscal,c1)*dx &
162  + gradcellscal(ycoord,ivarscal,c1)*dy &
163  + gradcellscal(zcoord,ivarscal,c1)*dz
164 
165  flx = mf*sl
166 
167  resscal(ivarscal,c1) = resscal(ivarscal,c1) + flx
168  END DO ! iVarScal
169  END DO ! ifc
170 
171 ! ==============================================================================
172 ! Slip wall
173 ! ==============================================================================
174 
175  CASE ( bc_slipwall )
176 
177 ! ==============================================================================
178 ! No-slip wall
179 ! ==============================================================================
180 
181  CASE ( bc_noslipwall_hflux,bc_noslipwall_temp )
182 
183 ! ==============================================================================
184 ! Farfield
185 ! ==============================================================================
186 
187  CASE ( bc_farfield )
188  DO ifc = 1,ppatch%nBFaces
189  c1 = ppatch%bf2c(ifc)
190 
191  mf = pmfmixt(ifc)
192 
193  IF ( mf > 0.0_rfreal ) THEN ! Outflow
194  dx = ppatch%fc(xcoord,ifc) - pgrid%cofg(xcoord,c1)
195  dy = ppatch%fc(ycoord,ifc) - pgrid%cofg(ycoord,c1)
196  dz = ppatch%fc(zcoord,ifc) - pgrid%cofg(zcoord,c1)
197 
198  DO ivarscal = 1,nvarscal
199  sl = cvscal(ivarscal,c1)
200 
201  sl = sl + gradcellscal(xcoord,ivarscal,c1)*dx &
202  + gradcellscal(ycoord,ivarscal,c1)*dy &
203  + gradcellscal(zcoord,ivarscal,c1)*dz
204 
205  flx = mf*sl
206 
207  resscal(ivarscal,c1) = resscal(ivarscal,c1) + flx
208  END DO ! iVarScal
209  ELSE ! Inflow
210  DO ivarscal = 1,nvarscal
211  flx = mf*valscal%vals(ivarscal,distscal*ifc)
212 
213  resscal(ivarscal,c1) = resscal(ivarscal,c1) + flx
214  END DO ! iVarScal
215  END IF ! mf
216  END DO ! ifc
217 
218 ! ==============================================================================
219 ! Injection
220 ! ==============================================================================
221 
222  CASE ( bc_injection )
223  DO ifc = 1,ppatch%nBFaces
224  c1 = ppatch%bf2c(ifc)
225 
226  mf = pmfmixt(ifc)
227 
228  DO ivarscal = 1,nvarscal
229  flx = mf*valscal%vals(ivarscal,distscal*ifc)
230 
231  resscal(ivarscal,c1) = resscal(ivarscal,c1) + flx
232  END DO ! iVarScal
233  END DO ! ifc
234 
235 ! ==============================================================================
236 ! Boundaries for which fluxes must not or need not be computed
237 ! ==============================================================================
238 
239  CASE ( bc_periodic, &
240  bc_symmetry, &
241  bc_virtual )
242 
243 ! ==============================================================================
244 ! Default
245 ! ==============================================================================
246 
247  CASE default
248  CALL errorstop(global,err_reached_default,__line__)
249  END SELECT ! bcType
250 
251 ! ******************************************************************************
252 ! End
253 ! ******************************************************************************
254 
255  CALL deregisterfunction(global)
256 
257 END SUBROUTINE rflu_scalarsecondpatch
258 
259 ! ******************************************************************************
260 !
261 ! RCS Revision history:
262 !
263 ! $Log: RFLU_ScalarSecondPatch.F90,v $
264 ! Revision 1.8 2008/12/06 08:44:13 mtcampbe
265 ! Updated license.
266 !
267 ! Revision 1.7 2008/11/19 22:17:26 mtcampbe
268 ! Added Illinois Open Source License/Copyright
269 !
270 ! Revision 1.6 2006/04/07 15:19:16 haselbac
271 ! Removed tabs
272 !
273 ! Revision 1.5 2006/03/26 20:28:42 haselbac
274 ! Removed unnecessary BC_RANGE
275 !
276 ! Revision 1.4 2006/03/25 21:43:47 haselbac
277 ! Added CASEs for sype patches
278 !
279 ! Revision 1.3 2005/11/10 02:03:16 haselbac
280 ! Added virtual boundary, cleaned up CASE statements
281 !
282 ! Revision 1.2 2005/04/20 14:40:15 haselbac
283 ! Removed CHECK_UNIFLOW code section, cosmetics
284 !
285 ! Revision 1.1 2004/01/29 22:56:14 haselbac
286 ! Initial revision
287 !
288 ! ******************************************************************************
289 
290 
291 
292 
293 
294 
295 
NT dx
NT rhs
subroutine rflu_scalarsecondpatch(pRegion, pPatch, nVarScal, cvScal, gradCellScal, valScal, resScal)
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
RT dz() const
Definition: Direction_3.h:133
NT dy
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
subroutine deregisterfunction(global)
Definition: ModError.F90:469