Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
INRT_CalcBurning.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 interaction sources on Lagrangian particles
26 ! for the burning case.
27 !
28 ! Description: none.
29 !
30 ! Input: region = current region.
31 !
32 ! Output: region%levels(iLev)%plag%inrtSources
33 !
34 ! Notes: none.
35 !
36 !******************************************************************************
37 !
38 ! $Id: INRT_CalcBurning.F90,v 1.4 2008/12/06 08:44:31 mtcampbe Exp $
39 !
40 ! Copyright: (c) 2003 by the University of Illinois
41 !
42 !******************************************************************************
43 
44 SUBROUTINE inrt_calcburning( region )
45 
46  USE moddatatypes
47  USE moddatastruct, ONLY : t_region
48  USE modglobal, ONLY : t_global
49  USE modpartlag, ONLY : t_plag
50  USE modinteract
51  USE moderror
52  USE modparameters
54 
55 #ifdef PLAG
57 #endif
58  IMPLICIT NONE
59 
60 ! ... parameters
61  TYPE(t_region), INTENT(INOUT), TARGET :: region
62 
63 ! ... loop variables
64  INTEGER :: icont, ipcls, ipeuloutedge
65 
66 ! ... local variables
67  CHARACTER(CHRLEN) :: rcsidentstring
68 
69  INTEGER :: burnmodel, icontin, icontout, ncont, nedges, &
70  npeuloutedges, npeuloxedges, ipeulox, npcls, icell
71 #ifdef RFLO
72  INTEGER :: ilev
73 #endif
74  INTEGER, POINTER, DIMENSION(:) :: pcvplagmass
75  INTEGER, POINTER, DIMENSION(:,:) :: paiv
76 
77  LOGICAL :: oxused, sendtovapor
78 
79  REAL(RFREAL) :: coeffheatlatent, coefflatentheat, coeffpeul, densal, &
80  densal2o3, densratio, diaml, diffrel, doxh2rdoxnoh2, &
81  expdiaml, exphermsen, exppresg, exptempg, expxieffg, &
82  hcond, hevap, hreac, hsolid, heatlatent, mdotburn, &
83  mfracl, molwal, molwal2o3, molwratio, presg, tempg, &
84  volfracl, xico2, xieffg, xio2, xih2, xih2o, massmixt, &
85  massox, sendtemp
86 
87  REAL(RFREAL), POINTER, DIMENSION(:) :: pdens, pmolw
88  REAL(RFREAL), POINTER, DIMENSION(:,:) :: pcv, pdv, pcvmixt, pcvpeul
89 
90  TYPE(t_inrt_input), POINTER :: pinputinrt
91  TYPE(t_inrt_interact), POINTER :: pinrtburn
92  TYPE(t_plag), POINTER :: pplag
93  TYPE(t_global), POINTER :: global
94 
95 !******************************************************************************
96 
97  rcsidentstring = '$RCSfile: INRT_CalcBurning.F90,v $ $Revision: 1.4 $'
98 
99  global => region%global
100 
101  CALL registerfunction( global,'INRT_CalcBurning',&
102  'INRT_CalcBurning.F90' )
103 
104 #ifdef PLAG
105 ! begin =======================================================================
106 
107 ! Set grid-dependent pointers -------------------------------------------------
108 
109 #ifdef RFLO
110  ilev = region%currLevel
111  pcvmixt => region%levels(ilev)%mixt%cv
112 #ifdef PEUL
113  pcvpeul => region%levels(ilev)%peul%cv
114 #endif
115  pplag => region%levels(ilev)%plag
116 #endif
117 
118 #ifdef RFLU
119  pcvmixt => region%mixt%cv
120  pcvpeul => region%spec%cv
121  pplag => region%plag
122 #endif
123 
124 ! Check if there are any particles
125 
126  npcls = 0
127  IF (global%plagUsed) npcls = pplag%nPcls
128 
129  IF (npcls < 1) go to 999
130 
131 ! Set pointers ----------------------------------------------------------------
132 
133  paiv => pplag%aiv
134  pcv => pplag%cv
135  pdv => pplag%dv
136 
137  pcvplagmass => pplag%cvPlagMass
138 
139  pdens => region%plagInput%dens
140  pmolw => region%plagInput%molw
141 
142  pinputinrt => region%inrtInput
143  pinrtburn => pinputinrt%inrts(inrt_type_burning)
144 
145 ! Get dimensions --------------------------------------------------------------
146 
147 ! Set parameters for oxidizer use
148 
149  npeuloxedges = 0
150  oxused = (pinrtburn%switches(inrt_swi_burning_oxused) /= 0)
151 
152  IF (oxused) THEN
153 
154  npeuloxedges = 1
155 ! - Extract index of oxidizer smoke type
156  ipeulox = pinrtburn%edges(inrt_burning_s_mass_x0 + &
157  npeuloxedges)%iNode(1) - pinputinrt%indPeul0
158 
159  END IF ! oxUsed
160 
161 ! Set other parameters
162 
163  ncont = region%plagInput%nCont
164 
165  nedges = pinrtburn%nEdges
166  npeuloutedges = nedges - npeuloxedges - inrt_burning_nedges0
167 
168  burnmodel = pinrtburn%switches(inrt_swi_burning_model)
169  coefflatentheat = pinrtburn%data(inrt_dat_burning_heat_coef)
170 
171  mfracl = pinrtburn%data(inrt_dat_burning_mfrc_plag)
172 
173 ! Extract index of AL (In) and AL2O3 (Out). "In" material represents ----------
174 ! the material that will burn and "out" is the burning product
175 
176  icontin = pinrtburn%edges(inrt_burning_l_mass_x)%iNode(1) &
177  - pinputinrt%indPlag0
178  icontout = pinrtburn%edges(inrt_burning_x_mass_l + npeuloxedges)%iNode(2) &
179  - pinputinrt%indPlag0
180 
181  densal = pdens(icontin)
182  densal2o3 = pdens(icontout)
183  densratio = densal/densal2o3
184 
185  molwal = pmolw(icontin)
186  molwal2o3 = pmolw(icontout)
187  molwratio = molwal2o3/(2.0_rfreal*molwal)
188 
189 ! Set appropriate coefficients pertinent to burn Model ------------------------
190 
191  SELECT CASE (burnmodel)
192 
193  CASE (inrt_burning_model_beckstead)
194 
195 ! --- Exponents from Hermsens Model -------------------------------------------
196 
197  exphermsen = 1.9_rfreal
198  expdiaml = 3.0_rfreal-exphermsen
199 
200 ! --- Exponents for Burning Rate Variables ------------------------------------
201 
202  exptempg = 1.57_rfreal
203  exppresg = 0.20_rfreal
204  expxieffg = 0.39_rfreal
205 
206 ! --- Compute Measure of Availability of Oxidizing Species --------------------
207 
208  xico2 = 0.20_rfreal
209  xio2 = 0.02_rfreal
210  xih2o = 0.20_rfreal
211  xih2 = 0.20_rfreal
212 
213 ! --- Will override this value of xiEffG if an oxidizer species is used
214 
215  xieffg = ( xio2 + 0.58_rfreal * xih2o + 0.22_rfreal * xico2 )
216 
217 ! --- Compute Relative Diffusivity Coefficient, D_rel -------------------------
218 
219 ! --- Define Ratio of Diffusivity of Oxidants with and without H2 -------------
220 
221  doxh2rdoxnoh2 = 3.7_rfreal
222 
223  diffrel = 1.0_rfreal + xih2 * ( doxh2rdoxnoh2 - 1.0_rfreal )
224 
225 ! --- Latent Heat for Energy Source -------------------------------------------
226 
227  hevap = 10896.0_rfreal *1000.0_rfreal
228  hreac = 9543.0_rfreal *1000.0_rfreal
229  hcond = 29767.0_rfreal *1000.0_rfreal
230  hsolid = 0.0_rfreal
231 
232  heatlatent = -hevap + hreac + hcond + hsolid
233 
234 ! --- Scale Latent heat by appropriate coefficient ----------------------------
235 
236  heatlatent = heatlatent*coefflatentheat
237 
238  CASE default
239  CALL errorstop( global,err_reached_default,__line__ )
240 
241  END SELECT ! burnModel
242 
243  sendtovapor = (pinrtburn%switches(inrt_swi_burning_vapor_meth) /= &
244  inrt_burning_vapor_meth_none)
245 
246  sendtemp = pinrtburn%data(inrt_dat_burning_vapor_temp)
247 
248  IF (sendtemp < 500._rfreal .OR. sendtemp > 10000._rfreal) THEN
249  CALL errorstop( global,err_inrt_badval,__line__ )
250  END IF ! sendTemp
251 
252 ! Loop over all the particles -------------------------------------------------
253 
254  DO ipcls = 1,npcls
255 
256  diaml = pdv(dv_plag_diam,ipcls)
257  tempg = pdv(dv_plag_tempmixt,ipcls)
258  presg = pdv(dv_plag_presmixt,ipcls)
259 
260  SELECT CASE (burnmodel)
261 
262  CASE (inrt_burning_model_beckstead)
263 
264 ! ----- Compute Particle Volume Fraction --------------------------------------
265 
266  volfracl = pcv(pcvplagmass(icontin),ipcls)/ &
267  ( pcv(pcvplagmass(icontin),ipcls) &
268  + pcv(pcvplagmass(icontout),ipcls) * densratio )
269 
270 ! ----- If oxidizer is used, compute xiEffG -----------------------------------
271 
272  IF (oxused) THEN
273 
274 ! ------- Compute gas and oxidizer mass in this cell
275 
276  icell = paiv(aiv_plag_icells,ipcls)
277 
278  massmixt = pcvmixt(cv_mixt_dens,icell)
279 #ifdef RFLO
280 #ifdef PEUL
281  massox = pcvpeul(ipeulox,icell)
282 #endif
283 #endif
284 #ifdef RFLU
285  massox = pcvpeul(ipeulox,icell)
286 #endif
287 
288  IF (massox <= 0._rfreal) THEN
289 
290  xieffg = 0._rfreal
291 
292  ELSE
293 
294 ! --------- Notes: this assumes that the molecular weights of the gas
295 ! --------- and oxidizer are the same. Technically, xiEffG should be
296 ! --------- massOx / massMixt, but that would be too dangerous.
297 
298  xieffg = massox / (massmixt + massox)
299 
300  END IF ! massOx
301 
302  END IF ! oxUsed
303 
304 ! ----- Compute Mass Burning Rate of Al ---------------------------------------
305 
306  mdotburn = 2.885e-13_rfreal * densal * ( tempg**exptempg ) &
307  * ( xieffg**expxieffg ) * ( presg**exppresg ) &
308  * ( diaml**expdiaml ) * diffrel * volfracl
309 
310  CASE default
311  CALL errorstop( global,err_reached_default,__line__ )
312 
313  END SELECT ! burnModel
314 
315 ! - Fill the interaction source terms -----------------------------------------
316 
317  pplag%inrtSources(inrt_burning_g_mass_x,ipcls) = (molwratio - 1.0_rfreal) &
318  * mdotburn
319 
320  pplag%inrtSources(inrt_burning_l_mass_x,ipcls) = mdotburn
321 
322  IF (oxused) THEN
323  pplag%inrtSources(inrt_burning_s_mass_x0 + npeuloxedges,ipcls) = &
324  (molwratio - 1.0_rfreal) * mdotburn
325  END IF ! oxUsed
326 
327  IF (sendtovapor .AND. tempg > sendtemp) THEN
328  pplag%inrtSources(inrt_burning_x_ener_g + npeuloxedges,ipcls) = &
329  0.0_rfreal
330  pplag%inrtSources(inrt_burning_x_ener_lv + npeuloxedges,ipcls) = &
331  heatlatent*mdotburn
332  ELSE
333  pplag%inrtSources(inrt_burning_x_ener_g + npeuloxedges,ipcls) = &
334  heatlatent*mdotburn
335  pplag%inrtSources(inrt_burning_x_ener_lv + npeuloxedges,ipcls) = &
336  0.0_rfreal
337  END IF ! sendToVapor
338 
339  pplag%inrtSources(inrt_burning_x_mass_g + npeuloxedges,ipcls) = 0.0_rfreal
340 
341  pplag%inrtSources(inrt_burning_x_mass_l + npeuloxedges,ipcls) = &
342  mfracl*molwratio*mdotburn
343 
344  DO ipeuloutedge = 1,npeuloutedges
345  coeffpeul = (1.0_rfreal-mfracl)*molwratio * &
346  pinrtburn%data(inrt_dat_burning_mfrc_peul0 + ipeuloutedge)
347 
348  pplag%inrtSources(inrt_burning_x_mass_s0 + npeuloxedges + ipeuloutedge, &
349  ipcls) = coeffpeul*mdotburn
350  END DO ! iPeulOutEdge
351 
352  END DO ! iPcls
353 
354 ! finalize --------------------------------------------------------------------
355 
356 999 CONTINUE
357 #endif
358  CALL deregisterfunction( global )
359 
360 END SUBROUTINE inrt_calcburning
361 
362 !******************************************************************************
363 !
364 ! RCS Revision history:
365 !
366 ! $Log: INRT_CalcBurning.F90,v $
367 ! Revision 1.4 2008/12/06 08:44:31 mtcampbe
368 ! Updated license.
369 !
370 ! Revision 1.3 2008/11/19 22:17:44 mtcampbe
371 ! Added Illinois Open Source License/Copyright
372 !
373 ! Revision 1.2 2006/02/15 20:18:17 wasistho
374 ! put peul within ifdef
375 !
376 ! Revision 1.1 2004/12/01 21:56:13 fnajjar
377 ! Initial revision after changing case
378 !
379 ! Revision 1.9 2004/07/23 22:43:16 jferry
380 ! Integrated rocspecies into rocinteract
381 !
382 ! Revision 1.8 2004/03/05 22:09:03 jferry
383 ! created global variables for peul, plag, and inrt use
384 !
385 ! Revision 1.7 2004/03/02 21:47:29 jferry
386 ! Added After Update interactions
387 !
388 ! Revision 1.6 2004/01/31 03:59:22 haselbac
389 ! Initial integration for Rocflu and Rocpart
390 !
391 ! Revision 1.5 2003/09/19 20:35:26 jferry
392 ! Implemented oxidizer species for burning interaction
393 !
394 ! Revision 1.4 2003/04/04 16:27:39 jferry
395 ! fixed inconsistency in use of burn rate information
396 !
397 ! Revision 1.3 2003/04/03 22:52:04 fnajjar
398 ! Bug fix for INRT data
399 !
400 ! Revision 1.2 2003/04/03 21:10:17 jferry
401 ! implemented additional safety checks for rocinteract
402 !
403 ! Revision 1.1 2003/04/03 16:19:28 fnajjar
404 ! Initial Import of routines for burning and scouring
405 !
406 !******************************************************************************
407 
408 
409 
410 
411 
412 
413 
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
IndexType nedges() const
Definition: Mesh.H:564
subroutine inrt_calcburning(region)
**********************************************************************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 icell
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
subroutine deregisterfunction(global)
Definition: ModError.F90:469