Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
ModInterfacesIO.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: set explicit interfaces to subroutines and functions
26 ! related to I/O.
27 !
28 ! Description: none
29 !
30 ! Notes: none.
31 !
32 !******************************************************************************
33 !
34 ! $Id: ModInterfacesIO.F90,v 1.9 2008/12/06 08:44:18 mtcampbe Exp $
35 !
36 ! Copyright: (c) 2001 by the University of Illinois
37 !
38 !******************************************************************************
39 
41 
42  IMPLICIT NONE
43 
44  INTERFACE
45 
46  INTEGER FUNCTION buildpatchidentifier(iRegion,iPatch)
47  INTEGER, INTENT(IN) :: ipatch,iregion
48  END FUNCTION buildpatchidentifier
49 
50  SUBROUTINE makenumberedkeys(keys,indBegin,string,numBegin,numEnd,numSkip)
51  CHARACTER(*), INTENT(inout) :: keys(:)
52  CHARACTER(*), INTENT(in) :: string
53  INTEGER, INTENT(in) :: indbegin,numbegin,numend,numskip
54  END SUBROUTINE makenumberedkeys
55 
56  SUBROUTINE readbothregionsection( global,fileID,nvals,nStrVals,keys, &
57  strkeys,vals,strvals,brbeg,brend, &
58  defined,strdefined )
59  USE moddatatypes
60  USE modglobal, ONLY : t_global
61  INTEGER :: fileid, nvals, nstrvals, brbeg, brend
62  CHARACTER(*) :: keys(nvals), strkeys(nstrvals)
63  LOGICAL :: defined(nvals), strdefined(nstrvals)
64  REAL(RFREAL) :: vals(nvals)
65  CHARACTER(*) :: strvals(nstrvals)
66  TYPE(t_global), POINTER :: global
67  END SUBROUTINE readbothregionsection
68 
69  SUBROUTINE readbothsection( global,fileID,nvals,nStrVals,keys,strKeys, &
70  vals,strvals,defined,strdefined )
71  USE moddatatypes
72  USE modglobal, ONLY : t_global
73  INTEGER :: fileid, nvals, nstrvals
74  CHARACTER(*) :: keys(nvals), strkeys(nstrvals)
75  LOGICAL :: defined(nvals), strdefined(nstrvals)
76  REAL(RFREAL) :: vals(nvals)
77  CHARACTER(*) :: strvals(nstrvals)
78  TYPE(t_global), POINTER :: global
79  END SUBROUTINE readbothsection
80 
81  SUBROUTINE readaccelerationsection( global )
82  USE modglobal, ONLY : t_global
83  TYPE(t_global), POINTER :: global
84  END SUBROUTINE readaccelerationsection
85 
86  SUBROUTINE readflowsection( regions )
87  USE moddatastruct, ONLY : t_region
88  TYPE(t_region), POINTER :: regions(:)
89  END SUBROUTINE readflowsection
90 
91  SUBROUTINE readforcessection( global )
92  USE modglobal, ONLY : t_global
93  TYPE(t_global), POINTER :: global
94  END SUBROUTINE readforcessection
95 
96  SUBROUTINE readformatssection( global )
97  USE modglobal, ONLY : t_global
98  TYPE(t_global), POINTER :: global
99  END SUBROUTINE readformatssection
100 
101 #ifdef RFLO
102  SUBROUTINE readgridmotionsection( global )
103  USE modglobal, ONLY : t_global
104  TYPE(t_global), POINTER :: global
105  END SUBROUTINE readgridmotionsection
106 #endif
107 #ifdef RFLU
108  SUBROUTINE readgridmotionsection(regions)
109  USE moddatastruct, ONLY : t_region
110  TYPE(t_region), POINTER :: regions(:)
111  END SUBROUTINE readgridmotionsection
112 #endif
113 
114  SUBROUTINE readinitflowsection(regions)
115  USE moddatastruct, ONLY: t_region
116  TYPE(t_region), DIMENSION(:), POINTER :: regions
117  END SUBROUTINE readinitflowsection
118 
119  SUBROUTINE readinputfile( regions )
120  USE moddatastruct, ONLY : t_region
121  TYPE(t_region), POINTER :: regions(:)
122  END SUBROUTINE readinputfile
123 
124  SUBROUTINE readlistsection( global,fileID,key,nCols,nRows,vals,defined )
125  USE moddatatypes
126  USE modglobal, ONLY : t_global
127  INTEGER :: fileid, ncols, nrows
128  CHARACTER(*) :: key
129  LOGICAL :: defined
130  REAL(RFREAL), POINTER :: vals(:,:)
131  TYPE(t_global), POINTER :: global
132  END SUBROUTINE readlistsection
133 
134  SUBROUTINE readmixturesection(regions)
135  USE moddatastruct, ONLY : t_region
136  TYPE(t_region), POINTER :: regions(:)
137  END SUBROUTINE readmixturesection
138 
139  SUBROUTINE readmultigridsection( global )
140  USE modglobal, ONLY : t_global
141  TYPE(t_global), POINTER :: global
142  END SUBROUTINE readmultigridsection
143 
144  SUBROUTINE readnumericssection( regions )
145  USE moddatastruct, ONLY : t_region
146  TYPE(t_region), POINTER :: regions(:)
147  END SUBROUTINE readnumericssection
148 
149 #ifdef RFLO
150  SUBROUTINE readpatchsection( global,fileID,nvals,keys,vals,brbeg,brend, &
151  prbeg,prend,distrib,fname,defined )
152 #endif
153 #ifdef RFLU
154  SUBROUTINE readpatchsection( global,fileID,nvals,keys,vals, &
155  prbeg,prend,distrib,fname,bcname,defined )
156 #endif
157  USE moddatatypes
158  USE modglobal, ONLY : t_global
159 #ifdef RFLO
160  INTEGER :: brbeg, brend
161 #endif
162  INTEGER :: fileid, nvals, prbeg, prend, distrib
163  CHARACTER(*) :: keys(nvals), fname
164 #ifdef RFLU
165  CHARACTER(*) :: bcname
166 #endif
167  LOGICAL :: defined(nvals)
168  REAL(RFREAL) :: vals(nvals)
169  TYPE(t_global), POINTER :: global
170  END SUBROUTINE readpatchsection
171 
172  SUBROUTINE readpostsection(global)
173  USE modglobal, ONLY: t_global
174  TYPE(t_global), POINTER :: global
175  END SUBROUTINE readpostsection
176 
177  SUBROUTINE readprefixedlistsection( global,fileID,key,nCols,nRows, &
178  vals,strvals,defined )
179  USE moddatatypes
180  USE modglobal, ONLY : t_global
181  INTEGER :: fileid, ncols, nrows
182  CHARACTER(*) :: key
183  LOGICAL :: defined
184  REAL(RFREAL), POINTER :: vals(:,:)
185  CHARACTER(*), POINTER :: strvals(:)
186  TYPE(t_global), POINTER :: global
187  END SUBROUTINE readprefixedlistsection
188 
189  SUBROUTINE readprepsection(global)
190  USE modglobal, ONLY: t_global
191  TYPE(t_global), POINTER :: global
192  END SUBROUTINE readprepsection
193 
194  SUBROUTINE readprobesection( global )
195  USE modglobal, ONLY : t_global
196  TYPE(t_global), POINTER :: global
197  END SUBROUTINE readprobesection
198 
199  SUBROUTINE readrandomsection( global )
200  USE modglobal, ONLY : t_global
201  TYPE(t_global), POINTER :: global
202  END SUBROUTINE readrandomsection
203 
204  SUBROUTINE readreferencesection( global )
205  USE modglobal, ONLY : t_global
206  TYPE(t_global), POINTER :: global
207  END SUBROUTINE readreferencesection
208 
209 #ifdef RFLU
210  SUBROUTINE readtimezoomingsection( global )
211  USE modglobal, ONLY : t_global
212  TYPE(t_global), POINTER :: global
213  END SUBROUTINE readtimezoomingsection
214 
215  SUBROUTINE readrocketsection( global )
216  USE modglobal, ONLY : t_global
217  TYPE(t_global), POINTER :: global
218  END SUBROUTINE readrocketsection
219 #endif
220 
221  SUBROUTINE readregionsection( global,fileID,nvals,keys,vals, &
222  brbeg,brend,defined )
223  USE moddatatypes
224  USE modglobal, ONLY : t_global
225  INTEGER :: fileid, nvals, brbeg, brend
226  CHARACTER(*) :: keys(nvals)
227  LOGICAL :: defined(nvals)
228  REAL(RFREAL) :: vals(nvals)
229  TYPE(t_global), POINTER :: global
230  END SUBROUTINE readregionsection
231 
232  SUBROUTINE readsection( global,fileID,nvals,keys,vals,defined )
233  USE moddatatypes
234  USE modglobal, ONLY : t_global
235  INTEGER :: fileid, nvals
236  CHARACTER(*) :: keys(nvals)
237  LOGICAL :: defined(nvals)
238  REAL(RFREAL) :: vals(nvals)
239  TYPE(t_global), POINTER :: global
240  END SUBROUTINE readsection
241 
242  SUBROUTINE readstringsection( global,fileID,nvals,keys,vals,defined )
243  USE moddatatypes
244  USE modglobal, ONLY : t_global
245  INTEGER :: fileid, nvals
246  CHARACTER(*) :: keys(nvals)
247  LOGICAL :: defined(nvals)
248  CHARACTER(*) :: vals(nvals)
249  TYPE(t_global), POINTER :: global
250  END SUBROUTINE readstringsection
251 
252  SUBROUTINE readthrustsection( global )
253  USE modglobal, ONLY : t_global
254  TYPE(t_global), POINTER :: global
255  END SUBROUTINE readthrustsection
256 
257  SUBROUTINE readtimestepsection( global )
258  USE modglobal, ONLY : t_global
259  TYPE(t_global), POINTER :: global
260  END SUBROUTINE readtimestepsection
261 
262  SUBROUTINE readtransformsection( global )
263  USE modglobal, ONLY : t_global
264  TYPE(t_global), POINTER :: global
265  END SUBROUTINE readtransformsection
266 
267  SUBROUTINE readviscositysection( regions )
268  USE moddatastruct, ONLY : t_region
269  TYPE(t_region), POINTER :: regions(:)
270  END SUBROUTINE readviscositysection
271 
272  SUBROUTINE writeconvergence( global )
273  USE modglobal, ONLY : t_global
274  TYPE(t_global), POINTER :: global
275  END SUBROUTINE writeconvergence
276 
277  SUBROUTINE writetotalmass(regions)
278  USE moddatastruct, ONLY: t_region
279  TYPE(t_region), POINTER :: regions(:)
280  END SUBROUTINE writetotalmass
281 
282  SUBROUTINE writeprobe( regions,iReg )
283  USE moddatastruct, ONLY : t_region
284  TYPE(t_region), POINTER :: regions(:)
285  INTEGER :: ireg
286  END SUBROUTINE writeprobe
287 
288  SUBROUTINE writethrust( global )
289  USE modglobal, ONLY : t_global
290  TYPE(t_global), POINTER :: global
291  END SUBROUTINE writethrust
292 
293  END INTERFACE
294 
295 END MODULE modinterfacesio
296 
297 !******************************************************************************
298 !
299 ! RCS Revision history:
300 !
301 ! $Log: ModInterfacesIO.F90,v $
302 ! Revision 1.9 2008/12/06 08:44:18 mtcampbe
303 ! Updated license.
304 !
305 ! Revision 1.8 2008/11/19 22:17:29 mtcampbe
306 ! Added Illinois Open Source License/Copyright
307 !
308 ! Revision 1.7 2007/04/14 14:29:34 mtcampbe
309 ! Updated for TZ and rocket case constraints
310 !
311 ! Revision 1.6 2005/10/31 19:26:48 haselbac
312 ! Added interface for ReadMixtureSection
313 !
314 ! Revision 1.5 2004/06/16 20:00:54 haselbac
315 ! Removed buildFileNameXXX routines
316 !
317 ! Revision 1.4 2004/04/08 03:17:07 wasistho
318 ! nDummyCells in Rocflo read from INITFLOW section
319 !
320 ! Revision 1.3 2003/11/21 22:35:51 fnajjar
321 ! Update Random Number Generator
322 !
323 ! Revision 1.2 2003/08/28 20:05:39 jblazek
324 ! Added acceleration terms.
325 !
326 ! Revision 1.1 2003/08/11 21:50:00 jblazek
327 ! Splitted ModInterfaces into 4 sections.
328 !
329 !******************************************************************************
330 
331 
332 
333 
334 
335 
subroutine readrocketsection(global)
subroutine makenumberedkeys(keys, indBegin, string, numBegin, numEnd, numSkip)
subroutine readmultigridsection(global)
subroutine readbothsection(global, fileID, nvals, nStrVals, keys, strKeys, vals, strVals, defined, strDefined)
subroutine readmixturesection(regions)
subroutine readbothregionsection(global, fileID, nvals, nStrVals, keys, strKeys, vals, strVals, brbeg, brend, defined, strDefined)
subroutine readrandomsection(global)
subroutine readstringsection(global, fileID, nvals, keys, vals, defined)
subroutine readlistsection(global, fileID, key, nCols, nRows, vals, defined)
subroutine readprobesection(global)
subroutine readthrustsection(global)
**********************************************************************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 readnumericssection(regions)
subroutine readprefixedlistsection(global, fileID, key, nCols, nRows, vals, strVals, defined)
subroutine readpatchsection(global, fileID, nvals, keys, vals, brbeg, brend, prbeg, prend, distrib, profType, fname, defined)
subroutine readaccelerationsection(global)
subroutine writeprobe(regions, iReg)
Definition: WriteProbe.F90:45
subroutine readformatssection(global)
**********************************************************************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 USE ModDataTypes USE prend
INTEGER function buildpatchidentifier(iRegion, iPatch)
subroutine readinputfile(regions)
subroutine readinitflowsection(regions)
subroutine readsection(global, fileID, nvals, keys, vals, defined)
subroutine readprepsection(global)
subroutine readtransformsection(global)
**********************************************************************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 USE ModDataTypes USE prbeg
subroutine readflowsection(regions)
subroutine readtimestepsection(global)
subroutine readreferencesection(global)
subroutine readregionsection(global, fileID, nvals, keys, vals, brbeg, brend, defined)
**********************************************************************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 USE ModDataTypes USE nvals
subroutine readforcessection(global)
subroutine writeconvergence(global)
subroutine readviscositysection(regions)
static T_Key key
Definition: vinci_lass.c:76
subroutine writetotalmass(regions)
static const char * string()
Definition: CImg.h:2085
subroutine readpostsection(global)
subroutine readtimezoomingsection(global)
subroutine writethrust(global)
Definition: WriteThrust.F90:43