generic-data-0.9.2.1: Deriving instances with GHC.Generics and related utilities
Safe HaskellNone
LanguageHaskell2010

Generic.Data.Internal.Generically

Description

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

Documentation

>>> :set -XDerivingVia -XDeriveGeneric
>>> import GHC.Generics (Generic, Generic1)

newtype Generically a Source #

Type with instances derived via Generic.

Examples

Deriving Eq, Ord, Show, Read

Expand
>>> :{
data T = C Int Bool
  deriving Generic
  deriving (Eq, Ord, Show, Read) via (Generically T)
:}

Deriving Semigroup, Monoid

Expand

The type must have only one constructor.

>>> import Data.Monoid (Sum)
>>> :{
data U = D [Int] (Sum Int)
  deriving Generic
  deriving (Semigroup, Monoid) via (Generically U)
:}

Deriving Enum, Bounded

Expand

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)
:}

Constructors

Generically 

Fields

Instances

Instances details
(AssertNoSum Semigroup a, Semigroup a, Generic a, Monoid (Rep a ())) => Monoid (Generically a) Source #

This uses the Semigroup instance of the wrapped type a to define mappend. The purpose of this instance is to derive mempty, while remaining consistent with possibly custom Semigroup instances.

Instance details

Defined in Generic.Data.Internal.Generically

(AssertNoSum Semigroup a, Generic a, Semigroup (Rep a ())) => Semigroup (Generically a) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

(Generic a, GBounded (Rep a)) => Bounded (Generically a) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

(Generic a, GEnum StandardEnum (Rep a)) => Enum (Generically a) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

Generic a => Generic (Generically a) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

Associated Types

type Rep (Generically a) :: Type -> Type Source #

(Generic a, Ord (Rep a ()), GIx (Rep a)) => Ix (Generically a) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

(Generic a, GRead0 (Rep a)) => Read (Generically a) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

(Generic a, GShow0 (Rep a)) => Show (Generically a) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

(Generic a, Eq (Rep a ())) => Eq (Generically a) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

(Generic a, Ord (Rep a ())) => Ord (Generically a) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

type Rep (Generically a) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

type Rep (Generically a) = Rep a

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

Expand
>>> :{
data Booool = Booool Bool Bool
  deriving Generic
  deriving (Enum, Bounded) via (FiniteEnumeration Booool)
:}

Constructors

FiniteEnumeration 

Fields

newtype Generically1 f a Source #

Type with instances derived via Generic1.

Examples

Deriving Functor, Applicative, Alternative

Expand

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)
:}
>>> import Control.Applicative (Alternative)
>>> :{
data G' a = G' (Maybe a) [a]
  deriving Generic1
  deriving (Functor, Applicative, Alternative) via (Generically1 G')
:}

Deriving Foldable

Expand
>>> 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

Expand
>>> import Data.Functor.Classes (Eq1, Ord1)
>>> :{
data I a = I [a] (Maybe a)
  deriving Generic1
  deriving (Eq1, Ord1) via (Generically1 I)
:}

Constructors

Generically1 

Fields

Instances

Instances details
(Generic1 f, GFoldable (Rep1 f)) => Foldable (Generically1 f) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

Methods

fold :: Monoid m => Generically1 f m -> m Source #

foldMap :: Monoid m => (a -> m) -> Generically1 f a -> m Source #

foldMap' :: Monoid m => (a -> m) -> Generically1 f a -> m Source #

foldr :: (a -> b -> b) -> b -> Generically1 f a -> b Source #

foldr' :: (a -> b -> b) -> b -> Generically1 f a -> b Source #

foldl :: (b -> a -> b) -> b -> Generically1 f a -> b Source #

foldl' :: (b -> a -> b) -> b -> Generically1 f a -> b Source #

foldr1 :: (a -> a -> a) -> Generically1 f a -> a Source #

foldl1 :: (a -> a -> a) -> Generically1 f a -> a Source #

toList :: Generically1 f a -> [a] Source #

null :: Generically1 f a -> Bool Source #

length :: Generically1 f a -> Int Source #

elem :: Eq a => a -> Generically1 f a -> Bool Source #

maximum :: Ord a => Generically1 f a -> a Source #

minimum :: Ord a => Generically1 f a -> a Source #

sum :: Num a => Generically1 f a -> a Source #

product :: Num a => Generically1 f a -> a Source #

(Generic1 f, Eq1 (Rep1 f)) => Eq1 (Generically1 f) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

Methods

liftEq :: (a -> b -> Bool) -> Generically1 f a -> Generically1 f b -> Bool Source #

(Generic1 f, Ord1 (Rep1 f)) => Ord1 (Generically1 f) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

Methods

liftCompare :: (a -> b -> Ordering) -> Generically1 f a -> Generically1 f b -> Ordering Source #

(Generic1 f, GRead1 (Rep1 f)) => Read1 (Generically1 f) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

(Generic1 f, GShow1 (Rep1 f)) => Show1 (Generically1 f) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Generically1 f a -> ShowS Source #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Generically1 f a] -> ShowS Source #

(Generic1 f, Functor (Rep1 f), GFoldable (Rep1 f), GTraversable (Rep1 f)) => Traversable (Generically1 f) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Generically1 f a -> f0 (Generically1 f b) Source #

sequenceA :: Applicative f0 => Generically1 f (f0 a) -> f0 (Generically1 f a) Source #

mapM :: Monad m => (a -> m b) -> Generically1 f a -> m (Generically1 f b) Source #

sequence :: Monad m => Generically1 f (m a) -> m (Generically1 f a) Source #

(Generic1 f, Alternative (Rep1 f)) => Alternative (Generically1 f) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

(Generic1 f, Applicative (Rep1 f)) => Applicative (Generically1 f) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

Methods

pure :: a -> Generically1 f a Source #

(<*>) :: Generically1 f (a -> b) -> Generically1 f a -> Generically1 f b Source #

liftA2 :: (a -> b -> c) -> Generically1 f a -> Generically1 f b -> Generically1 f c Source #

(*>) :: Generically1 f a -> Generically1 f b -> Generically1 f b Source #

(<*) :: Generically1 f a -> Generically1 f b -> Generically1 f a Source #

(Generic1 f, Functor (Rep1 f)) => Functor (Generically1 f) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

Methods

fmap :: (a -> b) -> Generically1 f a -> Generically1 f b Source #

(<$) :: a -> Generically1 f b -> Generically1 f a Source #

Generic1 f => Generic1 (Generically1 f :: Type -> Type) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

Associated Types

type Rep1 (Generically1 f) :: k -> Type Source #

Methods

from1 :: forall (a :: k). Generically1 f a -> Rep1 (Generically1 f) a Source #

to1 :: forall (a :: k). Rep1 (Generically1 f) a -> Generically1 f a Source #

Generic (f a) => Generic (Generically1 f a) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

Associated Types

type Rep (Generically1 f a) :: Type -> Type Source #

Methods

from :: Generically1 f a -> Rep (Generically1 f a) x Source #

to :: Rep (Generically1 f a) x -> Generically1 f a Source #

(Generic1 f, GRead1 (Rep1 f), Read a) => Read (Generically1 f a) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

(Generic1 f, GShow1 (Rep1 f), Show a) => Show (Generically1 f a) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

(Generic1 f, Eq1 (Rep1 f), Eq a) => Eq (Generically1 f a) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

(Generic1 f, Ord1 (Rep1 f), Ord a) => Ord (Generically1 f a) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

type Rep1 (Generically1 f :: Type -> Type) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

type Rep1 (Generically1 f :: Type -> Type) = Rep1 f
type Rep (Generically1 f a) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

type Rep (Generically1 f a) = Rep (f a)

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 GenericProduct U, where U 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

Expand
>>> import Data.Monoid (Sum(..))
>>> 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 Generically (Point (Sum a)) instead, then 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.

Constructors

GenericProduct 

Fields