| 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 AFEDWC(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 duct/pipe component using Colebrook equation for the
          ! turbulent friction factor
          ! 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:
          !     RE      - Reynolds number.
          !     FL      - friction factor for laminar flow.
          !     FT      - friction factor for turbulent flow.
         REAL(r64)     A0, A1, A2, B, C, D, EPS, S2, CDM, FL, FT, FTT, RE
         INTEGER  CompNum
         REAL(r64)     ed, ld, g, AA1
!
      DATA C,EPS / 0.868589d0, 0.001d0 /
      ! FLOW:
      CompNum = AirflowNetworkCompData(J)%TypeNum
      ed = DisSysCompDuctData(CompNum)%Rough/DisSysCompDuctData(CompNum)%D
      ld = DisSysCompDuctData(CompNum)%L/DisSysCompDuctData(CompNum)%D
      g  = 1.14d0 - 0.868589d0*LOG(ed)
      AA1 = g
      NF = 1
      IF(LFLAG.EQ.1) THEN
        ! Initialization by linear relation.
        IF(PDROP.GE.0.0d0) THEN
          DF(1) = (2.d0*RHOZ(N)*DisSysCompDuctData(CompNum)%A*DisSysCompDuctData(CompNum)%D)/ &
                  (VISCZ(N)*DisSysCompDuctData(CompNum)%InitLamCoef*ld)
        ELSE
          DF(1) = (2.d0*RHOZ(M)*DisSysCompDuctData(CompNum)%A*DisSysCompDuctData(CompNum)%D)/ &
                  (VISCZ(M)*DisSysCompDuctData(CompNum)%InitLamCoef*ld)
        END IF
        F(1) = -DF(1)*PDROP
        IF(LIST.GE.4) WRITE(Unit21,901) ' dwi:',I,DisSysCompDuctData(CompNum)%InitLamCoef,F(1),DF(1)
      ELSE
        ! Standard calculation.
        IF(PDROP.GE.0.0d0) THEN
          ! Flow in positive direction.
          ! Laminar flow coefficient !=0
          IF(DisSysCompDuctData(CompNum)%LamFriCoef.GE.0.001d0) THEN
            A2 = DisSysCompDuctData(CompNum)%LamFriCoef/(2.0d0*RHOZ(N)*DisSysCompDuctData(CompNum)%A* &
                 DisSysCompDuctData(CompNum)%A)
            A1 = (VISCZ(N)*DisSysCompDuctData(CompNum)%LamDynCoef*ld)/ &
                 (2.0d0*RHOZ(N)*DisSysCompDuctData(CompNum)%A*DisSysCompDuctData(CompNum)%D)
            A0 = -PDROP
            CDM = SQRT(A1*A1-4.0d0*A2*A0)
            FL = (CDM-A1)/(2.d0*A2)
            CDM = 1.0d0/CDM
          ELSE
            CDM = (2.d0*RHOZ(N)*DisSysCompDuctData(CompNum)%A*DisSysCompDuctData(CompNum)%D)/ &
                  (VISCZ(N)*DisSysCompDuctData(CompNum)%LamDynCoef*ld)
            FL = CDM*PDROP
          END IF
          RE = FL*DisSysCompDuctData(CompNum)%D/(VISCZ(N)*DisSysCompDuctData(CompNum)%A)
          IF(LIST.GE.4) WRITE(Unit21,901) ' dwl:',I,PDROP,FL,CDM,RE
          ! Turbulent flow; test when Re>10.
          IF(RE.GE.10.0d0) THEN
            S2 = SQRT(2.d0*RHOZ(N)*PDROP)*DisSysCompDuctData(CompNum)%A
            FTT = S2 / SQRT(ld/g**2+DisSysCompDuctData(CompNum)%TurDynCoef)
            IF(LIST.GE.4) WRITE(Unit21,901) ' dwt:',I,S2,FTT,g
            DO
              FT = FTT
              B = (9.3d0*VISCZ(N)*DisSysCompDuctData(CompNum)%A)/(FT*DisSysCompDuctData(CompNum)%Rough)
              D = 1.0d0 + g*B
              g = g - (g-AA1+C*LOG(D))/(1.0d0+C*B/D)
              FTT = S2 / SQRT(ld/g**2+DisSysCompDuctData(CompNum)%TurDynCoef)
              IF(LIST.GE.4) WRITE(Unit21,901) ' dwt:',I,B,FTT,g
              IF(ABS(FTT-FT)/FTT .LT. EPS) EXIT
            ENDDO
            FT = FTT
          ELSE
            FT = FL
          END IF
        ELSE
          ! Flow in negative direction.
          ! Laminar flow coefficient !=0
          IF(DisSysCompDuctData(CompNum)%LamFriCoef.GE.0.001d0) THEN
            A2 = DisSysCompDuctData(CompNum)%LamFriCoef/(2.d0*RHOZ(M)*DisSysCompDuctData(CompNum)%A* &
                 DisSysCompDuctData(CompNum)%A)
            A1 = (VISCZ(M)*DisSysCompDuctData(CompNum)%LamDynCoef*ld)/ &
                 (2.d0*RHOZ(M)*DisSysCompDuctData(CompNum)%A*DisSysCompDuctData(CompNum)%D)
            A0 = PDROP
            CDM = SQRT(A1*A1-4.0d0*A2*A0)
            FL = -(CDM-A1)/(2.d0*A2)
            CDM = 1.0d0/CDM
          ELSE
            CDM = (2.d0*RHOZ(M)*DisSysCompDuctData(CompNum)%A*DisSysCompDuctData(CompNum)%D)/ &
                  (VISCZ(M)*DisSysCompDuctData(CompNum)%LamDynCoef*ld)
            FL = CDM*PDROP
          END IF
          RE = -FL*DisSysCompDuctData(CompNum)%D/(VISCZ(M)*DisSysCompDuctData(CompNum)%A)
          IF(LIST.GE.4) WRITE(Unit21,901) ' dwl:',I,PDROP,FL,CDM,RE
          ! Turbulent flow; test when Re>10.
          IF(RE.GE.10.0d0) THEN
            S2 = SQRT(-2.d0*RHOZ(M)*PDROP)*DisSysCompDuctData(CompNum)%A
            FTT = S2 / SQRT(ld/g**2+DisSysCompDuctData(CompNum)%TurDynCoef)
            IF(LIST.GE.4) WRITE(Unit21,901) ' dwt:',I,S2,FTT,g
            DO
              FT = FTT
              B = (9.3d0*VISCZ(M)*DisSysCompDuctData(CompNum)%A)/(FT*DisSysCompDuctData(CompNum)%Rough)
              D = 1.0d0 + g*B
              g = g - (g-AA1+C*LOG(D))/(1.0d0+C*B/D)
              FTT = S2 / SQRT(ld/g**2+ DisSysCompDuctData(CompNum)%TurDynCoef)
              IF(LIST.GE.4) WRITE(Unit21,901) ' dwt:',I,B,FTT,g
              IF(ABS(FTT-FT)/FTT .LT. EPS) EXIT
            ENDDO
            FT = -FTT
          ELSE
            FT = FL
          END IF
        END IF
        ! Select laminar or turbulent flow.
        IF(ABS(FL).LE.ABS(FT)) THEN
          F(1) = FL
          DF(1) = CDM
        ELSE
          F(1) = FT
          DF(1) = 0.5d0*FT/PDROP
        END IF
      END IF
!
  901 FORMAT(A5,I3,6X,4E16.7)
      RETURN
      END SUBROUTINE AFEDWC