65 TYPE(t_region
) :: region
69 CHARACTER(CHRLEN) :: rcsidentstring
70 INTEGER ::
a,
b,c1g,c2g,c3g,
d,e,
g,hloc1,hloc2,ic1l,ic2l,ic3l,ifc,ifcp, &
71 iv1,iv2,iv3,
j,
k,l,
m,ncells,
nfaces,vloc1,vloc2
72 INTEGER,
DIMENSION(:),
POINTER :: f2fpoles
73 INTEGER,
DIMENSION(:,:),
POINTER :: fsoles
74 REAL(RFREAL) :: avgfac,corr,
term
75 REAL(RFREAL),
DIMENSION(:),
POINTER :: vol
76 REAL(RFREAL),
DIMENSION(:,:),
POINTER :: cv
77 REAL(RFREAL),
DIMENSION(:,:,:),
POINTER :: int31oles,int32oles
84 rcsidentstring =
'$RCSfile: RFLU_ComputeIntegral3OLES.F90,v $ $Revision: 1.5 $'
86 global => region%global
89 'RFLU_ComputeIntegral3OLES.F90')
91 IF ( region%mixt%cvState == cv_mixt_state_cons )
THEN
92 CALL
errorstop(global,err_cv_state_invalid,__line__)
99 fsoles => region%grid%fsOLES
100 f2fpoles => region%grid%f2fpOLES
102 int31oles => region%grid%int31OLES
103 int32oles => region%grid%int32OLES
105 vol => region%grid%vol
108 ncells =
SIZE(region%grid%fsOLES,1)
109 nfaces = region%grid%nFaces
110 avgfac = 3.0_rfreal/
REAL(nFaces,KIND=RFREAL)
116 int31oles(:,:,:) = 0.0_rfreal
117 int32oles(:,:,:) = 0.0_rfreal
131 c1g = fsoles(ic1l,ifc)
135 c2g = fsoles(ic2l,ifc)
140 c3g = fsoles(ic3l,ifc)
144 term = vol(c1g)*vol(c2g)*vol(c3g)
158 corr =
term*cv(iv1+1,c1g)*cv(iv2+1,c2g)*cv(iv3+1,c3g)
176 int31oles(ifcp,vloc1,hloc1) = int31oles(ifcp,vloc1,hloc1) &
178 int32oles(ifcp,vloc2,hloc2) = int32oles(ifcp,vloc2,hloc2) &
196 int31oles(:,:,:) =
term*int31oles(:,:,:)
197 int32oles(:,:,:) =
term*int32oles(:,:,:)
subroutine registerfunction(global, funName, fileName)
subroutine rflu_computeintegral3oles(region)
INTEGER function, public rflu_geti1posoles(l, d)
INTEGER function, public rflu_getlposoles(j, a)
INTEGER function, public rflu_geti4posoles(l, m, d, e, nCells)
subroutine errorstop(global, errorCode, errorLine, addMessage)
INTEGER function, public rflu_getqposoles(j, k, b, g, nCells)
subroutine deregisterfunction(global)