Copyright | (c) Ross Paterson 2013 |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | libraries@haskell.org |
Stability | experimental |
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 readsPrec = readsPrec1 instance (Show1 f, Show a) => Show (T f a) where showsPrec = showsPrec1
Since: 4.9.0.0
- class Eq1 f where
- eq1 :: (Eq1 f, Eq a) => f a -> f a -> Bool
- class Eq1 f => Ord1 f where
- compare1 :: (Ord1 f, Ord a) => f a -> f a -> Ordering
- class Read1 f where
- readsPrec1 :: (Read1 f, Read a) => Int -> ReadS (f a)
- class Show1 f where
- showsPrec1 :: (Show1 f, Show a) => Int -> f a -> ShowS
- class Eq2 f where
- eq2 :: (Eq2 f, Eq a, Eq b) => f a b -> f a b -> Bool
- class Eq2 f => Ord2 f where
- compare2 :: (Ord2 f, Ord a, Ord b) => f a b -> f a b -> Ordering
- class Read2 f where
- readsPrec2 :: (Read2 f, Read a, Read b) => Int -> ReadS (f a b)
- class Show2 f where
- showsPrec2 :: (Show2 f, Show a, Show b) => Int -> f a b -> ShowS
- readsData :: (String -> ReadS a) -> Int -> ReadS a
- readsUnaryWith :: (Int -> ReadS a) -> String -> (a -> t) -> String -> ReadS t
- readsBinaryWith :: (Int -> ReadS a) -> (Int -> ReadS b) -> String -> (a -> b -> t) -> String -> ReadS 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
Lifting of the Eq
class to unary type constructors.
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.
eq1 :: (Eq1 f, Eq a) => f a -> f a -> Bool Source
Lift the standard (
function through the type constructor.==
)
class Eq1 f => Ord1 f where Source
Lifting of the Ord
class to unary type constructors.
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.
compare1 :: (Ord1 f, Ord a) => f a -> f a -> Ordering Source
Lift the standard compare
function through the type constructor.
Lifting of the Read
class to unary type constructors.
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.
liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [f a] Source
Read1 [] | |
Read1 Maybe | |
Read1 Identity | |
Read a => Read1 (Either a) | |
Read a => Read1 ((,) a) | |
Read a => Read1 (Const (TYPE Lifted) a) | |
(Read1 f, Read1 g) => Read1 (Product (TYPE Lifted) f g) | |
(Read1 f, Read1 g) => Read1 (Sum (TYPE Lifted) f g) | |
(Read1 f, Read1 g) => Read1 (Compose (TYPE Lifted) (TYPE Lifted) f g) | |
Lifting of the Show
class to unary type constructors.
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.
liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [f a] -> ShowS Source
Show1 [] | |
Show1 Maybe | |
Show1 Identity | |
Show a => Show1 (Either a) | |
Show a => Show1 ((,) a) | |
Show a => Show1 (Const (TYPE Lifted) a) | |
(Show1 f, Show1 g) => Show1 (Product (TYPE Lifted) f g) | |
(Show1 f, Show1 g) => Show1 (Sum (TYPE Lifted) f g) | |
(Show1 f, Show1 g) => Show1 (Compose (TYPE Lifted) (TYPE Lifted) f g) | |
For binary constructors
Lifting of the Eq
class to binary type constructors.
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.
eq2 :: (Eq2 f, Eq a, Eq b) => f a b -> f a b -> Bool Source
Lift the standard (
function through the type constructor.==
)
class Eq2 f => Ord2 f where Source
Lifting of the Ord
class to binary type constructors.
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.
compare2 :: (Ord2 f, Ord a, Ord b) => f a b -> f a b -> Ordering Source
Lift the standard compare
function through the type constructor.
Lifting of the Read
class to binary type constructors.
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.
liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [f 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.
Lifting of the Show
class to binary type constructors.
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.
liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [f 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.
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 liftReadsPrec rp rl = readsData $ readsUnaryWith rp "Zero" Zero `mappend` readsUnaryWith (liftReadsPrec rp rl) "One" One `mappend` readsBinaryWith rp (liftReadsPrec rp rl) "Two" Two
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.
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
.
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.
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
.
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
.
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
.
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
.
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
.
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
.
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
.
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
.