Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1. Re:  Monadic Project Euler 1 (Javier M Mora)


----------------------------------------------------------------------

Message: 1
Date: Fri, 18 Feb 2011 21:25:22 +0100
From: Javier M Mora <jamar...@gmail.com>
Subject: Re: [Haskell-beginners] Monadic Project Euler 1
To: beginners@haskell.org
Message-ID: <4d5ed5b2.5020...@gmail.com>
Content-Type: text/plain; charset=UTF-8; format=flowed

On 18/02/11 11:46, Ozgur Akgun wrote:
> On 17 February 2011 21:02, Javier M Mora <jamar...@gmail.com
> <mailto:jamar...@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-Monad-State-Lazy.html#g:1
>
> http://hackage.haskell.org/packages/archive/mtl/1.1.1.1/doc/html/src/Control-Monad-State-Lazy.html#State
>
> (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.




------------------------------

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 32, Issue 35
*****************************************

Reply via email to