MFIX  2016-1
check_bc_dem.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
2 ! minimum amount of geometry data. !
3 ! !
4 ! Subroutine: CHECK_BC_DEM !
5 ! Author: J.Musser Date: 01-Mar-14 !
6 ! !
7 ! Purpose: Determine if BCs are "DEFINED" and that they contain the !
8 ! minimum amount of geometry data. !
9 ! !
10 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
11  SUBROUTINE check_bc_dem(M_TOT)
12 
13 ! Global Variables:
14 !---------------------------------------------------------------------//
15 ! User specified BC
16  use bc
17 ! User specified: BC geometry
18  use bc, only: bc_ep_s
19 ! Use specified flag for ignoring PO BC for discrete solids
20  USE bc, only: bc_po_apply_to_des
21 ! Solids phase identifier
22  use run, only: solids_model
23 ! Number of DEM inlet/outlet BCs detected.
24  use des_bc, only: dem_bcmi, dem_bcmo
25 !
26  use des_bc, only: dem_bcmi_map
27  use des_bc, only: dem_bcmo_map
28 ! Global Parameters:
29 !---------------------------------------------------------------------//
30 ! The max number of BCs.
31  use param, only: dimension_bc
32 ! Parameter constants
33  use param1, only: zero, undefined
34 
35 ! Use the error manager for posting error messages.
36 !---------------------------------------------------------------------//
37  use error_manager
38 
39 
40  IMPLICIT NONE
41 
42 
43 ! Passed Arguments:
44 !---------------------------------------------------------------------//
45 ! Total number of solids phases.
46  INTEGER, INTENT(in) :: M_TOT
47 
48 ! Local Variables:
49 !---------------------------------------------------------------------//
50 ! loop/variable indices
51  INTEGER :: BCV, M
52 !......................................................................!
53 
54 
55 ! Initialize the error manager.
56  CALL init_err_msg("CHECK_BC_DEM")
57 
58 ! Initialize
59  dem_bcmi = 0
60  dem_bcmo = 0
61 
62 ! Loop over all BCs looking for DEM solids inlets/outlets
63  DO bcv = 1, dimension_bc
64 
65  SELECT CASE (bc_type_enum(bcv))
66 
67 ! Determine the number of mass inlets that contain DEM solids.
68  CASE (mass_inflow)
69  m_lp: DO m=1,m_tot
70  IF(solids_model(m)=='DEM' .AND. &
71  bc_ep_s(bcv,m) > zero) THEN
72  dem_bcmi = dem_bcmi + 1
73  dem_bcmi_map(dem_bcmi) = bcv
74  EXIT m_lp
75  ENDIF
76  ENDDO m_lp
77 
78 ! Count the number of pressure outflows.
79  CASE (p_outflow,mass_outflow)
80  IF(bc_po_apply_to_des(bcv)) then
81  dem_bcmo = dem_bcmo + 1
82  dem_bcmo_map(dem_bcmo) = bcv
83  ENDIF
84 
85 ! Flag CG_MI as an error if DEM solids are present.
86  CASE (cg_mi)
87  DO m=1,m_tot
88  IF(solids_model(m)=='DEM') THEN
89  IF(bc_ep_s(bcv,m) /= undefined .AND. &
90  bc_ep_s(bcv,m) > zero) THEN
91  WRITE(err_msg,1100) trim(ivar('BC_TYPE',bcv)), &
92  'GC_MI'
93  CALL flush_err_msg(abort=.true.)
94  ENDIF
95  ENDIF
96  ENDDO
97 
98  CASE (cg_po)
99  WRITE(err_msg,1100) trim(ivar('BC_TYPE',bcv)), 'GC_PO'
100  CALL flush_err_msg(abort=.true.)
101 
102  CASE (outflow, p_inflow)
103  WRITE(err_msg,1100) trim(ivar('BC_TYPE',bcv)), &
104  bc_type_enum(bcv)
105  CALL flush_err_msg(abort=.true.)
106 
107  END SELECT
108 
109  ENDDO
110 
111  CALL finl_err_msg
112 
113  RETURN
114 
115  1100 FORMAT('Error 1100: Unsupported boundary condition specified ', &
116  'with',/'DEM simulation: ',a,' = ',a,/'Please correct the ',&
117  'mfix.dat file.')
118 
119  END SUBROUTINE check_bc_dem
character(len=32) function ivar(VAR, i1, i2, i3)
subroutine finl_err_msg
integer dem_bcmo
Definition: des_bc_mod.f:19
integer, parameter dimension_bc
Definition: param_mod.f:61
character(len=3), dimension(dim_m) solids_model
Definition: run_mod.f:253
double precision, parameter undefined
Definition: param1_mod.f:18
subroutine init_err_msg(CALLER)
subroutine check_bc_dem(M_TOT)
Definition: check_bc_dem.f:12
integer dem_bcmi
Definition: des_bc_mod.f:18
Definition: run_mod.f:13
Definition: param_mod.f:2
character(len=line_length), dimension(line_count) err_msg
logical, dimension(dimension_bc) bc_po_apply_to_des
Definition: bc_mod.f:192
integer, dimension(dimension_bc) dem_bcmo_map
Definition: des_bc_mod.f:25
integer, dimension(dimension_bc) dem_bcmi_map
Definition: des_bc_mod.f:24
double precision, dimension(dimension_bc, dim_m) bc_ep_s
Definition: bc_mod.f:93
double precision, parameter zero
Definition: param1_mod.f:27
subroutine flush_err_msg(DEBUG, HEADER, FOOTER, ABORT, LOG, CALL_TREE)
Definition: bc_mod.f:23