Safe Haskell | None |
---|---|
Language | Haskell2010 |
Derive instances without spelling out "deriving".
Usage
Step 1: add this pragma at the top of the file to load the plugin:
{-# OPTIONS_GHC -fplugin=Driving.Classes #-}
Step 2: enable DerivingStrategies
and other relevant extensions as needed
(DerivingVia
, GeneralizedNewtypeDeriving
, DeriveAnyClass
):
{-# LANGUAGE DerivingStrategies #-}
Step 3: add an ANN
pragma after imports to configure the classes to auto-derive:
{-# ANN module (Driving :: Driving '[ <LIST OF OPTIONS> ]) #-}
Example
This automatically declares instances of Eq
, Ord
, Show
for T
, U
, V
,
and disables auto-deriving for MyEndo
.
{-# ANN module (Driving :: Driving '[ Stock '(Eq, Ord, Show) , NoDriving '(Eq MyEndo, Ord MyEndo, Show MyEndo) ]) #-} data T = C1 | C2 data U = D1 | D2 data V = E1 | E2 newtype MyEndo a = MyEndo (a -> a)
Available options:
See more examples below.
Options
data Driving :: k -> Type where Source #
Type constructor for configuring the plugin in a source annotation.
Argument: list of types using the constructors below.
Example
{-# ANN module (Driving ::Driving
'[Stock
'(Eq, Ord),Newtype
Num ]) #-}
Instances
(Typeable a, Typeable k) => Data (Driving a) Source # | |
Defined in Driving.Classes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Driving a -> c (Driving a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Driving a) # toConstr :: Driving a -> Constr # dataTypeOf :: Driving a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Driving a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Driving a)) # gmapT :: (forall b. Data b => b -> b) -> Driving a -> Driving a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Driving a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Driving a -> r # gmapQ :: (forall d. Data d => d -> u) -> Driving a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Driving a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Driving a -> m (Driving a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Driving a -> m (Driving a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Driving a -> m (Driving a) # |
data Newtype :: k -> Type Source #
Auto-derive classes using the newtype
deriving strategy.
Enable the extension GeneralizedNewtypeDeriving
to use this.
Argument: a class (of kind k -> Constraint
for some k
), or a tuple of classes.
Examples
{-# ANN module (Driving ::Driving
'[Newtype
Num ]) #-} {-# ANN module (Driving ::Driving
'[Newtype
'(Semigroup, Monoid)]) #-}
data Anyclass :: k -> Type Source #
Auto-derive classes using the anyclass
deriving strategy.
Enable the extension DeriveAnyClass
to use this.
Argument: a class (of kind k -> Constraint
for some k
), or a tuple of classes.
Examples
{-# ANN module (Driving ::Driving
'[Anyclass
Binary ]) #-} {-# ANN module (Driving ::Driving
'[Anyclass
'(ToJSON, FromJSON) ]) #-} -- Classes from the packages binary and aeson
data Via :: k -> l -> Type Source #
Auto-derive classes using the via
deriving strategy, for a given via-type.
Enable the extension DerivingVia
to use this.
Arguments:
- a class (of kind
k -> Constraint
for somek
), or a tuple of classes; - a type.
Examples
{-# ANN module (Driving ::Driving
'[ Num `Via
` Int ]) #-} {-# ANN module (Driving ::Driving
'[ '(Eq, Ord) `Via
` Int ]) #-}
data ViaF :: k -> l -> Type Source #
Auto-derive classes using the via
deriving strategy, where the via-type
is an application of a given type constructor to each newly declared type.
Enable the extension DerivingVia
to use this.
Arguments:
- a class (of kind
k -> Constraint
for somek
), or a tuple of classes; - a type constructor.
Examples
{-# ANN module (Driving ::Driving
'[ '(Functor, Applicative) `ViaF
` WrappedMonad ]) #-} {-# ANN module (Driving ::Driving
'[ '(Semigroup, Monoid) `ViaF
` Generically ]) #-} -- Generically from the package generic-data