[GHC] #11237: Type synonyms are not expanded in the data type declaration return kind

#11237: Type synonyms are not expanded in the data type declaration return kind -------------------------------------+------------------------------------- Reporter: thomasw | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 (Type checker) | Keywords: | 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: -------------------------------------+------------------------------------- I was playing around with the cool new `-XTypeInType` stuff when I encountered the following issue: {{{#!hs {-# LANGUAGE TypeInType #-} {-# LANGUAGE GADTs #-} module TypeInTypeBug where import qualified Data.Kind -- This works, using Data.Kind.Type as return kind --------------vvvvvvvvvvvvvv data Works :: Data.Kind.Type where WorksConstr :: Works type Set = Data.Kind.Type -- This doesn't work, using a type synonym for Data.Kind.Type as return kind ---------------vvv data Doesnt :: Set where DoesntConstr :: Doesnt }}} {{{ TypeInTypeBug.hs:17:1: error: • Kind signature on data type declaration has non-* return kind Set • In the data declaration for ‘Doesnt’ }}} I suppose type synonyms should be expanded in the return kind of a data type declaration before checking it is `*`. I also think the error message is not totally correct, take the following '''valid''' data declaration: {{{#!hs data Foo :: Bool -> Data.Kind.Type where Tru :: Foo True Fal :: Foo False }}} The return kind of the data declaration is actually `Bool -> Data.Kind.Type` (or `Bool -> *`), which is not `*`. I assume the error message is talking about the return kind (`*`) of the return kind (`Bool -> *`) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11237 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11237: Type synonyms are not expanded in the data type declaration return kind -------------------------------------+------------------------------------- Reporter: thomasw | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.11 checker) | Resolution: | Keywords: 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): * owner: => goldfire -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11237#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11237: Type synonyms are not expanded in the data type declaration return kind -------------------------------------+------------------------------------- Reporter: thomasw | Owner: jstolarek Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.11 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1636 Wiki Page: | -------------------------------------+------------------------------------- Changes (by jstolarek): * owner: goldfire => jstolarek * differential: => Phab:D1636 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11237#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11237: Type synonyms are not expanded in the data type declaration return kind -------------------------------------+------------------------------------- Reporter: thomasw | Owner: jstolarek Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 7.11 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | typecheck/should_compile/T11237 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1636 Wiki Page: | -------------------------------------+------------------------------------- Changes (by jstolarek): * status: new => closed * testcase: => typecheck/should_compile/T11237 * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11237#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11237: Type synonyms are not expanded in the data type declaration return kind -------------------------------------+------------------------------------- Reporter: thomasw | Owner: jstolarek Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 7.11 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | typecheck/should_compile/T11237 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1636 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): What commit fixed this? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11237#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11237: Type synonyms are not expanded in the data type declaration return kind
-------------------------------------+-------------------------------------
Reporter: thomasw | Owner: jstolarek
Type: bug | Status: closed
Priority: normal | Milestone:
Component: Compiler (Type | Version: 7.11
checker) |
Resolution: fixed | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: GHC rejects | Test Case:
valid program | typecheck/should_compile/T11237
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D1636
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Jan Stolarek

#11237: Type synonyms are not expanded in the data type declaration return kind -------------------------------------+------------------------------------- Reporter: thomasw | Owner: jstolarek Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 7.11 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | typecheck/should_compile/T11237 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1636 Wiki Page: | -------------------------------------+------------------------------------- Comment (by jstolarek): Replying to [comment:4 simonpj]:
What commit fixed this? Forgot to push :-) Sorry.
-- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11237#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC