Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
PEUL_ReadConPartSection.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: read in user input related to Eulerian particle module.
26 !
27 ! Description: none.
28 !
29 ! Input: user input file.
30 !
31 ! Output: regions = PEUL information
32 !
33 ! Notes:
34 !
35 ! Reads in Sc and vis2, even though these do not do anything
36 !
37 !******************************************************************************
38 !
39 ! $Id: PEUL_ReadConPartSection.F90,v 1.3 2008/12/06 08:44:39 mtcampbe Exp $
40 !
41 ! Copyright: (c) 2002 by the University of Illinois
42 !
43 !******************************************************************************
44 
45 SUBROUTINE peul_readconpartsection( regions,nPtypes,brbeg,brend )
46 
47  USE moddatatypes
48  USE moddatastruct, ONLY : t_region
49  USE modglobal, ONLY : t_global
50  USE modparteul, ONLY : t_peul_input
51  USE moderror
52  USE modparameters
54 
57  IMPLICIT NONE
58 
59 ! ... parameters
60  TYPE(t_region), POINTER :: regions(:)
61  INTEGER, INTENT(IN) :: nptypes
62  INTEGER, INTENT(OUT) :: brbeg,brend
63 
64 ! ... loop variables
65  INTEGER :: ireg,iptype
66 
67 ! ... local variables
68  INTEGER, PARAMETER :: nstrkeys_max = 5
69  INTEGER, PARAMETER :: nkeys_max = 20
70 
71  CHARACTER(CHRLEN) :: rcsidentstring
72  CHARACTER(20) :: strkeys(nstrkeys_max),keys(nkeys_max)
73  CHARACTER(CHRLEN) :: strvals(nstrkeys_max)
74 
75  INTEGER :: nkeys,nstrkeys,nptypesused,errorflag,readstatus
76  INTEGER :: istrkeymaterial
77  INTEGER :: ikeyused,ikeydiam,ikeypuff,ikeyinitc
78  INTEGER :: ikeyschm,ikeyk2,ikeyinvk4,ikeysmoocf,ikeyconstinit
79  INTEGER :: ikeynegreport,ikeyclipmodel,ikeymethodv
80 
81  LOGICAL :: strdefined(nstrkeys_max),defined(nkeys_max)
82 
83  REAL(RFREAL) :: vals(nkeys_max)
84 
85  TYPE(t_peul_input), POINTER :: input
86  TYPE(t_global), POINTER :: global
87 
88 !******************************************************************************
89 
90  rcsidentstring = &
91  '$RCSfile: PEUL_ReadConPartSection.F90,v $ $Revision: 1.3 $'
92 
93  global => regions(1)%global
94 
95  CALL registerfunction( global,'PEUL_ReadConPartSection',&
96  'PEUL_ReadConPartSection.F90' )
97 
98 ! begin -----------------------------------------------------------------------
99 
100 ! define string keys
101 
102  istrkeymaterial = 1
103  nstrkeys = 1
104 
105  IF (nstrkeys > nstrkeys_max) &
106  CALL errorstop( global,err_exceeds_decl_mem,__line__ )
107 
108  strkeys(istrkeymaterial) = 'MATERIAL'
109 
110 ! define real keys
111 
112  ikeyused = 1
113  ikeydiam = 2
114  ikeypuff = 3
115  ikeyinitc = 4
116  ikeyschm = 5
117  ikeyk2 = 6
118  ikeyinvk4 = 7
119  ikeysmoocf = 8
120  ikeyconstinit = 9
121  ikeynegreport = 10
122  ikeyclipmodel = 11
123  ikeymethodv = 12
124  nkeys = 12
125 
126  IF (nkeys > nkeys_max) CALL errorstop( global,err_exceeds_decl_mem,__line__ )
127 
128  keys(ikeyused) = 'USED'
129  keys(ikeydiam) = 'DIAM'
130  keys(ikeypuff) = 'PUFF'
131  keys(ikeyinitc) = 'INITC'
132  keys(ikeyschm) = 'SCHM'
133  keys(ikeyk2) = 'K2'
134  keys(ikeyinvk4) = '1/K4'
135  keys(ikeysmoocf) = 'SMOOCF'
136  keys(ikeyconstinit) = 'CONSTINIT'
137  keys(ikeynegreport) = 'NEGREPORT'
138  keys(ikeyclipmodel) = 'CLIPMODEL'
139  keys(ikeymethodv) = 'METH_VEL'
140 
141 ! specify default values for keys
142 
143  vals = -1.0_rfreal ! default value for undefined quantity
144  vals(ikeyused) = 1.0_rfreal ! used by default CONPART section exists
145  vals(ikeypuff) = 1.0_rfreal ! default for puff factor
146  vals(ikeyinitc) = 1.e-9_rfreal ! default for initial concentration
147  vals(ikeyschm) = 1.0_rfreal ! default for Schmidt number
148  vals(ikeyk2) = 0.0_rfreal ! default for k2
149  vals(ikeyinvk4) = 128.0_rfreal ! default for 1/k4
150  vals(ikeysmoocf) = -1.0_rfreal ! default for residual smoothing (none)
151  vals(ikeyconstinit) = 0.0_rfreal ! default for constant init (.FALSE.)
152  vals(ikeynegreport) = 0.0_rfreal ! default for negativity report
153  vals(ikeyclipmodel) = 0.0_rfreal ! default for clipping model
154  vals(ikeymethodv) = 0.0_rfreal ! default method (0: smoke = fluid vel)
155  nptypesused = max(nptypes,1) ! must be at least one particle type
156 
157 ! read smoke section from input file
158 
159  CALL readbothregionsection( global,if_input,nkeys,nstrkeys,keys,strkeys, &
160  vals,strvals,brbeg,brend,defined,strdefined )
161 
162  IF (nint(vals(ikeyused)) == 1) THEN
163  readstatus = 1 ! read and used
164  ELSE
165  readstatus = 0 ! read and not used
166  END IF ! iKeyUsed
167 
168  DO ireg = brbeg,brend
169 
170  input => regions(ireg)%peulInput
171 
172  IF (input%readStatus == -1) THEN
173  input%readStatus = readstatus
174  ELSE
175  CALL errorstop( global,err_sec_read_twice,__line__ )
176  ENDIF
177 
178  IF (input%readStatus == 0) cycle
179 
180 ! - allocate ptypes
181 
182  ALLOCATE( input%ptypes(nptypesused),stat=errorflag )
183  global%error = errorflag
184  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
185 
186 ! - fill in input data
187 
188  input%nPtypes = nptypesused
189 
190  DO iptype=1,nptypesused
191  nullify(input%ptypes(iptype)%material)
192  IF (strdefined(istrkeymaterial)) THEN
193  CALL inrt_setmaterial(global,input%ptypes(iptype)%material, &
194  strvals(istrkeymaterial))
195  END IF ! strDefined
196  END DO ! iPtype
197 
198  input%ptypes(:)%diam = vals(ikeydiam)
199  input%ptypes(:)%puff = vals(ikeypuff)
200  input%ptypes(:)%initc = vals(ikeyinitc)
201  input%ptypes(:)%Sc = vals(ikeyschm)
202  input%ptypes(:)%vis2 = vals(ikeyk2)
203  input%ptypes(:)%vis4 = vals(ikeyinvk4) ! reciprocal taken in
204  ! PEUL_DerivedInputValues
205  input%smoocf = vals(ikeysmoocf)
206  input%constInit = (nint(vals(ikeyconstinit)) == 1)
207  input%ptypes(:)%negReport = nint(vals(ikeynegreport))
208  input%ptypes(:)%clipModel = nint(vals(ikeyclipmodel))
209 
210  SELECT CASE (nint(vals(ikeynegreport)))
211  CASE (0)
212  input%ptypes(:)%negReport = peul_neg_report_none
213  CASE (1)
214  input%ptypes(:)%negReport = peul_neg_report_used
215  CASE default
216  CALL errorstop( global,err_peul_badval,__line__ )
217  END SELECT ! vals(iKeyNegReport)
218 
219  SELECT CASE (nint(vals(ikeyclipmodel)))
220  CASE (0)
221  input%ptypes(:)%clipModel = peul_clip_model_none
222  CASE (1)
223  input%ptypes(:)%clipModel = peul_clip_model_used
224  CASE default
225  CALL errorstop( global,err_peul_badval,__line__ )
226  END SELECT ! vals(iKeyClipModel)
227 
228  SELECT CASE (nint(vals(ikeymethodv)))
229  CASE (0)
230  input%ptypes(:)%methodV = peul_methv_fluidvel
231  CASE (1)
232  input%ptypes(:)%methodV = peul_methv_eqeul
233  CASE default
234  CALL errorstop( global,err_peul_badval,__line__ )
235  END SELECT ! vals(iKeyMethodV)
236 
237  END DO ! iReg
238 
239 ! finalize --------------------------------------------------------------------
240 
241  CALL deregisterfunction( global )
242 
243 END SUBROUTINE peul_readconpartsection
244 
245 !******************************************************************************
246 !
247 ! RCS Revision history:
248 !
249 ! $Log: PEUL_ReadConPartSection.F90,v $
250 ! Revision 1.3 2008/12/06 08:44:39 mtcampbe
251 ! Updated license.
252 !
253 ! Revision 1.2 2008/11/19 22:17:51 mtcampbe
254 ! Added Illinois Open Source License/Copyright
255 !
256 ! Revision 1.1 2004/12/01 21:09:45 haselbac
257 ! Initial revision after changing case
258 !
259 ! Revision 1.11 2004/05/03 15:09:42 jferry
260 ! added equilibrium Eulerian capability for smoke
261 !
262 ! Revision 1.10 2004/03/05 22:09:04 jferry
263 ! created global variables for peul, plag, and inrt use
264 !
265 ! Revision 1.9 2004/03/02 21:44:52 jferry
266 ! Added clipping options
267 !
268 ! Revision 1.8 2003/09/26 21:49:06 fnajjar
269 ! Changed interface call for INRT_SetMaterial to ModInterfacesInteract
270 !
271 ! Revision 1.7 2003/04/14 16:33:52 jferry
272 ! added option to initialize to constant for t > 0
273 !
274 ! Revision 1.6 2003/04/07 18:29:01 jferry
275 ! added inflow boundary condition and initialization to a constant
276 !
277 ! Revision 1.5 2003/03/24 23:30:53 jferry
278 ! overhauled rocinteract to allow interaction design to use user input
279 !
280 ! Revision 1.4 2003/03/11 16:04:57 jferry
281 ! Created data type for material properties
282 !
283 ! Revision 1.3 2003/03/04 19:26:47 jferry
284 ! Cleaned up routines that read sections of input files
285 !
286 ! Revision 1.2 2003/02/12 23:34:48 jferry
287 ! Replaced [io]stat=global%error with local errorFlag
288 !
289 ! Revision 1.1 2003/02/11 22:52:51 jferry
290 ! Initial import of Rocsmoke
291 !
292 !******************************************************************************
293 
294 
295 
296 
297 
298 
299 
subroutine readbothregionsection(global, fileID, nvals, nStrVals, keys, strKeys, vals, strVals, brbeg, brend, defined, strDefined)
Vector_n max(const Array_n_const &v1, const Array_n_const &v2)
Definition: Vector_n.h:354
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 peul_readconpartsection(regions, nPtypes, brbeg, brend)
subroutine input(X, NNODE, NDC, NCELL, NFCE, NBPTS, NBFACE, ITYP, NPROP, XBNDY, XFAR, YFAR, ZFAR)
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
subroutine deregisterfunction(global)
Definition: ModError.F90:469