[GHC] #13731: DeriveFunctor and friends don't understand type families

#13731: DeriveFunctor and friends don't understand type families -------------------------------------+------------------------------------- Reporter: spacekitteh | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 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 DeriveFunctor #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE TypeFamilies #-} data Test ext a where Foo :: a -> Test ext a Extend :: (ExtensionType ext a) -> Test ext a type family ExtensionType ext a data ListExtension type instance ExtensionType ListExtension a = [a] deriving instance Functor (Test ListExtension) {- a.hs:15:1: error: • Can't make a derived instance of ‘Functor (Test ListExtension)’: Constructor ‘Extend’ must use the type variable only as the last argument of a data type • In the stand-alone deriving instance for ‘Functor (Test ListExtension)’ | 15 | deriving instance Functor (Test ListExtension) | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ Failed, modules loaded: none. -} }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13731 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13731: DeriveFunctor and friends don't understand type families -------------------------------------+------------------------------------- Reporter: spacekitteh | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 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): The error message is terrible. (Ryan might you look at that?) But the program IS wrong. In Haskell you can't write {{{ f (xs ++ ys) = ... }}} which pattern-matches on a function call. And similarly at the type level you can't pattern match on a function call, as in `instance Functor (Test ListExtension)`. Instead write `instance Functor []`. Oh! We have that instance already; so you can just omit it! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13731#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13731: DeriveFunctor and friends don't understand type families -------------------------------------+------------------------------------- Reporter: spacekitteh | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 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 RyanGlScott): What would you rather the error message say? I do think the phrase "the type variable" is unfortunate, as it should rather be "the //last// type variable" (since there can be more than one). But other than that, it's pretty spot-on: if you're using the last type variable within another type, it must be a data type, and `ExtensionType` is not a data type. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13731#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13731: DeriveFunctor and friends don't understand type families -------------------------------------+------------------------------------- Reporter: spacekitteh | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 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 Iceland_jack): That instance becomes writable if we mark `ExtensionType` injective {{{#!hs data Test :: Type -> Type -> Type where Foo :: a -> Test ext a Extend :: ExtensionType ext a -> Test ext a type family ExtensionType a = (res :: Type -> Type) | res -> a data ListExtension type instance ExtensionType ListExtension = [] instance Functor (ExtensionType ext) => Functor (Test ext) where fmap :: (a -> a') -> (Test ext a -> Test ext a') fmap f = \case Foo a -> Foo (f a) Extend ex -> Extend (fmap f ex) }}} We need to bump the arity of `ExtensionType` down to one, given that we don't have #10832. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13731#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13731: DeriveFunctor and friends don't understand type families -------------------------------------+------------------------------------- Reporter: spacekitteh | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 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): Oh my mistake. I thought `instance Functor (Test ListExtension)` involved a type family; but it doesn't. Neither `Test` nor `ListExtension` is a type family. My mistake. Then indeed the error message makes more sense. But not total sense. If you reduce the arity of `ExtensionType1 the `deriving` clause works fine (as it should) {{{ type family ExtensionType ext :: * -> * type instance ExtensionType ListExtension = [] }}} So it's not that it must be a data type; it can be a saturated type-family application. But I now think this is a non-bug; `deriving` is working right, and reducing the arity of `ExtensionType` is the right solution. But -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13731#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13731: DeriveFunctor and friends don't understand type families -------------------------------------+------------------------------------- Reporter: spacekitteh | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 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 RyanGlScott):
So it's not that it must be a data type; it can be a saturated type- family application.
Am I missing something? In the original example, the type family instance is: {{{#!hs type instance ExtensionType ListExtension a = [a] }}} And the instance we're deriving is: {{{#!hs deriving instance Functor (Test ListExtension) }}} In other words, the field of `Extend` will have type `ExtensionType ListExtension a`. This is a fully saturated type family application, right? So surely the rule you've proposed doesn't quite capture the essence of this problem. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13731#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13731: DeriveFunctor and friends don't understand type families -------------------------------------+------------------------------------- Reporter: spacekitteh | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 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 Iceland_jack): Replying to [comment:4 simonpj]:
If you reduce the arity of `ExtensionType1 the `deriving` clause works fine (as it should)
Ah, nothing to do with injective type families -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13731#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13731: DeriveFunctor and friends don't understand type families -------------------------------------+------------------------------------- Reporter: spacekitteh | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 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): Consider the instance we want: {{{ instance Functor (Test ListExtension) where fmap f (Extend x) = Extend (fmap f x) }}}
Am I missing something?
From the inner `fmap` we get `[W] Functor (ExtensionType ListExtension)`. If `ExtensionType` has arity 2, that would be an un-saturated type family. But if it has arity 1 it is saturated, and reduces to `[]`, so all is well.
... the field of `Extend` will have type `ExtensionType ListExtension a`. This is a fully saturated type family application
Yes, it's saturated in the field, but the use of `fmap` requires us to decompose the type application, we it must be decomposable. It's only decomposable if `ExtensionType` has arity 1. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13731#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13731: DeriveFunctor and friends don't understand type families -------------------------------------+------------------------------------- Reporter: spacekitteh | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 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 RyanGlScott): Replying to [comment:7 simonpj]:
Yes, it's saturated in the field, but the use of `fmap` requires us to decompose the type application, we it must be decomposable. It's only decomposable if `ExtensionType` has arity 1.
Thank you, this is the part that I wasn't understanding. So would you be happy with this error message? {{{ • Can't make a derived instance of ‘Functor (Test ListExtension)’: Constructor ‘Extend’ must use the last type variable only as the last argument of a data type or a saturated type family }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13731#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13731: DeriveFunctor and friends don't understand type families -------------------------------------+------------------------------------- Reporter: spacekitteh | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 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): You should ask users not me! But looking at {{{ Extend :: ExtensionType ext a -> Test ext a }}} a user might say that `ExtentionType ext a` ''does'' use `a` as the last arg of a saturated type-family application, namely `ExtensionType ext a`! An what is "the last type variable"? Guessing wildly, what about {{{ Illegal use of type variable 'a' in the first argument of `Extend`. Such uses must be of form `ty a` where `ty` is a data type or saturated type family application. }}} I'm not sure if that's better... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13731#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13731: DeriveFunctor and friends don't understand type families -------------------------------------+------------------------------------- Reporter: spacekitteh | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: deriving 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 RyanGlScott): * status: new => infoneeded * keywords: => deriving Comment: Requesting feedback from spacekitteh on what is expected here. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13731#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC