[Haskell-cafe] do {x<-[1,2,3]; True <- return (odd x); return x}.. why? (do notation, monads, guards)

Daniel Fischer daniel.is.fischer at web.de
Sun Jan 8 09:10:21 EST 2006


Am Sonntag, 8. Januar 2006 01:19 schrieb Marc Weber:
> 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 ?

Let's figure that out (I use Int, although Integral a => a is the most general 
type).
Overall, we have 'ok :: Int -> [b]', from the expression '[1,2,3] >>= ok'.
Now in line 1r3 we see that ok x (since that pattern is irrefutable, there's 
no need for line 1r4) is 'return (odd x) >>= ok2', so by that line alone we 
can infer the type 'Monad m => Bool -> m c' for ok2. But the result of ok2 is 
the result of ok, so we find '[b] === m c', hence in line 1r3, >>= is used at 
type [Bool] -> (Bool -> [b]) -> [b]. Finally, by 1r1 we see that 'b' is the 
input-type of ok, i.e. Int, so our type-inference has led to

list1annotated
    = let ok :: Int -> [Int]
          ok x = let ok2 :: Bool -> [Int]
                     ok2 True = return x     -- might as well write [x]
                     ok2 _      = fail "ok2"
                 in ((>>=) :: [Bool] -> (Bool -> [Int]) -> [Int]) (return (odd 
x) :: [Bool]) ok2
      in ((>>=) :: [Int] -> (Int -> [Int]) -> [Int]) [1,2,3] ok


>
>    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? -}
>
The difference is not really in the types a, b, but in the monad m.
For [] we have

list >>= func = concatMap func list,

for Maybe it's

Just x  >>= func = func x
Nothing >>= func = Nothing

and look at the code for more, I can recommend -- besides the 
Control.Monad.Whichevers -- ReadP and Parsec. If you've spent some time 
grasping that, you'll become more comfortable with monads.

>
>
> 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?
Exactly.

>     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] ? -}

mzero is not a constructor (as witnessed by the lowercase spelling), but a 
special value that 'm a' must contain for a MonadPlus m (and arbitrary a).

One of the laws requested for instances of MonadPlus is
'mzero >>= f === mzero'. For lists, this is fulfilled, since

concat (map f []) = concat [] = [].

If we evaluate the above ok, we have

ok 1 = guard (odd 1) >> return 1
     = guard True >>= (\_ -> return 1)
     = return () >>= (\_ -> return 1)
     = [()] >>= (\_ -> return 1)
     = concat $ map (\_ -> return 1) [()]
     = concat $ [return 1]
     = concat [[1]]
     = [1]

ok 2 = guard (odd 2) >> return 2
     = guard False >> return 2
     = mzero >>= (\_ -> return 2)
     = concat $ map (\_ -> return 2) []
     = concat []
     = []

>
>
> 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

Hope that helps,
Daniel


More information about the Haskell-Cafe mailing list