[GHC] #11621: GHC doesn't see () as a Constraint in type family
 
            #11621: GHC doesn't see () as a Constraint in type family -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs {-# LANGUAGE DataKinds, TypeOperators, KindSignatures, MultiParamTypeClasses, TypeFamilies #-} import Data.Kind class NotFound type family F b where F 'False = (NotFound :: Constraint) F 'True = (() :: Constraint) }}} works fine. Removing all constraints and final line it works without any annotations and infers the type of `F :: Bool -> Constraint`: {{{#!hs type family F b where F 'False = NotFound }}} GHC seems determined that `() :: Type` unless explicitly told otherwise, I would like to be able to write: {{{#!hs type family F b where F 'False = NotFound F 'True = () }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11621 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
 
            #11621: GHC doesn't see () as a Constraint in type family -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * version: 8.1 => 7.10.1 * component: Compiler => Compiler (Type checker) @@ -5,1 +5,1 @@ - import Data.Kind + import GHC.Exts New description: {{{#!hs {-# LANGUAGE DataKinds, TypeOperators, KindSignatures, MultiParamTypeClasses, TypeFamilies #-} import GHC.Exts class NotFound type family F b where F 'False = (NotFound :: Constraint) F 'True = (() :: Constraint) }}} works fine. Removing all constraints and final line it works without any annotations and infers the type of `F :: Bool -> Constraint`: {{{#!hs type family F b where F 'False = NotFound }}} GHC seems determined that `() :: Type` unless explicitly told otherwise, I would like to be able to write: {{{#!hs type family F b where F 'False = NotFound F 'True = () }}} -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11621#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
 
            #11621: GHC doesn't see () as a Constraint in type family -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): See also #11715, which tackles the bigger picture -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11621#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
 
            #11621: GHC doesn't see () as a Constraint in type family -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by spacekitteh): Has this been fixed? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11621#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
 
            #11621: GHC doesn't see () as a Constraint in type family -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11715 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: => #11715 Comment: Replying to [comment:3 spacekitteh]:
Has this been fixed?
No. {{{ GHCi, version 8.3.20170516: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Main ( Bug.hs, interpreted ) Bug.hs:10:14: error: • Expected a constraint, but ‘()’ has kind ‘*’ • In the type ‘()’ In the type family declaration for ‘F’ | 10 | F 'True = () | ^^ }}} Again, this probably requires fixing #11715 first. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11621#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
 
            #11621: GHC doesn't see () as a Constraint in type family -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Resolution: | ConstraintKinds Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11715 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: => ConstraintKinds Comment: See also #13742 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11621#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
 
            #11621: GHC doesn't see () as a Constraint in type family -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Resolution: | ConstraintKinds Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11715, #13742 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: #11715 => #11715, #13742 Comment: Astoundingly, this program appears to have fixed itself between GHC 8.4 and 8.6, since this program: {{{#!hs {-# LANGUAGE DataKinds, TypeOperators, KindSignatures, MultiParamTypeClasses, TypeFamilies #-} import GHC.Exts class NotFound type family F b where F 'False = NotFound F 'True = () }}} Typechecks without issue on GHC 8.6.2 and HEAD. Should we go ahead and add a test case for this, or is this program fragile without a full fix for #11715? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11621#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
 
            #11621: GHC doesn't see () as a Constraint in type family -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Resolution: | ConstraintKinds Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11715, #13742 | Differential Rev(s): Phab:D5413 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D5413 Comment: I decided to be bold and just submit a patch for this. See Phab:D5413. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11621#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
 
            #11621: GHC doesn't see () as a Constraint in type family -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Resolution: | ConstraintKinds Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11715, #13742 | Differential Rev(s): Phab:D5413 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I wish it was really fixed, but it isn't. Try this {{{ type family F2 b where F2 'True = () F2 'False = NotFound }}} That elicits {{{ T11621.hs:12:14: error: * Expected a type, but `NotFound' has kind `Constraint' * In the type `NotFound' In the type family declaration for `F2' | 12 | F 'False = NotFound | ^^^^^^^^ }}} GHC is generally very good about being robustly order-independent; nothing depends on the order in which the type inference engine encounters code. But this is a rare counter example. The hack is described in `Note [Inferring tuple kinds]` in `TcHsType`. In `F`, GHC sees `NotFound` first, and that tells it that the answer is `Constraint`. IN `F2` it sees `()` first and guesses (wrongly) `*`. So I would say not-fixed. I can think of ad-hoc ways to fix this -- such as having a built-in constraint `TK k` which means `k` must be either `*` or `Constraint`. But I have thus far lacked the time and energy to think it through enough or implement it. Especially since #11715 is still open. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11621#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
 
            #11621: GHC doesn't see () as a Constraint in type family -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Resolution: | ConstraintKinds Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11715, #13742 | Differential Rev(s): Phab:D5413 Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Good catch. Alas, I had a feeling this was too good to be true. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11621#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
 
            #11621: GHC doesn't see () as a Constraint in type family -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Resolution: | ConstraintKinds Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11715, #13742 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: patch => new * differential: Phab:D5413 => -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11621#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
 
            #11621: GHC doesn't see () as a Constraint in type family -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Resolution: | ConstraintKinds Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11715, #13742, | Differential Rev(s): #16139, #16148 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: #11715, #13742 => #11715, #13742, #16139, #16148 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11621#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
- 
                 GHC GHC