MFIX  2016-1
set_fluidbed_p.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
2 ! C
3 ! Subroutine: SET_FLUIDBED_P C
4 ! Purpose: Set the pressure field inside the bed assuming a fluidized C
5 ! bed with gravity acting the -ve y-direction C
6 ! C
7 ! Author: M. Syamlal Date: 21-JAN-92 C
8 ! Reviewer:M. Syamlal, S. Venkatesan, P. Nicoletti, Date: 29-JAN-92 C
9 ! W. Rogers C
10 ! C
11 ! Revision Number: 1 C
12 ! Purpose: Modifications for including cylindrical geometry C
13 ! Author: M. Syamlal Date: 6-MAR-92 C
14 ! Reviewer: M. Syamlal Date: 11-DEC-92 C
15 ! Revision Number: 2 C
16 ! Purpose: Set pressure drop for cyclic boundary condition w/ C
17 ! pressure drop C
18 ! Author: M. Syamlal Date: 29-APR-94 C
19 ! C
20 ! Literature/Document References: C
21 ! C
22 ! Variables referenced: BC_DEFINED, BC_TYPE, IC_P_g, BC_P_g C
23 ! EP_g, MW_MIX_G, RO_g0, T_g, C
24 ! SMAX, ROP_s, C
25 ! DX, DY, DZ, BFY_G, DELP_X, DELP_Y, DELP_Z, C
26 ! DO_I, DO_J, DO_K, IMIN1, KMIN1, JMIN1, IMAX1, C
27 ! IMAX2, JMAX1, JMAX2, KMAX1, KMAX2 C
28 ! Variables modified: P_g C
29 ! Local variables: C
30 ! C
31 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
32 
33  SUBROUTINE set_fluidbed_p
34 
35 !-----------------------------------------------
36 ! Modules
37 !-----------------------------------------------
38  USE bc
39  USE bodyforce
40  USE compar
41  USE constant
42  USE discretelement
43  USE eos, ONLY: eosg
44  USE exit, only: mfix_exit
45  USE fldvar
46  USE functions
47  USE funits
48  USE geometry
49  USE ic
50  USE indices
51  USE machine, only: start_log, end_log
52  USE mpi_utility
53  USE param
54  USE param1
55  USE physprop
56  USE scales
57  USE sendrecv
58  IMPLICIT NONE
59 !-----------------------------------------------
60 ! Local variables
61 !-----------------------------------------------
62 ! indices
63  INTEGER :: I, J, K, IJK, M
64 ! Local loop counter
65  INTEGER :: L
66 ! Gas pressure at the axial location j
67  DOUBLE PRECISION :: PJ
68 ! Bed weight per unit area
69  DOUBLE PRECISION :: BED_WEIGHT
70 ! Total area of a x-z plane
71  DOUBLE PRECISION :: AREA
72 ! x-z plane area of one cell
73  DOUBLE PRECISION :: dAREA
74 ! Average pressure drop per unit length
75  DOUBLE PRECISION :: DPoDX, DPoDY, DPoDZ
76 !-----------------------------------------------
77 
78 ! If any initial pressures are unspecified skip next section
79 ! calculations.
80  DO l = 1, dimension_ic
81  IF (ic_defined(l)) THEN
82  IF (ic_p_g(l) == undefined) GOTO 60
83  pj = ic_p_g(l)
84  ENDIF
85  ENDDO
86 
87 ! Here the pressure in each cell is determined from a specified pressure
88 ! drop across the domain length. This section requires that the pressure
89 ! is already defined in all initial condition regions (otherwise this
90 ! section would be skipped)
91 ! ---------------------------------------------------------------->>>
92  IF (do_i .AND. delp_x/=undefined) THEN
93  dpodx = delp_x/xlength
94  pj = pj - dpodx*half*(dx(imax1)+dx(imax2))
95  DO i = imax1, imin1, -1
96  pj = pj + dpodx*half*(dx(i)+dx(i+1))
97  DO k = kmin1, kmax1
98  DO j = jmin1, jmax1
99 ! Bound Checking
100  IF(.NOT.is_on_mype_owns(i,j,k)) cycle
101  IF (dead_cell_at(i,j,k)) cycle ! skip dead cells
102  ijk = funijk(i,j,k)
103  IF (fluid_at(ijk)) p_g(ijk) = scale_pressure(pj)
104  ENDDO
105  ENDDO
106  ENDDO
107  ENDIF
108 
109  IF (do_j .AND. delp_y/=undefined) THEN
110  dpody = delp_y/ylength
111  pj = pj - dpody*half*(dy(jmax1)+dy(jmax2))
112  DO j = jmax1, jmin1, -1
113  pj = pj + dpody*half*(dy(j)+dy(j+1))
114  DO k = kmin1, kmax1
115  DO i = imin1, imax1
116 ! Bound Checking
117  IF(.NOT.is_on_mype_owns(i,j,k)) cycle
118  IF (dead_cell_at(i,j,k)) cycle ! skip dead cells
119  ijk = funijk(i,j,k)
120  IF (fluid_at(ijk)) p_g(ijk) = scale_pressure(pj)
121  ENDDO
122  ENDDO
123  ENDDO
124  ENDIF
125 
126  IF (do_k .AND. delp_z/=undefined) THEN
127  dpodz = delp_z/zlength
128  pj = pj - dpodz*half*(dz(kmax1)+dz(kmax2))
129  DO k = kmax1, kmin1, -1
130  pj = pj + dpodz*half*(dz(k)+dz(k+1))
131  DO j = jmin1, jmax1
132  DO i = imin1, imax1
133 ! Bound Checking
134  IF(.NOT.is_on_mype_owns(i,j,k)) cycle
135  IF (dead_cell_at(i,j,k)) cycle ! skip dead cells
136  ijk = funijk(i,j,k)
137  IF (fluid_at(ijk)) p_g(ijk) = scale_pressure(pj)
138  ENDDO
139  ENDDO
140  ENDDO
141  ENDIF
142 ! ----------------------------------------------------------------<<<
143  GOTO 100 ! pressure in all intial condition region cells was defined
144 
145  60 CONTINUE ! pressure in an initial condition region cell was undefined
146 
147 
148 ! ---------------------------------------------------------------->>>
149 ! Search for an outflow boundary condition where pressure is specified
150  pj = undefined
151  DO l = 1, dimension_bc
152  IF (bc_defined(l) .AND. bc_type_enum(l)==p_outflow) pj = bc_p_g(l)
153  ENDDO
154 
155  IF (pj == undefined) THEN
156 ! either a PO was not specified and/or a PO was specified but not the
157 ! pressure at the outlet
158  IF (ro_g0 /= undefined) THEN
159 ! If incompressible flow set P_g to zero
160  DO ijk = ijkstart3, ijkend3
161  IF (fluid_at(ijk)) p_g(ijk) = zero
162  ENDDO
163  GOTO 100
164 
165  ELSE ! compressible case
166 
167 ! Error condition -- no pressure outflow boundary condition is specified
168 ! if a case is compressible and pressure in any of the initial
169 ! conditions regions is unspecified, then a PO is effectively required
170 ! (i.e., is specifies a bc_p_g).
171  CALL start_log
172  IF(dmp_log)WRITE (unit_log, 1000)
173  CALL mfix_exit(mype)
174  ENDIF
175  ENDIF
176 
177 
178 ! Set an approximate pressure field assuming that the pressure drop
179 ! balances the weight of the bed, if the initial pressure-field is not
180 ! specified
181  DO j = jmax2, jmin1, -1
182 
183 ! Find the average weight per unit area over an x-z slice
184  bed_weight = 0.0
185  area = 0.0
186  DO k = kmin1, kmax1
187  DO i = imin1, imax1
188  IF(.NOT.is_on_mype_owns(i,j,k)) cycle
189  IF (dead_cell_at(i,j,k)) cycle ! skip dead cells
190  ijk = funijk(i,j,k)
191  IF (fluid_at(ijk)) THEN
192  IF (coordinates == 'CARTESIAN') THEN
193  darea = dx(i)*dz(k)
194  ELSE IF (cylindrical) THEN
195  darea = dx(i)*x(i)*dz(k)
196  ENDIF
197  area = area + darea
198  IF (ro_g0 == undefined) THEN
199  bed_weight = bed_weight - dy(j)*bfy_g(ijk)*ep_g(ijk)*eosg(&
200  mw_mix_g(ijk),pj,t_g(ijk))*darea
201  ELSE
202  bed_weight = bed_weight - dy(j)*bfy_g(ijk)*ep_g(ijk)*ro_g0&
203  *darea
204  ENDIF
205 ! This code is turned off for DEM runs until the value of rop_s can be
206 ! ensured valid values for a DEM run at this point in the code.
207  IF (.NOT.discrete_element) THEN
208  DO m = 1, smax
209  bed_weight = bed_weight - dy(j)*bfy_s(ijk,m)*rop_s(ijk,m)*&
210  darea
211  ENDDO
212  ENDIF ! end if (.not.discrete_element)
213  ENDIF ! end if (fluid_at(ijk))
214  ENDDO ! end do loop (i=imin1,imax1)
215  ENDDO ! end do loop (k=kmin1,kmax1)
216 
217 ! Global Sum
218  call global_all_sum(bed_weight)
219  call global_all_sum(area)
220  IF (area /= 0.0) bed_weight = bed_weight/area
221 
222  pj = pj + bed_weight
223  DO k = kmin1, kmax1
224  DO i = imin1, imax1
225  IF(.NOT.is_on_mype_owns(i,j,k)) cycle
226  IF (dead_cell_at(i,j,k)) cycle ! skip dead cells
227  ijk = funijk(i,j,k)
228  IF(fluid_at(ijk).AND.p_g(ijk)==undefined)p_g(ijk)=scale_pressure(pj)
229  ENDDO ! end do (i=imin1,imax1)
230  ENDDO ! end do (k = kmin1,kmax1)
231  ENDDO ! end do (j=jmax2,jimn1, -1)
232 ! end setting an undefined pressure in an initial condition region
233 ! ----------------------------------------------------------------<<<
234 
235  100 CONTINUE
236 
237  call send_recv(p_g,2)
238 
239  RETURN
240 
241  1000 FORMAT(/1x,70('*')//' From: SET_FLUIDBED_P'/' Message: Outflow ',&
242  'pressure boundary condition (P_OUTFLOW) not found.',/&
243  'All the initial pressures (IC_P_g) or at least one P_OUTFLOW',/&
244  'condition need to be specified',/1x,70('*')/)
245 
246  END SUBROUTINE set_fluidbed_p
247 
248 
character(len=16) coordinates
Definition: geometry_mod.f:17
integer, parameter dimension_ic
Definition: param_mod.f:59
logical dmp_log
Definition: funits_mod.f:6
integer imax2
Definition: geometry_mod.f:61
integer ijkend3
Definition: compar_mod.f:80
double precision, dimension(:), allocatable ep_g
Definition: fldvar_mod.f:15
double precision delp_z
Definition: bc_mod.f:278
double precision, dimension(:), allocatable t_g
Definition: fldvar_mod.f:63
double precision delp_x
Definition: bc_mod.f:272
double precision function scale_pressure(XXX)
Definition: scales_mod.f:18
double precision, dimension(0:dim_j) dy
Definition: geometry_mod.f:70
logical, dimension(dimension_ic) ic_defined
Definition: ic_mod.f:107
double precision, dimension(:), allocatable p_g
Definition: fldvar_mod.f:26
integer, parameter dimension_bc
Definition: param_mod.f:61
integer, dimension(dimension_bc) bc_type_enum
Definition: bc_mod.f:146
double precision, parameter undefined
Definition: param1_mod.f:18
double precision, dimension(0:dim_k) dz
Definition: geometry_mod.f:72
Definition: ic_mod.f:9
integer kmax1
Definition: geometry_mod.f:58
double precision function eosg(MW, PG, TG)
Definition: eos_mod.f:22
subroutine mfix_exit(myID, normal_termination)
Definition: exit.f:5
logical, dimension(:,:,:), allocatable dead_cell_at
Definition: compar_mod.f:127
double precision ro_g0
Definition: physprop_mod.f:59
integer imax1
Definition: geometry_mod.f:54
integer jmax2
Definition: geometry_mod.f:63
Definition: exit.f:2
Definition: eos_mod.f:10
logical, dimension(dimension_bc) bc_defined
Definition: bc_mod.f:207
double precision, dimension(dimension_bc) bc_p_g
Definition: bc_mod.f:80
double precision, dimension(0:dim_i) dx
Definition: geometry_mod.f:68
logical do_j
Definition: geometry_mod.f:26
integer kmax2
Definition: geometry_mod.f:65
double precision xlength
Definition: geometry_mod.f:33
double precision, parameter half
Definition: param1_mod.f:28
integer jmax1
Definition: geometry_mod.f:56
subroutine set_fluidbed_p
integer, parameter unit_log
Definition: funits_mod.f:21
Definition: param_mod.f:2
double precision function bfy_g(IJK)
Definition: bodyforce_mod.f:27
double precision, dimension(:), allocatable mw_mix_g
Definition: physprop_mod.f:130
integer jmin1
Definition: geometry_mod.f:42
logical do_k
Definition: geometry_mod.f:30
double precision, dimension(dimension_ic) ic_p_g
Definition: ic_mod.f:65
integer mype
Definition: compar_mod.f:24
logical cylindrical
Definition: geometry_mod.f:168
integer ijkstart3
Definition: compar_mod.f:80
subroutine start_log
Definition: machine_mod.f:182
double precision delp_y
Definition: bc_mod.f:275
logical do_i
Definition: geometry_mod.f:22
double precision, dimension(:,:), allocatable rop_s
Definition: fldvar_mod.f:51
integer smax
Definition: physprop_mod.f:22
double precision ylength
Definition: geometry_mod.f:35
integer imin1
Definition: geometry_mod.f:40
integer kmin1
Definition: geometry_mod.f:44
double precision function bfy_s(IJK, M)
Definition: bodyforce_mod.f:48
double precision, dimension(:), allocatable x
Definition: geometry_mod.f:129
double precision, parameter zero
Definition: param1_mod.f:27
double precision zlength
Definition: geometry_mod.f:37
subroutine end_log
Definition: machine_mod.f:208
Definition: bc_mod.f:23