[GHC] #12679: Permit abstract data types in signatures that don't have kind *

#12679: Permit abstract data types in signatures that don't have kind * -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: feature | Status: new request | Priority: low | Milestone: Component: Compiler | Version: 8.1 (Type checker) | Keywords: backpack | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Here is a fascinating program that I would like to write, but cannot with Backpack today: {{{ unit p where signature Key where import GHC.Exts (Constraint) data Key k :: Constraint instance Key Bool signature Map where import Key data Map k a empty :: Map k a insert :: Key k => k -> a -> Map k a -> Map k a lookup :: Key k => k -> Map k a -> Maybe a signature Keys where import Map module M where import Map import Key x = insert True "foo" empty }}} `data Key k :: Constraint` is implementable, because we can implement abstract data types using type synonyms in Backpack, and synonyms can have more kinds than just `*`. However, GHC chokes on this declaration, because it thinks that data types always have to have kind `*`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12679 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12679: Permit abstract data types in signatures that don't have kind * -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: feature request | Status: new Priority: low | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: backpack Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by ezyang: @@ -16,2 +16,0 @@ - signature Keys where - import Map New description: Here is a fascinating program that I would like to write, but cannot with Backpack today: {{{ unit p where signature Key where import GHC.Exts (Constraint) data Key k :: Constraint instance Key Bool signature Map where import Key data Map k a empty :: Map k a insert :: Key k => k -> a -> Map k a -> Map k a lookup :: Key k => k -> Map k a -> Maybe a module M where import Map import Key x = insert True "foo" empty }}} `data Key k :: Constraint` is implementable, because we can implement abstract data types using type synonyms in Backpack, and synonyms can have more kinds than just `*`. However, GHC chokes on this declaration, because it thinks that data types always have to have kind `*`. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12679#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12679: Permit abstract data types in signatures that don't have kind * -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: feature request | Status: new Priority: low | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: backpack Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by ezyang: @@ -22,0 +22,3 @@ + The point is to make the *constraint* for Map parametrizable, so that + HashMap can levy a different constraint (Hashable) than Map (Ord). + New description: Here is a fascinating program that I would like to write, but cannot with Backpack today: {{{ unit p where signature Key where import GHC.Exts (Constraint) data Key k :: Constraint instance Key Bool signature Map where import Key data Map k a empty :: Map k a insert :: Key k => k -> a -> Map k a -> Map k a lookup :: Key k => k -> Map k a -> Maybe a module M where import Map import Key x = insert True "foo" empty }}} The point is to make the *constraint* for Map parametrizable, so that HashMap can levy a different constraint (Hashable) than Map (Ord). `data Key k :: Constraint` is implementable, because we can implement abstract data types using type synonyms in Backpack, and synonyms can have more kinds than just `*`. However, GHC chokes on this declaration, because it thinks that data types always have to have kind `*`. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12679#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12679: Permit abstract data types in signatures that don't have kind * -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: feature request | Status: new Priority: low | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: backpack 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): This is, I think, another example of the tension between `Constraint` and `*`. See #11715. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12679#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12679: Permit abstract data types in signatures that don't have kind * -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: feature request | Status: new Priority: low | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: backpack 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 ezyang): Also, you may be tempted to implement this using a constraint family: {{{ signature Key where import GHC.Exts (Constraint) type family Key k :: Constraint instance Key Bool }}} But this doesn't work, because GHC expects an instance head to be a type class. (This will probably be a problem even if we allow data types that are not kind Constraint.) The "silver lining" is that you can just defer the "insoluble" constraint to the use-site. But this is terribel, and there are other problems too. Here is some code that type checks with HEAD, but it is not pretty. {{{ {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE RoleAnnotations #-} unit p where signature Key where import GHC.Exts (Constraint) type family Key :: * -> Constraint signature Map where import Key type role Map nominal representational data Map k a empty :: Map k a insert :: Key k => k -> a -> Map k a -> Map k a lookup :: Key k => k -> Map k a -> Maybe a module M where import Map import Key -- Need to stick the instance constraint here -- (and need to do it explicitly! GHC won't infer it.) x :: Key Bool => Map Bool String x = insert True "foo" empty unit q where module Key where import GHC.Exts (Constraint) type family Key :: * -> Constraint type instance Key = Ord module Map(Map, M.empty, insert, lookup) where import Prelude hiding (lookup) import Data.Map (Map) import qualified Data.Map as M import Key -- Ord is NOT definitionally equal to Key, which means -- we have to massage the types insert :: Key k => k -> a -> Map k a -> Map k a insert = M.insert lookup :: Key k => k -> Map k a -> Maybe a lookup = M.lookup unit r where dependency p[Key=q:Key, Map=q:Map] -- OK! }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12679#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12679: Permit abstract data types in signatures that don't have kind * -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: feature request | Status: new Priority: low | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: backpack 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 goldfire): I don't think this is #11715 but is instead related to the commentary in #12680, where there seems to be some confusion about `data` vs `type` in signatures. See comment:10:ticket:12680 and comment:11:ticket:12680. If `data` can be implemented by a type synonym (something I dislike, to be honest), then `class` should be too. Can you use `class` instead of `data` in your example? That would seem to meet your needs. After all, `class` is essentially the same as `data` but with a different result kind. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12679#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12679: Permit abstract data types in signatures that don't have kind * -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: feature request | Status: patch Priority: low | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: backpack Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2595 Wiki Page: | -------------------------------------+------------------------------------- Changes (by ezyang): * status: new => patch * differential: => Phab:D2595 Comment: Richard is right. I put in a patch. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12679#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12679: Permit abstract data types in signatures that don't have kind *
-------------------------------------+-------------------------------------
Reporter: ezyang | Owner:
Type: feature request | Status: patch
Priority: low | Milestone:
Component: Compiler (Type | Version: 8.1
checker) |
Resolution: | Keywords: backpack
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D2595
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Edward Z. Yang

#12679: Permit abstract data types in signatures that don't have kind * -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: feature request | Status: closed Priority: low | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Resolution: fixed | Keywords: backpack Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2595 Wiki Page: | -------------------------------------+------------------------------------- Changes (by ezyang): * status: patch => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12679#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC