[GHC] #13404: Derive instances for classes with associated types

#13404: Derive instances for classes with associated types -------------------------------------+------------------------------------- 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: -------------------------------------+------------------------------------- When trying to derive an instance of a class with associated types {{{#!hs import Data.Distributive import Data.Functor.Rep data Pair a = a :# a deriving Functor instance Distributive Pair where distribute :: Functor f => f (Pair a) -> Pair (f a) distribute = distributeRep instance Representable Pair where type Rep Pair = Bool index :: Pair a -> (Bool -> a) index (a :# _) False = a index (_ :# b) True = b newtype PAIR a = PAIR (Pair a) deriving (Functor, Representable) instance Distributive PAIR where distribute = {- distributeRep -} }}} {{{ • Can't make a derived instance of ‘Representable PAIR’ (even with cunning GeneralizedNewtypeDeriving): the class has associated types • In the newtype declaration for ‘PAIR’ }}} But it could create an instance {{{#!hs instance Representable PAIR where type Rep PAIR = Bool index :: forall a. PAIR a -> (Bool -> a) index = coerce (index :: Pair a -> (Bool -> a)) }}} Same with complicated expressions like {{{#!hs infixr 9 · type (·) = Compose newtype P f g h a = P (Product (f·g·f) (h·f·g) a) deriving (Functor, Foldable, Traversable, Applicative, Alternative, Distributive) instance (Functor f, Functor g, Functor h, Representable f, Representable g, Representable h) => Distributive (P f g h) where distribute = distributeRep instance (Functor f, Functor g, Functor h, Representable f, Representable g, Representable h) => Representable (P f g h) where type Rep (P f g h) = Either (Rep f, (Rep g, Rep f)) (Rep h, (Rep f, Rep g)) index :: (P f g h) a -> (Either (Rep f, (Rep g, Rep f)) (Rep h, (Rep f, Rep g)) -> a) index = coerce (index @(Product (f·g·f) (h·f·g))) tabulate :: (Either (Rep f, (Rep g, Rep f)) (Rep h, (Rep f, Rep g)) -> a) -> (P f g h) a tabulate = coerce (tabulate @(Product (f·g·f) (h·f·g))) }}} Is this too limited to work on general -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13404 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13404: Derive instances for classes with associated types -------------------------------------+------------------------------------- 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:
When trying to derive an instance of a class with associated types
{{{#!hs import Data.Distributive import Data.Functor.Rep
data Pair a = a :# a deriving Functor
instance Distributive Pair where distribute :: Functor f => f (Pair a) -> Pair (f a) distribute = distributeRep
instance Representable Pair where type Rep Pair = Bool
index :: Pair a -> (Bool -> a) index (a :# _) False = a index (_ :# b) True = b
newtype PAIR a = PAIR (Pair a) deriving (Functor, Representable)
instance Distributive PAIR where distribute = {- distributeRep -} }}}
{{{ • Can't make a derived instance of ‘Representable PAIR’ (even with cunning GeneralizedNewtypeDeriving): the class has associated types • In the newtype declaration for ‘PAIR’ }}}
But it could create an instance
{{{#!hs instance Representable PAIR where type Rep PAIR = Bool
index :: forall a. PAIR a -> (Bool -> a) index = coerce (index :: Pair a -> (Bool -> a)) }}}
Same with complicated expressions like
{{{#!hs infixr 9 · type (·) = Compose
newtype P f g h a = P (Product (f·g·f) (h·f·g) a) deriving (Functor, Foldable, Traversable, Applicative, Alternative, Distributive)
instance (Functor f, Functor g, Functor h, Representable f, Representable g, Representable h) => Distributive (P f g h) where distribute = distributeRep
instance (Functor f, Functor g, Functor h, Representable f, Representable g, Representable h) => Representable (P f g h) where type Rep (P f g h) = Either (Rep f, (Rep g, Rep f)) (Rep h, (Rep f, Rep g))
index :: (P f g h) a -> (Either (Rep f, (Rep g, Rep f)) (Rep h, (Rep f, Rep g)) -> a) index = coerce (index @(Product (f·g·f) (h·f·g)))
tabulate :: (Either (Rep f, (Rep g, Rep f)) (Rep h, (Rep f, Rep g)) -> a) -> (P f g h) a tabulate = coerce (tabulate @(Product (f·g·f) (h·f·g))) }}}
Is this too limited to work on general
New description: When trying to derive an instance of a class with associated types {{{#!hs import Data.Distributive import Data.Functor.Rep data Pair a = a :# a deriving Functor instance Distributive Pair where distribute :: Functor f => f (Pair a) -> Pair (f a) distribute = distributeRep instance Representable Pair where type Rep Pair = Bool index :: Pair a -> (Bool -> a) index (a :# _) False = a index (_ :# b) True = b newtype PAIR a = PAIR (Pair a) deriving (Functor, Representable) instance Distributive PAIR where distribute = {- distributeRep -} }}} {{{ • Can't make a derived instance of ‘Representable PAIR’ (even with cunning GeneralizedNewtypeDeriving): the class has associated types • In the newtype declaration for ‘PAIR’ }}} But it could create an instance {{{#!hs instance Representable PAIR where type Rep PAIR = Bool index :: forall a. PAIR a -> (Bool -> a) index = coerce (index :: Pair a -> (Bool -> a)) }}} Same with complicated expressions like {{{#!hs infixr 9 · type (·) = Compose newtype P f g h a = P (Product (f·g·f) (h·f·g) a) deriving (Functor, Foldable, Traversable, Applicative, Alternative, Distributive) instance (Functor f, Functor g, Functor h, Representable f, Representable g, Representable h) => Distributive (P f g h) where distribute = distributeRep instance (Functor f, Functor g, Functor h, Representable f, Representable g, Representable h) => Representable (P f g h) where type Rep (P f g h) = Either (Rep f, (Rep g, Rep f)) (Rep h, (Rep f, Rep g)) index :: (P f g h) a -> (Either (Rep f, (Rep g, Rep f)) (Rep h, (Rep f, Rep g)) -> a) index = coerce (index @(Product (f·g·f) (h·f·g))) tabulate :: (Either (Rep f, (Rep g, Rep f)) (Rep h, (Rep f, Rep g)) -> a) -> (P f g h) a tabulate = coerce (tabulate @(Product (f·g·f) (h·f·g))) }}} Is this too limited to work in general -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13404#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13404: Derive instances for classes with associated types -------------------------------------+------------------------------------- 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: #4083 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Iceland_jack): * related: => #4083 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13404#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13404: Derive instances for classes with associated types -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #2721, #4083, | Differential Rev(s): #8165 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => duplicate * related: #4083 => #2721, #4083, #8165 * milestone: => 8.2.1 Comment: You're in luck, because this works in GHC 8.2. (In fact, I'll mark this as a duplicate of #2721/#8165.) This is the what the derived `Representable PAIR` instance is in the first example: {{{#!hs instance Representable PAIR where type Rep PAIR = Rep Pair tabulate = coerce @(forall (a :: Type). (Rep Pair -> a) -> Pair a) @(forall (a :: Type). (Rep PAIR -> a) -> PAIR a) tabulate index = coerce @(forall (a :: Type). Pair a -> Rep Pair -> a) @(forall (a :: Type). PAIR a -> Rep PAIR -> a) index }}} And in the second example: {{{#!hs instance (Representable h, Representable g, Representable f) => Representable (P f g h) where type Rep (P f g h) = Rep (Product (f · (g · f)) (h · (f · g))) tabulate = coerce @(forall (a :: Type). (Rep Product (·) f (·) g f (·) h (·) f g -> a) -> Product (·) f (·) g f (·) h (·) f g a) @(forall (a :: Type). (Rep P f g h -> a) -> P f g h a) tabulate index = coerce @(forall (a :: Type). Product (·) f (·) g f (·) h (·) f g a -> Rep Product (·) f (·) g f (·) h (·) f g -> a) @(forall (a :: Type). P f g h a -> Rep P f g h -> a) index }}} As you can see, the algorithm works by taking the newtype's underlying type and sticking the associate type family in front of it, so you get `type Rep PAIR = Rep Pair` and `type Rep (P f g h) = Rep (Product (f · (g · f)) (h · (f · g)))` (which expand to `Bool` and `Either (Rep f, (Rep g, Rep f)) (Rep h, (Rep f, Rep g))`, respectively). This requires `UndecidableInstances` to use, but then again, so does a bunch of other code that involves type families ;) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13404#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13404: Derive instances for classes with associated types -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #2721, #4083, | Differential Rev(s): #8165 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Does the user manual explain this? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13404#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13404: Derive instances for classes with associated types -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #2721, #4083, | Differential Rev(s): #8165 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Replying to [comment:4 simonpj]:
Does the user manual explain this?
Yes, see http://git.haskell.org/ghc.git/blob/ab27fdcfe26759f3e4cd7e2105e7e7e83e269e48... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13404#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13404: Derive instances for classes with associated types -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #2721, #4083, | Differential Rev(s): #8165 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Yes!! Jolly good -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13404#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC