[Haskell-beginners] my ugly code and the Maybe monad

Simon Parry sparry04 at googlemail.com
Tue Aug 18 17:41:45 EDT 2009


hello all,

Intro: I'm fairly new to Haskell, read some tutorials/books, this is my
first real attempt at making something rather than doing tutorial
problems - I thought I'd recode some financial maths up in Haskell...see
below.

It seems to work ok (I haven't properly tested it yet) but I feel the
pvs function is just ugly.  However it seems like its a fairly common
requirement for maths modelling ie using Maybe or Error or such to
represent conditions on the input variables and then later having to
combine those 'wrapped' values with other things.

Basically it seems inelegant and I feel like I'm confusing the monadic
and non-monadic parts?

help/criticism welcome,

thanks

Simon


module TimeValueMoney1 where

--taken from Financial Numerical Recipes in C++ by B A Odegaard (2006):
--Chapter 3

import Control.Monad

--time periods - assumes now is time 0--
times :: [Int]
times = [0..]

minusOne :: Double
minusOne = -1.0

--can have eg discrete or continuous compounding
type Compounding = Double -> Int -> Maybe Double

--discounting and present value--
discreteCompounding :: Compounding
discreteCompounding yield elapsed 
    | yield > minusOne = Just ( 1.0/ (1.0 + yield)^elapsed )
    | otherwise = Nothing

continuousCompounding :: Compounding
continuousCompounding yield elapsed 
    | yield > minusOne = Just (exp( minusOne * yield * fromIntegral
elapsed ) )
    | otherwise = Nothing

pvs :: Compounding -> Double -> [Double] -> Maybe [Double]
pvs df yield cashflow = zipWithM ( \c -> (>>= \d -> return $ c*d ) )
cashflow discounts
    where discounts = map discount times
          discount = df yield



More information about the Beginners mailing list