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) | :: | SystemType | |||
| integer, | intent(in) | :: | RadSysNum | |||
| real(kind=r64), | intent(in) | :: | outletTemp | |||
| real(kind=r64), | intent(in) | :: | inletTemp | |||
| real(kind=r64), | intent(in) | :: | mdot | 
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 CheckForOutOfRangeTempResult(SystemType, RadSysNum, outletTemp, inletTemp, mdot)
          ! SUBROUTINE INFORMATION:
          !       AUTHOR         B. Griffith
          !       DATE WRITTEN   March 2013
          !       MODIFIED       na
          !       RE-ENGINEERED  na
          ! PURPOSE OF THIS SUBROUTINE:
          ! check for crazy, out of range temperature results for fluid leaving radiant system
          ! METHODOLOGY EMPLOYED:
          ! <description>
          ! REFERENCES:
          ! na
          ! USE STATEMENTS:
  USE General,         ONLY : RoundSigDigits
  IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
          ! SUBROUTINE ARGUMENT DEFINITIONS:
  INTEGER, INTENT(IN)   :: SystemType
  INTEGER, INTENT(IN)   :: RadSysNum
  REAL(r64), INTENT(IN) :: outletTemp
  REAL(r64), INTENT(IN) :: inletTemp
  REAL(r64), INTENT(IN) :: mdot
          ! SUBROUTINE PARAMETER DEFINITIONS:
  REAL(r64), PARAMETER :: UpperRangeLimit = 500.d0  ! high error trigger limit for when model is not working
  REAL(r64), PARAMETER :: LowerRangeLimit = -300.d0 ! Low error trigger limit for when model is not working
          ! INTERFACE BLOCK SPECIFICATIONS:
          ! na
          ! DERIVED TYPE DEFINITIONS:
          ! na
          ! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
  LOGICAL :: WarnTooLow  = .FALSE.
  LOGICAL :: WarnTooHigh = .FALSE.
  WarnTooLow  = .FALSE.
  WarnTooHigh = .FALSE.
  IF (OutletTemp < LowerRangeLimit) THEN
    WarnTooLow  = .TRUE.
  ENDIF
  IF (OutletTemp > UpperRangeLimit) THEN
    WarnTooHigh = .TRUE.
  ENDIF
  IF (WarnTooLow .OR. WarnTooHigh) THEN
    SELECT CASE (SystemType)
    CASE (HydronicSystem)
      IF (WarnTooLow) THEN
        IF (HydrRadSys(RadSysNum)%OutRangeLoErrorCount == 0) THEN
          CALL ShowSevereMessage('UpdateLowTempRadiantSystem: model result for fluid outlet temperature is not physical.')
          CALL ShowContinueError('Occurs for radiant system name = '//TRIM(HydrRadSys(RadSysNum)%Name) )
          CALL ShowContinueError('Calculated radiant system outlet temperature = ' &
                                   //TRIM(RoundSigDigits(outletTemp, 3))//' [C]')
          CALL ShowContinueError('Radiant system inlet temperature = ' &
                                   //TRIM(RoundSigDigits(inletTemp, 3))//' [C]')
          CALL ShowContinueError('A possible cause is that the materials used in the internal source construction are ' &
                                  // 'not compatible with the model.')
        ENDIF
        CALL ShowRecurringSevereErrorAtEnd('UpdateLowTempRadiantSystem: Detected low out of range outlet temperature result ' &
                                            //'for radiant system name ='//TRIM(HydrRadSys(RadSysNum)%Name), &
                                             HydrRadSys(RadSysNum)%OutRangeLoErrorCount, &
                                             ReportMaxOf = outletTemp, &
                                             ReportMinOf = outletTemp )
      ENDIF
      IF (WarnTooHigh) THEN
        IF (HydrRadSys(RadSysNum)%OutRangeHiErrorCount == 0) THEN
          CALL ShowSevereMessage('UpdateLowTempRadiantSystem: model result for fluid outlet temperature is not physical.')
          CALL ShowContinueError('Occurs for radiant system name = '//TRIM(HydrRadSys(RadSysNum)%Name) )
          CALL ShowContinueError('Calculated radiant system outlet temperature = ' &
                                   //TRIM(RoundSigDigits(outletTemp, 3))//' [C]')
          CALL ShowContinueError('Radiant system inlet temperature = ' &
                                   //TRIM(RoundSigDigits(inletTemp, 3))//' [C]')
          CALL ShowContinueError('A possible cause is that the materials used in the internal source construction are ' &
                                  // 'not compatible with the model.')
        ENDIF
        CALL ShowRecurringSevereErrorAtEnd('UpdateLowTempRadiantSystem: Detected high out of range outlet temperature result ' &
                                            //' radiant system name ='//TRIM(HydrRadSys(RadSysNum)%Name), &
                                             HydrRadSys(RadSysNum)%OutRangeHiErrorCount, &
                                             ReportMaxOf = outletTemp, &
                                             ReportMinOf = outletTemp )
      ENDIF
    CASE (ConstantFlowSystem)
      IF (WarnTooLow) THEN
        IF (CFloRadSys(RadSysNum)%OutRangeLoErrorCount == 0) THEN
          CALL ShowSevereMessage('UpdateLowTempRadiantSystem: model result for fluid outlet temperature is not physical.')
          CALL ShowContinueError('Occurs for radiant system name = '//TRIM(CFloRadSys(RadSysNum)%Name) )
          CALL ShowContinueError('Calculated radiant system outlet temperature = ' &
                                   //TRIM(RoundSigDigits(outletTemp, 3))//' [C]')
          CALL ShowContinueError('Radiant system inlet temperature = ' &
                                   //TRIM(RoundSigDigits(inletTemp, 3))//' [C]')
          CALL ShowContinueError('A possible cause is that the materials used in the internal source construction are ' &
                                  // 'not compatible with the model.')
        ENDIF
        CALL ShowRecurringSevereErrorAtEnd('UpdateLowTempRadiantSystem: Detected high out of range temperature result for ' &
                                            //' radiant system name ='//TRIM(CFloRadSys(RadSysNum)%Name), &
                                             CFloRadSys(RadSysNum)%OutRangeLoErrorCount, &
                                             ReportMaxOf = outletTemp, &
                                             ReportMinOf = outletTemp )
      ENDIF
      IF (WarnTooHigh) THEN
        IF (CFloRadSys(RadSysNum)%OutRangeHiErrorCount == 0) THEN
          CALL ShowSevereMessage('UpdateLowTempRadiantSystem: model result for fluid outlet temperature is not physical.')
          CALL ShowContinueError('Occurs for radiant system name = '//TRIM(CFloRadSys(RadSysNum)%Name) )
          CALL ShowContinueError('Calculated radiant system outlet temperature = ' &
                                   //TRIM(RoundSigDigits(outletTemp, 3))//' [C]')
          CALL ShowContinueError('Radiant system inlet temperature = ' &
                                   //TRIM(RoundSigDigits(inletTemp, 3))//' [C]')
          CALL ShowContinueError('A possible cause is that the materials used in the internal source construction are ' &
                                  // 'not compatible with the model.')
        ENDIF
        CALL ShowRecurringSevereErrorAtEnd('UpdateLowTempRadiantSystem: Detected high out of range temperature result for ' &
                                            //' radiant system name ='//TRIM(CFloRadSys(RadSysNum)%Name), &
                                             CFloRadSys(RadSysNum)%OutRangeHiErrorCount, &
                                             ReportMaxOf = outletTemp, &
                                             ReportMinOf = outletTemp )
      ENDIF
    END SELECT
  ENDIF
  RETURN
END SUBROUTINE CheckForOutOfRangeTempResult