Safe Haskell | None |
---|---|
Language | Haskell2010 |
Newtypes with instances implemented using generic combinators.
Warning
This is an internal module: it is not subject to any versioning policy, breaking changes can happen at any time.
If something here seems useful, please report it or create a pull request to export it from an external module.
Synopsis
- newtype Generically a = Generically {
- unGenerically :: a
- newtype FiniteEnumeration a = FiniteEnumeration {
- unFiniteEnumeration :: a
- newtype Generically1 f a = Generically1 {
- unGenerically1 :: f a
- newtype GenericProduct a = GenericProduct {
- unGenericProduct :: a
Documentation
newtype Generically a Source #
Type with instances derived via Generic
.
Examples
Deriving Eq
, Ord
, Show
, Read
>>>
:set -XDerivingVia -XDeriveGeneric
>>>
:{
data T = C Int Bool deriving Generic deriving (Eq, Ord, Show, Read) via (Generically T) :}
Deriving Semigroup
, Monoid
The type must have only one constructor.
>>>
:{
data U = D [Int] (Sum Int) deriving Generic deriving (Semigroup, Monoid) via (Generically U) :}
Deriving Enum
, Bounded
The type must have only nullary constructors.
To lift that restriction, see FiniteEnumeration
.
>>>
:{
data V = X | Y | Z deriving Generic deriving (Eq, Ord, Enum, Bounded) via (Generically V) :}
Generically | |
|
Instances
newtype FiniteEnumeration a Source #
Type with Enum
instance derived via Generic
with FiniteEnum
option.
This allows deriving Enum
for types whose constructors have fields.
Some caution is advised; see details in FiniteEnum
.
Example
>>>
:{
data Booool = Booool Bool Bool deriving Generic deriving (Enum, Bounded) via (FiniteEnumeration Booool) :}
Instances
newtype Generically1 f a Source #
Type with instances derived via Generic1
.
Examples
Deriving Functor
, Applicative
, Alternative
Applicative
can be derived for types with only one
constructor, aka. products.
>>>
:{
data F a = F1 a | F2 (Maybe a) | F3 [Either Bool a] (Int, a) deriving Generic1 deriving Functor via (Generically1 F) :}
>>>
:{
data G a = G a (Maybe a) [a] (IO a) deriving Generic1 deriving (Functor, Applicative) via (Generically1 G) :}
>>>
:{
data G' a = G' (Maybe a) [a] deriving Generic1 deriving (Functor, Applicative, Alternative) via (Generically1 G') :}
Deriving Foldable
>>>
import Generic.Data.Orphans ()
>>>
:{
data H a = H1 a | H2 (Maybe a) deriving Generic1 deriving (Functor, Foldable) via (Generically1 H) :}
Note: we can't use DerivingVia
for Traversable
.
One may implement Traversable
explicitly using gtraverse
.
Deriving Eq1
, Ord1
>>>
:{
data I a = I [a] (Maybe a) deriving Generic1 deriving (Eq1, Ord1) via (Generically1 I) :}
Generically1 | |
|
Instances
newtype GenericProduct a Source #
Product type with generic instances of Semigroup
and Monoid
.
This is similar to Generically
in most cases, but
GenericProduct
also works for types T
with deriving
via
, where GenericProduct
UU
is a generic product type coercible to,
but distinct from T
. In particular, U
may not have an instance of
Semigroup
, which Generically
requires.
Example
>>>
:set -XDeriveGeneric -XDerivingVia
>>>
data Point a = Point a a deriving Generic
>>>
:{
newtype Vector a = Vector (Point a) deriving (Semigroup, Monoid) via GenericProduct (Point (Sum a)) :}
If it were via
instead, then
Generically
(Point (Sum a))Vector
's mappend
(the Monoid
method) would be defined as Point
's
(
(the <>
)Semigroup
method), which might not exist, or might not be
equivalent to Vector
's generic Semigroup
instance, which would be
unlawful.
Instances
Generic a => Generic (GenericProduct a) Source # | |
Defined in Generic.Data.Internal.Generically type Rep (GenericProduct a) :: Type -> Type # from :: GenericProduct a -> Rep (GenericProduct a) x # to :: Rep (GenericProduct a) x -> GenericProduct a # | |
(AssertNoSum Semigroup a, Generic a, Semigroup (Rep a ())) => Semigroup (GenericProduct a) Source # | |
Defined in Generic.Data.Internal.Generically (<>) :: GenericProduct a -> GenericProduct a -> GenericProduct a # sconcat :: NonEmpty (GenericProduct a) -> GenericProduct a # stimes :: Integral b => b -> GenericProduct a -> GenericProduct a # | |
(AssertNoSum Semigroup a, Generic a, Monoid (Rep a ())) => Monoid (GenericProduct a) Source # | |
Defined in Generic.Data.Internal.Generically mempty :: GenericProduct a # mappend :: GenericProduct a -> GenericProduct a -> GenericProduct a # mconcat :: [GenericProduct a] -> GenericProduct a # | |
type Rep (GenericProduct a) Source # | |
Defined in Generic.Data.Internal.Generically |