MFIX  2016-1
write_out0.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
2 ! !
3 ! Subroutine: WRITE_OUT0 !
4 ! Author: P. Nicoletti, M. Syamlal Date: 04-DEC-91 !
5 ! !
6 ! Purpose: Echo user input. !
7 ! !
8 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
9  SUBROUTINE write_out0
10 !
11 !-----------------------------------------------
12 ! M o d u l e s
13 !-----------------------------------------------
14  USE bc
15  USE compar
16  USE constant
17  USE discretelement
18  USE fldvar
19  USE funits
20  USE geometry
21  USE ic
22  USE indices
23  USE is
24  USE leqsol
25  USE machine
26  USE mfix_pic
27  USE mpi_utility
28  USE output
29  USE param
30  USE param1
31  USE particle_filter
32  USE physprop
33  USE run
34  USE rxns
35  USE scalars
36  USE scales
37  USE sendrecv
38  USE toleranc
39  USE ur_facs
40 
41  IMPLICIT NONE
42 !-----------------------------------------------
43 ! G l o b a l P a r a m e t e r s
44 !-----------------------------------------------
45 !-----------------------------------------------
46 ! L o c a l P a r a m e t e r s
47 !-----------------------------------------------
48 !-----------------------------------------------
49 ! L o c a l V a r i a b l e s
50 !-----------------------------------------------
51  INTEGER :: L, M, NN
52 
53  INTEGER :: MMAX_TOT
54  DOUBLE PRECISION :: TMP_DP
55 
56 
57  DOUBLE PRECISION, DIMENSION(6) :: LOC
58 
59 ! Coefficient of restitution (old symbol)
60  CHARACTER(LEN=3), DIMENSION(3) :: LEGEND
61  CHARACTER(LEN=12), DIMENSION(0:9) :: DISCR_NAME
62  CHARACTER(LEN=12), DIMENSION(0:9) :: DISCR_NAME1
63  CHARACTER(LEN=8), DIMENSION(1:4) :: LEQ_METHOD_NAME
64 !-----------------------------------------------
65 
66 !
67  DATA discr_name/'FOUP', 'FOUP', 'Superbee', 'Smart', 'Ultra-Quick', &
68  'QUICKEST', 'Muscl', 'VanLeer', 'Minmod', 'Central'/
69  DATA discr_name1/'FOUP', 'FOUP', 'Fourth Order', 'Smart', 'Ultra-Quick', &
70  'QUICKEST', 'Muscl', 'VanLeer', 'Minmod', 'Central'/
71  DATA leq_method_name/' SOR ', 'BiCGSTAB', ' GMRES ', ' CG '/
72 
73  if (mype.ne.pe_io) return
74 
75  mmax_tot = mmax + des_mmax
76 !
77 ! Write Headers for .OUT file
78 !
80  WRITE (unit_out, 1010) id_node(1:50)
81 !
82 ! Echo input data
83 !
84 ! Run control section
85 !
86  WRITE (unit_out, 1100)
87  WRITE (unit_out, 1110) run_name
88  WRITE (unit_out, 1120) description
89  WRITE (unit_out, 1130) units
90  IF (.NOT. steady_state) THEN
91  WRITE (unit_out, 1135) time, tstop, dt, dt_max, dt_min, dt_fac
92  ELSE
93  WRITE (unit_out, 1136)
94  ENDIF
95  WRITE (unit_out, 1137) run_type
96  IF (run_type == 'NEW') THEN
97  WRITE (unit_out, 1138)
98  ELSE IF (run_type == 'RESTART_1') THEN
99  WRITE (unit_out, 1139)
100  ENDIF
101  IF (momentum_x_eq(0)) THEN
102  WRITE (unit_out, 1140) 'X', ' '
103  ELSE
104  WRITE (unit_out, 1140) 'X', ' NOT '
105  ENDIF
106  IF (momentum_y_eq(0)) THEN
107  WRITE (unit_out, 1140) 'Y', ' '
108  ELSE
109  WRITE (unit_out, 1140) 'Y', ' NOT '
110  ENDIF
111  IF (momentum_z_eq(0)) THEN
112  WRITE (unit_out, 1140) 'Z', ' '
113  ELSE
114  WRITE (unit_out, 1140) 'Z', ' NOT '
115  ENDIF
116  DO m = 1, mmax
117  IF (momentum_x_eq(m)) THEN
118  WRITE (unit_out, 1141) m, 'X', ' '
119  ELSE
120  WRITE (unit_out, 1141) m, 'X', ' NOT '
121  ENDIF
122  IF (momentum_y_eq(m)) THEN
123  WRITE (unit_out, 1141) m, 'Y', ' '
124  ELSE
125  WRITE (unit_out, 1141) m, 'Y', ' NOT '
126  ENDIF
127  IF (momentum_z_eq(m)) THEN
128  WRITE (unit_out, 1141) m, 'Z', ' '
129  ELSE
130  WRITE (unit_out, 1141) m, 'Z', ' NOT '
131  ENDIF
132  END DO
133  IF (granular_energy) THEN
134  WRITE (unit_out, 1142)
135  IF(kt_type /= undefined_c) WRITE (unit_out, 1123) kt_type(1:50)
136  ENDIF
137  IF (energy_eq) THEN
138  WRITE (unit_out, 1143)
139  ELSE
140  WRITE (unit_out, 1144)
141  ENDIF
142  IF (species_eq(0)) THEN
143  WRITE (unit_out, 1145)
144  ELSE
145  WRITE (unit_out, 1146)
146  ENDIF
147  DO m = 1, mmax_tot
148  IF (species_eq(m)) THEN
149  WRITE (unit_out, 1147) m
150  ELSE
151  WRITE (unit_out, 1148) m
152  ENDIF
153  END DO
154  IF (call_usr) THEN
155  WRITE (unit_out, 1149) ' '
156  ELSE
157  WRITE (unit_out, 1149) ' NOT '
158  ENDIF
159  IF (model_b) WRITE (unit_out, 1101)
160  IF (nscalar /= 0)THEN
161  WRITE (unit_out, 1102)nscalar
162  DO l = 1, nscalar
163  WRITE (unit_out, 1103)l, phase4scalar(l)
164  END DO
165  ENDIF
166  IF (k_epsilon) WRITE (unit_out, 1104)
167  IF (simonin) WRITE (unit_out, 1105)
168  IF (ahmadi) WRITE (unit_out, 1106)
169  IF (simonin .OR. ahmadi) WRITE (unit_out, 1107)
170  IF (schaeffer) WRITE (unit_out, 1108)
171  IF (friction) WRITE (unit_out, 1109)
172  IF (added_mass) WRITE (unit_out, 1111)
173 !
174 ! Physical and numerical parameters
175 !
176  WRITE (unit_out, 1150)
177  IF (c_e /= undefined) WRITE (unit_out, 1151) c_e
178  IF (c_f /= undefined) WRITE (unit_out, 1152) c_f
179  IF (phi /= undefined) WRITE (unit_out, 1153) phi
180  IF (phi_w /= undefined) WRITE (unit_out, 1154) phi_w
181  WRITE (unit_out, 1155) l_scale0, mu_gmax
182  IF (v_ex /= zero) WRITE (unit_out, 1156) v_ex
183  WRITE (unit_out, 1157) p_ref, p_scale, gravity
184  WRITE (unit_out, 1158)
185  IF(fpfoi) THEN
186  WRITE (unit_out, 1159) (ur_fac(l),leq_it(l),&
187  leq_method_name(leq_method(l)),&
188  leq_sweep(l), leq_tol(l), leq_pc(l),&
189  discr_name1(discretize(l)),l=1,9)
190  ELSE
191  WRITE (unit_out, 1159) (ur_fac(l),leq_it(l),&
192  leq_method_name(leq_method(l)),&
193  leq_sweep(l), leq_tol(l), leq_pc(l),&
194  discr_name(discretize(l)),l=1,9)
195  ENDIF
196 
197  DO l = 1, dimension_c
198  IF (c(l) /= undefined) WRITE (unit_out, 1190) c_name(l), l, c(l)
199  END DO
200 
201 ! Geometry and Discretization.
202  IF(.NOT.reinitializing) THEN
203  WRITE (unit_out, 1200)
204  WRITE (unit_out, 1201) coordinates
205  IF (cyclic_x_pd) THEN
206  WRITE (unit_out, 1202) 'X', ' with pressure drop'
207  WRITE (unit_out, 1203) 'X', delp_x
208  ELSE IF (cyclic_x) THEN
209  WRITE (unit_out, 1202) 'X'
210  ENDIF
211  IF (cyclic_y_pd) THEN
212  WRITE (unit_out, 1202) 'Y', ' with pressure drop'
213  WRITE (unit_out, 1203) 'Y', delp_y
214  ELSE IF (cyclic_y) THEN
215  WRITE (unit_out, 1202) 'Y'
216  ENDIF
217  IF (cyclic_z_pd) THEN
218  WRITE (unit_out, 1202) 'Z', ' with pressure drop'
219  WRITE (unit_out, 1203) 'Z', delp_z
220  ELSE IF (cyclic_z) THEN
221  WRITE (unit_out, 1202) 'Z'
222  ENDIF
223  WRITE (unit_out, 1210)
224  legend(1) = ' I'
225  legend(2) = ' DX'
226  legend(3) = 'X_E'
227  CALL write_table (legend, dx, xmin, 1, imax2)
228  IF (xmin /= zero) WRITE (unit_out, 1211) xmin
229  WRITE (unit_out, 1212) imax
230  WRITE (unit_out, 1213) xlength
231  WRITE (unit_out, 1220)
232  legend(1) = ' J'
233  legend(2) = ' DY'
234  legend(3) = 'Y_N'
235  CALL write_table (legend, dy, zero, 1, jmax2)
236  WRITE (unit_out, 1221) jmax
237  WRITE (unit_out, 1222) ylength
238  WRITE (unit_out, 1230)
239  legend(1) = ' K'
240  legend(2) = ' DZ'
241  legend(3) = 'Z_T'
242  CALL write_table (legend, dz, zero, 1, kmax2)
243  WRITE (unit_out, 1231) kmax
244  WRITE (unit_out, 1232) zlength
245  ENDIF
246 
247 !
248 ! Gas Section
249 !
250  WRITE (unit_out, 1300)
251  IF (ro_g0 /= undefined) WRITE (unit_out, 1305) ro_g0
252  IF (mu_g0 /= undefined) WRITE (unit_out, 1310) mu_g0
253  IF (species_eq(0)) THEN
254  WRITE (unit_out, 1315) nmax(0)
255  WRITE (unit_out, 1316)
256  DO nn = 1, nmax(0)
257  WRITE (unit_out, 1317) nn, mw_g(nn)
258  END DO
259  ENDIF
260  IF (mw_avg /= undefined) WRITE (unit_out, 1320) mw_avg
261 !
262 ! Particle Section
263 !
264 
265  WRITE (unit_out, 1400)
266  WRITE (unit_out, 1401) mmax_tot
267 
268 
269  1400 FORMAT(//,3x,'5. SOLIDS PHASE',/)
270  1401 FORMAT(7x,'Number of particulate phases (MMAX) = ',i2)
271 
272  IF(mmax_tot > 0) THEN
273 
274  WRITE (unit_out, 1405)
275  DO m = 1, mmax_tot
276  WRITE (unit_out, 1406) m, solids_model(m), d_p0(m), &
277  ro_s0(m), close_packed(m)
278  END DO
279 
280 
281  1405 FORMAT(/7x,'M',4x,'Model',5x,'Diameter',8x,'Density',6x, &
282  'Close_Packed')
283  1406 FORMAT(6x,i2,4x,a3,5x,g12.5,3x,g12.5,9x,l1)
284 
285  1410 FORMAT(/7x,'Number of solids-',i2,' species (NMAX(',i2,')) = ',i3)
286 
287  1411 FORMAT(9x,'Solid',5x,'Molecular')
288  1412 FORMAT(26x,'Density',4x,'Mass Fraction')
289 
290  1415 FORMAT(8x,'Species',5x,'weight',7x,'Alias',5x,'Name')
291  1416 FORMAT(7x,'(RO_Xs0)',6x,'(X_s0)')
292 
293 
294  DO m = 1, mmax_tot
295  IF(.NOT.species_eq(m)) cycle
296  WRITE (unit_out, 1410) m, m, nmax(m)
297 
298 ! Header Line 1
299  WRITE(unit_out,1411,advance='NO')
300  IF(solve_ros(m)) WRITE(unit_out,1412, advance='NO')
301  WRITE(unit_out,*)' '
302 
303 ! Header Line 2
304  WRITE(unit_out,1415,advance='NO')
305  IF(solve_ros(m)) WRITE(unit_out,1416,advance='NO')
306  WRITE(unit_out,*)' '
307 
308 
309  DO nn = 1, nmax(m)
310  WRITE(unit_out, 1420, advance='NO') nn, mw_s(m,nn), &
311  species_alias_s(m,nn)(1:8), species_s(m,nn)(1:8)
312  IF(solve_ros(m)) WRITE(unit_out, 1421, advance='NO') &
313  ro_xs0(m,nn), x_s0(m,nn)
314  WRITE(unit_out,*) ' '
315 
316  1420 FORMAT(10x,i2,5x,g12.5,2(2x,a8))
317  1421 FORMAT(2(2x,g12.5))
318 
319  END DO
320  END DO
321 
322 
323  IF(tfm_solids) THEN
324  WRITE (unit_out, 1430) ep_star
325  DO m = 1,mmax
326  IF(mu_s0(m) /= undefined) &
327  WRITE(unit_out, 1431) m, mu_s0(m)
328  ENDDO
329  ENDIF
330  1430 FORMAT(/7x,'Void fraction at maximum packing (EP_star) = ',g12.5)
331  1431 FORMAT(7x,'Constant solids viscosity (MU_s0(',i2,') = ',g12.5)
332 
333 
334  IF(dem_solids .OR. pic_solids) THEN
335  IF(.NOT.des_continuum_coupled) THEN
336  WRITE(unit_out,"(/7X,'Gas/Solids NOT coupled.')")
337  ELSE
338  WRITE(unit_out,"(/7X,'Gas/Solids Coupling Information:')")
339 
340  IF(des_interp_on) THEN
341  WRITE(unit_out,1440) 'interpolation'
342  ELSE
343  WRITE(unit_out,1440) 'cell averaging'
344  ENDIF
345 
346  IF(des_interp_mean_fields) THEN
347  WRITE(unit_out,1441) 'interpolation'
348  ELSE
349  WRITE(unit_out,1441) 'cell averaging'
350  ENDIF
351  ENDIF
352 
353  1440 FORMAT(10x,'Use ',a,' to calculate gas/particle drag.')
354  1441 FORMAT(10x,'Use ',a,' to calculate dispersed phase scalar fields.')
355 
356  ENDIF
357 
358  IF(dem_solids) THEN
359 
360  1450 FORMAT(/7x,'Use ',a,' collsion model.',2/10x,&
361  'Spring Coefficients:',t37,'Normal',7x,'Tangential')
362 
363  IF(des_coll_model_enum .EQ. lsd) THEN
364  WRITE(unit_out,1450) 'Linear spring-dashpot'
365  WRITE(unit_out,1455) 'Particle-particle', kn, kt
366  WRITE(unit_out,1455) 'Particle-wall', kn_w, kt_w
367 
368  ELSEIF(des_coll_model_enum .EQ. hertzian) THEN
369  WRITE(unit_out,1450) 'Hertzian spring-dashpot'
370 
371  DO m = 1, des_mmax
372  DO nn = m, des_mmax
373  IF(m==nn) THEN
374  WRITE(unit_out,1456)m,nn,hert_kn(m,nn),hert_kt(m,nn)
375  ELSE
376  WRITE(unit_out,1457)nn,hert_kn(m,nn),hert_kt(m,nn)
377  ENDIF
378  ENDDO
379  WRITE(unit_out,1458) hert_kwn(m),hert_kwt(m)
380  ENDDO
381  ENDIF
382 
383  WRITE(unit_out,1451)
384  1451 FORMAT(/10x,'Damping Coefficients:',t37,'Normal',7x,'Tangential')
385 
386  DO m = 1, des_mmax
387  DO nn = m, des_mmax
388  IF(m==nn) THEN
389  WRITE(unit_out,1456)m,nn,des_etan(m,nn),des_etat(m,nn)
390  ELSE
391  WRITE(unit_out,1457)nn,des_etan(m,nn),des_etat(m,nn)
392  ENDIF
393  ENDDO
394  WRITE(unit_out,1458) des_etan_wall(m),des_etat_wall(m)
395  ENDDO
396 
397  1455 FORMAT(12x,a,t35,g12.5,3x,g12.5)
398  1456 FORMAT(12x,'Phase',i2,'-Phase',i2,' = ',t35,g12.5,3x,g12.5)
399  1457 FORMAT(19x,'-Phase',i2,' = ',t35,g12.5,3x,g12.5)
400  1458 FORMAT(19x,'-Wall',3x,' = ',t35,g12.5,3x,g12.5)
401 
402  ENDIF
403 
404  IF(pic_solids) THEN
405  WRITE(unit_out,"(/7X,A)") 'MP-PIC Model Parameters:'
407  WRITE(unit_out,"(10X,A)") &
408  'SNIDER model for solids Stress and integration'
409  ENDIF
410  ENDIF
411 
412  ENDIF
413 
414 !
415 ! Initial Conditions Section
416 !
417  WRITE (unit_out, 1500)
418  DO l = 1, dimension_ic
419  IF (ic_defined(l)) THEN
420  WRITE (unit_out, 1510) l
421  loc(1) = location(ic_i_w(l),xmin,dx) - half*dx(ic_i_w(l))
422  loc(2) = location(ic_i_e(l),xmin,dx) + half*dx(ic_i_e(l))
423  loc(3) = location(ic_j_s(l),zero,dy) - half*dy(ic_j_s(l))
424  loc(4) = location(ic_j_n(l),zero,dy) + half*dy(ic_j_n(l))
425  loc(5) = location(ic_k_b(l),zero,dz) - half*dz(ic_k_b(l))
426  loc(6) = location(ic_k_t(l),zero,dz) + half*dz(ic_k_t(l))
427  WRITE (unit_out, 1520) ic_x_w(l), loc(1), ic_x_e(l), loc(2), ic_y_s&
428  (l), loc(3), ic_y_n(l), loc(4), ic_z_b(l), loc(5), ic_z_t(l), &
429  loc(6)
430  WRITE (unit_out, 1530) ic_i_w(l), ic_i_e(l), ic_j_s(l), ic_j_n(l), &
431  ic_k_b(l), ic_k_t(l)
432  WRITE (unit_out, 1540) ic_ep_g(l)
433  IF (ic_p_g(l) /= undefined) WRITE (unit_out, 1541) ic_p_g(l)
434  WRITE (unit_out, 1542) ic_t_g(l)
435  IF (species_eq(0)) THEN
436  WRITE (unit_out, 1543)
437  DO nn = 1, nmax(0)
438  WRITE (unit_out, 1544) nn, ic_x_g(l,nn)
439  END DO
440  ENDIF
441  IF (ic_gama_rg(l) /= zero) WRITE (unit_out, 1545) ic_gama_rg(l), &
442  ic_t_rg(l)
443 !
444  WRITE (unit_out, 1550) ic_u_g(l), ic_v_g(l), ic_w_g(l)
445  DO m = 1, mmax_tot
446  WRITE (unit_out, 1560) m, ic_rop_s(l,m)
447  WRITE (unit_out, 1561) m, ic_t_s(l,m)
448 
449  END DO
450  DO m = 1, mmax_tot
451  IF (species_eq(m)) THEN
452  WRITE (unit_out, 1563) m
453 
454  DO nn = 1, nmax(m)
455  WRITE (unit_out, 1564) nn, ic_x_s(l,m,nn)
456  END DO
457  ENDIF
458  END DO
459  DO m = 1, mmax_tot
460  IF (ic_gama_rs(l,m) /= zero) WRITE (unit_out, 1565) m, &
461  ic_gama_rs(l,m), ic_t_rs(l,m)
462 !
463  WRITE(unit_out,1570)m,ic_u_s(l,m),m,ic_v_s(l,m),m,ic_w_s(l,m)
464  END DO
465  IF (ic_p_star(l) /= undefined) WRITE (unit_out, 1574) ic_p_star(l)
466  IF(ic_l_scale(l)/=undefined)WRITE(unit_out,1575)ic_l_scale(l)
467  ENDIF
468  END DO
469 
470 ! Boundary Condition Data
471  WRITE (unit_out, 1600)
472  IF (u_g0 /= undefined) WRITE (unit_out, 1601) 'U_g (U_g0) = ', u_g0
473  IF (v_g0 /= undefined) WRITE (unit_out, 1601) 'V_g (V_g0) = ', v_g0
474  IF (w_g0 /= undefined) WRITE (unit_out, 1601) 'W_g (W_g0) = ', w_g0
475  DO m = 1, mmax_tot
476  IF (u_s0(m) /= undefined) WRITE (unit_out, 1602) 'U_s (U_s0[', m, &
477  ']) = ', u_s0(m)
478  IF (v_s0(m) /= undefined) WRITE (unit_out, 1602) 'V_s (V_s0[', m, &
479  ']) = ', v_s0(m)
480  IF (w_s0(m) /= undefined) WRITE (unit_out, 1602) 'W_s (W_s0[', m, &
481  ']) = ', w_s0(m)
482  END DO
483  DO l = 1, dimension_bc
484  IF (bc_defined(l)) THEN
485  WRITE (unit_out, 1610) l
486  WRITE (unit_out, 1611) bc_type(l)
487  SELECT CASE (bc_type_enum(l))
488  CASE (mass_inflow,cg_mi)
489  WRITE (unit_out, 1612)
490  CASE (mass_outflow)
491  WRITE (unit_out, 1613)
492  CASE (p_inflow)
493  WRITE (unit_out, 1614)
494  CASE (p_outflow,cg_po)
495  WRITE (unit_out, 1615)
496  CASE (free_slip_wall,cg_fsw)
497  WRITE (unit_out, 1616)
498  CASE (no_slip_wall,cg_nsw)
499  WRITE (unit_out, 1617)
500  CASE (par_slip_wall,cg_psw)
501  WRITE (unit_out, 1618)
502  CASE (outflow)
503  WRITE (unit_out, 1619)
504  END SELECT
505  IF (.not.is_cg(bc_type_enum(l))) THEN
506  loc(1) = location(bc_i_w(l),xmin,dx) - half*dx(bc_i_w(l))
507  loc(2) = location(bc_i_e(l),xmin,dx) + half*dx(bc_i_e(l))
508  loc(3) = location(bc_j_s(l),zero,dy) - half*dy(bc_j_s(l))
509  loc(4) = location(bc_j_n(l),zero,dy) + half*dy(bc_j_n(l))
510  loc(5) = location(bc_k_b(l),zero,dz) - half*dz(bc_k_b(l))
511  loc(6) = location(bc_k_t(l),zero,dz) + half*dz(bc_k_t(l))
512  WRITE (unit_out, 1620) bc_x_w(l), loc(1), bc_x_e(l), loc(2), bc_y_s&
513  (l), loc(3), bc_y_n(l), loc(4), bc_z_b(l), loc(5), bc_z_t(l), &
514  loc(6)
515  WRITE (unit_out, 1630) bc_i_w(l), bc_i_e(l), bc_j_s(l), bc_j_n(l), &
516  bc_k_b(l), bc_k_t(l)
517  ENDIF
518  WRITE (unit_out,1635) bc_area(l)
519 
520  IF (bc_ep_g(l) /= undefined) WRITE (unit_out, 1640) bc_ep_g(l)
521  IF (bc_p_g(l) /= undefined) WRITE (unit_out, 1641) bc_p_g(l)
522  IF (bc_t_g(l) /= undefined) WRITE (unit_out, 1642) bc_t_g(l)
523  IF (species_eq(0) .AND. bc_x_g(l,1)/=undefined) THEN
524  WRITE (unit_out, 1643)
525  DO nn = 1, nmax(0)
526  WRITE (unit_out, 1644) nn, bc_x_g(l,nn)
527  END DO
528  ENDIF
529  IF (bc_massflow_g(l) /= undefined) WRITE (unit_out, 1648) &
530  bc_massflow_g(l)
531  IF (bc_volflow_g(l) /= undefined) WRITE (unit_out, 1649) &
532  bc_volflow_g(l)
533  IF (bc_u_g(l) /= undefined) WRITE (unit_out, 1650) bc_u_g(l)
534  IF (bc_v_g(l) /= undefined) WRITE (unit_out, 1651) bc_v_g(l)
535  IF (bc_w_g(l) /= undefined) WRITE (unit_out, 1652) bc_w_g(l)
536  IF (bc_dt_0(l) /= undefined) THEN
537  IF (bc_jet_g0(l) /= undefined) THEN
538  WRITE (unit_out, 1655) bc_dt_0(l), bc_jet_g0(l), bc_dt_l(l), &
539  bc_jet_gl(l), bc_dt_h(l), bc_jet_gh(l)
540  ELSE
541  WRITE (unit_out, 1656) bc_dt_0(l)
542  ENDIF
543  ENDIF
544  DO m = 1, mmax_tot
545  IF (bc_rop_s(l,m) /= undefined) THEN
546  WRITE (unit_out, "(' ')")
547  WRITE (unit_out, 1660) m, bc_rop_s(l,m)
548  WRITE (unit_out, 1661) m, bc_t_s(l,m)
549  ENDIF
550  END DO
551  DO m = 1, mmax_tot
552  IF (species_eq(m) .AND. bc_x_s(l,m,1)/=undefined) THEN
553  WRITE (unit_out, "(' ')")
554  WRITE (unit_out, 1663) m
555  DO nn = 1, nmax(m)
556  WRITE (unit_out, 1664) nn, bc_x_s(l,m,nn)
557  END DO
558  ENDIF
559  END DO
560  DO m = 1, mmax_tot
561  WRITE (unit_out, "(' ')")
562  IF (bc_massflow_s(l,m) /= undefined) WRITE (unit_out, 1668) m, &
563  bc_massflow_s(l,m)
564  IF (bc_volflow_s(l,m) /= undefined) WRITE (unit_out, 1669) m, &
565  bc_volflow_s(l,m)
566  IF(bc_u_s(l,m)/=undefined)WRITE(unit_out,1670)m,bc_u_s(l,m)
567  IF(bc_v_s(l,m)/=undefined)WRITE(unit_out,1671)m,bc_v_s(l,m)
568  IF(bc_w_s(l,m)/=undefined)WRITE(unit_out,1672)m,bc_w_s(l,m)
569  END DO
570  IF (bc_type_enum(l) == par_slip_wall) THEN
571  WRITE (unit_out, 1675) bc_hw_g(l), bc_uw_g(l), bc_vw_g(l), &
572  bc_ww_g(l)
573  DO m = 1, mmax_tot
574  WRITE (unit_out, 1676) m, bc_hw_s(l,m), bc_uw_s(l,m), bc_vw_s&
575  (l,m), bc_ww_s(l,m)
576  END DO
577  ENDIF
578  ENDIF
579  END DO
580  WRITE (unit_out, 1700)
581  DO l = 1, dimension_is
582  IF (is_defined(l)) THEN
583  WRITE (unit_out, 1710) l
584  WRITE (unit_out, 1711) is_type(l)
585  IF(is_type(l)=='IMPERMEABLE' .OR. &
586  is_type(l)(3:13)=='IMPERMEABLE') THEN
587  WRITE (unit_out, 1712)
588  ELSE IF (is_type(l)=='SEMIPERMEABLE' .OR. &
589  is_type(l)(3:15)=='SEMIPERMEABLE') THEN
590  WRITE (unit_out, 1713)
591  ENDIF
592  loc(1) = location(is_i_w(l),xmin,dx) - half*dx(is_i_w(l))
593  loc(2) = location(is_i_e(l),xmin,dx) + half*dx(is_i_e(l))
594  loc(3) = location(is_j_s(l),zero,dy) - half*dy(is_j_s(l))
595  loc(4) = location(is_j_n(l),zero,dy) + half*dy(is_j_n(l))
596  loc(5) = location(is_k_b(l),zero,dz) - half*dz(is_k_b(l))
597  loc(6) = location(is_k_t(l),zero,dz) + half*dz(is_k_t(l))
598  WRITE (unit_out, 1720) is_x_w(l), loc(1), is_x_e(l), loc(2), is_y_s&
599  (l), loc(3), is_y_n(l), loc(4), is_z_b(l), loc(5), is_z_t(l), &
600  loc(6)
601  WRITE (unit_out, 1730) is_i_w(l), is_i_e(l), is_j_s(l), is_j_n(l), &
602  is_k_b(l), is_k_t(l)
603  IF (is_pc(l,1) /= undefined) WRITE (unit_out, 1740) is_pc(l,1)
604  IF (is_pc(l,2) /= undefined) WRITE (unit_out, 1741) is_pc(l,2)
605  DO m = 1, mmax_tot
606  WRITE (unit_out, 1742) m, is_vel_s(l,m)
607  END DO
608  ENDIF
609  END DO
610 
611 !
612 ! Print out file descriptions and write intervals.
613 !
614  WRITE (unit_out, 1800)
615  WRITE (unit_out, 1801) &
616  '.OUT','This file (ASCII)',out_dt
617  WRITE (unit_out, 1801) &
618  '.LOG','Log file containing messages (ASCII)',undefined
619  WRITE (unit_out, 1801) &
620  '.RES','Restart file (Binary)', res_dt
621  WRITE (unit_out, 1801) &
622  '.SP1','EP_g (Binary, single precision)',spx_dt(1)
623  WRITE (unit_out, 1801) &
624  '.SP2','P_g, P_star (Binary, single precision)',spx_dt(2)
625  WRITE (unit_out, 1801) &
626  '.SP3','U_g, V_g, W_g (Binary, single precision)',spx_dt(3)
627  WRITE (unit_out, 1801) &
628  '.SP4','U_s, V_s, W_s (Binary, single precision)',spx_dt(4)
629  WRITE (unit_out, 1801) &
630  '.SP5','ROP_s (Binary, single precision)',spx_dt(5)
631  WRITE (unit_out, 1801) &
632  '.SP6','T_g, T_s (Binary, single precision)',spx_dt(6)
633  WRITE (unit_out, 1801) &
634  '.SP7','X_g, X_s (Binary, single precision)',spx_dt(7)
635  WRITE (unit_out, 1801) &
636  '.SP8','Theta_m (Binary, single precision)',spx_dt(8)
637  WRITE (unit_out, 1801) &
638  '.SP9','User Scalar (Binary, single precision)',spx_dt(9)
639  WRITE (unit_out, 1801) &
640  '.SPA','ReactionRates (Binary, single precision)',spx_dt(10)
641  WRITE (unit_out, 1801) &
642  '.SPB','K and Epsilon (Binary, single precision)',spx_dt(11)
643 !
644 ! Print out tolerance values from TOLERANCE.INC
645 !
646  WRITE (unit_out, 1900)
647  WRITE (unit_out, 1901) zero_ep_s
649  WRITE (unit_out, 1905) tol_com
650  IF(nscalar /= 0)WRITE (unit_out, 1906) tol_resid_scalar
651  IF(k_epsilon)WRITE (unit_out, 1907) tol_resid_k_epsilon
652  IF(granular_energy)WRITE (unit_out, 1908) tol_resid_th
653 !
654 ! Echo user defined input data
655 !
656  WRITE (unit_out, '(/,1X,1A1)') char(12)
657  IF (call_usr) CALL usr_write_out0
658 !
659  RETURN
660  1000 FORMAT(17x,'MM MM FFFFFFFFFF IIIIII XX XX',/17x,&
661  'MM MM FFFFFFFFFF IIIIII XX XX',/17x,&
662  'MMMM MMMM FF II XX XX',/17x,&
663  'MMMM MMMM FF II XX XX',/17x,&
664  'MM MM MM FF II XX XX ',/17x,&
665  'MM MM MM FF II XX XX ',/17x,&
666  'MM MM FFFFFFFF II XX ',/17x,&
667  'MM MM FFFFFFFF II XX ',/17x,&
668  'MM MM FF II XX XX ',/17x,&
669  'MM MM FF II XX XX ',/17x,&
670  'MM MM FF II XX XX',/17x,&
671  'MM MM FF II XX XX',/17x,&
672  'MM MM FF IIIIII XX XX',/17x,&
673  'MM MM FF IIIIII XX XX',2/20x,&
674  'Multiphase Flow with Interphase eXchanges'/34x,'Version: ',a,/20x,&
675  'Time: ',i2,':',i2,20x,'Date: ',i2,'-',i2,'-',i4)
676  1010 FORMAT(/7x,'Computer : ',a50,/,1x,79('_'))
677  1100 FORMAT(//,3x,'1. RUN CONTROL',/)
678  1101 FORMAT(/7x,'* Model B momentum equations are solved')
679  1102 FORMAT(/7x,'Number of scalars = ', i4,&
680  /7x,'Scalar No. Carrier Phase (Phase4Scalar)')
681  1103 FORMAT(/7x, i4,' ',i4)
682  1104 FORMAT(/7x,'* K and Epsilon equations are solved.')
683  1111 FORMAT(/7x,'* Virtual mass force is applied to momentum equations.')
684  1105 FORMAT(/7x,'* Simonin model is solved')
685  1106 FORMAT(/7x,'* Ahmadi model is solved')
686  1107 FORMAT(/7x,'** Note: When Simonin or Ahmadi model is solved, K-Epsilon', &
687  ' and granular energy are automatically solved.')
688  1108 FORMAT(/7x,'* Schaeffer frictional model is solved')
689  1109 FORMAT(/7x,'* Savage frictional model is solved')
690  1110 FORMAT(7x,'Run name(RUN_NAME): ',a60)
691  1120 FORMAT(7x,'Brief description of the run (DESCRIPTION) :',/9x,a60)
692  1123 FORMAT(14x,'Kinetic Theory : ',a50)
693  1130 FORMAT(7x,'Units (UNITS) : ',a16)
694  1135 FORMAT(7x,'Start-time (TIME) = ',g12.5,/7x,'Stop_time (TSTOP) = ',g12.5,/7x&
695  ,'Time step (DT) = ',g12.5,/7x,'Max time step (DT_MAX) = ',g12.5,/7x&
696  ,'Min time step (DT_MIN) = ',g12.5,/7x,&
697  'Time step adjustment factor (DT_FAC) = ',g12.5)
698  1136 FORMAT(7x,'* Steady state simulation.')
699  1137 FORMAT(7x,'Type of run (RUN_TYPE) : ',a16)
700  1138 FORMAT(30x,'(Initial conditions from the input (.DAT) file)')
701  1139 FORMAT(30x,'(Initial conditions from the restart (.RES) file)')
702  1140 FORMAT(/7x,'* Gas momentum equation-',a,' is',a,'solved.')
703  1141 FORMAT(/7x,'* Solids-',i2,' momentum equation-',a,' is',a,'solved.')
704  1142 FORMAT(/7x,'* Granular energy equation(s) is solved.')
705  1143 FORMAT(/7x,'* Energy equations are solved.')
706  1144 FORMAT(/7x,'* Energy equations are NOT solved.')
707  1145 FORMAT(/7x,'* Gas Species equations are solved.')
708  1146 FORMAT(/7x,'* Gas Species equations are NOT solved.')
709  1147 FORMAT(/7x,'* Solids-',i2,' Species equations are solved.')
710  1148 FORMAT(/7x,'* Solids-',i2,' Species equations are NOT solved.')
711  1149 FORMAT(/7x,'* User-defined subroutines are',a,'called.')
712 !
713  1150 FORMAT(//,3x,'2. PHYSICAL AND NUMERICAL PARAMETERS',/)
714  1151 FORMAT(7x,'Coefficient of restitution (C_e) = ',g12.5)
715  1152 FORMAT(7x,'Coefficient of friction (C_f) = ',g12.5)
716  1153 FORMAT(7x,'Angle of internal friction (Phi) = ',g12.5)
717  1154 FORMAT(7x,'Angle of wall_particle friction (Phi_w) = ',g12.5)
718  1155 FORMAT(7x,'Default turbulence length scale (L_scale0) = ',g12.5,/7x,&
719  'Maximum turbulent viscosity (MU_gmax) = ',g12.5)
720  1156 FORMAT(7x,'Excluded volume for B-M stress term (V_ex) = ',g12.5)
721  1157 FORMAT(7x,'Reference pressure (P_ref) = ',g12.5,/7x,&
722  'Pressure scale-factor (P_scale) = ',g12.5,/7x,&
723  'Gravitational acceleration (GRAVITY) = ',g12.5)
724  1158 FORMAT(7x,'Under relaxation (UR_FAC) and',&
725  ' Iterations in Leq solver (LEQ_IT):'/,9x,&
726  ' UR_FAC',2x,'LEQ_IT',' LEQ_METHOD',&
727  ' LEQ_SWEEP', ' LEQ_TOL', ' LEQ_PC', ' DISCRETIZE')
728  1159 FORMAT(9x,&
729  'Fluid cont. and P_g = ',f6.3,2x,i4,6x,a8,5x,a4,4x,g11.4,3x,a4,3x,a12/9x,&
730  'Solids cont. and P_s = ',f6.3,2x,i4,6x,a8,5x,a4,4x,g11.4,3x,a4,3x,a12/9x,&
731  'U velocity = ',f6.3,2x,i4,6x,a8,5x,a4,4x,g11.4,3x,a4,3x,a12/9x,&
732  'V velocity = ',f6.3,2x,i4,6x,a8,5x,a4,4x,g11.4,3x,a4,3x,a12/9x,&
733  'W velocity = ',f6.3,2x,i4,6x,a8,5x,a4,4x,g11.4,3x,a4,3x,a12/9x,&
734  'Energy = ',f6.3,2x,i4,6x,a8,5x,a4,4x,g11.4,3x,a4,3x,a12/9x,&
735  'Species = ',f6.3,2x,i4,6x,a8,5x,a4,4x,g11.4,3x,a4,3x,a12/9x,&
736  'Granular Energy = ',f6.3,2x,i4,6x,a8,5x,a4,4x,g11.4,3x,a4,3x,a12/9x,&
737  'User scalar = ',f6.3,2x,i4,6x,a8,5x,a4,4x,g11.4,3x,a4,3x,a12/)
738  1190 FORMAT(7x,1a20,'- C(',i2,') = ',g12.5)
739 !
740  1200 FORMAT(//,3x,'3. GEOMETRY AND DISCRETIZATION',/)
741  1201 FORMAT(7x,'Coordinates: ',1a16/)
742  1202 FORMAT(7x,'Cyclic boundary conditions in ',a,' direction',a)
743  1203 FORMAT(7x,'Pressure drop (DELP_',a,') = ',g12.5)
744  1210 FORMAT(7x,'X-direction cell sizes (DX) and East face locations:')
745  1211 FORMAT(7x,'Minimum value of X, or R (XMIN) =',g12.5)
746  1212 FORMAT(7x,'Number of cells in X, or R, direction (IMAX) = ',i4)
747  1213 FORMAT(7x,'Reactor length in X, or R, direction (XLENGTH) =',g12.5//)
748  1220 FORMAT(7x,'Y-direction cell sizes (DY) and North face locations:')
749  1221 FORMAT(7x,'Number of cells in Y direction (JMAX) = ',i4)
750  1222 FORMAT(7x,'Reactor length in Y direction (YLENGTH) =',g12.5//)
751  1230 FORMAT(7x,'Z-direction cell sizes (DZ) and Top face locations:')
752  1231 FORMAT(7x,'Number of cells in Z, or theta, direction (KMAX) = ',i4)
753  1232 FORMAT(7x,'Reactor length in Z, or theta, direction (ZLENGTH) =',g12.5)
754 !
755  1300 FORMAT(//,3x,'4. GAS PHASE',/)
756  1305 FORMAT(7x,'Gas density (RO_g0) = ',g12.5,&
757  ' (A constant value is used everywhere)')
758  1310 FORMAT(7x,'Viscosity (MU_g0) = ',g12.5,&
759  ' (A constant value is used everywhere)')
760  1315 FORMAT(7x,'Number of gas species (NMAX(0)) = ',i3)
761  1316 FORMAT(7x,'Gas species',5x,'Molecular weight (MW_g)')
762  1317 FORMAT(7x,3x,i3,15x,g12.5)
763  1320 FORMAT(7x,'Average molecular weight (MW_avg) = ',g12.5,&
764  ' (A constant value is used everywhere)')
765 !
766 !
767  1500 FORMAT(//,3x,'6. INITIAL CONDITIONS')
768  1510 FORMAT(/7x,'Initial condition no : ',i4)
769  1520 FORMAT(9x,39x,' Specified ',5x,' Simulated ',/9x,&
770  'X coordinate of west face (IC_X_w) = ',g12.5,5x,g12.5/,9x,&
771  'X coordinate of east face (IC_X_e) = ',g12.5,5x,g12.5/,9x,&
772  'Y coordinate of south face (IC_Y_s) = ',g12.5,5x,g12.5/,9x,&
773  'Y coordinate of north face (IC_Y_n) = ',g12.5,5x,g12.5/,9x,&
774  'Z coordinate of bottom face (IC_Z_b) = ',g12.5,5x,g12.5/,9x,&
775  'Z coordinate of top face (IC_Z_t) = ',g12.5,5x,g12.5)
776  1530 FORMAT(9x,'I index of cell at west (IC_I_w) = ',i4,/,9x,&
777  'I index of cell at east (IC_I_e) = ',i4,/,9x,&
778  'J index of cell at south (IC_J_s) = ',i4,/,9x,&
779  'J index of cell at north (IC_J_n) = ',i4,/,9x,&
780  'K index of cell at bottom (IC_K_b) = ',i4,/,9x,&
781  'K index of cell at top (IC_K_t) = ',i4)
782  1540 FORMAT(9x,'Void fraction (IC_EP_g) = ',g12.5)
783  1541 FORMAT(9x,'Gas pressure (IC_P_g) = ',g12.5)
784  1542 FORMAT(9x,'Gas temperature (IC_T_g) = ',g12.5)
785  1543 FORMAT(9x,'Gas species',5x,'Mass fraction (IC_X_g)')
786  1544 FORMAT(9x,3x,i3,15x,g12.5)
787  1545 FORMAT(9x,'Gas radiation coefficient (IC_GAMA_Rg) = ',g12.5,/,9x,&
788  'Gas radiation temperature (IC_T_Rg) = ',g12.5)
789  1550 FORMAT(9x,'X-component of gas velocity (IC_U_g) = ',g12.5,/9x,&
790  'Y-component of gas velocity (IC_V_g) = ',g12.5,/9x,&
791  'Z-component of gas velocity (IC_W_g) = ',g12.5)
792  1560 FORMAT(9x,'Solids phase-',i2,' Density x Volume fr. (IC_ROP_s) = ',g12.5)
793  1561 FORMAT(9x,'Solids phase-',i2,' temperature (IC_T_s) = ',g12.5)
794  1563 FORMAT(9x,'Solids-',i2,' species',5x,'Mass fraction (IC_X_s)')
795  1564 FORMAT(9x,3x,i3,20x,g12.5)
796  1565 FORMAT(9x,'Solids phase-',i2,' radiation coefficient (IC_GAMA_Rs)',' =',&
797  g12.5,/9x,'Solids phase-',i2,' radiation temperature (IC_T_Rs) =',&
798  g12.5)
799  1570 FORMAT(9x,'X-component of solids phase-',i2,' velocity (IC_U_s) =',g12.5,&
800  /9x,'Y-component of solids phase-',i2,' velocity (IC_V_s) =',g12.5,/9x&
801  ,'Z-component of solids phase-',i2,' velocity (IC_W_s) =',g12.5)
802  1574 FORMAT(9x,'Solids pressure (IC_P_star) = ',g12.5)
803  1575 FORMAT(9x,'Turbulence length scale (IC_L_scale) = ',g12.5)
804 !
805  1600 FORMAT(//,3x,'7. BOUNDARY CONDITIONS')
806  1601 FORMAT(/7x,'Average value of ',a,g12.5)
807  1602 FORMAT(/7x,'Average value of ',a,i2,a,g12.5)
808  1610 FORMAT(/7x,'Boundary condition no : ',i4)
809  1611 FORMAT(9x,'Type of boundary condition : ',a16)
810  1612 FORMAT(11x,'(Inlet with specified gas and solids mass flux)')
811  1613 FORMAT(11x,'(Outlet with specified gas and solids mass flux)')
812  1614 FORMAT(11x,'(Inlet with specified gas pressure)')
813  1615 FORMAT(11x,'(Outlet with specified gas pressure)')
814  1616 FORMAT(11x,'(Gradients of parallel velocity components are zero)')
815  1617 FORMAT(11x,'(Velocity is zero at wall)')
816  1618 FORMAT(11x,'(Partial slip condition at wall)')
817  1619 FORMAT(11x,'(Outflow condition)')
818  1620 FORMAT(9x,39x,' Specified ',5x,' Simulated ',/9x,&
819  'X coordinate of west face (BC_X_w) = ',g12.5,5x,g12.5/,9x,&
820  'X coordinate of east face (BC_X_e) = ',g12.5,5x,g12.5/,9x,&
821  'Y coordinate of south face (BC_Y_s) = ',g12.5,5x,g12.5/,9x,&
822  'Y coordinate of north face (BC_Y_n) = ',g12.5,5x,g12.5/,9x,&
823  'Z coordinate of bottom face (BC_Z_b) = ',g12.5,5x,g12.5/,9x,&
824  'Z coordinate of top face (BC_Z_t) = ',g12.5,5x,g12.5)
825  1630 FORMAT(9x,'I index of cell at west (BC_I_w) = ',i4,/,9x,&
826  'I index of cell at east (BC_I_e) = ',i4,/,9x,&
827  'J index of cell at south (BC_J_s) = ',i4,/,9x,&
828  'J index of cell at north (BC_J_n) = ',i4,/,9x,&
829  'K index of cell at bottom (BC_K_b) = ',i4,/,9x,&
830  'K index of cell at top (BC_K_t) = ',i4)
831  1635 FORMAT(9x,'Boundary area = ',g12.5)
832  1640 FORMAT(9x,'Void fraction (BC_EP_g) = ',g12.5)
833  1641 FORMAT(9x,'Gas pressure (BC_P_g) = ',g12.5)
834  1642 FORMAT(9x,'Gas temperature (BC_T_g) = ',g12.5)
835  1643 FORMAT(9x,'Gas species',5x,'Mass fraction (BC_X_g)')
836  1644 FORMAT(9x,3x,i3,15x,g12.5)
837  1648 FORMAT(9x,'Gas mass flow rate (BC_MASSFLOW_g) = ',g12.5)
838  1649 FORMAT(9x,'Gas volumetric flow rate (BC_VOLFLOW_g) = ',g12.5)
839  1650 FORMAT(9x,'X-component of gas velocity (BC_U_g) = ',g12.5)
840  1651 FORMAT(9x,'Y-component of gas velocity (BC_V_g) = ',g12.5)
841  1652 FORMAT(9x,'Z-component of gas velocity (BC_W_g) = ',g12.5)
842  1655 FORMAT(9x,'Initial interval when jet vel= BC_Jet_g0 (BC_DT_0) = ',g12.5,/9x,&
843  'Initial jet velocity (BC_Jet_g0) = ',g12.5,/9x,&
844  'Interval when jet vel= BC_Jet_gl (BC_DT_l) = ',g12.5,/9x,&
845  'Low value of jet velocity (BC_Jet_gl) = ',g12.5,/9x,&
846  'Interval when jet vel = BC_Jet_gh (BC_DT_h) = ',g12.5,/9x,&
847  'High value of jet velocity (BC_Jet_gh) = ',g12.5)
848  1656 FORMAT(9x,'Interval for averaging outflow rates= (BC_DT_0) = ',g12.5)
849  1660 FORMAT(9x,'Solids phase-',i2,' Density x Volume fr. (BC_ROP_s) = ',g12.5)
850  1661 FORMAT(9x,'Solids phase-',i2,' temperature (BC_T_s) = ',g12.5)
851 
852  1663 FORMAT(9x,'Solids-',i2,' species',5x,'Mass fraction (BC_X_s)')
853  1664 FORMAT(9x,3x,i3,20x,g12.5)
854  1668 FORMAT(9x,'Solids phase-',i2,' mass flow rate (BC_MASSFLOW_s) =',g12.5)
855  1669 FORMAT(9x,'Solids phase-',i2,' volumetric flow rate (BC_VOLFLOW_s) =',&
856  g12.5)
857  1670 FORMAT(9x,'X-component of solids phase-',i2,' velocity (BC_U_s) =',g12.5)
858  1671 FORMAT(9x,'Y-component of solids phase-',i2,' velocity (BC_V_s) =',g12.5)
859  1672 FORMAT(9x,'Z-component of solids phase-',i2,' velocity (BC_W_s) =',g12.5)
860  1675 FORMAT(9x,'Partial slip coefficient (BC_hw_g) = ',g12.5,/,9x,&
861  'Slip velociity U at wall (BC_Uw_g) = ',g12.5,/,9x,&
862  'Slip velociity V at wall (BC_Vw_g) = ',g12.5,/,9x,&
863  'Slip velociity W at wall (BC_Ww_g) = ',g12.5)
864  1676 FORMAT(9x,'Solids phase: ',i2,/,11x,&
865  'Partial slip coefficient (BC_hw_s) = ',g12.5,/,11x,&
866  'Slip velociity U at wall (BC_Uw_s) = ',g12.5,/,11x,&
867  'Slip velociity V at wall (BC_Vw_s) = ',g12.5,/,11x,&
868  'Slip velociity W at wall (BC_Ww_s) = ',g12.5)
869 !
870  1700 FORMAT(//,3x,'8. INTERNAL SURFACES')
871  1710 FORMAT(/7x,'Internal surface no : ',i4)
872  1711 FORMAT(9x,'Type of internal surface : ',a16)
873  1712 FORMAT(11x,'(No gas or solids flow through the surface)')
874  1713 FORMAT(11x,'(Only gas flows through the surface)')
875  1720 FORMAT(9x,39x,' Specified ',5x,' Simulated ',/9x,&
876  'X coordinate of west face (IS_X_w) = ',g12.5,5x,g12.5/,9x,&
877  'X coordinate of east face (IS_X_e) = ',g12.5,5x,g12.5/,9x,&
878  'Y coordinate of south face (IS_Y_s) = ',g12.5,5x,g12.5/,9x,&
879  'Y coordinate of north face (IS_Y_n) = ',g12.5,5x,g12.5/,9x,&
880  'Z coordinate of bottom face (IS_Z_b) = ',g12.5,5x,g12.5/,9x,&
881  'Z coordinate of top face (IS_Z_t) = ',g12.5,5x,g12.5)
882  1730 FORMAT(9x,'I index of cell at west (IS_I_w) = ',i4,/,9x,&
883  'I index of cell at east (IS_I_e) = ',i4,/,9x,&
884  'J index of cell at south (IS_J_s) = ',i4,/,9x,&
885  'J index of cell at north (IS_J_n) = ',i4,/,9x,&
886  'K index of cell at bottom (IS_K_b) = ',i4,/,9x,&
887  'K index of cell at top (IS_K_t) = ',i4)
888  1740 FORMAT(9x,'Permeability (IS_PC1) = ',g12.5)
889  1741 FORMAT(9x,'Inertial resistance factor (IS_PC2) = ',g12.5)
890  1742 FORMAT(9x,'Solids phase-',i2,' Velocity (IS_VEL_s) = ',g12.5)
891 !
892  1800 FORMAT(//,3x,'9. OUTPUT DATA FILES:',/7x,'Extension',t18,&
893  'Description',t59,'Interval for writing')
894  1801 FORMAT(7x,a4,t18,a,t61,g12.5)
895 !
896  1900 FORMAT(//,3x,'10. TOLERANCES',/7x,&
897  'The following values are specified in the file TOLERANCE.INC.')
898  1901 FORMAT(/7x,'Minimum value of EP_s tracked (ZERO_EP_s) = ',g12.5)
899  1904 FORMAT(7x,'Maximum average residual (TOL_RESID) = ',g12.5,/7x,&
900  'Maximum average residual (TOL_RESID_T) = ',g12.5,/7x,&
901  'Maximum average residual (TOL_RESID_X) = ',g12.5,/7x,&
902  'Minimum residual at divergence (TOL_DIVERGE) = ',g12.5)
903  1905 FORMAT(7x,'Tolerance for species and energy balances (TOL_COM) = ',g12.5)
904  1906 FORMAT(7x,'Tolerance for scalar mass balances (TOL_RESID_Scalar) = ',g12.5)
905  1907 FORMAT(7x,'Tolerance for K-Epsilon balances (TOL_RESID_K_Epsilon) = ',g12.5)
906  1908 FORMAT(7x,'Tolerance for Granular Temp. balances (TOL_RESID_Th) = ',g12.5)
907 !
908 
909  CONTAINS
910 
911 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
912 ! C
913 ! Module name: LOCATION(L2, XMIN, DX) C
914 ! Purpose: Find the cell center location in X, Y, or Z direction for C
915 ! the given index L2. C
916 ! C
917 ! Author: M. Syamlal Date: 01-SEP-92 C
918 ! Reviewer: M. Syamlal Date: 11-DEC-92 C
919 ! C
920 ! Literature/Document References: C
921 ! C
922 ! Variables referenced: None C
923 ! Variables modified: None C
924 ! C
925 ! Local variables: L C
926 ! C
927 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
928 !
929  DOUBLE PRECISION FUNCTION location (L2, XMIN, DX)
930 !...Translated by Pacific-Sierra Research VAST-90 2.06G5 12:17:31 12/09/98
931 !...Switches: -xf
932 !
933 !-----------------------------------------------
934 ! M o d u l e s
935 !-----------------------------------------------
936  USE param
937  USE param1
938  IMPLICIT NONE
939 !-----------------------------------------------
940 ! D u m m y A r g u m e n t s
941 !-----------------------------------------------
942 !
943 ! Index for which the location is required
944  INTEGER L2
945 !
946 ! Starting location of the coordinate
947  DOUBLE PRECISION XMIN
948 !
949 ! Cell sizes (DX, DY, or DZ)
950 !//EFD Nov/11 avoid using dx(*)
951 !// DOUBLE PRECISION DX(*)
952  DOUBLE PRECISION DX(0:l2)
953 !
954 ! Local variables
955 !
956 ! Index
957  INTEGER L
958 !-----------------------------------------------
959 !
960  location = xmin - half*dx(1)
961  l = 2
962  IF (l2 - 1 > 0) THEN
963 
964 !//EFD since indexing of dx starts from 0
965 !// using DX(1:(L2-1)) instead of DX(:,L2)
966 !// LOCATION = LOCATION + SUM(HALF*(DX(:L2-1)+DX(2:L2)))
967 
968  location = location + sum(half*(dx(1:(l2-1))+dx(2:l2)))
969  l = l2 + 1
970 
971  ENDIF
972  RETURN
973  END FUNCTION location
974 
975  END SUBROUTINE write_out0
976 
977  SUBROUTINE write_flags
978  USE param
979  USE param1
980  USE funits
981  USE geometry
982  USE indices
983  USE compar !//d
984  USE mpi_utility !//d
985  USE sendrecv !//d
986  USE functions
987  IMPLICIT NONE
988  integer ijk
989 !
990  character(LEN=3), allocatable :: array1(:) !//d
991  character(LEN=4), dimension(:), allocatable :: array2, array3
992 
993  if (mype .eq. pe_io) then
994  allocate (array1(ijkmax3))
995  allocate (array2(dimension_3))
996  allocate (array3(ijkmax3))
997  else
998  allocate (array1(1))
999  allocate (array2(dimension_3))
1000  allocate (array3(1))
1001  end if
1002 
1003 !write(*,*) 'ijkmax3', ijkmax3, dimension_3
1004 
1005 !//SP Filling the processor ghost layer with the correct values
1006 
1007  call gather (icbc_flag,array1,pe_io)
1008  call scatter (icbc_flag,array1,pe_io)
1009 
1010 !
1011 ! Superimpose internal surface flags on Initial and boundary condition flags
1012 !
1013  DO ijk = ijkstart3, ijkend3
1014  array2(ijk) = ' '
1015  array2(ijk)(1:3) = icbc_flag(ijk)(1:3)
1016  IF (ip_at_e(ijk)) THEN
1017  array2(ijk)(4:4) = 'E'
1018  ELSE IF (sip_at_e(ijk)) THEN
1019  array2(ijk)(4:4) = 'e'
1020  ENDIF
1021 !
1022  IF (ip_at_n(ijk)) THEN
1023  array2(ijk)(4:4) = 'N'
1024  ELSE IF (sip_at_n(ijk)) THEN
1025  array2(ijk)(4:4) = 'n'
1026  ENDIF
1027 !
1028  IF (ip_at_t(ijk)) THEN
1029  array2(ijk)(4:4) = 'T'
1030  ELSE IF (sip_at_t(ijk)) THEN
1031  array2(ijk)(4:4) = 't'
1032  ENDIF
1033  ENDDO
1034  call gather (array2,array3,pe_io)
1035 
1036  if(mype.eq.pe_io) then
1037  WRITE (unit_out, 2000)
1038  CALL out_array_c (array3, 'BC/IC condition flags')
1039  WRITE (unit_out, *)
1040  ENDIF
1041 
1042 
1043  deallocate (array1)
1044  deallocate (array2)
1045  deallocate (array3)
1046 !
1047  2000 FORMAT(//,3x,'11. INITIAL AND BOUNDARY CONDITION FLAGS',/7x,&
1048  'The initial and boundary conditions specified are shown in',/7x,&
1049  'the following map. Each computational cell is represented',/7x,&
1050  'by a string of three characters. The first character',/7x,&
1051  'represents the type of cell, and the last two characters',/7x,&
1052  'give a number that identifies a boundary or initial condi-',/7x,&
1053  'tion. For example, .02 indicates a cell where Initial',/7x,&
1054  'Condition No. 2 will be specified. Only the last two digits'/7x,&
1055  'are written. Hence, for example, Condition No. 12, 112, 212'/7x,&
1056  'etc. will be represented only as 12.',/7x,&
1057  ' First Character Description'/7x,&
1058  ' . Initial condition'/7x,&
1059  ' W No slip wall'/7x,&
1060  ' S Free-slip wall'/7x,&
1061  ' s Partial-slip wall'/7x,&
1062  ' c Cyclic boundary'/7x,&
1063  ' C Cyclic boundary with pressure drop'/7x,&
1064  ' I Specified mass-flux inflow cell'/7x,&
1065  ' O Outflow cell'/7x,&
1066  ' p Specified pressure inflow cell'/7x,&
1067  ' P Specified pressure outflow cell'/7x,&
1068  ' '/7x,&
1069  'Internal surfaces at East, North or Top of each cell is',/7x,&
1070  'is represented by the following letters to the right of the',/7x,&
1071  'three-character string:',/7x,&
1072  ' Side Impermeable Semipermeable',/7x,&
1073  ' East E e ',/7x,&
1074  ' North N n ',/7x,&
1075  ' Top T t ',/7x,&
1076  'For cells with internal surfaces on more than one side',/7x,&
1077  'the characters will be over-written in the above order',/1x,a1)
1078  RETURN
1079  END SUBROUTINE write_flags
1080 
1081 
double precision, dimension(dimension_bc, dim_m) bc_ww_s
Definition: bc_mod.f:328
double precision l_scale0
Definition: constant_mod.f:177
integer, dimension(dimension_bc) bc_k_b
Definition: bc_mod.f:70
double precision, dimension(dimension_ic) ic_p_star
Definition: ic_mod.f:68
double precision out_dt
Definition: output_mod.f:23
character(len=16) coordinates
Definition: geometry_mod.f:17
integer, parameter dimension_c
Definition: param_mod.f:57
double precision, dimension(dimension_bc) bc_y_n
Definition: bc_mod.f:42
logical, dimension(0:dim_m) momentum_y_eq
Definition: run_mod.f:77
double precision c_e
Definition: constant_mod.f:105
integer, parameter dimension_ic
Definition: param_mod.f:59
double precision, dimension(dimension_ic) ic_l_scale
Definition: ic_mod.f:71
double precision, dimension(dim_eqs) ur_fac
Definition: ur_facs_mod.f:6
logical dem_solids
Definition: run_mod.f:257
logical steady_state
Definition: run_mod.f:57
character(len=60) description
Definition: run_mod.f:27
integer imax2
Definition: geometry_mod.f:61
double precision, dimension(dimension_bc) bc_dt_0
Definition: bc_mod.f:221
double precision, dimension(dimension_bc) bc_volflow_g
Definition: bc_mod.f:195
character(len=18), dimension(dim_m, dim_n_s) species_s
Definition: rxns_mod.f:51
double precision, dimension(dimension_bc) bc_uw_g
Definition: bc_mod.f:313
double precision, dimension(dimension_ic, dim_m) ic_rop_s
Definition: ic_mod.f:74
double precision, dimension(dimension_bc, dim_m) bc_uw_s
Definition: bc_mod.f:322
double precision, dimension(dim_m) d_p0
Definition: physprop_mod.f:25
character(len=16), dimension(dimension_is) is_type
Definition: is_mod.f:70
integer ijkend3
Definition: compar_mod.f:80
integer, parameter dimension_is
Definition: param_mod.f:63
double precision, dimension(dimension_bc) bc_t_g
Definition: bc_mod.f:97
double precision, dimension(dimension_ic) ic_t_g
Definition: ic_mod.f:80
integer, dimension(dimension_ic) ic_j_s
Definition: ic_mod.f:47
double precision dt_fac
Definition: run_mod.f:226
subroutine write_table(LEGEND, ARRAY, DIST_MIN, LSTART, LEND)
Definition: write_table.f:24
logical mppic_solid_stress_snider
Definition: mfix_pic_mod.f:20
integer dimension_3
Definition: param_mod.f:11
double precision function location(L2, XMIN, DX)
Definition: write_out0.f:930
double precision, dimension(dimension_bc) bc_dt_l
Definition: bc_mod.f:236
integer, parameter unit_out
Definition: funits_mod.f:18
double precision, dimension(dimension_is) is_x_e
Definition: is_mod.f:25
double precision phi
Definition: constant_mod.f:117
integer id_month
Definition: machine_mod.f:22
integer, dimension(dimension_bc) bc_i_w
Definition: bc_mod.f:54
logical added_mass
Definition: run_mod.f:91
integer, dimension(dimension_is) is_i_w
Definition: is_mod.f:45
double precision delp_z
Definition: bc_mod.f:278
logical, dimension(0:dim_m) momentum_x_eq
Definition: run_mod.f:74
integer, dimension(dimension_bc) bc_j_n
Definition: bc_mod.f:66
Definition: rxns_mod.f:1
character(len=60) run_name
Definition: run_mod.f:24
logical, dimension(0:dim_m) species_eq
Definition: run_mod.f:115
double precision, dimension(dimension_bc, dim_m) bc_w_s
Definition: bc_mod.f:129
double precision p_scale
Definition: scales_mod.f:13
integer, dimension(dimension_ic) ic_j_n
Definition: ic_mod.f:50
logical friction
Definition: run_mod.f:149
double precision, dimension(dimension_bc, dim_m, dim_n_s) bc_x_s
Definition: bc_mod.f:254
double precision delp_x
Definition: bc_mod.f:272
subroutine out_array_c(ARRAY, MESSAGE)
Definition: out_array_c.f:24
double precision mu_g0
Definition: physprop_mod.f:62
integer id_day
Definition: machine_mod.f:23
double precision tol_resid_t
Definition: toleranc_mod.f:57
double precision tol_resid_scalar
Definition: toleranc_mod.f:63
logical, dimension(0:dim_m) momentum_z_eq
Definition: run_mod.f:80
logical, dimension(dim_m) solve_ros
Definition: run_mod.f:250
double precision, dimension(0:dim_j) dy
Definition: geometry_mod.f:70
logical, dimension(dimension_ic) ic_defined
Definition: ic_mod.f:107
double precision, dimension(dimension_bc) bc_jet_g0
Definition: bc_mod.f:227
character(len=64) id_node
Definition: machine_mod.f:19
double precision dt
Definition: run_mod.f:51
double precision, dimension(dimension_bc) bc_jet_gh
Definition: bc_mod.f:233
double precision v_ex
Definition: constant_mod.f:135
integer, parameter dimension_bc
Definition: param_mod.f:61
double precision, dimension(dimension_ic) ic_z_b
Definition: ic_mod.f:35
logical cyclic_z
Definition: geometry_mod.f:153
integer, dimension(dimension_bc) bc_type_enum
Definition: bc_mod.f:146
double precision, dimension(dim_m, dim_n_s) x_s0
Definition: physprop_mod.f:32
double precision, dimension(dimension_bc) bc_x_e
Definition: bc_mod.f:34
double precision, dimension(dimension_ic) ic_x_w
Definition: ic_mod.f:23
character(len=3), dimension(dim_m) solids_model
Definition: run_mod.f:253
character(len=4), dimension(dim_eqs) leq_sweep
Definition: leqsol_mod.f:20
double precision mu_gmax
Definition: constant_mod.f:180
double precision, parameter undefined
Definition: param1_mod.f:18
double precision, dimension(dim_m, dim_n_s) ro_xs0
Definition: physprop_mod.f:35
double precision, dimension(dimension_ic, dim_m) ic_gama_rs
Definition: ic_mod.f:122
double precision, dimension(0:dim_k) dz
Definition: geometry_mod.f:72
double precision tol_resid_k_epsilon
Definition: toleranc_mod.f:66
character(len=3), dimension(:), pointer icbc_flag
Definition: geometry_mod.f:111
logical, dimension(dim_m) close_packed
Definition: physprop_mod.f:56
Definition: is_mod.f:11
double precision, dimension(dim_n_g) mw_g
Definition: physprop_mod.f:124
double precision, dimension(:), allocatable a
Definition: scalars_mod.f:29
logical des_interp_mean_fields
double precision, dimension(dimension_bc) bc_v_g
Definition: bc_mod.f:117
double precision, parameter tol_com
Definition: toleranc_mod.f:28
double precision, dimension(n_spx) spx_dt
Definition: output_mod.f:21
logical cyclic_z_pd
Definition: geometry_mod.f:159
double precision res_dt
Definition: output_mod.f:15
integer imax
Definition: geometry_mod.f:47
double precision c_f
Definition: constant_mod.f:114
integer ijkmax3
Definition: geometry_mod.f:82
double precision, dimension(dimension_bc) bc_y_s
Definition: bc_mod.f:38
double precision, dimension(dimension_ic) ic_u_g
Definition: ic_mod.f:89
double precision phi_w
Definition: constant_mod.f:120
double precision, dimension(dimension_is) is_x_w
Definition: is_mod.f:21
integer pe_io
Definition: compar_mod.f:30
Definition: ic_mod.f:9
double precision, dimension(dimension_bc, dim_m) bc_volflow_s
Definition: bc_mod.f:198
double precision, dimension(dimension_ic) ic_z_t
Definition: ic_mod.f:38
double precision dt_max
Definition: run_mod.f:220
integer id_year
Definition: machine_mod.f:24
subroutine usr_write_out0
double precision, dimension(dimension_ic, dim_m) ic_w_s
Definition: ic_mod.f:104
integer, dimension(dimension_ic) ic_i_w
Definition: ic_mod.f:41
integer, dimension(dimension_bc) bc_k_t
Definition: bc_mod.f:74
integer mmax
Definition: physprop_mod.f:19
integer, dimension(dim_eqs) leq_it
Definition: leqsol_mod.f:11
logical cyclic_y_pd
Definition: geometry_mod.f:157
double precision, dimension(dimension_bc, dim_m) bc_t_s
Definition: bc_mod.f:101
double precision ro_g0
Definition: physprop_mod.f:59
integer id_minute
Definition: machine_mod.f:26
integer jmax2
Definition: geometry_mod.f:63
integer, dimension(dimension_ic) ic_i_e
Definition: ic_mod.f:44
logical simonin
Definition: run_mod.f:143
double precision, dimension(dimension_ic) ic_v_g
Definition: ic_mod.f:95
integer, dimension(dimension_ic) ic_k_b
Definition: ic_mod.f:53
integer, dimension(dimension_bc) bc_j_s
Definition: bc_mod.f:62
integer, dimension(dimension_is) is_k_b
Definition: is_mod.f:61
double precision w_g0
Definition: bc_mod.f:292
character(len=20), dimension(dimension_c) c_name
Definition: constant_mod.f:170
logical cyclic_y
Definition: geometry_mod.f:151
double precision tstop
Definition: run_mod.f:48
double precision, dimension(dimension_is, dim_m) is_vel_s
Definition: is_mod.f:88
character(len=16) run_type
Definition: run_mod.f:33
double precision tol_resid_th
Definition: toleranc_mod.f:69
double precision, parameter zero_ep_s
Definition: toleranc_mod.f:15
double precision, dimension(dim_m) v_s0
Definition: bc_mod.f:298
double precision, dimension(dimension_is) is_z_b
Definition: is_mod.f:37
double precision, dimension(dimension_ic) ic_y_n
Definition: ic_mod.f:32
double precision, dimension(dimension_bc, dim_m) bc_hw_s
Definition: bc_mod.f:310
double precision, dimension(dimension_bc) bc_hw_g
Definition: bc_mod.f:307
logical schaeffer
Definition: run_mod.f:157
logical, dimension(dimension_bc) bc_defined
Definition: bc_mod.f:207
double precision, dimension(dimension_is, 2) is_pc
Definition: is_mod.f:85
double precision, dimension(dimension_ic, dim_m, dim_n_s) ic_x_s
Definition: ic_mod.f:113
double precision, dimension(dimension_bc) bc_p_g
Definition: bc_mod.f:80
double precision, dimension(dimension_ic) ic_w_g
Definition: ic_mod.f:101
logical tfm_solids
Definition: run_mod.f:256
double precision, dimension(0:dim_i) dx
Definition: geometry_mod.f:68
double precision, dimension(dimension_ic) ic_gama_rg
Definition: ic_mod.f:116
double precision tol_diverge
Definition: toleranc_mod.f:72
integer kmax2
Definition: geometry_mod.f:65
double precision, dimension(dim_eqs) leq_tol
Definition: leqsol_mod.f:23
double precision xlength
Definition: geometry_mod.f:33
double precision, parameter half
Definition: param1_mod.f:28
Definition: run_mod.f:13
double precision, dimension(dimension_bc) bc_dt_h
Definition: bc_mod.f:230
logical cyclic_x
Definition: geometry_mod.f:149
integer, dimension(dimension_ic) ic_k_t
Definition: ic_mod.f:56
character(len=16), dimension(dimension_bc) bc_type
Definition: bc_mod.f:145
Definition: param_mod.f:2
integer kmax
Definition: geometry_mod.f:51
logical, dimension(dimension_is) is_defined
Definition: is_mod.f:73
double precision, dimension(dimension_ic, dim_m) ic_v_s
Definition: ic_mod.f:98
character(len=16) units
Definition: run_mod.f:30
double precision ep_star
Definition: constant_mod.f:29
double precision, dimension(dimension_bc, dim_m) bc_v_s
Definition: bc_mod.f:121
double precision, dimension(dimension_bc) bc_massflow_g
Definition: bc_mod.f:201
integer, dimension(0:dim_m) nmax
Definition: physprop_mod.f:119
logical ahmadi
Definition: run_mod.f:146
double precision, dimension(dimension_bc) bc_z_b
Definition: bc_mod.f:46
integer, dimension(dimension_is) is_j_s
Definition: is_mod.f:53
double precision u_g0
Definition: bc_mod.f:286
double precision, dimension(dimension_bc, dim_m) bc_massflow_s
Definition: bc_mod.f:204
double precision, dimension(dimension_ic) ic_p_g
Definition: ic_mod.f:65
logical k_epsilon
Definition: run_mod.f:97
logical reinitializing
Definition: run_mod.f:208
integer mype
Definition: compar_mod.f:24
logical cyclic_x_pd
Definition: geometry_mod.f:155
double precision, dimension(dimension_bc) bc_u_g
Definition: bc_mod.f:109
double precision gravity
Definition: constant_mod.f:149
double precision mw_avg
Definition: physprop_mod.f:71
double precision, dimension(dimension_bc) bc_vw_g
Definition: bc_mod.f:316
logical energy_eq
Definition: run_mod.f:100
double precision tol_resid
Definition: toleranc_mod.f:54
integer ijkstart3
Definition: compar_mod.f:80
double precision, dimension(dimension_ic) ic_x_e
Definition: ic_mod.f:26
double precision, dimension(dimension_is) is_z_t
Definition: is_mod.f:41
double precision, dimension(dim_m, dim_n_s) mw_s
Definition: physprop_mod.f:127
double precision tol_resid_x
Definition: toleranc_mod.f:60
double precision, dimension(dimension_bc, dim_m) bc_u_s
Definition: bc_mod.f:113
double precision p_ref
Definition: scales_mod.f:10
integer nscalar
Definition: scalars_mod.f:7
double precision, dimension(dimension_ic, dim_m) ic_u_s
Definition: ic_mod.f:92
double precision, dimension(dim_m) u_s0
Definition: bc_mod.f:295
double precision xmin
Definition: geometry_mod.f:75
double precision delp_y
Definition: bc_mod.f:275
integer jmax
Definition: geometry_mod.f:49
double precision, dimension(dim_m) w_s0
Definition: bc_mod.f:301
double precision, dimension(dimension_bc, dim_n_g) bc_x_g
Definition: bc_mod.f:251
double precision, dimension(dimension_bc) bc_ep_g
Definition: bc_mod.f:77
integer, dimension(dim_eqs) discretize
Definition: run_mod.f:67
double precision, dimension(dimension_is) is_y_s
Definition: is_mod.f:29
double precision, dimension(dimension_ic, dim_n_g) ic_x_g
Definition: ic_mod.f:110
double precision, dimension(dimension_bc) bc_z_t
Definition: bc_mod.f:50
double precision, dimension(dimension_c) c
Definition: constant_mod.f:167
integer id_hour
Definition: machine_mod.f:25
double precision dt_min
Definition: run_mod.f:223
double precision, dimension(dimension_ic) ic_ep_g
Definition: ic_mod.f:62
double precision, dimension(dimension_is) is_y_n
Definition: is_mod.f:33
integer, dimension(dim_eqs) leq_method
Definition: leqsol_mod.f:14
logical model_b
Definition: run_mod.f:88
double precision, dimension(dim_m) ro_s0
Definition: physprop_mod.f:28
double precision, dimension(dim_m) mu_s0
Definition: physprop_mod.f:53
double precision, dimension(dimension_bc) bc_jet_gl
Definition: bc_mod.f:239
subroutine write_flags
Definition: write_out0.f:978
double precision ylength
Definition: geometry_mod.f:35
integer, dimension(dimension_is) is_j_n
Definition: is_mod.f:57
subroutine write_out0
Definition: write_out0.f:10
integer, dimension(1:dim_scalar) phase4scalar
Definition: scalars_mod.f:10
double precision time
Definition: run_mod.f:45
character(len=32), dimension(dim_m, dim_n_s) species_alias_s
Definition: rxns_mod.f:52
integer, dimension(dimension_is) is_i_e
Definition: is_mod.f:49
logical granular_energy
Definition: run_mod.f:112
double precision, dimension(dimension_bc) bc_w_g
Definition: bc_mod.f:125
double precision, dimension(dimension_ic) ic_y_s
Definition: ic_mod.f:29
double precision, dimension(dimension_bc, dim_m) bc_vw_s
Definition: bc_mod.f:325
double precision, dimension(dimension_bc) bc_ww_g
Definition: bc_mod.f:319
logical pic_solids
Definition: run_mod.f:258
double precision, dimension(dimension_ic) ic_t_rg
Definition: ic_mod.f:119
double precision v_g0
Definition: bc_mod.f:289
logical fpfoi
Definition: run_mod.f:106
double precision, dimension(dimension_ic, dim_m) ic_t_s
Definition: ic_mod.f:83
integer, dimension(dimension_bc) bc_i_e
Definition: bc_mod.f:58
double precision, dimension(:), allocatable x
Definition: geometry_mod.f:129
double precision, parameter zero
Definition: param1_mod.f:27
double precision zlength
Definition: geometry_mod.f:37
character(len=10) id_version
Definition: run_mod.f:42
logical function is_cg(boundary_condition)
Definition: bc_mod.f:422
double precision, dimension(dimension_bc, dim_m) bc_rop_s
Definition: bc_mod.f:92
Definition: bc_mod.f:23
double precision, dimension(dimension_bc) bc_area
Definition: bc_mod.f:245
double precision, dimension(dimension_bc) bc_x_w
Definition: bc_mod.f:30
character, parameter undefined_c
Definition: param1_mod.f:20
logical call_usr
Definition: run_mod.f:121
integer, dimension(dimension_is) is_k_t
Definition: is_mod.f:65
character(len=4), dimension(dim_eqs) leq_pc
Definition: leqsol_mod.f:26
double precision, dimension(dimension_ic, dim_m) ic_t_rs
Definition: ic_mod.f:125