[Haskell-cafe] passing a polymorphic function as a parameter vs
using it directly in a function definition
Pasqualino "Titto" Assini
tittoassini at gmail.com
Thu Jul 15 05:50:16 EDT 2010
Hi,
can anyone please explain why in the following code evalAST compiles
while evalAST2 doesn't?:
Is that because the polymorphic function k is specialised in two
different ways in evalAST while in evalAST2 it is constrained to be
the same function?
{-# LANGUAGE GADTs #-}
test = evalAST (TxtA "abc")
-- This is OK
evalAST :: AST -> IO ()
evalAST (IntA i) = k $ Lit i
evalAST (TxtA i) = k $ Lit i
k :: (Show a) => Expr a -> IO ()
k e = print $ eval e
-- This is the same thing, only the k function is passed as a parameter.
-- But it won't compile.
-- I would expect its type to be:
-- evalAST2 :: (Expr a -> IO()) -> AST -> IO ()
-- But is actually:
-- evalAST2 :: (Expr Int -> IO ()) -> AST -> IO ()
evalAST2 k (IntA i) = k $ Lit i
-- evalAST2 k (TxtA i) = k $ Lit i
-- The untyped expression
data AST = IntA Int | TxtA String
-- A typed expression.
data Expr a where Lit :: a -> Expr a
eval :: Expr a -> a
eval (Lit i) = i
Thanks
titto
More information about the Haskell-Cafe
mailing list