[GHC] #14048: Data instances of kind Constraint

#14048: Data instances of kind Constraint -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: #12369 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Continuation of #12369. Allow data instances ending in `Constraint`. This may be a bug but GHC already accepts (something to do with #11715) `data family Bot :: Constraint` but I can't make instances of it. Also fails for `data family Bot :: TYPE IntRep`. I propose letting users take these disparate data types and type classes {{{#!hs data Compose :: (k' -> Type) -> (k -> k') -> (k -> Type) where Compose :: f (g a) -> Compose f g a data Compose2 :: (k' -> (kk -> Type)) -> (k -> k') -> (k -> (kk -> Type)) where Compose2 :: f (g a) b -> Compose2 f g a b -- ComposeC :: (k' -> Constraint) -> (k -> k') -> (k -> Constraint) class f (g a) => ComposeC f g a instance f (g a) => ComposeC f g a -- ComposeC2 :: (k' -> (kk -> Constraint)) -> (k -> k') -> (k -> (kk -> Constraint)) class f (g a) b => ComposeC2 f g a b instance f (g a) b => ComposeC2 f g a b }}} and unify them as instances of a 'data' family indexed by `Type`, `kk -> Type`, `Constraint`, `kk -> Constraint`. (Same can be done for `Data.Functor.Product` and `class (f a, g a) => ProductC f g a`): {{{#!hs data family (·) :: (k' -> k'') -> (k -> k') -> (k -> k'') data instance (f · g) a where Compose :: f (g a) -> (f · g) a data instance (f · g) a b where Compose2 :: f (g a) b -> (f · g) a b instance f (g a) => (f · g) a instance f (g a) b => (f · g) a b }}} ---- TODO Once we have #1311 allow data instances of unlifted types. ---- Fun note: `(·) @(kk -> Type)` is used by [https://gist.github.com/ekmett/48f1b578cadeeaeee7a309ec6933d7ec Kmett] (as `Tensor`) & to motivate [http://i.cs.hku.hk/~bruno/papers/hs2017.pdf quantified class constraints], this should automatically pick the right data instance: {{{#!hs instance (Trans t, Trans t') => Trans (t · t') where lift :: Monad m => m ~> (t · t') m lift = Compose2 . lift @t . lift @t' }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14048 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14048: Data instances of kind Constraint -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12369 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): This is a larger feature request than just a relaxation of kind checking. It requires, e. g. the syntax for declaring a class instance for a data family. I think this is a large enough delta on the current intentions for data families that it should properly be a ghc-proposal. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14048#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14048: Data instances of kind Constraint -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12369 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Let me first throw some ideas out there to see if this even makes sense: Some data types have a related type class, for example `TypeRep` & `Typeable`, `Sing` & `SingI` {{{#!hs TypeRep :: k -> Type Typeable :: k -> Constraint Sing :: k -> Type SingI :: k -> Constraint }}} and classes that work for types as well as constructors {{{#!hs Eq :: Type -> Constraint Eq1 :: (Type -> Type) -> Constraint Eq2 :: (Type -> Type -> Type) -> Constraint }}} ---- It could completely re-use the syntax of type classes {{{#!hs data family Sing (a :: k) :: k' data instance Sing (a :: Bool) where SFalse :: Sing False STrue :: Sing True -- creates a class of kind `Sing :: k -> Constraint' class Sing (a :: k) where sing :: Sing a instance Sing (False :: Bool) where sing :: Sing (False :: Bool) sing = SFalse instance Sing (True :: Bool) where sing :: Sing (True :: Bool) sing = STrue }}} This lets us unify many names, {{{#!hs data family (,) :: k -> k -> k -- (,) :: Type -> Type -> Type data instance (a, b) = (a, b) -- (,) :: (k -> Type) -> (k -> Type) -> (k -> Type) data instance (f, g) a = Pair (f a) (g a) -- (,) :: (k -> k' -> Type) -> (k -> k' -> Type) -> (k -> k' -> Type) data instance (f, g) a b = Pair (f a b) (g a b) -- (,) :: Constraint -> Constraint -> Constraint class (a, b) => (a, b) instance (a, b) => (a, b) -- (,) :: (k -> Constraint) -> (k -> Constraint) -> (k -> Constraint) class (f a, g a) => (f, g) a instance (f a, g a) => (f, g) a }}} if you don't see a problem with this I can submit a proposal -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14048#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14048: Data instances of kind Constraint -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12369 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): I'm a little uncomfortable that this requires two declarations of the name: the `data family Sing :: ...` and the `class Sing ...`. More broadly, I think the code might be easier to read using two different names, frankly. But maybe others disagree. I don't see any major problems with adding it -- it's just a question of programmability (and maintenance burden). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14048#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14048: Data instances of kind Constraint -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12369 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Is [https://github.com/ghc-proposals/ghc- proposals/pull/32#issuecomment-319175473 Type v Constraint] not a use case, {{{#!hs data family (=>) data instance (=>) :: forall (r :: RuntimeRep). Constraint -> TYPE r -> Type data instance (=>) :: Constraint -> Constraint -> Constraint data instance (=>) :: forall (r :: RuntimeRep). TYPE r -> Constraint -> Constraint }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14048#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14048: Data instances of kind Constraint -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12369 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Could you elaborate on comment:4? As in, give a program that would benefit from this treatment (inventing syntax as you go). I think `(=>)` should have kind `Constraint -> TYPE r -> Type`, and that's it. Yes, in class and instance heads, the symbol `=>` appears between two types of kind `Constraint`, but that's not properly a use of the `(=>)` operator; it's just a piece of concrete syntax. To clarify my comment:3, I do think this is a possible direction of future travel and would make an appropriate ghc-proposal. I'm not yet convinced about the idea, but my reluctance is based in personal preference/taste, not technical grounds. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14048#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14048: Data instances of kind Constraint -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12369 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): [https://gist.github.com/Icelandjack/378d0b38e8043d68c8c78c62659cdb3d Gist] -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14048#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14048: Data instances of kind Constraint -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12369 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Re comment:6 : I'm not so worried about finding examples of where this would possibly be helpful. I'm interested in full examples showing how this might work, in practice. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14048#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14048: Data instances of kind Constraint -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12369 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Not to distract too much from the actual ticket (and perhaps this should be its own ticket), but it is rather disturbing that, as you briefly mentioned, `data Foo1 :: Constraint`/`data family Foo2 :: Constraint` is accepted today. Ultimately, it comes down to the fact that `isLiftedTypeKind` returns `True` for both `Type` //and// `Constraint`—see #14869—so GHC doesn't reject when the return kind is `Constraint`. I suppose that could be fixable by inserting an additional check for `not (isConstraintKind k)`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14048#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14048: Data instances of kind Constraint -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12369 | Differential Rev(s): Phab:D4479 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * differential: => Phab:D4479 Comment: Until we've agreed to actually allow this feature, Phab:D4479 properly catches uses of data types with return kind `Constraint` and rejects them. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14048#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14048: Data instances of kind Constraint
-------------------------------------+-------------------------------------
Reporter: Iceland_jack | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: #12369 | Differential Rev(s): Phab:D4479
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#14048: Data instances of kind Constraint -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: 8.4.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12369 | Differential Rev(s): Phab:D4479 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => merge * milestone: => 8.4.2 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14048#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14048: Data instances of kind Constraint -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.2 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12369 | Differential Rev(s): Phab:D4479 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-8.4` with a2e02a5f868d487667a26005ddcb557178b26475. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14048#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC