70 INTEGER,
INTENT(IN) :: nvarscal
71 REAL(RFREAL),
DIMENSION(:,:),
INTENT(IN) :: cvscal
72 REAL(RFREAL),
DIMENSION(:,:),
INTENT(INOUT) :: resscal
74 TYPE(t_patch),
POINTER :: ppatch
75 TYPE(t_region
),
POINTER :: pregion
81 CHARACTER(CHRLEN) :: rcsidentstring
82 INTEGER :: c1,bctype,distscal,ifc,ivarscal
83 REAL(RFREAL) :: flx,mf
84 REAL(RFREAL),
DIMENSION(:),
POINTER :: pmfmixt
85 REAL(RFREAL),
DIMENSION(:,:),
POINTER ::
rhs
87 TYPE(t_grid),
POINTER :: pgrid
93 rcsidentstring =
'$RCSfile: RFLU_ScalarFirstPatch.F90,v $ $Revision: 1.7 $'
95 global => pregion%global
98 'RFLU_ScalarFirstPatch.F90')
104 IF ( pregion%mixtInput%indMfMixt /= 1 )
THEN
105 CALL
errorstop(global,err_indmfmixt_invalid,__line__)
112 pgrid => pregion%grid
113 pmfmixt => ppatch%mfMixt
115 bctype = ppatch%bcType
116 distscal = valscal%distrib
122 SELECT CASE ( bctype )
128 CASE ( bc_inflow_totang,bc_inflow_veltemp )
129 DO ifc = 1,ppatch%nBFaces
130 c1 = ppatch%bf2c(ifc)
134 DO ivarscal = 1,nvarscal
135 flx = mf*valscal%vals(ivarscal,distscal*ifc)
137 resscal(ivarscal,c1) = resscal(ivarscal,c1) + flx
146 DO ifc = 1,ppatch%nBFaces
147 c1 = ppatch%bf2c(ifc)
151 DO ivarscal = 1,nvarscal
152 flx = mf*cvscal(ivarscal,c1)
154 resscal(ivarscal,c1) = resscal(ivarscal,c1) + flx
168 CASE ( bc_noslipwall_hflux,bc_noslipwall_temp )
175 DO ifc = 1,ppatch%nBFaces
176 c1 = ppatch%bf2c(ifc)
180 IF ( mf > 0.0_rfreal )
THEN
181 DO ivarscal = 1,nvarscal
182 flx = mf*cvscal(ivarscal,c1)
184 resscal(ivarscal,c1) = resscal(ivarscal,c1) + flx
187 DO ivarscal = 1,nvarscal
188 flx = mf*valscal%vals(ivarscal,distscal*ifc)
190 resscal(ivarscal,c1) = resscal(ivarscal,c1) + flx
199 CASE ( bc_injection )
200 DO ifc = 1,ppatch%nBFaces
201 c1 = ppatch%bf2c(ifc)
205 DO ivarscal = 1,nvarscal
206 flx = mf*valscal%vals(ivarscal,distscal*ifc)
208 resscal(ivarscal,c1) = resscal(ivarscal,c1) + flx
216 CASE ( bc_periodic, &
225 CALL
errorstop(global,err_reached_default,__line__)
subroutine registerfunction(global, funName, fileName)
subroutine errorstop(global, errorCode, errorLine, addMessage)
subroutine deregisterfunction(global)
subroutine rflu_scalarfirstpatch(pRegion, pPatch, nVarScal, cvScal, valScal, resScal)