{-# LANGUAGE RankNTypes #-}
继续previous series of questions,我有一个普遍的功能 量化函数作为参数,如下:
emap :: (forall a. Expression a -> Expression a) -> Expression b -> Expression b
对于不需要其他约束的函数,可以使用它,例如:
postmap :: (forall a. Expression a -> Expression a) -> Expression b -> Expression b
postmap f = f . emap (postmap f)
reduce = postmap step
但是,我现在想要将此函数与一个额外的函数一起使用 约束,但以下不进行类型检查。
substitute :: Pack a => Identifier -> a -> Expression a -> Expression a
substitute i v (Var x) | x == i = pack v
substitute _ _ x = x
bind :: Pack a => Identifier -> a -> Expression a -> Expression a
bind ident value = postmap (subsitute ident value)
所以我似乎需要以某种方式削弱'或者'专门化'对{的forall a
约束
forall a. Pack a
约束。似乎似乎没有必要将约束添加到
emap
本身的签名,但我无法看到解决此问题的任何其他方法。
我不确定如何解决这个问题,但我可以看到一些选项。
bind
的签名周围添加约束,以便它可以愉快
类型检查。emap'
,并根据实现emap'
emap
或反之亦然(emap
是一个无聊的机械定义,它不会使
感觉有两个相同的功能体,只有签名不同。)答案 0 :(得分:5)
假设您重写了type T = forall a . Expression a -> Expression a
和postmap' :: T -> T
之类的所有内容。我认为应该清楚postmap
的类型是相同的。 (您可以尝试>:t [postmap', postmap]
)。
鉴于substitute :: Pack a => Identifier -> a -> Expression a -> Expression a
,请考虑您对bind
的定义:您将参数传递给postmap
,该参数需要类型为T
的值;但是你给它一个Expression a -> Expression a
类型的值。小心!这些类型不一样,因为在后一种情况下,forall a
位于左侧; postmap
期待 it 可以选择a
的函数,但是如果其他人已经选择a
,则会给它一个函数。假设您的示例是要进行类型检查,然后使用bind
调用a ~ ()
。赋予postmap
的函数类型必须为Expression () -> Expression ()
,但这显然是无稽之谈。
如果我不是很清楚,请考虑“工作”版本:
type T = forall a . Expression a -> Expression a
postmap :: T -> T
postmap = undefined
-- These two substitutes have different types!
substitute :: Pack a => Identifier -> a -> Expression a -> Expression a
substitute = undefined
substitute' :: Pack a => Identifier -> a -> T
substitute' = undefined
-- Doesn't compile
bind :: Pack a => Identifier -> a -> Expression a -> Expression a
bind ident value = postmap (substitute ident value)
-- Does compile!
bind' :: Pack a => Identifier -> a -> T
bind' ident value = postmap (substitute' ident value)
需要注意的重要事项是:无论是如上定义还是type T = forall a . Pack a => ...
,错误都是一样的。所以你的问题与你认为的不同。
调试这类问题的简便方法是使用
newtype T = T (forall a . Expression a -> Expression a)
错误通常更清楚(尽管不是在这种情况下)。我很抱歉我无法提供真正的解决方案,因为我不确切知道这些功能究竟在做什么。但我怀疑#3是你的答案。
答案 1 :(得分:3)
首先,让我们用足够的代码充实您的示例。 LiteralToken
只是代表用。替换变量的任何内容。
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE StandaloneDeriving #-}
type Identifier = String
data LiteralToken = LiteralToken
deriving Show
class Pack a where
pack :: a -> LiteralToken
instance Pack Int where
pack = const LiteralToken
data Expression a where
Var :: Identifier -> Expression a
Lit :: LiteralToken -> Expression a
Tuple :: Expression a -> Expression b -> Expression (a, b)
deriving instance Show (Expression a)
emap :: (forall a. Expression a -> Expression a) -> Expression b -> Expression b
emap f e = case e of
Tuple a b -> Tuple (f a) (f b)
otherwise -> e
postmap :: (forall a. Expression a -> Expression a) -> Expression b -> Expression b
postmap f = f . emap (postmap f)
bind :: Pack a => Identifier -> a -> Expression b -> Expression b
bind ident value = postmap (substitute ident value)
现在,我们可以为substitute
实施Identifier
。要在emap
或postmap
中使用,substitute
需要能够对Expression
树的所有部分进行操作,无论它是否属于同一类型作为被替换的变量。这就是为什么Expression
的类型变量与值的类型变量不同(这也是user2407038 explains)。
substitute :: Pack a => Identifier -> a -> Expression b -> Expression b
substitute ident value e = case e of
Var id | id == ident -> Lit (pack value)
otherwise -> e
现在我们可以尝试一些例子:
example1 :: Expression (Int, Bool)
example1 = Tuple (Var "x") (Var "y")
print . bind "x" (7 :: Int) $ example1
Tuple (Lit LiteralToken) (Var "y")
如果我们的标识符类型错误,我们无法获得我们想要的内容,无论如何都要替换它。那是因为substitute
无法检查它所代替的变量的类型。在以下示例中,Var "x"
被替换为Int
的文字,即使第二个变量是Bool
。
example2 :: Expression (Int, Bool)
example2 = Tuple (Var "x") (Var "x")
print . bind "x" (7 :: Int) $ example2
Tuple (Lit LiteralToken) (Lit LiteralToken)
如果我们将一个类型变量添加到LiteralToken
,以便它以某种方式取决于它所代表的类型
data LiteralToken a = LiteralToken
deriving Show
class Pack a where
pack :: a -> LiteralToken a
data Expression a where
Var :: Identifier -> Expression a
Lit :: LiteralToken a -> Expression a
Tuple :: Expression a -> Expression b -> Expression (a, b)
我们之前的substitute
会出现编译错误。
Could not deduce (b ~ a)
...
In the first argument of `pack', namely `value'
In the first argument of `Lit', namely `(pack value)'
In the expression: Lit (pack value)
substitute
需要一些方法来检查它正在运行的类型是否正确。 Data.Typeable
解决了这个问题。要求变量表示的任何术语都具有运行时可识别类型,这似乎是不合理的,因此将此约束添加到Expression
树本身是合理的。或者,我们可以在表达式树中添加一个类型注释,它可以提供任何术语属于特定类型的证明。我们将遵循第二条路线。这将需要一些进口。
import Data.Typeable
import Data.Maybe
这里扩展了表达式树以包含类型注释。
data Expression a where
Var :: Identifier -> Expression a
Lit :: LiteralToken a -> Expression a
Tuple :: Expression a -> Expression b -> Expression (a, b)
Typed :: Typeable a => Expression a -> Expression a
emap :: (forall a. Expression a -> Expression a) -> Expression b -> Expression b
emap f e = case e of
Tuple a b -> Tuple (f a) (f b)
Typed a -> Typed (f a)
otherwise -> e
bind
和substitute
现在只能处理Typeable
个变量。替换缺少类型注释的变量什么都不做,变量保持不变。
bind :: (Pack a, Typeable a) => Identifier -> a -> Expression b -> Expression b
bind ident value = postmap (substitute ident value)
substitute :: (Pack a, Typeable a) => Identifier -> a -> Expression b -> Expression b
substitute ident value e = case e of
Typed (Var id) | id == ident -> fromMaybe e . fmap Typed . gcast . Lit . pack $ value
otherwise -> e
substitute
中的所有类型检查和转换工作均由gcast
完成。来自函数签名的Typeable a
提供了由a
构建的LiteralToken a
中的Lit . pack $ value
具有Typeable
实例的证据。 Typed
中的case
构造函数提供了输出表达式类型b
也具有Typeable
实例的证明。请注意,如果删除了fmap Typed
,代码仍然有用;它只是保留了类型注释。
以下两个功能可以轻松添加类型注释
typed :: Typeable a => Expression a -> Expression a
typed t@(Typed _) = t
typed e = Typed e
typedVar :: Typeable a => Identifier -> Expression a
typedVar = Typed . Var
我们的两个例子现在做我们希望他们做的事情。尽管两个变量名在第二个示例中都相同,但这两个示例仅替换整数变量。我们使用智能typedVar
构造函数而不是Var
来构建带有类型注释的所有变量。
example1 :: Expression (Int, Bool)
example1 = Tuple (typedVar "x") (typedVar "y")
print . bind "x" (7 :: Int) $ example1
Tuple (Typed (Lit LiteralToken)) (Typed (Var "y"))
example2 :: Expression (Int, Bool)
example2 = Tuple (typedVar "x") (typedVar "x")
print . bind "x" (7 :: Int) $ example2
Tuple (Typed (Lit LiteralToken)) (Typed (Var "x"))
为了好玩,我们可以在表达式树上实现类型推断。与Haskell不同,这种非常简单的类型推断只能从叶子到根部进行。
inferType :: Expression a -> Expression a
inferType e = case e of
Typed t@(Typed _) -> t
t@(Tuple (Typed _) (Typed _)) -> typed t
otherwise -> e
inferTypes = postmap inferType
print . inferTypes $ example1
Typed (Tuple (Typed (Var "x")) (Typed (Var "y")))