[GHC] #13404: Derive instances for classes with associated types
GHC
ghc-devs at haskell.org
Thu Mar 9 19:33:19 UTC 2017
#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
More information about the ghc-tickets
mailing list