MFIX  2016-1
coeff_mod.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
2 ! !
3 ! MODULE: COEFF !
4 ! Purpose: Contains logic flags that tells the code whether to !
5 ! perform the indicated type of calculation when the !
6 ! value is true !
7 ! !
8 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
9  MODULE coeff
10 
11 ! Flags used by PHYSICAL_PROP :: (0:DIMENSION_M)
12 !```````````````````````````````````````````````````````````````````````
13  LOGICAL, ALLOCATABLE :: density(:) ! Density
14  LOGICAL, ALLOCATABLE :: sp_heat(:) ! Specific heat
15  LOGICAL, ALLOCATABLE :: psize(:) ! Particle diameter
16 
17 
18 ! Flags used by TRANSPORT_PROP :: (0:DIMENSION_M)
19 !```````````````````````````````````````````````````````````````````````
20  LOGICAL, ALLOCATABLE :: visc(:) ! Viscosity
21  LOGICAL, ALLOCATABLE :: cond(:) ! Conductivity
22  LOGICAL, ALLOCATABLE :: diff(:) ! Diffusivity
23  LOGICAL, ALLOCATABLE :: gran_diss(:) ! Granular energy dissipation
24 
25 
26 ! Flags used by EXCHANGE :: (0:DIMENSION_M)x(0:DIMENSION_M)
27 !```````````````````````````````````````````````````````````````````````
28  LOGICAL, ALLOCATABLE :: dragcoef(:,:) ! Drag coefficient
29  LOGICAL, ALLOCATABLE :: heat_tr(:,:) ! Heat transfer coeff
30 
31 
32  contains
33 
34 !**********************************************************************!
35 ! SUBROUTINE: INIT_COEFF !
36 ! !
37 ! Purpose: Initialize logical flags. !
38 ! !
39 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
40  SUBROUTINE init_coeff(IER)
41 
42 ! Global Variables:
43 !-----------------------------------------------------------------------
44  use param, only: dimension_m
45  use param1, only: undefined
46 ! Kinetic theory model.
47  USE run, only: kt_type_enum
48  USE run, only: gd_1999, gtsh_2012, ia_2005, ghd_2007
49 ! Run-time flag for invoking DQMOM
50  use run, only: call_dqmom
51 ! Real number of solids phases (GHD theory)
52  use physprop, only: smax
53 ! Run-time flag for to solve energy equations.
54  use run, only: energy_eq
55 ! Run-time flag for to solve species equations.
56  use run, only: species_eq
57 ! Flag to recalculate gas viscosity.
58  use visc_g, only: recalc_visc_g
59 ! Run-time flag for invoking discrete element model
60  use discretelement, only: discrete_element
61 ! Run-time flag for gas/DEM coupling
62  use discretelement, only: des_continuum_coupled
63 ! Run-time flag for invoking TFM/DEM hybrid model
64  use discretelement, only: des_continuum_hybrid
65 ! Run-time flag invoking QMOM theory
66  use qmom_kinetic_equation, only: qmomk
67 ! Specified constant gas phase density (incompressible)
68  use physprop, only: ro_g0
69 ! Specified constant specific heat.
70  use physprop, only: c_pg0, c_ps0
71 ! Specified constant thermal conductivity.
72  use physprop, only: k_g0, k_s0
73 ! specified constant diffusivity
74  use physprop, only: dif_g0, dif_s0
75 ! Specified number of solids phases.
76  use physprop, only: mmax
77 ! Specified constant viscosity.
78  use physprop, only: mu_g0
79 ! Variable solids density flag.
80  use run, only: solve_ros
81 ! MMS flag
82  use mms, only: use_mms
83 ! user defined flags
86  use usr_prop, only: usr_gama, usr_fgs, usr_fss
87  implicit none
88 
89 ! Dummy Arguments:
90 !-----------------------------------------------------------------------
91 ! Error flag.
92  INTEGER, intent(inout) :: IER
93 
94 
95 ! Local Variables.
96 !-----------------------------------------------------------------------
97 ! Invoke debug routine:
98  LOGICAL, parameter :: dbg_coeffs = .false.
99 ! Loop counter for solids phases
100  INTEGER :: M
101 
102 ! Allocate and initialize:
103 !```````````````````````````````````````````````````````````````````````
104  IF(.NOT.allocated(density)) allocate( density(0:dimension_m))
105  IF(.NOT.allocated(sp_heat)) allocate( sp_heat(0:dimension_m))
106  IF(.NOT.allocated(psize)) allocate( psize(0:dimension_m))
107 ! Interphase heat transfer coefficient (GAMA)
108 
109  density = .false.
110  sp_heat = .false.
111  psize = .false.
112 
113  IF(.NOT.allocated(visc)) allocate( visc(0:dimension_m))
114  IF(.NOT.allocated(cond)) allocate( cond(0:dimension_m))
115  IF(.NOT.allocated(diff)) allocate( diff(0:dimension_m))
116  IF(.NOT.allocated(gran_diss)) allocate( gran_diss(0:dimension_m))
117 
118  visc = .false.
119  cond = .false.
120  diff = .false.
121  gran_diss = .false.
122 
123  IF(.NOT.allocated(dragcoef)) &
124  allocate( dragcoef(0:dimension_m,0:dimension_m))
125  IF(.NOT.allocated(heat_tr)) &
126  allocate( heat_tr(0:dimension_m,0:dimension_m))
127 
128  dragcoef = .false.
129  heat_tr = .false.
130 
131 ! Coefficients for gas phase parameters.
132 !```````````````````````````````````````````````````````````````````````
133 ! Compressible flow.
134  if(ro_g0 == undefined .OR. usr_rog) density(0) = .true.
135 
136 ! Gas viscosity:
137 ! Calc_mu_g must be invoked every iteration even if constant viscosity
138 ! (mu_g0 /= undefined) to incorporate ishii form of governing equations
139 ! wherein the viscosity is multiplied by the phase volume fraction.
140 ! Alternatively, we could invoke calc_mu_g only if energy, k_epsilon,
141 ! l_scale0 /= 0, or ishii (use recalc_visc_g)
142  visc(0) = .true.
143 
144 ! Specific heat and thermal conductivity.
145  if(energy_eq) then
146  if(c_pg0 == undefined .or. usr_cpg) sp_heat(0) = .true.
147  if(k_g0 == undefined .or. usr_kg) cond(0) = .true.
148  endif
149 
150 ! Species diffusivity.
151  if(species_eq(0)) then
152  if (dif_g0 == undefined .or. usr_difg) diff(0) = .true.
153  endif
154 
155 ! Interphase transfer terms.
156 !```````````````````````````````````````````````````````````````````````
157 ! this needs to be mmax for ghd
158  if(.NOT.qmomk .AND. .NOT.use_mms) dragcoef(0:mmax,0:mmax)=.true.
159 
160 ! Interphase heat transfer coefficient (GAMA)
161  IF (.NOT.discrete_element .OR. des_continuum_hybrid) THEN
162  if(energy_eq .AND. .NOT.use_mms) heat_tr(0:smax,0:smax)=.true.
163  ENDIF
164 
165 ! Coefficients for solids phase parameters.
166 !```````````````````````````````````````````````````````````````````````
167  IF (.NOT.discrete_element .OR. des_continuum_hybrid) THEN
168  DO m=1,smax
169 ! Variable solids density or user solids density
170  if(solve_ros(m) .or. usr_ros(m)) density(m) = .true.
171  ENDDO
172 
173 ! Solids viscosity.
174 ! Calc_mu_s must be invoked every iteration even if constant viscosity
175 ! (mu_s0 /= undefined) to incorporate ishii form of governing equations
176 ! wherein the viscosity is multiplied by the phase volume fraction
177  visc(1:smax) = .true.
178 ! mu_s only needs to be called for ghd_2007 when m=mmax
179  IF (kt_type_enum == ghd_2007) THEN
180  visc(1:smax) = .false.
181  visc(mmax) = .true.
182  ENDIF
183 
184  do m=1,smax
185 ! Specific heat and thermal conductivity.
186  if(energy_eq) THEN
187  if(c_ps0(m) == undefined .or. usr_cps(m)) sp_heat(m) = .true.
188  if(k_s0(m) == undefined .or. usr_ks(m)) cond(m) = .true.
189  endif
190 ! Species diffusivity. Generally no need to invoke this routine since
191 ! by default solids diffusivisty is zero, however, now it is invoked
192 ! for user options
193  IF(species_eq(m)) THEN
194  IF (dif_s0(m) == undefined .or. usr_difs(m)) diff(m) = .true.
195  ENDIF
196  enddo
197 
198 ! Particle-Particle Energy Dissipation
199  IF (kt_type_enum == ia_2005 .OR. &
200  kt_type_enum == gd_1999 .OR. &
201  kt_type_enum == gtsh_2012) THEN
202  gran_diss(:smax) = .true.
203  ENDIF
204 
205 ! Particle diameter.
206  if(call_dqmom) psize(1:smax)=.true.
207 
208  ENDIF ! end if (.not.discrete_element .or des_continuum_hybrid)
209 
210  if(dbg_coeffs) CALL debug_coeff
211 
212 ! Invoke calc_coeff.
213  IF(.NOT.discrete_element .OR. des_continuum_coupled) THEN
214  CALL calc_coeff(ier, 2)
215 
216 ! If gas viscosity is undefined and the flag for calculating gas
217 ! viscosity is turned off: Turn it on and make the call to calc_coeff.
218 ! Once viscosity values have been calculated (i.e., an initial value
219 ! is calculated), turn the flag off again so it isn't recalculated.
220 ! IF(MU_g0 == UNDEFINED .AND. .NOT.VISC(0)) THEN
221 ! VISC(0) = .TRUE.; CALL CALC_COEFF(IER, 2)
222 ! VISC(0) = .FALSE.
223 ! ELSE
224 ! CALL CALC_COEFF(IER, 2)
225 ! ENDIF
226  ENDIF
227 
228  END SUBROUTINE init_coeff
229 
230 !**********************************************************************!
231 ! SUBROUTINE: DEBUG_COEFF !
232 ! !
233 ! Purpose: Dump the coefficient arrays for debugging. !
234 ! !
235 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
236  SUBROUTINE debug_coeff
238  use compar
239  use physprop, only: mmax
240 
241  implicit none
242 
243  INTEGER :: M, MM
244 
245  if(mype /= pe_io) return
246 
247  write(*,"(/3x,'From DEBUG_COEFF:')")
248 
249  write(*,"(/3x,'Gas phase coefficients:')")
250  write(*,"( 5x,'Density (RO_g):',1x,1L1)") density(0)
251  write(*,"( 5x,'Specific heat (C_pg):',1x,1L1)") sp_heat(0)
252  write(*,"( 5x,'Viscosity: (MU_g)',1x,1L1)") visc(0)
253  write(*,"( 5x,'Thermal conductivity (K_g):',1x,1L1)") cond(0)
254  write(*,"( 5x,'Species diffusivity: (DIF_G)',1x,1L1)") diff(0)
255 
256 
257  DO m=1, mmax
258  write(*,"(/3x,'Solids ',I1,' phase coefficients:')") m
259  write(*,"( 5x,'Density: (RO_s)',1x,1L1)") density(m)
260  write(*,"( 5x,'Specific heat (C_ps):',1x,1L1)") sp_heat(m)
261  write(*,"( 5x,'Viscosity (MU_s):',1x,1L1)") visc(m)
262  write(*,"( 5x,'Thermal conductivity (K_s):',1x,1L1)") cond(m)
263  write(*,"( 5x,'Species diffusivity (DIF_s):',1x,1L1)") diff(m)
264  write(*,"( 5x,'Gran. Dissipation (D_p):',1x,1L1)") gran_diss(m)
265  write(*,"( 5x,'Diameter (D_p):',1x,1L1)") psize(m)
266  ENDDO
267 
268 
269  write(*,"(/3x,'Interphase drag:')")
270  write(*,"( 5x,'ref')",advance="NO")
271  DO m=0, mmax
272  write(*,"(2x,I3)",advance="NO")m
273  ENDDO
274  write(*,"('')")
275 
276  DO m=0, mmax
277  write(*,"( 5x,I3)",advance="NO") m
278  DO mm=0, mmax
279  write(*,"(2x,L3)",advance="NO")dragcoef(m, mm)
280  ENDDO
281  write(*,"('')")
282  ENDDO
283 
284  write(*,"(/3x,'Interphase heat transfer:')")
285  write(*,"( 5x,'ref')",advance="NO")
286  DO m=0, mmax
287  write(*,"(2x,I3)",advance="NO")m
288  ENDDO
289  write(*,"('')")
290  DO m=0, mmax
291  write(*,"( 5x,I3)",advance="NO") m
292  DO mm=0, mmax
293  write(*,"(2x,L3)",advance="NO")heat_tr(m, mm)
294  ENDDO
295  write(*,"('')")
296  ENDDO
297 
298  write(*,"(/3x,'DEBUG_COEFF - Exit',3/)")
299 
300  END SUBROUTINE debug_coeff
301 
302  END MODULE coeff
logical, dimension(dim_m) usr_ros
Definition: usr_prop_mod.f:9
double precision, dimension(dim_m) c_ps0
Definition: physprop_mod.f:83
logical recalc_visc_g
Definition: visc_g_mod.f:27
double precision c_pg0
Definition: physprop_mod.f:74
logical usr_rog
Definition: usr_prop_mod.f:7
double precision, dimension(dim_m) dif_s0
Definition: physprop_mod.f:113
logical, dimension(0:dim_m) species_eq
Definition: run_mod.f:115
double precision mu_g0
Definition: physprop_mod.f:62
logical, dimension(dim_m) solve_ros
Definition: run_mod.f:250
logical usr_mug
Definition: usr_prop_mod.f:13
double precision, parameter undefined
Definition: param1_mod.f:18
logical, dimension(:), allocatable cond
Definition: coeff_mod.f:21
logical, dimension(:), allocatable density
Definition: coeff_mod.f:13
logical, dimension(dim_m) usr_difs
Definition: usr_prop_mod.f:18
logical, dimension(:), allocatable diff
Definition: coeff_mod.f:22
integer pe_io
Definition: compar_mod.f:30
logical, dimension(:), allocatable gran_diss
Definition: coeff_mod.f:23
integer mmax
Definition: physprop_mod.f:19
subroutine calc_coeff(IER, pLevel)
Definition: calc_coeff.f:99
logical usr_difg
Definition: usr_prop_mod.f:15
double precision ro_g0
Definition: physprop_mod.f:59
logical usr_cpg
Definition: usr_prop_mod.f:8
logical, dimension(:), allocatable psize
Definition: coeff_mod.f:15
subroutine init_coeff(IER)
Definition: coeff_mod.f:41
double precision, dimension(dim_m) k_s0
Definition: physprop_mod.f:95
Definition: mms_mod.f:12
logical call_dqmom
Definition: run_mod.f:127
Definition: run_mod.f:13
double precision k_g0
Definition: physprop_mod.f:89
logical, dimension((dim_m *(dim_m-1)/2)+1) usr_fss
Definition: usr_prop_mod.f:22
Definition: param_mod.f:2
integer mype
Definition: compar_mod.f:24
logical energy_eq
Definition: run_mod.f:100
logical use_mms
Definition: mms_mod.f:15
logical, dimension(dim_m) usr_ks
Definition: usr_prop_mod.f:17
logical, dimension(dim_m) usr_mus
Definition: usr_prop_mod.f:16
subroutine debug_coeff
Definition: coeff_mod.f:237
integer smax
Definition: physprop_mod.f:22
Definition: coeff_mod.f:9
logical, dimension(:), allocatable visc
Definition: coeff_mod.f:20
logical, dimension(dim_m) usr_fgs
Definition: usr_prop_mod.f:21
double precision dif_g0
Definition: physprop_mod.f:107
integer dimension_m
Definition: param_mod.f:18
logical, dimension(:), allocatable sp_heat
Definition: coeff_mod.f:14
logical usr_kg
Definition: usr_prop_mod.f:14
logical, dimension(:,:), allocatable heat_tr
Definition: coeff_mod.f:29
logical, dimension(:,:), allocatable dragcoef
Definition: coeff_mod.f:28
logical, dimension(dim_m) usr_cps
Definition: usr_prop_mod.f:10
logical, dimension(dim_m) usr_gama
Definition: usr_prop_mod.f:24