Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
Rocburn_1D_APN.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 ! *********************************************************************
24 ! ----------------------------------------------------------------
25 !
26 ! This module provides the following subroutines for ROCBURN_1D_APN
27 ! to support ROCBURN_2D:
28 !
29 ! INITIALIZE_0D
30 ! INITIALIZE_1D
31 ! GET_BURNING_RATE_1D
32 !
33 !
34 ! The combustion model used in this quasi-steady empirical model
35 ! rb=a*P^n
36 !
37 ! Creation Date : Sep. 10, 2002
38 !
39 ! Modifications :
40 !
41 ! No. Date Authors Description
42 !
43 ! ----------------------------------------------------------------
44 !
45 !
46 
48 
49  IMPLICIT NONE
50 
51  include 'mpif.h'
52 
53 
54  CONTAINS
55 
56 !
57 ! ------------------------------------------------------------------------
58 ! INTERNAL PROCEDURES
59 ! ------------------------------------------------------------------------
60 
61  SUBROUTINE check_alloc( ierr)
62  INTEGER, INTENT(IN) :: ierr
63  IF(ierr /= 0) print *, "ROCBRUN_APN ERROR: unable to allocate memory"
64  CALL mpi_abort( mpi_comm_world, -1)
65  END SUBROUTINE check_alloc
66 ! ============================================================================
67 
68 
69 
70 
71 
72 
73  SUBROUTINE initialize_0d( G_APN, comm, Indir, nxmax, To_read)
74  TYPE (g_burn_1d), POINTER :: g_apn
75  INTEGER, INTENT(IN) :: comm
76  CHARACTER(*), INTENT(IN) :: indir
77  INTEGER, INTENT(OUT) :: nxmax
78  REAL(DBL), INTENT (OUT) :: to_read
79 
80 ! ---------------------------------------------------------------------------
81 ! local variables
82 !
83 
84 
85  INTEGER :: ierror
86 
87  INTERFACE
88  SUBROUTINE apn_input_0d(G_APN, Indir)
90  TYPE(g_burn_1d), POINTER :: g_apn
91  CHARACTER(*), INTENT(IN) :: indir
92  END SUBROUTINE apn_input_0d
93 
94  END INTERFACE
95 
96  ALLOCATE(g_apn)
97 
98 !
99 ! read Rocburn_APN 0d data
100 !
101 
102  g_apn%MPI_COMM_ROCBURN = comm
103  CALL mpi_comm_rank(comm, g_apn%rank, ierror)
104 
105  CALL apn_input_0d(g_apn, indir)
106 
107  nxmax = g_apn%nxmax
108  to_read = g_apn%To
109 
110  RETURN
111 
112  END SUBROUTINE initialize_0d
113 ! ============================================================================
114 
115 
116 
117 
118 
119 
120  SUBROUTINE initialize_1d( G_APN, bflag, P_mks, To, rhoc_mks, p_coor, rb_mks, Toa, fr, Tn, Tflame)
121 
122 
123  IMPLICIT NONE
124 
125  TYPE (g_burn_1d), POINTER :: g_apn
126  INTEGER, INTENT(INOUT) :: bflag
127  REAL(DBL), INTENT (IN) :: p_mks, to, rhoc_mks, p_coor(3)
128  REAL(DBL), INTENT (OUT) :: rb_mks, toa, fr
129  REAL(DBL), INTENT (OUT) :: tn(:)
130  REAL(DBL), INTENT (OUT) :: tflame
131 
132 ! ---------------------------------------------------------------------------
133 ! local variables
134 
135  INTEGER :: mat
136 
137 ! ---------------------------------------------------------------------------
138 
139  IF( bflag == 0 ) THEN
140 !
141 ! not burning or ignition simulation required
142 ! set condensed phase temperature profile to initial temperature
143 !
144 
145  rb_mks = 0.
146  tn = g_apn%To
147  tflame = g_apn%To
148 
149  ELSE
150 !
151 ! burning from onset and no ignition simulation required
152 !
153 ! P = P_mks *9.869232667E-6 ! Pa to atm
154 
155 !RAF
156 !RAF Find out which material applies for this face. I need the x coord.
157 !RAF
158 
159  DO mat=1,g_apn%nmat
160  IF (p_coor(1) <= g_apn%xmax(mat)) EXIT
161  END DO
162  mat = min(mat, g_apn%nmat)
163 
164  rb_mks = (g_apn%a_p(mat)*(p_mks*9.869232667e-6)**g_apn%n_p(mat))*0.01 ! cm/s to m/s
165  tflame = g_apn%Tf_adiabatic(mat)
166 
167  tn = 700.0 ! do not acutually need temperature profile
168  ! and do not use in the code
169 
170  END IF
171 
172  RETURN
173 
174  END SUBROUTINE initialize_1d
175 !! ============================================================================
176 
177 
178 
179 
180 
181 
182  SUBROUTINE get_burning_rate_1d( G_APN, delt, P_mks, To, Tn, &
183  qc_mks, qc_old_mks, qr_mks, qr_old_mks, rhoc_mks, &
184  toa, rb_mks, fr, bflag, tnp1, tflame, p_coor)
185  TYPE (g_burn_1d), POINTER :: g_apn
186  REAL(DBL), INTENT (IN) :: delt, p_mks, to
187  REAL(DBL), INTENT (IN) :: tn(:)
188  REAL(DBL), INTENT (IN) :: qc_mks, qc_old_mks, qr_mks, qr_old_mks
189  REAL(DBL), INTENT (IN) :: rhoc_mks
190  REAL(DBL), INTENT (INOUT) :: toa, rb_mks, fr
191  INTEGER, INTENT (INOUT) :: bflag
192  REAL(DBL), INTENT (OUT) :: tnp1(:)
193  REAL(DBL), INTENT (OUT) :: tflame
194  REAL(DBL), INTENT (IN) :: p_coor(3)
195 
196 
197 ! ---------------------------------------------------------------------------
198 ! local variables
199 
200  INTEGER :: mat
201 
202 ! ---------------------------------------------------------------------------
203 
204 
205 
206  IF(bflag == 1) THEN
207 
208 !
209 ! propellant burning already, calculate burning rate using
210 !
211 ! P = P_mks *9.869232667E-6 ! Pa to atm
212 
213 !RAF
214 !RAF Find out which material applies for this face. I need the x coord.
215 !RAF
216 
217  DO mat=1,g_apn%nmat
218  IF (p_coor(1) <= g_apn%xmax(mat)) EXIT
219  END DO
220  mat = min(mat, g_apn%nmat)
221 
222  rb_mks = (g_apn%a_p(mat)*(p_mks*9.869232667e-6)**g_apn%n_p(mat))*0.01 ! cm/s to m/s
223  tflame = g_apn%Tf_adiabatic(mat)
224 
225  ELSE
226 !
227 ! propellant not burning yet
228 !
229 
230  rb_mks = 0.0
231  tflame = g_apn%To
232 
233  END IF
234 
235  RETURN
236 
237  END SUBROUTINE get_burning_rate_1d
238 
239  SUBROUTINE finalize_0d( G_APN)
240  TYPE (g_burn_1d), POINTER :: g_apn
241 
242  DEALLOCATE( g_apn)
243  END SUBROUTINE finalize_0d
244 
245 
246  END MODULE m_rocburn_1d_apn
247 
248 
249 
250 
251 
252 
subroutine get_burning_rate_1d(G_APN, delt, P_mks, To, Tn, qc_mks, qc_old_mks, qr_mks, qr_old_mks, rhoc_mks, Toa, rb_mks, fr, bflag, Tnp1, Tflame, p_coor)
subroutine apn_input_0d(G_APN, Indir)
subroutine initialize_0d(G_APN, comm, Indir, nxmax, To_read)
subroutine initialize_1d(G_APN, bflag, P_mks, To, rhoc_mks, p_coor, rb_mks, Toa, fr, Tn, Tflame)
virtual std::ostream & print(std::ostream &os) const
Vector_n min(const Array_n_const &v1, const Array_n_const &v2)
Definition: Vector_n.h:346
subroutine finalize_0d(G_APN)
subroutine check_alloc(ierr)
Definition: rocburn_2D.f90:53