Haskell Quiz/Internal Rate of Return/Solution Dolio
My solution for this quiz uses the secant method, which is quite easy to implement.
import Data.Function
import Numeric
import System.Environment
secant :: (Double -> Double) -> Double -> Double
secant f delta = fst $ until err update (0,1)
where
update (x,y) = (x - (x - y)*(f x)/(f x - f y), x)
err (x,y) = abs (x - y) < delta
npv :: Double -> [Double] -> Double
npv i = sum . zipWith (\t c -> c / (1 + i)**t) [0..]
main = do (s:t) <- getArgs
let sig = read s
cs = map read t
putStrLn . ($"") . showFFloat (Just sig) $ secant (flip npv cs) (0.1^sig)
The resulting program expects the first argument to be the number of digits to be displayed after the decimal point, while the rest are the yearly income. For instance:
./IRR 4 -100 30 35 40 45 0.1709