MFIX  2016-1
check_odepack_stiff_chem.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
2 ! !
3 ! Module name: CHECK_DATA_CHEM !
4 ! Author: J.Musser Date: 02-Aug-13 !
5 ! !
6 ! Purpose: Check the chemical rxns namelist variables. !
7 ! !
8 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
9  SUBROUTINE check_odepack_stiff_chem
10 
11 ! Global Variables:
12 !---------------------------------------------------------------------//
13 ! Dimension of IJK arrays.
14  use param, only: dimension_3
15 ! Double precision zero.
16  use param1, only: zero
17 ! Double precision value for undefined variables.
18  use param1, only: undefined
19 ! Constant gas phase density
20  use physprop, only : ro_g0
21 ! Runtime logical for solving energy equations.
22  use run, only: energy_eq
23 ! Run time logical for solving species equations.
24  use run, only: species_eq
25 ! Net rate of gas phase production/consumption
26  use rxns, only: sum_r_g
27 ! Net rate of solids phase production/consumption
28  use rxns, only: sum_r_s
29 ! Run time logical for using stiff chemistry solver
30  use stiff_chem, only: stiff_chemistry
31 ! Run time logicals for identifying cells owned by myPE
32  use stiff_chem, only: notowner
33 
34 ! Full access to the following modules:
35 !---------------------------------------------------------------------//
36  use compar
37  use geometry
38  use indices
39 
40  use error_manager
41  use functions
42 
43  implicit none
44 
45 ! Local Variables:
46 !---------------------------------------------------------------------//
47  INTEGER :: I, J, K, IJK
48 
49  CALL init_err_msg('CHECK_ODEPACK_STIFF_CHEM')
50 
51 ! Verify that there is sufficient run complexity to use the stiff solver
52  IF(stiff_chemistry) THEN
53 
54 ! Energy equations must be solved.
55  IF(.NOT.energy_eq) THEN
56  WRITE(err_msg,1004)'ENERGY_EQ = .FALSE.'
57  CALL flush_err_msg(abort=.true.)
58  ENDIF
59 
60 ! Must be compressible
61  IF(ro_g0 /= undefined) THEN
62  WRITE(err_msg,1004)'RO_G0 /= UNDEFINED'
63  CALL flush_err_msg(abort=.true.)
64  ENDIF
65 
66  IF(.NOT.species_eq(0)) THEN
67  WRITE(err_msg,1004)'SPECIES_EQ(0) = .FALSE.'
68  CALL flush_err_msg(abort=.true.)
69  ENDIF
70 
71 ! The stiff chemistry solver only needs to loop over physical cells
72 ! owned by a process (e.g., not ghost cells). To avoid having a
73 ! triple do loop, this array is populated to identify the cells that
74 ! are not owned.
75  ALLOCATE( notowner(dimension_3) ); notowner = .true.
76  do k=kstart, kend
77  do j=jstart, jend
78  do i=istart, iend
79  ijk = funijk(i,j,k)
80  notowner(ijk) = .false.
81  enddo
82  enddo
83  enddo
84 
85 ! Initialize ODEPACK operating parameters.
86  CALL odepack_init
87 
88 ! Clear the interphase mass transfer terms as the stiff solver
89 ! does no use them.
90  IF(allocated(sum_r_g)) sum_r_g = zero
91  IF(allocated(sum_r_s)) sum_r_s = zero
92 
93  ENDIF
94 
95  CALL finl_err_msg
96 
97 
98 
99  1004 FORMAT('Error 1004: ', &
100  'Invalid parameters for stiff chemistry solver!',// &
101  ' The following criteria must be satisfied:',/ &
102  ' > Solving the energy equations.',/ &
103  ' > Compressible gas phase.',/ &
104  ' > Solving gas phase species equations.',// &
105  ' >>> Invalid Parameter: ',a,// &
106  'Check the user documentation and correct the mfix.dat file.')
107 
108  RETURN
109  END SUBROUTINE check_odepack_stiff_chem
110 
111 
112 
113 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
114 ! C
115 ! Module name: MCHEM_ODEPACK_INIT C
116 ! Purpose: controlling values for ODEAPCK(reference to ODEPACK manual)C
117 ! C
118 ! Author: Nan Xie Date: 02-Aug-04 C
119 ! Reviewer: Date: C
120 ! C
121 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
122  SUBROUTINE odepack_init
124 ! Global Variables:
125 !---------------------------------------------------------------------//
126  use physprop, only: mmax
127  use physprop, only: nmax
128 
129  use run, only: species_eq
130 
131  use stiff_chem, only: neq_dimn
132  use stiff_chem, only: ode_dimn_g
133  use stiff_chem, only: ode_dimn_all
134 
135  use stiff_chem, only: ode_itol
136  use stiff_chem, only: ode_rtol
137  use stiff_chem, only: ode_atol
138 
139  use stiff_chem, only: ode_lrw
140  use stiff_chem, only: ode_liw
141  use stiff_chem, only: ode_jt
142 
144 
147 
148 ! Double precision value for undefined variables.
149  use param1, only: undefined_i
150 
151  implicit none
152 
153 
154 ! Local Variables:
155 !---------------------------------------------------------------------//
156  INTEGER :: LRN, LRS
157  INTEGER :: M
158 
159  LOGICAL :: LIMIT_MAX_STEPS
160 
161 ! Number of ODEs (maximum)
162  neq_dimn = 2 + mmax
163 
164 ! Dimension of ODEs solved if only the gas phase is present:
165 ! Gas density, temperature, and species
166  ode_dimn_g = 2 + nmax(0)
167 ! Solids temperature excluding for all phases.
168  ode_dimn_g = ode_dimn_g + mmax
169 
170 ! Calculate the total number of ODEs that are solve.
171  ode_dimn_all = ode_dimn_g
172  DO m=1, mmax
173 ! Solids bulk density and species.
174  IF(species_eq(m)) ode_dimn_all = ode_dimn_all + (1 + nmax(m))
175  ENDDO
176 
177 ! Indicates type of Error control.
178  ode_itol = 2 ! :: EWT(i) = RTOL * ABS(Y(i)) * ATOL(i)
179 
180 ! Relative error tolerance parameter.
181  ode_rtol(1) = 1.0d-5
182 
183 ! Absolute error tolerance parameter.
184  IF(.NOT.(allocated(ode_atol))) allocate(ode_atol(ode_dimn_all))
185  ode_atol(:) = 1.0d-6 ! All Equations
186 
187 ! Declared length of RWORK.
188  lrn = 20 + 16*ode_dimn_all
189  lrs = 22 + 9*ode_dimn_all + (ode_dimn_all**2)
190  ode_lrw = max(lrn, lrs)
191 
192 ! Declared length of IWORK.
193  ode_liw = 20 + ode_dimn_all
194 
195 ! Jacobian type indicator.
196  ode_jt = 2 ! Internally generated.
197 
198 
200  stiff_chem_max_steps = 500000
201  limit_max_steps = .false.
202  ELSE
203  limit_max_steps = .true.
204  ENDIF
205 
206 
207  CALL allocate_stiff_chem_dbg(ode_dimn_all)
209 
210  return
211  END SUBROUTINE odepack_init
integer stiff_chem_max_steps
subroutine finl_err_msg
integer neq_dimn
integer iend
Definition: compar_mod.f:87
integer dimension_3
Definition: param_mod.f:11
integer ode_liw
integer ode_itol
Definition: rxns_mod.f:1
logical, dimension(0:dim_m) species_eq
Definition: run_mod.f:115
double precision, dimension(:), allocatable sum_r_g
Definition: rxns_mod.f:28
double precision, dimension(:,:), allocatable sum_r_s
Definition: rxns_mod.f:35
double precision, parameter undefined
Definition: param1_mod.f:18
integer kstart
Definition: compar_mod.f:87
double precision, dimension(1) ode_rtol
subroutine init_err_msg(CALLER)
integer mmax
Definition: physprop_mod.f:19
double precision ro_g0
Definition: physprop_mod.f:59
integer ode_lrw
integer ode_jt
integer ode_dimn_g
Definition: run_mod.f:13
double precision, dimension(:), allocatable ode_atol
Definition: param_mod.f:2
integer kend
Definition: compar_mod.f:87
integer, dimension(0:dim_m) nmax
Definition: physprop_mod.f:119
integer jstart
Definition: compar_mod.f:87
subroutine odepack_init
logical energy_eq
Definition: run_mod.f:100
subroutine check_odepack_stiff_chem
integer, parameter undefined_i
Definition: param1_mod.f:19
character(len=line_length), dimension(line_count) err_msg
integer istart
Definition: compar_mod.f:87
integer jend
Definition: compar_mod.f:87
subroutine, public allocate_stiff_chem_stats
integer ode_dimn_all
logical, dimension(:), allocatable notowner
logical stiff_chemistry
double precision, parameter zero
Definition: param1_mod.f:27
subroutine flush_err_msg(DEBUG, HEADER, FOOTER, ABORT, LOG, CALL_TREE)
subroutine, public allocate_stiff_chem_dbg(lODE_DIMN)