[GHC] #13962: GHCi allows unsaturated type family

#13962: GHCi allows unsaturated type family -------------------------------------+------------------------------------- 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: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Taken from [http://ics.p.lodz.pl/~stolarek/_media/pl:research:promotion- haskell14-slides.pdf Promoting Functions to Type Families in Haskell] {{{#!hs {-# Language TypeFamilies, PolyKinds, DataKinds, TypeOperators #-} type family Map (f :: a -> b) (xs :: [a]) :: [b] where Map f '[] = '[] Map f (x ': xs) = f x ': Map f xs data N = O | S N type family Pred (n :: N) :: N where Pred O = O Pred (S n) = n -- The type family ‘Map’ should have 2 arguments, but has been given 1 type MapPred = Map Pred }}} fails as expected, but it works in GHCi {{{ ghci> :kind Map Pred Map Pred :: [N] -> [N] ghci> :kind! Map Pred '[S (S O), S O, O] Map Pred '[S (S O), S O, O] :: [N] = '['S 'O, 'O, 'O] }}} I can only test this in GHC 7.8, 8 now. I know GHCi has weird rules for unsaturated type families but I figured I'd write a ticket because the slides say "But it is invalid to write: `Map Pred '[O, S O]`". -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13962 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13962: GHCi allows unsaturated type family -------------------------------------+------------------------------------- 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: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by Iceland_jack: Old description:
Taken from [http://ics.p.lodz.pl/~stolarek/_media/pl:research:promotion- haskell14-slides.pdf Promoting Functions to Type Families in Haskell]
{{{#!hs {-# Language TypeFamilies, PolyKinds, DataKinds, TypeOperators #-}
type family Map (f :: a -> b) (xs :: [a]) :: [b] where Map f '[] = '[] Map f (x ': xs) = f x ': Map f xs
data N = O | S N
type family Pred (n :: N) :: N where Pred O = O Pred (S n) = n
-- The type family ‘Map’ should have 2 arguments, but has been given 1 type MapPred = Map Pred }}}
fails as expected, but it works in GHCi
{{{ ghci> :kind Map Pred Map Pred :: [N] -> [N] ghci> :kind! Map Pred '[S (S O), S O, O] Map Pred '[S (S O), S O, O] :: [N] = '['S 'O, 'O, 'O] }}}
I can only test this in GHC 7.8, 8 now. I know GHCi has weird rules for unsaturated type families but I figured I'd write a ticket because the slides say "But it is invalid to write: `Map Pred '[O, S O]`".
New description: Taken from [http://ics.p.lodz.pl/~stolarek/_media/pl:research:promotion- haskell14-slides.pdf Promoting Functions to Type Families in Haskell] {{{#!hs {-# Language TypeFamilies, PolyKinds, DataKinds, TypeOperators #-} type family Map (f :: a -> b) (xs :: [a]) :: [b] where Map f '[] = '[] Map f (x ': xs) = f x ': Map f xs data N = O | S N type family Pred (n :: N) :: N where Pred O = O Pred (S n) = n -- The type family ‘Map’ should have 2 arguments, but has been given 1 type MapPred = Map Pred }}} fails as expected, but commenting it out and writing `Map Pred` works in GHCi {{{ ghci> :kind Map Pred Map Pred :: [N] -> [N] ghci> :kind! Map Pred '[S (S O), S O, O] Map Pred '[S (S O), S O, O] :: [N] = '['S 'O, 'O, 'O] }}} I can only test this in GHC 7.8, 8 now. I know GHCi has weird rules for unsaturated type families but I figured I'd write a ticket because the slides say "But it is invalid to write: `Map Pred '[O, S O]`". -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13962#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13962: GHCi allows unsaturated type family -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12089 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott, goldfire (added) * keywords: => TypeFamilies * related: => #12089 Comment: Wow, that's astounding that it actually gives you the right answer... Richard, do you know how this is even working? Because I have to admit, this is shaking my faith in the belief that we need defunctionalization to partially apply type families ;) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13962#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13962: GHCi allows unsaturated type family -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12089 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): GHC is behaving according to its manual. See [https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/ghci.html #ghci-cmd-:kind this section]. We made a special case for `:kind` some years ago to allow queries like `:kind Map`. The user sensibly wants `Map`'s kind, and we should give it to them. So the TF-saturation requirement is dropped in `:kind`. I support this design choice. On the other hand, it's very suspect in `:kind!`. It's surprising to me, too, that this gives the right result. But, after all, TF evaluation makes fine sense with unsaturated type families -- it's just type inference that gets muddled. So: we could keep the current behavior (which doesn't seem to be hurting anyone), or restrict the behavior of `kind!` to disallow partially applied type families. Maybe an intermediate approach is to keep the current behavior but issue a warning in the event of a partially applied family. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13962#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13962: GHCi allows unsaturated type family -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12089 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I see. I'm a bit embarrassed that I've been doing `:kind Map` all this time and never realized that I was doing something unsavory. I'm curious - how does type inference get muddled exactly? And moreover, is the particular way in which it becomes muddled relevant for `:kind`? If not, then I'd vote to leave things the way they are. Otherwise, we might want to reconsider. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13962#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13962: GHCi allows unsaturated type family -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12089 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): The muddiness all comes down to this: If GHC knows `m a ~ Maybe Int`, should it choose `m ~ Maybe` and `a ~ Int`? After all, if `m` could be an unsaturated type family, committing to the above decomposition would be wrong. This kind of inference seems unlikely in `:kind` or `:kind!`, though I can't rule it out if someone tried to. In the end, I think we should just keep the current behavior. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13962#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13962: GHCi allows unsaturated type family -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: wontfix | Keywords: TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12089 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => wontfix Comment: Replying to [comment:5 goldfire]:
The muddiness all comes down to this: If GHC knows `m a ~ Maybe Int`, should it choose `m ~ Maybe` and `a ~ Int`? After all, if `m` could be an unsaturated type family, committing to the above decomposition would be wrong.
This kind of inference seems unlikely in `:kind` or `:kind!`, though I can't rule it out if someone tried to.
Thanks for explaining this.
In the end, I think we should just keep the current behavior.
That sounds reasonable to me. Given that there's already a section in the users' manual about this, I'd say we can just close this ticket. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13962#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13962: GHCi allows unsaturated type family
-------------------------------------+-------------------------------------
Reporter: Iceland_jack | Owner: (none)
Type: bug | Status: closed
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: wontfix | Keywords: TypeFamilies
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: #12089, #16013 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Changes (by RyanGlScott):
* related: #12089 => #12089, #16013
Comment:
Note that we opted to disallow unsaturated type synonyms/families in GHCi
when not at the top level in commit
[https://gitlab.haskell.org/ghc/ghc/commit/6b70cf611e5ddc475edaa54b893d209906...
6b70cf611e5ddc475edaa54b893d20990699ddb8]:
{{{
commit 6b70cf611e5ddc475edaa54b893d20990699ddb8
Author: Ryan Scott
participants (1)
-
GHC