data kinds and exhaustiveness of typeclass instances

Hello, the following program doesn't typecheck in GHC 9: data Tag = A | B data Foo (a :: Tag) = Foo class C a where f :: a -> Int instance C (Foo A) where f x = 1 instance C (Foo B) where f x = 2 g :: Foo a -> Int g = f Yet one could argue that for all a :: Tag, C (Foo a) holds because a :: Tag can only take two values: A or B, and C (Foo A) and C (Foo B) hold. Is there a way to somehow convince GHC of that fact so that g typechecks? Cheers, Paul

On Tue, Mar 02, 2021 at 03:16:23PM +0100, Paul Brauner wrote:
the following program doesn't typecheck in GHC 9:
data Tag = A | B data Foo (a :: Tag) = Foo
class C a where f :: a -> Int
instance C (Foo A) where f x = 1
instance C (Foo B) where f x = 2
g :: Foo a -> Int g = f
Yet one could argue that for all a :: Tag, C (Foo a) holds because a :: Tag can only take two values: A or B, and C (Foo A) and C (Foo B) hold. Is there a way to somehow convince GHC of that fact so that g typechecks?
What would you expect the type of 'g Foo' to be?

Is there a way to somehow convince GHC of that fact so that g typechecks?
No. First, it would actually be unsound to do so, because of the possibility of exotic types, built with pathological combinations of type and data families: https://gitlab.haskell.org/ghc/ghc/-/issues/14420 https://gitlab.haskell.org/ghc/ghc/-/issues/14420 But, actually, the bigger problem is that we need a class constraint in order to allow a function to compute at runtime. The function f actually takes two arguments at runtime: a representation of the instance which carries f's implementation (this is sometimes called a dictionary), and the normal argument of type a. `g`, on the other hand, has no access to the dictionary needed at runtime, and so it's unclear how it should compute. Put another way: a value of type Foo carries no information (beyond the fact that it terminates), because Foo has only one data constructor. So there's no way that g :: Foo a -> Int could be anything but a constant function. You need the class constraint to change this fact. Hope this helps! Richard
On Mar 2, 2021, at 9:16 AM, Paul Brauner
wrote: Hello,
the following program doesn't typecheck in GHC 9:
data Tag = A | B data Foo (a :: Tag) = Foo
class C a where f :: a -> Int
instance C (Foo A) where f x = 1
instance C (Foo B) where f x = 2
g :: Foo a -> Int g = f
Yet one could argue that for all a :: Tag, C (Foo a) holds because a :: Tag can only take two values: A or B, and C (Foo A) and C (Foo B) hold. Is there a way to somehow convince GHC of that fact so that g typechecks?
Cheers, Paul _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

On Tue, Mar 02, 2021 at 03:00:55PM +0000, Richard Eisenberg wrote:
Is there a way to somehow convince GHC of that fact so that g typechecks?
No.
First, it would actually be unsound to do so, because of the possibility of exotic types, built with pathological combinations of type and data families: https://gitlab.haskell.org/ghc/ghc/-/issues/14420 https://gitlab.haskell.org/ghc/ghc/-/issues/14420
But, actually, the bigger problem is that we need a class constraint in order to allow a function to compute at runtime. The function f actually takes two arguments at runtime: a representation of the instance which carries f's implementation (this is sometimes called a dictionary), and the normal argument of type a. `g`, on the other hand, has no access to the dictionary needed at runtime, and so it's unclear how it should compute.
Put another way: a value of type Foo carries no information (beyond the fact that it terminates), because Foo has only one data constructor. So there's no way that g :: Foo a -> Int could be anything but a constant function. You need the class constraint to change this fact.
Hope this helps! Richard
To elaborate a little on Richard’s answer, this is the reason for GHC.TypeLits’ KnownNat class, so that we have natVal :: KnownNat n => proxy n -> Integer You’d have to supplement your program with a class KnownTag, like so: data Tag = A | B data Foo (a :: Tag) = Foo class KnownTag (a :: Tag) where tagVal :: proxy a -> Tag instance KnownTag A where tagVal _ = A instance KnownTag B where tagVal _ = B class C a where f :: a -> Int instance KnownTag a => C (Foo a) where f _ = case tagVal (Proxy :: Proxy a) of A -> 1; B -> 2 g :: KnownTag a => Foo a -> Int g = f Regards, Seph -- Seph Shewell Brockway, BSc MSc (Glas.) Pronouns: she/her

Thanks all, this all makes sense!
On Tue, Mar 2, 2021 at 4:34 PM Seph Shewell Brockway
Is there a way to somehow convince GHC of that fact so that g typechecks?
No.
First, it would actually be unsound to do so, because of the possibility of exotic types, built with pathological combinations of type and data families: https://gitlab.haskell.org/ghc/ghc/-/issues/14420 < https://gitlab.haskell.org/ghc/ghc/-/issues/14420>
But, actually, the bigger problem is that we need a class constraint in order to allow a function to compute at runtime. The function f actually takes two arguments at runtime: a representation of the instance which carries f's implementation (this is sometimes called a dictionary), and the normal argument of type a. `g`, on the other hand, has no access to the dictionary needed at runtime, and so it's unclear how it should compute.
Put another way: a value of type Foo carries no information (beyond the fact that it terminates), because Foo has only one data constructor. So
On Tue, Mar 02, 2021 at 03:00:55PM +0000, Richard Eisenberg wrote: there's no way that g :: Foo a -> Int could be anything but a constant function. You need the class constraint to change this fact.
Hope this helps! Richard
To elaborate a little on Richard’s answer, this is the reason for GHC.TypeLits’ KnownNat class, so that we have
natVal :: KnownNat n => proxy n -> Integer
You’d have to supplement your program with a class KnownTag, like so:
data Tag = A | B data Foo (a :: Tag) = Foo
class KnownTag (a :: Tag) where tagVal :: proxy a -> Tag
instance KnownTag A where tagVal _ = A
instance KnownTag B where tagVal _ = B
class C a where f :: a -> Int
instance KnownTag a => C (Foo a) where f _ = case tagVal (Proxy :: Proxy a) of A -> 1; B -> 2
g :: KnownTag a => Foo a -> Int g = f
Regards,
Seph
-- Seph Shewell Brockway, BSc MSc (Glas.) Pronouns: she/her

Another way of putting it, please correct me if I'm wrong. In coq we could
prove forall a, C (Foo a) by case analysis on a. Then we could use that
proof to recover the f by applying it to p inside g. It can't work in
Haskell because p has no runtime representation. In Haskell the proxy plays
the role of p, KnownTag plays the role of the proof that p can be
eliminated, and "instance KnownTag a => C (Foo a)" plays the role of the
theorem.
On Tue, Mar 2, 2021 at 8:23 PM Paul Brauner
Thanks all, this all makes sense!
On Tue, Mar 2, 2021 at 4:34 PM Seph Shewell Brockway
wrote: Is there a way to somehow convince GHC of that fact so that g typechecks?
No.
First, it would actually be unsound to do so, because of the
On Tue, Mar 02, 2021 at 03:00:55PM +0000, Richard Eisenberg wrote: possibility of exotic types, built with pathological combinations of type and data families: https://gitlab.haskell.org/ghc/ghc/-/issues/14420 < https://gitlab.haskell.org/ghc/ghc/-/issues/14420>
But, actually, the bigger problem is that we need a class constraint in
order to allow a function to compute at runtime. The function f actually takes two arguments at runtime: a representation of the instance which carries f's implementation (this is sometimes called a dictionary), and the normal argument of type a. `g`, on the other hand, has no access to the dictionary needed at runtime, and so it's unclear how it should compute.
Put another way: a value of type Foo carries no information (beyond the
fact that it terminates), because Foo has only one data constructor. So there's no way that g :: Foo a -> Int could be anything but a constant function. You need the class constraint to change this fact.
Hope this helps! Richard
To elaborate a little on Richard’s answer, this is the reason for GHC.TypeLits’ KnownNat class, so that we have
natVal :: KnownNat n => proxy n -> Integer
You’d have to supplement your program with a class KnownTag, like so:
data Tag = A | B data Foo (a :: Tag) = Foo
class KnownTag (a :: Tag) where tagVal :: proxy a -> Tag
instance KnownTag A where tagVal _ = A
instance KnownTag B where tagVal _ = B
class C a where f :: a -> Int
instance KnownTag a => C (Foo a) where f _ = case tagVal (Proxy :: Proxy a) of A -> 1; B -> 2
g :: KnownTag a => Foo a -> Int g = f
Regards,
Seph
-- Seph Shewell Brockway, BSc MSc (Glas.) Pronouns: she/her

To "more directly" do the same thing as in coq, you can also take the singletons approach, and either explicitly use a "proof providing" function: withC :: STag t -> (C (Foo t) => r) -> r withC tag k = case tag of SA -> k SB -> k (so if you call `withC tag body` you now have the required constraint in `body` or you could use the implicit singleton carrying type class: instance STagI t => C (Foo t) where f = case tagSing of SA -> f SB -> f and the remaining boilerplate code required: data STag t where SA :: STag A SB :: STag B class STagI t where tagSing :: STag t instance STag A where tagSing = SA instance STag B where tagSing = SB

On Tue, 2 Mar 2021, Paul Brauner wrote:
Hello, the following program doesn't typecheck in GHC 9:
data Tag = A | B data Foo (a :: Tag) = Foo
class C a where f :: a -> Int
instance C (Foo A) where f x = 1
instance C (Foo B) where f x = 2
g :: Foo a -> Int g = f
You need a typecase on Tag's constructors. E.g. class C a where switch :: f A -> f B -> f a instance C A where switch h _ = h instance C B where switch _ h = h newtype G a = G {getG :: Foo a -> Int} g :: (C a) => Foo a -> Int g = getG $ switch (G f) (G f) Or you define a helper GADT: data Choice a where A :: Choice A B :: Choice B class C a where choice :: Choice a instance C A where choice = A instance C B where choice = B choiceFromFoo :: (C a) => Foo a -> Choice a choiceFromFoo Foo = choice g :: (C a) => Foo a -> Int g foo = case choiceFromFoo foo of A -> f foo B -> f foo
participants (6)
-
Georgi Lyubenov
-
Henning Thielemann
-
Paul Brauner
-
Richard Eisenberg
-
Seph Shewell Brockway
-
Tom Ellis