Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
INRT_ReadBurning.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: Reads in information related to the interaction Burning
26 !
27 ! Description: none.
28 !
29 ! Input: regions = data of all regions
30 !
31 ! Output: fills user data into region%inrtInput%inrts
32 !
33 ! Notes: none.
34 !
35 !******************************************************************************
36 !
37 ! $Id: INRT_ReadBurning.F90,v 1.3 2008/12/06 08:44:31 mtcampbe Exp $
38 !
39 ! Copyright: (c) 2003 by the University of Illinois
40 !
41 !******************************************************************************
42 
43 SUBROUTINE inrt_readburning( regions )
44 
45  USE moddatatypes
46  USE moddatastruct, ONLY : t_region
47  USE modglobal, ONLY : t_global
48  USE modmaterials, ONLY : t_material
50  USE moderror
51  USE modparameters
53 
54 #ifdef RFLO
56 #endif
57 #ifdef RFLU
58  USE modinterfaces, ONLY : readbothsection
59 #endif
61 
65  IMPLICIT NONE
66 
67 ! ... parameters
68  TYPE(t_region), POINTER :: regions(:)
69 
70 ! ... loop variables
71  INTEGER :: ireg,iplag,ipeul,ipeuloutedge
72 
73 ! ... local variables
74  INTEGER, PARAMETER :: nstrkeys_max = 5
75  INTEGER, PARAMETER :: nkeys_max = 50
76  INTEGER, PARAMETER :: npeul_max = 10
77 
78  CHARACTER(CHRLEN) :: rcsidentstring
79  CHARACTER(CHRLEN) :: strkeys(nstrkeys_max),keys(nkeys_max)
80  CHARACTER(CHRLEN) :: strvals(nstrkeys_max)
81 
82  INTEGER :: brbeg,brend
83  INTEGER :: nplag,npeul
84  INTEGER :: iedge,nedges,npeuloutedges,npeuloxedges
85  INTEGER :: nstrkeys,nfixedimplkeys,nfixednodekeys,nkeys
86  INTEGER :: ind,indmixt,indplag0,indpeul0,indintl
87  INTEGER :: istrkeymaterialin,istrkeymaterialout,istrkeymaterialox
88  INTEGER :: ikey,ikeyused,ikeymodel,ikeyoxused,ikeyheatcoef
89  INTEGER :: ikeyvapormeth,ikeyvaportemp
90  INTEGER :: ikeymfrcplag,ikeymfrcpeul0
91  INTEGER :: ikeynode0,ikeymixtactv,ikeymixtperm,ikeyplagactv,ikeyplagperm
92  INTEGER :: ikeypeulactv0,ikeypeulperm0,ikeyactv,ikeyperm
93 
94  LOGICAL :: plagoutexists,oxused
95  LOGICAL :: defined(nkeys_max),strdefined(nstrkeys_max)
96 
97  REAL(RFREAL) :: coef
98  REAL(RFREAL) :: vals(nkeys_max)
99 
100  TYPE(t_material), POINTER :: matin,matout,matox
101  TYPE(t_inrt_input), POINTER :: input
102  TYPE(t_inrt_interact), POINTER :: inrt
103  TYPE(t_global), POINTER :: global
104 
105 !******************************************************************************
106 
107  rcsidentstring = '$RCSfile: INRT_ReadBurning.F90,v $ $Revision: 1.3 $'
108 
109  global => regions(1)%global
110 
111  CALL registerfunction( global,'INRT_ReadBurning',&
112  'INRT_ReadBurning.F90' )
113 
114 ! begin -----------------------------------------------------------------------
115 
116 ! define string keys
117 
118  istrkeymaterialin = 1
119  istrkeymaterialout = 2
120  istrkeymaterialox = 3
121  nstrkeys = 3
122 
123  strkeys(istrkeymaterialin) = 'MATERIAL_IN'
124  strkeys(istrkeymaterialout) = 'MATERIAL_OUT'
125  strkeys(istrkeymaterialox) = 'MATERIAL_OX'
126 
127  IF (nstrkeys > nstrkeys_max) &
128  CALL errorstop( global,err_exceeds_decl_mem,__line__ )
129 
130 ! define implementation-dependent keys
131 
132  ikeyused = 1
133  ikeymodel = 2
134  ikeyoxused = 3
135  ikeyvapormeth = 4
136  ikeyvaportemp = 5
137  ikeyheatcoef = 6
138  ikeymfrcplag = 7
139  nfixedimplkeys = 8
140 
141  keys(ikeyused) = 'USED'
142  keys(ikeymodel) = 'MODEL'
143  keys(ikeyoxused) = 'OX_USED'
144  keys(ikeyvapormeth) = 'VAPOR_METH'
145  keys(ikeyvaportemp) = 'VAPOR_TEMP'
146  keys(ikeyheatcoef) = 'HEAT_COEF'
147  keys(ikeymfrcplag) = 'MFRC_PLAG'
148 
149  ikeymfrcpeul0 = nfixedimplkeys
150 
151 #ifdef RFLO
152  CALL makenumberedkeys(keys,ikeymfrcpeul0+1,'MFRC_PEUL',1,npeul_max,1)
153 #endif
154 #ifdef RFLU
155  CALL makenumberedkeys(keys,ikeymfrcpeul0+1,'MFRC_SPEC',1,npeul_max,1)
156 #endif
157 
158 ! define Node keys
159 
160  ikeynode0 = ikeymfrcpeul0 + npeul_max
161  ikeymixtactv = ikeynode0 + 1
162  ikeymixtperm = ikeynode0 + 2
163  ikeyplagactv = ikeynode0 + 3
164  ikeyplagperm = ikeynode0 + 4
165  nfixednodekeys = 4
166 
167  keys(ikeymixtactv) = 'MIXT_ACTV'
168  keys(ikeymixtperm) = 'MIXT_PERM'
169  keys(ikeyplagactv) = 'PLAG_ACTV'
170  keys(ikeyplagperm) = 'PLAG_PERM'
171 
172  ikeypeulactv0 = ikeynode0 + nfixednodekeys
173  ikeypeulperm0 = ikeypeulactv0 + npeul_max
174 
175 #ifdef RFLO
176  CALL makenumberedkeys(keys,ikeypeulactv0+1,'PEUL',1,npeul_max,1)
177  CALL makenumberedkeys(keys,ikeypeulperm0+1,'PEUL',1,npeul_max,1)
178 #endif
179 #ifdef RFLU
180  CALL makenumberedkeys(keys,ikeypeulactv0+1,'SPEC',1,npeul_max,1)
181  CALL makenumberedkeys(keys,ikeypeulperm0+1,'SPEC',1,npeul_max,1)
182 #endif
183 
184  DO ipeul=1,npeul_max
185  keys(ikeypeulactv0+ipeul) = trim(keys(ikeypeulactv0+ipeul))//'_ACTV'
186  keys(ikeypeulperm0+ipeul) = trim(keys(ikeypeulperm0+ipeul))//'_PERM'
187  END DO ! iPeul
188 
189  nkeys = ikeypeulperm0 + npeul_max
190 
191  IF (nkeys > nkeys_max) CALL errorstop( global,err_exceeds_decl_mem,__line__ )
192 
193 ! Read interaction section from input file
194 
195 #ifdef RFLO
196  CALL readbothregionsection( global,if_input,nkeys,nstrkeys,keys,strkeys, &
197  vals,strvals,brbeg,brend,defined,strdefined )
198 #endif
199 #ifdef RFLU
200  CALL readbothsection( global,if_input,nkeys,nstrkeys,keys,strkeys, &
201  vals,strvals,defined,strdefined )
202  brbeg = lbound(regions,1)
203  brend = ubound(regions,1)
204 #endif
205 
206  DO ireg=brbeg,brend
207 
208  input => regions(ireg)%inrtInput
209  inrt => input%inrts(inrt_type_burning)
210 
211 ! - Check that INRT_DEFAULT section has been read, and that interaction has not
212 
213  IF (.NOT. input%defaultRead) &
214  CALL errorstop( global,err_inrt_defunread,__line__ )
215 
216  IF (inrt%used) CALL errorstop( global,err_inrt_read,__line__ )
217 
218 ! - Use local variables for some useful quantities
219 
220  nplag = input%nPlag
221  npeul = input%nPeul
222 
223  IF (npeul > npeul_max) &
224  CALL errorstop( global,err_exceeds_decl_mem,__line__ )
225 
226  indmixt = input%indMixt
227  indplag0 = input%indPlag0
228  indpeul0 = input%indPeul0
229  indintl = input%indIntl
230 
231 ! - Check if interaction is used
232 
233  inrt%used = .true. ! used by default when its section appears
234 
235  IF (defined(ikeyused)) THEN
236  IF (nint(vals(ikeyused)) == 0) inrt%used = .false.
237  END IF ! defined(iKeyUsed)
238 
239  IF (nplag < 1) inrt%used = .false. ! cannot occur without particles
240 
241  IF (.NOT. inrt%used) cycle ! do not bother with unused interactions
242 
243 ! - Check if oxidizer is used
244 
245  oxused = .false.
246 
247  IF (defined(ikeyoxused) .AND. npeul > 0) THEN
248 
249  SELECT CASE (nint(vals(ikeyoxused)))
250 
251  CASE (0)
252  oxused = .false.
253 
254  CASE (1)
255  oxused = .true.
256 
257  CASE default
258  CALL errorstop( global,err_inrt_badswitch,__line__ )
259 
260  END SELECT ! vals(iKeyOxUsed)
261 
262  END IF ! defined(iKeyOxUsed)
263 
264 ! - Set pointers to in, out, and ox materials
265 
266  IF (strdefined(istrkeymaterialin)) THEN
267  CALL inrt_setmaterial(global,matin,strvals(istrkeymaterialin))
268  ELSE
269  CALL errorstop( global,err_inrt_missingmat,__line__ )
270  END IF ! strDefined(iStrKeyMaterialIn)
271 
272  IF (strdefined(istrkeymaterialout)) THEN
273  CALL inrt_setmaterial(global,matout,strvals(istrkeymaterialout))
274  ELSE
275  CALL errorstop( global,err_inrt_missingmat,__line__ )
276  END IF ! strDefined(iStrKeyMaterialOut)
277 
278  IF (strdefined(istrkeymaterialox)) THEN
279  CALL inrt_setmaterial(global,matox,strvals(istrkeymaterialox))
280  ELSE
281 ! --- Give missing material error if oxidizer used but material undefined
282  IF (oxused) CALL errorstop( global,err_inrt_missingmat,__line__ )
283 ! --- set matOx to point to something even if it is not defined
284  CALL inrt_setmaterial(global,matox,strvals(istrkeymaterialin))
285  END IF ! strDefined(iStrKeyMaterialOx)
286 
287 ! - Define interaction (using any relevant information from input deck)
288 
289  CALL inrt_defineburning(regions(ireg),matin%index,matout%index, &
290  matox%index,oxused,plagoutexists)
291 
292 ! - Check for switches
293 
294 ! - Which burning model is used
295 
296  inrt%switches(inrt_swi_burning_model) = inrt_burning_model_default
297 
298  IF (defined(ikeymodel)) THEN
299 
300  SELECT CASE (nint(vals(ikeymodel)))
301 
302  CASE (1)
303  inrt%switches(inrt_swi_burning_model) = inrt_burning_model_beckstead
304 
305  CASE default
306  CALL errorstop( global,err_inrt_badswitch,__line__ )
307 
308  END SELECT ! vals(iKeyModel)
309 
310  END IF ! defined(iKeyModel)
311 
312 ! - Whether oxidizer is used
313 
314  IF (oxused) THEN
315  inrt%switches(inrt_swi_burning_oxused) = 1
316  npeuloxedges = 1
317  ELSE
318  inrt%switches(inrt_swi_burning_oxused) = 0
319  npeuloxedges = 0
320  END IF ! oxUsed
321 
322 ! - Which Vapor Energy method is used
323 
324  inrt%switches(inrt_swi_burning_vapor_meth) = inrt_burning_vapor_meth_used
325 
326  IF (defined(ikeyvapormeth)) THEN
327 
328  SELECT CASE (nint(vals(ikeyvapormeth)))
329 
330  CASE (0)
331  inrt%switches(inrt_swi_burning_vapor_meth) = &
332  inrt_burning_vapor_meth_none
333 
334  CASE (1)
335  inrt%switches(inrt_swi_burning_vapor_meth) = &
336  inrt_burning_vapor_meth_used
337 
338  CASE default
339  CALL errorstop( global,err_inrt_badswitch,__line__ )
340 
341  END SELECT ! vals(iKeyVaporMeth)
342 
343  END IF ! defined(iKeyVaporMeth)
344 
345 ! - Check for data
346 
347 ! - temperature above which to shunt burning energy to vapor
348 
349  coef = matout%Tboil
350 
351  IF (defined(ikeyvaportemp)) coef = vals(ikeyvaportemp)
352 
353  IF (coef < 0._rfreal) CALL errorstop( global,err_inrt_badval,__line__ )
354 
355  inrt%data(inrt_dat_burning_vapor_temp) = coef
356 
357 ! - fraction of heat actually released
358 
359  coef = 1._rfreal ! default heat release coefficient
360 
361  IF (defined(ikeyheatcoef)) coef = vals(ikeyheatcoef)
362 
363  IF (coef < 0._rfreal) CALL errorstop( global,err_inrt_badval,__line__ )
364 
365  inrt%data(inrt_dat_burning_heat_coef) = coef
366 
367 ! - fraction of substance produced that goes immediately back to the particle
368 
369  coef = 0._rfreal ! default mass fraction that goes back to particle
370 
371  IF (defined(ikeymfrcplag)) coef = vals(ikeymfrcplag)
372 
373  IF (.NOT. plagoutexists) coef = 0._rfreal ! no transfer to non-existent Node
374 
375  IF (coef < 0._rfreal) CALL errorstop( global,err_inrt_badval,__line__ )
376 
377  inrt%data(inrt_dat_burning_mfrc_plag) = coef
378 
379 ! - fraction of substance going to smoke that goes to each smoke type
380 
381  npeuloutedges = inrt%nEdges - npeuloxedges - inrt_burning_nedges0
382 
383  DO ipeuloutedge = 1,npeuloutedges ! loop over edges that output smoke
384 
385  iedge = inrt_burning_x_mass_s0 + npeuloxedges + ipeuloutedge
386 
387  ipeul = inrt%edges(iedge)%iNode(2) - indpeul0
388 
389  IF (ipeul < 1 .OR. ipeul > npeul) &
390  CALL errorstop( global,err_inrt_indexrange,__line__ )
391 
392  ikey = ikeymfrcpeul0 + ipeul
393  ind = inrt_dat_burning_mfrc_peul0 + ipeuloutedge
394 
395  coef = 0._rfreal ! default mass fraction that goes to a smoke type
396 
397  IF (defined(ikey)) coef = vals(ikey)
398 
399  IF (coef < 0._rfreal) CALL errorstop( global,err_inrt_badval,__line__ )
400 
401  inrt%data(ind) = coef
402 
403  END DO ! iPeulOutEdge
404 
405 ! - Check for Mixture controls
406 
407  IF (defined(ikeymixtactv)) &
408  CALL inrt_setactiveness(global,vals(ikeymixtactv), &
409  inrt%activeness(indmixt))
410 
411  IF (defined(ikeymixtperm)) &
412  CALL inrt_setpermission(global,vals(ikeymixtperm), &
413  inrt%permission(indmixt))
414 
415 ! - Check for Lagrangian particle controls
416 
417  DO iplag=1,nplag+1
418 
419  ind = indplag0 + iplag
420 
421  IF (defined(ikeyplagactv)) &
422  CALL inrt_setactiveness(global,vals(ikeyplagactv), &
423  inrt%activeness(ind))
424 
425  IF (defined(ikeyplagperm)) &
426  CALL inrt_setpermission(global,vals(ikeyplagperm), &
427  inrt%permission(ind))
428 
429  END DO ! iPlag
430 
431 ! - Check for Smoke controls
432 
433  DO ipeul = 1,npeul
434 
435  ikeyactv = ikeypeulactv0 + ipeul
436  ikeyperm = ikeypeulperm0 + ipeul
437  ind = indpeul0 + ipeul
438 
439  IF (defined(ikeyactv)) &
440  CALL inrt_setactiveness(global,vals(ikeyactv), &
441  inrt%activeness(ind))
442 
443  IF (defined(ikeyperm)) &
444  CALL inrt_setpermission(global,vals(ikeyperm), &
445  inrt%permission(ind))
446 
447  END DO ! iPeul
448 
449 ! - Define Activeness of Internal Node
450 
451 ! - For the Burning interaction, this is defined as the minimum of the
452 ! - Activeness of the Gas and the Lagrangian particles
453 
454  inrt%activeness(indintl) = min(inrt%activeness(indmixt), &
455  inrt%activeness(indplag0+1))
456 
457 ! - Determine permission Tokens
458 
459  CALL inrt_determinetokens(regions(ireg),inrt)
460 
461  END DO ! iReg
462 
463 ! finalize --------------------------------------------------------------------
464 
465  CALL deregisterfunction( global )
466 
467 END SUBROUTINE inrt_readburning
468 
469 !******************************************************************************
470 !
471 ! RCS Revision history:
472 !
473 ! $Log: INRT_ReadBurning.F90,v $
474 ! Revision 1.3 2008/12/06 08:44:31 mtcampbe
475 ! Updated license.
476 !
477 ! Revision 1.2 2008/11/19 22:17:44 mtcampbe
478 ! Added Illinois Open Source License/Copyright
479 !
480 ! Revision 1.1 2004/12/01 21:56:33 fnajjar
481 ! Initial revision after changing case
482 !
483 ! Revision 1.11 2004/07/23 22:43:16 jferry
484 ! Integrated rocspecies into rocinteract
485 !
486 ! Revision 1.10 2004/03/08 21:57:36 jferry
487 ! better error checking for burning without smoke case
488 !
489 ! Revision 1.9 2004/03/05 22:09:03 jferry
490 ! created global variables for peul, plag, and inrt use
491 !
492 ! Revision 1.8 2004/03/02 21:47:29 jferry
493 ! Added After Update interactions
494 !
495 ! Revision 1.7 2003/09/26 21:46:54 fnajjar
496 ! Modified ModInterfaces call to ModInterfacesInteract
497 !
498 ! Revision 1.6 2003/09/25 15:46:31 jferry
499 ! removed temporary comments
500 !
501 ! Revision 1.5 2003/09/19 20:35:26 jferry
502 ! Implemented oxidizer species for burning interaction
503 !
504 ! Revision 1.4 2003/04/02 22:32:04 jferry
505 ! codified Activeness and Permission structures for rocinteract
506 !
507 ! Revision 1.3 2003/03/24 23:30:52 jferry
508 ! overhauled rocinteract to allow interaction design to use user input
509 !
510 ! Revision 1.2 2003/03/11 16:09:39 jferry
511 ! Added comments
512 !
513 ! Revision 1.1 2003/03/04 22:12:35 jferry
514 ! Initial import of Rocinteract
515 !
516 !******************************************************************************
517 
518 
519 
520 
521 
522 
523 
subroutine makenumberedkeys(keys, indBegin, string, numBegin, numEnd, numSkip)
subroutine readbothsection(global, fileID, nvals, nStrVals, keys, strKeys, vals, strVals, defined, strDefined)
subroutine readbothregionsection(global, fileID, nvals, nStrVals, keys, strKeys, vals, strVals, brbeg, brend, defined, strDefined)
subroutine inrt_setmaterial(global, material, name)
subroutine inrt_readburning(regions)
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
subroutine inrt_determinetokens(region, inrt)
IndexType nedges() const
Definition: Mesh.H:564
**********************************************************************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 input(X, NNODE, NDC, NCELL, NFCE, NBPTS, NBFACE, ITYP, NPROP, XBNDY, XFAR, YFAR, ZFAR)
subroutine inrt_setactiveness(global, val, actv)
Vector_n min(const Array_n_const &v1, const Array_n_const &v2)
Definition: Vector_n.h:346
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
subroutine deregisterfunction(global)
Definition: ModError.F90:469
subroutine inrt_setpermission(global, val, perm)
subroutine inrt_defineburning(region, matIndIn, matIndOut, matIndOx, oxUsed, plagOutExists)