2012-01-16 35 views
5

sonucuna ulaşılamadı Bu nedenle, değişken uzunluklu çekimler için bir tür oluşturmaya çalışıyorum, temel olarak Either a (Either (a,b) (Either (a,b,c) ...)) ve Either (Either (Either ... (x,y,z)) (y,z)) z'un daha güzel bir sürümü olarak. Ben derleyici yardımcı olmak için yapabileceğiniz bir şey bu çıkarsama yapmakGHC: phantom type parametresi

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)' 

var mı:

{-# 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 

Ancak derleyici özyinelemeli durumlarda prepend veya append hayalet türü parametresi anlaması mümkün görünüyor?

NB: `Prepend' is a type function, and may not be injective 

Bu ne demek:

cevap

7

burada hata mesajının önemli bir parçasıdır? Bu, type Prepend ... = a gibi çok sayıda instance Prependable olabileceği anlamına gelir, böylece Prepend'un a olmasını alırsanız, hangi örneğe ait olduğunu bilmeniz gerekmez.

Sen (siz örten ama injektif olabilir ve bunun yerine bijective olan tip "ilişkiler", tip fonksiyonlar, anlaşma yok avantajına sahip data types in type families kullanarak Yani her bu çözebilir Prepend türü yalnızca bir tür aileye ait olabilir ve her tür ailede ayrı bir Prepend tipi bulunur.

(Bana bir yorum yazın ailelerde veri türleri ile bir çözüm göstermek bırakmak istiyorsanız! Temelde, sadece kullandıkları bir data Prepend yerine type Prepend arasında)

+0

Ah benim için hata mesajının anlamını ipuçları vermeyi için teşekkürler. – rampion

+1

Orijinal kodun * tip aileleri kullandığını unutmayın (özellikle, eşanlamlı aileleri yazın); Bunun yerine kullanması gereken veri aileleridir. – ehird

+0

@ehird, "Tür sınıflarındaki yazım takma adları" nın hala, tür ailesinin uzantısına değil, TIL'ye ait olduğunu düşündüm. – dflemstr

1

Ben ile geldi çözüm bir kukla argüman eklemek oldu fantom parametresine prepend ve append kravat:

-- 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