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
Generic1 f => Generic1 (Generically1 f :: Type -> Type) Source # | This is a hack to implicitly wrap/unwrap in the instances of | ||||
Defined in Generic.Data.Internal.Generically Associated Types
Methods from1 :: Generically1 f a -> Rep1 (Generically1 f) a # to1 :: Rep1 (Generically1 f) a -> Generically1 f a # | |||||
(Generic1 f, Eq1 (Rep1 f)) => Eq1 (Generically1 f) | Since: base-4.17.0.0 | ||||
Defined in Data.Functor.Classes Methods liftEq :: (a -> b -> Bool) -> Generically1 f a -> Generically1 f b -> Bool # | |||||
(Generic1 f, Ord1 (Rep1 f)) => Ord1 (Generically1 f) | Since: base-4.17.0.0 | ||||
Defined in Data.Functor.Classes Methods liftCompare :: (a -> b -> Ordering) -> Generically1 f a -> Generically1 f b -> Ordering # | |||||
(Generic1 f, GRead1 (Rep1 f)) => Read1 (Generically1 f) Source # | |||||
Defined in Generic.Data.Internal.Generically Methods liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Generically1 f a) # liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Generically1 f a] # liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Generically1 f a) # liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Generically1 f a] # | |||||
(Generic1 f, GShow1 (Rep1 f)) => Show1 (Generically1 f) Source # | |||||
Defined in Generic.Data.Internal.Generically Methods liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Generically1 f a -> ShowS # liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Generically1 f a] -> ShowS # | |||||
(Generic1 f, Alternative (Rep1 f)) => Alternative (Generically1 f) | Since: base-4.17.0.0 | ||||
Defined in GHC.Internal.Generics Methods empty :: Generically1 f a # (<|>) :: Generically1 f a -> Generically1 f a -> Generically1 f a # some :: Generically1 f a -> Generically1 f [a] # many :: Generically1 f a -> Generically1 f [a] # | |||||
(Generic1 f, Applicative (Rep1 f)) => Applicative (Generically1 f) | Since: base-4.17.0.0 | ||||
Defined in GHC.Internal.Generics Methods pure :: a -> Generically1 f a # (<*>) :: Generically1 f (a -> b) -> Generically1 f a -> Generically1 f b # liftA2 :: (a -> b -> c) -> Generically1 f a -> Generically1 f b -> Generically1 f c # (*>) :: Generically1 f a -> Generically1 f b -> Generically1 f b # (<*) :: Generically1 f a -> Generically1 f b -> Generically1 f a # | |||||
(Generic1 f, Functor (Rep1 f)) => Functor (Generically1 f) | Since: base-4.17.0.0 | ||||
Defined in GHC.Internal.Generics Methods fmap :: (a -> b) -> Generically1 f a -> Generically1 f b # (<$) :: a -> Generically1 f b -> Generically1 f a # | |||||
(Generic1 f, GFoldable (Rep1 f)) => Foldable (Generically1 f) Source # | |||||
Defined in Generic.Data.Internal.Generically Methods fold :: Monoid m => Generically1 f m -> m # foldMap :: Monoid m => (a -> m) -> Generically1 f a -> m # foldMap' :: Monoid m => (a -> m) -> Generically1 f a -> m # foldr :: (a -> b -> b) -> b -> Generically1 f a -> b # foldr' :: (a -> b -> b) -> b -> Generically1 f a -> b # foldl :: (b -> a -> b) -> b -> Generically1 f a -> b # foldl' :: (b -> a -> b) -> b -> Generically1 f a -> b # foldr1 :: (a -> a -> a) -> Generically1 f a -> a # foldl1 :: (a -> a -> a) -> Generically1 f a -> a # toList :: Generically1 f a -> [a] # null :: Generically1 f a -> Bool # length :: Generically1 f a -> Int # elem :: Eq a => a -> Generically1 f a -> Bool # maximum :: Ord a => Generically1 f a -> a # minimum :: Ord a => Generically1 f a -> a # sum :: Num a => Generically1 f a -> a # product :: Num a => Generically1 f a -> a # | |||||
(Generic1 f, Functor (Rep1 f), GFoldable (Rep1 f), GTraversable (Rep1 f)) => Traversable (Generically1 f) Source # | |||||
Defined in Generic.Data.Internal.Generically Methods traverse :: Applicative f0 => (a -> f0 b) -> Generically1 f a -> f0 (Generically1 f b) # sequenceA :: Applicative f0 => Generically1 f (f0 a) -> f0 (Generically1 f a) # mapM :: Monad m => (a -> m b) -> Generically1 f a -> m (Generically1 f b) # sequence :: Monad m => Generically1 f (m a) -> m (Generically1 f a) # | |||||
Generic (f a) => Generic (Generically1 f a) Source # | This is a hack to implicitly wrap/unwrap in the instances of | ||||
Defined in Generic.Data.Internal.Generically Associated Types
Methods from :: Generically1 f a -> Rep (Generically1 f a) x # to :: Rep (Generically1 f a) x -> Generically1 f a # | |||||
(Generic1 f, GRead1 (Rep1 f), Read a) => Read (Generically1 f a) Source # | |||||
Defined in Generic.Data.Internal.Generically Methods readsPrec :: Int -> ReadS (Generically1 f a) # readList :: ReadS [Generically1 f a] # readPrec :: ReadPrec (Generically1 f a) # readListPrec :: ReadPrec [Generically1 f a] # | |||||
(Generic1 f, GShow1 (Rep1 f), Show a) => Show (Generically1 f a) Source # | |||||
Defined in Generic.Data.Internal.Generically Methods showsPrec :: Int -> Generically1 f a -> ShowS # show :: Generically1 f a -> String # showList :: [Generically1 f a] -> ShowS # | |||||
(Generic1 f, Eq (Rep1 f a)) => Eq (Generically1 f a) | Since: base-4.18.0.0 | ||||
Defined in GHC.Internal.Generics Methods (==) :: Generically1 f a -> Generically1 f a -> Bool # (/=) :: Generically1 f a -> Generically1 f a -> Bool # | |||||
(Generic1 f, Ord (Rep1 f a)) => Ord (Generically1 f a) | Since: base-4.18.0.0 | ||||
Defined in GHC.Internal.Generics Methods compare :: Generically1 f a -> Generically1 f a -> Ordering # (<) :: Generically1 f a -> Generically1 f a -> Bool # (<=) :: Generically1 f a -> Generically1 f a -> Bool # (>) :: Generically1 f a -> Generically1 f a -> Bool # (>=) :: Generically1 f a -> Generically1 f a -> Bool # max :: Generically1 f a -> Generically1 f a -> Generically1 f a # min :: Generically1 f a -> Generically1 f a -> Generically1 f a # | |||||
type Rep1 (Generically1 f :: Type -> Type) Source # | |||||
Defined in Generic.Data.Internal.Generically | |||||
type Rep (Generically1 f a) Source # | |||||
Defined in Generic.Data.Internal.Generically |
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
(Generic a, GBounded (Rep a)) => Bounded (FiniteEnumeration a) Source # | The same instance as | ||||
Defined in Generic.Data.Internal.Generically | |||||
(Generic a, GEnum FiniteEnum (Rep a)) => Enum (FiniteEnumeration a) Source # | |||||
Defined in Generic.Data.Internal.Generically Methods succ :: FiniteEnumeration a -> FiniteEnumeration a # pred :: FiniteEnumeration a -> FiniteEnumeration a # toEnum :: Int -> FiniteEnumeration a # fromEnum :: FiniteEnumeration a -> Int # enumFrom :: FiniteEnumeration a -> [FiniteEnumeration a] # enumFromThen :: FiniteEnumeration a -> FiniteEnumeration a -> [FiniteEnumeration a] # enumFromTo :: FiniteEnumeration a -> FiniteEnumeration a -> [FiniteEnumeration a] # enumFromThenTo :: FiniteEnumeration a -> FiniteEnumeration a -> FiniteEnumeration a -> [FiniteEnumeration a] # | |||||
Generic a => Generic (FiniteEnumeration a) Source # | |||||
Defined in Generic.Data.Internal.Generically Associated Types
Methods from :: FiniteEnumeration a -> Rep (FiniteEnumeration a) x # to :: Rep (FiniteEnumeration a) x -> FiniteEnumeration a # | |||||
type Rep (FiniteEnumeration a) Source # | |||||
Defined in Generic.Data.Internal.Generically |
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
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 |
Orphan instances
Generic1 f => Generic1 (Generically1 f :: Type -> Type) Source # | This is a hack to implicitly wrap/unwrap in the instances of | ||||
Associated Types
Methods from1 :: Generically1 f a -> Rep1 (Generically1 f) a # to1 :: Rep1 (Generically1 f) a -> Generically1 f a # | |||||
(Generic a, GBounded (Rep a)) => Bounded (Generically a) Source # | |||||
(Generic a, GEnum StandardEnum (Rep a)) => Enum (Generically a) Source # | |||||
Methods succ :: Generically a -> Generically a # pred :: Generically a -> Generically a # toEnum :: Int -> Generically a # fromEnum :: Generically a -> Int # enumFrom :: Generically a -> [Generically a] # enumFromThen :: Generically a -> Generically a -> [Generically a] # enumFromTo :: Generically a -> Generically a -> [Generically a] # enumFromThenTo :: Generically a -> Generically a -> Generically a -> [Generically a] # | |||||
Generic a => Generic (Generically a) Source # | This is a hack to implicitly wrap/unwrap in the instances of | ||||
Associated Types
Methods from :: Generically a -> Rep (Generically a) x # to :: Rep (Generically a) x -> Generically a # | |||||
(Generic a, Ord (Rep a ()), GIx (Rep a)) => Ix (Generically a) Source # | |||||
Methods range :: (Generically a, Generically a) -> [Generically a] # index :: (Generically a, Generically a) -> Generically a -> Int # unsafeIndex :: (Generically a, Generically a) -> Generically a -> Int # inRange :: (Generically a, Generically a) -> Generically a -> Bool # rangeSize :: (Generically a, Generically a) -> Int # unsafeRangeSize :: (Generically a, Generically a) -> Int # | |||||
(Generic a, GRead0 (Rep a)) => Read (Generically a) Source # | |||||
Methods readsPrec :: Int -> ReadS (Generically a) # readList :: ReadS [Generically a] # readPrec :: ReadPrec (Generically a) # readListPrec :: ReadPrec [Generically a] # | |||||
(Generic a, GShow0 (Rep a)) => Show (Generically a) Source # | |||||
Methods showsPrec :: Int -> Generically a -> ShowS # show :: Generically a -> String # showList :: [Generically a] -> ShowS # | |||||
(Generic a, Eq (Rep a ())) => Eq (Generically a) Source # | |||||
Methods (==) :: Generically a -> Generically a -> Bool # (/=) :: Generically a -> Generically a -> Bool # | |||||
(Generic a, Ord (Rep a ())) => Ord (Generically a) Source # | |||||
Methods compare :: Generically a -> Generically a -> Ordering # (<) :: Generically a -> Generically a -> Bool # (<=) :: Generically a -> Generically a -> Bool # (>) :: Generically a -> Generically a -> Bool # (>=) :: Generically a -> Generically a -> Bool # max :: Generically a -> Generically a -> Generically a # min :: Generically a -> Generically a -> Generically a # | |||||
(Generic1 f, GRead1 (Rep1 f)) => Read1 (Generically1 f) Source # | |||||
Methods liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Generically1 f a) # liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Generically1 f a] # liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Generically1 f a) # liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Generically1 f a] # | |||||
(Generic1 f, GShow1 (Rep1 f)) => Show1 (Generically1 f) Source # | |||||
Methods liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Generically1 f a -> ShowS # liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Generically1 f a] -> ShowS # | |||||
(Generic1 f, GFoldable (Rep1 f)) => Foldable (Generically1 f) Source # | |||||
Methods fold :: Monoid m => Generically1 f m -> m # foldMap :: Monoid m => (a -> m) -> Generically1 f a -> m # foldMap' :: Monoid m => (a -> m) -> Generically1 f a -> m # foldr :: (a -> b -> b) -> b -> Generically1 f a -> b # foldr' :: (a -> b -> b) -> b -> Generically1 f a -> b # foldl :: (b -> a -> b) -> b -> Generically1 f a -> b # foldl' :: (b -> a -> b) -> b -> Generically1 f a -> b # foldr1 :: (a -> a -> a) -> Generically1 f a -> a # foldl1 :: (a -> a -> a) -> Generically1 f a -> a # toList :: Generically1 f a -> [a] # null :: Generically1 f a -> Bool # length :: Generically1 f a -> Int # elem :: Eq a => a -> Generically1 f a -> Bool # maximum :: Ord a => Generically1 f a -> a # minimum :: Ord a => Generically1 f a -> a # sum :: Num a => Generically1 f a -> a # product :: Num a => Generically1 f a -> a # | |||||
(Generic1 f, Functor (Rep1 f), GFoldable (Rep1 f), GTraversable (Rep1 f)) => Traversable (Generically1 f) Source # | |||||
Methods traverse :: Applicative f0 => (a -> f0 b) -> Generically1 f a -> f0 (Generically1 f b) # sequenceA :: Applicative f0 => Generically1 f (f0 a) -> f0 (Generically1 f a) # mapM :: Monad m => (a -> m b) -> Generically1 f a -> m (Generically1 f b) # sequence :: Monad m => Generically1 f (m a) -> m (Generically1 f a) # | |||||
Generic (f a) => Generic (Generically1 f a) Source # | This is a hack to implicitly wrap/unwrap in the instances of | ||||
Associated Types
Methods from :: Generically1 f a -> Rep (Generically1 f a) x # to :: Rep (Generically1 f a) x -> Generically1 f a # | |||||
(Generic1 f, GRead1 (Rep1 f), Read a) => Read (Generically1 f a) Source # | |||||
Methods readsPrec :: Int -> ReadS (Generically1 f a) # readList :: ReadS [Generically1 f a] # readPrec :: ReadPrec (Generically1 f a) # readListPrec :: ReadPrec [Generically1 f a] # | |||||
(Generic1 f, GShow1 (Rep1 f), Show a) => Show (Generically1 f a) Source # | |||||
Methods showsPrec :: Int -> Generically1 f a -> ShowS # show :: Generically1 f a -> String # showList :: [Generically1 f a] -> ShowS # |