| 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 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
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
| Eq1 []Source# | Since: 4.9.0.0 |
| Eq1MaybeSource# | Since: 4.9.0.0 |
| Eq1NonEmptySource# | Since: 4.10.0.0 |
| Eq1DownSource# | Since: 4.12.0.0 |
| Eq1IdentitySource# | Since: 4.9.0.0 |
| Eq a =>Eq1 (Either a)Source# | Since: 4.9.0.0 |
| Eq a =>Eq1 ((,) a)Source# | Since: 4.9.0.0 |
| Eq1 (Proxy ::Type ->Type)Source# | Since: 4.9.0.0 |
| Eq a =>Eq1 (Const a ::Type ->Type)Source# | Since: 4.9.0.0 |
| (Eq1 f,Eq1 g) =>Eq1 (Sum f g)Source# | Since: 4.9.0.0 |
| (Eq1 f,Eq1 g) =>Eq1 (Product f g)Source# | Since: 4.9.0.0 |
| (Eq1 f,Eq1 g) =>Eq1 (Compose f g)Source# | Since: 4.9.0.0 |
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
| Ord1 []Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Functor.Classes Methods liftCompare :: (a -> b ->Ordering) -> [a] -> [b] ->OrderingSource# | |
| Ord1MaybeSource# | Since: 4.9.0.0 |
Instance detailsDefined inData.Functor.Classes | |
| Ord1NonEmptySource# | Since: 4.10.0.0 |
Instance detailsDefined inData.Functor.Classes | |
| Ord1DownSource# | Since: 4.12.0.0 |
Instance detailsDefined inData.Functor.Classes | |
| Ord1IdentitySource# | Since: 4.9.0.0 |
Instance detailsDefined inData.Functor.Classes | |
| Ord a =>Ord1 (Either a)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Functor.Classes | |
| Ord a =>Ord1 ((,) a)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Functor.Classes Methods liftCompare :: (a0 -> b ->Ordering) -> (a, a0) -> (a, b) ->OrderingSource# | |
| Ord1 (Proxy ::Type ->Type)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Functor.Classes | |
| Ord a =>Ord1 (Const a ::Type ->Type)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Functor.Classes | |
| (Ord1 f,Ord1 g) =>Ord1 (Sum f g)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Functor.Sum | |
| (Ord1 f,Ord1 g) =>Ord1 (Product f g)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Functor.Product | |
| (Ord1 f,Ord1 g) =>Ord1 (Compose f g)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Functor.Compose | |
compare1 :: (Ord1 f,Ord a) => f a -> f a ->OrderingSource#
Lift the standardcompare function through the type constructor.
Since: 4.9.0.0
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:
instanceRead1T whereliftReadPrec= ...liftReadListPrec=liftReadListPrecDefault
For more information, refer to the documentation for theRead class.
Since: 4.9.0.0
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 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
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
Lifting of theShow class to unary type constructors.
Since: 4.9.0.0
Minimal complete definition
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#
| Show1 []Source# | Since: 4.9.0.0 |
| Show1MaybeSource# | Since: 4.9.0.0 |
| Show1NonEmptySource# | Since: 4.10.0.0 |
| Show1DownSource# | Since: 4.12.0.0 |
| Show1IdentitySource# | Since: 4.9.0.0 |
| Show a =>Show1 (Either a)Source# | Since: 4.9.0.0 |
| Show a =>Show1 ((,) a)Source# | Since: 4.9.0.0 |
| Show1 (Proxy ::Type ->Type)Source# | Since: 4.9.0.0 |
| Show a =>Show1 (Const a ::Type ->Type)Source# | Since: 4.9.0.0 |
| (Show1 f,Show1 g) =>Show1 (Sum f g)Source# | Since: 4.9.0.0 |
| (Show1 f,Show1 g) =>Show1 (Product f g)Source# | Since: 4.9.0.0 |
| (Show1 f,Show1 g) =>Show1 (Compose f g)Source# | Since: 4.9.0.0 |
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
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
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
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:
instanceRead2T whereliftReadPrec2= ...liftReadListPrec2=liftReadListPrec2Default
For more information, refer to the documentation for theRead class. @since 4.9.0.0
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 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
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
Lifting of theShow class to binary type constructors.
Since: 4.9.0.0
Minimal complete definition
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#
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
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#
is a parser for datatypes where each alternative begins with a data constructor. It parses the constructor and passes it toreadsData p dp. 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#
is a parser for datatypes where each alternative begins with a data constructor. It parses the constructor and passes it toreadData pp. 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#
matches the name of a unary data constructor and then parses its argument usingreadsUnaryWith rp n c n'rp.
Since: 4.9.0.0
readUnaryWith ::ReadPrec a ->String -> (a -> t) ->ReadPrec tSource#
matches the name of a unary data constructor and then parses its argument usingreadUnaryWith rp n c'rp.
Since: 4.10.0.0
readsBinaryWith :: (Int ->ReadS a) -> (Int ->ReadS b) ->String -> (a -> b -> t) ->String ->ReadS tSource#
matches the name of a binary data constructor and then parses its arguments usingreadsBinaryWith rp1 rp2 n c n'rp1 andrp2 respectively.
Since: 4.9.0.0
readBinaryWith ::ReadPrec a ->ReadPrec b ->String -> (a -> b -> t) ->ReadPrec tSource#
matches the name of a binary data constructor and then parses its arguments usingreadBinaryWith rp1 rp2 n c'rp1 andrp2 respectively.
Since: 4.10.0.0
showsUnaryWith :: (Int -> a ->ShowS) ->String ->Int -> a ->ShowSSource#
produces the string representation of a unary data constructor with nameshowsUnaryWith sp n d xn and argumentx, in precedence contextd.
Since: 4.9.0.0
showsBinaryWith :: (Int -> a ->ShowS) -> (Int -> b ->ShowS) ->String ->Int -> a -> b ->ShowSSource#
produces the string representation of a binary data constructor with nameshowsBinaryWith sp1 sp2 n d x yn and argumentsx andy, in precedence contextd.
Since: 4.9.0.0
readsUnary ::Read a =>String -> (a -> t) ->String ->ReadS tSource#
Deprecated: Use readsUnaryWith to define liftReadsPrec
matches the name of a unary data constructor and then parses its argument usingreadsUnary n c n'readsPrec.
Since: 4.9.0.0
readsUnary1 :: (Read1 f,Read a) =>String -> (f a -> t) ->String ->ReadS tSource#
Deprecated: Use readsUnaryWith to define liftReadsPrec
matches the name of a unary data constructor and then parses its argument usingreadsUnary1 n c n'readsPrec1.
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
matches the name of a binary data constructor and then parses its arguments usingreadsBinary1 n c n'readsPrec1.
Since: 4.9.0.0
showsUnary ::Show a =>String ->Int -> a ->ShowSSource#
Deprecated: Use showsUnaryWith to define liftShowsPrec
produces the string representation of a unary data constructor with nameshowsUnary n d xn 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
produces the string representation of a unary data constructor with nameshowsUnary1 n d xn 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
produces the string representation of a binary data constructor with nameshowsBinary1 n d x yn and argumentsx andy, in precedence contextd.
Since: 4.9.0.0
Produced byHaddock version 2.20.0