[GHC] #13774: Singletons code fails to typecheck when type signature involving type family is added

#13774: Singletons code fails to typecheck when type signature involving type family is added -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (Type checker) | Keywords: TypeFamilies | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Yes, I know "singletons" is in the title... but the code isn't //that// scary, I promise. Here's some code which //does// typecheck: {{{#!hs {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} module Bug where data family Sing (a :: k) data Nat = Zero | Succ Nat data instance Sing (b :: Bool) where SFalse :: Sing 'False STrue :: Sing 'True data instance Sing (n :: Nat) where SZero :: Sing 'Zero SSucc :: Sing n -> Sing ('Succ n) type family Not (x :: Bool) :: Bool where Not 'True = 'False Not 'False = 'True sNot :: Sing b -> Sing (Not b) sNot STrue = SFalse sNot SFalse = STrue class PFD a b | a -> b where type L2r (x :: a) :: b instance PFD Bool Nat where type L2r 'False = 'Zero type L2r 'True = 'Succ 'Zero type T2 = L2r 'False class SFD a b | a -> b where sL2r :: forall (x :: a). Sing x -> Sing (L2r x :: b) instance SFD Bool Nat where sL2r SFalse = SZero sL2r STrue = SSucc SZero sT2 = sL2r SFalse }}} It also typechecks if you give `sT2` this particular type signature: {{{#!hs sT2 :: Sing 'Zero sT2 = sL2r SFalse }}} However, if you give it either of these two type signatures: {{{#!hs sT2 :: Sing T2 }}} {{{#!hs sT2 :: Sing (L2r 'False) }}} Then GHC 8.0.1, 8.0.2, 8.2.1, and HEAD will choke: {{{ GHCi, version 8.2.0.20170522: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:46:7: error: • No instance for (SFD Bool k) arising from a use of ‘sL2r’ • In the expression: sL2r SFalse In an equation for ‘sT2’: sT2 = sL2r SFalse | 46 | sT2 = sL2r SFalse | ^^^^^^^^^^^ }}} At this point, I get the urge to yell obscenities at GHC, because there definitely //is// an instance of the form `SFD Bool k` in scope (and moreover, `SFD`'s functional dependency should make sure that `k ~ Nat`). Shouldn't it be using that? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13774 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

Inference dependent on functional dependencies is unpredictably bad. The
#13774: Singletons code fails to typecheck when type signature involving type family is added -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: FunDeps, Resolution: | TypeFamilies Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: goldfire (added) * keywords: TypeFamilies => FunDeps, TypeFamilies Comment: Some possible wisdom from the `singletons` [https://github.com/goldfirere/singletons/tree/f9910fef9084ad9e3ca6b4f713c882... #known-bugs README]: problem is that a use of an associated type family tied to a class with fundeps doesn't provoke the fundep to kick in. This is GHC's problem, in the end. And this [https://github.com/goldfirere/singletons/issues/37#issuecomment-41488816 comment]:
If only a type family could have functional dependencies, we could get somewhere, but alas, no. (Sidenote: of course, a type family can be declared within a class with functional dependencies, but GHC doesn't apply the fundeps when examining the type family.)
I was unable to dig up anything which explained these comments. Richard, can you elaborate more on this interaction between type families and functional dependencies? Is there an existing ticket which describes the root issue? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13774#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13774: Singletons code fails to typecheck when type signature involving type family is added -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: FunDeps, Resolution: | TypeFamilies Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): I don't think this is related to those comments. To explain those comments: {{{ class C a b | a -> b where f :: a -> b class PC a b | a -> b where type F (x :: a) :: b }}} A use of `f` will trigger a need for a `C` instance. But a use of `F` won't. So, an inference that succeeds on terms fails on types. But that's not what's going on here. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13774#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13774: Singletons code fails to typecheck when type signature involving type family is added -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: FunDeps, Resolution: invalid | TypeFamilies Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => invalid Comment: Your type signature {{{ sT2 :: Sing (L2r 'False) }}} means {{{ sT2 :: forall k. Sing k (L2r Bool k 'False) }}} And, since `k` is universally quantified, we can't unify it with `Nat`. So the instance doesn't match. You can fix it thus {{{ sT2 :: Sing (L2r 'False :: Nat) }}} which indeed compiles fine. I'm not sure what other error message would be better. I'll close as invalid for now. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13774#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13774: Singletons code fails to typecheck when type signature involving type family is added -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: FunDeps, Resolution: invalid | TypeFamilies Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Well spotted -- thanks. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13774#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13774: Singletons code fails to typecheck when type signature involving type family is added -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: FunDeps, Resolution: invalid | TypeFamilies Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Urgh. I'd like to feign ignorance and claim that I would have never thought in a million years to put in a kind ascription, but this isn't even the first time that this bug has bit me (#11275). So I should probably know better by now... but thanks for patiently explaining to me again anyways :) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13774#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC