Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
init_py.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 MODULE init_py
24  USE data_py
25 
26 CONTAINS
27 
28 
29 !****************************************************************
30  SUBROUTINE burn_get_film_coeff_1d(bp,p_coor,Ts,Teuler,P_in,Qc,Qcprime)
31 
32  IMPLICIT NONE
33 !---------------------------------------------------------------
34 ! DUMMY VARIABLES
35  TYPE(parameter_structure),POINTER :: bp
36  REAL(DBL), INTENT(IN) :: p_coor(3),ts,teuler,p_in
37  REAL(DBL), INTENT(OUT) :: qc,qcprime
38 ! LOCAL VARIABLES
39  REAL(DBL) :: p, te, try_film, front_dist
40  REAL(DBL) :: cp_mks, exp_moser, coe_moser, coe1, par
41  REAL(DBL) :: prndtl, lambda, mu, x_surf
42 !----------------------------------------------------------------
43 
44  p = p_in !MKS
45 !
46 ! Avoid Euler temperatures larger than 2.0*(adiabatic flame temperature)
47 ! this is a temporary hardwired fix, it should never affect the solution
48 !
49  te = min(teuler,2.0d0*bp%Tstar0)
50 
51  IF(bp%ixsymm >= 1)THEN
52  x_surf = p_coor(bp%ixsymm)
53  prndtl = 0.72d0
54  cp_mks = bp%C/j_kg2cal_g
55  lambda = (2.581d-7*te + 3.1788d-5)*4186.8/10.0 !Buckmaster
56  mu = prndtl*lambda
57 
58  exp_moser = - 1.0d0/5.0d0
59  coe_moser = 800.0d0*14.0d0
60  coe1 = 800.0d0/0.0287d0
61 
62 !
63 ! for x_surf < bp%x_surf_burn the propellan is all burning
64 !
65  front_dist = (x_surf - bp%x_surf_burn)
66  par = max( (coe1*front_dist*mu*cp_mks*lambda**(-2.0)), 1.d-6 )
67 
68  try_film = merge(coe_moser*par**exp_moser, 0.0d0, front_dist >= 0.0d0)
69 
70  ELSE
71 
72  try_film = bp%film_cons !MKS
73 
74  ENDIF
75 
76 !
77 ! Avoid negative heat flux
78 !
79  qc = max(try_film * (te - ts), 0.0d0) !MKS
80  qcprime = - try_film !MKS
81 
82 !------------------------------------------------------------------------
83  RETURN
84  END SUBROUTINE burn_get_film_coeff_1d
85 !*************************************************************************
86 
87 
88 
89 !*************************************************************************
90  SUBROUTINE burn_init_1d(bp,bflag,Pin,To,rhoc,p_coor,rb,Toa,fr,Tn,Tflame)
91 
92  IMPLICIT NONE
93 !-------------------------------------------------------------------------
94 ! DUMMY VARIABLES
95  TYPE(parameter_structure),POINTER :: bp
96  INTEGER, INTENT(INOUT) :: bflag
97  REAL(DBL), INTENT(IN) :: pin,to,rhoc,p_coor(3)
98  REAL(DBL), INTENT(OUT) :: rb,toa,fr
99  REAL(DBL), INTENT(OUT) :: tn(:)
100  REAL(DBL), INTENT (OUT) :: tflame
101 ! LOCAL VARIABLES
102  REAL(DBL) :: xcond, c1, ts, dtemp, p, x_surf, dytab, alp
103  INTEGER :: i,jj,kk
104 !-------------------------------------------------------------------------
105 
106 !
107 ! SET BFLAG IF AXISYMMETIC BURNING, OTHERWISE BFLAG COMES FROM FLUIDS
108 !
109  IF(bp%ixsymm >= 1)THEN
110  x_surf = p_coor(bp%ixsymm)
111  IF(x_surf <= bp%x_surf_burn) THEN
112  bflag = 1
113  ELSE
114  bflag = 0
115  ENDIF
116 !RAF ----------------------------------------------------------------------
117  ELSE
118 
119 !RAF HACK: Turn the initial burning off so we can do problems with igniters.
120 !RAF HACK: For the lab scale rocket, we must set ixsymm >= 1.
121 
122  bflag = 0
123 !RAF ----------------------------------------------------------------------
124  ENDIF
125 !
126 ! CONVERT inputs
127 !
128  p = pin*pa2atm
129 
130 !
131 ! calculate Ts, rb given To, P
132 !
133  if(bflag /= 0 ) THEN
134 
135  if(bp%TABUSE == 0) then
136  rb = bp%a_p*( p/bp%Pref )**bp%n_p
137  c1 = -log( rb/bp%Ac ) / bp%ec_ru
138  ts = one/c1
139  alp = bp%alfac
140  else
141  call polint(bp,bp%TABLE%press00,bp%TABLE%Tstd00,bp%TABLE%ny_table,p,ts,dytab)
142  call polint(bp,bp%TABLE%press00,bp%TABLE%rstd00,bp%TABLE%ny_table,p,rb,dytab)
143  jj = 0;kk = 0
144  call polin2(bp,bp%TABLE%tsurf00,bp%TABLE%press00,bp%TABLE%alph00, &
145  bp%TABLE%nx_TABLE,bp%TABLE%ny_table,ts,p,alp,jj,kk)
146  endif
147 
148  xcond = rb / alp
149  dtemp = ts - to
150  do i=1,bp%numx
151  tn(i) = ts - dtemp * (dexp(bp%x(i)*xcond) - one) &
152  / (dexp(bp%xmax*xcond) - one)
153  ENDDO
154  tflame = bp%Tstar0
155  else
156  dtemp = bp%Tsurf - to
157  do i=1,bp%numx
158  xcond = (bp%x(i) - bp%xmax)/bp%xmax !-1:0
159  tn(i) = to - dtemp * xcond
160  enddo
161 !set the flame temp (there's no flame at this point) to the surf temp
162  tflame = bp%Tsurf
163  rb = 0.0d0
164  endif
165 
166  toa = bp%Tsurf
167  fr = 0.0d0
168 
169  rb = rb / m2cm
170 
171 !------------------------------------------------------------------------
172  RETURN
173  END SUBROUTINE burn_init_1d
174 !***********************************************************************
175 
176 END MODULE init_py
177 
178 
179 
180 
181 
182 
const NT & d
subroutine burn_init_1d(bp, bflag, Pin, To, rhoc, p_coor, rb, Toa, fr, Tn, Tflame)
Definition: init_py.f90:90
Vector_n max(const Array_n_const &v1, const Array_n_const &v2)
Definition: Vector_n.h:354
subroutine polint(bp, xa, ya, n, x, y, dx)
Definition: data_py.f90:182
blockLoc i
Definition: read.cpp:79
subroutine polin2(bp, x1a, x2a, y12a, m, n, x1, x2, y, j, k)
Definition: data_py.f90:106
blockLoc pin(const blockLoc &l) const
Definition: split.cpp:77
Vector_n min(const Array_n_const &v1, const Array_n_const &v2)
Definition: Vector_n.h:346
subroutine burn_get_film_coeff_1d(bp, p_coor, Ts, Teuler, P_in, Qc, Qcprime)
Definition: init_py.f90:30
*********************************************************************Illinois Open Source License ****University of Illinois NCSA **Open Source License University of Illinois All rights reserved ****Developed free of to any person **obtaining a copy of this software and associated documentation to deal with the Software without including without limitation the rights to merge
Definition: roccomf90.h:20