72 TYPE(t_region
),
POINTER :: pregion
78 CHARACTER(CHRLEN) :: rcsidentstring
79 INTEGER :: ccsize,errorflag,icg,icl,ipcl,ivar
80 INTEGER,
DIMENSION(:),
ALLOCATABLE :: cc
81 REAL(RFREAL) :: delfrac,xdel,
xmax,
xmin,xpcl,ydel,
ymax,
ymin,ypcl,zdel,
zmax, &
84 TYPE(t_grid),
POINTER :: pgrid
85 TYPE(t_plag),
POINTER :: pplag
92 '$RCSfile: PLAG_RFLU_InitSolSerial_3D.F90,v $ $Revision: 1.3 $'
94 global => pregion%global
97 'PLAG_RFLU_InitSolSerial_3D.F90')
99 IF ( global%verbLevel > verbose_none )
THEN
100 WRITE(stdout,
'(A,1X,A)') solver_name,
'Initializing particle solution '// &
101 'for serial region in 3d...'
102 WRITE(stdout,
'(A,3X,A,1X,I5.5)') solver_name,
'Global region:', &
103 pregion%iRegionGlobal
110 pgrid => pregion%grid
112 pplag => pregion%plag
114 ccsize =
min(100,pgrid%nCells)
116 delfrac = 0.01_rfreal
122 xmin = minval(pgrid%xyz(xcoord,1:pgrid%nVert))
123 xmax = maxval(pgrid%xyz(xcoord,1:pgrid%nVert))
124 ymin = minval(pgrid%xyz(ycoord,1:pgrid%nVert))
125 ymax = maxval(pgrid%xyz(ycoord,1:pgrid%nVert))
126 zmin = minval(pgrid%xyz(zcoord,1:pgrid%nVert))
127 zmax = maxval(pgrid%xyz(zcoord,1:pgrid%nVert))
147 pgrid%cofg(ycoord,1:pgrid%nCells), &
148 pgrid%cofg(zcoord,1:pgrid%nCells), &
151 ALLOCATE(cc(ccsize),stat=errorflag)
152 global%error = errorflag
153 IF ( global%error /= err_none )
THEN
154 CALL
errorstop(global,err_allocate,__line__,
'cc')
164 DO ipcl = 1,pplag%nPcls
170 xpcl = pplag%cv(cv_plag_xpos,ipcl)
171 ypcl = pplag%cv(cv_plag_ypos,ipcl)
172 zpcl = pplag%cv(cv_plag_zpos,ipcl)
180 cellloop:
DO icl = 1,ccsize
184 pplag%aiv(aiv_plag_icells,ipcl) = icg
185 pplag%aiv(aiv_plag_regini,ipcl) = pregion%iRegionGlobal
198 DEALLOCATE(cc,stat=errorflag)
199 global%error = errorflag
200 IF ( global%error /= err_none )
THEN
201 CALL
errorstop(global,err_deallocate,__line__,
'cc')
210 IF ( global%verbLevel > verbose_none )
THEN
211 WRITE(stdout,
'(A,1X,A)') solver_name, &
212 'Initializing particle solution for serial region in 3d done.'
subroutine, public rflu_buildcell2facelist(pRegion)
subroutine, public rflu_destroycell2facelist(pRegion)
subroutine, public rflu_queryoctree(XPT, YPT, ZPT, NUMP, NEIGHP)
subroutine, public rflu_createcell2facelist(pRegion)
subroutine registerfunction(global, funName, fileName)
subroutine, public rflu_buildoctree(XI, YI, ZI, XLOW, XUPP, YLOW, YUPP, ZLOW, ZUPP)
subroutine, public rflu_destroyoctree(global)
LOGICAL function, public rflu_ict_testincell(pRegion, xLoc, yLoc, zLoc, icg)
Vector_n min(const Array_n_const &v1, const Array_n_const &v2)
subroutine plag_rflu_initsolserial_3d(pRegion)
subroutine errorstop(global, errorCode, errorLine, addMessage)
subroutine deregisterfunction(global)
subroutine, public rflu_createoctree(global, nPoints)