Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
INRT_ReadBoilingRegulation.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 Boiling Regulation
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_ReadBoilingRegulation.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_readboilingregulation( 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
62  IMPLICIT NONE
63 
64 ! ... parameters
65  TYPE(t_region), POINTER :: regions(:)
66 
67 ! ... loop variables
68  INTEGER :: ireg
69 
70 ! ... local variables
71  INTEGER, PARAMETER :: nstrkeys_max = 5
72  INTEGER, PARAMETER :: nkeys_max = 20
73 
74  CHARACTER(CHRLEN) :: rcsidentstring
75  CHARACTER(CHRLEN) :: strkeys(nstrkeys_max),keys(nkeys_max)
76  CHARACTER(CHRLEN) :: strvals(nstrkeys_max)
77 
78  INTEGER :: brbeg,brend
79  INTEGER :: nstrkeys,nimplkeys,nkeys
80  INTEGER :: istrkeymaterialliq,istrkeymaterialgas
81  INTEGER :: ikey,ikeyused,ikeymodel,ikeyboilpt,ikeyenpms
82 
83  LOGICAL :: defined(nkeys_max),strdefined(nstrkeys_max)
84 
85  REAL(RFREAL) :: boilpt,enpms
86  REAL(RFREAL) :: vals(nkeys_max)
87 
88  TYPE(t_material), POINTER :: matliq,matgas
89  TYPE(t_inrt_input), POINTER :: input
90  TYPE(t_inrt_interact), POINTER :: inrt
91  TYPE(t_global), POINTER :: global
92 
93 !******************************************************************************
94 
95  rcsidentstring = '$RCSfile: INRT_ReadBoilingRegulation.F90,v $ $Revision: 1.3 $'
96 
97  global => regions(1)%global
98 
99  CALL registerfunction( global,'INRT_ReadBoilingRegulation',&
100  'INRT_ReadBoilingRegulation.F90' )
101 
102 ! begin -----------------------------------------------------------------------
103 
104 ! define string keys
105 
106  istrkeymaterialliq = 1
107  istrkeymaterialgas = 2
108  nstrkeys = 2
109 
110  strkeys(istrkeymaterialliq) = 'MATERIAL_LIQ'
111  strkeys(istrkeymaterialgas) = 'MATERIAL_GAS'
112 
113  IF (nstrkeys > nstrkeys_max) &
114  CALL errorstop( global,err_exceeds_decl_mem,__line__ )
115 
116 ! define implementation-dependent keys
117 
118  ikeyused = 1
119  ikeymodel = 2
120  ikeyboilpt = 3
121  ikeyenpms = 4
122  nimplkeys = 4
123 
124  keys(ikeyused) = 'USED'
125  keys(ikeymodel) = 'MODEL'
126  keys(ikeyboilpt) = 'BOILING_POINT'
127  keys(ikeyenpms) = 'ENERGY_PER_MASS'
128 
129  nkeys = nimplkeys
130 
131  IF (nkeys > nkeys_max) CALL errorstop( global,err_exceeds_decl_mem,__line__ )
132 
133 ! Read interaction section from input file
134 
135 #ifdef RFLO
136  CALL readbothregionsection( global,if_input,nkeys,nstrkeys,keys,strkeys, &
137  vals,strvals,brbeg,brend,defined,strdefined )
138 #endif
139 #ifdef RFLU
140  CALL readbothsection( global,if_input,nkeys,nstrkeys,keys,strkeys, &
141  vals,strvals,defined,strdefined )
142  brbeg = lbound(regions,1)
143  brend = ubound(regions,1)
144 #endif
145 
146  DO ireg=brbeg,brend
147 
148  input => regions(ireg)%inrtInput
149  inrt => input%inrts(inrt_type_boilrgn)
150 
151 ! - Check that INRT_DEFAULT section has been read, and that interaction has not
152 
153  IF (.NOT. input%defaultRead) &
154  CALL errorstop( global,err_inrt_defunread,__line__ )
155 
156  IF (inrt%used) CALL errorstop( global,err_inrt_read,__line__ )
157 
158 ! - Check if interaction is used
159 
160  inrt%used = .true. ! used by default when its section appears
161 
162  IF (defined(ikeyused)) THEN
163  IF (nint(vals(ikeyused)) == 0) inrt%used = .false.
164  END IF ! defined(iKeyUsed)
165 
166  IF (.NOT. inrt%used) cycle ! do not bother with unused interactions
167 
168 ! - Define interaction (using any relevant information from input deck)
169 
170  CALL inrt_defineboilingregulation(regions(ireg))
171 
172 ! - Set pointers to liq and gas materials
173 
174  IF (strdefined(istrkeymaterialliq)) THEN
175  CALL inrt_setmaterial(global,matliq,strvals(istrkeymaterialliq))
176  ELSE
177  CALL errorstop( global,err_inrt_missingmat,__line__ )
178  END IF ! strDefined(iStrKeyMaterialLiq)
179 
180  IF (strdefined(istrkeymaterialgas)) THEN
181  CALL inrt_setmaterial(global,matgas,strvals(istrkeymaterialgas))
182  ELSE
183  CALL errorstop( global,err_inrt_missingmat,__line__ )
184  END IF ! strDefined(iStrKeyMaterialGas)
185 
186 ! - Check that input and output materials have the same properties
187 
188  IF (matliq%molw /= matgas%molw .OR. matliq%dens /= matgas%dens .OR. &
189  matliq%spht /= matgas%spht) &
190  CALL errorstop( global,err_inrt_boil_same,__line__ )
191 
192 ! - Check for switches
193 
194 ! - Material indices
195 
196  inrt%switches(inrt_swi_boilrgn_liqind) = matliq%index
197  inrt%switches(inrt_swi_boilrgn_gasind) = matgas%index
198 
199 ! - Which model is used
200 
201  inrt%switches(inrt_swi_boilrgn_model) = inrt_boilrgn_model_default
202 
203  IF (defined(ikeymodel)) THEN
204 
205  SELECT CASE (nint(vals(ikeymodel)))
206 
207  CASE (1)
208  inrt%switches(inrt_swi_boilrgn_model) = inrt_boilrgn_model_sharp
209 
210  CASE default
211  CALL errorstop( global,err_inrt_badswitch,__line__ )
212 
213  END SELECT ! vals(iKeyModel)
214 
215  END IF ! defined(iKeyModel)
216 
217 ! - Check for data
218 
219 ! - Boiling point of substance
220 
221  IF (defined(ikeyboilpt)) THEN
222 
223  boilpt = vals(ikeyboilpt)
224 
225  IF (boilpt <= 0._rfreal) CALL errorstop( global,err_inrt_badval,__line__ )
226 
227  inrt%data(inrt_dat_boilrgn_boilpt) = boilpt
228 
229  ELSE
230 
231  CALL errorstop( global,err_inrt_missingval,__line__ )
232 
233  END IF ! defined(iKeyBoilPt)
234 
235 ! - Energy released during condensation per unit mass of substance
236 
237  IF (defined(ikeyenpms)) THEN
238 
239  enpms = vals(ikeyenpms)
240 
241  IF (enpms <= 0._rfreal) CALL errorstop( global,err_inrt_badval,__line__ )
242 
243  inrt%data(inrt_dat_boilrgn_enpms) = enpms
244 
245  ELSE
246 
247  CALL errorstop( global,err_inrt_missingval,__line__ )
248 
249  END IF ! defined(iKeyEnPMs)
250 
251  END DO ! iReg
252 
253 ! finalize --------------------------------------------------------------------
254 
255  CALL deregisterfunction( global )
256 
257 END SUBROUTINE inrt_readboilingregulation
258 
259 !******************************************************************************
260 !
261 ! RCS Revision history:
262 !
263 ! $Log: INRT_ReadBoilingRegulation.F90,v $
264 ! Revision 1.3 2008/12/06 08:44:31 mtcampbe
265 ! Updated license.
266 !
267 ! Revision 1.2 2008/11/19 22:17:44 mtcampbe
268 ! Added Illinois Open Source License/Copyright
269 !
270 ! Revision 1.1 2004/12/01 21:56:32 fnajjar
271 ! Initial revision after changing case
272 !
273 ! Revision 1.5 2004/07/23 22:43:16 jferry
274 ! Integrated rocspecies into rocinteract
275 !
276 ! Revision 1.4 2004/03/05 22:09:03 jferry
277 ! created global variables for peul, plag, and inrt use
278 !
279 ! Revision 1.3 2004/03/02 21:48:09 jferry
280 ! First phase of replacing Detangle interaction
281 !
282 ! Revision 1.2 2003/09/26 21:46:54 fnajjar
283 ! Modified ModInterfaces call to ModInterfacesInteract
284 !
285 ! Revision 1.1 2003/09/25 15:48:43 jferry
286 ! implemented Boiling Regulation interaction
287 !
288 !******************************************************************************
289 
290 
291 
292 
293 
294 
295 
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 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 brbeg
subroutine input(X, NNODE, NDC, NCELL, NFCE, NBPTS, NBFACE, ITYP, NPROP, XBNDY, XFAR, YFAR, ZFAR)
subroutine inrt_readboilingregulation(regions)
subroutine inrt_defineboilingregulation(region)
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
subroutine deregisterfunction(global)
Definition: ModError.F90:469