2012-01-16 13 views
5

Por lo tanto, estoy tratando de hacer un tipo de tuplas de longitud variable, básicamente como una versión más bonita de Either a (Either (a,b) (Either (a,b,c) ...)) y Either (Either (Either ... (x,y,z)) (y,z)) z.GHC: error al inferir el tipo de parámetro phantom

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

Sin embargo, el compilador parece incapaz de inferir el parámetro de tipo fantasma de prepend o append en los casos recurrentes:

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

¿Hay algo que pueda hacer para ayudar a hacer que el compilador esta inferencia?

Respuesta

7

La parte importante del mensaje de error aquí es el:

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

¿Qué significa esto? Significa que puede haber múltiples instance Prependable tales que su type Prepend ... = a, de modo que si se infiere que Prepend es , no necesariamente se sabe a qué instancia pertenece.

Puede resolver esto mediante el uso data types in type families, que tienen la ventaja de que no se ocupan de funciones de tipo, que son sobreyectiva pero podría ser inyectiva, y en su lugar con el tipo de "relaciones", que son biyectiva (Así que cada El tipo Prepend solo puede pertenecer a una familia de tipos, y cada familia de tipos tiene un tipo distinto Prepend).

(Si quieres que te muestre una solución con tipos de datos en las familias tipo, dejar un comentario! Básicamente, sólo tiene que utilizar un data Prepend en lugar de type Prepend)

+0

Ah, gracias por las burlas el significado de ese mensaje de error para mí. – rampion

+1

Tenga en cuenta que el código * original * usa * familias de tipos (específicamente, escriba familias de sinónimos); lo que debería usar en su lugar es familias de datos. – ehird

+0

@ehird, siempre pensé que "escribir alias en las clases de tipos" todavía no pertenecía a la extensión de familias de tipos, sino a TIL. – dflemstr

1

La solución que se me ocurrió fue la de añadir un argumento ficticio para atar prepend y append al parámetro fantasma:

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