Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
INRT_DefineBurning.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: Defines the interaction Burning
26 !
27 ! Description: none.
28 !
29 ! Input: region = data of current region.
30 !
31 ! Output: modifies region%inrtInput%inrts
32 !
33 ! Notes:
34 !
35 ! Whereas INRT_Initialize sets up everything generic to all interactions,
36 ! this routine sets up things specific to this interaction.
37 !
38 ! In particular, this is where the designer
39 !
40 ! (a) gives values for all the interactions parameters (or leaves them
41 ! as default values given in INRT_Initialize). These parameters are
42 ! described in ModInteract.
43 !
44 ! (b) defines the Edges of the interaction. Here the type of an Edge is
45 ! given (i.e., whether it transports mass, momentum, or energy), as well
46 ! as the indices of the Nodes at either end. For each momentum Edge
47 ! he must call the routine INRT_FinishMomentumEdge.
48 !
49 !******************************************************************************
50 !
51 ! $Id: INRT_DefineBurning.F90,v 1.5 2008/12/06 08:44:31 mtcampbe Exp $
52 !
53 ! Copyright: (c) 2003 by the University of Illinois
54 !
55 !******************************************************************************
56 
57 SUBROUTINE inrt_defineburning( region,matIndIn,matIndOut,matIndOx, &
58  oxused,plagoutexists )
59 
60  USE moddatatypes
61  USE moddatastruct, ONLY : t_region
62  USE modglobal, ONLY : t_global
63  USE modinteract
64  USE moderror
65  USE modparameters
67 
69  IMPLICIT NONE
70 
71 ! ... parameters
72  TYPE(t_region), INTENT(INOUT) :: region
73  INTEGER, INTENT(IN) :: matindin,matindout,matindox
74  LOGICAL, INTENT(INOUT) :: oxused
75  LOGICAL, INTENT(OUT) :: plagoutexists
76 
77 ! ... loop variables
78  INTEGER :: iplag,ipeul,ipeuloutedge
79 
80 ! ... local variables
81  INTEGER, PARAMETER :: npeuloutedges_max = 10
82 
83  CHARACTER(CHRLEN) :: rcsidentstring
84 
85  INTEGER :: nplag,npeul,nedges,nplaginedges,nplagoutedges,npeuloutedges
86  INTEGER :: npeuloxedges,matindplag,matindpeul
87  INTEGER :: iplagin,iplagout,ipeulox,ipeuloxedge
88  INTEGER :: ipeularr(npeuloutedges_max)
89 
90  TYPE(t_inrt_input), POINTER :: input
91  TYPE(t_inrt_interact), POINTER :: inrt
92  TYPE(t_inrt_edge), POINTER :: edge
93  TYPE(t_global), POINTER :: global
94 
95 !******************************************************************************
96 
97  rcsidentstring = '$RCSfile: INRT_DefineBurning.F90,v $ $Revision: 1.5 $'
98 
99  global => region%global
100 
101  CALL registerfunction( global,'INRT_DefineBurning',&
102  'INRT_DefineBurning.F90' )
103 
104 ! begin -----------------------------------------------------------------------
105 
106 ! allocate memory for edges, switches and data
107 
108  input => region%inrtInput
109  inrt => input%inrts(inrt_type_burning)
110 
111  inrt%name = "Burning"
112 
113  nplag = input%nPlag
114  npeul = input%nPeul
115 
116 ! loop over particle types looking for those with material index
117 ! matIndIn or matIndOut
118 
119  nplaginedges = 0
120  nplagoutedges = 0
121  DO iplag = 1,nplag
122 
123 #ifdef PLAG
124  matindplag = region%plagInput%materialIndex(iplag)
125 #endif
126 
127  IF (matindplag == matindin) THEN
128 
129  nplaginedges = nplaginedges + 1
130  iplagin = iplag
131 
132  ELSE IF (matindplag == matindout) THEN
133 
134  nplagoutedges = nplagoutedges + 1
135  iplagout = iplag
136 
137  END IF ! matIndPlag
138 
139  END DO ! iPlag
140 
141  IF (nplaginedges > 1 .OR. nplagoutedges > 1) &
142  CALL errorstop( global,err_inrt_multplagmat,__line__ )
143 
144  IF (nplaginedges < 1) &
145  CALL errorstop( global,err_inrt_missplagmat,__line__ )
146 
147  plagoutexists = .true.
148  IF (nplagoutedges < 1) THEN
149  plagoutexists = .false. ! flag that no transfer can occur for this Edge
150  iplagout = iplagin ! therefore the Node index used does not matter
151  END IF ! nPlagOutEdges
152 
153 ! loop over smoke types looking for those with material index matIndOut
154 ! or, if oxidizer is used, those with index matIndOx
155 
156  ipeuloutedge = 0
157  ipeuloxedge = 0
158  DO ipeul = 1,npeul
159 
160 #ifdef RFLO
161 #ifdef PEUL
162  matindpeul = region%peulInput%ptypes(ipeul)%material%index
163 #endif
164 #endif
165 #ifdef RFLU
166  matindpeul = region%specInput%specType(ipeul)%pMaterial%index
167 #endif
168 
169  IF (matindpeul == matindout) THEN
170 
171  ipeuloutedge = ipeuloutedge + 1
172 
173  IF (ipeuloutedge > npeuloutedges_max) &
174  CALL errorstop( global,err_exceeds_decl_mem,__line__ )
175 
176  ipeularr(ipeuloutedge) = ipeul
177 
178  ELSE IF (oxused) THEN
179 
180  IF (matindpeul == matindox) THEN
181 
182  ipeuloxedge = ipeuloxedge + 1
183 
184  IF (ipeuloxedge > 1) &
185  CALL errorstop( global,err_inrt_only1,__line__ )
186 
187  ipeulox = ipeul
188 
189  END IF ! matIndPeul
190 
191  END IF ! oxUsed
192 
193  END DO ! iPeul
194 
195  npeuloutedges = ipeuloutedge
196  npeuloxedges = ipeuloxedge
197  nedges = inrt_burning_nedges0 + npeuloutedges + npeuloxedges
198 
199  IF (oxused .AND. npeuloxedges < 1) THEN
200  WRITE(stdout,'(A)') solver_name//'### INRT_WARNING: no oxidizer smoke '// &
201  'type: setting OX_USED = NO'
202  oxused = .false.
203  END IF
204 
205  CALL inrt_allocateauxillary(global,inrt,nedges, &
206  inrt_swi_burning_total,inrt_dat_burning_total0 + npeuloutedges)
207 
208 ! set parameters for this interaction: see comment in ModInteract
209 
210  inrt%nIntl = 1
211  inrt%nInputEdges = 2 + npeuloxedges
212 
213 ! define Edges
214 
215  edge => inrt%edges(inrt_burning_g_mass_x)
216 
217  edge%tEdge = inrt_edge_mass
218  edge%iNode(1) = input%indMixt
219  edge%iNode(2) = input%indIntl
220 
221  edge => inrt%edges(inrt_burning_l_mass_x)
222 
223  edge%tEdge = inrt_edge_mass
224  edge%iNode(1) = input%indPlag0 + iplagin
225  edge%iNode(2) = input%indIntl
226 
227  IF (npeuloxedges > 0) THEN
228 
229  edge => inrt%edges(inrt_burning_s_mass_x0 + npeuloxedges)
230 
231  edge%tEdge = inrt_edge_mass_gho
232  edge%iNode(1) = input%indPeul0 + ipeulox
233  edge%iNode(2) = input%indIntl
234 
235  END IF ! nPeulOxEdges
236 
237  edge => inrt%edges(inrt_burning_x_ener_g + npeuloxedges)
238 
239  edge%tEdge = inrt_edge_ener
240  edge%iNode(1) = input%indIntl
241  edge%iNode(2) = input%indMixt
242 
243  edge => inrt%edges(inrt_burning_x_ener_lv + npeuloxedges)
244 
245  edge%tEdge = inrt_edge_ener
246  edge%iNode(1) = input%indIntl
247  edge%iNode(2) = input%indPlagVapor
248 
249  edge => inrt%edges(inrt_burning_x_mass_g + npeuloxedges)
250 
251  edge%tEdge = inrt_edge_mass
252  edge%iNode(1) = input%indIntl
253  edge%iNode(2) = input%indMixt
254 
255  edge => inrt%edges(inrt_burning_x_mass_l + npeuloxedges)
256 
257  edge%tEdge = inrt_edge_mass
258  edge%iNode(1) = input%indIntl
259  edge%iNode(2) = input%indPlag0 + iplagout
260 
261  DO ipeuloutedge = 1,npeuloutedges
262 
263  edge => inrt%edges(inrt_burning_x_mass_s0 + npeuloxedges + ipeuloutedge)
264 
265  edge%tEdge = inrt_edge_mass
266  edge%iNode(1) = input%indIntl
267  edge%iNode(2) = input%indPeul0 + ipeularr(ipeuloutedge)
268 
269  END DO ! iPeulOutEdge
270 
271 ! finalize --------------------------------------------------------------------
272 
273  CALL deregisterfunction( global )
274 
275 END SUBROUTINE inrt_defineburning
276 
277 !******************************************************************************
278 !
279 ! RCS Revision history:
280 !
281 ! $Log: INRT_DefineBurning.F90,v $
282 ! Revision 1.5 2008/12/06 08:44:31 mtcampbe
283 ! Updated license.
284 !
285 ! Revision 1.4 2008/11/19 22:17:44 mtcampbe
286 ! Added Illinois Open Source License/Copyright
287 !
288 ! Revision 1.3 2006/02/15 20:40:00 wasistho
289 ! put plag within ifdef
290 !
291 ! Revision 1.2 2006/02/15 20:17:42 wasistho
292 ! put peul within ifdef
293 !
294 ! Revision 1.1 2004/12/01 21:56:21 fnajjar
295 ! Initial revision after changing case
296 !
297 ! Revision 1.9 2004/07/23 22:43:16 jferry
298 ! Integrated rocspecies into rocinteract
299 !
300 ! Revision 1.8 2004/03/08 21:57:36 jferry
301 ! better error checking for burning without smoke case
302 !
303 ! Revision 1.7 2004/03/02 21:47:29 jferry
304 ! Added After Update interactions
305 !
306 ! Revision 1.6 2003/09/25 15:47:58 jferry
307 ! minor change: error message parameter altered
308 !
309 ! Revision 1.5 2003/09/19 20:35:26 jferry
310 ! Implemented oxidizer species for burning interaction
311 !
312 ! Revision 1.4 2003/04/02 22:32:03 jferry
313 ! codified Activeness and Permission structures for rocinteract
314 !
315 ! Revision 1.3 2003/03/24 23:30:52 jferry
316 ! overhauled rocinteract to allow interaction design to use user input
317 !
318 ! Revision 1.2 2003/03/11 16:09:39 jferry
319 ! Added comments
320 !
321 ! Revision 1.1 2003/03/04 22:12:35 jferry
322 ! Initial import of Rocinteract
323 !
324 !******************************************************************************
325 
326 
327 
328 
329 
330 
331 
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
IndexType nedges() const
Definition: Mesh.H:564
subroutine inrt_allocateauxillary(global, inrt, nEdges, nSwitches, nData)
subroutine input(X, NNODE, NDC, NCELL, NFCE, NBPTS, NBFACE, ITYP, NPROP, XBNDY, XFAR, YFAR, ZFAR)
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
subroutine deregisterfunction(global)
Definition: ModError.F90:469
subroutine inrt_defineburning(region, matIndIn, matIndOut, matIndOx, oxUsed, plagOutExists)