所以我正在尝试为可变长度元组创建一个类型,基本上是Either a (Either (a,b) (Either (a,b,c) ...))
和Either (Either (Either ... (x,y,z)) (y,z)) z
的更漂亮的版本。
{-# LANGUAGE TypeOperators, TypeFamilies, MultiParamTypeClasses, FlexibleInstances #-}
module Temp where
-- type level addition
data Unit
data Succ n
class Summable n m where
type Sum n m :: *
instance Summable Unit m where
type Sum Unit m = Succ m
instance Summable n m => Summable (Succ n) m where
type Sum (Succ n) m = Succ (Sum n m)
-- variable length tuple, left-to-right
data a :+ b = a :+ Maybe b
infixr 5 :+
class Prependable t r s where
type Prepend t r s :: *
prepend :: r -> Maybe s -> Prepend t r s
instance Prependable Unit x y where
type Prepend Unit x y = x :+ y
prepend = (:+)
instance Prependable n x y => Prependable (Succ n) (w :+ x) y where
type Prepend (Succ n) (w :+ x) y = w :+ Prepend n x y
prepend (w :+ Nothing) _ = w :+ Nothing
prepend (w :+ Just x) y = w :+ Just (prepend x y)
-- variable length tuple, right-to-left
data a :- b = Maybe a :- b
infixl 5 :-
class Appendable t r s where
type Append t r s :: *
append :: Maybe r -> s -> Append t r s
instance Appendable Unit x y where
type Append Unit x y = x :- y
append = (:-)
instance Appendable n x y => Appendable (Succ n) x (y :- z) where
type Append (Succ n) x (y :- z) = Append n x y :- z
append _ (Nothing :- z) = Nothing :- z
append x (Just y :- z) = Just (append x y) :- z
但是,编译器似乎无法在递归情况下推断出prepend
或append
的幻像类型参数:
Temp.hs:32:40:
Could not deduce (Prepend t1 x y ~ Prepend n x y)
from the context (Prependable n x y)
bound by the instance declaration at Temp.hs:29:10-61
NB: `Prepend' is a type function, and may not be injective
In the return type of a call of `prepend'
In the first argument of `Just', namely `(prepend x y)'
In the second argument of `(:+)', namely `Just (prepend x y)'
Temp.hs:49:34:
Could not deduce (Append t0 x y ~ Append n x y)
from the context (Appendable n x y)
bound by the instance declaration at Temp.hs:46:10-59
NB: `Append' is a type function, and may not be injective
In the return type of a call of `append'
In the first argument of `Just', namely `(append x y)'
In the first argument of `(:-)', namely `Just (append x y)'
我能做些什么来帮助编译器进行推理吗?
答案 0 :(得分:7)
此处错误消息的重要部分是:
NB: `Prepend' is a type function, and may not be injective
这是什么意思?这意味着可能有多个instance Prependable
这样type Prepend ... = a
,因此,如果您将某些Prepend
推断为a
,则您不一定知道它属于哪个实例到。
你可以使用data types in type families来解决这个问题,它的优势在于你不处理类型函数,这些函数是完全的,但可能是单射的,而不是类型“关系“,这是双射的(因此每个Prepend
类型只能属于一个类型系列,并且每个类型系列都有不同的Prepend
类型。”
(如果您希望我在类型系列中显示包含数据类型的解决方案,请发表评论!基本上,只需使用data Prepend
代替type Prepend
)
答案 1 :(得分:1)
我想出的解决方案是添加一个伪参数来将prepend
和append
绑定到幻像参数:
-- as above, except...
unsucc :: Succ n -> n
unsucc _ = undefined
class Prependable t r s where
type Prepend t r s :: *
prepend :: t -> r -> Maybe s -> Prepend t r s
instance Prependable Unit x y where
type Prepend Unit x y = x :+ y
prepend _ = (:+)
instance Prependable n x y => Prependable (Succ n) (w :+ x) y where
type Prepend (Succ n) (w :+ x) y = w :+ Prepend n x y
prepend _ (w :+ Nothing) _ = w :+ Nothing
prepend t (w :+ Just x) y = w :+ Just (prepend (unsucc t) x y)
class Appendable t r s where
type Append t r s :: *
append :: t -> Maybe r -> s -> Append t r s
instance Appendable Unit x y where
type Append Unit x y = x :- y
append _ = (:-)
instance Appendable n x y => Appendable (Succ n) x (y :- z) where
type Append (Succ n) x (y :- z) = Append n x y :- z
append _ _ (Nothing :- z) = Nothing :- z
append t x (Just y :- z) = Just (append (unsucc t) x y) :- z