Type inference of singular matches on GADTs

Hi all, Today I was writing some code that uses a GADT to represent heterogeneous lists: data HList as where HNil :: HList '[] HCons :: a -> HList as -> HList (a ': as) This type is used to provide a generic way to manipulate n-ary functions. Naturally, I have some functions that accept these n-ary functions as arguments, which have types like this: foo :: Blah as => (HList as -> Widget) -> Whatsit The idea is that Blah does some type-level induction on as and supplies the function with some appropriate values. Correspondingly, my use sites look something like this: bar = foo (\HNil -> ...) Much to my dismay, I quickly discovered that GHC finds these expressions quite unfashionable, and it invariably insults them: • Ambiguous type variable ‘as0’ arising from a use of ‘foo’ prevents the constraint ‘(Blah as0)’ from being solved. The miscommunication is simple enough. I expected that when given an expression like \HNil -> ... GHC would see a single pattern of type HList '[] and consequently infer a type like HList '[] -> ... Alas, it was not to be. It seems GHC is reluctant to commit to the choice of '[] for as, lest perhaps I add another case to my function in the future. Indeed, if I were to do that, the choice of '[] would be premature, as as ~ '[] would only be available within one branch. However, I do not in fact have any such intention, which makes me quietly wish GHC would get over its anxiety and learn to be a bit more of a risk-taker. I ended up taking a look at the OutsideIn(X) paper, hoping to find some commentary on this situation, but in spite of the nice examples toward the start about the trickiness of GADTs, I found no discussion of this specific scenario: a function with exactly one branch and an utterly unambiguous pattern. Most examples come at the problem from precisely the opposite direction, trying to tease out a principle type from a collection of branches. The case of a function (or perhaps more accurately, a case expression) with only a single branch does not seem to be given any special attention. Of course, fewer special cases is always nice. I have great sympathy for generality. Still, I can’t help but feel a little unsatisfied here. Theoretically, there is no reason GHC cannot treat \(a `HCons` b `HCons` c `HCons` HNil) -> ... and \a b c -> ... almost identically, with a well-defined principle type and pleasant type inference properties, but there is no way for me to communicate this to the typechecker! So, my questions: 1. Have people considered this problem before? Is it discussed anywhere already? 2. Is my desire here reasonable, or is there some deep philosophical argument for why my program should be rejected? 3. If it /is/ reasonable, are there any obvious situations where a change targeted at what I’m describing (vague as that is) would affect programs negatively, not positively? I realize this gets rather at the heart of the typechecker, so I don’t intend to imply a change of this sort should be made frivolously. Indeed, I’m not even particularly attached to the idea that a change must be made! But I do want to understand the tradeoffs better, so any insight would be much appreciated. Thanks, Alexis

On Sat, Mar 20, 2021 at 04:40:59AM -0500, Alexis King wrote:
Today I was writing some code that uses a GADT to represent heterogeneous lists:
data HList as where HNil :: HList '[] HCons :: a -> HList as -> HList (a ': as)
This type is used to provide a generic way to manipulate n-ary functions. Naturally, I have some functions that accept these n-ary functions as arguments, which have types like this:
foo :: Blah as => (HList as -> Widget) -> Whatsit
The idea is that Blah does some type-level induction on as and supplies the function with some appropriate values. Correspondingly, my use sites look something like this:
bar = foo (\HNil -> ...)
Much to my dismay, I quickly discovered that GHC finds these expressions quite unfashionable, and it invariably insults them:
• Ambiguous type variable ‘as0’ arising from a use of ‘foo’ prevents the constraint ‘(Blah as0)’ from being solved.
FWIW, the simplest possible example: {-# LANGUAGE DataKinds, TypeOperators, GADTs #-} data HList as where HNil :: HList '[] HCons :: a -> HList as -> HList (a ': as) foo :: (as ~ '[]) => (HList as -> Int) -> Int foo f = f HNil bar :: Int bar = foo (\HNil -> 1) compiles without error. As soon as I try add more complex contraints, I appear to need an explicit type signature for HNil, and then the code again compiles: {-# LANGUAGE DataKinds , GADTs , PolyKinds , ScopedTypeVariables , TypeFamilies , TypeOperators #-} import GHC.Types data HList as where HNil :: HList '[] HCons :: a -> HList as -> HList (a ': as) class Nogo a where type family Blah (as :: [Type]) :: Constraint type instance Blah '[] = () type instance Blah (_ ': '[]) = () type instance Blah (_ ': _ ': _) = (Nogo ()) foo :: (Blah as) => (HList as -> Int) -> Int foo _ = 42 bar :: Int bar = foo (\ (HNil :: HNilT) -> 1) type HNilT = HList '[] baz :: Int baz = foo (\ (True `HCons` HNil :: HOneT Bool) -> 2) type HOneT a = HList (a ': '[]) Is this at all useful? -- Viktor.

On Sat, Mar 20, 2021 at 08:13:18AM -0400, Viktor Dukhovni wrote:
As soon as I try add more complex contraints, I appear to need an explicit type signature for HNil, and then the code again compiles:
But aliasing the promoted constructors via pattern synonyms, and using those instead, appears to resolve the ambiguity. -- Viktor. {-# LANGUAGE DataKinds , GADTs , PatternSynonyms , PolyKinds , ScopedTypeVariables , TypeFamilies , TypeOperators #-} import GHC.Types infixr 1 `HC` data HList as where HNil :: HList '[] HCons :: a -> HList as -> HList (a ': as) pattern HN :: HList '[]; pattern HN = HNil pattern HC :: a -> HList as -> HList (a ': as) pattern HC a as = HCons a as class Nogo a where type family Blah (as :: [Type]) :: Constraint type instance Blah '[] = () type instance Blah (_ ': '[]) = () type instance Blah (_ ': _ ': '[]) = () type instance Blah (_ ': _ ': _ ': _) = (Nogo ()) foo :: (Blah as) => (HList as -> Int) -> Int foo _ = 42 bar :: Int bar = foo (\ HN -> 1) baz :: Int baz = foo (\ (True `HC` HN) -> 2) pattern One :: Int pattern One = 1 bam :: Int bam = foo (\ (True `HC` One `HC` HN) -> 2)

Hi Alexis, The following works and will have inferred type `Int`:
bar = foo (\(HNil :: HList '[]) -> 42)
I'd really like it if we could write
bar2 = foo (\(HNil @'[]) -> 42)
though, even if you write out the constructor type with explicit constraints and forall's. E.g. by using a -XTypeApplications here, I specify the universal type var of the type constructor `HList`. I think that is a semantics that is in line with Type Variables in Patterns, Section 4 https://dl.acm.org/doi/10.1145/3242744.3242753: The only way to satisfy the `as ~ '[]` constraint in the HNil pattern is to refine the type of the pattern match to `HList '[]`. Consequently, the local `Blah '[]` can be discharged and bar2 will have inferred `Int`. But that's simply not implemented at the moment, I think. I recall there's some work that has to happen before. The corresponding proposal seems to be https://ghc-proposals.readthedocs.io/en/latest/proposals/0126-type-applicati... (or https://github.com/ghc-proposals/ghc-proposals/pull/238? I'm confused) and your example should probably be added there as motivation. If `'[]` is never mentioned anywhere in the pattern like in the original example, I wouldn't expect it to type-check (or at least emit a pattern-match warning): First off, the type is ambiguous. It's a similar situation as in https://stackoverflow.com/questions/50159349/type-abstraction-in-ghc-haskell. If it was accepted and got type `Blah as => Int`, then you'd get a pattern-match warning, because depending on how `as` is instantiated, your pattern-match is incomplete. E.g., `bar3 @[Int]` would crash. Complete example code: {-# LANGUAGE DataKinds #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE RankNTypes #-} module Lib where data HList as where HNil :: forall as. (as ~ '[]) => HList as HCons :: forall as a as'. (as ~ (a ': as')) => a -> HList as' -> HList as class Blah as where blah :: HList as instance Blah '[] where blah = HNil foo :: Blah as => (HList as -> Int) -> Int foo f = f blah bar = foo (\(HNil :: HList '[]) -> 42) -- compiles bar2 = foo (\(HNil @'[]) -> 42) -- errors Cheers, Sebastian Am Sa., 20. März 2021 um 13:57 Uhr schrieb Viktor Dukhovni < ietf-dane@dukhovni.org>:
On Sat, Mar 20, 2021 at 08:13:18AM -0400, Viktor Dukhovni wrote:
As soon as I try add more complex contraints, I appear to need an explicit type signature for HNil, and then the code again compiles:
But aliasing the promoted constructors via pattern synonyms, and using those instead, appears to resolve the ambiguity.
-- Viktor.
{-# LANGUAGE DataKinds , GADTs , PatternSynonyms , PolyKinds , ScopedTypeVariables , TypeFamilies , TypeOperators #-}
import GHC.Types
infixr 1 `HC`
data HList as where HNil :: HList '[] HCons :: a -> HList as -> HList (a ': as)
pattern HN :: HList '[]; pattern HN = HNil pattern HC :: a -> HList as -> HList (a ': as) pattern HC a as = HCons a as
class Nogo a where
type family Blah (as :: [Type]) :: Constraint type instance Blah '[] = () type instance Blah (_ ': '[]) = () type instance Blah (_ ': _ ': '[]) = () type instance Blah (_ ': _ ': _ ': _) = (Nogo ())
foo :: (Blah as) => (HList as -> Int) -> Int foo _ = 42
bar :: Int bar = foo (\ HN -> 1)
baz :: Int baz = foo (\ (True `HC` HN) -> 2)
pattern One :: Int pattern One = 1 bam :: Int bam = foo (\ (True `HC` One `HC` HN) -> 2) _______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

Cale made me aware of the fact that the "Type applications in patterns" proposal had already been implemented. See https://gitlab.haskell.org/ghc/ghc/-/issues/19577 where I adapt Alexis' use case into a test case that I'd like to see compiling. Am Sa., 20. März 2021 um 15:45 Uhr schrieb Sebastian Graf < sgraf1337@gmail.com>:
Hi Alexis,
The following works and will have inferred type `Int`:
bar = foo (\(HNil :: HList '[]) -> 42)
I'd really like it if we could write
bar2 = foo (\(HNil @'[]) -> 42)
though, even if you write out the constructor type with explicit constraints and forall's. E.g. by using a -XTypeApplications here, I specify the universal type var of the type constructor `HList`. I think that is a semantics that is in line with Type Variables in Patterns, Section 4 https://dl.acm.org/doi/10.1145/3242744.3242753: The only way to satisfy the `as ~ '[]` constraint in the HNil pattern is to refine the type of the pattern match to `HList '[]`. Consequently, the local `Blah '[]` can be discharged and bar2 will have inferred `Int`.
But that's simply not implemented at the moment, I think. I recall there's some work that has to happen before. The corresponding proposal seems to be https://ghc-proposals.readthedocs.io/en/latest/proposals/0126-type-applicati... (or https://github.com/ghc-proposals/ghc-proposals/pull/238? I'm confused) and your example should probably be added there as motivation.
If `'[]` is never mentioned anywhere in the pattern like in the original example, I wouldn't expect it to type-check (or at least emit a pattern-match warning): First off, the type is ambiguous. It's a similar situation as in https://stackoverflow.com/questions/50159349/type-abstraction-in-ghc-haskell. If it was accepted and got type `Blah as => Int`, then you'd get a pattern-match warning, because depending on how `as` is instantiated, your pattern-match is incomplete. E.g., `bar3 @[Int]` would crash.
Complete example code:
{-# LANGUAGE DataKinds #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE RankNTypes #-}
module Lib where
data HList as where HNil :: forall as. (as ~ '[]) => HList as HCons :: forall as a as'. (as ~ (a ': as')) => a -> HList as' -> HList as
class Blah as where blah :: HList as
instance Blah '[] where blah = HNil
foo :: Blah as => (HList as -> Int) -> Int foo f = f blah
bar = foo (\(HNil :: HList '[]) -> 42) -- compiles bar2 = foo (\(HNil @'[]) -> 42) -- errors
Cheers, Sebastian
Am Sa., 20. März 2021 um 13:57 Uhr schrieb Viktor Dukhovni < ietf-dane@dukhovni.org>:
On Sat, Mar 20, 2021 at 08:13:18AM -0400, Viktor Dukhovni wrote:
As soon as I try add more complex contraints, I appear to need an explicit type signature for HNil, and then the code again compiles:
But aliasing the promoted constructors via pattern synonyms, and using those instead, appears to resolve the ambiguity.
-- Viktor.
{-# LANGUAGE DataKinds , GADTs , PatternSynonyms , PolyKinds , ScopedTypeVariables , TypeFamilies , TypeOperators #-}
import GHC.Types
infixr 1 `HC`
data HList as where HNil :: HList '[] HCons :: a -> HList as -> HList (a ': as)
pattern HN :: HList '[]; pattern HN = HNil pattern HC :: a -> HList as -> HList (a ': as) pattern HC a as = HCons a as
class Nogo a where
type family Blah (as :: [Type]) :: Constraint type instance Blah '[] = () type instance Blah (_ ': '[]) = () type instance Blah (_ ': _ ': '[]) = () type instance Blah (_ ': _ ': _ ': _) = (Nogo ())
foo :: (Blah as) => (HList as -> Int) -> Int foo _ = 42
bar :: Int bar = foo (\ HN -> 1)
baz :: Int baz = foo (\ (True `HC` HN) -> 2)
pattern One :: Int pattern One = 1 bam :: Int bam = foo (\ (True `HC` One `HC` HN) -> 2) _______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

I appreciate your point Sebastian, but I think in this particular case, type applications in patterns are still not enough to satisfy me. I provided the empty argument list example because it was simple, but I’d also like this to typecheck: baz :: Int -> String -> Widget baz = .... bar = foo (\(a `HCons` b `HCons` HNil) -> baz a b) I don’t want to have to annotate the types of a and b because they’re both eminently inferrable. I’d like to get type inference properties comparable to an ordinary two-argument lambda expression, since that’s how I’m trying to use this, after all. Really what I’m complaining about here is type inference of GADT patterns. For comparison, suppose I had these definitions: class Blah a where foo :: (a -> Widget) -> Whatsit instance Blah (Int, String) where foo = .... baz :: Int -> String -> Widget baz = .... bar = foo (\(a, b) -> baz a b) This compiles without any issues. The pattern (a, b) is inferred to have type (t1, t2), where both t1 and t2 are metavariables. These are unified to particular types in the body, and everything is fine. But type inference for GADT patterns works differently. In fact, even this simple definition fails to compile: bar = \(a `HCons` HNil) -> not a GHC rejects it with the following error: error: • Could not deduce: a ~ Bool from the context: as ~ (a : as1) This seems to arise from GHC’s strong reluctance to pick any particular type for a match on a GADT constructor. One way to explain this is as a sort of “open world assumption” as it applies to case expressions: we always /could/ add more cases, and if we did, specializing the type based on the existing cases might be premature. Furthermore, non-exhaustive pattern-matching is not a type error in Haskell, only a warning, so perhaps we /wanted/ to write a non-exhaustive function on an arbitrary HList. Of course, I think that’s somewhat silly. If there’s a single principal type that makes my function well-typed /and exhaustive/, I’d really like GHC to pick it. Alexis On 3/22/21 1:28 PM, Sebastian Graf wrote:
Cale made me aware of the fact that the "Type applications in patterns" proposal had already been implemented. See https://gitlab.haskell.org/ghc/ghc/-/issues/19577 where I adapt Alexis' use case into a test case that I'd like to see compiling.
Am Sa., 20. März 2021 um 15:45 Uhr schrieb Sebastian Graf
mailto:sgraf1337@gmail.com>: Hi Alexis,
The following works and will have inferred type `Int`:
> bar = foo (\(HNil :: HList '[]) -> 42)
I'd really like it if we could write
> bar2 = foo (\(HNil @'[]) -> 42)
though, even if you write out the constructor type with explicit constraints and forall's. E.g. by using a -XTypeApplications here, I specify the universal type var of the type constructor `HList`. I think that is a semantics that is in line with Type Variables in Patterns, Section 4 https://dl.acm.org/doi/10.1145/3242744.3242753: The only way to satisfy the `as ~ '[]` constraint in the HNil pattern is to refine the type of the pattern match to `HList '[]`. Consequently, the local `Blah '[]` can be discharged and bar2 will have inferred `Int`.
But that's simply not implemented at the moment, I think. I recall there's some work that has to happen before. The corresponding proposal seems to be https://ghc-proposals.readthedocs.io/en/latest/proposals/0126-type-applicati... (or https://github.com/ghc-proposals/ghc-proposals/pull/238? I'm confused) and your example should probably be added there as motivation.
If `'[]` is never mentioned anywhere in the pattern like in the original example, I wouldn't expect it to type-check (or at least emit a pattern-match warning): First off, the type is ambiguous. It's a similar situation as in https://stackoverflow.com/questions/50159349/type-abstraction-in-ghc-haskell. If it was accepted and got type `Blah as => Int`, then you'd get a pattern-match warning, because depending on how `as` is instantiated, your pattern-match is incomplete. E.g., `bar3 @[Int]` would crash.
Complete example code:
{-# LANGUAGE DataKinds #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE RankNTypes #-}
module Lib where
data HList as where HNil :: forall as. (as ~ '[]) => HList as HCons :: forall as a as'. (as ~ (a ': as')) => a -> HList as' -> HList as
class Blah as where blah :: HList as
instance Blah '[] where blah = HNil
foo :: Blah as => (HList as -> Int) -> Int foo f = f blah
bar = foo (\(HNil :: HList '[]) -> 42) -- compiles bar2 = foo (\(HNil @'[]) -> 42) -- errors
Cheers, Sebastian
Am Sa., 20. März 2021 um 13:57 Uhr schrieb Viktor Dukhovni
mailto:ietf-dane@dukhovni.org>: On Sat, Mar 20, 2021 at 08:13:18AM -0400, Viktor Dukhovni wrote:
> As soon as I try add more complex contraints, I appear to need an > explicit type signature for HNil, and then the code again compiles:
But aliasing the promoted constructors via pattern synonyms, and using those instead, appears to resolve the ambiguity.
-- Viktor.
{-# LANGUAGE DataKinds , GADTs , PatternSynonyms , PolyKinds , ScopedTypeVariables , TypeFamilies , TypeOperators #-}
import GHC.Types
infixr 1 `HC`
data HList as where HNil :: HList '[] HCons :: a -> HList as -> HList (a ': as)
pattern HN :: HList '[]; pattern HN = HNil pattern HC :: a -> HList as -> HList (a ': as) pattern HC a as = HCons a as
class Nogo a where
type family Blah (as :: [Type]) :: Constraint type instance Blah '[] = () type instance Blah (_ ': '[]) = () type instance Blah (_ ': _ ': '[]) = () type instance Blah (_ ': _ ': _ ': _) = (Nogo ())
foo :: (Blah as) => (HList as -> Int) -> Int foo _ = 42
bar :: Int bar = foo (\ HN -> 1)
baz :: Int baz = foo (\ (True `HC` HN) -> 2)
pattern One :: Int pattern One = 1 bam :: Int bam = foo (\ (True `HC` One `HC` HN) -> 2)

On Fri, Mar 26, 2021 at 07:41:09PM -0500, Alexis King wrote:
type applications in patterns are still not enough to satisfy me. I provided the empty argument list example because it was simple, but I’d also like this to typecheck:
baz :: Int -> String -> Widget baz = ....
bar = foo (\(a `HCons` b `HCons` HNil) -> baz a b)
Can you be a bit more specific on how the constraint `Blah` is presently defined, and how `foo` uses the HList type to execute a function of the appropriate arity and signature? The example below my signature typechecks, provided I use pattern synonyms for the GADT constructors, rather than use the constructors directly. -- Viktor. {-# language DataKinds , FlexibleInstances , GADTs , PatternSynonyms , ScopedTypeVariables , TypeApplications , TypeFamilies , TypeOperators #-} import GHC.Types import Data.Proxy import Type.Reflection import Data.Type.Equality data HList as where HNil_ :: HList '[] HCons_ :: a -> HList as -> HList (a ': as) infixr 5 `HCons_` pattern HNil :: HList '[]; pattern HNil = HNil_ pattern (:^) :: a -> HList as -> HList (a ': as) pattern (:^) a as = HCons_ a as pattern (:$) a b = a :^ b :^ HNil infixr 5 :^ infixr 5 :$ class Typeable as => Blah as where params :: HList as instance Blah '[Int,String] where params = 39 :$ "abc" baz :: Int -> String -> Int baz i s = i + length s bar = foo (\(a :$ b) -> baz a b) foo :: Blah as => (HList as -> Int) -> Int foo f = f params

Hi Alexis, If you really want to get by without type annotations, then Viktor's pattern synonym suggestion really is your best option! Note that pattern HNil :: HList '[]; pattern HNil = HNil_ Does not actually declare an HNil that is completely synonymous with HNil_, but it changes the *provided* GADT constraint (as ~ '[]) into a *required* constraint (as ~ '[]). "Provided" as in "a pattern match on the synonym provides this constraint as a new Given", "required" as in "... requires this constraint as a new Wanted". (I hope I used the terminology correctly here.) Thus, a pattern ((a :: Int) `HCons` HNil) really has type (HList '[Int]) and is exhaustive. See also https://gitlab.haskell.org/ghc/ghc/-/wikis/pattern-synonyms#static-semantics . At the moment, I don't think it's possible to declare a GADT constructor with required constraints, so a pattern synonym seems like your best bet and fits your use case exactly. You can put each of these pattern synonyms into a singleton COMPLETE pragma. Hope that helps, Sebastian Am Sa., 27. März 2021 um 06:27 Uhr schrieb Viktor Dukhovni < ietf-dane@dukhovni.org>:
On Fri, Mar 26, 2021 at 07:41:09PM -0500, Alexis King wrote:
type applications in patterns are still not enough to satisfy me. I provided the empty argument list example because it was simple, but I’d also like this to typecheck:
baz :: Int -> String -> Widget baz = ....
bar = foo (\(a `HCons` b `HCons` HNil) -> baz a b)
Can you be a bit more specific on how the constraint `Blah` is presently defined, and how `foo` uses the HList type to execute a function of the appropriate arity and signature?
The example below my signature typechecks, provided I use pattern synonyms for the GADT constructors, rather than use the constructors directly.
-- Viktor.
{-# language DataKinds , FlexibleInstances , GADTs , PatternSynonyms , ScopedTypeVariables , TypeApplications , TypeFamilies , TypeOperators #-}
import GHC.Types import Data.Proxy import Type.Reflection import Data.Type.Equality
data HList as where HNil_ :: HList '[] HCons_ :: a -> HList as -> HList (a ': as) infixr 5 `HCons_`
pattern HNil :: HList '[]; pattern HNil = HNil_ pattern (:^) :: a -> HList as -> HList (a ': as) pattern (:^) a as = HCons_ a as pattern (:$) a b = a :^ b :^ HNil infixr 5 :^ infixr 5 :$
class Typeable as => Blah as where params :: HList as instance Blah '[Int,String] where params = 39 :$ "abc"
baz :: Int -> String -> Int baz i s = i + length s
bar = foo (\(a :$ b) -> baz a b)
foo :: Blah as => (HList as -> Int) -> Int foo f = f params _______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

On Mar 26, 2021, at 8:41 PM, Alexis King
wrote: If there’s a single principal type that makes my function well-typed and exhaustive, I’d really like GHC to pick it.
I think this is the key part of Alexis's plea: that the type checker take into account exhaustivity in choosing how to proceed. Another way to think about this:
f1 :: HList '[] -> () f1 HNil = ()
f2 :: HList as -> () f2 HNil = ()
Both f1 and f2 are well typed definitions. In any usage site where both are well-typed, they will behave the same. Yet f1 is exhaustive while f2 is not. This isn't really about an open-world assumption or the possibility of extra cases -- it has to do with what the runtime behaviors of the two functions are. f1 never fails, while f2 must check a constructor tag and perhaps throw an exception. If we just see \HNil -> (), Alexis seems to be suggesting we prefer the f1 interpretation over the f2 interpretation. Why? Because f1 is exhaustive, and when we can choose an exhaustive interpretation, that's probably a good idea to pursue. I haven't thought about how to implement such a thing. At the least, it would probably require some annotation saying that we expect `\HNil -> ()` to be exhaustive (as GHC won't, in general, make that assumption). Even with that, could we get type inference to behave? Possibly. But first: does this match your understanding? Richard

i like how you've boiled down this discussion, it makes it much clearer to
me at least :)
On Sun, Mar 28, 2021 at 10:19 PM Richard Eisenberg
On Mar 26, 2021, at 8:41 PM, Alexis King
wrote: If there’s a single principal type that makes my function well-typed *and exhaustive*, I’d really like GHC to pick it.
I think this is the key part of Alexis's plea: that the type checker take into account exhaustivity in choosing how to proceed.
Another way to think about this:
f1 :: HList '[] -> () f1 HNil = ()
f2 :: HList as -> () f2 HNil = ()
Both f1 and f2 are well typed definitions. In any usage site where both are well-typed, they will behave the same. Yet f1 is exhaustive while f2 is not. This isn't really about an open-world assumption or the possibility of extra cases -- it has to do with what the runtime behaviors of the two functions are. f1 never fails, while f2 must check a constructor tag and perhaps throw an exception.
If we just see \HNil -> (), Alexis seems to be suggesting we prefer the f1 interpretation over the f2 interpretation. Why? Because f1 is exhaustive, and when we can choose an exhaustive interpretation, that's probably a good idea to pursue.
I haven't thought about how to implement such a thing. At the least, it would probably require some annotation saying that we expect `\HNil -> ()` to be exhaustive (as GHC won't, in general, make that assumption). Even with that, could we get type inference to behave? Possibly.
But first: does this match your understanding?
Richard _______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

On Sun, Mar 28, 2021 at 11:00:56PM -0400, Carter Schonwald wrote:
On Sun, Mar 28, 2021 at 10:19 PM Richard Eisenberg
wrote: I think this is the key part of Alexis's plea: that the type checker take into account exhaustivity in choosing how to proceed.
Another way to think about this:
f1 :: HList '[] -> () f1 HNil = ()
f2 :: HList as -> () f2 HNil = ()
Both f1 and f2 are well typed definitions. In any usage site where both are well-typed, they will behave the same. Yet f1 is exhaustive while f2 is not. ...
I like how you've boiled down this discussion, it makes it much clearer to me at least :)
+1. Very much distills it for me too. Thanks! FWIW, I've since boiled down the pattern-synonym example to the below, where I find the choices of ":^" and ":$" to be pleasantly mnemonic, though "HSolo" is perhaps a bit too distracting... {-# language DataKinds, FlexibleInstances, FlexibleContexts, GADTs , PatternSynonyms, TypeOperators #-} {-# OPTIONS_GHC -Wno-type-defaults #-} import Data.Reflection import Data.Proxy default (Int) data HList as where HNil_ :: HList '[] HCons_ :: a -> HList as -> HList (a ': as) infixr 5 `HCons_` pattern HNil :: HList '[]; pattern HNil = HNil_ pattern HSolo :: a -> HList '[a] pattern HSolo a = a :^ HNil pattern (:^) :: a -> HList as -> HList (a ': as) pattern (:^) a as = HCons_ a as infixr 5 :^ pattern (:$) :: a -> b -> HList '[a,b] pattern (:$) a b = a :^ HSolo b infixr 5 :$ hApp :: Reifies s (HList as) => (HList as -> r) -> Proxy s -> r hApp f = f . reflect main :: IO () main = do print $ reify HNil $ hApp (\ HNil -> 42) print $ reify (HSolo 42) $ hApp (\ (HSolo a) -> a) print $ reify (28 :$ "0xe") $ hApp (\ (a :$ b) -> a + read b) -- Viktor.

I haven't thought about how to implement such a thing. At the least, it would probably require some annotation saying that we expect `\HNil -> ()` to be exhaustive (as GHC won't, in general, make that assumption). Even with that, could we get type inference to behave? Possibly.
As I wrote in another post on this thread, it’s a bit tricky.
What would you expect of (EX1)
\x -> case x of HNil -> blah
Here the lambda and the case are separated
Now (EX2)
\x -> (x, case x of HNil -> blah)
Here the lambda and the case are separated more, and x is used twice.
What if there are more data constructors that share a common return type? (EX3)
data HL2 a where
HNil1 :: HL2 []
HNil2 :: HL2 []
HCons :: …blah…
\x -> case x of { HNil1 -> blah; HNil 2 -> blah }
Here HNil1 and HNil2 both return HL2 []. Is that “singular”?
What if one was a bit more general than the other? Do we seek the least common generalisation of the alternatives given? (EX4)
data HL3 a where
HNil1 :: HL2 [Int]
HNil2 :: HL2 [a]
HCons :: …blah…
\x -> case x of { HNil1 -> blah; HNil 2 -> blah }
What if the cases were incompatible? (EX5)
data HL4 a where
HNil1 :: HL2 [Int]
HNil2 :: HL2 [Bool]
HCons :: …blah…
\x -> case x of { HNil1 -> blah; HNil 2 -> blah }
Would you expect that to somehow generalise to `HL4 [a] -> blah`?
What if x matched multiple times, perhaps on different constructors (EX6)
\x -> (case s of HNil1 -> blah1; case x of HNil2 -> blah)
The water gets deep quickly here. I don’t (yet) see an obviously-satisfying design point that isn’t massively ad-hoc.
Simon
From: ghc-devs

As usual, I want to separate out the specification of a feature from the implementation. So let's just focus on specification for now -- with the caveat that there might be no possible implementation of these ideas. The key innovation I see lurking here is the idea of an *exhaustive* function, where we know that any pattern-match on an argument is always exhaustive. I will write such a thing with @->, in both the type and in the arrow that appears after the lambda. The @-> type is a subtype of -> (and perhaps does not need to be written differently from ->). EX1: \x @-> case x of HNil -> blah This is easy: we can infer HList '[] @-> blah's type, because the pattern match is declared to be exhaustive, and no other type grants that property. EX2: \x @-> (x, case x of HNit -> blah) Same as EX1. EX3: \x @-> case x of { HNil1 -> blah; HNil2 -> blah } Same as EX1. There is still a unique type for which the patten-match is exhaustive. EX4: Reject. There are multiple valid types, and we don't know which one to pick. This is like classic untouchable-variables territory. EX5: This is hard. A declarative spec would probably choose HL2 [a] -> ... as you suggest, but there may be no implementation of such an idea. EX6: Reject. No type leads to exhaustive matches. I'm not saying this is a good idea for GHC or that it's implementable. But the idea of having type inference account for exhaustivity in this way does not seem, a priori, unspecified. Richard
On Mar 29, 2021, at 5:00 AM, Simon Peyton Jones
wrote: I haven't thought about how to implement such a thing. At the least, it would probably require some annotation saying that we expect `\HNil -> ()` to be exhaustive (as GHC won't, in general, make that assumption). Even with that, could we get type inference to behave? Possibly.
As I wrote in another post on this thread, it’s a bit tricky.
What would you expect of (EX1)
\x -> case x of HNil -> blah
Here the lambda and the case are separated
Now (EX2)
\x -> (x, case x of HNil -> blah)
Here the lambda and the case are separated more, and x is used twice. What if there are more data constructors that share a common return type? (EX3)
data HL2 a where HNil1 :: HL2 [] HNil2 :: HL2 [] HCons :: …blah…
\x -> case x of { HNil1 -> blah; HNil 2 -> blah }
Here HNil1 and HNil2 both return HL2 []. Is that “singular”?
What if one was a bit more general than the other? Do we seek the least common generalisation of the alternatives given? (EX4)
data HL3 a where HNil1 :: HL2 [Int] HNil2 :: HL2 [a] HCons :: …blah…
\x -> case x of { HNil1 -> blah; HNil 2 -> blah }
What if the cases were incompatible? (EX5)
data HL4 a where HNil1 :: HL2 [Int] HNil2 :: HL2 [Bool] HCons :: …blah…
\x -> case x of { HNil1 -> blah; HNil 2 -> blah }
Would you expect that to somehow generalise to `HL4 [a] -> blah`?
What if x matched multiple times, perhaps on different constructors (EX6)
\x -> (case s of HNil1 -> blah1; case x of HNil2 -> blah)
The water gets deep quickly here. I don’t (yet) see an obviously-satisfying design point that isn’t massively ad-hoc.
Simon
From: ghc-devs
On Behalf Of Richard Eisenberg Sent: 29 March 2021 03:18 To: Alexis King Cc: ghc-devs@haskell.org Subject: Re: Type inference of singular matches on GADTs On Mar 26, 2021, at 8:41 PM, Alexis King
mailto:lexi.lambda@gmail.com> wrote: If there’s a single principal type that makes my function well-typed and exhaustive, I’d really like GHC to pick it.
I think this is the key part of Alexis's plea: that the type checker take into account exhaustivity in choosing how to proceed.
Another way to think about this:
f1 :: HList '[] -> () f1 HNil = ()
f2 :: HList as -> () f2 HNil = ()
Both f1 and f2 are well typed definitions. In any usage site where both are well-typed, they will behave the same. Yet f1 is exhaustive while f2 is not. This isn't really about an open-world assumption or the possibility of extra cases -- it has to do with what the runtime behaviors of the two functions are. f1 never fails, while f2 must check a constructor tag and perhaps throw an exception.
If we just see \HNil -> (), Alexis seems to be suggesting we prefer the f1 interpretation over the f2 interpretation. Why? Because f1 is exhaustive, and when we can choose an exhaustive interpretation, that's probably a good idea to pursue.
I haven't thought about how to implement such a thing. At the least, it would probably require some annotation saying that we expect `\HNil -> ()` to be exhaustive (as GHC won't, in general, make that assumption). Even with that, could we get type inference to behave? Possibly.
But first: does this match your understanding?
Richard

I'm not saying this is a good idea for GHC or that it's implementable. But the idea of having type inference account for exhaustivity in this way does not seem, a priori, unspecified.
No, but I’m pointing out that specifying it might be tricky, involving some highly non-local reasoning. I can’t yet see how to write a formal specification. Note “yet” -- growth mindset!
Simon
From: Richard Eisenberg

On 3/28/21 9:17 PM, Richard Eisenberg wrote:
I think this is the key part of Alexis's plea: that the type checker take into account exhaustivity in choosing how to proceed.
[…]
Does this match your understanding?
Yes, precisely. :) Without GADTs, exhaustivity doesn’t yield any useful information to the typechecker, but with them, it can. I agree with Simon that it seems tricky—his examples are good ones—and I agree with Richard that I don’t know if this is actually a good or fruitful idea. I’m certainly not demanding anyone else produce a solution! But I was curious if anyone had explored this before, and it sounds like perhaps the answer is “no.” Fair enough! I still appreciate the discussion. Alexis

What would you expect of
1. \x -> case x of HNil -> blah
Here the lambda and the case are separated.
1. \x -> (x, case x of HNil -> blah)
Here the lambda and the case are separated more, and x is used twice.
What if there are more data constructors that share a common return type?
1. data HL2 a where
HNil1 :: HL2 []
HNil2 :: HL2 []
HCons :: …blah…
\x -> case x of { HNil1 -> blah; HNil 2 -> blah }
Here HNil1 and HNil2 both return HL2 []. Is that “singular”? What if one was a bit more general than the other? Do we seek the least common generalisation of the alternatives given?
The water gets deep quickly here. I don’t (yet) see an obviously-satisfying design point that isn’t massively ad-hoc.
Simon
From: ghc-devs
participants (6)
-
Alexis King
-
Carter Schonwald
-
Richard Eisenberg
-
Sebastian Graf
-
Simon Peyton Jones
-
Viktor Dukhovni