5

GHC rejects the program

{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
import GHC.TypeLits

data Foo = Foo
data Bar = Bar

data (:::) :: * -> * -> * where
    (:=) :: sy -> t -> sy ::: t

data Rec :: [*] -> * where
    RNil :: Rec '[]
    (:&) :: (sy ::: ty) -> Rec xs ->  Rec ((sy ::: ty) ': xs)

infix 3 :=
infixr 2 :&

baz :: Num ty => Rec [Foo ::: String, Bar ::: ty]
baz = Foo := "foo" :& Bar := 1 :& RNil

--bang :: (String, Integer)
bang = case baz of
         (Foo := a :& Bar := b :& RNil) -> (a, b)

with

Rec2.hs:25:44:
    Couldn't match type ‛t’ with ‛(String, Integer)’
      ‛t’ is untouchable
        inside the constraints (xs1 ~ '[] *)
        bound by a pattern with constructor
                   RNil :: Rec ('[] *),
                 in a case alternative
        at Rec2.hs:25:35-38
      ‛t’ is a rigid type variable bound by
          the inferred type of bang :: t at Rec2.hs:24:1
    Expected type: t
      Actual type: (ty, ty1)
    Relevant bindings include bang :: t (bound at Rec2.hs:24:1)
    In the expression: (a, b)
    In a case alternative: (Foo := a :& Bar := b :& RNil) -> (a, b)
    In the expression:
      case baz of { (Foo := a :& Bar := b :& RNil) -> (a, b) }

, with the type annotation it works fine. All answers regarding untouchable type variables and GADTs that I found on the net asserted that type inference would be impossible, or at least intractable but in this case it seems evident that GHC got hold of the type (String, Integer), it's just refusing to unify.

barsoap
  • 3,376
  • 3
  • 23
  • 21

1 Answers1

4

Maybe your original GADT could be sugar for something that doesn't use GADTs like the following (which works):

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
import GHC.TypeLits

data Foo = Foo
data Bar = Bar

data (:::) sy t = (:=) sy t

data RNil = RNil
data (:&) a b = a :& b

type family Rec (xs :: [*]) :: *
type instance Rec (x ': xs) = x :& Rec xs
type instance Rec '[] = RNil

infix 3 :=
infixr 2 :&

baz :: Num ty => Rec [Foo ::: String, Bar ::: ty]
baz = Foo := "foo" :& Bar := 1 :& RNil

bang = case baz of
         ( Foo := a :& Bar := b :& RNil) -> (a, b)
aavogt
  • 1,308
  • 6
  • 14
  • That's a *very* good suggestion and I'm going to play around and see how it interacts with the rest of my plans, it doesn't really answer my question, though :) – barsoap Sep 29 '13 at 16:44
  • Hmm. One consequence of this is that the inferred type for "baz" now Isn't a nice `Rec` with its elements listed as type parameters as in e.g. vinyl, but a type-level list a la HList, records etc. Which is a thing I definitely want, I'd sacrifice pattern matching for it. It all works nicely with a data family, though, which in the end might be the thing that I want. – barsoap Sep 29 '13 at 16:55
  • 1
    well this example suggests that you don't need all the power of GADTs for your `data Rec`, but you still pay the price in terms of type inference.... so maybe there is some room for having nice syntax like GADTs while keeping type inference as good plain ADTs. – aavogt Sep 29 '13 at 20:01
  • 2
    It seems you can have the best of both, if you write a class to convert between the two http://lpaste.net/93610 – aavogt Sep 29 '13 at 20:15