[Haskell-beginners] Monadic Project Euler 1

Javier M Mora jamarier at gmail.com
Thu Feb 17 20:13:08 CET 2011


Hi, I'm trying to improve my skills with monads.

I'm started with project Euler problems but creating/using Monads.
I know that can be an overkill approach but, they are easy enough to 
focus in monad only.

First Step: What I want?
------------------------


In this problem: I think monads as a DSL (Domain Specific Language)

main = do
   print $ sumM $ do
     makeList 10        -- create candidates list
     multiples 3        -- choose multiples of 3
     multiples 5        -- choose multiples of 5 (not choosed yet)

Data under de monad is a pair of lists:
(validValues, CandidatesNonValidYet)


so
   makeList 10 = MyState ([],[1,2,3,4,5,6,7,8,9])

after
   multiples 3 -> MyState ([3,6,9],[1,2,4,5,7,8])

after
   multiples 5 -> MyState ([3,5,6,9],[1,2,4,7,8])


Second Step: What I have?
-------------------------


newType MyState a = MyState {execMyState :: ([a],[a])}

sumM :: (Integral a) => MyState a -> a
sumM = sum $ fst $ execMyState

makeList:: (Integral a) => a -> MyState a
makeList max = MyState ([],[1..max-1])
-- maybe: makeList max = return [1..max-1]


Third Step: function prototypes
-------------------------------

ideal:

multiple :: (Integral a) => a -> [a] -> MyState a

less ideal

multiple :: (Integral a) => a -> ([a],[a]) -> MyState a


Fourth Step: Instanciate Monad
------------------------------

instance Monad MyState where
   return = error "no implemented"
   --(>>=) :: (Monad m) => m a -> (a -> m b) -> m b
   m >>= k = let (v, c) = execMyState m
                 n      = k c
                 (nv, nc) = execMyState n
             in MyState (v++nv, nc)

with this instanciation: k :: a -> m b
but (multiple 3) :: [a] -> MyState a

in one the function ask for a value "a" type and in the other case for a 
list. So, doesn't compile :-(


Second option:

newType MyState a = MyState {execMyState :: (a,a)}

I like more the other option, because when you say "MyState Int" or 
"MyState float" you're saying than the possibilities are type Int or 
float or whatever. With this option (the second) you have to coerce that 
a type have to be a container in other part.

if I can force (MonadPlus a) :

instance Monad MyState where
   return a = MyState (a,mzero)
   --(>>=) :: (Monad m) => m a -> (a -> m b) -> m b
   m >>= k = let (v, c) = execMyState m
                 n      = k c
                 (nv, nc) = execMyState n
             in MyState (v `mplus` nv, nc)


or maybe I must use Monoid... but I don't know how force that
and here I'm stuck


Any hints?













More information about the Beginners mailing list