2012-01-16 13 views
5

Quindi sto provando a creare un tipo per tuple di lunghezza variabile, fondamentalmente come una versione più carina di Either a (Either (a,b) (Either (a,b,c) ...)) e Either (Either (Either ... (x,y,z)) (y,z)) z.GHC: impossibile dedurre il parametro di tipo fantasma

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

Tuttavia, il compilatore sembra incapace di dedurre il parametro di tipo fantasma della prepend o append nei casi ricorsive:

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

C'è qualcosa che posso fare per aiutare il compilatore a rendere questa inferenza?

risposta

7

La parte importante del messaggio di errore qui è il:

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

Cosa significa? Significa che potrebbero esserci più instance Prependable tali che il loro type Prepend ... = a, in modo che se si deduce che alcuni Prepend siano a, non si sa necessariamente a quale istanza appartiene.

È possibile risolvere questo problema utilizzando data types in type families, che hanno il vantaggio di non trattare con funzioni di tipo, che sono surjective ma potrebbe essere iniettiva, e invece con il tipo di "relazioni", che sono biunivoca (Così ogni Il tipo Prepend può appartenere solo a una famiglia di tipi e ogni famiglia di tipi ha un tipo distinto Prepend).

(Se si desidera me di mostrare una soluzione con i tipi di dati a famiglie tipo, lasciare un commento! In pratica, basta usare un data Prepend invece di type Prepend)

+0

Ah, grazie per prendere in giro il significato di quel messaggio di errore per me. – rampion

+1

Si noti che il codice originale * fa * utilizza famiglie di tipi (in particolare, digita sinonimo famiglie); ciò che invece dovrebbe usare sono le famiglie di dati. – ehird

+0

@ehird, ho sempre pensato che "digitare alias nelle classi di tipi" non appartenesse ancora all'estensione delle famiglie di tipi, ma TIL. – dflemstr

1

La soluzione mi è venuta era quello di aggiungere un argomento fittizio per legare prepend e append al parametro phantom:

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