bound-simple-0.2.0.0: A lightweight implementation of 'bound'
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Functor.Classes.Generic

Synopsis

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

Instances details
Eq1 []

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> [a] -> [b] -> Bool #

Eq1 Maybe

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> Maybe a -> Maybe b -> Bool #

Eq1 Identity

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> Identity a -> Identity b -> Bool #

Eq1 Down

Since: base-4.12.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> Down a -> Down b -> Bool #

Eq1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> NonEmpty a -> NonEmpty b -> Bool #

Eq a => Eq1 (Either a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a0 -> b -> Bool) -> Either a a0 -> Either a b -> Bool #

Eq a => Eq1 ((,) a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a0 -> b -> Bool) -> (a, a0) -> (a, b) -> Bool #

Eq1 (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> Proxy a -> Proxy b -> Bool #

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

Defined in Data.Functor.Classes.Generic

Methods

liftEq :: (a -> b -> Bool) -> Generically f a -> Generically f b -> Bool #

Eq b => Eq1 (Var b) Source # 
Instance details

Defined in Bound.Simple

Methods

liftEq :: (a -> b0 -> Bool) -> Var b a -> Var b b0 -> Bool #

Eq a => Eq1 (Const a :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a0 -> b -> Bool) -> Const a a0 -> Const a b -> Bool #

(Functor f, Eq1 f, Eq b) => Eq1 (Scope b f) Source # 
Instance details

Defined in Bound.Simple

Methods

liftEq :: (a -> b0 -> Bool) -> Scope b f a -> Scope b f b0 -> Bool #

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

Instances details
Ord1 []

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a -> b -> Ordering) -> [a] -> [b] -> Ordering #

Ord1 Maybe

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a -> b -> Ordering) -> Maybe a -> Maybe b -> Ordering #

Ord1 Identity

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a -> b -> Ordering) -> Identity a -> Identity b -> Ordering #

Ord1 Down

Since: base-4.12.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a -> b -> Ordering) -> Down a -> Down b -> Ordering #

Ord1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a -> b -> Ordering) -> NonEmpty a -> NonEmpty b -> Ordering #

Ord a => Ord1 (Either a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a0 -> b -> Ordering) -> Either a a0 -> Either a b -> Ordering #

Ord a => Ord1 ((,) a)

Since: base-4.9.0.0

Instance details

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

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a -> b -> Ordering) -> Proxy a -> Proxy b -> Ordering #

(Generic1 f, GEq1 (Rep1 f), GOrd1 (Rep1 f)) => Ord1 (Generically f) Source # 
Instance details

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

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a0 -> b -> Ordering) -> Const a a0 -> Const a b -> Ordering #

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

liftShowsPrec

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 #

showList function for an application of the type constructor based on showsPrec and showList functions for the argument type. The default implementation using standard list syntax is correct for most types.

Since: base-4.9.0.0

Instances

Instances details
Show1 []

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

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

Show1 Maybe

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Maybe a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Maybe a] -> ShowS #

Show1 Identity

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Identity a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Identity a] -> ShowS #

Show1 Down

Since: base-4.12.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Down a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Down a] -> ShowS #

Show1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> NonEmpty a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [NonEmpty a] -> ShowS #

Show a => Show1 (Either a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> Either a a0 -> ShowS #

liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [Either a a0] -> ShowS #

Show a => Show1 ((,) a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> (a, a0) -> ShowS #

liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [(a, a0)] -> ShowS #

Show1 (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Proxy a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Proxy a] -> ShowS #

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

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 # 
Instance details

Defined in Bound.Simple

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Var b a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Var b a] -> ShowS #

Show a => Show1 (Const a :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> Const a a0 -> ShowS #

liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [Const a a0] -> ShowS #

(Functor f, Show1 f, Show b) => Show1 (Scope b f) Source # 
Instance details

Defined in Bound.Simple

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Scope b f a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Scope b f a] -> ShowS #

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 #

Used with the DerivingVia extension to provide fast derivations for Eq1, Show1, and Ord1.

Constructors

Generically 

Fields

Instances

Instances details
(Generic1 f, GEq1 (Rep1 f)) => Eq1 (Generically f) Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

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 #