----------------------------------------------------------------------------- -- -- Module : Data.Function.Finance -- Copyright : (c) 2014-16 Brian W Bush -- License : MIT -- -- Maintainer : Brian W Bush -- Stability : Stable -- Portability : Portable -- -- | Financial functions. -- ----------------------------------------------------------------------------- {-# LANGUAGE Safe #-} module Data.Function.Finance ( -- * Financial functions netPresentValue , internalRateOfReturn , capitalRecoveryFactor ) where import Math.Roots (bracket) import Math.Roots.Bisection (findRoot) -- | Compute the net present value of a series of values. netPresentValue :: (Fractional a, Num a) => a -- ^ The rate per period. -> [a] -- ^ The values at the end of the periods. -> a -- ^ The net present value. netPresentValue _ [] = 0 netPresentValue rate (x : xs) = (x + netPresentValue rate xs) / (1 + rate) -- | Compute the internal rate of return for a series of values. internalRateOfReturn :: (Fractional a, Num a, Ord a) => [a] -- ^ The values at the end of the periods. -> Either String a -- ^ The rate per period that yields a zero net present value. internalRateOfReturn x | null x = return 0 | minimum x * maximum x > 0 = Left "Both negative and positive values must be present." | otherwise = do let f = flip netPresentValue x xs <- bracket 100 f (0, 10) findRoot 100 1e-8 f xs -- | Compute a capital recovery factor. capitalRecoveryFactor :: (Floating a, Real b) => a -- ^ The interest rate. -> b -- ^ The lifetime of the capital. -> a -- ^ The capital recovery factor. capitalRecoveryFactor interestRate lifetime = interestRate * (1 + interestRate)**lifetime' / ((1 + interestRate)**lifetime' - 1) where lifetime' = fromRational $ toRational lifetime