Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
INRT_VaporEnergyConversion.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: convert vapor energy of particles to gas energy
26 !
27 ! Description: none.
28 !
29 ! Input: region = current region.
30 !
31 ! Output: region%levels(iLev)%plag%cv
32 ! region%levels(iLev)%mixt%cv
33 !
34 ! Notes:
35 !
36 ! Need to investigate release of energy into dummy cells
37 !
38 !******************************************************************************
39 !
40 ! $Id: INRT_VaporEnergyConversion.F90,v 1.4 2008/12/06 08:44:32 mtcampbe Exp $
41 !
42 ! Copyright: (c) 2004 by the University of Illinois
43 !
44 !******************************************************************************
45 
46 SUBROUTINE inrt_vaporenergyconversion( region )
47 
48  USE moddatatypes
49  USE moddatastruct, ONLY : t_region
50  USE modglobal, ONLY : t_global
51  USE modmixture, ONLY : t_mixt
52  USE modpartlag, ONLY : t_plag
53  USE modinteract, ONLY : t_inrt_interact
54  USE moderror
55  USE modparameters
57 
58 #ifdef PLAG
60 #endif
61 
62 #ifdef RFLO
64 
65 #include "Indexing.h"
66 #endif
67 
69  IMPLICIT NONE
70 
71 ! ... parameters
72  TYPE(t_region), INTENT(INOUT), TARGET :: region
73 
74 ! ... loop variables
75  INTEGER :: ipcls, ic
76 
77 ! ... local variables
78  CHARACTER(CHRLEN) :: rcsidentstring
79 
80 #ifdef RFLO
81  INTEGER :: idcbeg, idcend, jdcbeg, jdcend, kdcbeg, kdcend
82  INTEGER :: ilev, icoff, ijcoff
83 #endif
84  INTEGER :: indplagvapor, errorflag, ibc, iec, indcp, indmol, npcls, icell
85 
86  INTEGER, POINTER, DIMENSION(:,:) :: pplagaiv
87 
88  REAL(RFREAL) :: releasetemp, gastemp, keepfrac, rgas, gamma, hcap, deltaener
89 
90  REAL(RFREAL), POINTER, DIMENSION(:) :: vol
91  REAL(RFREAL), POINTER, DIMENSION(:,:) :: pmixtcv, pmixtdv, pmixtgv
92  REAL(RFREAL), POINTER, DIMENSION(:,:) :: pplagcv, pplagarv
93 
94  REAL(RFREAL), ALLOCATABLE :: vaportot(:)
95 
96  TYPE(t_inrt_interact), POINTER :: pinrtburn
97  TYPE(t_mixt), POINTER :: pmixt
98  TYPE(t_plag), POINTER :: pplag
99  TYPE(t_global), POINTER :: global
100 
101 !******************************************************************************
102 
103  rcsidentstring = &
104  '$RCSfile: INRT_VaporEnergyConversion.F90,v $ $Revision: 1.4 $'
105 
106  global => region%global
107 
108  CALL registerfunction( global,'INRT_VaporEnergyConversion',&
109  'INRT_VaporEnergyConversion.F90' )
110 
111 #ifdef PLAG
112 ! begin -----------------------------------------------------------------------
113 
114 #ifdef RFLO
115  ilev = region%currLevel
116  CALL rflo_getdimensdummy( region,ilev,idcbeg,idcend, &
117  jdcbeg,jdcend,kdcbeg,kdcend )
118  CALL rflo_getcelloffset( region,ilev,icoff,ijcoff )
119 
120  ibc = indijk(idcbeg,jdcbeg,kdcbeg,icoff,ijcoff)
121  iec = indijk(idcend,jdcend,kdcend,icoff,ijcoff)
122  pmixt => region%levels(ilev)%mixt
123  pplag => region%levels(ilev)%plag
124  vol => region%levels(ilev)%grid%vol
125  indcp = pmixt%indCp
126  indmol = pmixt%indMol
127 #endif
128 
129 #ifdef RFLU
130  ibc = 1
131  iec = region%grid%nCellsTot
132  pmixt => region%mixt
133  pplag => region%plag
134  vol => region%grid%vol
135  indcp = region%mixtInput%indCp
136  indmol = region%mixtInput%indMol
137 #endif
138 
139 ! Check if there are any particles --------------------------------------------
140 
141  npcls = 0
142  IF (global%plagUsed) npcls = pplag%nPcls
143 
144  IF (npcls < 1) go to 9
145 
146 ! Check if particle vapor energy is active ------------------------------------
147 
148  indplagvapor = region%inrtInput%indPlagVapor
149  IF (region%inrtInput%globActiveness(indplagvapor) /= inrt_act_active) go to 9
150 
151 ! Set pointers and values -----------------------------------------------------
152 
153  pmixtcv => pmixt%cv
154  pmixtdv => pmixt%dv
155  pmixtgv => pmixt%gv
156 
157  pplagcv => pplag%cv
158  pplagaiv => pplag%aiv
159  pplagarv => pplag%arv
160 
161  pinrtburn => region%inrtInput%inrts(inrt_type_burning)
162 
163 ! temperature below which to release vapor energy, which is set to be the same
164 ! as the temperature above which burning shunts energy to vapor
165 
166  releasetemp = pinrtburn%data(inrt_dat_burning_vapor_temp)
167 
168  IF (releasetemp < 500._rfreal .OR. releasetemp > 10000._rfreal) THEN
169  CALL errorstop( global,err_inrt_badval,__line__ )
170  END IF ! releaseTemp
171 
172 ! need mixture temperature and spht, so compute all dv and gv for mixture
173 
174  IF ( region%mixtInput%gasModel == gas_model_tcperf ) THEN ! cp, Mol=const.
175  CALL mixtureproperties(region,ibc,iec,.false.)
176  ELSE
177  CALL mixtureproperties(region,ibc,iec,.true.)
178  END IF ! region%mixtInput%gasModel
179 
180 ! allocate and zero temporary array -------------------------------------------
181 
182  ALLOCATE( vaportot(ibc:iec),stat=errorflag )
183  errorflag = global%error
184  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
185 
186  vaportot(:) = 0._rfreal
187 
188 ! sum up vapor energy in cells ------------------------------------------------
189 
190  DO ipcls = 1,npcls
191 
192  icell = pplagaiv(aiv_plag_icells,ipcls)
193 
194  vaportot(icell) = vaportot(icell) + pplagcv( cv_plag_enervapor,ipcls) * &
195  pplagarv(arv_plag_spload, ipcls)
196  END DO ! iPcls
197 
198  DO ic = ibc,iec
199 
200  keepfrac = -1._rfreal
201  gastemp = pmixtdv(dv_mixt_temp,ic)
202 
203  IF (vaportot(ic) > 0._rfreal .AND. gastemp < releasetemp) THEN
204 
205 ! --- normalize vaporTot by cell volume
206 
207 ! --- Note: normalization is necessary because cv values are not per volume
208 ! --- for particles, but are per volume for continuua, in contrast to rhs
209 ! --- values, which are not per unit volume either for particles or continuua.
210 
211  vaportot(ic) = vaportot(ic) / vol(ic)
212 
213 ! --- Compute heat capacity of gas (this is based on how revision 1.12 of
214 ! --- perfgasDependentVars.F90 computes these quantities)
215 
216  rgas = mixtperf_r_m( pmixtgv(gv_mixt_mol,ic*indmol))
217  gamma = mixtperf_g_cpr(pmixtgv(gv_mixt_cp, ic*indcp ),rgas)
218 
219  hcap = (rgas/(gamma - 1._rfreal)) * pmixtcv(cv_mixt_dens,ic)
220 
221 ! --- Compute difference between current energy and that which would
222 ! --- result from raising the gas temperature to releaseTemp
223 
224  deltaener = hcap*(releasetemp - gastemp)
225 
226 ! --- Augment gas energy
227 
228  IF (vaportot(ic) > deltaener) THEN
229 
230  pmixtcv(cv_mixt_ener,ic) = pmixtcv(cv_mixt_ener,ic) + deltaener
231 
232  keepfrac = 1._rfreal - deltaener / vaportot(ic)
233 
234  ELSE
235 
236  pmixtcv(cv_mixt_ener,ic) = pmixtcv(cv_mixt_ener,ic) + vaportot(ic)
237 
238  keepfrac = 0._rfreal
239 
240  END IF ! vaporTot(ic) > deltaEner
241 
242  ELSE
243 
244  keepfrac = 1._rfreal
245 
246  END IF ! vaporTot(ic) > 0._RFREAL .AND. gasTemp < releaseTemp
247 
248  IF (keepfrac < 0._rfreal .OR. keepfrac > 1._rfreal) THEN
249  CALL errorstop( global,err_invalid_value,__line__ )
250  END IF ! keepFrac
251 
252 ! - save value of keepFrac in the vaporTot array
253 
254  vaportot(ic) = keepfrac
255 
256  END DO ! ic
257 
258 ! Loop over all the particles -------------------------------------------------
259 
260  DO ipcls = 1,npcls
261 
262  icell = pplagaiv(aiv_plag_icells,ipcls)
263 
264  pplagcv(cv_plag_enervapor,ipcls) = pplagcv(cv_plag_enervapor,ipcls) * &
265  vaportot(icell)
266  END DO ! iPcls
267 
268 ! Deallocate temporary array --------------------------------------------------
269 
270  DEALLOCATE( vaportot,stat=errorflag )
271  global%error = errorflag
272  IF (global%error /= 0) CALL errorstop( global,err_deallocate,__line__ )
273 
274 ! finalize --------------------------------------------------------------------
275 
276 9 CONTINUE
277 #endif
278  CALL deregisterfunction( global )
279 
280 END SUBROUTINE inrt_vaporenergyconversion
281 
282 !******************************************************************************
283 !
284 ! RCS Revision history:
285 !
286 ! $Log: INRT_VaporEnergyConversion.F90,v $
287 ! Revision 1.4 2008/12/06 08:44:32 mtcampbe
288 ! Updated license.
289 !
290 ! Revision 1.3 2008/11/19 22:17:44 mtcampbe
291 ! Added Illinois Open Source License/Copyright
292 !
293 ! Revision 1.2 2005/10/31 21:09:37 haselbac
294 ! Changed specModel and SPEC_MODEL_NONE
295 !
296 ! Revision 1.1 2004/12/01 21:56:49 fnajjar
297 ! Initial revision after changing case
298 !
299 ! Revision 1.3 2004/03/25 21:15:33 jferry
300 ! added MixtureProperties to ModInterfaces list
301 !
302 ! Revision 1.2 2004/03/05 22:09:03 jferry
303 ! created global variables for peul, plag, and inrt use
304 !
305 ! Revision 1.1 2004/03/02 21:47:29 jferry
306 ! Added After Update interactions
307 !
308 !******************************************************************************
309 
310 
311 
312 
313 
314 
315 
**********************************************************************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 idcend
real(rfreal) function mixtperf_r_m(M)
Definition: MixtPerf_R.F90:54
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 inrt_vaporenergyconversion(region)
subroutine rflo_getdimensdummy(region, iLev, idcbeg, idcend, jdcbeg, jdcend, kdcbeg, kdcend)
**********************************************************************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 kdcbeg
subroutine rflo_getcelloffset(region, iLev, iCellOffset, ijCellOffset)
**********************************************************************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 idcbeg
**********************************************************************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
**********************************************************************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 jdcend
**********************************************************************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 jdcbeg
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
subroutine mixtureproperties(region, inBeg, inEnd, gasUpdate)
subroutine deregisterfunction(global)
Definition: ModError.F90:469
real(rfreal) function mixtperf_g_cpr(Cp, R)
Definition: MixtPerf_G.F90:39