| Type | Intent | Optional | Attributes | Name | ||
|---|---|---|---|---|---|---|
| real(kind=r64), | intent(inout) | :: | Coef | |||
| real(kind=r64), | intent(in) | :: | Expn | |||
| integer, | intent(in) | :: | LFLAG | |||
| real(kind=r64), | intent(in) | :: | PDROP | |||
| 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 GenericCrack(Coef,Expn,LFLAG,PDROP,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  This subroutine is revised from AFEPLR developed by George Walton, NIST
          ! PURPOSE OF THIS SUBROUTINE:
          ! This subroutine solves airflow for a power law component
          ! METHODOLOGY EMPLOYED:
          ! Using Q=C(dP)^n
          ! REFERENCES:
          ! na
          ! USE STATEMENTS:
          ! na
          IMPLICIT NONE    ! Enforce explicit typing of all variables in this routine
          ! SUBROUTINE ARGUMENT DEFINITIONS:
          REAL(r64), INTENT(INOUT)  :: Coef     ! Flow coefficient
          REAL(r64), INTENT(IN)  :: Expn     ! Flow exponent
          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)  :: 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:
         REAL(r64)     CDM, FL, FT
         REAL(r64)     RhozNorm, VisczNorm, Ctl, VisAve, Tave, RhoCor
      ! FLOW:
      ! Calculate normal density and viscocity at Crack standard condition: T=20C, p=101325 Pa and 0 g/kg
      RhozNorm = PsyRhoAirFnPbTdbW(101325.0d0,20.0d0,0.0d0)
      VisczNorm = 1.71432d-5+4.828d-8*20.0d0
      VisAve = (VISCZ(N)+VISCZ(M))/2.0d0
      Tave = (TZ(N)+TZ(M))/2.0d0
      IF(PDROP.GE.0.0d0) THEN
         coef = Coef/SQRTDZ(N)
      ELSE
         coef = Coef/SQRTDZ(M)
      END IF
      NF = 1
      IF(LFLAG.EQ.1) THEN
        ! Initialization by linear relation.
        IF(PDROP.GE.0.0d0) THEN
          RhoCor = (TZ(N)+KelvinConv)/(Tave+KelvinConv)
          ctl = (RhozNorm/RHOZ(N)/RhoCor)**(expn-1.0d0)*(VisczNorm/VisAve)**(2.d0*expn-1.0d0)
          DF(1) = Coef*RHOZ(N)/VISCZ(N)*ctl
        ELSE
          RhoCor = (TZ(M)+KelvinConv)/(Tave+KelvinConv)
          ctl = (RhozNorm/RHOZ(M)/RhoCor)**(expn-1.0d0)*(VisczNorm/VisAve)**(2.d0*expn-1.0d0)
          DF(1) = Coef*RHOZ(M)/VISCZ(M)*ctl
        END IF
        F(1) = -DF(1)*PDROP
      ELSE
        ! Standard calculation.
        IF(PDROP.GE.0.0d0) THEN
          ! Flow in positive direction.
          ! Laminar flow.
          RhoCor = (TZ(N)+KelvinConv)/(Tave+KelvinConv)
          ctl = (RhozNorm/RHOZ(N)/RhoCor)**(expn-1.0d0)*(VisczNorm/VisAve)**(2.d0*expn-1.0d0)
          CDM = Coef*RHOZ(N)/VISCZ(N)*ctl
          FL = CDM*PDROP
          ! Turbulent flow.
          IF(expn .EQ. 0.5d0) THEN
            FT = Coef*SQRTDZ(N)*SQRT(PDROP)*ctl
          ELSE
            FT = Coef*SQRTDZ(N)*(PDROP**expn)*ctl
          END IF
        ELSE
          ! Flow in negative direction.
          ! Laminar flow.
          RhoCor = (TZ(M)+KelvinConv)/(Tave+KelvinConv)
          ctl = (RhozNorm/RHOZ(M)/RhoCor)**(expn-1.0d0)*(VisczNorm/VisAve)**(2.d0*expn-1.0d0)
          CDM = Coef*RHOZ(M)/VISCZ(M)*ctl
          FL = CDM*PDROP
          ! Turbulent flow.
          IF(expn .EQ. 0.5d0) THEN
            FT = -Coef*SQRTDZ(M)*SQRT(-PDROP)*ctl
          ELSE
            FT = -Coef*SQRTDZ(M)*(-PDROP)**expn*ctl
          END IF
        END IF
        ! Select laminar or turbulent flow.
        IF(LIST.GE.4) WRITE(Unit21,901) ' generic crack: ',PDROP,FL,FT
        IF(ABS(FL).LE.ABS(FT)) THEN
          F(1) = FL
          DF(1) = CDM
        ELSE
          F(1) = FT
          DF(1) = FT*expn/PDROP
        END IF
      END IF
!
  901 FORMAT(A5,6X,4E16.7)
      RETURN
      END SUBROUTINE GenericCrack