Copyright | (c) Ross Paterson 2013 |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | libraries@haskell.org |
Stability | stable |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
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
- class (forall a. Eq a => Eq (f a)) => Eq1 f where
- eq1 :: (Eq1 f, Eq a) => f a -> f a -> Bool
- class (Eq1 f, forall a. Ord a => Ord (f a)) => Ord1 f where
- liftCompare :: (a -> b -> Ordering) -> f a -> f b -> Ordering
- compare1 :: (Ord1 f, Ord a) => f a -> f a -> Ordering
- class (forall a. Read a => Read (f a)) => Read1 f where
- liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (f a)
- liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [f a]
- liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (f a)
- liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [f a]
- readsPrec1 :: (Read1 f, Read a) => Int -> ReadS (f a)
- readPrec1 :: (Read1 f, Read a) => ReadPrec (f a)
- liftReadListDefault :: Read1 f => (Int -> ReadS a) -> ReadS [a] -> ReadS [f a]
- liftReadListPrecDefault :: Read1 f => ReadPrec a -> ReadPrec [a] -> ReadPrec [f a]
- class (forall a. Show a => Show (f a)) => Show1 f where
- showsPrec1 :: (Show1 f, Show a) => Int -> f a -> ShowS
- class (forall a. Eq a => Eq1 (f a)) => Eq2 f where
- eq2 :: (Eq2 f, Eq a, Eq b) => f a b -> f a b -> Bool
- class (Eq2 f, forall a. Ord a => Ord1 (f a)) => Ord2 f where
- liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> f a c -> f b d -> Ordering
- compare2 :: (Ord2 f, Ord a, Ord b) => f a b -> f a b -> Ordering
- class (forall a. Read a => Read1 (f a)) => Read2 f where
- liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (f a b)
- liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [f a b]
- liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (f a b)
- liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [f a b]
- readsPrec2 :: (Read2 f, Read a, Read b) => Int -> ReadS (f a b)
- readPrec2 :: (Read2 f, Read a, Read b) => ReadPrec (f a b)
- liftReadList2Default :: Read2 f => (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [f a b]
- liftReadListPrec2Default :: Read2 f => ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [f a b]
- class (forall a. Show a => Show1 (f a)) => Show2 f where
- showsPrec2 :: (Show2 f, Show a, Show b) => Int -> f a b -> ShowS
- readsData :: (String -> ReadS a) -> Int -> ReadS a
- readData :: ReadPrec a -> ReadPrec a
- readsUnaryWith :: (Int -> ReadS a) -> String -> (a -> t) -> String -> ReadS t
- readUnaryWith :: ReadPrec a -> String -> (a -> t) -> ReadPrec t
- readsBinaryWith :: (Int -> ReadS a) -> (Int -> ReadS b) -> String -> (a -> b -> t) -> String -> ReadS t
- readBinaryWith :: ReadPrec a -> ReadPrec b -> String -> (a -> b -> t) -> ReadPrec t
- showsUnaryWith :: (Int -> a -> ShowS) -> String -> Int -> a -> ShowS
- showsBinaryWith :: (Int -> a -> ShowS) -> (Int -> b -> ShowS) -> String -> Int -> a -> b -> ShowS
- readsUnary :: Read a => String -> (a -> t) -> String -> ReadS t
- readsUnary1 :: (Read1 f, Read a) => String -> (f a -> t) -> String -> ReadS t
- readsBinary1 :: (Read1 f, Read1 g, Read a) => String -> (f a -> g a -> t) -> String -> ReadS t
- showsUnary :: Show a => String -> Int -> a -> ShowS
- showsUnary1 :: (Show1 f, Show a) => String -> Int -> f a -> ShowS
- showsBinary1 :: (Show1 f, Show1 g, Show a) => String -> Int -> f a -> g a -> ShowS
Liftings of Prelude classes
For unary constructors
class (forall a. Eq a => Eq (f a)) => Eq1 f where Source #
Lifting of the 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
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
Nothing
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
Eq1 Complex Source # |
Since: base-4.16.0.0 |
Eq1 Identity Source # | Since: base-4.9.0.0 |
Eq1 Down Source # | Since: base-4.12.0.0 |
Eq1 NonEmpty Source # | Since: base-4.10.0.0 |
Eq1 Maybe Source # | Since: base-4.9.0.0 |
Eq1 Solo Source # | Since: base-4.15 |
Eq1 List Source # | Since: base-4.9.0.0 |
Eq a => Eq1 (Either a) Source # | Since: base-4.9.0.0 |
Eq1 (Proxy :: Type -> Type) Source # | Since: base-4.9.0.0 |
Eq a => Eq1 ((,) a) Source # | Since: base-4.9.0.0 |
Eq a => Eq1 (Const a :: Type -> Type) Source # | Since: base-4.9.0.0 |
(Generic1 f, Eq1 (Rep1 f)) => Eq1 (Generically1 f) Source # | Since: base-4.17.0.0 |
Defined in Data.Functor.Classes liftEq :: (a -> b -> Bool) -> Generically1 f a -> Generically1 f b -> Bool Source # | |
(Eq a, Eq b) => Eq1 ((,,) a b) Source # | Since: base-4.16.0.0 |
(Eq1 f, Eq1 g) => Eq1 (Product f g) Source # | Since: base-4.9.0.0 |
(Eq1 f, Eq1 g) => Eq1 (Sum f g) Source # | Since: base-4.9.0.0 |
(Eq a, Eq b, Eq c) => Eq1 ((,,,) a b c) Source # | Since: base-4.16.0.0 |
(Eq1 f, Eq1 g) => Eq1 (Compose f g) Source # | Since: base-4.9.0.0 |
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, forall a. Ord a => Ord (f a)) => Ord1 f where Source #
Lifting of the Ord
class to unary type constructors.
Any instance should be subject to the following law that canonicity is preserved:
liftCompare compare
= compare
This class therefore represents the generalization of 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
Nothing
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
Ord1 Identity Source # | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Ord1 Down Source # | Since: base-4.12.0.0 |
Defined in Data.Functor.Classes | |
Ord1 NonEmpty Source # | Since: base-4.10.0.0 |
Defined in Data.Functor.Classes | |
Ord1 Maybe Source # | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Ord1 Solo Source # | Since: base-4.15 |
Defined in Data.Functor.Classes | |
Ord1 List Source # | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes liftCompare :: (a -> b -> Ordering) -> [a] -> [b] -> Ordering Source # | |
Ord a => Ord1 (Either a) Source # | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Ord1 (Proxy :: Type -> Type) Source # | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Ord a => Ord1 ((,) a) Source # | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes liftCompare :: (a0 -> b -> Ordering) -> (a, a0) -> (a, b) -> Ordering Source # | |
Ord a => Ord1 (Const a :: Type -> Type) Source # | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
(Generic1 f, Ord1 (Rep1 f)) => Ord1 (Generically1 f) Source # | Since: base-4.17.0.0 |
Defined in Data.Functor.Classes liftCompare :: (a -> b -> Ordering) -> Generically1 f a -> Generically1 f b -> Ordering Source # | |
(Ord a, Ord b) => Ord1 ((,,) a b) Source # | Since: base-4.16.0.0 |
Defined in Data.Functor.Classes liftCompare :: (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 |
Defined in Data.Functor.Product | |
(Ord1 f, Ord1 g) => Ord1 (Sum f g) Source # | Since: base-4.9.0.0 |
Defined in Data.Functor.Sum | |
(Ord a, Ord b, Ord c) => Ord1 ((,,,) a b c) Source # | Since: base-4.16.0.0 |
Defined in Data.Functor.Classes liftCompare :: (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 |
Defined in Data.Functor.Compose |
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 (forall a. Read a => Read (f a)) => Read1 f where Source #
Lifting of the Read
class to unary type constructors.
Any instance should be subject to the following laws that canonicity is preserved:
liftReadsPrec readsPrec readList
= readsPrec
liftReadList readsPrec readList
= readList
liftReadPrec readPrec readListPrec
= readPrec
liftReadListPrec readPrec readListPrec
= readListPrec
This class therefore represents the generalization of Read
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
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:
instanceRead1
T whereliftReadPrec
= ...liftReadListPrec
=liftReadListPrecDefault
For more information, refer to the documentation for the Read
class.
Since: base-4.9.0.0
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
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 (forall a. Show a => Show (f a)) => Show1 f where Source #
Lifting of the Show
class to unary type constructors.
Any instance should be subject to the following laws that canonicity is preserved:
liftShowsPrec showsPrec showList
= showsPrec
liftShowList showsPrec showList
= showList
This class therefore represents the generalization of Show
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
Nothing
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
default liftShowsPrec :: (f ~ f' b, Show2 f', Show b) => (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS Source #
liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [f a] -> ShowS Source #
Instances
Show1 Complex Source # |
Since: base-4.16.0.0 |
Show1 Identity Source # | Since: base-4.9.0.0 |
Show1 Down Source # | Since: base-4.12.0.0 |
Show1 NonEmpty Source # | Since: base-4.10.0.0 |
Show1 Maybe Source # | Since: base-4.9.0.0 |
Show1 Solo Source # | Since: base-4.15 |
Show1 List Source # | Since: base-4.9.0.0 |
Show a => Show1 (Either a) Source # | Since: base-4.9.0.0 |
Show1 (Proxy :: Type -> Type) Source # | Since: base-4.9.0.0 |
Show a => Show1 ((,) a) Source # | Since: base-4.9.0.0 |
Show a => Show1 (Const a :: Type -> Type) Source # | Since: base-4.9.0.0 |
(Show a, Show b) => Show1 ((,,) a b) Source # | Since: base-4.16.0.0 |
(Show1 f, Show1 g) => Show1 (Product f g) Source # | Since: base-4.9.0.0 |
(Show1 f, Show1 g) => Show1 (Sum f g) Source # | Since: base-4.9.0.0 |
(Show a, Show b, Show c) => Show1 ((,,,) a b c) Source # | Since: base-4.16.0.0 |
(Show1 f, Show1 g) => Show1 (Compose f g) Source # | Since: base-4.9.0.0 |
For binary constructors
class (forall a. Eq a => Eq1 (f a)) => Eq2 f where Source #
Lifting of the Eq
class to binary type constructors.
Since: base-4.9.0.0
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
Eq2 Either Source # | Since: base-4.9.0.0 |
Eq2 (,) Source # | Since: base-4.9.0.0 |
Eq2 (Const :: Type -> Type -> Type) Source # | Since: base-4.9.0.0 |
Eq a => Eq2 ((,,) a) Source # |
Since: base-4.16.0.0 |
(Eq a, Eq b) => Eq2 ((,,,) a b) Source # |
Since: base-4.16.0.0 |
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, forall a. Ord a => Ord1 (f a)) => Ord2 f where Source #
Lifting of the Ord
class to binary type constructors.
Since: base-4.9.0.0
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
Ord2 Either Source # | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Ord2 (,) Source # | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Ord2 (Const :: Type -> Type -> Type) Source # | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Ord a => Ord2 ((,,) a) Source # |
Since: base-4.16.0.0 |
Defined in Data.Functor.Classes | |
(Ord a, Ord b) => Ord2 ((,,,) a b) Source # |
Since: base-4.16.0.0 |
Defined in Data.Functor.Classes |
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 (forall a. Read a => Read1 (f a)) => 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:
instanceRead2
T whereliftReadPrec2
= ...liftReadListPrec2
=liftReadListPrec2Default
For more information, refer to the documentation for the Read
class.
Since: base-4.9.0.0
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
Read2 Either Source # | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes 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: base-4.9.0.0 |
Defined in Data.Functor.Classes 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: base-4.9.0.0 |
Defined in Data.Functor.Classes 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 # | |
Read a => Read2 ((,,) a) Source # |
Since: base-4.16.0.0 |
Defined in Data.Functor.Classes liftReadsPrec2 :: (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 # |
Since: base-4.16.0.0 |
Defined in Data.Functor.Classes liftReadsPrec2 :: (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 # |
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 (forall a. Show a => Show1 (f a)) => Show2 f where Source #
Lifting of the Show
class to binary type constructors.
Since: base-4.9.0.0
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 #
Instances
Show2 Either Source # | Since: base-4.9.0.0 |
Show2 (,) Source # | Since: base-4.9.0.0 |
Show2 (Const :: Type -> Type -> Type) Source # | Since: base-4.9.0.0 |
Show a => Show2 ((,,) a) Source # |
Since: base-4.16.0.0 |
Defined in Data.Functor.Classes | |
(Show a, Show b) => Show2 ((,,,) a b) Source # |
Since: base-4.16.0.0 |
Defined in Data.Functor.Classes |
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 #
is a parser for datatypes where each alternative
begins with a data constructor. It parses the constructor and
passes it to readsData
p dp
. 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 #
is a parser for datatypes where each alternative
begins with a data constructor. It parses the constructor and
passes it to readData
pp
. 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 #
matches the name of a unary data constructor
and then parses its argument using readsUnaryWith
rp n c n'rp
.
Since: base-4.9.0.0
readUnaryWith :: ReadPrec a -> String -> (a -> t) -> ReadPrec t Source #
matches the name of a unary data constructor
and then parses its argument using readUnaryWith
rp n c'rp
.
Since: base-4.10.0.0
readsBinaryWith :: (Int -> ReadS a) -> (Int -> ReadS b) -> String -> (a -> b -> t) -> String -> ReadS t Source #
matches the name of a binary
data constructor and then parses its arguments using readsBinaryWith
rp1 rp2 n c n'rp1
and rp2
respectively.
Since: base-4.9.0.0
readBinaryWith :: ReadPrec a -> ReadPrec b -> String -> (a -> b -> t) -> ReadPrec t Source #
matches the name of a binary
data constructor and then parses its arguments using readBinaryWith
rp1 rp2 n c'rp1
and rp2
respectively.
Since: base-4.10.0.0
showsUnaryWith :: (Int -> a -> ShowS) -> String -> Int -> a -> ShowS Source #
produces the string representation of a
unary data constructor with name showsUnaryWith
sp n d xn
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 #
produces the string
representation of a binary data constructor with name showsBinaryWith
sp1 sp2 n d x yn
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
matches the name of a unary data constructor
and then parses its argument using readsUnary
n c n'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
matches the name of a unary data constructor
and then parses its argument using readsUnary1
n c n'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
matches the name of a binary data constructor
and then parses its arguments using readsBinary1
n c n'readsPrec1
.
Since: base-4.9.0.0
showsUnary :: Show a => String -> Int -> a -> ShowS Source #
Deprecated: Use showsUnaryWith
to define liftShowsPrec
produces the string representation of a unary data
constructor with name showsUnary
n d xn
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
produces the string representation of a unary data
constructor with name showsUnary1
n d xn
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
produces the string representation of a binary
data constructor with name showsBinary1
n d x yn
and arguments x
and y
, in precedence
context d
.
Since: base-4.9.0.0