61 TYPE(t_region
),
INTENT(INOUT),
TARGET :: region
64 INTEGER :: icont, ipcls, ipeuloutedge
67 CHARACTER(CHRLEN) :: rcsidentstring
69 INTEGER :: burnmodel, icontin, icontout, ncont,
nedges, &
70 npeuloutedges, npeuloxedges, ipeulox, npcls,
icell
74 INTEGER,
POINTER,
DIMENSION(:) :: pcvplagmass
75 INTEGER,
POINTER,
DIMENSION(:,:) :: paiv
77 LOGICAL :: oxused, sendtovapor
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, &
87 REAL(RFREAL),
POINTER,
DIMENSION(:) :: pdens, pmolw
88 REAL(RFREAL),
POINTER,
DIMENSION(:,:) :: pcv, pdv, pcvmixt, pcvpeul
92 TYPE(t_plag),
POINTER :: pplag
97 rcsidentstring =
'$RCSfile: INRT_CalcBurning.F90,v $ $Revision: 1.4 $'
99 global => region%global
102 'INRT_CalcBurning.F90' )
110 ilev = region%currLevel
111 pcvmixt => region%levels(ilev)%mixt%cv
113 pcvpeul => region%levels(ilev)%peul%cv
115 pplag => region%levels(ilev)%plag
119 pcvmixt => region%mixt%cv
120 pcvpeul => region%spec%cv
127 IF (global%plagUsed) npcls = pplag%nPcls
129 IF (npcls < 1) go to 999
137 pcvplagmass => pplag%cvPlagMass
139 pdens => region%plagInput%dens
140 pmolw => region%plagInput%molw
142 pinputinrt => region%inrtInput
143 pinrtburn => pinputinrt%inrts(inrt_type_burning)
150 oxused = (pinrtburn%switches(inrt_swi_burning_oxused) /= 0)
156 ipeulox = pinrtburn%edges(inrt_burning_s_mass_x0 + &
157 npeuloxedges)%iNode(1) - pinputinrt%indPeul0
163 ncont = region%plagInput%nCont
166 npeuloutedges =
nedges - npeuloxedges - inrt_burning_nedges0
168 burnmodel = pinrtburn%switches(inrt_swi_burning_model)
169 coefflatentheat = pinrtburn%data(inrt_dat_burning_heat_coef)
171 mfracl = pinrtburn%data(inrt_dat_burning_mfrc_plag)
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
181 densal = pdens(icontin)
182 densal2o3 = pdens(icontout)
183 densratio = densal/densal2o3
185 molwal = pmolw(icontin)
186 molwal2o3 = pmolw(icontout)
187 molwratio = molwal2o3/(2.0_rfreal*molwal)
191 SELECT CASE (burnmodel)
193 CASE (inrt_burning_model_beckstead)
197 exphermsen = 1.9_rfreal
198 expdiaml = 3.0_rfreal-exphermsen
202 exptempg = 1.57_rfreal
203 exppresg = 0.20_rfreal
204 expxieffg = 0.39_rfreal
215 xieffg = ( xio2 + 0.58_rfreal * xih2o + 0.22_rfreal * xico2 )
221 doxh2rdoxnoh2 = 3.7_rfreal
223 diffrel = 1.0_rfreal + xih2 * ( doxh2rdoxnoh2 - 1.0_rfreal )
227 hevap = 10896.0_rfreal *1000.0_rfreal
228 hreac = 9543.0_rfreal *1000.0_rfreal
229 hcond = 29767.0_rfreal *1000.0_rfreal
232 heatlatent = -hevap + hreac + hcond + hsolid
236 heatlatent = heatlatent*coefflatentheat
239 CALL
errorstop( global,err_reached_default,__line__ )
243 sendtovapor = (pinrtburn%switches(inrt_swi_burning_vapor_meth) /= &
244 inrt_burning_vapor_meth_none)
246 sendtemp = pinrtburn%data(inrt_dat_burning_vapor_temp)
248 IF (sendtemp < 500._rfreal .OR. sendtemp > 10000._rfreal)
THEN
249 CALL
errorstop( global,err_inrt_badval,__line__ )
256 diaml = pdv(dv_plag_diam,ipcls)
257 tempg = pdv(dv_plag_tempmixt,ipcls)
258 presg = pdv(dv_plag_presmixt,ipcls)
260 SELECT CASE (burnmodel)
262 CASE (inrt_burning_model_beckstead)
266 volfracl = pcv(pcvplagmass(icontin),ipcls)/ &
267 ( pcv(pcvplagmass(icontin),ipcls) &
268 + pcv(pcvplagmass(icontout),ipcls) * densratio )
276 icell = paiv(aiv_plag_icells,ipcls)
278 massmixt = pcvmixt(cv_mixt_dens,
icell)
281 massox = pcvpeul(ipeulox,
icell)
285 massox = pcvpeul(ipeulox,
icell)
288 IF (massox <= 0._rfreal)
THEN
298 xieffg = massox / (massmixt + massox)
306 mdotburn = 2.885e-13_rfreal * densal * ( tempg**exptempg ) &
307 * ( xieffg**expxieffg ) * ( presg**exppresg ) &
308 * ( diaml**expdiaml ) * diffrel * volfracl
311 CALL
errorstop( global,err_reached_default,__line__ )
317 pplag%inrtSources(inrt_burning_g_mass_x,ipcls) = (molwratio - 1.0_rfreal) &
320 pplag%inrtSources(inrt_burning_l_mass_x,ipcls) = mdotburn
323 pplag%inrtSources(inrt_burning_s_mass_x0 + npeuloxedges,ipcls) = &
324 (molwratio - 1.0_rfreal) * mdotburn
327 IF (sendtovapor .AND. tempg > sendtemp)
THEN
328 pplag%inrtSources(inrt_burning_x_ener_g + npeuloxedges,ipcls) = &
330 pplag%inrtSources(inrt_burning_x_ener_lv + npeuloxedges,ipcls) = &
333 pplag%inrtSources(inrt_burning_x_ener_g + npeuloxedges,ipcls) = &
335 pplag%inrtSources(inrt_burning_x_ener_lv + npeuloxedges,ipcls) = &
339 pplag%inrtSources(inrt_burning_x_mass_g + npeuloxedges,ipcls) = 0.0_rfreal
341 pplag%inrtSources(inrt_burning_x_mass_l + npeuloxedges,ipcls) = &
342 mfracl*molwratio*mdotburn
344 DO ipeuloutedge = 1,npeuloutedges
345 coeffpeul = (1.0_rfreal-mfracl)*molwratio * &
346 pinrtburn%data(inrt_dat_burning_mfrc_peul0 + ipeuloutedge)
348 pplag%inrtSources(inrt_burning_x_mass_s0 + npeuloxedges + ipeuloutedge, &
349 ipcls) = coeffpeul*mdotburn
subroutine registerfunction(global, funName, fileName)
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)
subroutine deregisterfunction(global)