generic-deriving-1.14.2: Generic programming library for generalised deriving.
LicenseBSD-3-Clause
Maintainergenerics@haskell.org
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe
LanguageHaskell2010

Generics.Deriving.Default

Description

GHC 8.6 introduced the DerivingVia language extension, which means a typeclass instance can be derived from an existing instance for an isomorphic type. Any newtype is isomorphic to the underlying type. By implementing a typeclass once for the newtype, it is possible to derive any typeclass for any type with a Generic instance.

For a number of classes, there are sensible default instantiations. In older GHCs, these can be supplied in the class definition, using the DefaultSignatures extension. However, only one default can be provided! With DerivingVia it is now possible to choose from many default instantiations.

This package contains a number of such classes. This module demonstrates how one might create a family of newtypes (Default, Default1) for which such instances are defined.

One might then use DerivingVia as follows. The implementations of the data types are elided here (they are irrelevant). For most cases, either the deriving clause with the data type definition or the standalone clause will work (for some types it is necessary to supply the context explicitly using the latter form). See the source of this module for the implementations of instances for the Default family of newtypes and the source of the test suite for some types which derive instances via these wrappers.

Synopsis

Kind * (aka Type)

For classes which take an argument of kind Type, use Default. An example of this class from base would be Eq, or Generic.

These examples use GShow and GEq; they are interchangeable.

data MyType = …
 deriving (Generic)
 deriving (GEq) via (Default MyType)

deriving via (Default MyType) instance GShow MyType

Instances may be parameterized by type variables.

data MyType1 a = …
 deriving (Generic)
 deriving (GShow) via (Default (MyType1 a))

deriving via Default (MyType1 a) instance GEq a => GEq (MyType1 a)

These types both require instances for Generic. This is because the implementations of geq and gshowsPrec for Default b have a Generic b constraint, i.e. the type corresponding to b require a Generic instance. For these two types, that means instances for Generic MyType and Generic (MyType1 a) respectively.

It also means the Generic instance is not needed when there is already a generic instance for the type used to derive the relevant instances. For an example, see the documentation of the GShow instance for Default, below.

newtype Default a Source #

This newtype wrapper can be used to derive default instances for classes taking an argument of kind Type.

Constructors

Default 

Fields

Instances

Instances details
(Generic a, GEq' (Rep a)) => GEq (Default a) Source # 
Instance details

Defined in Generics.Deriving.Default

Methods

geq :: Default a -> Default a -> Bool Source #

(Generic a, GEq a, Enum' (Rep a)) => GEnum (Default a) Source #

The Enum class in base is slightly different; it comprises toEnum and fromEnum. Generics.Deriving.Enum provides functions toEnumDefault and fromEnumDefault.

Instance details

Defined in Generics.Deriving.Default

Methods

genum :: [Default a] Source #

(Generic a, GSemigroup' (Rep a)) => GSemigroup (Default a) Source #

Semigroups often have many sensible implementations of <> / gsappend, and therefore no sensible default. Indeed, there is no GSemigroup' instance for representations of sum types.

In other cases, one may wish to use the existing wrapper newtypes in base, such as the following (using First):

newtype FirstSemigroup = FirstSemigroup Bool
  deriving stock (Eq, Show)
  deriving (GSemigroup) via (First Bool)
Instance details

Defined in Generics.Deriving.Default

(Generic a, GMonoid' (Rep a)) => GMonoid (Default a) Source # 
Instance details

Defined in Generics.Deriving.Default

(Generic a, GShow' (Rep a)) => GShow (Default a) Source #

For example, with this type:

newtype TestShow = TestShow Bool
  deriving (GShow) via (Default Bool)

gshow for TestShow would produce the same string as gshow for Bool.

In this example, TestShow requires no Generic instance, as the constraint on gshowsPrec from Default Bool is Generic Bool.

In general, when using a newtype wrapper, the instance can be derived via the wrapped type, as here (via Default Bool rather than Default TestShow).

Instance details

Defined in Generics.Deriving.Default

(Generic a, Uniplate' (Rep a) a, Context' (Rep a) a) => Uniplate (Default a) Source # 
Instance details

Defined in Generics.Deriving.Default

Methods

children :: Default a -> [Default a] Source #

context :: Default a -> [Default a] -> Default a Source #

descend :: (Default a -> Default a) -> Default a -> Default a Source #

descendM :: Monad m => (Default a -> m (Default a)) -> Default a -> m (Default a) Source #

transform :: (Default a -> Default a) -> Default a -> Default a Source #

transformM :: Monad m => (Default a -> m (Default a)) -> Default a -> m (Default a) Source #

Kind * -> * (aka Type -> Type)

For classes which take an argument of kind Type -> Type, use Default1. An example of this class from base would be Eq1, or Generic1.

Unlike for MyType1, there can be no implementation of these classes for MyType :: Type.

data MyType1 a = …
 deriving (Generic1)
 deriving (GFunctor) via (Default1 MyType1)

deriving via (Default1 MyType1) instance GFoldable MyType1

Note that these instances require a Generic1 MyType1 constraint as gmap and gfoldMap have Generic1 a constraints on the implementations for Default1 a.

newtype Default1 f a Source #

This newtype wrapper can be used to derive default instances for classes taking an argument of kind Type -> Type.

Constructors

Default1 

Fields

Instances

Instances details
(Generic1 f, GFunctor' (Rep1 f)) => GFunctor (Default1 f) Source # 
Instance details

Defined in Generics.Deriving.Default

Methods

gmap :: (a -> b) -> Default1 f a -> Default1 f b Source #

(Generic1 t, GFoldable' (Rep1 t)) => GFoldable (Default1 t) Source # 
Instance details

Defined in Generics.Deriving.Default

Methods

gfoldMap :: Monoid m => (a -> m) -> Default1 t a -> m Source #

gfold :: Monoid m => Default1 t m -> m Source #

gfoldr :: (a -> b -> b) -> b -> Default1 t a -> b Source #

gfoldr' :: (a -> b -> b) -> b -> Default1 t a -> b Source #

gfoldl :: (a -> b -> a) -> a -> Default1 t b -> a Source #

gfoldl' :: (a -> b -> a) -> a -> Default1 t b -> a Source #

gfoldr1 :: (a -> a -> a) -> Default1 t a -> a Source #

gfoldl1 :: (a -> a -> a) -> Default1 t a -> a Source #

(Generic1 f, GCopoint' (Rep1 f)) => GCopoint (Default1 f) Source # 
Instance details

Defined in Generics.Deriving.Default

Methods

gcopoint :: Default1 f a -> a Source #

(Generic1 t, GFunctor' (Rep1 t), GFoldable' (Rep1 t), GTraversable' (Rep1 t)) => GTraversable (Default1 t) Source # 
Instance details

Defined in Generics.Deriving.Default

Methods

gtraverse :: Applicative f => (a -> f b) -> Default1 t a -> f (Default1 t b) Source #

gsequenceA :: Applicative f => Default1 t (f a) -> f (Default1 t a) Source #

gmapM :: Monad m => (a -> m b) -> Default1 t a -> m (Default1 t b) Source #

gsequence :: Monad m => Default1 t (m a) -> m (Default1 t a) Source #

Other kinds

These principles extend to classes taking arguments of other kinds.