File: N:\mfix\model\des\pic\mfix_pic_mod.f

1     !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
2     !                                                                      !
3     !  Module: MFIX_PIC                                                    !
4     !  Purpose: MP-PIC related data                                        !
5     !  Author: R. Garg                                                     !
6     !                                                                      !
7     !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
8           MODULE MFIX_PIC
9     
10           use param, only: dim_m
11     !......................................................................!
12     
13     ! flag for turning on MP-PIC method
14           LOGICAL :: MPPIC
15     
16           DOUBLE PRECISION :: PSFAC_FRIC_PIC
17           DOUBLE PRECISION :: FRIC_EXP_PIC
18           DOUBLE PRECISION :: FRIC_NON_SING_FAC
19     
20           LOGICAL :: MPPIC_SOLID_STRESS_SNIDER
21           LOGICAL :: MPPIC_CORR_VOLFRAC
22           INTEGER :: ITER_VOL_FRAC_CORR
23     
24     ! force to solids pressure gradient
25           DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: PS_FORCE_PIC
26     
27     ! avg solid velocity at particle position (used for MP-PIC)
28           DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: AVGSOLVEL_P
29     
30     ! EP_g interpolated at particle position (used for MP-PIC)
31           DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: EPG_P
32     
33     ! to initially seed the particles based on constant number of
34     ! particles per cell or constant statistical weight of each particle
35     ! number of particles per cell for the case of CONSTANTNPC
36           LOGICAL :: MPPIC_CONSTANTNPC, MPPIC_CONSTANTWT
37     
38           INTEGER NPC_PIC(DIM_M)
39     
40     ! coefficeient of restituion used in MPPIC case in the
41     ! frictional regime
42           DOUBLE PRECISION :: MPPIC_COEFF_EN1, MPPIC_COEFF_EN2
43           DOUBLE PRECISION :: MPPIC_COEFF_EN_WALL, MPPIC_COEFF_ET_WALL
44     
45     ! statistical weight or number of real particles per computational
46     ! particle for the case of CONSTANTWT
47           DOUBLE PRECISION STATWT_PIC(DIM_M)
48     
49     ! # of computational particles for the entire grid
50     ! keep it double precision for inlow BC
51           DOUBLE PRECISION , DIMENSION(:,:), ALLOCATABLE :: CNP_ARRAY
52     
53     ! Statistical weight of each particle
54           DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: DES_STAT_WT
55     
56     !     logical variable to decide if special treatment is needed or not
57     !     in the direction of gravity in the frictional stress tensor
58           LOGICAL :: MPPIC_GRAV_TREATMENT
59     
60     ! Particle response time scale for each phase
61           DOUBLE PRECISION :: DES_TAU_P(DIM_M)
62     
63     ! The maximum dt for point particles based on particle response time
64     ! (taup) and cfl. See cfassign for its computation
65           DOUBLE PRECISION :: DTPIC_MAX
66     
67     ! CFL value for point-particles that is used to control DTSOLID
68     ! DTPP_CFL, dt for point-particles based on user specified CFL_PP
69     ! and maximum velocity of particles
70           DOUBLE PRECISION CFL_PIC, DTPIC_CFL, DTPIC_TAUP
71     
72           DOUBLE PRECISION :: DTSOLID_ORIG
73     ! solid pressure gradient
74           DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: PS_GRAD
75     
76     ! flag to turn on implicit treatment of drag force term in particle
77     ! trajectory evolution equation
78           LOGICAL MPPIC_PDRAG_IMPLICIT
79     
80     ! Solids pressure as a result of granular motion
81           DOUBLE PRECISION, DIMENSION(:, :), ALLOCATABLE :: PIC_P_s
82     !Face centered u-velocity required by PIC model.
83           DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: PIC_U_S
84     ! Face centered v-velocity required by PIC model. Not using the U_s arrays anymore
85           DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: PIC_V_S
86     ! Face centered z-velocity required by PIC model. Not using the U_s arrays anymore
87           DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: PIC_W_S
88     
89     ! A run time flag to report minimum value of gas voidage
90           LOGICAL :: PIC_REPORT_MIN_EPG
91     
92           END MODULE MFIX_PIC
93     
94