Movatterモバイル変換


[0]ホーム

URL:


base-4.12.0.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

Contents

Description

Liftings of the Prelude classesEq,Ord,Read andShow 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 transformerT, 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 (==) = eq1instance (Ord1 f, Ord a) => Ord (T f a) where compare = compare1instance (Read1 f, Read a) => Read (T f a) where  readPrec     = readPrec1  readListPrec = readListPrecDefaultinstance (Show1 f, Show a) => Show (T f a) where showsPrec = showsPrec1

Since: 4.9.0.0

Synopsis

Liftings of Prelude classes

For unary constructors

classEq1 fwhereSource#

Lifting of theEq class to unary type constructors.

Since: 4.9.0.0

Methods

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

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: 4.9.0.0

Instances
Eq1 []Source#

Since: 4.9.0.0

Instance details

Defined inData.Functor.Classes

Methods

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

Eq1MaybeSource#

Since: 4.9.0.0

Instance details

Defined inData.Functor.Classes

Methods

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

Eq1NonEmptySource#

Since: 4.10.0.0

Instance details

Defined inData.Functor.Classes

Methods

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

Eq1DownSource#

Since: 4.12.0.0

Instance details

Defined inData.Functor.Classes

Methods

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

Eq1IdentitySource#

Since: 4.9.0.0

Instance details

Defined inData.Functor.Classes

Methods

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

Eq a =>Eq1 (Either a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Functor.Classes

Methods

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

Eq a =>Eq1 ((,) a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Functor.Classes

Methods

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

Eq1 (Proxy ::Type ->Type)Source#

Since: 4.9.0.0

Instance details

Defined inData.Functor.Classes

Methods

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

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

Since: 4.9.0.0

Instance details

Defined inData.Functor.Classes

Methods

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

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

Since: 4.9.0.0

Instance details

Defined inData.Functor.Sum

Methods

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

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

Since: 4.9.0.0

Instance details

Defined inData.Functor.Product

Methods

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

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

Since: 4.9.0.0

Instance details

Defined inData.Functor.Compose

Methods

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

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

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

Since: 4.9.0.0

classEq1 f =>Ord1 fwhereSource#

Lifting of theOrd class to unary type constructors.

Since: 4.9.0.0

Methods

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

Lift acompare 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: 4.9.0.0

Instances
Ord1 []Source#

Since: 4.9.0.0

Instance details

Defined inData.Functor.Classes

Methods

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

Ord1MaybeSource#

Since: 4.9.0.0

Instance details

Defined inData.Functor.Classes

Methods

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

Ord1NonEmptySource#

Since: 4.10.0.0

Instance details

Defined inData.Functor.Classes

Methods

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

Ord1DownSource#

Since: 4.12.0.0

Instance details

Defined inData.Functor.Classes

Methods

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

Ord1IdentitySource#

Since: 4.9.0.0

Instance details

Defined inData.Functor.Classes

Methods

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

Ord a =>Ord1 (Either a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Functor.Classes

Methods

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

Ord a =>Ord1 ((,) a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Functor.Classes

Methods

liftCompare :: (a0 -> b ->Ordering) -> (a, a0) -> (a, b) ->OrderingSource#

Ord1 (Proxy ::Type ->Type)Source#

Since: 4.9.0.0

Instance details

Defined inData.Functor.Classes

Methods

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

Ord a =>Ord1 (Const a ::Type ->Type)Source#

Since: 4.9.0.0

Instance details

Defined inData.Functor.Classes

Methods

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

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

Since: 4.9.0.0

Instance details

Defined inData.Functor.Sum

Methods

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

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

Since: 4.9.0.0

Instance details

Defined inData.Functor.Product

Methods

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

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

Since: 4.9.0.0

Instance details

Defined inData.Functor.Compose

Methods

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

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

Lift the standardcompare function through the type constructor.

Since: 4.9.0.0

classRead1 fwhereSource#

Lifting of theRead class to unary type constructors.

BothliftReadsPrec andliftReadPrec exist to match the interface provided in theRead type class, but it is recommended to implementRead1 instances usingliftReadPrec as opposed toliftReadsPrec, since the former is more efficient than the latter. For example:

instanceRead1 T whereliftReadPrec     = ...liftReadListPrec =liftReadListPrecDefault

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

Since: 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 onreadsPrec andreadList functions for the argument type.

Since: 4.9.0.0

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

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

Since: 4.9.0.0

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

readPrec function for an application of the type constructor based onreadPrec andreadListPrec functions for the argument type.

Since: 4.10.0.0

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

readListPrec function for an application of the type constructor based onreadPrec andreadListPrec functions for the argument type.

The default definition usesliftReadList. Instances that defineliftReadPrec should also defineliftReadListPrec asliftReadListPrecDefault.

Since: 4.10.0.0

Instances
Read1 []Source#

Since: 4.9.0.0

Instance details

Defined inData.Functor.Classes

Read1MaybeSource#

Since: 4.9.0.0

Instance details

Defined inData.Functor.Classes

Read1NonEmptySource#

Since: 4.10.0.0

Instance details

Defined inData.Functor.Classes

Read1DownSource#

Since: 4.12.0.0

Instance details

Defined inData.Functor.Classes

Read1IdentitySource#

Since: 4.9.0.0

Instance details

Defined inData.Functor.Classes

Read a =>Read1 (Either a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Functor.Classes

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

Since: 4.9.0.0

Instance details

Defined inData.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)Source#

Since: 4.9.0.0

Instance details

Defined inData.Functor.Classes

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

Since: 4.9.0.0

Instance details

Defined inData.Functor.Classes

(Read1 f,Read1 g) =>Read1 (Sum f g)Source#

Since: 4.9.0.0

Instance details

Defined inData.Functor.Sum

(Read1 f,Read1 g) =>Read1 (Product f g)Source#

Since: 4.9.0.0

Instance details

Defined inData.Functor.Product

(Read1 f,Read1 g) =>Read1 (Compose f g)Source#

Since: 4.9.0.0

Instance details

Defined inData.Functor.Compose

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

Lift the standardreadsPrec andreadList functions through the type constructor.

Since: 4.9.0.0

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

Lift the standardreadPrec andreadListPrec functions through the type constructor.

Since: 4.10.0.0

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

A possible replacement definition for theliftReadList method. This is only needed forRead1 instances whereliftReadListPrec isn't defined asliftReadListPrecDefault.

Since: 4.10.0.0

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

A possible replacement definition for theliftReadListPrec method, defined usingliftReadPrec.

Since: 4.10.0.0

classShow1 fwhereSource#

Lifting of theShow class to unary type constructors.

Since: 4.9.0.0

Minimal complete definition

liftShowsPrec

Methods

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

showsPrec function for an application of the type constructor based onshowsPrec andshowList functions for the argument type.

Since: 4.9.0.0

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

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

Since: 4.9.0.0

Instances
Show1 []Source#

Since: 4.9.0.0

Instance details

Defined inData.Functor.Classes

Methods

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

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

Show1MaybeSource#

Since: 4.9.0.0

Instance details

Defined inData.Functor.Classes

Methods

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

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

Show1NonEmptySource#

Since: 4.10.0.0

Instance details

Defined inData.Functor.Classes

Methods

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

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

Show1DownSource#

Since: 4.12.0.0

Instance details

Defined inData.Functor.Classes

Methods

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

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

Show1IdentitySource#

Since: 4.9.0.0

Instance details

Defined inData.Functor.Classes

Methods

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

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

Show a =>Show1 (Either a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Functor.Classes

Methods

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

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

Show a =>Show1 ((,) a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Functor.Classes

Methods

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

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

Show1 (Proxy ::Type ->Type)Source#

Since: 4.9.0.0

Instance details

Defined inData.Functor.Classes

Methods

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

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

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

Since: 4.9.0.0

Instance details

Defined inData.Functor.Classes

Methods

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

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

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

Since: 4.9.0.0

Instance details

Defined inData.Functor.Sum

Methods

liftShowsPrec :: (Int -> a ->ShowS) -> ([a] ->ShowS) ->Int ->Sum f g a ->ShowSSource#

liftShowList :: (Int -> a ->ShowS) -> ([a] ->ShowS) -> [Sum f g a] ->ShowSSource#

(Show1 f,Show1 g) =>Show1 (Product f g)Source#

Since: 4.9.0.0

Instance details

Defined inData.Functor.Product

Methods

liftShowsPrec :: (Int -> a ->ShowS) -> ([a] ->ShowS) ->Int ->Product f g a ->ShowSSource#

liftShowList :: (Int -> a ->ShowS) -> ([a] ->ShowS) -> [Product f g a] ->ShowSSource#

(Show1 f,Show1 g) =>Show1 (Compose f g)Source#

Since: 4.9.0.0

Instance details

Defined inData.Functor.Compose

Methods

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

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

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

Lift the standardshowsPrec andshowList functions through the type constructor.

Since: 4.9.0.0

For binary constructors

classEq2 fwhereSource#

Lifting of theEq class to binary type constructors.

Since: 4.9.0.0

Methods

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

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: 4.9.0.0

Instances
Eq2EitherSource#

Since: 4.9.0.0

Instance details

Defined inData.Functor.Classes

Methods

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

Eq2(,)Source#

Since: 4.9.0.0

Instance details

Defined inData.Functor.Classes

Methods

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

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

Since: 4.9.0.0

Instance details

Defined inData.Functor.Classes

Methods

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

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

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

Since: 4.9.0.0

classEq2 f =>Ord2 fwhereSource#

Lifting of theOrd class to binary type constructors.

Since: 4.9.0.0

Methods

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

Liftcompare 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: 4.9.0.0

Instances
Ord2EitherSource#

Since: 4.9.0.0

Instance details

Defined inData.Functor.Classes

Methods

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

Ord2(,)Source#

Since: 4.9.0.0

Instance details

Defined inData.Functor.Classes

Methods

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

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

Since: 4.9.0.0

Instance details

Defined inData.Functor.Classes

Methods

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

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

Lift the standardcompare function through the type constructor.

Since: 4.9.0.0

classRead2 fwhereSource#

Lifting of theRead class to binary type constructors.

BothliftReadsPrec2 andliftReadPrec2 exist to match the interface provided in theRead type class, but it is recommended to implementRead2 instances usingliftReadPrec2 as opposed toliftReadsPrec2, since the former is more efficient than the latter. For example:

instanceRead2 T whereliftReadPrec2     = ...liftReadListPrec2 =liftReadListPrec2Default

For more information, refer to the documentation for theRead 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 onreadsPrec andreadList functions for the argument types.

Since: 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 onreadsPrec andreadList functions for the argument types. The default implementation using standard list syntax is correct for most types.

Since: 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 onreadPrec andreadListPrec functions for the argument types.

Since: 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 onreadPrec andreadListPrec functions for the argument types.

The default definition usesliftReadList2. Instances that defineliftReadPrec2 should also defineliftReadListPrec2 asliftReadListPrec2Default.

Since: 4.10.0.0

Instances
Read2EitherSource#

Since: 4.9.0.0

Instance details

Defined inData.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(,)Source#

Since: 4.9.0.0

Instance details

Defined inData.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)Source#

Since: 4.9.0.0

Instance details

Defined inData.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 standardreadsPrec function through the type constructor.

Since: 4.9.0.0

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

Lift the standardreadPrec function through the type constructor.

Since: 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 theliftReadList2 method. This is only needed forRead2 instances whereliftReadListPrec2 isn't defined asliftReadListPrec2Default.

Since: 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 theliftReadListPrec2 method, defined usingliftReadPrec2.

Since: 4.10.0.0

classShow2 fwhereSource#

Lifting of theShow class to binary type constructors.

Since: 4.9.0.0

Minimal complete definition

liftShowsPrec2

Methods

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

showsPrec function for an application of the type constructor based onshowsPrec andshowList functions for the argument types.

Since: 4.9.0.0

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

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

Since: 4.9.0.0

Instances
Show2EitherSource#

Since: 4.9.0.0

Instance details

Defined inData.Functor.Classes

Methods

liftShowsPrec2 :: (Int -> a ->ShowS) -> ([a] ->ShowS) -> (Int -> b ->ShowS) -> ([b] ->ShowS) ->Int ->Either a b ->ShowSSource#

liftShowList2 :: (Int -> a ->ShowS) -> ([a] ->ShowS) -> (Int -> b ->ShowS) -> ([b] ->ShowS) -> [Either a b] ->ShowSSource#

Show2(,)Source#

Since: 4.9.0.0

Instance details

Defined inData.Functor.Classes

Methods

liftShowsPrec2 :: (Int -> a ->ShowS) -> ([a] ->ShowS) -> (Int -> b ->ShowS) -> ([b] ->ShowS) ->Int -> (a, b) ->ShowSSource#

liftShowList2 :: (Int -> a ->ShowS) -> ([a] ->ShowS) -> (Int -> b ->ShowS) -> ([b] ->ShowS) -> [(a, b)] ->ShowSSource#

Show2 (Const ::Type ->Type ->Type)Source#

Since: 4.9.0.0

Instance details

Defined inData.Functor.Classes

Methods

liftShowsPrec2 :: (Int -> a ->ShowS) -> ([a] ->ShowS) -> (Int -> b ->ShowS) -> ([b] ->ShowS) ->Int ->Const a b ->ShowSSource#

liftShowList2 :: (Int -> a ->ShowS) -> ([a] ->ShowS) -> (Int -> b ->ShowS) -> ([b] ->ShowS) -> [Const a b] ->ShowSSource#

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

Lift the standardshowsPrec function through the type constructor.

Since: 4.9.0.0

Helper functions

These functions can be used to assembleRead andShow instances fornew algebraic types. For example, given the definition

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

a standardRead1 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 correspondingShow1 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 aSource#

readsData p d is a parser for datatypes where each alternative begins with a data constructor. It parses the constructor and passes it top. Parsers for various constructors can be constructed withreadsUnary,readsUnary1 andreadsBinary1, and combined withmappend from theMonoid class.

Since: 4.9.0.0

readData ::ReadPrec a ->ReadPrec aSource#

readData p is a parser for datatypes where each alternative begins with a data constructor. It parses the constructor and passes it top. Parsers for various constructors can be constructed withreadUnaryWith andreadBinaryWith, and combined with '(|)' from theAlternative class.

Since: 4.10.0.0

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

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

Since: 4.9.0.0

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

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

Since: 4.10.0.0

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

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

Since: 4.9.0.0

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

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

Since: 4.10.0.0

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

showsUnaryWith sp n d x produces the string representation of a unary data constructor with namen and argumentx, in precedence contextd.

Since: 4.9.0.0

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

showsBinaryWith sp1 sp2 n d x y produces the string representation of a binary data constructor with namen and argumentsx andy, in precedence contextd.

Since: 4.9.0.0

Obsolete helpers

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

Deprecated: Use readsUnaryWith to define liftReadsPrec

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

Since: 4.9.0.0

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

Deprecated: Use readsUnaryWith to define liftReadsPrec

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

Since: 4.9.0.0

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

Deprecated: Use readsBinaryWith to define liftReadsPrec

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

Since: 4.9.0.0

showsUnary ::Show a =>String ->Int -> a ->ShowSSource#

Deprecated: Use showsUnaryWith to define liftShowsPrec

showsUnary n d x produces the string representation of a unary data constructor with namen and argumentx, in precedence contextd.

Since: 4.9.0.0

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

Deprecated: Use showsUnaryWith to define liftShowsPrec

showsUnary1 n d x produces the string representation of a unary data constructor with namen and argumentx, in precedence contextd.

Since: 4.9.0.0

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

Deprecated: Use showsBinaryWith to define liftShowsPrec

showsBinary1 n d x y produces the string representation of a binary data constructor with namen and argumentsx andy, in precedence contextd.

Since: 4.9.0.0

Produced byHaddock version 2.20.0


[8]ページ先頭

©2009-2025 Movatter.jp