"do" notation and ">>"
James B. White III (Trey)
whitejbiii@ornl.gov
Wed, 27 Mar 2002 14:59:17 -0500
Hugs appears to ignore definitions of ">>" when using "do" notation,
perhaps relying on the default definition in terms of ">>=". Here is an example.
According to the Haskell 98 Tutorial, the following two statements
should be equivalent, right?
main = do put "hello"; put "world"
main' = put "hello" >> put "world"
In the Hugs output below, it appears that they are not.
% hugs TestDo
__ __ __ __ ____ ___ _________________________________________
|| || || || || || ||__ Hugs 98: Based on the Haskell 98 standard
||___|| ||__|| ||__|| __|| Copyright (c) 1994-2001
||---|| ___|| World Wide Web: http://haskell.org/hugs
|| || Report bugs to: hugs-bugs@haskell.org
|| || Version: December 2001 _________________________________________
...
TestDo> run main
hello
>>=
world
TestDo> run main'
hello
>>
world
TestDo> :quit
[Leaving Hugs]
% cat TestDo.hs
module TestDo where
type State = [String]
newtype MyMonad a = MyMonad (State -> (a, State))
instance Monad MyMonad where
(MyMonad m) >>= fm = MyMonad $
\s -> let (x, s') = m s
MyMonad m' = fm x
s'' = ">>=" : s'
in m' s''
(MyMonad m) >> (MyMonad m') = MyMonad $
\s -> let (_, s') = m s
s'' = ">>":s'
in m' s''
return x = MyMonad (\s -> (x, "return":s))
put x = MyMonad (\s -> (s, x:s))
get = MyMonad (\s -> (s,s))
run (MyMonad m) = let (_,s) = m []
s' = map putStrLn s
in sequence_ (reverse s')
main = do put "hello"; put "world"
main' = put "hello" >> put "world"
--
James B. White III (Trey)
Center for Computational Sciences
Oak Ridge National Laboratory
whitejbiii@ornl.gov