
#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