| Type | Intent | Optional | Attributes | Name | ||
|---|---|---|---|---|---|---|
| integer, | intent(in) | :: | J | |||
| integer, | intent(in) | :: | LFLAG | |||
| real(kind=r64), | intent(in) | :: | PDROP | |||
| integer, | intent(in) | :: | I | |||
| integer, | intent(in) | :: | N | |||
| integer, | intent(in) | :: | M | |||
| real(kind=r64), | intent(out) | :: | F(2) | |||
| real(kind=r64), | intent(out) | :: | DF(2) | |||
| integer, | intent(out) | :: | NF | 
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 AFESOP(J,LFLAG,PDROP,I,N,M,F,DF,NF)
          ! SUBROUTINE INFORMATION:
          !       AUTHOR         George Walton
          !       DATE WRITTEN   Extracted from AIRNET
          !       MODIFIED       Lixing Gu, 2/1/04
          !                      Revised the subroutine to meet E+ needs
          !       MODIFIED       Lixing Gu, 6/8/05
          !
          !       RE-ENGINEERED  na
          ! PURPOSE OF THIS SUBROUTINE:
          ! This subroutine solves airflow for a Doorway airflow component using standard interface.
          ! A doorway may have two-way airflows. Heights measured relative to the bottom of the door.
          ! METHODOLOGY EMPLOYED:
          ! na
          ! REFERENCES:
          ! na
          ! USE STATEMENTS:
          ! na
          IMPLICIT NONE    ! Enforce explicit typing of all variables in this routine
          ! SUBROUTINE ARGUMENT DEFINITIONS:
          INTEGER, INTENT(IN)  :: J     ! Component number
          INTEGER, INTENT(IN)  :: LFLAG ! Initialization flag.If = 1, use laminar relationship
          REAL(r64), INTENT(IN)     :: PDROP ! Total pressure drop across a component (P1 - P2) [Pa]
          INTEGER, INTENT(IN)  :: I     ! Linkage number
          INTEGER, INTENT(IN)  :: N     ! Node 1 number
          INTEGER, INTENT(IN)  :: M     ! Node 2 number
          INTEGER, INTENT(OUT) :: NF    ! Number of flows, either 1 or 2
          REAL(r64), INTENT(OUT)    :: F(2)  ! Airflow through the component [kg/s]
          REAL(r64), INTENT(OUT)    :: DF(2) ! Partial derivative:  DF/DP
          ! SUBROUTINE PARAMETER DEFINITIONS:
          ! na
          ! INTERFACE BLOCK SPECIFICATIONS
          ! na
          ! DERIVED TYPE DEFINITIONS
          ! na
          ! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
          !     DPMID   - pressure drop at mid-height of doorway.
          !     DRHO    - difference in air densities between rooms.
          !     Y       - height of neutral plane rel. to bottom of door (m).
          !     F0      - flow factor at the bottom of the door.
          !     FH      - flow factor at the top of the door.
          !     DF0     - derivative factor at the bottom of the door.
          !     DFH     - derivative factor at the top of the door.
!
         REAL(r64) DPMID
         REAL(r64)     C, DF0, DFH, DRHO, GDRHO, F0, FH, Y, SQRT2
         INTEGER  CompNum
         REAL(r64) FlowCoef,FlowExpo,MinRhoDiff,DischCoeff,Width,Height,OpenFactor
!
      DATA SQRT2 / 1.414214d0 /
      ! FLOW:
      CompNum = AirflowNetworkCompData(J)%TypeNum
      MinRhoDiff = MultizoneCompSimpleOpeningData(CompNum)%MinRhoDiff
      DischCoeff = MultizoneCompSimpleOpeningData(CompNum)%DischCoeff
      Width = MultizoneSurfaceData(i)%Width
      Height = MultizoneSurfaceData(i)%Height
      FlowCoef = MultizoneCompSimpleOpeningData(CompNum)%FlowCoef*2.0d0*(Width+Height)
      FlowExpo = MultizoneCompSimpleOpeningData(CompNum)%FlowExpo
      OpenFactor = MultizoneSurfaceData(I)%OpenFactor
      If (OpenFactor > 0.0d0) then
        Width = Width*OpenFactor
        If (Surface(MultizoneSurfaceData(I)%SurfNum)%Tilt .LT. 90.d0) then
          Height = Height*Surface(MultizoneSurfaceData(I)%SurfNum)%SinTilt
        End If
      End If
      IF(PDROP.GE.0.0d0) THEN
         FlowCoef = FlowCoef/SQRTDZ(N)
      ELSE
         FlowCoef = FlowCoef/SQRTDZ(M)
      END IF
      ! Add window multiplier with window close
      If (MultizoneSurfaceData(I)%Multiplier > 1.0d0) FlowCoef=FlowCoef*MultizoneSurfaceData(I)%Multiplier
      ! Add window multiplier with window open
      If (OpenFactor .gt. 0.0d0) then
        If (MultizoneSurfaceData(I)%Multiplier > 1.0d0) Width=Width*MultizoneSurfaceData(I)%Multiplier
      End If
      NF = 1
      DRHO = RHOZ(N)-RHOZ(M)
      GDRHO = 9.8d0*DRHO
      IF(LIST.GE.4) WRITE(Unit21,903) ' DOR:',I,N,M,PDROP,ABS(DRHO),MinRhoDiff
      IF(OpenFactor .eq. 0.0d0) THEN
        CALL GenericCrack(FlowCoef,FlowExpo,LFLAG,PDROP,N,M,F,DF,NF)
        Return
      end if
      IF(ABS(DRHO).LT.MinRhoDiff .OR. LFLAG.EQ.1) THEN
        DPMID = PDROP-0.5d0*Height*GDRHO
        ! Initialization or identical temps: treat as one-way flow.
        CALL GenericCrack(FlowCoef,FlowExpo,LFLAG,DPMID,N,M,F,DF,NF)
        IF(LIST.GE.4) WRITE(Unit21,900) ' Drs:',DPMID,F(1),DF(1)
      ELSE
        ! Possible two-way flow:
        Y = PDROP/GDRHO
        IF(LIST.GE.4) WRITE(Unit21,900) ' DrY:',PDROP,GDRHO,Y
        ! F0 = lower flow, FH = upper flow.
        C = SQRT2*Width*DischCoeff
        DF0 = C*SQRT(ABS(PDROP))/ABS(GDRHO)
!        F0 = 0.666667d0*C*SQRT(ABS(GDRHO*Y))*ABS(Y)
        F0 = (2.0d0/3.0d0)*C*SQRT(ABS(GDRHO*Y))*ABS(Y)
        DFH = C*SQRT(ABS((Height-Y)/GDRHO))
!        FH = 0.666667d0*DFH*ABS(GDRHO*(Height-Y))
        FH = (2.0d0/3.0d0)*DFH*ABS(GDRHO*(Height-Y))
        IF(LIST.GE.4) WRITE(Unit21,900) ' DrF:',F0,DF0,FH,DFH
        IF(Y.LE.0.0d0) THEN
          ! One-way flow (negative).
          IF(DRHO.GE.0.0d0) THEN
            F(1) = -SQRTDZ(M)*ABS(FH-F0)
            DF(1) = SQRTDZ(M)*ABS(DFH-DF0)
          ELSE
            F(1) =  SQRTDZ(N)*ABS(FH-F0)
            DF(1) = SQRTDZ(N)*ABS(DFH-DF0)
          END IF
          IF(LIST.GE.4) WRITE(Unit21,900) ' Dr1:',C,F(1),DF(1)
        ELSE IF(Y.GE.Height) THEN
          ! One-way flow (positive).
          IF(DRHO.GE.0.0d0) THEN
            F(1) =  SQRTDZ(N)*ABS(FH-F0)
            DF(1) = SQRTDZ(N)*ABS(DFH-DF0)
          ELSE
            F(1) = -SQRTDZ(M)*ABS(FH-F0)
            DF(1) = SQRTDZ(M)*ABS(DFH-DF0)
          END IF
          IF(LIST.GE.4) WRITE(Unit21,900) ' Dr2:',C,F(1),DF(1)
        ELSE
          ! Two-way flow.
          NF = 2
          IF(DRHO.GE.0.0d0) THEN
            F(1) = -SQRTDZ(M)*FH
            DF(1) = SQRTDZ(M)*DFH
            F(2) =  SQRTDZ(N)*F0
            DF(2) = SQRTDZ(N)*DF0
          ELSE
            F(1) =  SQRTDZ(N)*FH
            DF(1) = SQRTDZ(N)*DFH
            F(2) = -SQRTDZ(M)*F0
            DF(2) = SQRTDZ(M)*DF0
          END IF
          IF(LIST.GE.4) WRITE(Unit21,900) ' Dr3:',C,F(1),DF(1)
          IF(LIST.GE.4) WRITE(Unit21,900) ' Dr4:',C,F(2),DF(2)
        ENDIF
      END IF
  900 FORMAT(A5,9X,4E16.7)
  903 FORMAT(A5,3I3,4E16.7)
      RETURN
      END SUBROUTINE AFESOP