MFIX  2016-1
eos_mod.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
2 ! C
3 ! Module name: EOS C
4 ! Purpose: Equation of state for gas and initial solids density C
5 ! C
6 ! Author: M. Syamlal Date: 29-JAN-92 C
7 ! C
8 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
9 
10  MODULE eos
11 
12  CONTAINS
13 
14 
15 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
16 ! C
17 ! Function: EOSG C
18 ! Purpose: Equation of state for gas C
19 ! C
20 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
21  DOUBLE PRECISION FUNCTION eosg (MW, PG, TG)
22 
23 ! Global Variables:
24 !---------------------------------------------------------------------//
25  USE constant, only: gas_const
26  USE scales, only: unscale_pressure
27  IMPLICIT NONE
28 
29 ! Dummy arguments
30 !---------------------------------------------------------------------//
31  DOUBLE PRECISION, INTENT(IN) :: MW, PG, TG
32 
33  eosg = unscale_pressure(pg)*mw/(gas_const*tg)
34  RETURN
35  END FUNCTION eosg
36 
37 
38 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
39 ! C
40 ! Function: dROodP_g C
41 ! Purpose: derivative of gas density w.r.t pressure C
42 ! C
43 ! Author: M. Syamlal Date: 14-AUG-96 C
44 ! C
45 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
46  DOUBLE PRECISION FUNCTION droodp_g (ROG, PG)
47 
48 ! Global Variables:
49 !---------------------------------------------------------------------//
50  USE scales, only: p_ref
51  IMPLICIT NONE
52 
53 ! Dummy arguments
54 !---------------------------------------------------------------------//
55 ! gas density and pressure
56  DOUBLE PRECISION, INTENT(IN) :: ROG, PG
57 
58  droodp_g = rog/(pg + p_ref)
59  RETURN
60  END FUNCTION droodp_g
61 
62 
63 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
64 ! !
65 ! Function: EOSS0 !
66 ! Author: J.Musser Date: 02-Dec-13 !
67 ! !
68 ! Purpose: Calculate the initial solids density. This calculation is !
69 ! only valid at time zero. Thus, this routine should only be invoked !
70 ! by the initialization routines. !
71 ! !
72 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
73  DOUBLE PRECISION FUNCTION eoss0(M)
74 
75 ! Global Variables:
76 !---------------------------------------------------------------------//
77 ! Baseline/initial solids density
78  use physprop, only: ro_xs0
79 ! Baseline/initial solids mass fractions.
80  use physprop, only: x_s0
81 ! Number of species comprising each phase.
82  use physprop, only: nmax
83 ! Process Rank
84  use compar, only: mype
85 ! Unit number for RUN_NAME.LOG file
86  use funits, only: unit_log
87 ! Logical for who writes error messages
88  use funits, only: dmp_log
89 
90 ! Global parameters
91 !---------------------------------------------------------------------/
92  use param1, only: one
93  use param1, only: zero
94  use param1, only: small_number
95  use exit, only: mfix_exit
96 
97  implicit none
98 
99 ! Passed Arguments:
100 !---------------------------------------------------------------------/
101 ! Solids phase index.
102  INTEGER, intent(in) :: M
103 
104 ! Local Variables:
105 !---------------------------------------------------------------------/
106 ! Alias for inert species index.
107  DOUBLE PRECISION :: OoRO_s0
108 ! Character string for error messages
109  CHARACTER(len=64) :: MSG
110 
111 ! Evaluate the first part of the calculation.
112  ooro_s0 = sum(x_s0(m,:nmax(m))/ro_xs0(m,:nmax(m)))
113 ! If the value is physical (positive) finish the calculation and return.
114  IF(ooro_s0 > zero) THEN
115  eoss0 = one/ooro_s0
116  return
117  ENDIF
118 
119 ! This is an extra sanity check that should be caught be one ore more
120 ! of the data checks.
121  msg=''
122  IF(abs(ooro_s0) <= small_number) THEN
123  WRITE(msg,"('Infinity')")
124  ELSE
125  WRITE(msg,*) one/ooro_s0
126  ENDIF
127 
128  IF(dmp_log) THEN
129  WRITE(*,1000) m, trim(msg)
130  WRITE(unit_log,1000) m, trim(msg)
131  ENDIF
132 
133  CALL mfix_exit(mype)
134 
135  1000 FORMAT(//1x,70('*')/' From: EOSS',/,' Error 1300:', &
136  ' Unphysical baseline density calculated:',/' RO_s(',i2,') = ' &
137  ,a,/' Please refer to the Readme file on the required input', &
138  ' and make',/' the necessary corrections to the data file.', &
139  /1x,70('*')//)
140 
141  END FUNCTION eoss0
142 
143 
144 
145 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
146 ! !
147 ! Function: EOSS !
148 ! Author: J.Musser Date: 09-Oct-13 !
149 ! !
150 ! Purpose: Calculate solid density - runtime. !
151 ! !
152 ! !
153 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
154  DOUBLE PRECISION FUNCTION eoss(pBase, Xs0_INERT, Xs_INERT)
156  implicit none
157 
158 ! Passed Arguments:
159 !---------------------------------------------------------------------/
160 ! Baseline phase density (unreacted)
161  DOUBLE PRECISION, intent(in) :: pBase
162 ! Baseline inert mass fraction
163  DOUBLE PRECISION, intent(in) :: Xs0_INERT
164 ! Current mass fraction of inert
165  DOUBLE PRECISION, intent(in) :: Xs_INERT
166 
167 ! Evaluate the solids EOS.
168  eoss = pbase * xs0_inert / max(xs_inert, 1.0d-8)
169 
170  RETURN
171  END FUNCTION eoss
172 
173  END MODULE eos
logical dmp_log
Definition: funits_mod.f:6
double precision, parameter one
Definition: param1_mod.f:29
double precision gas_const
Definition: constant_mod.f:152
double precision, dimension(dim_m, dim_n_s) x_s0
Definition: physprop_mod.f:32
double precision, dimension(dim_m, dim_n_s) ro_xs0
Definition: physprop_mod.f:35
double precision function eoss0(M)
Definition: eos_mod.f:74
double precision function eosg(MW, PG, TG)
Definition: eos_mod.f:22
subroutine mfix_exit(myID, normal_termination)
Definition: exit.f:5
double precision function droodp_g(ROG, PG)
Definition: eos_mod.f:47
double precision function eoss(pBase, Xs0_INERT, Xs_INERT)
Definition: eos_mod.f:155
double precision, parameter small_number
Definition: param1_mod.f:24
Definition: exit.f:2
Definition: eos_mod.f:10
double precision function unscale_pressure(XXX)
Definition: scales_mod.f:24
integer, parameter unit_log
Definition: funits_mod.f:21
integer, dimension(0:dim_m) nmax
Definition: physprop_mod.f:119
integer mype
Definition: compar_mod.f:24
double precision p_ref
Definition: scales_mod.f:10
double precision, parameter zero
Definition: param1_mod.f:27