考虑以下Haskell代码(GHC 8.2):
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
import Data.Constraint
type family Head xs where
Head (x ': xs) = x
type family Tail xs where
Tail (x ': xs) = xs
class IsList xs where
isList :: (xs ~ '[] => r) -> ((xs ~ (Head xs ': Tail xs), IsList (Tail xs)) => r) -> r
instance IsList '[] where isList r _ = r
instance IsList xs => IsList (x ': xs) where isList _ r = r
type family Prepend xs ys where
Prepend '[] ys = ys
Prepend (x ': xs) ys = x ': Prepend xs ys
prependPreservesIsList :: forall xs ys. (IsList xs, IsList ys) => Dict (IsList (Prepend xs ys))
prependPreservesIsList = isList @xs Dict (withDict (prependPreservesIsList @(Tail xs) @ys) Dict)
class IsList (Deps a) => Hard (a :: *) where
type Deps a :: [*]
instance (Hard a, Hard b) => Hard (Either a b) where
type Deps (Either a b) = Prepend (Deps a) (Deps b)
失败并
Main.hs:37:10: error:
• Could not deduce (IsList (Prepend (Deps a) (Deps b)))
arising from the superclasses of an instance declaration
from the context: (Hard a, Hard b)
bound by the instance declaration at Main.hs:37:10-46
• In the instance declaration for ‘Hard (Either a b)’
|
37 | instance (Hard a, Hard b) => Hard (Either a b) where
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
代码试图做的是构造一个类Hard
,该类具有一个类型为Deps
的关联列表,其中对应于Deps
的{{1}}应该是是与Either a b
和Deps
对应的a
的串联。
正如b
所见证的那样,我们知道如何向GHC证明这种连接形式保留了IsList
类。如果我们有prependPreservesIsList
,并且需要编写需要(Hard a, Hard b)
的普通代码,那么我们只需(IsList (Deps (Either a b)))
就可以了。但是我们需要GHC在“编译时”识别此约束,以便授予withDict prependPreservesIsList
实例合法。
有什么办法在编译时“打开约束字典”,或者以其他方式伪造此代码以使GHC接受Either a b
实例?
答案 0 :(得分:2)
考虑从类型级别列表切换到类型级别树。所以:
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
data Tree a = Empty | Node a | Branch (Tree a) (Tree a)
class IsTree xs where
isTree ::
(xs ~ 'Empty => a) ->
(forall x. xs ~ 'Node x => a) ->
(forall l r. (xs ~ 'Branch l r, IsTree l, IsTree r) => a) ->
a
instance IsTree 'Empty where isTree a _ _ = a
instance IsTree ('Node x) where isTree _ a _ = a
instance (IsTree l, IsTree r) => IsTree ('Branch l r) where isTree _ _ a = a
class IsTree (Deps a) => Hard a where
type Deps a :: Tree *
instance (Hard a, Hard b) => Hard (Either a b) where
type Deps (Either a b) = 'Branch (Deps a) (Deps b)
答案 1 :(得分:0)
还有另一种表示类型类约束的方法,即第一类字典(Dict
),尽管它并不符合人体工程学:
class Hard a where
type Deps a :: [*]
depsIsList :: Dict (IsList (Deps a))
instance (Hard a, Hard b) => Hard (Either a b) where
type Deps (Either a b) = Prepend (Deps a) (Deps b)
depsIsList =
case depsIsList @a of
Dict ->
case depsIsList @b of
Dict -> prependPreservesIsList @(Deps a) @(Deps b)
使用 constraints 包中的(:-)
可能会使编写这样的字典的痛苦减轻一些。