| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Generic.Data.Internal.Generically
Contents
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
- newtype Generically a = Generically a
- newtype Generically1 (f :: k -> Type) (a :: k) where
- Generically1 :: forall {k} (f :: k -> Type) (a :: k). f a -> Generically1 f a
- newtype FiniteEnumeration a = FiniteEnumeration a
- newtype GenericProduct a = GenericProduct a
Documentation
newtype Generically a #
A datatype whose instances are defined generically, using the
Generic representation. Generically1 is a higher-kinded version
of Generically that uses Generic1.
Generic instances can be derived via using
Generically A-XDerivingVia.
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DerivingVia #-}
import GHC.Generics (Generic)
data V4 a = V4 a a a a
deriving stock Generic
deriving (Semigroup, Monoid)
via Generically (V4 a)
This corresponds to Semigroup and Monoid instances defined by
pointwise lifting:
instance Semigroup a => Semigroup (V4 a) where
(<>) :: V4 a -> V4 a -> V4 a
V4 a1 b1 c1 d1 <> V4 a2 b2 c2 d2 =
V4 (a1 <> a2) (b1 <> b2) (c1 <> c2) (d1 <> d2)
instance Monoid a => Monoid (V4 a) where
mempty :: V4 a
mempty = V4 mempty mempty mempty mempty
Historically this required modifying the type class to include
generic method definitions (-XDefaultSignatures) and deriving it
with the anyclass strategy (-XDeriveAnyClass). Having a /via
type/ like Generically decouples the instance from the type
class.
Since: base-4.17.0.0
Constructors
| Generically a |
Instances
newtype Generically1 (f :: k -> Type) (a :: k) where #
A type whose instances are defined generically, using the
Generic1 representation. Generically1 is a higher-kinded
version of Generically that uses Generic.
Generic instances can be derived for type constructors via
using Generically1 F-XDerivingVia.
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DerivingVia #-}
import GHC.Generics (Generic)
data V4 a = V4 a a a a
deriving stock (Functor, Generic1)
deriving Applicative
via Generically1 V4
This corresponds to Applicative instances defined by pointwise
lifting:
instance Applicative V4 where
pure :: a -> V4 a
pure a = V4 a a a a
liftA2 :: (a -> b -> c) -> (V4 a -> V4 b -> V4 c)
liftA2 (·) (V4 a1 b1 c1 d1) (V4 a2 b2 c2 d2) =
V4 (a1 · a2) (b1 · b2) (c1 · c2) (d1 · d2)
Historically this required modifying the type class to include
generic method definitions (-XDefaultSignatures) and deriving it
with the anyclass strategy (-XDeriveAnyClass). Having a /via
type/ like Generically1 decouples the instance from the type
class.
Since: base-4.17.0.0
Constructors
| Generically1 :: forall {k} (f :: k -> Type) (a :: k). f a -> Generically1 f a |
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) :}
Constructors
| FiniteEnumeration a |
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
>>>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 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.
Constructors
| GenericProduct a |
Instances
| (AssertNoSum Semigroup a, Generic a, Monoid (Rep a ())) => Monoid (GenericProduct a) Source # | |
Defined in Generic.Data.Internal.Generically Methods mempty :: GenericProduct a # mappend :: GenericProduct a -> GenericProduct a -> GenericProduct a # mconcat :: [GenericProduct a] -> GenericProduct a # | |
| (AssertNoSum Semigroup a, Generic a, Semigroup (Rep a ())) => Semigroup (GenericProduct a) Source # | |
Defined in Generic.Data.Internal.Generically Methods (<>) :: GenericProduct a -> GenericProduct a -> GenericProduct a # sconcat :: NonEmpty (GenericProduct a) -> GenericProduct a # stimes :: Integral b => b -> GenericProduct a -> GenericProduct a # | |
| Generic a => Generic (GenericProduct a) Source # | |
Defined in Generic.Data.Internal.Generically Associated Types type Rep (GenericProduct a) :: Type -> Type # Methods from :: GenericProduct a -> Rep (GenericProduct a) x # to :: Rep (GenericProduct a) x -> GenericProduct a # | |
| type Rep (GenericProduct a) Source # | |
Defined in Generic.Data.Internal.Generically | |