MFIX  2016-1
set_ro_s.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
2 ! !
3 ! Subroutine: SET_RO_s !
4 ! !
5 ! Author: J.Musser Date: 09-Oct-13 !
6 ! Reviewer: !
7 ! !
8 ! Purpose: Initialize solids densities. !
9 ! !
10 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
11  SUBROUTINE set_ro_s
12 
13 ! Global Variables:
14 !---------------------------------------------------------------------/
15 ! Number of solids phases.
16  use physprop, only: mmax
17 ! Solids density field variable.
18  use fldvar, only: ro_s, rop_s
19 ! Solid phase species mass fractions.
20  use fldvar, only: x_s
21 ! Initial mass fraction of inert species
22  use physprop, only: x_s0
23 ! Index of inert solids phase species.
24  use physprop, only: inert_species
25 ! Inert solids phase species mass fraction in dilute region.
26  use physprop, only: dil_inert_x_vsd
27 ! Factor to define dilute region where DIL_INERT_X_VSD is used
28  use physprop, only: dil_factor_vsd
29 ! Run-time flag for variable soilds density
30  use run, only: solve_ros
31 ! Constant solids density.
32  use physprop, only: ro_s0
33 ! Minimum solids volume fraction
34  use toleranc, only: dil_ep_s
35 
36 ! Function for evaluating solids density.
37  use eos, only: eoss
38 
39 ! Modules needed to support function.inc
40  use compar
41  use geometry
42  use indices
43  use functions
44 
45  implicit none
46 
47 ! Local Variables:
48 !---------------------------------------------------------------------/
49 ! Solids phase index
50  INTEGER :: M
51 ! Fluid cell index
52  INTEGER :: IJK
53 ! Index of the inert solids species.
54  INTEGER :: IIS
55 ! Flag for debugging.
56  LOGICAL, parameter :: dbgMode = .false.
57 
58  DOUBLE PRECISION :: minROPs
59 
60 ! Loop over all solids
61  DO m=1,mmax
62 
63 ! Variable solids density.
64  IF (solve_ros(m)) THEN
65 ! Set the index of the intert phase.
66  iis = inert_species(m)
67 ! Calculate the minimum solids denisty.
68 ! minROPs = RO_s0(M)*DIL_EP_s
69  minrops = ro_s0(m)*(dil_factor_vsd*dil_ep_s)
70 ! Debug/Development option.
71  IF(dbgmode) CALL check_set_ros()
72 
73 ! Calculate Ro_s in all fluid and flow boundary cells.
74  DO ijk = ijkstart3, ijkend3
75  IF(wall_at(ijk)) cycle
76  IF(rop_s(ijk,m) > minrops) THEN
77  ro_s(ijk,m) = eoss(ro_s0(m), x_s0(m,iis), &
78  x_s(ijk,m,iis))
79  ELSE
80 ! RO_s(IJK,M) = RO_s0(M)
81  ro_s(ijk,m) = eoss(ro_s0(m), x_s0(m,iis), &
82  dil_inert_x_vsd(m))
83  ENDIF
84  ENDDO
85  ELSE
86 ! Constant solids density.
87  DO ijk = ijkstart3, ijkend3
88  IF (wall_at(ijk)) cycle
89  ro_s(ijk,m) = ro_s0(m)
90  ENDDO
91  ENDIF
92  ENDDO
93 
94  RETURN
95 
96  CONTAINS
97 
98 !``````````````````````````````````````````````````````````````````````!
99 ! Subroutine: CHECK_SET_ROs !
100 ! Author: J.Musser Date: 21-JAN-92 !
101 ! !
102 ! Purpose: Verify that all the variable solids density information is !
103 ! present for solids phase M. !
104 ! !
105 ! Note: The check_data routines should have caught any !
106 ! problematic IC/BC specifications. This is included mainly !
107 ! for development efforts. !
108 !``````````````````````````````````````````````````````````````````````!
109  SUBROUTINE check_set_ros()
111  use exit, only: mfix_exit
112 ! Flag for who writes
113  use funits, only: dmp_log
114 ! Solids species mass fractions.
115  use fldvar, only: x_s
116 
117  use param1, only: zero
118 ! Number of phase species.
119  use physprop, only: nmax
120 ! Index of inert species.
121  use physprop, only: inert_species
122 
123  use toleranc
124 
125  implicit none
126 
127 ! Sum of solids phase mass fractions.
128  DOUBLE PRECISION :: SUM_Xs
129 ! Index of inert solids phase species.
130  INTEGER :: INERT
131 ! Integer Error Flag.
132  INTEGER :: IER(2)
133 
134 ! Error file log.
135  INTEGER, parameter :: lUnit = 8454
136  LOGICAL :: lExists
137  CHARACTER(LEN=64) :: lFName
138 
139 ! Initialize error flags.
140  ier = 0
141 
142 ! Set the inert species index.
143  inert = inert_species(m)
144 
145 ! Check all computational cells.
146  DO ijk = ijkstart3, ijkend3
147 ! Skip walls.
148  IF (wall_at(ijk)) cycle
149 ! Calculate the solids species mass fraction sum.
150  sum_xs = sum(x_s(ijk,m,:nmax(m)))
151 ! Verify that the species mass fractions are specified and valid.
152  IF(.NOT.compare(one,sum_xs)) ier(1) = ier(1)+1
153 ! Verify that the inert species mass fraction is greater than zero.
154  IF(x_s(ijk,m,inert) <= zero) ier(2) = ier(2)+1
155 
156  ENDDO
157 
158 ! An error was detected. Open a log file.
159  IF(sum(ier) /= 0) THEN
160  lfname=''
161  IF(numpes == 1) THEN
162  WRITE(lfname,"('setROs.log')")
163  ELSE
164  WRITE(lfname,"('setROs_',I6.6,'.log')") mype
165  ENDIF
166  inquire(file=trim(lfname),exist=lexists)
167  IF(lexists) THEN
168  OPEN(convert='BIG_ENDIAN',unit=lunit,file=trim(lfname),status='replace')
169  ELSE
170  OPEN(convert='BIG_ENDIAN',unit=lunit,file=trim(lfname),status='new')
171  ENDIF
172  ENDIF
173 
174 
175 ! An error was detected in species mass fraction sum.
176  IF(ier(1) /= 0)THEN
177  WRITE(lunit,1100) mype
178 ! Skip walls.
179  DO ijk = ijkstart3, ijkend3
180  IF (wall_at(ijk)) cycle
181 ! Calculate the solids species mass fraction sum.
182  sum_xs = sum(x_s(ijk,m,:nmax(m)))
183 ! Verify that the species mass fractions are specified and valid.
184  IF(.NOT.compare(one,sum_xs)) WRITE(lunit,1101) ijk, sum_xs
185  ENDDO
186  WRITE(lunit,9999)
187  ENDIF
188 
189 ! An error was detected in inert species mass fraction.
190  IF(ier(2) /= 0)THEN
191  WRITE(lunit,1200) mype
192  WRITE(lunit,1201) m
193  WRITE(lunit,1202) inert
194 ! Skip walls.
195  DO ijk = ijkstart3, ijkend3
196  IF (wall_at(ijk)) cycle
197 ! Calculate the solids species mass fraction sum.
198 ! Verify that the species mass fractions are specified and valid.
199  IF(x_s(ijk,m,inert) <= zero) WRITE(lunit,1203) &
200  ijk, x_s(ijk,m,inert)
201  ENDDO
202  WRITE(lunit,9999)
203  ENDIF
204 
205 ! Close the file, cleanup, and exit.
206  IF(sum(ier) /= 0) THEN
207  CLOSE(lunit)
208  IF(dmp_log) THEN
209  ENDIF
210  CALL mfix_exit(mype)
211  ENDIF
212 
213 
214  RETURN
215 
216  1100 FORMAT(//1x,70('*')/' From: CHECK_SET_ROs',/,' Error 1100:', &
217  ' One or more fluid cells contain invalid species mass',/ &
218  ' fractions which do NOT sum to one.'/,' > myPE = ',i6)
219 
220  1101 FORMAT(' > sum(X_s(',i6,')) = ',g12.5)
221 
222  1200 FORMAT(//1x,70('*')/' From: CHECK_SET_ROs',/,' Error 1200:', &
223  ' One or more fluid cells contain an invalid species mass',/ &
224  ' fraction for the inert material.'/,' > myPE = ',i6)
225 
226  1201 FORMAT(' > Solid Phase: ',i2)
227 
228  1202 FORMAT(' > Inert species index: ',i4)
229 
230  1203 FORMAT(' > X_s(',i6,',INERT) = ',g12.5)
231 
232  9999 FORMAT(1x,70('*')/)
233 
234  END SUBROUTINE check_set_ros
235 
236  END SUBROUTINE set_ro_s
logical dmp_log
Definition: funits_mod.f:6
integer ijkend3
Definition: compar_mod.f:80
logical function compare(V1, V2)
Definition: toleranc_mod.f:94
logical, dimension(dim_m) solve_ros
Definition: run_mod.f:250
subroutine set_ro_s
Definition: set_ro_s.f:12
double precision, dimension(dim_m, dim_n_s) x_s0
Definition: physprop_mod.f:32
integer numpes
Definition: compar_mod.f:24
subroutine check_set_ros()
Definition: set_ro_s.f:110
subroutine mfix_exit(myID, normal_termination)
Definition: exit.f:5
integer mmax
Definition: physprop_mod.f:19
double precision, dimension(:,:,:), allocatable x_s
Definition: fldvar_mod.f:78
double precision function eoss(pBase, Xs0_INERT, Xs_INERT)
Definition: eos_mod.f:155
integer, dimension(dim_m) inert_species
Definition: physprop_mod.f:39
Definition: exit.f:2
Definition: eos_mod.f:10
double precision, dimension(dim_m) dil_inert_x_vsd
Definition: physprop_mod.f:43
Definition: run_mod.f:13
double precision, parameter dil_ep_s
Definition: toleranc_mod.f:24
double precision, dimension(:,:), allocatable ro_s
Definition: fldvar_mod.f:45
integer, dimension(0:dim_m) nmax
Definition: physprop_mod.f:119
integer mype
Definition: compar_mod.f:24
integer ijkstart3
Definition: compar_mod.f:80
double precision, dimension(:,:), allocatable rop_s
Definition: fldvar_mod.f:51
double precision, dimension(dim_m) ro_s0
Definition: physprop_mod.f:28
double precision, dimension(:), allocatable x
Definition: geometry_mod.f:129
double precision, parameter zero
Definition: param1_mod.f:27
double precision dil_factor_vsd
Definition: physprop_mod.f:47