考虑以下GADT定义的表达式functor:
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
import Control.Monad.Free
data ExprF :: * -> * where
Term :: Foo a -> (a -> r) -> ExprF r
instance Functor ExprF where
fmap f (Term d k) = Term d (f . k)
type Expr = Free ExprF
其中Foo
定义为
data Foo :: * -> * where
Bar :: Int -> Foo Int
Baz :: Double -> Foo Double
instance Show a => Show (Foo a) where
show (Bar j) = show j
show (Baz j) = show j
(a -> r)
中的ExprF
字段与(其他理想的)限制性GADT构造函数的组合似乎使编写一个漂亮的打印解释器变得不可能:
pretty (Pure r) = show r
pretty (Free (Term f k)) = "Term " ++ show f ++ pretty (k _)
类型漏洞是人们所期望的:
Found hole ‘_’ with type: a1
Where: ‘a1’ is a rigid type variable bound by
a pattern with constructor
Term :: forall r a. Foo a -> (a -> r) -> ExprF r,
in an equation for ‘pretty’
at Test.hs:23:15
Relevant bindings include
k :: a1 -> Free ExprF a (bound at Test.hs:23:22)
f :: Foo a1 (bound at Test.hs:23:20)
pretty :: Free ExprF a -> String (bound at Test.hs:22:1)
In the first argument of ‘k’, namely ‘_’
In the first argument of ‘pretty’, namely ‘(k _)’
In the second argument of ‘(++)’, namely ‘pretty (k _)’
似乎没有办法给延续赋予它所需类型的值。该类型在f
中编码,而我正在使用的其他解释器都以某种方式处理f
来提取适当类型的值。但是String
表示的路径似乎被阻止了。
我在这里缺少一些常见的习语吗?如果确实可能的话,如何打印Expr
的价值呢?如果不可能,ExprF
的替代结构可能会捕获相同的结构,但也支持漂亮的打印机?
答案 0 :(得分:4)
f
上的模式匹配。如果您这样做,k
的类型会被细化以匹配Foo
中包含的类型:
pretty (Pure r) = show r
pretty (Free (Term f k)) = "Term " ++ show f ++ pretty r where
r = case f of
Bar a -> k a
Baz a -> k a
您可能想要分解这种模式:
applyToFoo :: (a -> r) -> Foo a -> r
applyToFoo f (Bar a) = f a
applyToFoo f (Baz a) = f a
pretty (Pure r) = show r
pretty (Free (Term f k)) = "Term " ++ show f ++ pretty (applyToFoo k f)
答案 1 :(得分:2)
嗯,这不是不可能的。至少你可以在f
上进行模式匹配:
pretty :: (Show a) => Expr a -> String
pretty (Pure r) = show r
pretty (Free (Term f@(Bar x) k)) = "Term " ++ show f ++ pretty (k x)
pretty (Free (Term f@(Baz x) k)) = "Term " ++ show f ++ pretty (k x)
但这不是很令人满意,因为你已经在Foo
show
个实例中做过了。
然后,挑战是适当抽象。