[GHC] #13403: Derive instances (Applicative, Monad, ...) for structures lifted over functors

#13403: Derive instances (Applicative, Monad, ...) for structures lifted over functors -------------------------------------+------------------------------------- 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: -------------------------------------+------------------------------------- I'll start small: Given that we know how to define various instances for [https://hackage.haskell.org/package/base-4.9.1.0/docs/Data-Functor- Product.html Product] GHC could do it automatically. {{{#!hs data P f g a = f a ::: g a deriving (Functor, Applicative, Alternative) {- instance (Applicative f, Applicative g) => Applicative (P f g) where pure x = pure x ::: pure x (f:::g) <*> (x:::y) = (f <*> x) ::: (g <*> y) -} }}} And for specific constructors as well {{{#!hs data Q a = [a] :*: Maybe a deriving (Functor, Applicative, Alternative) {- instance Applicative Q where pure x = [x] :*: Just x (f:*:g) <*> (x:*:y) = (f <*> x) :*: (g <*> y) -} }}} == Alternative == Use `GeneralizedNewtypeDeriving` {{{#!hs newtype Q a = Q (Product [] Maybe a) deriving (Functor, Applicative, Alternative) pattern (:*:) :: [a] -> Maybe a -> Q a pattern a :*: b = Q (Pair a b) }}} == Future Work == This should work for a combination of various things, using `Const _` deprives us of `Alternative` {{{#!hs newtype U e a = U (([] `Product` Maybe `Product` Const e) a) deriving (Functor, Applicative) }}} using sums where [https://hackage.haskell.org/package/transformers-0.5.4.0/docs/Control- Applicative-Lift.html one summand is identity] gives us `Applicative` / `Alternative` {{{#!hs -- data Lift f a = Pure a | Other (f a) import Control.Applicative.Lift data V a = V ((Lift [] `Product` Maybe) a) deriving (Functor, Applicative, Alternative) }}} I want to be able to write this directly {{{#!hs data U e a = U [a] (Maybe a) (Const e a) deriving (Functor, Applicative) data V a = VL a (Maybe a) | VR [a] (Maybe a) deriving (Functor, Applicative, Alternative) }}} == Future, Future Work == [https://hackage.haskell.org/package/kan-extensions-5.0.1/docs/Data- Functor-Kan-Lan.html left-Kan extension] {{{#!hs data Lan g h a where Lan :: (g b -> a) -> h b -> Lan g h a deriving (Functor, Applicative) }}} [https://hackage.haskell.org/package/kan-extensions-5.0.1/docs/Control- Monad-Codensity.html codensity] {{{#!hs data Endo a = Endo (a -> a) newtype CodEndo a = CE (forall xx. (a -> Endo xx) -> Endo xx) deriving (Functor, Applicative, Monad) }}} and [https://hackage.haskell.org/package/free-4.12.4/docs/Control-Comonad- Cofree.html comonad] {{{#!hs data Rose a = a :< [Rose a] deriving (Functor, Applicative, Monad, Comonad, ...) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13403 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13403: Derive instances (Applicative, Monad, ...) for structures lifted over functors -------------------------------------+------------------------------------- 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: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): I'm sure some derivations will be ambiguous, but some can be determined uniquely surely. Getting instances for free is such a huge strength of Haskell, it would be great to have better support for it. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13403#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13403: Derive instances (Applicative, Monad, ...) for structures lifted over functors -------------------------------------+------------------------------------- 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: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): This feels extremely //ad hoc// and not nearly formalized enough to where I'd be comfortable with it. One nice thing about `deriving` is that it tends to work with ~90% of the datatypes you'd use regularly, but with this proposal, it feels closer to <50%. I have no idea how you could teach GHC to recognize "product types" in a way that's uniform and comprehensive. What happens when there are more than two fields? What happens when you have arbitrary nestings of types like `data Product f g h a = Product (f (g (f a))) (h (f (g a)))`? What if there are constants like `data Product a = Product Int a`? But I'm even more concerned about what this proposed feature would do on things that //aren't// of the particular form that you've labeled "product types". What happens with: * `newtype Compose f g a = Compose (f (g a))` * `data Proxy a = Proxy` and so on? What would the error messages be like in cases where it wouldn't work? I'm quite skeptical that this could be made workable. -1 from me. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13403#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13403: Derive instances (Applicative, Monad, ...) for structures lifted over functors -------------------------------------+------------------------------------- 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: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Thanks for taking the time to respond to my proposals Replying to [comment:2 RyanGlScott]:
This feels extremely //ad hoc// and not nearly formalized enough to where I'd be comfortable with it.
At least it gets a reaction :) the proposal was but we can go into the direction of [https://hackage.haskell.org/package/base-4.9.1.0/docs/GHC- Generics.html#t:Rep Generic's Rep]
I have no idea how you could teach GHC to recognize "product types"
It's not just for product types, I should have made myself more clear but I didn't want to complicate the proposal. This should work for our entire polynomial arsenal, `Sum`, `Product`, `Identity`, `Const _`, when we get to weirder things like [https://hackage.haskell.org/package/bifunctors-5.4.1/docs/Data-Bifunctor- Biff.html Biff] things start to collide. Maybe it's a matter of picking a comfortable subset.
`data Product f g h a = Product (f (g (f a))) (h (f (g a)))`?
That could be encoded as ↓ and we can still derive a whole host of instances {{{#!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, Contravariant) }}} In any case it could be implemented incrementally.
What if there are constants like `data Product a = Product Int a`?
They could always be rewritten as (I changed `Int` to `String` to get that `Applicative` instance) {{{#!hs newtype Q a = Q (Product (Const String) Identity a) deriving (Functor, Foldable, Traversable, Applicative) }}}
* `newtype Compose f g a = Compose (f (g a))` * `data Proxy a = Proxy`
`Compose` and `Proxy` would likely be primitives in what ever subset of types we support. Are there other discussions about something similar? Or is this the first time this is proposed. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13403#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

At least it incites a reaction :) the proposal was but we can go into
#13403: Derive instances (Applicative, Monad, ...) for structures lifted over functors -------------------------------------+------------------------------------- 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: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Replying to [comment:3 Iceland_jack]: the direction of [https://hackage.haskell.org/package/base-4.9.1.0/docs /GHC-Generics.html#t:Rep Generic's Rep] Funny enough, I was going recommend exactly `GHC.Generics` as a solution to your problem. It gives you the power to exclude awkward subsets of datatypes (e.g., no `Monad` instances for `Compose`-like things), and it requires no changes to GHC. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13403#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13403: Derive instances (Applicative, Monad, ...) for structures lifted over functors -------------------------------------+------------------------------------- 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: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Moreover, it wouldn't take much code at all to set up the machinery needed to do this: {{{#!hs {-# LANGUAGE DeriveFunctor #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE FlexibleContexts #-} module DeriveApplicativeMonad where import GHC.Generics -- Applicative genericPure :: (Generic1 f, Applicative (Rep1 f)) => a -> f a genericPure = to1 . pure genericAp :: (Generic1 f, Applicative (Rep1 f)) => f (a -> b) -> f a -> f b genericAp f x = to1 $ from1 f <*> from1 x -- Monad genericBind :: (Generic1 m, Monad (Rep1 m)) => m a -> (a -> m b) -> m b genericBind m f = to1 $ from1 m >>= from1 . f -- Example data Product f g h a = Product (f (g (f a))) (h (f (g a))) deriving (Functor, Generic1) instance (Applicative f, Applicative g, Applicative h) => Applicative (Product f g h) where pure = genericPure (<*>) = genericAp }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13403#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13403: Derive instances (Applicative, Monad, ...) for structures lifted over functors -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: feature request | 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: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * type: bug => feature request -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13403#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13403: Derive instances (Applicative, Monad, ...) for structures lifted over functors -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: feature request | 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: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Good solution, it won't be possible to derive them unless added as default methods. I am getting feedback on and mulling over an approach different from my initial proposal -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13403#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13403: Derive instances (Applicative, Monad, ...) for structures lifted over functors -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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): * keywords: => deriving -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13403#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC