Copyright | (c) Ross Paterson 2013 |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | R.Paterson@city.ac.uk |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell98 |
Liftings of the Prelude classes Eq
, Ord
, Read
and Show
to
unary 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) => Eq (T f a) where ... instance (Ord1 f) => Ord (T f a) where ... instance (Read1 f) => Read (T f a) where ... instance (Show1 f) => Show (T f a) where ...
If these instances can be defined, defining instances of the lifted classes is mechanical:
instance (Eq1 f) => Eq1 (T f) where eq1 = (==) instance (Ord1 f) => Ord1 (T f) where compare1 = compare instance (Read1 f) => Read1 (T f) where readsPrec1 = readsPrec instance (Show1 f) => Show1 (T f) where showsPrec1 = showsPrec
- class Eq1 f where
- class Eq1 f => Ord1 f where
- class Read1 f where
- readsPrec1 :: Read a => Int -> ReadS (f a)
- class Show1 f where
- showsPrec1 :: Show a => Int -> f a -> ShowS
- readsData :: (String -> ReadS a) -> Int -> ReadS a
- 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
Lifting of the Eq
class to unary type constructors.
Eq1 [] Source | |
Eq1 Identity Source | |
Eq1 Maybe Source | |
Eq a => Eq1 (Either a) Source | |
Eq a => Eq1 ((,) a) Source | |
Eq a => Eq1 (Const a) Source | |
Eq a => Eq1 (Constant a) Source | |
Eq1 f => Eq1 (Lift f) Source | |
Eq1 f => Eq1 (IdentityT f) Source | |
Eq1 m => Eq1 (ListT m) Source | |
Eq1 m => Eq1 (MaybeT m) Source | |
Eq1 f => Eq1 (Backwards f) Source | |
Eq1 f => Eq1 (Reverse f) Source | |
(Eq e, Eq1 m) => Eq1 (ExceptT e m) Source | |
(Eq e, Eq1 m) => Eq1 (ErrorT e m) Source | |
(Eq w, Eq1 m) => Eq1 (WriterT w m) Source | |
(Eq w, Eq1 m) => Eq1 (WriterT w m) Source | |
(Functor f, Eq1 f, Eq1 g) => Eq1 (Compose f g) Source | |
(Eq1 f, Eq1 g) => Eq1 (Product f g) Source | |
(Eq1 f, Eq1 g) => Eq1 (Sum f g) Source |
class Eq1 f => Ord1 f where Source
Lifting of the Ord
class to unary type constructors.
Ord1 [] Source | |
Ord1 Identity Source | |
Ord1 Maybe Source | |
Ord a => Ord1 (Either a) Source | |
Ord a => Ord1 ((,) a) Source | |
Ord a => Ord1 (Const a) Source | |
Ord a => Ord1 (Constant a) Source | |
Ord1 f => Ord1 (Lift f) Source | |
Ord1 f => Ord1 (IdentityT f) Source | |
Ord1 m => Ord1 (ListT m) Source | |
Ord1 m => Ord1 (MaybeT m) Source | |
Ord1 f => Ord1 (Backwards f) Source | |
Ord1 f => Ord1 (Reverse f) Source | |
(Ord e, Ord1 m) => Ord1 (ExceptT e m) Source | |
(Ord e, Ord1 m) => Ord1 (ErrorT e m) Source | |
(Ord w, Ord1 m) => Ord1 (WriterT w m) Source | |
(Ord w, Ord1 m) => Ord1 (WriterT w m) Source | |
(Functor f, Ord1 f, Ord1 g) => Ord1 (Compose f g) Source | |
(Ord1 f, Ord1 g) => Ord1 (Product f g) Source | |
(Ord1 f, Ord1 g) => Ord1 (Sum f g) Source |
Lifting of the Read
class to unary type constructors.
readsPrec1 :: Read a => Int -> ReadS (f a) Source
Read1 [] Source | |
Read1 Identity Source | |
Read1 Maybe Source | |
Read a => Read1 (Either a) Source | |
Read a => Read1 ((,) a) Source | |
Read a => Read1 (Const a) Source | |
Read a => Read1 (Constant a) Source | |
Read1 f => Read1 (Lift f) Source | |
Read1 f => Read1 (IdentityT f) Source | |
Read1 m => Read1 (ListT m) Source | |
Read1 m => Read1 (MaybeT m) Source | |
Read1 f => Read1 (Backwards f) Source | |
Read1 f => Read1 (Reverse f) Source | |
(Read e, Read1 m) => Read1 (ExceptT e m) Source | |
(Read e, Read1 m) => Read1 (ErrorT e m) Source | |
(Read w, Read1 m) => Read1 (WriterT w m) Source | |
(Read w, Read1 m) => Read1 (WriterT w m) Source | |
(Functor f, Read1 f, Read1 g) => Read1 (Compose f g) Source | |
(Read1 f, Read1 g) => Read1 (Product f g) Source | |
(Read1 f, Read1 g) => Read1 (Sum f g) Source |
Lifting of the Show
class to unary type constructors.
showsPrec1 :: Show a => Int -> f a -> ShowS Source
Show1 [] Source | |
Show1 Identity Source | |
Show1 Maybe Source | |
Show a => Show1 (Either a) Source | |
Show a => Show1 ((,) a) Source | |
Show a => Show1 (Const a) Source | |
Show a => Show1 (Constant a) Source | |
Show1 f => Show1 (Lift f) Source | |
Show1 f => Show1 (IdentityT f) Source | |
Show1 m => Show1 (ListT m) Source | |
Show1 m => Show1 (MaybeT m) Source | |
Show1 f => Show1 (Backwards f) Source | |
Show1 f => Show1 (Reverse f) Source | |
(Show e, Show1 m) => Show1 (ExceptT e m) Source | |
(Show e, Show1 m) => Show1 (ErrorT e m) Source | |
(Show w, Show1 m) => Show1 (WriterT w m) Source | |
(Show w, Show1 m) => Show1 (WriterT w m) Source | |
(Functor f, Show1 f, Show1 g) => Show1 (Compose f g) Source | |
(Show1 f, Show1 g) => Show1 (Product f g) Source | |
(Show1 f, Show1 g) => Show1 (Sum f g) Source |
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 (f a) (f a)
a standard Read
instance may be defined as
instance (Read1 f, Read a) => Read (T f a) where readsPrec = readsData $ readsUnary "Zero" Zero `mappend` readsUnary1 "One" One `mappend` readsBinary1 "Two" Two
and the corresponding Show
instance as
instance (Show1 f, Show a) => Show (T f a) where showsPrec d (Zero x) = showsUnary "Zero" d x showsPrec d (One x) = showsUnary1 "One" d x showsPrec d (Two x y) = showsBinary1 "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.
readsUnary :: Read a => String -> (a -> t) -> String -> ReadS t Source
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
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
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
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
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
produces the string representation of a binary
data constructor with name showsBinary1
n d xn
and arguments x
and y
, in precedence
context d
.