Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Data.Functor.Classes.Generic
Synopsis
- class Eq1 (f :: Type -> Type) where
- genericLiftEq :: (Generic1 f, GEq1 (Rep1 f)) => (a -> b -> Bool) -> f a -> f b -> Bool
- class Eq1 f => Ord1 (f :: Type -> Type) where
- liftCompare :: (a -> b -> Ordering) -> f a -> f b -> Ordering
- genericLiftCompare :: (Generic1 f, GOrd1 (Rep1 f)) => (a -> b -> Ordering) -> f a -> f b -> Ordering
- class Show1 (f :: Type -> Type) where
- newtype GShow1Options = GShow1Options {}
- defaultGShow1Options :: GShow1Options
- genericLiftShowsPrec :: (Generic1 f, GShow1 (Rep1 f)) => (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS
- genericLiftShowsPrecWithOptions :: (Generic1 f, GShow1 (Rep1 f)) => GShow1Options -> (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS
- newtype Generically f a = Generically {
- unGenerically :: f a
Documentation
class Eq1 (f :: Type -> Type) where #
Lifting of the Eq
class to unary type constructors.
Since: base-4.9.0.0
Methods
liftEq :: (a -> b -> Bool) -> f a -> f b -> Bool #
Lift an equality test through the type constructor.
The function will usually be applied to an equality function, but the more general type ensures that the implementation uses it to compare elements of the first container with elements of the second.
Since: base-4.9.0.0
Instances
Eq1 [] | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Eq1 Maybe | Since: base-4.9.0.0 |
Eq1 Identity | Since: base-4.9.0.0 |
Eq1 Down | Since: base-4.12.0.0 |
Eq1 NonEmpty | Since: base-4.10.0.0 |
Eq a => Eq1 (Either a) | Since: base-4.9.0.0 |
Eq a => Eq1 ((,) a) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Eq1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
(Generic1 f, GEq1 (Rep1 f)) => Eq1 (Generically f) Source # | |
Defined in Data.Functor.Classes.Generic Methods liftEq :: (a -> b -> Bool) -> Generically f a -> Generically f b -> Bool # | |
Eq b => Eq1 (Var b) Source # | |
Eq a => Eq1 (Const a :: Type -> Type) | Since: base-4.9.0.0 |
(Functor f, Eq1 f, Eq b) => Eq1 (Scope b f) Source # | |
genericLiftEq :: (Generic1 f, GEq1 (Rep1 f)) => (a -> b -> Bool) -> f a -> f b -> Bool Source #
A suitable implementation of Eq1’s liftEq for Generic1 types.
class Eq1 f => Ord1 (f :: Type -> Type) where #
Lifting of the Ord
class to unary type constructors.
Since: base-4.9.0.0
Methods
liftCompare :: (a -> b -> Ordering) -> f a -> f b -> Ordering #
Lift a compare
function through the type constructor.
The function will usually be applied to a comparison function, but the more general type ensures that the implementation uses it to compare elements of the first container with elements of the second.
Since: base-4.9.0.0
Instances
Ord1 [] | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes Methods liftCompare :: (a -> b -> Ordering) -> [a] -> [b] -> Ordering # | |
Ord1 Maybe | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Ord1 Identity | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Ord1 Down | Since: base-4.12.0.0 |
Defined in Data.Functor.Classes | |
Ord1 NonEmpty | Since: base-4.10.0.0 |
Defined in Data.Functor.Classes | |
Ord a => Ord1 (Either a) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Ord a => Ord1 ((,) a) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes Methods liftCompare :: (a0 -> b -> Ordering) -> (a, a0) -> (a, b) -> Ordering # | |
Ord1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
(Generic1 f, GEq1 (Rep1 f), GOrd1 (Rep1 f)) => Ord1 (Generically f) Source # | |
Defined in Data.Functor.Classes.Generic Methods liftCompare :: (a -> b -> Ordering) -> Generically f a -> Generically f b -> Ordering # | |
Ord a => Ord1 (Const a :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes |
genericLiftCompare :: (Generic1 f, GOrd1 (Rep1 f)) => (a -> b -> Ordering) -> f a -> f b -> Ordering Source #
A suitable implementation of Ord1’s liftCompare for Generic1 types.
class Show1 (f :: Type -> Type) where #
Lifting of the Show
class to unary type constructors.
Since: base-4.9.0.0
Minimal complete definition
Methods
liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS #
showsPrec
function for an application of the type constructor
based on showsPrec
and showList
functions for the argument type.
Since: base-4.9.0.0
liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [f a] -> ShowS #
Instances
Show1 [] | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Show1 Maybe | Since: base-4.9.0.0 |
Show1 Identity | Since: base-4.9.0.0 |
Show1 Down | Since: base-4.12.0.0 |
Show1 NonEmpty | Since: base-4.10.0.0 |
Show a => Show1 (Either a) | Since: base-4.9.0.0 |
Show a => Show1 ((,) a) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Show1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
(Generic1 f, GShow1 (Rep1 f)) => Show1 (Generically f) Source # | |
Defined in Data.Functor.Classes.Generic Methods liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Generically f a -> ShowS # liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Generically f a] -> ShowS # | |
Show b => Show1 (Var b) Source # | |
Show a => Show1 (Const a :: Type -> Type) | Since: base-4.9.0.0 |
(Functor f, Show1 f, Show b) => Show1 (Scope b f) Source # | |
newtype GShow1Options Source #
Constructors
GShow1Options | |
Fields |
genericLiftShowsPrec :: (Generic1 f, GShow1 (Rep1 f)) => (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS Source #
A suitable implementation of Show1’s liftShowsPrec for Generic1 types.
genericLiftShowsPrecWithOptions :: (Generic1 f, GShow1 (Rep1 f)) => GShow1Options -> (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS Source #
A suitable implementation of Show1’s liftShowsPrec for Generic1 types.
newtype Generically f a Source #
Constructors
Generically | |
Fields
|
Instances
(Generic1 f, GEq1 (Rep1 f)) => Eq1 (Generically f) Source # | |
Defined in Data.Functor.Classes.Generic Methods liftEq :: (a -> b -> Bool) -> Generically f a -> Generically f b -> Bool # | |
(Generic1 f, GEq1 (Rep1 f), GOrd1 (Rep1 f)) => Ord1 (Generically f) Source # | |
Defined in Data.Functor.Classes.Generic Methods liftCompare :: (a -> b -> Ordering) -> Generically f a -> Generically f b -> Ordering # | |
(Generic1 f, GShow1 (Rep1 f)) => Show1 (Generically f) Source # | |
Defined in Data.Functor.Classes.Generic Methods liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Generically f a -> ShowS # liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Generically f a] -> ShowS # |