Nodes of different colours represent the following:
Solid arrows point from a parent (sub)module to the submodule which is descended from it. Dashed arrows point from a module being used to the module or program unit using it. Where possible, edges connecting nodes are given different colours to make them easier to distinguish in large graphs.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer, | intent(in) | :: | ZoneNum |
Nodes of different colours represent the following:
Solid arrows point from a procedure to one which it calls. Dashed arrows point from an interface to procedures which implement that interface. This could include the module procedures in a generic interface or the implementation in a submodule of an interface in a parent module. Where possible, edges connecting nodes are given different colours to make them easier to distinguish in large graphs.
Nodes of different colours represent the following:
Solid arrows point from a procedure to one which it calls. Dashed arrows point from an interface to procedures which implement that interface. This could include the module procedures in a generic interface or the implementation in a submodule of an interface in a parent module. Where possible, edges connecting nodes are given different colours to make them easier to distinguish in large graphs.
SUBROUTINE EvolveParaUCSDCV(ZoneNum)
! SUBROUTINE INFORMATION:
! AUTHOR G. Carrilho da Graca
! DATE WRITTEN October 2004
! MODIFIED 8/2013 - Sam Brunswick
! To incorporate an improved model
! and add modeling of multiple jets
! RE-ENGINEERED -
! PURPOSE OF THIS SUBROUTINE:
! Subroutine for parameter actualization in the UCSD Cross Ventilation model.
!
! METHODOLOGY EMPLOYED:
! -
! -
! -
! -
! REFERENCES:
! -
! -
! USE STATEMENTS:
USE Psychrometrics
USE DataHeatBalFanSys
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER,INTENT (IN) :: ZoneNum !
! SUBROUTINE PARAMETER DEFINITIONS:
REAL(r64),PARAMETER :: MinUin = 0.2d0
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: Ctd ! counter
INTEGER :: Ctd2 ! counter
INTEGER :: OPtr ! counter
REAL(r64), SAVE :: Win ! Inflow aperture width
REAL(r64), SAVE :: Aroom ! Room area cross section
REAL(r64), SAVE :: Wroom ! Room width
REAL(r64) :: Uin ! Inflow air velocity [m/s]
REAL(r64) :: CosPhi ! Angle (in degrees) between the wind and the outward normal of the dominant surface
REAL(r64) :: SurfNorm ! Outward normal of surface
REAL(r64) :: SumToZone ! Sum of velocities through
REAL(r64) :: MaxFlux
INTEGER :: MaxSurf
REAL(r64) :: XX
REAL(r64) :: YY
REAL(r64) :: ZZ
REAL(r64) :: XX_Wall
REAL(r64) :: YY_Wall
REAL(r64) :: ZZ_Wall
REAL(r64) :: ActiveSurfNum
INTEGER :: NSides ! Number of sides in surface
INTEGER :: CompNum = 0 ! AirflowNetwork Component number
INTEGER :: TypeNum = 0 ! Airflownetwork Type Number within a component
INTEGER :: NodeNum1 = 0 ! The first node number in an AirflowNetwork linkage data
INTEGER :: NodeNum2 = 0 ! The Second node number in an AirflowNetwork linkage data
maxsurf=0
sumtozone=0.0d0
maxflux=0.0d0
RecInflowRatio(ZoneNum)=0.0d0
! Identify the dominant aperture:
MaxSurf=AirflowNetworkSurfaceUCSDCV(ZoneNum,1)
IF (Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%Zone == ZoneNum) THEN
! this is a direct airflow network aperture
SumToZone=AirflowNetworkLinkSimu(AirflowNetworkSurfaceUCSDCV(ZoneNum,1))%VolFlow2
MaxFlux=AirflowNetworkLinkSimu(AirflowNetworkSurfaceUCSDCV(ZoneNum,1))%VolFlow2
ELSE
! this is an indirect airflow network aperture
SumToZone=AirflowNetworkLinkSimu(AirflowNetworkSurfaceUCSDCV(ZoneNum,1))%VolFlow
MaxFlux=AirflowNetworkLinkSimu(AirflowNetworkSurfaceUCSDCV(ZoneNum,1))%VolFlow
END IF
DO Ctd2=2,AirflowNetworkSurfaceUCSDCV(ZoneNum,0)
IF (Surface(MultizoneSurfaceData(AirflowNetworkSurfaceUCSDCV(ZoneNum,ctd2))%SurfNum)%Zone== ZoneNum) THEN
IF (AirflowNetworkLinkSimu(AirflowNetworkSurfaceUCSDCV(ZoneNum,Ctd2))%VolFlow2 > MaxFlux) THEN
MaxFlux=AirflowNetworkLinkSimu(AirflowNetworkSurfaceUCSDCV(ZoneNum,Ctd2))%VolFlow2
MaxSurf=AirflowNetworkSurfaceUCSDCV(ZoneNum,Ctd2)
END IF
SumToZone=SumToZone+AirflowNetworkLinkSimu(AirflowNetworkSurfaceUCSDCV(ZoneNum,Ctd2))%VolFlow2
ELSE
IF (AirflowNetworkLinkSimu(AirflowNetworkSurfaceUCSDCV(ZoneNum,Ctd2))%VolFlow > MaxFlux) THEN
MaxFlux=AirflowNetworkLinkSimu(AirflowNetworkSurfaceUCSDCV(ZoneNum,Ctd2))%VolFlow
MaxSurf=AirflowNetworkSurfaceUCSDCV(ZoneNum,Ctd2)
END IF
SumToZone=SumToZone+AirflowNetworkLinkSimu(AirflowNetworkSurfaceUCSDCV(ZoneNum,Ctd2))%VolFlow
END IF
END DO
! Check if wind direction is within +/- 90 degrees of the outward normal of the dominant surface
SurfNorm=Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%Azimuth
CosPhi=COS((WindDir-SurfNorm)*DegToRadians)
IF (CosPhi <= 0) THEN
AirModel(ZoneNum)%SimAirModel= .FALSE.
CVJetRecFlows(ZoneNum,:)%Ujet=0.0d0
CVJetRecFlows(ZoneNum,:)%Urec=0.0d0
Urec(ZoneNum)=0.0d0
Ujet(ZoneNum)=0.0d0
Qrec(ZoneNum)=0.0d0
IF (Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%ExtBoundCond>0) THEN
Tin(ZoneNum)=MAT(surface(Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%ExtBoundCond)%zone)
ELSEIF(Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%ExtBoundCond == ExternalEnvironment) THEN
Tin(ZoneNum)=Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%OutDryBulbTemp
ELSEIF (Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%ExtBoundCond == Ground) THEN
Tin(ZoneNum)=Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%OutDryBulbTemp
ELSEIF (Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%ExtBoundCond == OtherSideCoefNoCalcExt .or. &
Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%ExtBoundCond == OtherSideCoefCalcExt) THEN
OPtr=Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%OSCPtr
OSC(OPtr)%OSCTempCalc = ( OSC(OPtr)%ZoneAirTempCoef*MAT(ZoneNum) &
+OSC(OPtr)%ExtDryBulbCoef*Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%OutDryBulbTemp &
+OSC(OPtr)%ConstTempCoef*OSC(OPtr)%ConstTemp &
+OSC(OPtr)%GroundTempCoef*GroundTemp &
+OSC(OPtr)%WindSpeedCoef &
*Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%WindSpeed &
*Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%OutDryBulbTemp )
Tin(ZoneNum) = OSC(OPtr)%OSCTempCalc
ELSE
Tin(ZoneNum)=Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%OutDryBulbTemp
END IF
RETURN
END IF
! Calculate the opening area for all apertures
DO Ctd=1,AirflowNetworkSurfaceUCSDCV(ZoneNum,0)
CompNum = AirflowNetworkLinkageData(Ctd)%CompNum
TypeNum = AirflowNetworkCompData(CompNum)%TypeNum
IF (AirflowNetworkCompData(CompNum)%CompTypeNum == CompTypeNum_DOP) THEN
CVJetRecFlows(ZoneNum,Ctd)%Area=SurfParametersCVDV(Ctd)%Width* &
SurfParametersCVDV(Ctd)%Height*MultizoneSurfaceData(Ctd)%OpenFactor
ELSE IF (AirflowNetworkCompData(CompNum)%CompTypeNum == CompTypeNum_SCR) THEN
CVJetRecFlows(ZoneNum,Ctd)%Area=SurfParametersCVDV(Ctd)%Width*SurfParametersCVDV(Ctd)%Height
ELSE
CALL ShowSevereError('RoomAirModelCrossVent:EvolveParaUCSDCV: Illegal leakage component referenced '// &
'in the cross ventilation room air model')
CALL ShowContinueError('Surface '//TRIM(AirflowNetworkLinkageData(Ctd)%Name)//' in zone '//TRIM(Zone(ZoneNum)%Name) &
//' uses leakage component '//TRIM(AirflowNetworkLinkageData(Ctd)%CompName))
CALL ShowContinueError('Only leakage component types AirflowNetwork:MultiZone:Component:DetailedOpening and ')
CALL ShowContinueError('AirflowNetwork:MultiZone:Surface:Crack can be used with the cross ventilation room air model')
CALL ShowFatalError('Previous severe error causes program termination')
END IF
END DO
! Calculate Droom, Wroom, Dstar
! Droom the distance between the average point of the base surface of the airflow network Surface (if the base surface
! is a Window or Door it looks for the second base surface).
! Dstar is Droom corrected for wind angle
Wroom=Zone(ZoneNum)%Volume/Zone(ZoneNum)%FloorArea
IF ((Surface(Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%BaseSurf)%Sides == 3) .OR. &
(Surface(Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%BaseSurf)%Sides == 4)) THEN
XX=Surface(Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%BaseSurf)%Centroid%X
YY=Surface(Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%BaseSurf)%Centroid%Y
ZZ=Surface(Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%BaseSurf)%Centroid%Z
ELSE
! If the surface has more than 4 vertex then average the vertex coordinates in X, Y and Z.
NSides=Surface(Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%BaseSurf)%Sides
XX=SUM(Surface(Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%BaseSurf)%Vertex(1:NSides)%X) / REAL(NSides,r64)
YY=SUM(Surface(Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%BaseSurf)%Vertex(1:NSides)%Y) / REAL(NSides,r64)
ZZ=SUM(Surface(Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%BaseSurf)%Vertex(1:NSides)%Z) / REAL(NSides,r64)
END IF
DO Ctd=PosZ_Wall(2*ZoneNum-1),PosZ_Wall(2*ZoneNum)
IF ((Surface(Apos_Wall(Ctd))%Sides==3) .OR. (Surface(Apos_Wall(Ctd))%Sides==4)) THEN
XX_Wall=Surface(Apos_Wall(Ctd))%Centroid%X
YY_Wall=Surface(Apos_Wall(Ctd))%Centroid%Y
ZZ_Wall=Surface(Apos_Wall(Ctd))%Centroid%Z
ELSE
NSides=Surface(Apos_Wall(Ctd))%Sides
XX_Wall=SUM(Surface(Apos_Wall(Ctd))%Vertex(1:NSides)%X)/REAL(NSides,r64)
YY_Wall=SUM(Surface(Apos_Wall(Ctd))%Vertex(1:NSides)%Y)/REAL(NSides,r64)
ZZ_Wall=SUM(Surface(Apos_Wall(Ctd))%Vertex(1:NSides)%Z)/REAL(NSides,r64)
END IF
IF (SQRT((XX-XX_Wall)**2+(YY-YY_Wall)**2+(ZZ-ZZ_Wall)**2)>Droom(ZoneNum)) THEN
Droom(ZoneNum)=SQRT((XX-XX_Wall)**2+(YY-YY_Wall)**2+(ZZ-ZZ_Wall)**2)
END IF
Dstar(ZoneNum)=MIN(Droom(ZoneNum)/CosPhi,SQRT(Wroom**2+Droom(ZoneNum)**2))
END DO
! Room area
Aroom=Zone(ZoneNum)%Volume/Droom(ZoneNum)
!Populate an array of inflow volume fluxes (Fin) for all apertures in the zone
!Calculate inflow velocity (%Uin) for each aperture in the zone
DO Ctd=1,AirflowNetworkSurfaceUCSDCV(ZoneNum,0)
IF (Surface(MultizoneSurfaceData(Ctd)%SurfNum)%Zone == ZoneNum) THEN
! this is a direct airflow network aperture
CVJetRecFlows(ZoneNum,Ctd)%Fin=AirflowNetworkLinkSimu(AirflowNetworkSurfaceUCSDCV(ZoneNum,Ctd))%VolFlow2
ELSE
! this is an indirect airflow network aperture
CVJetRecFlows(ZoneNum,Ctd)%Fin=AirflowNetworkLinkSimu(AirflowNetworkSurfaceUCSDCV(ZoneNum,Ctd))%VolFlow
END IF
IF (CVJetRecFlows(ZoneNum,Ctd)%Area /= 0) THEN
CVJetRecFlows(ZoneNum,Ctd)%Uin=CVJetRecFlows(ZoneNum,Ctd)%Fin/CVJetRecFlows(ZoneNum,Ctd)%Area
ELSE
CVJetRecFlows(ZoneNum,Ctd)%Uin=0.0d0
ENDIF
END DO
! Verify if Uin is higher than minimum for each aperture
! Create a flow flag for each aperture
! Calculate the total area of all active apertures
ActiveSurfNum=0.0d0
Ain(ZoneNum)=0.0d0
DO Ctd=1,AirflowNetworkSurfaceUCSDCV(ZoneNum,0)
IF (CVJetRecFlows(ZoneNum,Ctd)%Uin <= MinUin) THEN
CVJetRecFlows(ZoneNum,Ctd)%FlowFlag=0
ELSE
CVJetRecFlows(ZoneNum,Ctd)%FlowFlag=1
END IF
ActiveSurfNum = ActiveSurfNum + CVJetRecFlows(ZoneNum,Ctd)%FlowFlag
Ain(ZoneNum)=Ain(ZoneNum)+CVJetRecFlows(ZoneNum,Ctd)%Area*CVJetRecFlows(ZoneNum,Ctd)%FlowFlag
END DO
! Verify if any of the apertures have minimum flow
IF (ActiveSurfNum == 0 ) THEN
AirModel(ZoneNum)%SimAirModel= .FALSE.
IF (Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%ExtBoundCond>0) THEN
Tin(ZoneNum)=MAT(surface(Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%ExtBoundCond)%zone)
ELSEIF(Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%ExtBoundCond == ExternalEnvironment) THEN
Tin(ZoneNum)=Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%OutDryBulbTemp
ELSEIF (Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%ExtBoundCond == Ground) THEN
Tin(ZoneNum)=Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%OutDryBulbTemp
ELSEIF (Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%ExtBoundCond == OtherSideCoefNoCalcExt .or. &
Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%ExtBoundCond == OtherSideCoefCalcExt) THEN
OPtr=Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%OSCPtr
OSC(OPtr)%OSCTempCalc =( OSC(OPtr)%ZoneAirTempCoef*MAT(ZoneNum) &
+OSC(OPtr)%ExtDryBulbCoef*Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%OutDryBulbTemp &
+OSC(OPtr)%ConstTempCoef*OSC(OPtr)%ConstTemp &
+OSC(OPtr)%GroundTempCoef*GroundTemp &
+OSC(OPtr)%WindSpeedCoef &
*Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%WindSpeed &
*Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%OutDryBulbTemp )
Tin(ZoneNum) = OSC(OPtr)%OSCTempCalc
ELSE
Tin(ZoneNum)=Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%OutDryBulbTemp
END IF
Urec(ZoneNum)=0.0d0
Ujet(ZoneNum)=0.0d0
Qrec(ZoneNum)=0.0d0
CVJetRecFlows(ZoneNum,:)%Ujet=0.0d0
CVJetRecFlows(ZoneNum,:)%Urec=0.0d0
RETURN
END IF
! Calculate Uin, the area weighted average velocity of all the active apertures in the zone
! Calculate Qtot, the total volumetric flow rate through all active openings in the zone
Uin=0.0d0
DO Ctd=1,AirflowNetworkSurfaceUCSDCV(ZoneNum,0)
Uin=Uin+CVJetRecFlows(ZoneNum,Ctd)%Area*CVJetRecFlows(ZoneNum,Ctd)%Uin*CVJetRecFlows(ZoneNum,Ctd)%FlowFlag/Ain(ZoneNum)
END DO
!Verify if Uin is higher than minimum:
IF (Uin < MinUin) THEN
AirModel(ZoneNum)%SimAirModel= .FALSE.
Urec(ZoneNum)=0.0d0
Ujet(ZoneNum)=0.0d0
Qrec(ZoneNum)=0.0d0
RecInflowRatio(ZoneNum)=0.0d0
CVJetRecFlows(ZoneNum,:)%Ujet=0.0d0
CVJetRecFlows(ZoneNum,:)%Urec=0.0d0
IF (Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%ExtBoundCond>0) THEN
Tin(ZoneNum)=MAT(surface(Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%ExtBoundCond)%zone)
ELSEIF(Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%ExtBoundCond == ExternalEnvironment) THEN
Tin(ZoneNum)=Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%OutDryBulbTemp
ELSEIF (Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%ExtBoundCond == Ground) THEN
Tin(ZoneNum)=Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%OutDryBulbTemp
ELSEIF (Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%ExtBoundCond == OtherSideCoefNoCalcExt .or. &
Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%ExtBoundCond == OtherSideCoefCalcExt) THEN
OPtr=Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%OSCPtr
OSC(OPtr)%OSCTempCalc = ( OSC(OPtr)%ZoneAirTempCoef*MAT(ZoneNum) &
+OSC(OPtr)%ExtDryBulbCoef*Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%OutDryBulbTemp &
+OSC(OPtr)%ConstTempCoef*OSC(OPtr)%ConstTemp &
+OSC(OPtr)%GroundTempCoef*GroundTemp &
+OSC(OPtr)%WindSpeedCoef &
*Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%WindSpeed &
*Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%OutDryBulbTemp )
Tin(ZoneNum) = OSC(OPtr)%OSCTempCalc
ELSE
Tin(ZoneNum)=Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%OutDryBulbTemp
END IF
RETURN
END IF
! Evaluate parameter that determines whether recirculations are present
DO Ctd=1,TotUCSDCV
IF(ZoneNum == ZoneUCSDCV(Ctd)%ZonePtr) THEN
IF (Ain(ZoneNum)/Aroom >1.0d0/2.0d0) THEN
JetRecAreaRatio(ZoneNum)=1.0d0
ELSE
JetRecAreaRatio(ZoneNum)=Sqrt(Ain(ZoneNum)/Aroom)
ENDIF
ENDIF
ENDDO
AirModel(ZoneNum)%SimAirModel= .TRUE.
! Calculate jet and recirculation velocities for all active apertures
Ujet(ZoneNum)=0.0d0
Urec(ZoneNum)=0.0d0
Qrec(ZoneNum)=0.0d0
Qtot(ZoneNum)=0.0d0
CVJetRecFlows(ZoneNum,:)%Ujet=0.0d0
CVJetRecFlows(ZoneNum,:)%Urec=0.0d0
CVJetRecFlows(ZoneNum,:)%Qrec=0.0d0
DO Ctd=1,AirflowNetworkSurfaceUCSDCV(ZoneNum,0)
IF (CVJetRecFlows(ZoneNum,Ctd)%Uin /=0) THEN
CVJetRecFlows(ZoneNum,Ctd)%Vjet = CVJetRecFlows(ZoneNum,Ctd)%Uin * SQRT(CVJetRecFlows(ZoneNum,Ctd)%Area) * &
6.3d0*LOG(Dstar(ZoneNum) / (6.0d0 * SQRT(CVJetRecFlows(ZoneNum,Ctd)%Area))) / Dstar(ZoneNum)
CVJetRecFlows(ZoneNum,Ctd)%Yjet = Cjet1 * &
SQRT(CVJetRecFlows(ZoneNum,Ctd)%Area/Aroom) * CVJetRecFlows(ZoneNum,Ctd)%Vjet / CVJetRecFlows(ZoneNum,Ctd)%Uin + Cjet2
CVJetRecFlows(ZoneNum,Ctd)%Yrec = Crec1 * &
SQRT(CVJetRecFlows(ZoneNum,Ctd)%Area/Aroom) * CVJetRecFlows(ZoneNum,Ctd)%Vjet / CVJetRecFlows(ZoneNum,Ctd)%Uin + Crec2
CVJetRecFlows(ZoneNum,Ctd)%YQrec = CrecFlow1 * &
SQRT(CVJetRecFlows(ZoneNum,Ctd)%Area*Aroom) * CVJetRecFlows(ZoneNum,Ctd)%Vjet / CVJetRecFlows(ZoneNum,Ctd)%Uin + CrecFlow2
CVJetRecFlows(ZoneNum,Ctd)%Ujet = CVJetRecFlows(ZoneNum,Ctd)%FlowFlag * CVJetRecFlows(ZoneNum,Ctd)%Yjet / &
CVJetRecFlows(ZoneNum,Ctd)%Uin
CVJetRecFlows(ZoneNum,Ctd)%Urec = CVJetRecFlows(ZoneNum,Ctd)%FlowFlag * CVJetRecFlows(ZoneNum,Ctd)%Yrec / &
CVJetRecFlows(ZoneNum,Ctd)%Uin
CVJetRecFlows(ZoneNum,Ctd)%Qrec = CVJetRecFlows(ZoneNum,Ctd)%FlowFlag * CVJetRecFlows(ZoneNum,Ctd)%YQrec / &
CVJetRecFlows(ZoneNum,Ctd)%Uin
Ujet(ZoneNum) = Ujet(ZoneNum) + CVJetRecFlows(ZoneNum,Ctd)%Area * CVJetRecFlows(ZoneNum,Ctd)%Ujet / Ain(ZoneNum)
Urec(ZoneNum) = Urec(ZoneNum) + CVJetRecFlows(ZoneNum,Ctd)%Area * CVJetRecFlows(ZoneNum,Ctd)%Urec / Ain(ZoneNum)
Qrec(ZoneNum) = Qrec(ZoneNum) + CVJetRecFlows(ZoneNum,Ctd)%Qrec
Qtot(ZoneNum) = Qtot(ZoneNum)+CVJetRecFlows(ZoneNum,Ctd)%Fin*CVJetRecFlows(ZoneNum,Ctd)%FlowFlag
IF (ActiveSurfNum > 1) THEN ! Recirculation flow for multiple surfaces is 90% of flow with one surface
Urec(ZoneNum) = 0.9d0 * Urec(ZoneNum) + CVJetRecFlows(ZoneNum,Ctd)%Area * CVJetRecFlows(ZoneNum,Ctd)%Urec / Ain(ZoneNum)
ELSE
Urec(ZoneNum) = Urec(ZoneNum) + CVJetRecFlows(ZoneNum,Ctd)%Area * CVJetRecFlows(ZoneNum,Ctd)%Urec / Ain(ZoneNum)
END IF
ENDIF
END DO
! Ratio between recirculation flow rate and total inflow rate
IF (Qtot(ZoneNum) /=0) THEN
RecInflowRatio(ZoneNum) = Qrec(ZoneNum)/Qtot(ZoneNum)
ELSE
RecInflowRatio(ZoneNum) = 0.0d0
ENDIF
! Set Tin based on external conditions of the dominant aperture
IF (Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%ExtBoundCond <= 0) THEN
IF(Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%ExtBoundCond == ExternalEnvironment) THEN
Tin(ZoneNum)=Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%OutDryBulbTemp
ELSEIF (Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%ExtBoundCond == Ground) THEN
Tin(ZoneNum)=Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%OutDryBulbTemp
ELSEIF (Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%ExtBoundCond == OtherSideCoefNoCalcExt .or. &
Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%ExtBoundCond == OtherSideCoefCalcExt) THEN
OPtr=Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%OSCPtr
OSC(OPtr)%OSCTempCalc = ( OSC(OPtr)%ZoneAirTempCoef*MAT(ZoneNum) &
+OSC(OPtr)%ExtDryBulbCoef*Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%OutDryBulbTemp &
+OSC(OPtr)%ConstTempCoef*OSC(OPtr)%ConstTemp &
+OSC(OPtr)%GroundTempCoef*GroundTemp &
+OSC(OPtr)%WindSpeedCoef &
*Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%WindSpeed &
*Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%OutDryBulbTemp )
Tin(ZoneNum) = OSC(OPtr)%OSCTempCalc
ELSE
Tin(ZoneNum)=Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%OutDryBulbTemp
END IF
ELSE
! adiabatic surface
IF (MultizoneSurfaceData(MaxSurf)%SurfNum == Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%ExtBoundCond) THEN
NodeNum1 = AirflowNetworkLinkageData(MaxSurf)%NodeNums(1)
NodeNum2 = AirflowNetworkLinkageData(MaxSurf)%NodeNums(2)
IF (Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%Zone ==ZoneNum) THEN
IF (AirflowNetworkNodeData(NodeNum1)%EplusZoneNum <= 0) THEN
Tin(ZoneNum)= Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%OutDryBulbTemp
ELSEIF (AirModel(AirflowNetworkNodeData(NodeNum1)%EplusZoneNum)%AirModelType==RoomAirModel_UCSDCV) THEN
Tin(ZoneNum)=RoomOutflowTemp(AirflowNetworkNodeData(NodeNum1)%EplusZoneNum)
ELSE
Tin(ZoneNum)=MAT(AirflowNetworkNodeData(NodeNum1)%EplusZoneNum)
END IF
ELSE
IF (AirflowNetworkNodeData(NodeNum2)%EplusZoneNum <= 0) THEN
Tin(ZoneNum)= Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%OutDryBulbTemp
ELSEIF (AirModel(AirflowNetworkNodeData(NodeNum2)%EplusZoneNum)%AirModelType==RoomAirModel_UCSDCV) THEN
Tin(ZoneNum)=RoomOutflowTemp(AirflowNetworkNodeData(NodeNum2)%EplusZoneNum)
ELSE
Tin(ZoneNum)=MAT(AirflowNetworkNodeData(NodeNum2)%EplusZoneNum)
END IF
ENDIF
ELSEIF ((Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%Zone ==ZoneNum) .AND. &
(AirModel(Surface(Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%ExtBoundcond)%Zone)%AirModelType==RoomAirModel_UCSDCV)) THEN
Tin(ZoneNum)=RoomOutflowTemp(Surface(Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%ExtBoundcond)%Zone)
ELSEIF ((Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%Zone /=ZoneNum) .AND. &
(AirModel(Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%Zone)%AirModelType==RoomAirModel_UCSDCV)) THEN
Tin(ZoneNum)=RoomOutflowTemp(MultizoneSurfaceData(MaxSurf)%SurfNum)
ELSE
IF (Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%Zone ==ZoneNum) THEN
Tin(ZoneNum)=MAT(Surface(Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%ExtBoundCond)%Zone)
ELSE
Tin(ZoneNum)=MAT(Surface(MultizoneSurfaceData(MaxSurf)%SurfNum)%Zone)
END IF
END IF
END IF
END SUBROUTINE EvolveParaUCSDCV