HargreavesSamani Subroutine

private subroutine HargreavesSamani(time, Tavg, Tmax, Tmin, etRad, pet)

Compute potential evapotranspiration with Hargreaves Samani model at daily time scale

References: Hargreaves, G.H., and Z.A. Samani (1982). Estimating potential evapotranspiration. J. Irrig. Drain. Eng., ASCE, 108(3), 223-230

Allen, R.G.; Pereira, L.S.; Raes, D.; Smith, M. Crop Evapotranspiration-Guidelines for Computing Crop Water Requirements-FAO Irrigation and Drainage Paper 56, 9th ed.; Food and Agriculture Organization of the United Nations: Rome, Italy, 1998; ISBN 92-5-104219-5.

Arguments

Type IntentOptional Attributes Name
type(DateTime), intent(in) :: time

simulation time

real(kind=float), intent(in) :: Tavg

average daily temperature [°C]

real(kind=float), intent(in) :: Tmax

maximum daily temperature [°C]

real(kind=float), intent(in) :: Tmin

minimum daily temperature [°C]

real(kind=float), intent(in) :: etRad

extra terrestrial solar radiation [mm/day]

real(kind=float), intent(out) :: pet

potential evapotranspiration [m/s]


Variables

Type Visibility Attributes Name Initial
real(kind=float), public, parameter :: HC = 0.0023

empirical coefficient

real(kind=float), public, parameter :: HE = 0.5

empirical exponent

real(kind=float), public, parameter :: HT = 17.8

empirical temperature coefficient


Source Code

SUBROUTINE HargreavesSamani &
!
(time, Tavg, Tmax, Tmin, etrad, pet)

IMPLICIT NONE

!Arguments with intent(in):
TYPE(DateTime)     , INTENT(in)  :: time !!simulation time
REAL (KIND = float), INTENT(in)  :: Tavg !!average daily temperature [°C]
REAL (KIND = float), INTENT(in)  :: Tmax !!maximum daily temperature [°C]
REAL (KIND = float), INTENT(in)  :: Tmin !!minimum daily temperature [°C]
REAL (KIND = float), INTENT(in)  :: etRad !!extra terrestrial solar radiation [mm/day]

!Arguments with intent(out):
REAL (KIND = float), INTENT(out) :: pet		!! potential evapotranspiration [m/s]

!local declarations.
REAL (KIND = float), PARAMETER   :: HC = 0.0023 !!empirical coefficient
REAL (KIND = float), PARAMETER   :: HE = 0.5  !!empirical exponent
REAL (KIND = float), PARAMETER   :: HT = 17.8  !!empirical temperature coefficient

!-----------------------------------------end of declarations------------------

!calculate evapotranspiration
IF ( ( Tmax - Tmin) < 0.) THEN
    CALL Catch ('warning', 'Evapotranspiration', '(Tmax - Tmin) < 0.' )
	pet = 0.
	RETURN
ELSE
	pet = HC * etRad * (Tmax - Tmin) ** HE * (Tavg + HT)
END IF

!conversion from mm/day to m/s
pet = pet * millimeter / day
	
    
RETURN	
END SUBROUTINE HargreavesSamani