base-4.14.1.0: Basic libraries
Copyright(c) Ross Paterson 2013
LicenseBSD-style (see the file LICENSE)
Maintainerlibraries@haskell.org
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Data.Functor.Classes

Description

Liftings of the Prelude classes Eq, Ord, Read and Show 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

Synopsis

Liftings of Prelude classes

For unary constructors

class Eq1 f where Source #

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 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 [] #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

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 Source #

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 Source #

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 Source #

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 Source #

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 Source #

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 Source #

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 Source #

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 Source #

(Eq1 f, Eq1 g) => Eq1 (Sum f g) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

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

(Eq1 f, Eq1 g) => Eq1 (Product f g) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

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

(Eq1 f, Eq1 g) => Eq1 (Compose f g) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

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

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

Lift the standard (==) function through the type constructor.

Since: base-4.9.0.0

class Eq1 f => Ord1 f where Source #

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 Source #

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 Source #

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 Source #

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 Source #

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 Source #

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 Source #

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 Source #

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 Source #

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 Source #

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 Source #

(Ord1 f, Ord1 g) => Ord1 (Sum f g) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

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

(Ord1 f, Ord1 g) => Ord1 (Product f g) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

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

(Ord1 f, Ord1 g) => Ord1 (Compose f g) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

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

compare1 :: (Ord1 f, Ord a) => f a -> f a -> Ordering Source #

Lift the standard compare function through the type constructor.

Since: base-4.9.0.0

class Read1 f where Source #

Lifting of the Read class to unary type constructors.

Both liftReadsPrec and liftReadPrec exist to match the interface provided in the Read type class, but it is recommended to implement Read1 instances using liftReadPrec as opposed to liftReadsPrec, since the former is more efficient than the latter. For example:

instance Read1 T where
  liftReadPrec     = ...
  liftReadListPrec = liftReadListPrecDefault

For more information, refer to the documentation for the Read class.

Since: base-4.9.0.0

Minimal complete definition

liftReadsPrec | liftReadPrec

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (f a) Source #

readsPrec function for an application of the type constructor based on readsPrec and readList functions for the argument type.

Since: base-4.9.0.0

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [f a] Source #

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

Since: base-4.9.0.0

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (f a) Source #

readPrec function for an application of the type constructor based on readPrec and readListPrec functions for the argument type.

Since: base-4.10.0.0

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [f a] Source #

readListPrec function for an application of the type constructor based on readPrec and readListPrec functions for the argument type.

The default definition uses liftReadList. Instances that define liftReadPrec should also define liftReadListPrec as liftReadListPrecDefault.

Since: base-4.10.0.0

Instances

Instances details
Read1 [] #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec :: (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 #

Read1 Maybe #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Read1 NonEmpty #

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Read1 Down #

Since: base-4.12.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec :: (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 Identity #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Read a => Read1 (Either a) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec :: (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 #

Read a => Read1 ((,) a) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec :: (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 #

Read1 (Proxy :: Type -> Type) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Read a => Read1 (Const a :: Type -> Type) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec :: (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 g) => Read1 (Sum f g) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

liftReadsPrec :: (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 (Product f g) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

liftReadsPrec :: (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 (Compose f g) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

liftReadsPrec :: (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 #

readsPrec1 :: (Read1 f, Read a) => Int -> ReadS (f a) Source #

Lift the standard readsPrec and readList functions through the type constructor.

Since: base-4.9.0.0

readPrec1 :: (Read1 f, Read a) => ReadPrec (f a) Source #

Lift the standard readPrec and readListPrec functions through the type constructor.

Since: base-4.10.0.0

liftReadListDefault :: Read1 f => (Int -> ReadS a) -> ReadS [a] -> ReadS [f a] Source #

A possible replacement definition for the liftReadList method. This is only needed for Read1 instances where liftReadListPrec isn't defined as liftReadListPrecDefault.

Since: base-4.10.0.0

liftReadListPrecDefault :: Read1 f => ReadPrec a -> ReadPrec [a] -> ReadPrec [f a] Source #

A possible replacement definition for the liftReadListPrec method, defined using liftReadPrec.

Since: base-4.10.0.0

class Show1 f where Source #

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 Source #

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 Source #

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 Source #

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

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 Source #

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

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 Source #

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

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 Source #

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

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 Source #

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

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 Source #

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

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 Source #

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

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 Source #

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

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 Source #

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

(Show1 f, Show1 g) => Show1 (Sum f g) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

liftShowsPrec :: (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 (Product f g) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

liftShowsPrec :: (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 (Compose f g) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Compose f g a -> ShowS Source #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Compose f g a] -> ShowS Source #

showsPrec1 :: (Show1 f, Show a) => Int -> f a -> ShowS Source #

Lift the standard showsPrec and showList functions through the type constructor.

Since: base-4.9.0.0

For binary constructors

class Eq2 f where Source #

Lifting of the 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 #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Eq2 (,) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Eq2 (Const :: Type -> Type -> Type) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

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

Lift the standard (==) function through the type constructor.

Since: base-4.9.0.0

class Eq2 f => Ord2 f where Source #

Lifting of the 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 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 #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Ord2 (,) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Ord2 (Const :: Type -> Type -> Type) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

compare2 :: (Ord2 f, Ord a, Ord b) => f a b -> f a b -> Ordering Source #

Lift the standard compare function through the type constructor.

Since: base-4.9.0.0

class Read2 f where Source #

Lifting of the Read class to binary type constructors.

Both liftReadsPrec2 and liftReadPrec2 exist to match the interface provided in the Read type class, but it is recommended to implement Read2 instances using liftReadPrec2 as opposed to liftReadsPrec2, since the former is more efficient than the latter. For example:

instance Read2 T where
  liftReadPrec2     = ...
  liftReadListPrec2 = liftReadListPrec2Default

For more information, refer to the documentation for the Read class. @since 4.9.0.0

Minimal complete definition

liftReadsPrec2 | liftReadPrec2

Methods

liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (f a b) Source #

readsPrec function for an application of the type constructor based on readsPrec and readList functions for the argument types.

Since: base-4.9.0.0

liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [f a b] Source #

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

Since: base-4.9.0.0

liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (f a b) Source #

readPrec function for an application of the type constructor based on readPrec and readListPrec functions for the argument types.

Since: base-4.10.0.0

liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [f a b] Source #

readListPrec function for an application of the type constructor based on readPrec and readListPrec functions for the argument types.

The default definition uses liftReadList2. Instances that define liftReadPrec2 should also define liftReadListPrec2 as liftReadListPrec2Default.

Since: base-4.10.0.0

Instances

Instances details
Read2 Either #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec2 :: (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 (,) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec2 :: (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) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec2 :: (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 #

readsPrec2 :: (Read2 f, Read a, Read b) => Int -> ReadS (f a b) Source #

Lift the standard readsPrec function through the type constructor.

Since: base-4.9.0.0

readPrec2 :: (Read2 f, Read a, Read b) => ReadPrec (f a b) Source #

Lift the standard readPrec function through the type constructor.

Since: base-4.10.0.0

liftReadList2Default :: Read2 f => (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [f a b] Source #

A possible replacement definition for the liftReadList2 method. This is only needed for Read2 instances where liftReadListPrec2 isn't defined as liftReadListPrec2Default.

Since: base-4.10.0.0

liftReadListPrec2Default :: Read2 f => ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [f a b] Source #

A possible replacement definition for the liftReadListPrec2 method, defined using liftReadPrec2.

Since: base-4.10.0.0

class Show2 f where Source #

Lifting of the Show class to binary type constructors.

Since: base-4.9.0.0

Minimal complete definition

liftShowsPrec2

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> f a b -> ShowS Source #

showsPrec function for an application of the type constructor based on showsPrec and showList functions for the argument types.

Since: base-4.9.0.0

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [f a b] -> ShowS Source #

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

Since: base-4.9.0.0

Instances

Instances details
Show2 Either #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec2 :: (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 (,) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec2 :: (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) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec2 :: (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 #

showsPrec2 :: (Show2 f, Show a, Show b) => Int -> f a b -> ShowS Source #

Lift the standard showsPrec function through the type constructor.

Since: base-4.9.0.0

Helper functions

These functions can be used to assemble Read and Show 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 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 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

readsData :: (String -> ReadS a) -> Int -> ReadS a Source #

readsData p d is a parser for datatypes where each alternative begins with a data constructor. It parses the constructor and passes it to p. Parsers for various constructors can be constructed with readsUnary, readsUnary1 and readsBinary1, and combined with mappend from the Monoid class.

Since: base-4.9.0.0

readData :: ReadPrec a -> ReadPrec a Source #

readData p is a parser for datatypes where each alternative begins with a data constructor. It parses the constructor and passes it to p. Parsers for various constructors can be constructed with readUnaryWith and readBinaryWith, and combined with (<|>) from the Alternative class.

Since: base-4.10.0.0

readsUnaryWith :: (Int -> ReadS a) -> String -> (a -> t) -> String -> ReadS t Source #

readsUnaryWith rp n c n' matches the name of a unary data constructor and then parses its argument using rp.

Since: base-4.9.0.0

readUnaryWith :: ReadPrec a -> String -> (a -> t) -> ReadPrec t Source #

readUnaryWith rp n c' matches the name of a unary data constructor and then parses its argument using rp.

Since: base-4.10.0.0

readsBinaryWith :: (Int -> ReadS a) -> (Int -> ReadS b) -> String -> (a -> b -> t) -> String -> ReadS t Source #

readsBinaryWith rp1 rp2 n c n' matches the name of a binary data constructor and then parses its arguments using rp1 and rp2 respectively.

Since: base-4.9.0.0

readBinaryWith :: ReadPrec a -> ReadPrec b -> String -> (a -> b -> t) -> ReadPrec t Source #

readBinaryWith rp1 rp2 n c' matches the name of a binary data constructor and then parses its arguments using rp1 and rp2 respectively.

Since: base-4.10.0.0

showsUnaryWith :: (Int -> a -> ShowS) -> String -> Int -> a -> ShowS Source #

showsUnaryWith sp n d x produces the string representation of a unary data constructor with name n and argument x, in precedence context d.

Since: base-4.9.0.0

showsBinaryWith :: (Int -> a -> ShowS) -> (Int -> b -> ShowS) -> String -> Int -> a -> b -> ShowS Source #

showsBinaryWith sp1 sp2 n d x y produces the string representation of a binary data constructor with name n and arguments x and y, in precedence context d.

Since: base-4.9.0.0

Obsolete helpers

readsUnary :: Read a => String -> (a -> t) -> String -> ReadS t Source #

Deprecated: Use readsUnaryWith to define liftReadsPrec

readsUnary n c n' matches the name of a unary data constructor and then parses its argument using readsPrec.

Since: base-4.9.0.0

readsUnary1 :: (Read1 f, Read a) => String -> (f a -> t) -> String -> ReadS t Source #

Deprecated: Use readsUnaryWith to define liftReadsPrec

readsUnary1 n c n' matches the name of a unary data constructor and then parses its argument using readsPrec1.

Since: base-4.9.0.0

readsBinary1 :: (Read1 f, Read1 g, Read a) => String -> (f a -> g a -> t) -> String -> ReadS t Source #

Deprecated: Use readsBinaryWith to define liftReadsPrec

readsBinary1 n c n' matches the name of a binary data constructor and then parses its arguments using readsPrec1.

Since: base-4.9.0.0

showsUnary :: Show a => String -> Int -> a -> ShowS Source #

Deprecated: Use showsUnaryWith to define liftShowsPrec

showsUnary n d x produces the string representation of a unary data constructor with name n and argument x, in precedence context d.

Since: base-4.9.0.0

showsUnary1 :: (Show1 f, Show a) => String -> Int -> f a -> ShowS Source #

Deprecated: Use showsUnaryWith to define liftShowsPrec

showsUnary1 n d x produces the string representation of a unary data constructor with name n and argument x, in precedence context d.

Since: base-4.9.0.0

showsBinary1 :: (Show1 f, Show1 g, Show a) => String -> Int -> f a -> g a -> ShowS Source #

Deprecated: Use showsBinaryWith to define liftShowsPrec

showsBinary1 n d x y produces the string representation of a binary data constructor with name n and arguments x and y, in precedence context d.

Since: base-4.9.0.0