Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
RFLU_ComputeIntegralValues.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 integrals for GENx checking.
26 !
27 ! Description: None.
28 !
29 ! Input:
30 ! regions Region data
31 !
32 ! Output:
33 ! integ Vector of integrals (for output by Rocman)
34 !
35 ! Notes: None.
36 !
37 ! ******************************************************************************
38 !
39 ! $Id: RFLU_ComputeIntegralValues.F90,v 1.7 2008/12/06 08:44:29 mtcampbe Exp $
40 !
41 ! Copyright: (c) 2002-2005 by the University of Illinois
42 !
43 ! ******************************************************************************
44 
45 #ifdef GENX
46 SUBROUTINE rflu_computeintegralvalues(regions,integ)
47 #else
48 SUBROUTINE rflu_computeintegralvalues(regions)
49 #endif
50 
51  USE modglobal, ONLY: t_global
52  USE modparameters
53  USE moddatatypes
54  USE modbndpatch, ONLY: t_patch
55  USE moddatastruct, ONLY: t_region
56  USE moderror
57  USE modmpi
58 
59  IMPLICIT NONE
60 
61 #ifdef GENX
62  include 'rocmanf90.h'
63 #endif
64 
65 ! ******************************************************************************
66 ! Declarations and definitions
67 ! ******************************************************************************
68 
69 ! ==============================================================================
70 ! Arguments
71 ! ==============================================================================
72 
73  TYPE(t_region), POINTER :: regions(:)
74 
75 ! ==============================================================================
76 ! Locals
77 ! ==============================================================================
78 
79  CHARACTER(CHRLEN) :: rcsidentstring
80  INTEGER :: errorflag,i,ic,ifc,ipatch,ireg
81  REAL(RFREAL) :: enerlocal,ibarealocal,inbarealocal,masslocal,xmomlocal, &
82  ymomlocal,zmomlocal,vollocal
83 #ifdef GENX
84  DOUBLE PRECISION, DIMENSION(MAN_INTEG_SIZE) :: integ
85  REAL(RFREAL), DIMENSION(MAN_INTEG_SIZE) :: globalvals,localvals
86 #else
87  REAL(RFREAL), DIMENSION(2) :: globalvals,localvals
88 #endif
89  REAL(RFREAL), DIMENSION(:), POINTER :: pvol
90  REAL(RFREAL), DIMENSION(:,:), POINTER :: pcv
91  TYPE(t_global), POINTER :: global
92  TYPE(t_patch), POINTER :: ppatch
93  TYPE(t_region), POINTER :: pregion
94 
95 ! ******************************************************************************
96 ! Start
97 ! ******************************************************************************
98 
99  rcsidentstring = '$RCSfile: RFLU_ComputeIntegralValues.F90,v $ $Revision: 1.7 $'
100 
101  global => regions(1)%global
102 
103  CALL registerfunction(global,'RFLU_ComputeIntegralValues',&
104  'RFLU_ComputeIntegralValues.F90')
105 
106 ! ******************************************************************************
107 ! Compute total volume and total mass
108 ! ******************************************************************************
109 
110  vollocal = 0.0_rfreal
111  masslocal = 0.0_rfreal
112 
113  DO ireg = 1,global%nRegionsLocal
114  pregion => regions(ireg)
115 
116  pvol => pregion%grid%vol
117  pcv => pregion%mixt%cv
118 
119  DO ic = 1,pregion%grid%nCells
120  vollocal = vollocal + pvol(ic)
121  masslocal = masslocal + pcv(cv_mixt_dens,ic)*pvol(ic)
122  END DO ! ic
123  END DO ! iReg
124 
125 #ifdef GENX
126 ! ******************************************************************************
127 ! Compute momenta components and energy
128 ! ******************************************************************************
129 
130  xmomlocal = 0.0_rfreal ! Not computed at present
131  ymomlocal = 0.0_rfreal
132  zmomlocal = 0.0_rfreal
133  enerlocal = 0.0_rfreal
134 
135 ! ******************************************************************************
136 ! Compute interacting surface areas
137 ! ******************************************************************************
138 
139  inbarealocal = 0.0_rfreal
140  ibarealocal = 0.0_rfreal
141 
142  DO ireg = 1,global%nRegionsLocal
143  pregion => regions(ireg)
144 
145  DO ipatch = 1,pregion%grid%nPatches
146  ppatch => pregion%patches(ipatch)
147 
148  IF ( ppatch%bcCoupled == bc_burning ) THEN
149  DO ifc = 1,ppatch%nBFaces
150  ibarealocal = ibarealocal + ppatch%fn(xyzmag,ifc)
151  END DO ! ifc
152  ELSE IF ( ppatch%bcCoupled == bc_not_burning ) THEN
153  DO ifc = 1,ppatch%nBFaces
154  inbarealocal = inbarealocal + ppatch%fn(xyzmag,ifc)
155  END DO ! ifc
156  END IF ! pPatach%bcCoupled
157  END DO ! iPatch
158  END DO ! iReg
159 #endif
160 
161 ! ******************************************************************************
162 ! Gather data
163 ! ******************************************************************************
164 
165 #ifdef GENX
166  localvals(man_integ_vol ) = vollocal
167  localvals(man_integ_mass ) = masslocal
168  localvals(man_integ_xmom ) = xmomlocal
169  localvals(man_integ_ymom ) = ymomlocal
170  localvals(man_integ_zmom ) = zmomlocal
171  localvals(man_integ_ener ) = enerlocal
172  localvals(man_integ_ibarea ) = ibarealocal
173  localvals(man_integ_inbarea) = inbarealocal
174 #else
175  localvals(1) = vollocal
176  localvals(2) = masslocal
177 #endif
178 
179 ! ******************************************************************************
180 ! Perform reduction operation
181 ! ******************************************************************************
182 
183  CALL mpi_reduce(localvals,globalvals,SIZE(localvals,1),mpi_rfreal,mpi_sum, &
184  masterproc,global%mpiComm,errorflag)
185  global%error = errorflag
186  IF ( global%error /= err_none ) THEN
187  CALL errorstop(global,err_mpi_trouble,__line__)
188  END IF ! global%errorFlag
189 
190 ! ******************************************************************************
191 ! Scatter data
192 ! ******************************************************************************
193 
194 #ifdef GENX
195  DO i = 1,man_integ_size ! Explicit loop to avoid ASCI White problem
196  integ(i) = globalvals(i)
197  END DO ! i
198 #else
199  global%totalVol = globalvals(1)
200  global%totalMass = globalvals(2)
201 #endif
202 
203 ! ******************************************************************************
204 ! End
205 ! ******************************************************************************
206 
207  CALL deregisterfunction(global)
208 
209 END SUBROUTINE rflu_computeintegralvalues
210 
211 !* *****************************************************************************
212 !
213 ! RCS Revision history:
214 !
215 ! $Log: RFLU_ComputeIntegralValues.F90,v $
216 ! Revision 1.7 2008/12/06 08:44:29 mtcampbe
217 ! Updated license.
218 !
219 ! Revision 1.6 2008/11/19 22:17:42 mtcampbe
220 ! Added Illinois Open Source License/Copyright
221 !
222 ! Revision 1.5 2006/04/07 15:19:22 haselbac
223 ! Removed tabs
224 !
225 ! Revision 1.4 2005/04/15 15:07:14 haselbac
226 ! Converted to MPI, cosmetics
227 !
228 ! Revision 1.3 2003/04/23 13:58:56 haselbac
229 ! Bug fix
230 !
231 ! Revision 1.2 2003/01/28 14:32:16 haselbac
232 ! Use parameters in fn
233 !
234 ! Revision 1.1 2002/11/15 21:27:46 haselbac
235 ! Initial revision
236 !
237 ! ******************************************************************************
238 
239 
240 
241 
242 
243 
244 
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 ic
subroutine rflu_computeintegralvalues(regions)
blockLoc i
Definition: read.cpp:79
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
subroutine deregisterfunction(global)
Definition: ModError.F90:469