File: /nfs/home/0/users/jenkins/mfix.git/model/mark_phase_4_cor.f

1     !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
2     !                                                                      C
3     !  Subroutine name: MARK_PHASE_4_COR                                   C
4     !  Purpose: For each cell mark the phase whose continuity equation is  C
5     !           being skipped/activated (see conv_rop_g/conv_rop_s for     C
6     !           details) and whose volume fraction is then corrected (see  C
7     !           calc_vol_fr for details)                                   C
8     !                                                                      C
9     !  Author: M. Syamlal                                 Date: 19-JUN-96  C
10     !  Reviewer:                                          Date:            C
11     !                                                                      C
12     !                                                                      C
13     !  Literature/Document References:                                     C
14     !                                                                      C
15     !  Variables referenced:                                               C
16     !  Variables modified:                                                 C
17     !                                                                      C
18     !  Local variables:                                                    C
19     !                                                                      C
20     !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
21     
22           SUBROUTINE MARK_PHASE_4_COR(PHASE_4_P_G, PHASE_4_P_S, DO_CONT,&
23                 MCP, DO_P_S, SWITCH_4_P_G, SWITCH_4_P_S)
24     
25     !-----------------------------------------------
26     ! Modules
27     !-----------------------------------------------
28           USE param
29           USE param1
30           USE geometry
31           USE indices
32           USE fldvar
33           USE physprop
34           USE constant
35           USE compar
36           USE visc_s
37           USE functions
38           IMPLICIT NONE
39     !-----------------------------------------------
40     ! Dummy arguments
41     !-----------------------------------------------
42     ! in each cell mark the phase index of the solids phase whose continuity
43     ! equation becomes skipped but gas phase continuity is solved and whose
44     ! volume fraction is then corrected based on sum of gas and other solids
45     ! volume fractions. only in cells where the solids phase does not close
46     ! pack and whose concentration exceeds the gas phase.
47           INTEGER :: PHASE_4_P_g(DIMENSION_3)
48     ! in each cell mark the phase index of the solids phase whose continuity
49     ! equation becomes skipped and whose volume fraction is then corrected
50     ! based on the maximum solids packing and sum of other solids volumes
51     ! fractions that can become close packed. only in cells where maximum
52     ! packing occurs.
53           INTEGER :: PHASE_4_P_s(DIMENSION_3)
54     ! flag whether continuity equation needs to be solved in addition to
55     ! pressure correction equation
56           LOGICAL :: DO_CONT(0:DIMENSION_M)
57     ! index for the solids phase that can close pack.
58           INTEGER :: MCP
59     ! flag whether solids pressure correction is needed
60           LOGICAL :: DO_P_s
61     ! flag whether different phases were used for gas pressure correction
62           LOGICAL :: SWITCH_4_P_g
63     ! flag wether different phases were used for solids pressure correction
64           LOGICAL :: SWITCH_4_P_s
65     
66     ! Here are some notes on the outcomes of the code following the changes
67     ! by Sof on 11/22/10:
68     ! -currently phase_4_p_g is always set to 0 in every cell.
69     ! -currently phase_4_p_s is always undefined in every cell.
70     ! -do_cont for the gas phase (M=0) is always F.
71     !  do_cont for the solids phases (M>1) is always F.
72     ! -mcp is assigned the index of the solids phase that has close_packed=T
73     !  (i.e. solids phases that reach a maximum packing).  in cases
74     !  involving multiple solids phases that have close_packed=T, then this
75     !  will be assigned the solids phase with the lowest index. if no solids
76     !  phase has close_packed=T, or no solids phases exist (mmax=0) then it
77     !  remains undefined.
78     ! -do_p_s is set to T if mcp is assigned, otherwise it is F.
79     ! -switch_4_p_g is always set to F (see below for logic).
80     ! -switch_4_p_s is always set to F (see below for logic).
81     
82     ! If this routine is reverted to the earlier code then some of the above,
83     ! may change, namely:
84     ! -phase_4_p_g could also be assigned the index of the gas phase in some
85     !  cells, and if a solids phase has close_packed=F, then the index of
86     !  that solids phase in other cells.
87     ! -phase_4_p_s could be assigned the index of a solids phase that has
88     !  close_packed=T (MCP) if the cell exhibits close packing. if no cell
89     !  exhibits close packing or no solids phase has close_packed then, this
90     !  will always be undefined. note this code has always been commented.
91     ! -do_cont for gas phase (M=0) is likely to be F, however, it could be
92     !  set to T if there exists a solids phase that has close_packed=F (MF)
93     !  and that has a greater mass concentration in any given fluid cell
94     !  than the fluid phase. do_cont for solids phases (M>1) will still
95     !  always be F.
96     ! -switch_4_p_g will only be T if there exists a solids phase that has
97     !  close_packed=F (MF; i.e. does not close pack) and that has a greater
98     !  mass concentration in any  given fluid cell than the fluid phase.
99     
100     !-----------------------------------------------
101     ! Local variables
102     !-----------------------------------------------
103     ! Indices
104           INTEGER          IJK, M
105     ! Index for second continuous fluid phase
106           INTEGER          MF
107     ! Count number true values
108           INTEGER          True_g, True_s
109     ! Local check for whether pressure switches are made, that is, whether
110     ! phase_4_p_g or phase_4_p_s are changed from their default setting.
111     ! if true for that index, then switch.
112           LOGICAL          SW_g(0:DIMENSION_M), SW_s(DIMENSION_M)
113     !-----------------------------------------------
114     
115     ! Initializiations
116           MF = UNDEFINED_I
117           MCP = UNDEFINED_I
118           SW_G(0) = .FALSE.
119           DO_CONT(0) = .TRUE.
120     
121     ! assigning MCP to the lowest solids phase index of those solids
122     ! phases that have close_packed=T. assigning MF to the lowest solids
123     ! phase index of those solids phases that do not close pack (i.e.,
124     ! close_packed=F; the 'solids' phase that can overpack)
125           DO M = MMAX, 1, -1
126              IF (CLOSE_PACKED(M)) THEN
127                 MCP = M
128              ELSE
129                 MF = M
130              ENDIF
131              SW_G(M) = .FALSE.
132              SW_S(M) = .FALSE.
133              DO_CONT(M) = .TRUE.
134           ENDDO
135     
136     
137     ! Sof 11/2010. : pressure correction equation is always solved for the
138     ! gas-phase (i.e., M=0). The user must decide which phase to designate
139     ! as the continuous phase (i.e., M=0). This is necessary for bubble
140     ! column simulations to work. The new code effectively marks all cells
141     ! the same way. The code below can be uncommented to revert back to
142     ! the original implementation.
143     
144           DO IJK = ijkstart3, ijkend3
145              IF (FLUID_AT(IJK)) THEN
146     
147     ! Sof: uncomment to revert back to original implementation
148     ! if one of the solids phases does not close pack (MF=defined) then
149     ! assign phase_4_p_g in the current cell to either that 'solids' phase
150     ! or the fluid phase (m=0) depending on which one has the greatest
151     ! mass concentration in that cell.
152     !            IF (MF /= UNDEFINED_I) THEN
153     !               IF (EP_G(IJK)/RO_G(IJK) > EP_S(IJK,MF)/RO_S(MF)) THEN
154     !                  PHASE_4_P_G(IJK) = 0
155     !                  SW_G(0) = .TRUE.
156     !               ELSE
157     !                  PHASE_4_P_G(IJK) = MF
158     !                  SW_G(MF) = .TRUE.
159     !               ENDIF
160     !            ELSE
161     
162     ! now always marking phase_4_p_g to 0 (the fluid phase)
163                    PHASE_4_P_G(IJK) = 0
164                    SW_G(0) = .TRUE.
165     !            ENDIF
166     
167     
168     ! if the current cell is close packed then assign phase_4_p_s to the
169     ! the lowest solids phase index of those solids phases that can close
170     ! pack (i.e. MCP)
171     !          IF(EP_g(IJK) .LE. EP_star_array(ijk)) THEN
172     !            PHASE_4_P_s(IJK) = MCP
173     !            IF(MCP .NE. UNDEFINED_I) SW_s(MCP) = .TRUE.
174     !          ELSE
175                 PHASE_4_P_S(IJK) = UNDEFINED_I       !to indicate no need for pressure correction
176     !          ENDIF
177              ELSE
178                 PHASE_4_P_G(IJK) = UNDEFINED_I       !to indicate a non-fluid cell
179                 PHASE_4_P_S(IJK) = UNDEFINED_I       !to indicate a non-fluid cell
180              ENDIF   ! end if/else fluid_at(ijk)
181           ENDDO   ! end do ijk=ijkstart3,ijkend3
182     
183     
184     ! setting the local values for true_g and true_s
185           TRUE_G = 0
186           TRUE_S = 0
187           IF (SW_G(0)) TRUE_G = TRUE_G + 1
188           DO M = 1, MMAX
189     ! sw_g(m) will be true only if one of the solids phases (M>1) does not
190     ! close pack (MF) and if it has a greater mass concentration in any given
191     ! cell than the fluid phase (m=0).  so true_g is likely to be 1 but may
192     ! be 2 if such an event occurs.
193              IF (SW_G(M)) TRUE_G = TRUE_G + 1
194     ! sw_s(m) will be true only if one of the solids phaes (M>1) does close
195     ! pack (MCP) and any given cell shows close packed conditions. hence
196     ! true_s is likely to be 1 in any simulation where close packing may
197     ! occur. it is unclear how true_s can exceed 1 since sw_s is only
198     ! switched to T for one solids index (mcp).  true_s will be 0 if no
199     ! solids phase can close pack or if no cell exhibits close pack
200     ! conditions.
201              IF (SW_S(M)) TRUE_S = TRUE_S + 1
202           ENDDO
203     
204     
205     ! unlikely for switch_4_p_g to be true (see above).  switch_4_p_g will
206     ! only be T if there exists a solids phase that does not close pack (MF)
207     ! and that has a greater mass concentration in any given fluid cell than
208     ! the fluid phase
209           IF (TRUE_G > 1) THEN
210              SWITCH_4_P_G = .TRUE.
211           ELSE
212              SWITCH_4_P_G = .FALSE.
213           ENDIF
214     
215     ! unlikely for switch_4_p_s to be true since it does not appear that
216     ! true_s can ever exceed 1 (see above).
217           IF (TRUE_S > 1) THEN
218              SWITCH_4_P_S = .TRUE.
219           ELSE
220              SWITCH_4_P_S = .FALSE.
221           ENDIF
222     
223     ! MCP will only be undefined if none of the solids phases can close
224     ! pack.  therefore if any solids phases can close pack do_p_s will be
225     ! set to true.
226           IF (MCP == UNDEFINED_I) THEN
227              DO_P_S = .FALSE.
228           ELSE
229              DO_P_S = .TRUE.
230           ENDIF
231     
232     !      DO_P_s = .FALSE.
233     ! true_s will be 0 if none of the solids phases (M>1) can close pack or
234     ! if none of the cells exhibit close pack conditions.  otherwise if a
235     ! solids phase can close pack and one of the cells exhibits close pack
236     ! conditions then true_s will be 1.
237     !      IF(True_s .EQ. 0)THEN
238     !        DO_P_s = .FALSE.
239     !      ELSE
240     !        DO_P_s = .TRUE.
241     !      ENDIF
242     
243     ! if a phase was used for pressure correction and no other phases were
244     ! used for pressure correction, there is no need to solve its continuity
245     ! equation.
246           IF (SW_G(0) .AND. TRUE_G==1) DO_CONT(0) = .FALSE.
247     !      DO M = 1, MMAX
248     !         IF(SW_g(M) .AND. True_g .EQ. 1)DO_CONT(M) = .FALSE.
249     !         IF(SW_s(M) .AND. True_s .EQ. 1)DO_CONT(M) = .FALSE.
250     !      ENDDO
251     
252     
253           RETURN
254           END SUBROUTINE MARK_PHASE_4_COR
255     
256     
257