Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=*), | intent(in) | :: | Glycol | |||
real(kind=r64), | intent(in) | :: | Temperature | |||
integer, | intent(inout) | :: | GlycolIndex | |||
character(len=*), | intent(in) | :: | calledfrom |
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.
FUNCTION GetConductivityGlycol(Glycol,Temperature,GlycolIndex,calledfrom) RESULT(ReturnValue)
! FUNCTION INFORMATION:
! AUTHOR Rick Strand
! DATE WRITTEN June 2004
! MODIFIED N/A
! RE-ENGINEERED N/A
! PURPOSE OF THIS FUNCTION:
! This subroutine finds the conductivity for glycols at different
! temperatures.
! METHODOLOGY EMPLOYED:
! Linear interpolation is used to find conductivity values for a
! particular glycol (water or some mixture of water and another fluid).
! Warnings are given if the point is not clearly in the bounds of the
! glycol data. The value returned is the appropriate limit value.
! REFERENCES:
! GetFluidPropertiesData: subroutine enforces that temperatures in
! all temperature lists are entered in ascending order.
! USE STATEMENTS:
! na
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! FUNCTION ARGUMENT DEFINITIONS:
CHARACTER(len=*), INTENT(IN) :: Glycol ! carries in substance name
REAL(r64), INTENT(IN) :: Temperature ! actual temperature given as input
INTEGER, INTENT(INOUT) :: GlycolIndex ! Index to Glycol Properties
character(len=*), intent(in) :: calledfrom ! routine this function was called from (error messages)
REAL(r64) :: ReturnValue
! FUNCTION PARAMETERS:
CHARACTER(len=*), PARAMETER :: RoutineName='GetConductivityGlycol: '
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! FUNCTION LOCAL VARIABLE DECLARATIONS:
INTEGER :: Loop ! DO loop counter
INTEGER,SAVE :: HighTempLimitErr = 0
INTEGER,SAVE :: LowTempLimitErr = 0
INTEGER,SAVE :: HighTempLimitIndex = 0
INTEGER,SAVE :: LowTempLimitIndex = 0
INTEGER :: GlycolNum
LOGICAL :: LowErrorThisTime
LOGICAL :: HighErrorThisTime
! FLOW:
LowErrorThisTime = .FALSE.
HighErrorThisTime = .FALSE.
! Get the input if we haven't already
IF (GetInput) THEN
CALL GetFluidPropertiesData
GetInput = .FALSE.
END IF
! If no glycols, no fluid properties can be evaluated
GlycolNum=0
IF (NumOfGlycols == 0) &
CALL ReportFatalGlycolErrors(NumOfGlycols,GlycolNum,.true.,Glycol,'GetConductivityGlycol','conductivity',calledfrom)
! If glycol index has not yet been found for this fluid, find its value now
IF (GlycolIndex > 0) THEN
GlycolNum=GlycolIndex
ELSE ! Find which refrigerant (index) is being requested
GlycolNum = FindGlycol(Glycol)
IF (GlycolNum == 0) THEN
CALL ReportFatalGlycolErrors(NumOfGlycols,GlycolNum,.true.,Glycol,'GetConductivityGlycol','conductivity',calledfrom)
ENDIF
GlycolIndex=GlycolNum
ENDIF
! If user didn't input data (shouldn't get this far, but just in case...), we can't find a value
IF (.NOT. GlycolData(GlycolIndex)%CondDataPresent)THEN
CALL ReportFatalGlycolErrors(NumOfGlycols,GlycolNum,GlycolData(GlycolIndex)%CondDataPresent,Glycol, &
'GetConductivityGlycol','conductivity',calledfrom)
ENDIF
! Now determine the value of specific heat using interpolation
IF (Temperature < GlycolData(GlycolIndex)%CondLowTempValue) THEN ! Temperature too low
LowErrorThisTime = .TRUE.
ReturnValue = GlycolData(GlycolIndex)%CondValues(GlycolData(GlycolIndex)%CondLowTempIndex)
ELSE IF (Temperature > GlycolData(GlycolIndex)%CondHighTempValue) THEN ! Temperature too high
HighErrorThisTime = .TRUE.
ReturnValue = GlycolData(GlycolIndex)%CondValues(GlycolData(GlycolIndex)%CondHighTempIndex)
ELSE ! Temperature somewhere between the lowest and highest value
ReturnValue = GlycolData(GlycolIndex)%CondValues(GlycolData(GlycolIndex)%CondLowTempIndex)
! bracket is temp > low, <= high (for interpolation
DO Loop = GlycolData(GlycolIndex)%CondLowTempIndex+1, GlycolData(GlycolIndex)%CondHighTempIndex
IF (Temperature > GlycolData(GlycolIndex)%CondTemps(Loop)) CYCLE
ReturnValue = GetInterpValue(Temperature, &
GlycolData(GlycolIndex)%CondTemps(Loop-1), &
GlycolData(GlycolIndex)%CondTemps(Loop), &
GlycolData(GlycolIndex)%CondValues(Loop-1), &
GlycolData(GlycolIndex)%CondValues(Loop))
EXIT ! DO loop
END DO
END IF
! Error handling
IF (.not. WarmupFlag) THEN
! IF (LowErrorThisTime) LowTempLimitErr = LowTempLimitErr + 1
! IF (HighErrorThisTime) HighTempLimitErr = HighTempLimitErr + 1
IF (LowErrorThisTime) THEN
GlycolErrorTracking(GlycolIndex)%ConductivityLowErrCount = GlycolErrorTracking(GlycolIndex)%ConductivityLowErrCount + 1
LowTempLimitErr = GlycolErrorTracking(GlycolIndex)%ConductivityLowErrCount
ENDIF
IF (HighErrorThisTime) THEN
GlycolErrorTracking(GlycolIndex)%ConductivityHighErrCount = GlycolErrorTracking(GlycolIndex)%ConductivityHighErrCount + 1
HighTempLimitErr = GlycolErrorTracking(GlycolIndex)%ConductivityHighErrCount
ENDIF
IF ( (LowErrorThisTime) .AND. (LowTempLimitErr <= GlycolErrorLimitTest) ) THEN
CALL ShowWarningMessage(RoutineName//'Temperature is out of range (too low) for fluid ['// &
trim(GlycolData(GlycolIndex)%Name)//'] conductivity **')
CALL ShowContinueError('..Called From:'//trim(calledfrom)//',Temperature=['//TRIM(RoundSigDigits(Temperature,2))// &
'], supplied data range=['// &
trim(RoundSigDigits(GlycolData(GlycolIndex)%CondLowTempValue,2))//','// &
trim(RoundSigDigits(GlycolData(GlycolIndex)%CondHighTempValue,2))//']')
CALL ShowContinueErrorTimeStamp(' ')
ENDIF
IF (LowErrorThisTime) THEN
CALL ShowRecurringWarningErrorAtEnd(RoutineName//'Temperature out of range (too low) for fluid ['// &
trim(GlycolData(GlycolIndex)%Name)//'] conductivity **', &
GlycolErrorTracking(GlycolIndex)%ConductivityLowErrIndex,ReportMinOf=Temperature,ReportMaxOf=Temperature, &
ReportMaxUnits='{C}',ReportMinUnits='{C}')
END IF
IF ( (HighErrorThisTime) .AND. (HighTempLimitErr <= GlycolErrorLimitTest) ) THEN
CALL ShowWarningMessage(RoutineName//'Temperature is out of range (too high) for fluid ['// &
trim(GlycolData(GlycolIndex)%Name)//'] conductivity **')
CALL ShowContinueError('..Called From:'//trim(calledfrom)//',Temperature=['//TRIM(RoundSigDigits(Temperature,2))// &
'], supplied data range=['// &
trim(RoundSigDigits(GlycolData(GlycolIndex)%CondLowTempValue,2))//','// &
trim(RoundSigDigits(GlycolData(GlycolIndex)%CondHighTempValue,2))//']')
CALL ShowContinueErrorTimeStamp(' ')
ENDIF
IF (HighErrorThisTime) THEN
CALL ShowRecurringWarningErrorAtEnd(RoutineName//'Temperature out of range (too high) for fluid ['// &
trim(GlycolData(GlycolIndex)%Name)//'] conductivity **', &
GlycolErrorTracking(GlycolIndex)%ConductivityHighErrIndex,ReportMinOf=Temperature,ReportMaxOf=Temperature, &
ReportMaxUnits='{C}',ReportMinUnits='{C}')
END IF
ENDIF
RETURN
END FUNCTION GetConductivityGlycol