67 TYPE(t_region
),
POINTER :: pregion
73 CHARACTER(CHRLEN) :: rcsidentstring
74 INTEGER :: errorflag,icont,infloopcntr,ipcl,npcls
75 INTEGER,
POINTER,
DIMENSION(:) :: pcvplagmass
76 INTEGER,
POINTER,
DIMENSION(:,:) :: paiv
77 REAL(RFREAL) :: delfrac,diamdel,diammax,diammin,diam,heatcapsum,massratio, &
78 massfluxratiosum,massfluxratiosumr,massfluxratiolimit, &
79 masssum,npclsfrac,rn,sploaddel,sploadmax,sploadmin,spload, &
80 tempdel,tempmax,tempmin,temp,udel,umax,umin,u,vdel,vmin, &
81 vmax,
v,wdel,wmin,wmax,w,xdel,xloc,
xmax,
xmin,ydel,yloc,
ymax, &
83 REAL(RFREAL),
POINTER,
DIMENSION(:) :: pdens,pinjcmassfluxratio,pspcheat
84 REAL(RFREAL),
POINTER,
DIMENSION(:,:) :: parv,pcv
86 TYPE(t_grid),
POINTER :: pgrid
93 '$RCSfile: PLAG_RFLU_InitSolutionRandom.F90,v $ $Revision: 1.13 $'
95 global => pregion%global
98 'PLAG_RFLU_InitSolutionRandom.F90')
100 IF ( global%verbLevel > verbose_none )
THEN
101 WRITE(stdout,
'(A,1X,A)') solver_name, &
102 'Initializing particle solution from random state...'
109 pgrid => pregion%grid
111 delfrac = 0.01_rfreal
113 pregion%plag%nextIdNumber = pregion%plag%nPcls
115 npcls = pregion%plag%nPcls
116 npclsfrac = 0.1_rfreal
120 massfluxratiolimit = 1.0e-10_rfreal
126 xmin = pregion%plagInput%iniRandXMin
127 xmax = pregion%plagInput%iniRandXMax
128 ymin = pregion%plagInput%iniRandYMin
129 ymax = pregion%plagInput%iniRandYMax
130 zmin = pregion%plagInput%iniRandZMin
131 zmax = pregion%plagInput%iniRandZMax
141 pdens => pregion%plagInput%dens
142 pspcheat => pregion%plagInput%spht
143 pinjcmassfluxratio => pregion%plagInput%injcMassFluxRatio
145 pcvplagmass => pregion%plag%cvPlagMass
146 paiv => pregion%plag%aiv
147 parv => pregion%plag%arv
148 pcv => pregion%plag%cv
150 massfluxratiosum =
sum(pinjcmassfluxratio)
156 IF ( massfluxratiosum > massfluxratiolimit )
THEN
157 massfluxratiosumr = 1.0_rfreal/massfluxratiosum
159 massfluxratiosumr = 1.0_rfreal
162 diammin = pregion%plagInput%iniRandDiamMin
163 diammax = pregion%plagInput%iniRandDiamMax
164 tempmin = pregion%plagInput%iniRandTempMin
165 tempmax = pregion%plagInput%iniRandTempMax
166 sploadmin = pregion%plagInput%iniRandSpLoadMin
167 sploadmax = pregion%plagInput%iniRandSpLoadMax
169 umin = pregion%plagInput%iniRandUMin
170 umax = pregion%plagInput%iniRandUMax
171 vmin = pregion%plagInput%iniRandVMin
172 vmax = pregion%plagInput%iniRandVMax
173 wmin = pregion%plagInput%iniRandWMin
174 wmax = pregion%plagInput%iniRandWMax
176 diamdel = diammax - diammin
177 tempdel = tempmax - tempmin
178 sploaddel = sploadmax - sploadmin
190 infloopcntr = infloopcntr + 1
192 IF ( ipcl == npcls )
THEN
203 xloc =
xmin + xdel*rn
206 yloc =
ymin + ydel*rn
209 zloc =
zmin + zdel*rn
223 diam = diammin + diamdel*rn
226 temp = tempmin + tempdel*rn
229 spload = sploadmin + sploaddel*rn
244 pcv(cv_plag_xpos,ipcl) = xloc
245 pcv(cv_plag_ypos,ipcl) = yloc
246 pcv(cv_plag_zpos,ipcl) = zloc
248 DO icont = 1,pregion%plagInput%nCont
249 massratio = pinjcmassfluxratio(icont)*massfluxratiosumr
250 pcv(pcvplagmass(icont),ipcl) = pdens(icont)*massratio*global%pi/6.0_rfreal &
254 heatcapsum =
sum(pcv(pcvplagmass(:),ipcl)*pspcheat(:))
255 masssum =
sum(pcv(pcvplagmass(:),ipcl))
257 pcv(cv_plag_xmom,ipcl) = masssum*u
258 pcv(cv_plag_ymom,ipcl) = masssum*
v
259 pcv(cv_plag_zmom,ipcl) = masssum*w
260 pcv(cv_plag_ener,ipcl) = heatcapsum*temp
262 parv(arv_plag_spload,ipcl) = spload
263 paiv(aiv_plag_pidini,ipcl) = ipcl
264 paiv(aiv_plag_icells,ipcl) = crazy_value_int
265 paiv(aiv_plag_regini,ipcl) = crazy_value_int
271 IF ( ipcl/
REAL(nPcls,KIND=RFREAL) > npclsfrac ) then
272 npclsfrac = npclsfrac + 0.1_rfreal
274 IF ( global%verbLevel > verbose_low )
THEN
275 WRITE(stdout,
'(A,3X,A,1X,I10,1X,A)') solver_name,
'Generated',ipcl, &
284 IF ( infloopcntr >= 100*npcls )
THEN
285 CALL
errorstop(global,err_infinite_loop,__line__)
293 IF ( global%verbLevel > verbose_none )
THEN
294 WRITE(stdout,
'(A,1X,A)') solver_name, &
295 'Initializing particle solution from random state done.'
Tfloat sum() const
Return the sum of all the pixel values in an image.
subroutine registerfunction(global, funName, fileName)
REAL(RFREAL) function rand1uniform(rdata)
*********************************************************************Illinois Open Source License ****University of Illinois NCSA **Open Source License University of Illinois All rights reserved ****Developed free of to any person **obtaining a copy of this software and associated documentation to deal with the Software without including without limitation the rights to and or **sell copies of the and to permit persons to whom the **Software is furnished to do subject to the following this list of conditions and the following disclaimers ****Redistributions in binary form must reproduce the above **copyright this list of conditions and the following **disclaimers in the documentation and or other materials **provided with the distribution ****Neither the names of the Center for Simulation of Advanced the University of nor the names of its **contributors may be used to endorse or promote products derived **from this Software without specific prior written permission ****THE SOFTWARE IS PROVIDED AS WITHOUT WARRANTY OF ANY **EXPRESS OR INCLUDING BUT NOT LIMITED TO THE WARRANTIES **OF FITNESS FOR A PARTICULAR PURPOSE AND **NONINFRINGEMENT IN NO EVENT SHALL THE CONTRIBUTORS OR **COPYRIGHT HOLDERS BE LIABLE FOR ANY DAMAGES OR OTHER WHETHER IN AN ACTION OF TORT OR **ARISING OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE **USE OR OTHER DEALINGS WITH THE SOFTWARE v
subroutine errorstop(global, errorCode, errorLine, addMessage)
subroutine deregisterfunction(global)
subroutine plag_rflu_initsolutionrandom(pRegion)