
#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