Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=r64), | intent(in) | :: | Tdb | |||
real(kind=r64), | intent(in) | :: | Rhovapor | |||
character(len=*), | intent(in), | optional | :: | 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 PsyRhFnTdbRhovLBnd0C(Tdb,Rhovapor,calledfrom) RESULT(RHValue)
! FUNCTION INFORMATION:
! AUTHOR R. J. Liesen
! DATE WRITTEN July 2000
! MODIFIED Name change to signify derivation and temperatures were used
! with 0C as minimum; LKL January 2008
! RE-ENGINEERED na
! PURPOSE OF THIS FUNCTION:
! This function provides the Relative Humidity in air as a
! function of dry bulb temperature and Vapor Density.
! METHODOLOGY EMPLOYED:
! ideal gas law
! Universal gas const for water vapor 461.52 J/(kg K)
! REFERENCES:
! ASHRAE handbook 1993 Fundamentals,
! USE STATEMENTS:
! na
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! FUNCTION ARGUMENT DEFINITIONS:
REAL(r64), intent(in) :: Tdb ! dry-bulb temperature {C}
REAL(r64), intent(in) :: Rhovapor ! vapor density in air {kg/m3}
character(*), intent(in), optional :: calledfrom ! routine this function was called from (error messages)
REAL(r64) :: RHValue ! relative humidity value (0.0-1.0)
! FUNCTION PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! FUNCTION LOCAL VARIABLE DECLARATIONS:
! integer,save :: b0cerrcount=0
If(Rhovapor <= 0.0d0) Then
RHValue = 0.0d0
Else
RHValue =Rhovapor*461.52d0*(Tdb+KelvinConv)*Exp(-23.7093d0+4111.0d0/ &
((Tdb+KelvinConv)-35.45d0))
End If
# 1162
! VALIDITY TEST
IF (RHValue < 0.0d0 .or. RHValue > 1.0d0) THEN
IF (RHValue > 1.0d0) THEN
IF (RHValue > 1.01d0) THEN
IF (.not. WarmupFlag) THEN
IF (iPsyErrIndex(iPsyRhFnTdbRhovLBnd0C) == 0) THEN
String=' Dry-Bulb= '//TRIM(TrimSigDigits(TDB,2))// &
' Rhovapor= '//TRIM(TrimSigDigits(Rhovapor,3))// &
' Calculated Relative Humidity [%]= '//TRIM(TrimSigDigits(RHValue*100.d0,2))
CALL ShowWarningMessage('Calculated Relative Humidity out of range (PsyRhFnTdbRhovLBnd0C) ')
if (present(calledfrom)) then
CALL ShowContinueErrorTimeStamp(' Routine='//trim(calledfrom)//',')
else
CALL ShowContinueErrorTimeStamp(' Routine=Unknown,')
endif
CALL ShowContinueError(TRIM(String))
CALL ShowContinueError('Relative Humidity being reset to 100.0%')
ENDIF
CALL ShowRecurringWarningErrorAtEnd('Calculated Relative Humidity out of range (PsyRhFnTdbRhovLBnd0C)', &
iPsyErrIndex(iPsyRhFnTdbRhovLBnd0C),ReportMinOf=RHValue*100.d0,ReportMaxOf=RHValue*100.d0, &
ReportMinUnits='%',ReportMaxUnits='%')
ENDIF
ENDIF
RHValue=1.0d0
ELSE ! RHValue < 0.0
IF (RHValue < -0.05d0) THEN
IF (.not. WarmupFlag) THEN
IF (iPsyErrIndex(iPsyRhFnTdbRhovLBnd0C) == 0) THEN
String=' Dry-Bulb= '//TRIM(TrimSigDigits(TDB,2))// &
' Rhovapor= '//TRIM(TrimSigDigits(Rhovapor,3))// &
' Calculated Relative Humidity [%]= '//TRIM(TrimSigDigits(RHValue*100.d0,2))
CALL ShowWarningMessage('Calculated Relative Humidity out of range (PsyRhFnTdbRhovLBnd0C) ')
if (present(calledfrom)) then
CALL ShowContinueErrorTimeStamp(' Routine='//trim(calledfrom)//',')
else
CALL ShowContinueErrorTimeStamp(' Routine=Unknown,')
endif
CALL ShowContinueError(TRIM(String))
CALL ShowContinueError('Relative Humidity being reset to 1%')
ENDIF
CALL ShowRecurringWarningErrorAtEnd('Calculated Relative Humidity out of range (PsyRhFnTdbRhovLBnd0C)', &
iPsyErrIndex(iPsyRhFnTdbRhovLBnd0C),ReportMinOf=RHValue*100.d0,ReportMaxOf=RHValue*100.d0, &
ReportMinUnits='%',ReportMaxUnits='%')
ENDIF
ENDIF
RHValue=.01d0
ENDIF
ENDIF ! RHValue in proper range
return
end function PsyRhFnTdbRhovLBnd0C