Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
Rocburn_1D_ZN.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_ZN
27 ! to support ROCBURN_2D:
28 !
29 ! INITIALIZE_0D
30 ! INITIALIZE_1D
31 ! GET_FILM_COEFF_1D
32 ! GET_TIME_STEP_1D
33 ! GET_BURNING_RATE_1D
34 !
35 !
36 ! The combustion model used in this module is Zeldovich-Novozhilov
37 ! model implemented by J. Weber, K.C. Tang, and M. Q. Brewster.
38 !
39 ! Creation Date : Sep. 2, 2002
40 !
41 ! Modifications :
42 !
43 ! No. Date Authors Description
44 !
45 ! ----------------------------------------------------------------
46 !
47 !
48 
50 
51  IMPLICIT NONE
52 
53  include 'mpif.h'
54 
55 
56 ! ----------------------------------------------------------------
57 ! local variables
58 
59  CONTAINS
60 
61 !
62 ! ------------------------------------------------------------------------
63 ! INTERNAL PROCEDURES
64 ! ------------------------------------------------------------------------
65 
66  SUBROUTINE check_alloc( ierr)
67  INTEGER, INTENT(IN) :: ierr
68  IF(ierr /= 0) THEN
69  print *, "ROCBRUN_ZN ERROR: unable to allocate memory"
70  CALL mpi_abort( mpi_comm_world, -1)
71  ENDIF
72  END SUBROUTINE check_alloc
73 
74  SUBROUTINE initialize_0d(G_ZN, comm, Indir, nxmax, To_read)
75  TYPE(g_burn_1d), POINTER :: g_zn
76  INTEGER, INTENT(IN) :: comm
77  CHARACTER(*), INTENT(IN) :: indir
78  INTEGER, INTENT(OUT) :: nxmax
79  REAL(DBL), INTENT (OUT) :: to_read
80 
81 ! ---------------------------------------------------------------------------
82 ! local variables
83 !
84 
85 
86  INTEGER :: ierror
87 
88  INTERFACE
89  SUBROUTINE zn_input_0d(G_ZN, Indir)
91  TYPE(g_burn_1d), POINTER :: g_zn
92  CHARACTER(*), INTENT(IN) :: indir
93  END SUBROUTINE zn_input_0d
94 
95  SUBROUTINE zn_gen_grid(G_ZN, gridtype, numx, x, z, zx, zxx)
97  TYPE(g_burn_1d), POINTER :: g_zn
98  INTEGER, INTENT(IN) :: gridtype, numx
99  REAL(DBL), INTENT (OUT) :: x(:), z(:), zx(:), zxx(:)
100  END SUBROUTINE zn_gen_grid
101  END INTERFACE
102 
103  ALLOCATE(g_zn)
104 
105 !
106 ! read Rocburn_ZN 0d data
107 !
108 
109  g_zn%MPI_COMM_ROCBURN = comm
110  CALL mpi_comm_rank(comm, g_zn%rank, ierror)
111 
112  CALL zn_input_0d(g_zn, trim(indir))
113 
114  nxmax = g_zn%nxmax
115  to_read = g_zn%To
116 
117 !
118 ! allocate memory for variables related to grid generation
119 !
120  ALLOCATE(g_zn%x(1:g_zn%nxmax), stat=ierror); CALL check_alloc(ierror)
121  ALLOCATE(g_zn%z(1:g_zn%nxmax), stat=ierror); CALL check_alloc(ierror)
122  ALLOCATE(g_zn%zx(1:g_zn%nxmax), stat=ierror); CALL check_alloc(ierror)
123  ALLOCATE(g_zn%zxx(1:g_zn%nxmax), stat=ierror); CALL check_alloc(ierror)
124 
125 !
126 ! grid generation
127 !
128  CALL zn_gen_grid(g_zn, g_zn%igrid, g_zn%nx, &
129  g_zn%x, g_zn%z, g_zn%zx, g_zn%zxx)
130 
131  RETURN
132 
133  END SUBROUTINE initialize_0d
134 ! ============================================================================
135 
136 
137 
138 
139 
140 
141  SUBROUTINE initialize_1d( G_ZN, bflag, P_mks, To, rhoc_mks, p_coor, rb_mks, Toa, fr, Tn, Tflame)
142 
143 
144  IMPLICIT NONE
145 
146  TYPE(g_burn_1d), POINTER :: g_zn
147  INTEGER, INTENT(INOUT) :: bflag
148  REAL(DBL), INTENT (IN) :: p_mks, to, rhoc_mks, p_coor(3)
149  REAL(DBL), INTENT (OUT) :: rb_mks, toa, fr
150  REAL(DBL), INTENT (OUT) :: tn(:)
151  REAL(DBL), INTENT (OUT) :: tflame
152 
153  INTERFACE
154  SUBROUTINE zn_sswsb(G_ZN, P, qr, To, rhoc, rb, Ts, Tf, fr, Tn)
156  TYPE(g_burn_1d), POINTER :: g_zn
157  REAL(DBL), INTENT(IN) :: p, qr, to, rhoc
158  REAL(DBL), INTENT(OUT) :: rb, ts, tf, fr
159  REAL(DBL), INTENT(OUT) :: tn(:)
160  END SUBROUTINE zn_sswsb
161  END INTERFACE
162 
163 ! ---------------------------------------------------------------------------
164 ! local variables
165  REAL(DBL) :: p, rhoc, rb, ts, tf
166  REAL(DBL) :: qr
167 
168 ! ---------------------------------------------------------------------------
169 
170  IF( (bflag == 0).OR.(g_zn%ign_flag == 1) ) THEN
171 !
172 ! not burning or ignition simulation required
173 ! set condensed phase temperature profile to initial temperature
174 !
175  tn = g_zn%To
176 
177  ELSE
178 !
179 ! burning from onset and no ignition simulation required,
180 ! calculate steady state solution and use as initial condition
181 !
182  p = p_mks *9.869232667e-6 ! Pa to atm
183  rhoc = rhoc_mks*1.0e-3 ! Kg/m^3 to g/cm^3
184  qr = 0.0
185 
186  CALL zn_sswsb(g_zn, p, qr , g_zn%To, rhoc, rb, ts, tf, fr, tn)
187 
188  rb_mks = rb*0.01 ! cm/s to m/s
189 
190  END IF
191 
192  tflame = g_zn%Tf_adiabatic
193  toa = g_zn%To
194 
195  RETURN
196 
197  END SUBROUTINE initialize_1d
198 !! ============================================================================
199 
200 
201 
202 
203 
204 
205  SUBROUTINE get_film_coeff_1d(G_ZN, p_coor, Ts, T_euler, P, qc, qcPrime)
206  TYPE (g_burn_1d), POINTER :: g_zn
207 
208  REAL(DBL), INTENT (IN) :: p_coor(3), ts, t_euler, p
209  REAL(DBL), INTENT (OUT) :: qc, qcprime ! do not change qcPrime
210 !
211 ! place holder for calculating convective heat flux qc for
212 ! Rocburn_1D_ZN
213 !
214 ! currently not available; set qc to 0
215 !
216  qc = 0.0
217  qcprime = 0.0
218 
219  RETURN
220 
221  END SUBROUTINE get_film_coeff_1d
222 ! ============================================================================
223 
224 
225 
226 
227 
228 
229  SUBROUTINE get_time_step_1d(G_ZN, rb, Toa, dt_max)
230  TYPE (g_burn_1d), POINTER :: g_zn
231 
232  REAL(DBL), INTENT (IN) :: rb, toa
233  REAL(DBL), INTENT (OUT) :: dt_max
234 
235 ! ---------------------------------------------------------------------------
236 ! local variables
237 
238  REAL(DBL) :: dt_c
239 ! ---------------------------------------------------------------------------
240 
241  IF( abs(toa - g_zn%To) >= 0.9*g_zn%To) THEN
242  dt_c = 0.1*g_zn%alfac/(rb*rb*1.0e4) ! G_ZN%alfac in cm^2/sec, rb in m/s
243  dt_max= min(g_zn%delt_max, dt_c) ! dt_max in sec
244  ELSE
245  dt_max= g_zn%delt_max ! dt_max in sec
246  END IF
247 
248  RETURN
249 
250  END SUBROUTINE get_time_step_1d
251 ! ============================================================================
252 
253 
254 
255 
256 
257 
258 
259  SUBROUTINE get_burning_rate_1d( G_ZN, delt, P_mks, To, Tn, &
260  qc_mks, qc_old_mks, qr_mks, qr_old_mks, rhoc_mks, &
261  toa, rb_mks, fr, bflag, tnp1, tflame)
262  TYPE (g_burn_1d), POINTER :: g_zn
263 
264  REAL(DBL), INTENT (IN) :: delt, p_mks, to
265  REAL(DBL), INTENT (IN) :: tn(:)
266  REAL(DBL), INTENT (IN) :: qc_mks, qc_old_mks, qr_mks, qr_old_mks
267  REAL(DBL), INTENT (IN) :: rhoc_mks
268  REAL(DBL), INTENT (INOUT) :: toa, rb_mks, fr
269  INTEGER, INTENT (INOUT) :: bflag
270  REAL(DBL), INTENT (OUT) :: tnp1(:)
271  REAL(DBL), INTENT (OUT) :: tflame
272 
273  INTERFACE
274  SUBROUTINE zn_sswsb(G_ZN, P, qr, To, rhoc, rb, Ts, Tf, fr, Tn)
276  TYPE(g_burn_1d), POINTER :: g_zn
277  REAL(DBL), INTENT(IN) :: p, qr, to, rhoc
278  REAL(DBL), INTENT(OUT) :: rb, ts, tf, fr
279  REAL(DBL), INTENT(OUT) :: tn(:)
280  END SUBROUTINE zn_sswsb
281 
282  SUBROUTINE zn_calc_burning_rate(G_ZN, delt, P, qr, To, rhoc, qr_old, fr_old, &
283  toa, rb, ts, fr, tn, tnp1)
285  TYPE(g_burn_1d), POINTER :: g_zn
286  REAL(DBL), INTENT(IN) :: delt, p, qr, to, rhoc
287  REAL(DBL), INTENT(IN) :: qr_old, fr_old, toa
288  REAL(DBL), INTENT(OUT) :: rb, ts, fr
289  REAL(DBL), INTENT(IN) :: tn(:)
290  REAL(DBL), INTENT(OUT) :: tnp1(:)
291  END SUBROUTINE zn_calc_burning_rate
292  END INTERFACE
293 
294 
295 ! ---------------------------------------------------------------------------
296 ! local variables
297  REAL(DBL) :: p, qc, qc_old, qr, qr_old, rhoc, rb
298  REAL(DBL) :: ts, tf
299 ! ---------------------------------------------------------------------------
300 
301 
302  tflame = g_zn%Tf_adiabatic
303 
304  IF(bflag/=0) THEN
305 
306  IF(tn(1) > g_zn%To) THEN
307 !
308 ! propellant burning already, calculate burning rate using ZN_cal_burning_rate
309 !
310  p = p_mks *9.869232667e-6 ! Pa to atm
311  rb = rb_mks * 100.0 ! m/s to cm/s
312  qr = qr_mks * 0.2388459e-4 ! W/m^2 to cal/cm^2/s 1 J = 0.2388459 cal
313  qc = qc_mks * 0.2388459e-4 ! W/m^2 to cal/cm^2/s
314  qr_old = qr_old_mks * 0.2388459e-4 ! W/m^2 to cal/cm^2/s
315  qc_old = qc_old_mks * 0.2388459e-4 ! W/m^2 to cal/cm^2/s
316  rhoc = rhoc_mks*1.0e-3 ! Kg/m^3 to g/cm^3
317  ts = tn(1)
318 
319  CALL zn_calc_burning_rate(g_zn, delt, p, qr, to, rhoc, qr_old, fr, &
320  toa, rb, ts, fr, tn, tnp1)
321 
322 
323  rb_mks = rb*0.01 ! cm/s to m/s
324 
325  ELSE
326 !
327 ! propellant burning for the first time , set initial condition using ZN_ssWSB
328 !
329  p = p_mks *9.869232667e-6 ! Pa to atm
330  rhoc = rhoc_mks*1.0e-3 ! Kg/m^3 to g/cm^3
331  qr = qr_mks * 0.2388459e-4 ! W/m^2 to cal/cm^2/s 1 J = 0.2388459 cal
332 
333  CALL zn_sswsb(g_zn, p, qr, g_zn%To, rhoc, rb, ts, tf, fr, tnp1)
334 
335  rb_mks = rb*0.01 ! cm/s to m/s
336  END IF
337 
338 
339  ELSE
340 !
341 ! propellant not burning yet, check for ignition simulation requirement
342 !
343  IF(g_zn%ign_flag == 1) THEN
344 !
345 ! ignition simulation required
346 !
347 ! place holder for ignition model
348 !
349  WRITE(*,*) 'ROCBURN_ZN: rank=',g_zn%rank
350  WRITE(*,*) ' Error: igntion model not ready'
351  WRITE(*,*) ' job aborted'
352  CALL mpi_abort( mpi_comm_world, -1)
353  stop
354 
355  ELSE
356 !
357 ! ignition simulation not required
358 !
359  bflag = 1
360  RETURN
361 
362  END IF
363 
364  END IF
365 
366  RETURN
367 
368  END SUBROUTINE get_burning_rate_1d
369 
370 !***************************************************************************
371  SUBROUTINE finalize_0d(G_ZN)
372 
373  TYPE (g_burn_1d), POINTER :: g_zn
374 
375  DEALLOCATE( g_zn)
376 
377  END SUBROUTINE finalize_0d
378 
379 
380  END MODULE m_rocburn_1d_zn
381 
382 
383 
384 
385 
386 
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 get_time_step_1d(bp, rb, Toa, dt_max)
Definition: setup_py.f90:30
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)
subroutine get_film_coeff_1d(G_ZN, p_coor, Ts, T_euler, P, qc, qcPrime)
subroutine zn_sswsb(G_ZN, P, qr, To, rhoc, rb, Ts, Tf, fr, Tn)
Definition: ZN_ssWSB.f90:56
subroutine zn_gen_grid(G_ZN, gridtype, numx, x, z, zx, zxx)
Definition: ZN_gen_grid.f90:58
void int int int REAL REAL REAL * z
Definition: write.cpp:76
void int int REAL * x
Definition: read.cpp:74
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 zn_input_0d(G_ZN, Indir)
Definition: ZN_input_0d.f90:49
subroutine finalize_0d(G_APN)
subroutine zn_calc_burning_rate(G_ZN, delt, P, qr, To, rhoc, qr_old, fr_old, Toa, rb, Ts, fr, Tn, Tnp1)
subroutine check_alloc(ierr)
Definition: rocburn_2D.f90:53