| 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 | 
Data.Functor.Classes
Contents
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 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.
Minimal complete definition
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.
Instances
| Eq1 [] Source # | |
| Eq1 Maybe Source # | |
| Eq1 Identity Source # | |
| Eq a => Eq1 (Either a) Source # | |
| Eq a => Eq1 ((,) a) Source # | |
| Eq1 (Proxy *) Source # | Since: 4.9.0.0 | 
| Eq a => Eq1 (Const * a) Source # | |
| (Eq1 f, Eq1 g) => Eq1 (Product * f g) Source # | |
| (Eq1 f, Eq1 g) => Eq1 (Sum * f g) Source # | |
| (Eq1 f, Eq1 g) => Eq1 (Compose * * f g) Source # | |
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.
Minimal complete definition
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.
Instances
| Ord1 [] Source # | |
| Ord1 Maybe Source # | |
| Ord1 Identity Source # | |
| Ord a => Ord1 (Either a) Source # | |
| Ord a => Ord1 ((,) a) Source # | |
| Ord1 (Proxy *) Source # | Since: 4.9.0.0 | 
| Ord a => Ord1 (Const * a) Source # | |
| (Ord1 f, Ord1 g) => Ord1 (Product * f g) Source # | |
| (Ord1 f, Ord1 g) => Ord1 (Sum * f g) Source # | |
| (Ord1 f, Ord1 g) => Ord1 (Compose * * f g) Source # | |
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.
Minimal complete definition
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.
liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [f a] Source #
Instances
| Read1 [] Source # | |
| Read1 Maybe Source # | |
| Read1 Identity Source # | |
| Read a => Read1 (Either a) Source # | |
| Read a => Read1 ((,) a) Source # | |
| Read1 (Proxy *) Source # | Since: 4.9.0.0 | 
| Read a => Read1 (Const * a) Source # | |
| (Read1 f, Read1 g) => Read1 (Product * f g) Source # | |
| (Read1 f, Read1 g) => Read1 (Sum * f g) Source # | |
| (Read1 f, Read1 g) => Read1 (Compose * * f g) Source # | |
Lifting of the Show class to unary type constructors.
Minimal complete definition
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.
liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [f a] -> ShowS Source #
Instances
| Show1 [] Source # | |
| Show1 Maybe Source # | |
| Show1 Identity Source # | |
| Show a => Show1 (Either a) Source # | |
| Show a => Show1 ((,) a) Source # | |
| Show1 (Proxy *) Source # | Since: 4.9.0.0 | 
| Show a => Show1 (Const * a) Source # | |
| (Show1 f, Show1 g) => Show1 (Product * f g) Source # | |
| (Show1 f, Show1 g) => Show1 (Sum * f g) Source # | |
| (Show1 f, Show1 g) => Show1 (Compose * * f g) Source # | |
For binary constructors
Lifting of the Eq class to binary type constructors.
Minimal complete definition
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.
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.
Minimal complete definition
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.
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.
Minimal complete definition
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.
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.
Minimal complete definition
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.
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" Twoand 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 yreadsData :: (String -> ReadS a) -> Int -> ReadS a Source #
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 #
readsUnaryWith rp n c n'rp.
readsBinaryWith :: (Int -> ReadS a) -> (Int -> ReadS b) -> String -> (a -> b -> t) -> String -> ReadS t Source #
readsBinaryWith rp1 rp2 n c n'rp1 and rp2
 respectively.
showsUnaryWith :: (Int -> a -> ShowS) -> String -> Int -> a -> ShowS Source #
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 #
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
readsUnary n c n'readsPrec.
readsUnary1 :: (Read1 f, Read a) => String -> (f a -> t) -> String -> ReadS t Source #
Deprecated: Use readsUnaryWith to define liftReadsPrec
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
readsBinary1 n c n'readsPrec1.
showsUnary :: Show a => String -> Int -> a -> ShowS Source #
Deprecated: Use showsUnaryWith to define liftShowsPrec
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
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
showsBinary1 n d x yn and arguments x and y, in precedence
 context d.