Confused about Monad output
Dean Herington
heringto@cs.unc.edu
Wed, 30 Jan 2002 18:09:58 -0500 (EST)
You have an extra `show` in the `Show` instance for `Out`.
Change `show x` to `x` there.
On Wed, 30 Jan 2002, Shawn P. Garbett wrote:
> -----BEGIN PGP SIGNED MESSAGE-----
> Hash: SHA1
>
> I've been fiddling with the example in section 10.2 of Bird's book,
> _Introduction_to_Functional_Programming_. I can't seem to make sense of why
> the output appears as it does. It's as if the final evaluation through Show
> doesn't take place, is there some critical piece of syntax missing?
>
> I expect:
>
> Main> evalOut(answer)
> term: Con 1972, yields 1972
> term: Con 2, yields 2
> term: Div (Con 1972) (Con 2), yields 986
> term: Con 23, yields 23
> term: Div(Div(Con 1972)(Con 2))(Con 23), yields 42
> value: 42
>
> but I get:
>
> Main> evalOut(answer)
> ("term: Con 1972, yields 1972\nterm: Con 2, yields 2\nterm: Div (Con 1972)
> (Con 2), yields 986\nterm: Con 23, yields 23\nterm: Div (Div (Con 1972) (Con
> 2)) (Con 23), yields 42\n",42)
> (1149 reductions, 3134 cells)
> Main>
>
>
> Here's the program:
>
> data Term = Con Int | Div Term Term
> deriving(Show)
>
> - -- 10.2.5 Monadic evaluator
> eval :: Monad m => Term -> m Int
> eval (Con x) = return x
> eval (Div t u) = do x <- eval t
> y <- eval u
> return (x `div` y)
>
> - -- Examples to try
>
> answer, wrong :: Term
> answer = Div ( Div ( Con 1972 ) (Con 2)) (Con 23)
> wrong = Div (Con 2) (Div (Con 1)(Con 0))
>
> - -- Output monad
> newtype Out a = MkOut (String, a)
>
> instance Monad Out where
> return x = MkOut ("", x)
> p >>= q = MkOut (ox ++ oy, y)
> where MkOut (ox, x) = p
> MkOut (oy, y) = q x
>
> instance Show a => Show (Out a) where
> show (MkOut (x,y)) = show x ++ "value: " ++ show y
>
> - -- operation to generate output
>
>
> out :: String -> Out()
> out ox = MkOut (ox, ())
>
>
> line :: Term -> Int -> String
> line t x = "term: " ++ show t ++ ", yields " ++ show x ++ "\n"
>
> evalOut :: Term -> Out Int
> evalOut (Con x) = do out (line(Con x) x)
> return x
> evalOut (Div t u) = do x <- evalOut t
> y <- evalOut u
> out(line(Div t u) (x `div` y))
> return (x `div` y)
>
>
> Shawn