
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?

On 17 February 2011 19:13, Javier M Mora
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)
Although my suggestion is not to use a monad for this problem, assuming this is a learning exercise, a solution using the state monad is as follows. I'll keep the main function exactly as you wanted. sumM x = sum $ fst $ execState ([],[]) x or, point-free: sumM = sum . fst . flip execState ([],[]) Here, sumM executes the given state monad, and we end up with the pair of selected and not-selected elements. Then project the fst component, and sum them up. makeList n = put ([],[1..n]) makeList initialises the state. multiples n = chooseIf (\ i -> i `mod` n == 0) multiplies chooses those elements satisfying the given criteria. chooseIf is a helper function I've chosen to define. Obviously, you can do just fine without it. chooseIf f = do a <- gets fst (b,c) <- partition f <$> gets snd put (a++b,c) chooseIf partitions the list of candidates into 2, b is the list of elements satisfying the condition, c is the elements not satisfying it. (Remark: ++ is O(n)) And that should be it. If you plug these all together, you'll get 33 as the answer. That is the sum of [3,6,9,5,10]. I don't know why you didn't include 10 in the list of candidates, but if that is very important you can remove it by modifying makeList. Hope this helps. Ozgur

On 17/02/11 20:54, Ozgur Akgun wrote:
On 17 February 2011 19:13, Javier M Mora
mailto:jamarier@gmail.com> wrote: 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)
Although my suggestion is not to use a monad for this problem, assuming this is a learning exercise, a solution using the state monad is as follows.
Yes, I'm trying to learn/practice Design Patterns in Haskell making euler problems three times: 1. Non Monad 2. Ad-hoc Monad 3. Standard Monad Thank you for help me in the 3rd Stage. I was trying to solve 2nd Stage. :-(
[...]
And that should be it. If you plug these all together, you'll get 33 as the answer. That is the sum of [3,6,9,5,10]. I don't know why you didn't include 10 in the list of candidates, but if that is very important you can remove it by modifying makeList.
I don't included 10 because the the original problem say multiples below X. But as you know it isn't very important.
Hope this helps.
Yes, a lot. I understand standard libraries are very well done. But they are a bit difficult to understand source code for me yet. That is the point of try very easy problems with ad-hoc Monads. Understand what problems presents Monads and how to solve.
Ozgur
Jamarier.

On Thursday 17 February 2011 22:02:58, Javier M Mora wrote:
Yes, I'm trying to learn/practice Design Patterns in Haskell making euler problems three times:
1. Non Monad
That's easy for this one. And I don't think this problem lends itself well to a monadic approach (it can be done okay enough with a State and/or Writer, but it still seems artificial to use those).
2. Ad-hoc Monad
The problem is too specialised to fit a custom Monad to it, I think. There's only one (base) type involved, so you have not enough to find out how (>>=) :: m a -> (a -> m b) -> m b should work.
3. Standard Monad
State 1: import Data.List (partition) multiples :: Integral a => a -> State [a] [a] multiples k = state (partition (\m -> m `mod` k == 0)) -- if you use mtl-1.*, replace the lowercase state with State -- could also be any Integral type euler1M :: [Integer] -> State [Integer] Integer euler1M nums = do mlists <- mapM multiples nums return (sum $ concat mlists) -- or, special and not general -- euler1 :: State [Integer] Integer -- euler1M = do -- m3 <- multiples 3 -- m5 <- multiples 5 -- return (sum m3 + sum m5) euler1 :: [Integer] -> Integer -> Integer euler1 nums limit = evalState (euler1M nums) [1 .. limit-1] answer = euler1 [3,5] 1000 State 2: import Data.List (partition) multiples :: Integral a => a -> State ([a],[a]) () multiples k = state $ \(v,c) -> let (nv,nc) = partition (\m -> m `mod` k == 0) c in ((), (nv ++ v, nc)) validSum :: Num a => State ([a],[a]) a validSum = state $ \s@(v,_) -> (sum v, s) euler1M :: Integral a => [a] -> State ([a],[a]) a euler1M nums = do mapM_ multiples nums validSum Writer: import Data.List (partition) multiples :: Integral a => [a] -> a -> Writer [a] [a] multiples candidates k = writer (partition (\m -> m `mod` k /= 0) candidates -- For mtl-1.*, that has to be Writer euler1M :: Integral a => [a] -> [a] -> Writer [a] [a] euler1M = foldM multiples euler1 :: [Integer] -> Integer -> Integer euler1 nums limit = sum . execWriter $ euler1M [1 .. limit-1] nums Really, there are problems that lend themselves better to a monadic approach.
Thank you for help me in the 3rd Stage. I was trying to solve 2nd Stage. :-(

On 17 February 2011 21:02, Javier M Mora
Yes, I'm trying to learn/practice Design Patterns in Haskell making euler problems three times:
1. Non Monad 2. Ad-hoc Monad 3. Standard Monad
Thank you for help me in the 3rd Stage. I was trying to solve 2nd Stage. :-(
Sorry for jumping over one of the stages then :) For this problem though, I can't see what the semantics of your ad-hoc monad would be. You'll end up reimplementing a state monad, I suppose. If so, you can always check the definition of the "standard" state monad: http://hackage.haskell.org/packages/archive/mtl/1.1.1.1/doc/html/Control-Mon... http://hackage.haskell.org/packages/archive/mtl/1.1.1.1/doc/html/src/Control... (Disclaimer: This one is mtl-1, in mtl-2 there is no State monad. There is the StateT monad transformer, whose Monad instance declaration might be a bit harder to get a grasp of, and State s is a type alias to StateT s Identity) -- Ozgur Akgun

On 18/02/11 11:46, Ozgur Akgun wrote:
On 17 February 2011 21:02, Javier M Mora
mailto:jamarier@gmail.com> wrote: Yes, I'm trying to learn/practice Design Patterns in Haskell making euler problems three times:
1. Non Monad 2. Ad-hoc Monad 3. Standard Monad
Thank you for help me in the 3rd Stage. I was trying to solve 2nd Stage. :-(
Sorry for jumping over one of the stages then :)
For this problem though, I can't see what the semantics of your ad-hoc monad would be. You'll end up reimplementing a state monad, I suppose. If so, you can always check the definition of the "standard" state monad:
http://hackage.haskell.org/packages/archive/mtl/1.1.1.1/doc/html/Control-Mon...
http://hackage.haskell.org/packages/archive/mtl/1.1.1.1/doc/html/src/Control...
(Disclaimer: This one is mtl-1, in mtl-2 there is no State monad. There is the StateT monad transformer, whose Monad instance declaration might be a bit harder to get a grasp of, and State s is a type alias to StateT s Identity)
Great!!!!! When I saw source code of State I saw mtl-2 and it's mandarin for me The mtl-1 versión it's more clear. Here is my 2nd Stage version: As we said before it's only for learning purposes ;-) I've create a ad-hoc Monad witch is a Reduced versión of State Monad. The big diference is here satus data are a fixed type (Data). main = do print $ evalState $ do listM 100 multiplesM 3 multiplesM 5 sumM -- first list values to add, second list values not valid yet. type Data = ([Int],[Int]) -- empty state. emptyData :: Data emptyData = ([],[]) newtype MyState v = MyState { runState :: (Data -> (v,Data)) } -- functions to extract info from MyState calcState :: MyState v -> (v,Data) calcState m = runState m emptyData evalState :: MyState v -> v evalState = fst.calcState execState :: MyState v -> Data execState = snd.calcState -- Instanciating Monad. instance Monad MyState where return v = MyState $ \ d -> (v,d) m >>= k = MyState $ \ d -> let (a, d') = runState m d in runState (k a) d' -- DSL instructions listM :: Int -> MyState [Int] listM max = MyState (\(values,_) -> (list, (values,list)) ) where list = [1..max-1] sumM :: MyState Int sumM = MyState $ \ d@(values,_) -> (sum values, d) multiplesM :: Int -> MyState Int multiplesM divider = MyState $ \ (values,candidates) -> let count = length nvalues (nvalues, ncandidates) = partition (multiple divider) candidates in (count,(values++nvalues,ncandidates)) What I've learned? + I thought every line or "DSL instruction" in a do extructure has the same type than "k" in Monad: (a -> m b). That it's not true! every line in do sintax has to be a monad: m b (in this case: MyState _). like "sumM", "listM 10" or "multiplesM 3". do-sintax convert that monad expresions in a -> mb if It's used x <- Monad value. + I'm starting to think that if you want pass information from line to line in the do-sintax, the internal structure of the monad has to be a function to access information and drop to next line. thanks to all. and to Ozgur to show me the path jamarier.
participants (3)
-
Daniel Fischer
-
Javier M Mora
-
Ozgur Akgun