
Here is a simple program implementing the above function in 4 different ways.. See my comments to get to know where I have problems: ---------- begin test.hs ---------- module Main where import IO import Control.Monad.List {- list1,2 are both implementations of the same function f=[1,3] ;-) I've both rewritten with the translation rules for do notation to better understand what's going on and where the differences are -} list1=do { x <- [1,2,3]; True <- return (odd x); return x} list2=do { x <- [1,2,3]; guard (odd x); return x} -- <- provided by xerox list1rewritten :: [Int] list1rewritten=let ok x = let ok2 True = do return x --1r1 ok2 _ = fail "ok2" --1r2 in return (odd x) >>= ok2 --1r3 ok _ = fail "outer" --1r4 in [1,2,3] >>= ok {- The outer let .. in >>= is used to "call" the inner >>= for each element of [1,2,3] (the list Monad causes this) True <- return (odd x): really nice trick...! if x is odd then line --1r1 is matched the values is returned otherwise line --1r2 is matched calling fail which is implemented as = [] ignoring the message hence no element is added but I'm not sure which implementation of >>= is used in --lr3: It should satisfy (Monad m) => m Bool -> (Bool -> m Int), right ? Looking at the definition taken from GHC/Base.lhs: class Monad m where (>>=) :: forall a b. m a -> (a -> m b) -> m b and a sample implementation: instance Monad [] where m >>= k = foldr ((++) . k) [] m I wonder how a, b (from m a and m b) and m (from class Monad m) are renated? Can you tell me how the implementation declaration of m a -> (...) -> m b differs in these cases: eg: 1. a = Int, b=String 2. the other way round: a=String b=Int? -} list2rewritten :: [Int] list2rewritten = let ok x = guard (odd x) >> return x ok _ = fail "I think never used?" in [1,2,3] >>= ok {- Here ok is feeded with 1,2 and three due to the list Monad again? So fail will never be called, right? I also know that guard returns either the monad data type constructor mzero or return () But how is this used in combintation with >> return x::Int to return either [] or [x] ? -} main=do -- print result of all implementations to show that they are equal sequence [ print x| x <- [[1,3], -- [1,3] should be the result list1, list1rewritten, list2, list2rewritten ] ] -------------- end ------------------------- I hope there will be some time when I can say: Monads.. I don't bother anymore I'm practicing every night while dreaming.... ;-) Marc