MFIX  2016-1
check_solids_common_discrete.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
2 ! !
3 ! SUBROUTINE: CHECK_SOLIDS_COMMON_DISCRETE !
4 ! Author: J.Musser Date: 02-FEB-14 !
5 ! !
6 ! Purpose: !
7 ! !
8 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
10 
11 ! Modules
12 !---------------------------------------------------------------------//
13 ! Runtime Flag: Generate initial particle configuration.
14  USE discretelement, only: gener_part_config
15 ! Runtime Flag: Store DES_*_OLD arrays.
16  USE discretelement, only: do_old
17 ! Number of DEM solids phases.
18  USE discretelement, only: des_mmax
19 ! User specified integration method.
20  USE discretelement, only: des_intg_method
21  USE discretelement, only: intg_adams_bashforth
22  USE discretelement, only: intg_euler
23 ! User specified neighbor search method.
24  USE discretelement, only: des_neighbor_search
25 ! User specified data out format (VTP, TecPlot)
26  USE discretelement, only: des_output_type
27 ! Max/Min particle radii
28  USE discretelement, only: max_radius, min_radius
29 ! Runtime Flag: Periodic boundaries
30  USE discretelement, only: des_periodic_walls
31  USE discretelement, only: des_periodic_walls_x
32  USE discretelement, only: des_periodic_walls_y
33  USE discretelement, only: des_periodic_walls_z
34 ! Use the error manager for posting error messages.
35  use error_manager
36 ! Runtime Flag: Invoke MPPIC model.
37  USE mfix_pic, only: mppic
38  USE mpi_utility
39 
40  use param1, only: undefined, undefined_c
41  use param, only: dim_m
42 ! number of continuous solids phases and
43 ! solids 'phase' diameters and densities
44  USE physprop, only: mmax, d_p0, ro_s0
45 ! Calculated baseline variable solids density.
46  USE physprop, only: close_packed
47 ! Runtime Flag: Solve energy equations
48  USE run, only: energy_eq
49 ! Runtime Flag: One or more species equations are solved.
50  use run, only: any_species_eq
51 ! Flag: Solve variable solids density.
52  use run, only: solve_ros
53  use run, only: solids_model
54  USE run, only: momentum_x_eq
55  USE run, only: momentum_y_eq
56  USE run, only: momentum_z_eq
57  use run, only: run_type
58  implicit none
59 
60 ! Local Variables
61 !---------------------------------------------------------------------//
62  INTEGER :: M
63 !......................................................................!
64 
65 ! Initialize the error manager.
66  CALL init_err_msg("CHECK_SOLIDS_COMMON_DISCRETE")
67 
68 ! Determine the maximum particle size in the system (MAX_RADIUS), which
69 ! in turn is used for various tasks
70  max_radius = -undefined
71  min_radius = undefined
72 ! For number of continuous solids phases (use MMAX rather than SMAX to
73 ! accomodate GHD particularity)
74  DO m = mmax+1,des_mmax+mmax
75  max_radius = max(max_radius, 0.5d0*d_p0(m))
76  min_radius = min(min_radius, 0.5d0*d_p0(m))
77  ENDDO
78 
79 ! Set close_packed to true to prevent possible issues stemming from the
80 ! pressure correction equation. Specifically, if closed_packed is false
81 ! then a mixture pressure correction equation is invoked and this is not
82 ! correctly setup for DEM. To do so would require ensuring that
83 ! 1) the solids phase continuum quantities used in these equations are
84 ! correctly set based on their DEM counterparts and
85 ! 2) the pressure correction coefficients for such solids phases are
86 ! also calculated (currently these calculations are turned off
87 ! when using DEM)
88  close_packed((mmax+1):dim_m) = .true.
89 
90 
91 ! Turn off the 'continuum' equations for discrete solids if the user
92 ! specified them. We could make use of these flags.
93  momentum_x_eq((mmax+1):dim_m) = .false.
94  momentum_y_eq((mmax+1):dim_m) = .false.
95  momentum_z_eq((mmax+1):dim_m) = .false.
96 
97 ! Derive periodicity from cyclic boundary flags.
98  des_periodic_walls_x = cyclic_x .OR. cyclic_x_pd
99  des_periodic_walls_y = cyclic_y .OR. cyclic_y_pd
100  des_periodic_walls_z = cyclic_z .OR. cyclic_z_pd
101 
102  des_periodic_walls = (des_periodic_walls_x .OR. &
103  des_periodic_walls_y .OR. des_periodic_walls_z)
104 
105 
106 ! Overwrite for restart cases.
107  IF(trim(run_type) .NE. 'NEW') gener_part_config = .false.
108 
109 ! Check for valid neighbor search option.
110  SELECT CASE(des_neighbor_search)
111  CASE (1) ! N-Square
112  CASE (2)
113  WRITE(err_msg,2001) 2, 'QUADTREE'
114  CALL flush_err_msg(abort=.true.)
115  CASE (3)
116  WRITE(err_msg,2001) 3, 'OCTREE'
117  CALL flush_err_msg(abort=.true.)
118  CASE (4) ! Grid based
119  CASE DEFAULT
120  WRITE(err_msg,2001) des_neighbor_search,'UNKNOWN'
121  CALL flush_err_msg(abort=.true.)
122 
123  2001 FORMAT('Error 2001:Invalid DES_NEIGHBOR_SEARCH method: ',i2,1x, &
124  a,/'Please correct the mfix.dat file.')
125 
126  END SELECT
127 
128 
129 ! Check the output file format
130  IF(des_output_type == undefined_c) des_output_type = 'PARAVIEW'
131  SELECT CASE(trim(des_output_type))
132  CASE ('PARAVIEW')
133  CASE ('TECPLOT')
134  CASE DEFAULT
135  WRITE(err_msg,2010) trim(des_output_type)
136  CALL flush_err_msg(abort=.true.)
137 
138  2010 FORMAT('Error 2010:Invalid DES_OUTPUT_TYPE: ',a,/'Please ', &
139  'correct the mfix.dat file.')
140 
141  END SELECT
142 
143 
144 ! Check for valid integration method
145  SELECT CASE(trim(des_intg_method))
146  CASE ('EULER')
147  intg_euler = .true.
148  intg_adams_bashforth = .false.
149  !DES_INTG_METHOD_ENUM = 1
150  CASE ('ADAMS_BASHFORTH')
151  intg_euler = .false.
152  intg_adams_bashforth = .true.
153  !DES_INTG_METHOD_ENUM = 2
154  CASE DEFAULT
155  WRITE(err_msg,2020) trim(des_intg_method)
156  CALL flush_err_msg(abort=.true.)
157 
158  2020 FORMAT('Error 2020:Invalid DES_INGT_METHOD: ',a,/'Please ', &
159  'correct the mfix.dat file.')
160 
161  END SELECT
162 
163  do_old = intg_adams_bashforth .OR. mppic
164 
165 ! Check interpolation input.
167 
168 ! Set flags for energy equations
169  IF(energy_eq) CALL check_solids_common_discrete_energy
170 
171 ! Check thermodynamic properties of discrete solids.
172  IF(any_species_eq) &
174 
175 ! Check geometry constrains.
177 
178  CALL finl_err_msg
179 
180 
181  RETURN
182 
183  END SUBROUTINE check_solids_common_discrete
184 
185 
186 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
187 ! !
188 ! SUBROUTINE CHECK_SOLIDS_COMMON_DISCRETE_ENERGY !
189 ! Author: J.Musser Date: 02-FEB-14 !
190 ! !
191 ! Purpose: Check input parameters for solving discrete solids phase !
192 ! energy equations. Only DEM simulations (neither hybrid nor MPPIC) !
193 ! can invoke particle-particle heat transfer. Therefore, checks for !
194 ! those functions are reseved for later. !
195 ! !
196 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
199 ! Modules
200 !---------------------------------------------------------------------//
201  use param1, only: zero, undefined
202  use des_thermo, only: des_conv_corr
203  use des_thermo, only: des_conv_corr_enum
204  use des_thermo, only: ranz_1952
205  use des_thermo, only: sb_const
206  use des_thermo, only: des_em
207  use des_thermo, only: calc_conv_des ! Convection
208  use des_thermo, only: calc_cond_des ! Conduction
209  use des_thermo, only: calc_radt_des ! Radiation
210 ! Flag to explicitly couple source terms and DES
211  use discretelement, only: des_explicitly_coupled
212  use discretelement, only: des_mmax
213  use discretelement, only: des_continuum_coupled
214 ! Use the error manager for posting error messages.
215  use error_manager
216 ! User input for DES interpolation scheme.
218 ! Enumerated interpolation scheme for faster access
221 
222  use physprop, only: mmax
223  use physprop, only: k_s0
224  use run, only: units
225  use run, only: solids_model
226 
227  IMPLICIT NONE
228 
229 ! Local Variables:
230 !---------------------------------------------------------------------//
231 ! Loop counter
232  INTEGER :: M
233 
234 !......................................................................!
235 
236 
237 ! Initialize the error manager.
238  CALL init_err_msg("CHECK_SOLIDS_COMMON_DISCRETE_ENERGY")
239 
240 
241 ! Set runtime flags for which modes of heat transfer to calculate.
242  calc_conv_des = des_continuum_coupled
243  DO m = mmax+1, mmax+des_mmax
244 ! Flag to calculate radiation.
245  IF(des_em(m) > zero) calc_radt_des(m) = .true.
246 ! Flag to calculate conduction.
247  calc_cond_des(m) = (k_s0(m) > zero .AND. k_s0(m) /= undefined)
248  ENDDO
249 
250 ! Gas/Solids convection:
251 !'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
252 ! Verify the selected convective heat transfer coefficient model
253  SELECT CASE(trim(des_conv_corr))
254 ! Ranz, W.E. and Marshall, W.R., "Friction and transfer coefficients
255 ! for single particles and packed beds," Chemical Engineering Science,
256 ! Vol. 48, No. 5, pp 247-253, 1952.
257  CASE ('RANZ_1952')
258  des_conv_corr_enum = ranz_1952
259 ! If the heat transfer coefficient correlation provided by the user does
260 ! not match one of the models outlined above, flag the error and exit.
261  CASE DEFAULT
262  WRITE(err_msg,1001)'DES_CONV_CORR', trim(des_conv_corr)
263  CALL flush_err_msg(abort=.true.)
264  END SELECT
265 
266 
267 ! Radiation Equation:
268 !'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
269 ! Verify that a emmisivity value is specified for each solids phase
270  DO m = mmax+1, mmax+des_mmax
271  IF(des_em(m) == undefined) THEN
272  WRITE(err_msg,1000) trim(ivar('DES_Em',m))
273  CALL flush_err_msg(abort=.true.)
274  ENDIF
275  ENDDO
276 
277 ! Set the value of the Stefan-Boltzman Constant based on the units
278  IF(units == 'SI')THEN
279  sb_const = 5.6704d0*(10.0d0**(-8)) ! W/((m^2).K^4)
280  ELSE
281  sb_const = 1.355282d0*(10.0d0**(-12)) ! cal/((cm^2).sec.K^4)
282  ENDIF
283 
284 
285 ! Notify that interpolation is not support for thermo variables
286  SELECT CASE(des_interp_scheme_enum)
287  CASE(des_interp_none)
288  CASE DEFAULT
289  WRITE(err_msg,2000) trim(adjustl(des_interp_scheme))
290  CALL flush_err_msg()
291  END SELECT
292 
293  2000 FORMAT('WARNING 2000: The selected interpolation scheme (',a, &
294  ') is not',/'supported by the DES energy equation implemen', &
295  'tation. All energy',/'equation variables will use the ', &
296  'centroid method for interphase',/'data exchange.')
297 
298  IF(des_explicitly_coupled)THEN
299  WRITE(err_msg, 2100)
300  CALL flush_err_msg!(ABORT=.TRUE.)
301  ENDIF
302 
303  2100 FORMAT('Error 2100: The DES Energy equation implementation ', &
304  'does not',/'currently support explicit coupling (DES_', &
305  'EXPLICITLY_COUPLED).',/'Please correct the mfix.dat file.')
306 
307  CALL finl_err_msg
308 
309 
310  RETURN
311 
312  1000 FORMAT('Error 1000: Required input not specified: ',a,/'Please ',&
313  'correct the mfix.dat file.')
314 
315  1001 FORMAT('Error 1001: Illegal or unknown input: ',a,' = ',a,/ &
316  'Please correct the mfix.dat file.')
317 
319 
320 
321 
322 
323 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
324 ! !
325 ! Subroutine: CHECK_SOLIDS_COMMON_DISCRETE_THERMO !
326 ! Author: J.Musser Date: 17-Jun-10 !
327 ! !
328 ! Purpose: !
329 ! !
330 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
333 ! Modules
334 !---------------------------------------------------------------------//
335  use discretelement, only: des_explicitly_coupled
336  use error_manager
337 ! User input for DES interpolation scheme.
339 ! Enumerated interpolation scheme for faster access
342  use stiff_chem, only: stiff_chemistry
343  IMPLICIT NONE
344 
345 !......................................................................!
346 
347 
348 ! Initialize the error manager.
349  CALL init_err_msg("CHECK_SOLIDS_COMMON_DISCRETE_THERMO")
350 
351 ! Stiff chemistry solver is a TFM reaction model not for DES.
352  IF(stiff_chemistry) THEN
353  WRITE(err_msg,9003)
354  CALL flush_err_msg(abort=.false.)
355  ENDIF
356 
357  9003 FORMAT('Error 9003: The stiff chemistry solver is not ', &
358  'available in DES',/'simulations. Please correct the input file.')
359 
360 ! Notify that interpolation is not support for thermo variables
361  SELECT CASE(des_interp_scheme_enum)
362  CASE(des_interp_none)
363  CASE DEFAULT
364  WRITE(err_msg,2000) trim(adjustl(des_interp_scheme))
365  CALL flush_err_msg()
366  END SELECT
367 
368  2000 FORMAT('WARNING 2000: The selected interpolation scheme (',a, &
369  ') is not',/'supported by the DES Species equation implemen', &
370  'tation. All energy',/'equation variables will use the ', &
371  'centroid method for interphase',/'data exchange.')
372 
373  IF(des_explicitly_coupled)THEN
374  WRITE(err_msg, 2100)
375  CALL flush_err_msg!(ABORT=.TRUE.)
376  ENDIF
377 
378  2100 FORMAT('Error 2100: The DES Species equation implementation ', &
379  'does not',/'currently support explicit coupling (DES_', &
380  'EXPLICITLY_COUPLED).',/'Please correct the mfix.dat file.')
381 
382  CALL finl_err_msg
383 
384  RETURN
386 
387 
388 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
389 ! !
390 ! Subroutine: CHECK_SOLIDS_COMMON_DISCRETE_GEOMETRY !
391 ! Author: J.Musser Date: 11-DEC-13 !
392 ! !
393 ! Purpose: Check user input data !
394 ! !
395 ! Comments: Geometry checks were moved here from CHECK_DES_DATA. !
396 ! !
397 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
400 ! Modules
401 !---------------------------------------------------------------------//
402 ! Flag: Use Cartesian grid cut-cell implementation
403  USE cutcell, only: cartesian_grid
404 ! Flag: Use STL representation in CG
405  USE cutcell, only: use_stl
406 ! Flag: Use DES E-L model
407  USE discretelement, only: des_continuum_coupled
408  USE discretelement, only: max_radius
409  use error_manager
410  USE geometry, only: coordinates
411  USE geometry, only: no_i, no_j
412  USE geometry, only: zlength
413  IMPLICIT NONE
414 
415 ! Local Variables
416 !---------------------------------------------------------------------//
417  DOUBLE PRECISION :: MIN_DEPTH
418 
419 !......................................................................!
420 
421 
422 ! Initialize the error manager.
423  CALL init_err_msg("CHECK_SOLIDS_COMMON_DISCRETE_GEOMETRY")
424 
425 
426 ! DEM/MPPIC is restricted to CARTESIAN coordinates.
427  IF(coordinates == 'CYLINDRICAL') THEN
428  WRITE (err_msg, 1100)
429  CALL flush_err_msg(abort=.true.)
430  ENDIF
431 
432  1100 FORMAT('Error: 1100: DES and MPPIC models only support ', &
433  'CARTESIAN coordinates.')
434 
435 
436 ! Check dimension. This is redundant with check_data_03.
437  IF(no_i .OR. no_j) THEN
438  WRITE(err_msg, 1200)
439  CALL flush_err_msg(abort=.true.)
440  ENDIF
441 
442  1200 FORMAT('Error 1200: Illegal geometry for DEM/MPPIC. 2D ', &
443  'simulations are',/'restricted to the XY plane. Please ', &
444  'correct the mfix.dat file.')
445 
446 
447  IF(des_continuum_coupled)THEN
448 ! Check that the depth of the simulation exceeds the largest particle
449 ! to ensure correct calculation of volume fraction. This is important
450 ! for coupled simulations.
451  min_depth = 2.0d0*max_radius
452  IF(zlength < min_depth)THEN
453  WRITE(err_msg, 1300)
454  CALL flush_err_msg(abort=.false.)
455  ENDIF
456  ENDIF
457 
458  1300 FORMAT('Error 1300: The maximum particle diameter exceeds the ', &
459  'simulation',/'depth (ZLENGTH). Please correct the mfix.dat ',&
460  'file.')
461 
462 
463  IF(cartesian_grid .AND. .NOT.use_stl) THEN
464  WRITE(err_msg,1400)
465  CALL flush_err_msg(abort =.true.)
466  ENDIF
467 
468  1400 FORMAT('Error 1400: Cartesian grid and discrete models (DEM or ',&
469  'PIC) only',/'support STL wall representations. Quadrics ', &
470  'and polygons are not',/'supported.')
471 
472 
473  CALL finl_err_msg
474 
475  RETURN
476 
478 
479 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
480 ! !
481 ! Subroutine: CHECK_SOLIDS_COMMON_DISCRETE_INTERP !
482 ! Author: J.Musser Date: 25-Nov-14 !
483 ! !
484 ! Purpose: !
485 ! !
486 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
489 ! Modules
490 !---------------------------------------------------------------------//
491 ! Runtime Flag: Invoke gas/solids coupled simulation.
492  use discretelement, only: des_continuum_coupled
493  use error_manager
494 ! Runtime FLag: 3D simulation
495  use geometry, only: do_k
496 ! Runtime Flag: Invoke MPPIC model.
497  USE mfix_pic, only: mppic
498  use param1, only: undefined
499 ! User input for DES interpolation scheme.
501 ! Enumerated interpolation scheme for faster access
508 ! User specified filter width
510 ! Flag: Diffuse DES field variables.
512 ! Diffusion filter width
514 ! Flag: Interpolate continuum fields
516 ! Flag: Interplate variables for drag calculation.
517  use particle_filter, only: des_interp_on
518 ! Size of interpolation filter
519  use particle_filter, only: filter_size
520  IMPLICIT NONE
521 
522 !......................................................................!
523 
524 
525 ! Initialize the error manager.
526  CALL init_err_msg("CHECK_SOLIDS_COMMON_DISCRETE_INTERP")
527 
528 ! Set the runtime flag for diffusing mean fields
529  des_diffuse_mean_fields = (des_diffuse_width /= undefined)
530 
531 ! Set the interpolation ENUM value.
532  SELECT CASE(trim(adjustl(des_interp_scheme)))
533  CASE ('NONE')
534  des_interp_scheme_enum = des_interp_none
535 ! Cannot use interpolation when no scheme is selected.
536  IF(des_interp_on)THEN
537  WRITE(err_msg,2001) 'DES_INTERP_ON'
538  CALL flush_err_msg(abort=.true.)
539  ELSEIF(des_interp_mean_fields)THEN
540  WRITE(err_msg,2001) 'DES_INTERP_MEAN_FIELDS'
541  CALL flush_err_msg(abort=.true.)
542 
543  ELSEIF(des_continuum_coupled) THEN
544  IF(mppic) THEN
545  WRITE(err_msg,2002) 'MPPIC solids'
546  CALL flush_err_msg(abort=.false.)
547  ELSEIF(mppic) THEN
548  WRITE(err_msg,2002) 'Cartesian grid cut-cells'
549  CALL flush_err_msg(abort=.true.)
550  ENDIF
551  ENDIF
552 
553  CASE ('GARG_2012')
554  des_interp_scheme_enum = des_interp_garg
555 
556  CASE ('SQUARE_DPVM')
557  des_interp_scheme_enum = des_interp_dpvm
558 
559  CASE ('GAUSS_DPVM')
560  des_interp_scheme_enum = des_interp_gauss
561 
562  CASE ('LINEAR_HAT')
563  des_interp_scheme_enum = des_interp_lhat
564 
565  CASE DEFAULT
566  WRITE(err_msg,2000) trim(adjustl(des_interp_scheme))
567  CALL flush_err_msg(abort=.true.)
568  END SELECT
569 
570  2000 FORMAT('Error 2000: Invalid DES_INTERP_SCHEME: ',a,/'Please ', &
571  'correct the mfix.dat file.')
572 
573  2001 FORMAT('Error 2001: No interpolation scheme specified when ',a,/ &
574  'is enabled. Please correct the mfix.dat file.')
575 
576  2002 FORMAT('Error 2002: DES simulations utilizing ',a,' require',/ &
577  'interpolation (DES_INTERP_ON and DES_INTERP_MEANFIELDS). ',/ &
578  'Please correct the mfix.dat file.')
579 
580 
581  SELECT CASE(des_interp_scheme_enum)
582 
583  CASE(des_interp_none)
584 
585  IF(des_interp_width /= undefined) THEN
586  WRITE(err_msg,2100) trim(adjustl(des_interp_scheme))
587  CALL flush_err_msg(abort=.true.)
588  ENDIF
589 
590  2100 FORMAT('Error 2100: The selected interpolation scheme (',a,') ', &
591  'does',/'not support an adjustable interpolation width.',/ &
592  'Please correct the input file.')
593 
594 
595  CASE(des_interp_garg)
596  des_interp_mean_fields= .true.
597 
598  IF(des_interp_width /= undefined) THEN
599  WRITE(err_msg,2100) trim(adjustl(des_interp_scheme))
600  CALL flush_err_msg(abort=.true.)
601  ENDIF
602 
603  IF(des_diffuse_mean_fields) THEN
604  WRITE(err_msg,2110) trim(adjustl(des_interp_scheme))
605  CALL flush_err_msg(abort=.true.)
606  ENDIF
607 
608  2110 FORMAT('Error 2110: The selected interpolation scheme (',a,') ', &
609  'does not',/'support diffusive filtering of mean field ', &
610  'quantities. Please correct',/'the input file.')
611 
612  CASE(des_interp_dpvm, des_interp_gauss)
613 
614 ! Set the size of the interpolation filter.
615  filter_size = merge(27, 9, do_k)
616 
617  IF(des_interp_width == undefined) THEN
618  WRITE(err_msg,2120) trim(adjustl(des_interp_scheme))
619  CALL flush_err_msg(abort=.true.)
620  ENDIF
621 
622  2120 FORMAT('Error 2120: The selected interpolation scheme (',a,') ', &
623  'requires',/'a DES_INTERP_WIDTH. Please correct the ', &
624  'input file.')
625 
626 
627  CASE(des_interp_lhat)
628 
629 ! Set the size of the interpolation filter.
630  filter_size = merge(27, 9, do_k)
631 
632  IF(des_interp_width /= undefined) THEN
633  WRITE(err_msg,2100) trim(adjustl(des_interp_scheme))
634  CALL flush_err_msg(abort=.true.)
635  ENDIF
636 
637  END SELECT
638 
639  CALL finl_err_msg
640 
641  RETURN
character(len=16) coordinates
Definition: geometry_mod.f:17
logical, dimension(0:dim_m) momentum_y_eq
Definition: run_mod.f:77
logical des_diffuse_mean_fields
integer, parameter des_interp_gauss
double precision, dimension(dim_m) d_p0
Definition: physprop_mod.f:25
character(len=32) function ivar(VAR, i1, i2, i3)
double precision sb_const
subroutine finl_err_msg
logical no_i
Definition: geometry_mod.f:20
integer, parameter des_interp_garg
integer, parameter ranz_1952
logical, dimension(dim_m) calc_cond_des
logical, dimension(dim_m) calc_radt_des
subroutine check_solids_common_discrete_thermo
logical, dimension(0:dim_m) momentum_x_eq
Definition: run_mod.f:74
logical calc_conv_des
integer, parameter dim_m
Definition: param_mod.f:67
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(dim_m) des_em
character(len=3), dimension(dim_m) solids_model
Definition: run_mod.f:253
double precision, parameter undefined
Definition: param1_mod.f:18
logical, dimension(dim_m) close_packed
Definition: physprop_mod.f:56
logical des_interp_mean_fields
double precision des_interp_width
integer des_conv_corr_enum
integer, parameter des_interp_lhat
subroutine init_err_msg(CALLER)
character(len=32) des_interp_scheme
logical use_stl
Definition: cutcell_mod.f:428
integer mmax
Definition: physprop_mod.f:19
integer, parameter des_interp_none
character(len=16) run_type
Definition: run_mod.f:33
subroutine check_solids_common_discrete
double precision, dimension(dim_m) k_s0
Definition: physprop_mod.f:95
integer, parameter des_interp_dpvm
logical any_species_eq
Definition: run_mod.f:118
subroutine check_solids_common_discrete_energy
Definition: run_mod.f:13
double precision des_diffuse_width
Definition: param_mod.f:2
logical cartesian_grid
Definition: cutcell_mod.f:13
character(len=16) units
Definition: run_mod.f:30
integer des_interp_scheme_enum
logical do_k
Definition: geometry_mod.f:30
logical no_j
Definition: geometry_mod.f:24
logical energy_eq
Definition: run_mod.f:100
character(len=line_length), dimension(line_count) err_msg
subroutine check_solids_common_discrete_interp
logical mppic
Definition: mfix_pic_mod.f:14
double precision, dimension(dim_m) ro_s0
Definition: physprop_mod.f:28
character(len=24) des_conv_corr
logical stiff_chemistry
double precision, parameter zero
Definition: param1_mod.f:27
double precision zlength
Definition: geometry_mod.f:37
subroutine flush_err_msg(DEBUG, HEADER, FOOTER, ABORT, LOG, CALL_TREE)
character, parameter undefined_c
Definition: param1_mod.f:20
subroutine check_solids_common_discrete_geometry