Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
ReadTimeZoomingSection.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 timezooming.
26 !
27 ! Description: none.
28 !
29 ! Input: user input file.
30 !
31 ! Output: global = timezooming parameters
32 !
33 ! Notes: none.
34 !
35 !******************************************************************************
36 
37 
38 SUBROUTINE readtimezoomingsection( global )
39 
40  USE moddatatypes
41  USE modglobal, ONLY : t_global
42  USE modinterfaces, ONLY : readsection
43  USE moderror
44  USE modparameters
45  USE modmpi
46 
47  IMPLICIT NONE
48 
49 ! ... parameters
50  TYPE(t_global), POINTER :: global
51 
52 ! ... local variables
53  INTEGER :: nvals
54  INTEGER, PARAMETER :: nvals_max = 9
55 
56  CHARACTER(10) :: keys(nvals_max)
57 
58  LOGICAL :: defined(nvals_max)
59 
60  REAL(RFREAL) :: vals(nvals_max)
61 
62 !******************************************************************************
63 
64  CALL registerfunction( global,'ReadTimeZoomingSection',&
65  'ReadTimeZoomingSection.F90' )
66 ! specify keywords and search for them
67 
68  nvals = nvals_max
69 
70  keys(1) = 'MINPLANE'
71  keys(2) = 'MAXPLANE'
72  keys(3) = 'NOZINLET'
73  keys(4) = 'NOZRAD'
74  keys(5) = 'AXIS'
75  keys(6) = 'THROATRAD'
76  keys(7) = 'N'
77  keys(8) = 'RHO'
78  keys(9) = 'A'
79 
80 
81  CALL readsection( global,if_input,nvals,keys,vals,defined )
82 
83  IF (defined( 1)) THEN
84  global%tzMinPlane = vals( 1)
85  ELSE
86  global%tzMinPlane = -9d10
87  ENDIF
88 
89  IF (defined( 2)) THEN
90  global%tzMaxPlane = vals( 2)
91  ELSE
92  global%tzMaxPlane = 0.85_rfreal
93  ENDIF
94 
95  IF (defined( 8)) THEN
96  global%tzRhos = vals( 8)
97  ELSE
98  global%tzRhos = 1702.68_rfreal
99  ENDIF
100 
101  IF (defined( 9)) THEN
102  global%tzA = vals( 9)
103  ELSE
104  global%tzA = .000003789917_rfreal
105  ENDIF
106 
107  IF (defined( 7)) THEN
108  global%tzN = vals( 7)
109  ELSE
110  global%tzN = 0.461_rfreal
111  ENDIF
112 
113  IF (defined( 6)) THEN
114  global%tzThroatRad = vals( 6)
115  ELSE
116  global%tzThroatRad = 0.013208_rfreal
117  ENDIF
118 
119  IF (defined( 5)) THEN
120  IF(vals(5) == 1.0) THEN
121  global%tzCoordLong = xcoord
122  global%tzCoordTrans1 = ycoord
123  global%tzCoordTrans2 = zcoord
124  ELSE IF (vals(5) == 2.0) THEN
125  global%tzCoordLong = ycoord
126  global%tzCoordTrans1 = zcoord
127  global%tzCoordTrans2 = xcoord
128  ELSE
129  global%tzCoordLong = zcoord
130  global%tzCoordTrans1 = xcoord
131  global%tzCoordTrans2 = ycoord
132  ENDIF
133  ELSE
134  global%tzCoordLong = xcoord
135  global%tzCoordTrans1 = ycoord
136  global%tzCoordTrans2 = zcoord
137  ENDIF
138 
139  global%tzSubNoz = .false.
140  IF (defined(3)) THEN
141  global%tzNozInlet = vals( 3)
142  global%tzSubNoz = .true.
143  ELSE
144  global%tzNozInlet = global%tzMaxPlane
145  ENDIF
146 
147  IF (defined(4)) THEN
148  global%tzNozRad = vals(4)
149  global%tzSubNoz = .true.
150  ELSE
151  global%tzNozRad = global%tzThroatRad
152  ENDIF
153 
154 ! finalize
155 
156  CALL deregisterfunction( global )
157 
158 END SUBROUTINE readtimezoomingsection
159 
160 
161 
162 
163 
164 
165 
166 
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
subroutine readsection(global, fileID, nvals, keys, vals, 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 deregisterfunction(global)
Definition: ModError.F90:469
subroutine readtimezoomingsection(global)