[GHC] #8516: Add (->) representation and the Invariant class to GHC.Generics
GHC
ghc-devs at haskell.org
Wed Nov 30 08:58:26 UTC 2016
#8516: Add (->) representation and the Invariant class to GHC.Generics
-------------------------------------+-------------------------------------
Reporter: nfrisby | Owner:
Type: feature request | Status: new
Priority: low | Milestone:
Component: Compiler (Type | Version: 7.7
checker) |
Resolution: | Keywords: Generics
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 songzh):
* cc: songzh (added)
Comment:
Replying to [ticket:8516 nfrisby]:
> We currently disallow any use of the parameter in the domain of (->).
>
> {{{
> newtype F a = F ((a -> Int) -> Int) deriving Generic1
>
> <interactive>:4:38:
> Can't make a derived instance of `Generic1 (F g)':
> Constructor `F' must use the last type parameter only as the last
argument of a data type, newtype, or (->)
> In the data declaration for `F'
> }}}
>
> !DeriveFunctor succeeds for this F.
>
> I'd like to add this representation type to GHC.Generics and
!DeriveGeneric.
>
> {{{
> newtype (f :->: g) a = FArrow1 (f a -> g a)
> }}}
>
> We could then represent the first example above. We could also derive
the more interesting Generic1 (F g).
>
> {{{
> newtype F g a = F (g a -> Int) deriving Generic1
>
> type instance Rep1 (F g) = Rec1 g :->: Rec0 Int
>
> instance Generic1 (F g) where
> to x = F $ unRec0 . unArrow1 x . Rec1
> from (F x) = FArrow1 $ Rec0 . x . unRec1
> }}}
>
> Admittedly, there's not many generic definitions impeded by not having
(:->:). Contra- and in-variant types are uncommon.
>
> I'm suggesting this feature without strong motivating examples because I
think this would streamline the implementation of -XDeriveGenerics in some
ways while also making it more general — assuming that we added the
Invariant class to base or ghc-prim.
>
> {{{
> class Invariant t where
> invmap :: (a -> b) -> (b -> a) -> t a -> t b
>
> invmap_covariant :: Functor t => (a -> b) -> (b -> a) -> t a -> t b
> invmap_covariant f _ = fmap f
>
> instance (Invariant f,Invariant g) => Invariant (FArrow f g) where
> invmap co contra (FArrow h) = FArrow $ invmap co contra . h . invmap
contra co
> }}}
>
> (Of course, Invariant should be a super class of Functor. :/ )
>
> Now we can handle quite involved examples:
>
> {{{
> newtype F g h a = F (g (h a)) deriving Generic1
>
> instance Invariant g => Generic1 (F g h) where
> to x = invmap unRec1 Rec1 $ unComp1 x
> from (F x) = Comp1 $ invmap Rec1 unRec1
> }}}
>
> All of that said, I'm mostly opening this ticket so I can get feedback
on difficulties I might not be anticipating and have a place to reference
from the compiler source code comments.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8516#comment:14>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list