Data.Functor.Classes (original) (raw)

Description

Liftings of the Prelude classes [Eq](Data-Eq.html#t:Eq "Data.Eq"), [Ord](Data-Ord.html#t:Ord "Data.Ord"), [Read](Prelude.html#t:Read "Prelude") and [Show](Prelude.html#t:Show "Prelude") to unary and binary type constructors.

These classes are needed to express the constraints on arguments of transformers in portable Haskell. Thus for a new transformer T, one might write instances like

instance (Eq1 f) => Eq1 (T f) where ... instance (Ord1 f) => Ord1 (T f) where ... instance (Read1 f) => Read1 (T f) where ... instance (Show1 f) => Show1 (T f) where ...

If these instances can be defined, defining instances of the base classes is mechanical:

instance (Eq1 f, Eq a) => Eq (T f a) where (==) = eq1 instance (Ord1 f, Ord a) => Ord (T f a) where compare = compare1 instance (Read1 f, Read a) => Read (T f a) where readPrec = readPrec1 readListPrec = readListPrecDefault instance (Show1 f, Show a) => Show (T f a) where showsPrec = showsPrec1

Since: base-4.9.0.0

Liftings of Prelude classesFor unary constructors

class (forall a. Eq a => Eq (f a)) => Eq1 (f :: Type -> Type) where Source #

Lifting of the [Eq](Data-Eq.html#t:Eq "Data.Eq") class to unary type constructors.

Any instance should be subject to the following law that canonicity is preserved:

liftEq (==) = (==)

This class therefore represents the generalization of [Eq](Data-Eq.html#t:Eq "Data.Eq") by decomposing its main method into a canonical lifting on a canonical inner method, so that the lifting can be reused for other arguments than the canonical one.

Since: base-4.9.0.0

Minimal complete definition

Nothing

Methods

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

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 Complex Source # >>> eq1 (1 :+ 2) (1 :+ 2) True >>> eq1 (1 :+ 2) (1 :+ 3) False Since: base-4.16.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftEq :: (a -> b -> Bool) -> Complex a -> Complex b -> Bool Source #
Eq1 NonEmpty Source # Since: base-4.10.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftEq :: (a -> b -> Bool) -> NonEmpty a -> NonEmpty b -> Bool Source #
Eq1 Identity Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftEq :: (a -> b -> Bool) -> Identity a -> Identity b -> Bool Source #
Eq1 Down Source # Since: base-4.12.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftEq :: (a -> b -> Bool) -> Down a -> Down b -> Bool Source #
Eq1 Par1 Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftEq :: (a -> b -> Bool) -> Par1 a -> Par1 b -> Bool Source #
Eq1 Maybe Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftEq :: (a -> b -> Bool) -> Maybe a -> Maybe b -> Bool Source #
Eq1 Solo Source # Since: base-4.15
Instance detailsDefined in Data.Functor.Classes MethodsliftEq :: (a -> b -> Bool) -> Solo a -> Solo b -> Bool Source #
Eq1 [] Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftEq :: (a -> b -> Bool) -> [a] -> [b] -> Bool Source #
Eq a => Eq1 (Either a) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftEq :: (a0 -> b -> Bool) -> Either a a0 -> Either a b -> Bool Source #
Eq1 (Proxy :: Type -> Type) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftEq :: (a -> b -> Bool) -> Proxy a -> Proxy b -> Bool Source #
Eq1 (U1 :: Type -> Type) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftEq :: (a -> b -> Bool) -> U1 a -> U1 b -> Bool Source #
Eq1 (UAddr :: Type -> Type) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftEq :: (a -> b -> Bool) -> UAddr a -> UAddr b -> Bool Source #
Eq1 (UChar :: Type -> Type) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftEq :: (a -> b -> Bool) -> UChar a -> UChar b -> Bool Source #
Eq1 (UDouble :: Type -> Type) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftEq :: (a -> b -> Bool) -> UDouble a -> UDouble b -> Bool Source #
Eq1 (UFloat :: Type -> Type) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftEq :: (a -> b -> Bool) -> UFloat a -> UFloat b -> Bool Source #
Eq1 (UInt :: Type -> Type) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftEq :: (a -> b -> Bool) -> UInt a -> UInt b -> Bool Source #
Eq1 (UWord :: Type -> Type) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftEq :: (a -> b -> Bool) -> UWord a -> UWord b -> Bool Source #
Eq1 (V1 :: Type -> Type) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftEq :: (a -> b -> Bool) -> V1 a -> V1 b -> Bool Source #
Eq a => Eq1 ((,) a) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftEq :: (a0 -> b -> Bool) -> (a, a0) -> (a, b) -> Bool Source #
Eq a => Eq1 (Const a :: Type -> Type) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftEq :: (a0 -> b -> Bool) -> Const a a0 -> Const a b -> Bool Source #
(Generic1 f, Eq1 (Rep1 f)) => Eq1 (Generically1 f) Source # Since: base-4.17.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftEq :: (a -> b -> Bool) -> Generically1 f a -> Generically1 f b -> Bool Source #
Eq1 f => Eq1 (Rec1 f) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftEq :: (a -> b -> Bool) -> Rec1 f a -> Rec1 f b -> Bool Source #
(Eq a, Eq b) => Eq1 ((,,) a b) Source # Since: base-4.16.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftEq :: (a0 -> b0 -> Bool) -> (a, b, a0) -> (a, b, b0) -> Bool Source #
(Eq1 f, Eq1 g) => Eq1 (Product f g) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Product MethodsliftEq :: (a -> b -> Bool) -> Product f g a -> Product f g b -> Bool Source #
(Eq1 f, Eq1 g) => Eq1 (Sum f g) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Sum MethodsliftEq :: (a -> b -> Bool) -> Sum f g a -> Sum f g b -> Bool Source #
(Eq1 f, Eq1 g) => Eq1 (f :*: g) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftEq :: (a -> b -> Bool) -> (f :*: g) a -> (f :*: g) b -> Bool Source #
(Eq1 f, Eq1 g) => Eq1 (f :+: g) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftEq :: (a -> b -> Bool) -> (f :+: g) a -> (f :+: g) b -> Bool Source #
Eq c => Eq1 (K1 i c :: Type -> Type) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftEq :: (a -> b -> Bool) -> K1 i c a -> K1 i c b -> Bool Source #
(Eq a, Eq b, Eq c) => Eq1 ((,,,) a b c) Source # Since: base-4.16.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftEq :: (a0 -> b0 -> Bool) -> (a, b, c, a0) -> (a, b, c, b0) -> Bool Source #
(Eq1 f, Eq1 g) => Eq1 (Compose f g) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Compose MethodsliftEq :: (a -> b -> Bool) -> Compose f g a -> Compose f g b -> Bool Source #
(Eq1 f, Eq1 g) => Eq1 (f :.: g) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftEq :: (a -> b -> Bool) -> (f :.: g) a -> (f :.: g) b -> Bool Source #
Eq1 f => Eq1 (M1 i c f) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftEq :: (a -> b -> Bool) -> M1 i c f a -> M1 i c f b -> Bool Source #

eq1 :: (Eq1 f, Eq a) => f a -> f a -> Bool Source #

Lift the standard (`[==](Data-Eq.html#v:-61--61- "Data.Eq")`) function through the type constructor.

Since: base-4.9.0.0

class (Eq1 f, forall a. Ord a => Ord (f a)) => Ord1 (f :: Type -> Type) where Source #

Lifting of the [Ord](Data-Ord.html#t:Ord "Data.Ord") class to unary type constructors.

Any instance should be subject to the following law that canonicity is preserved:

liftCompare compare = [compare](Data-Ord.html#v:compare "Data.Ord")

This class therefore represents the generalization of [Ord](Data-Ord.html#t:Ord "Data.Ord") by decomposing its main method into a canonical lifting on a canonical inner method, so that the lifting can be reused for other arguments than the canonical one.

Since: base-4.9.0.0

Minimal complete definition

Nothing

Methods

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

Lift a [compare](Data-Ord.html#v:compare "Data.Ord") 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 NonEmpty Source # Since: base-4.10.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftCompare :: (a -> b -> Ordering) -> NonEmpty a -> NonEmpty b -> Ordering Source #
Ord1 Identity Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftCompare :: (a -> b -> Ordering) -> Identity a -> Identity b -> Ordering Source #
Ord1 Down Source # Since: base-4.12.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftCompare :: (a -> b -> Ordering) -> Down a -> Down b -> Ordering Source #
Ord1 Par1 Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftCompare :: (a -> b -> Ordering) -> Par1 a -> Par1 b -> Ordering Source #
Ord1 Maybe Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftCompare :: (a -> b -> Ordering) -> Maybe a -> Maybe b -> Ordering Source #
Ord1 Solo Source # Since: base-4.15
Instance detailsDefined in Data.Functor.Classes MethodsliftCompare :: (a -> b -> Ordering) -> Solo a -> Solo b -> Ordering Source #
Ord1 [] Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftCompare :: (a -> b -> Ordering) -> [a] -> [b] -> Ordering Source #
Ord a => Ord1 (Either a) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftCompare :: (a0 -> b -> Ordering) -> Either a a0 -> Either a b -> Ordering Source #
Ord1 (Proxy :: Type -> Type) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftCompare :: (a -> b -> Ordering) -> Proxy a -> Proxy b -> Ordering Source #
Ord1 (U1 :: Type -> Type) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftCompare :: (a -> b -> Ordering) -> U1 a -> U1 b -> Ordering Source #
Ord1 (UAddr :: Type -> Type) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftCompare :: (a -> b -> Ordering) -> UAddr a -> UAddr b -> Ordering Source #
Ord1 (UChar :: Type -> Type) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftCompare :: (a -> b -> Ordering) -> UChar a -> UChar b -> Ordering Source #
Ord1 (UDouble :: Type -> Type) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftCompare :: (a -> b -> Ordering) -> UDouble a -> UDouble b -> Ordering Source #
Ord1 (UFloat :: Type -> Type) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftCompare :: (a -> b -> Ordering) -> UFloat a -> UFloat b -> Ordering Source #
Ord1 (UInt :: Type -> Type) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftCompare :: (a -> b -> Ordering) -> UInt a -> UInt b -> Ordering Source #
Ord1 (UWord :: Type -> Type) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftCompare :: (a -> b -> Ordering) -> UWord a -> UWord b -> Ordering Source #
Ord1 (V1 :: Type -> Type) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftCompare :: (a -> b -> Ordering) -> V1 a -> V1 b -> Ordering Source #
Ord a => Ord1 ((,) a) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftCompare :: (a0 -> b -> Ordering) -> (a, a0) -> (a, b) -> Ordering Source #
Ord a => Ord1 (Const a :: Type -> Type) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftCompare :: (a0 -> b -> Ordering) -> Const a a0 -> Const a b -> Ordering Source #
(Generic1 f, Ord1 (Rep1 f)) => Ord1 (Generically1 f) Source # Since: base-4.17.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftCompare :: (a -> b -> Ordering) -> Generically1 f a -> Generically1 f b -> Ordering Source #
Ord1 f => Ord1 (Rec1 f) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftCompare :: (a -> b -> Ordering) -> Rec1 f a -> Rec1 f b -> Ordering Source #
(Ord a, Ord b) => Ord1 ((,,) a b) Source # Since: base-4.16.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftCompare :: (a0 -> b0 -> Ordering) -> (a, b, a0) -> (a, b, b0) -> Ordering Source #
(Ord1 f, Ord1 g) => Ord1 (Product f g) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Product MethodsliftCompare :: (a -> b -> Ordering) -> Product f g a -> Product f g b -> Ordering Source #
(Ord1 f, Ord1 g) => Ord1 (Sum f g) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Sum MethodsliftCompare :: (a -> b -> Ordering) -> Sum f g a -> Sum f g b -> Ordering Source #
(Ord1 f, Ord1 g) => Ord1 (f :*: g) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftCompare :: (a -> b -> Ordering) -> (f :*: g) a -> (f :*: g) b -> Ordering Source #
(Ord1 f, Ord1 g) => Ord1 (f :+: g) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftCompare :: (a -> b -> Ordering) -> (f :+: g) a -> (f :+: g) b -> Ordering Source #
Ord c => Ord1 (K1 i c :: Type -> Type) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftCompare :: (a -> b -> Ordering) -> K1 i c a -> K1 i c b -> Ordering Source #
(Ord a, Ord b, Ord c) => Ord1 ((,,,) a b c) Source # Since: base-4.16.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftCompare :: (a0 -> b0 -> Ordering) -> (a, b, c, a0) -> (a, b, c, b0) -> Ordering Source #
(Ord1 f, Ord1 g) => Ord1 (Compose f g) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Compose MethodsliftCompare :: (a -> b -> Ordering) -> Compose f g a -> Compose f g b -> Ordering Source #
(Ord1 f, Ord1 g) => Ord1 (f :.: g) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftCompare :: (a -> b -> Ordering) -> (f :.: g) a -> (f :.: g) b -> Ordering Source #
Ord1 f => Ord1 (M1 i c f) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftCompare :: (a -> b -> Ordering) -> M1 i c f a -> M1 i c f b -> Ordering Source #

class (forall a. Read a => Read (f a)) => Read1 (f :: Type -> Type) where Source #

Lifting of the [Read](Prelude.html#t:Read "Prelude") class to unary type constructors.

Any instance should be subject to the following laws that canonicity is preserved:

liftReadsPrec readsPrec readList = [readsPrec](Prelude.html#v:readsPrec "Prelude")

liftReadList readsPrec readList = [readList](Prelude.html#v:readList "Prelude")

liftReadPrec readPrec readListPrec = [readPrec](Text-Read.html#v:readPrec "Text.Read")

liftReadListPrec readPrec readListPrec = [readListPrec](Text-Read.html#v:readListPrec "Text.Read")

This class therefore represents the generalization of [Read](Prelude.html#t:Read "Prelude") by decomposing it's methods into a canonical lifting on a canonical inner method, so that the lifting can be reused for other arguments than the canonical one.

Both [liftReadsPrec](Data-Functor-Classes.html#v:liftReadsPrec "Data.Functor.Classes") and [liftReadPrec](Data-Functor-Classes.html#v:liftReadPrec "Data.Functor.Classes") exist to match the interface provided in the [Read](Prelude.html#t:Read "Prelude") type class, but it is recommended to implement[Read1](Data-Functor-Classes.html#t:Read1 "Data.Functor.Classes") instances using [liftReadPrec](Data-Functor-Classes.html#v:liftReadPrec "Data.Functor.Classes") as opposed to [liftReadsPrec](Data-Functor-Classes.html#v:liftReadsPrec "Data.Functor.Classes"), since the former is more efficient than the latter. For example:

instance [Read1](Data-Functor-Classes.html#t:Read1 "Data.Functor.Classes") T where [liftReadPrec](Data-Functor-Classes.html#v:liftReadPrec "Data.Functor.Classes") = ... [liftReadListPrec](Data-Functor-Classes.html#v:liftReadListPrec "Data.Functor.Classes") = [liftReadListPrecDefault](Data-Functor-Classes.html#v:liftReadListPrecDefault "Data.Functor.Classes")

For more information, refer to the documentation for the [Read](Prelude.html#t:Read "Prelude") class.

Since: base-4.9.0.0

Instances

Instances details

Read1 Complex Source # >>> readPrec_to_S readPrec1 0 "(2 % 3) :+ (3 % 4)" :: [(Complex Rational, String)] [(2 % 3 :+ 3 % 4,"")] Since: base-4.16.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Complex a) Source #liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Complex a] Source #liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Complex a) Source #liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Complex a] Source #
Read1 NonEmpty Source # Since: base-4.10.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (NonEmpty a) Source #liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [NonEmpty a] Source #liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (NonEmpty a) Source #liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [NonEmpty a] Source #
Read1 Identity Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Identity a) Source #liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Identity a] Source #liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Identity a) Source #liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Identity a] Source #
Read1 Down Source # Since: base-4.12.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Down a) Source #liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Down a] Source #liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Down a) Source #liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Down a] Source #
Read1 Par1 Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Par1 a) Source #liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Par1 a] Source #liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Par1 a) Source #liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Par1 a] Source #
Read1 Maybe Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Maybe a) Source #liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Maybe a] Source #liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Maybe a) Source #liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Maybe a] Source #
Read1 Solo Source # Since: base-4.15
Instance detailsDefined in Data.Functor.Classes MethodsliftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Solo a) Source #liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Solo a] Source #liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Solo a) Source #liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Solo a] Source #
Read1 [] Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS [a] Source #liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [[a]] Source #liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [a] Source #liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [[a]] Source #
Read a => Read1 (Either a) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (Either a a0) Source #liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [Either a a0] Source #liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (Either a a0) Source #liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [Either a a0] Source #
Read1 (Proxy :: Type -> Type) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Proxy a) Source #liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Proxy a] Source #liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Proxy a) Source #liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Proxy a] Source #
Read1 (U1 :: Type -> Type) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (U1 a) Source #liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [U1 a] Source #liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (U1 a) Source #liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [U1 a] Source #
Read1 (V1 :: Type -> Type) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (V1 a) Source #liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [V1 a] Source #liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (V1 a) Source #liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [V1 a] Source #
Read a => Read1 ((,) a) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (a, a0) Source #liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [(a, a0)] Source #liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (a, a0) Source #liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [(a, a0)] Source #
Read a => Read1 (Const a :: Type -> Type) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (Const a a0) Source #liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [Const a a0] Source #liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (Const a a0) Source #liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [Const a a0] Source #
Read1 f => Read1 (Rec1 f) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Rec1 f a) Source #liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Rec1 f a] Source #liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Rec1 f a) Source #liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Rec1 f a] Source #
(Read a, Read b) => Read1 ((,,) a b) Source # Since: base-4.16.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (a, b, a0) Source #liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [(a, b, a0)] Source #liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (a, b, a0) Source #liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [(a, b, a0)] Source #
(Read1 f, Read1 g) => Read1 (Product f g) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Product MethodsliftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Product f g a) Source #liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Product f g a] Source #liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Product f g a) Source #liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Product f g a] Source #
(Read1 f, Read1 g) => Read1 (Sum f g) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Sum MethodsliftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Sum f g a) Source #liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Sum f g a] Source #liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Sum f g a) Source #liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Sum f g a] Source #
(Read1 f, Read1 g) => Read1 (f :*: g) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS ((f :*: g) a) Source #liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [(f :*: g) a] Source #liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec ((f :*: g) a) Source #liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [(f :*: g) a] Source #
(Read1 f, Read1 g) => Read1 (f :+: g) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS ((f :+: g) a) Source #liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [(f :+: g) a] Source #liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec ((f :+: g) a) Source #liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [(f :+: g) a] Source #
Read c => Read1 (K1 i c :: Type -> Type) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (K1 i c a) Source #liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [K1 i c a] Source #liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (K1 i c a) Source #liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [K1 i c a] Source #
(Read a, Read b, Read c) => Read1 ((,,,) a b c) Source # Since: base-4.16.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (a, b, c, a0) Source #liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [(a, b, c, a0)] Source #liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (a, b, c, a0) Source #liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [(a, b, c, a0)] Source #
(Read1 f, Read1 g) => Read1 (Compose f g) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Compose MethodsliftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Compose f g a) Source #liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Compose f g a] Source #liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Compose f g a) Source #liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Compose f g a] Source #
(Read1 f, Read1 g) => Read1 (f :.: g) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS ((f :.: g) a) Source #liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [(f :.: g) a] Source #liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec ((f :.: g) a) Source #liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [(f :.: g) a] Source #
Read1 f => Read1 (M1 i c f) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (M1 i c f a) Source #liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [M1 i c f a] Source #liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (M1 i c f a) Source #liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [M1 i c f a] Source #

class (forall a. Show a => Show (f a)) => Show1 (f :: Type -> Type) where Source #

Lifting of the [Show](Prelude.html#t:Show "Prelude") class to unary type constructors.

Any instance should be subject to the following laws that canonicity is preserved:

liftShowsPrec showsPrec showList = [showsPrec](Prelude.html#v:showsPrec "Prelude")

liftShowList showsPrec showList = [showList](Prelude.html#v:showList "Prelude")

This class therefore represents the generalization of [Show](Prelude.html#t:Show "Prelude") by decomposing it's methods into a canonical lifting on a canonical inner method, so that the lifting can be reused for other arguments than the canonical one.

Since: base-4.9.0.0

Minimal complete definition

Nothing

Instances

Instances details

Show1 Complex Source # >>> showsPrec1 0 (2 :+ 3) "" "2 :+ 3" Since: base-4.16.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Complex a -> ShowS Source #liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Complex a] -> ShowS Source #
Show1 NonEmpty Source # Since: base-4.10.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> NonEmpty a -> ShowS Source #liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [NonEmpty a] -> ShowS Source #
Show1 Identity Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Identity a -> ShowS Source #liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Identity a] -> ShowS Source #
Show1 Down Source # Since: base-4.12.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Down a -> ShowS Source #liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Down a] -> ShowS Source #
Show1 Par1 Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Par1 a -> ShowS Source #liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Par1 a] -> ShowS Source #
Show1 Maybe Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Maybe a -> ShowS Source #liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Maybe a] -> ShowS Source #
Show1 Solo Source # Since: base-4.15
Instance detailsDefined in Data.Functor.Classes MethodsliftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Solo a -> ShowS Source #liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Solo a] -> ShowS Source #
Show1 [] Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> [a] -> ShowS Source #liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [[a]] -> ShowS Source #
Show a => Show1 (Either a) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> Either a a0 -> ShowS Source #liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [Either a a0] -> ShowS Source #
Show1 (Proxy :: Type -> Type) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Proxy a -> ShowS Source #liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Proxy a] -> ShowS Source #
Show1 (U1 :: Type -> Type) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> U1 a -> ShowS Source #liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [U1 a] -> ShowS Source #
Show1 (UAddr :: Type -> Type) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> UAddr a -> ShowS Source #liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [UAddr a] -> ShowS Source #
Show1 (UChar :: Type -> Type) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> UChar a -> ShowS Source #liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [UChar a] -> ShowS Source #
Show1 (UDouble :: Type -> Type) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> UDouble a -> ShowS Source #liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [UDouble a] -> ShowS Source #
Show1 (UFloat :: Type -> Type) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> UFloat a -> ShowS Source #liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [UFloat a] -> ShowS Source #
Show1 (UInt :: Type -> Type) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> UInt a -> ShowS Source #liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [UInt a] -> ShowS Source #
Show1 (UWord :: Type -> Type) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> UWord a -> ShowS Source #liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [UWord a] -> ShowS Source #
Show1 (V1 :: Type -> Type) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> V1 a -> ShowS Source #liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [V1 a] -> ShowS Source #
Show a => Show1 ((,) a) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> (a, a0) -> ShowS Source #liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [(a, a0)] -> ShowS Source #
Show a => Show1 (Const a :: Type -> Type) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> Const a a0 -> ShowS Source #liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [Const a a0] -> ShowS Source #
Show1 f => Show1 (Rec1 f) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Rec1 f a -> ShowS Source #liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Rec1 f a] -> ShowS Source #
(Show a, Show b) => Show1 ((,,) a b) Source # Since: base-4.16.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> (a, b, a0) -> ShowS Source #liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [(a, b, a0)] -> ShowS Source #
(Show1 f, Show1 g) => Show1 (Product f g) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Product MethodsliftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Product f g a -> ShowS Source #liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Product f g a] -> ShowS Source #
(Show1 f, Show1 g) => Show1 (Sum f g) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Sum MethodsliftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Sum f g a -> ShowS Source #liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Sum f g a] -> ShowS Source #
(Show1 f, Show1 g) => Show1 (f :*: g) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> (f :*: g) a -> ShowS Source #liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [(f :*: g) a] -> ShowS Source #
(Show1 f, Show1 g) => Show1 (f :+: g) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> (f :+: g) a -> ShowS Source #liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [(f :+: g) a] -> ShowS Source #
Show c => Show1 (K1 i c :: Type -> Type) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> K1 i c a -> ShowS Source #liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [K1 i c a] -> ShowS Source #
(Show a, Show b, Show c) => Show1 ((,,,) a b c) Source # Since: base-4.16.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> (a, b, c, a0) -> ShowS Source #liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [(a, b, c, a0)] -> ShowS Source #
(Show1 f, Show1 g) => Show1 (Compose f g) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Compose MethodsliftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Compose f g a -> ShowS Source #liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Compose f g a] -> ShowS Source #
(Show1 f, Show1 g) => Show1 (f :.: g) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> (f :.: g) a -> ShowS Source #liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [(f :.: g) a] -> ShowS Source #
Show1 f => Show1 (M1 i c f) Source # Since: base-4.21.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> M1 i c f a -> ShowS Source #liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [M1 i c f a] -> ShowS Source #

For binary constructors

class (forall a. Eq a => Eq1 (f a)) => Eq2 (f :: Type -> Type -> Type) where Source #

Lifting of the [Eq](Data-Eq.html#t:Eq "Data.Eq") class to binary type constructors.

Since: base-4.9.0.0

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> f a c -> f b d -> Bool Source #

Lift equality tests through the type constructor.

The function will usually be applied to equality functions, but the more general type ensures that the implementation uses them to compare elements of the first container with elements of the second.

Since: base-4.9.0.0

Instances

Instances details

Eq2 Either Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> Either a c -> Either b d -> Bool Source #
Eq2 (,) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> (a, c) -> (b, d) -> Bool Source #
Eq2 (Const :: Type -> Type -> Type) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> Const a c -> Const b d -> Bool Source #
Eq a => Eq2 ((,,) a) Source # >>> eq2 ('x', True, "str") ('x', True, "str") True Since: base-4.16.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftEq2 :: (a0 -> b -> Bool) -> (c -> d -> Bool) -> (a, a0, c) -> (a, b, d) -> Bool Source #
(Eq a, Eq b) => Eq2 ((,,,) a b) Source # >>> eq2 ('x', True, "str", 2) ('x', True, "str", 2 :: Int) True Since: base-4.16.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftEq2 :: (a0 -> b0 -> Bool) -> (c -> d -> Bool) -> (a, b, a0, c) -> (a, b, b0, d) -> Bool Source #

eq2 :: (Eq2 f, Eq a, Eq b) => f a b -> f a b -> Bool Source #

Lift the standard (`[==](Data-Eq.html#v:-61--61- "Data.Eq")`) function through the type constructor.

Since: base-4.9.0.0

class (Eq2 f, forall a. Ord a => Ord1 (f a)) => Ord2 (f :: Type -> Type -> Type) where Source #

Lifting of the [Ord](Data-Ord.html#t:Ord "Data.Ord") class to binary type constructors.

Since: base-4.9.0.0

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> f a c -> f b d -> Ordering Source #

Lift [compare](Data-Ord.html#v:compare "Data.Ord") functions through the type constructor.

The function will usually be applied to comparison functions, but the more general type ensures that the implementation uses them to compare elements of the first container with elements of the second.

Since: base-4.9.0.0

Instances

Instances details

Ord2 Either Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> Either a c -> Either b d -> Ordering Source #
Ord2 (,) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> (a, c) -> (b, d) -> Ordering Source #
Ord2 (Const :: Type -> Type -> Type) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> Const a c -> Const b d -> Ordering Source #
Ord a => Ord2 ((,,) a) Source # >>> compare2 ('x', True, "aaa") ('x', True, "zzz") LT Since: base-4.16.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftCompare2 :: (a0 -> b -> Ordering) -> (c -> d -> Ordering) -> (a, a0, c) -> (a, b, d) -> Ordering Source #
(Ord a, Ord b) => Ord2 ((,,,) a b) Source # >>> compare2 ('x', True, "str", 2) ('x', True, "str", 3 :: Int) LT Since: base-4.16.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftCompare2 :: (a0 -> b0 -> Ordering) -> (c -> d -> Ordering) -> (a, b, a0, c) -> (a, b, b0, d) -> Ordering Source #

class (forall a. Read a => Read1 (f a)) => Read2 (f :: Type -> Type -> Type) where Source #

Instances

Instances details

Read2 Either Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Either a b) Source #liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Either a b] Source #liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Either a b) Source #liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Either a b] Source #
Read2 (,) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (a, b) Source #liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [(a, b)] Source #liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (a, b) Source #liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [(a, b)] Source #
Read2 (Const :: Type -> Type -> Type) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Const a b) Source #liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Const a b] Source #liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Const a b) Source #liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Const a b] Source #
Read a => Read2 ((,,) a) Source # >>> readPrec_to_S readPrec2 0 "('x', True, 2)" :: [((Char, Bool, Int), String)] [(('x',True,2),"")] Since: base-4.16.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftReadsPrec2 :: (Int -> ReadS a0) -> ReadS [a0] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (a, a0, b) Source #liftReadList2 :: (Int -> ReadS a0) -> ReadS [a0] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [(a, a0, b)] Source #liftReadPrec2 :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (a, a0, b) Source #liftReadListPrec2 :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [(a, a0, b)] Source #
(Read a, Read b) => Read2 ((,,,) a b) Source # >>> readPrec_to_S readPrec2 0 "('x', True, 2, 4.5)" :: [((Char, Bool, Int, Double), String)] [(('x',True,2,4.5),"")] Since: base-4.16.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftReadsPrec2 :: (Int -> ReadS a0) -> ReadS [a0] -> (Int -> ReadS b0) -> ReadS [b0] -> Int -> ReadS (a, b, a0, b0) Source #liftReadList2 :: (Int -> ReadS a0) -> ReadS [a0] -> (Int -> ReadS b0) -> ReadS [b0] -> ReadS [(a, b, a0, b0)] Source #liftReadPrec2 :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec b0 -> ReadPrec [b0] -> ReadPrec (a, b, a0, b0) Source #liftReadListPrec2 :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec b0 -> ReadPrec [b0] -> ReadPrec [(a, b, a0, b0)] Source #

class (forall a. Show a => Show1 (f a)) => Show2 (f :: Type -> Type -> Type) where Source #

Lifting of the [Show](Prelude.html#t:Show "Prelude") class to binary type constructors.

Since: base-4.9.0.0

Instances

Instances details

Show2 Either Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> Either a b -> ShowS Source #liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [Either a b] -> ShowS Source #
Show2 (,) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> (a, b) -> ShowS Source #liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [(a, b)] -> ShowS Source #
Show2 (Const :: Type -> Type -> Type) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> Const a b -> ShowS Source #liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [Const a b] -> ShowS Source #
Show a => Show2 ((,,) a) Source # >>> showsPrec2 0 ('x', True, 2 :: Int) "" "('x',True,2)" Since: base-4.16.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftShowsPrec2 :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> (a, a0, b) -> ShowS Source #liftShowList2 :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [(a, a0, b)] -> ShowS Source #
(Show a, Show b) => Show2 ((,,,) a b) Source # >>> showsPrec2 0 ('x', True, 2 :: Int, 4.5 :: Double) "" "('x',True,2,4.5)" Since: base-4.16.0.0
Instance detailsDefined in Data.Functor.Classes MethodsliftShowsPrec2 :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> (Int -> b0 -> ShowS) -> ([b0] -> ShowS) -> Int -> (a, b, a0, b0) -> ShowS Source #liftShowList2 :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> (Int -> b0 -> ShowS) -> ([b0] -> ShowS) -> [(a, b, a0, b0)] -> ShowS Source #

Helper functions

These functions can be used to assemble [Read](Prelude.html#t:Read "Prelude") and [Show](Prelude.html#t:Show "Prelude") instances for new algebraic types. For example, given the definition

data T f a = Zero a | One (f a) | Two a (f a)

a standard [Read1](Data-Functor-Classes.html#t:Read1 "Data.Functor.Classes") instance may be defined as

instance (Read1 f) => Read1 (T f) where liftReadPrec rp rl = readData $ readUnaryWith rp "Zero" Zero <|> readUnaryWith (liftReadPrec rp rl) "One" One <|> readBinaryWith rp (liftReadPrec rp rl) "Two" Two liftReadListPrec = liftReadListPrecDefault

and the corresponding [Show1](Data-Functor-Classes.html#t:Show1 "Data.Functor.Classes") instance as

instance (Show1 f) => Show1 (T f) where liftShowsPrec sp _ d (Zero x) = showsUnaryWith sp "Zero" d x liftShowsPrec sp sl d (One x) = showsUnaryWith (liftShowsPrec sp sl) "One" d x liftShowsPrec sp sl d (Two x y) = showsBinaryWith sp (liftShowsPrec sp sl) "Two" d x y

Obsolete helpers