| Type | Intent | Optional | Attributes | Name | ||
|---|---|---|---|---|---|---|
| integer, | intent(in) | :: | GeneratorNum | |||
| real(kind=r64), | intent(in) | :: | FluidTemp | |||
| real(kind=r64), | intent(out) | :: | Hair | 
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 FigureAirEnthalpy(GeneratorNum, FluidTemp, Hair)
          ! SUBROUTINE INFORMATION:
          !       AUTHOR         B griffith
          !       DATE WRITTEN   August 2005
          !       MODIFIED       na
          !       RE-ENGINEERED  na
          ! PURPOSE OF THIS SUBROUTINE:
          ! calculate Enthalpy from Shomate equations for fuel
          ! METHODOLOGY EMPLOYED:
          ! sum by weighting molar fractions of all fuel constituents.
          ! assumes mixture is sum of parts.
          ! REFERENCES:
          ! NIST Webbook on gas phase thermochemistry
          ! USE STATEMENTS:
          ! na
  IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
          ! SUBROUTINE ARGUMENT DEFINITIONS:
  INTEGER, INTENT(IN)  ::   GeneratorNum ! ID of generator FuelCell data structure
  REAL(r64),    INTENT(IN)  ::   FluidTemp    ! degree C
  REAL(r64),    INTENT(OUT) ::   Hair         ! (kJ/mol)
          ! SUBROUTINE PARAMETER DEFINITIONS:
          ! na
          ! INTERFACE BLOCK SPECIFICATIONS:
          ! na
          ! DERIVED TYPE DEFINITIONS:
          ! na
          ! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
  REAL(r64)  :: Tsho ! temp for Shomate eq  in (Kelvin/1000)
  REAL(r64)  :: Tkel ! temp for NASA eq. in Kelvin
  REAL(r64)  :: tempHair
  REAL(r64)  :: HairI
  INTEGER   :: thisConstit !loop index
  INTEGER   :: gasID !look up into Gas structure
  REAL(r64) :: A ! shomate coeff
  REAL(r64) :: B ! shomate coeff
  REAL(r64) :: C ! shomate coeff
  REAL(r64) :: D ! shomate coeff
  REAL(r64) :: E ! shomate coeff
  REAL(r64) :: F ! shomate coeff
  REAL(r64) :: H ! shomate coeff
  REAL(r64) :: A1 ! NASA poly coeff
  REAL(r64) :: A2 ! NASA poly coeff
  REAL(r64) :: A3 ! NASA poly coeff
  REAL(r64) :: A4 ! NASA poly coeff
  REAL(r64) :: A5 ! NASA poly coeff
  REAL(r64) :: A6 ! NASA poly coeff
  Tsho = (FluidTemp +KelvinConv) / 1000.0d0
  Tkel = (FluidTemp +KelvinConv)
  ! loop through fuel constituents and sum up Cp
  tempHair = 0.0d0
  DO thisConstit=1, FuelCell(GeneratorNum)%AirSup%NumConstituents
    gasID = FuelCell(GeneratorNum)%AirSup%GasLibID(thisConstit)
    If (gasID > 0) THEN
     If (GasPhaseThermoChemistryData(gasID)%ThermoMode == NISTShomate) Then
       A = GasPhaseThermoChemistryData(gasID)%ShomateA
       B = GasPhaseThermoChemistryData(gasID)%ShomateB
       C = GasPhaseThermoChemistryData(gasID)%ShomateC
       D = GasPhaseThermoChemistryData(gasID)%ShomateD
       E = GasPhaseThermoChemistryData(gasID)%ShomateE
       F = GasPhaseThermoChemistryData(gasID)%ShomateF
       H = GasPhaseThermoChemistryData(gasID)%ShomateH
       HairI =  (A*Tsho + B*(Tsho**2)/2.0d0 + C*(Tsho**3)/3.0d0 + D*(Tsho**4)/4.0d0 - E/Tsho + F - H )
       tempHair = tempHair + HairI * FuelCell(GeneratorNum)%AirSup%ConstitMolalFract(thisConstit)
     ENDIF
     IF (GasPhaseThermoChemistryData(gasID)%ThermoMode == NASAPolynomial) THEN
       A1 = GasPhaseThermoChemistryData(gasID)%NASA_A1
       A2 = GasPhaseThermoChemistryData(gasID)%NASA_A2
       A3 = GasPhaseThermoChemistryData(gasID)%NASA_A3
       A4 = GasPhaseThermoChemistryData(gasID)%NASA_A4
       A5 = GasPhaseThermoChemistryData(gasID)%NASA_A5
       A6 = GasPhaseThermoChemistryData(gasID)%NASA_A6
       tempHair = tempHair + ( ( (A1 + A2*Tkel/2.0d0 + A3*Tkel**2/3.0d0 + A4*Tkel**3/4.0d0 + A5*Tkel**4/5.0d0 + A6/Tkel)  &
                               * RinKJperMolpK * Tkel) - GasPhaseThermoChemistryData(gasID)%StdRefMolarEnthOfForm) &
                               * FuelCell(GeneratorNum)%AirSup%ConstitMolalFract(thisConstit)
     ENDIF
    ENDIF
  ENDDO
  Hair = tempHair
  RETURN
END SUBROUTINE FigureAirEnthalpy