{-# LANGUAGE FlexibleContexts #-}{-# LANGUAGE DefaultSignatures #-}{-# LANGUAGE InstanceSigs #-}{-# LANGUAGE Safe #-}{-# LANGUAGE TypeOperators #-}{-# LANGUAGE UndecidableInstances #-}{-# LANGUAGE QuantifiedConstraints #-}------------------------------------------------------------------------------- |-- Module : Data.Functor.Classes-- Copyright : (c) Ross Paterson 2013-- License : BSD-style (see the file LICENSE)---- Maintainer : libraries@haskell.org-- Stability : stable-- Portability : portable---- 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 4.9.0.0-----------------------------------------------------------------------------moduleData.Functor.Classes(-- * Liftings of Prelude classes-- ** For unary constructorsEq1 (..),eq1 ,Ord1 (..),compare1 ,Read1 (..),readsPrec1 ,readPrec1 ,liftReadListDefault ,liftReadListPrecDefault ,Show1 (..),showsPrec1 ,-- ** For binary constructorsEq2 (..),eq2 ,Ord2 (..),compare2 ,Read2 (..),readsPrec2 ,readPrec2 ,liftReadList2Default ,liftReadListPrec2Default ,Show2 (..),showsPrec2 ,-- * Helper functions-- $examplereadsData ,readData ,readsUnaryWith ,readUnaryWith ,readsBinaryWith ,readBinaryWith ,showsUnaryWith ,showsBinaryWith ,-- ** Obsolete helpersreadsUnary ,readsUnary1 ,readsBinary1 ,showsUnary ,showsUnary1 ,showsBinary1 ,)whereimportControl.Applicative (Alternative ((<|>) ),Const (Const ))importData.Functor.Identity (Identity (Identity ))importData.Proxy (Proxy (Proxy ))importData.List.NonEmpty (NonEmpty (..))importData.Ord (Down (Down ))importData.Complex (Complex ((:+) ))importGHC.Generics (Generic1 (..),Generically1 (..))importGHC.Tuple (Solo (..))importGHC.Read (expectP ,list ,paren )importText.ParserCombinators.ReadPrec (ReadPrec ,readPrec_to_S ,readS_to_Prec )importText.Read (Read (..),parens ,prec ,step )importText.Read.Lex (Lexeme (..))importText.Show (showListWith )-- $setup-- >>> import Prelude-- >>> import Data.Complex (Complex (..))-- >>> import Text.ParserCombinators.ReadPrec-- | 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 4.9.0.0class(foralla .Eq a =>Eq (f a ))=>Eq1 f where-- | 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.0liftEq ::(a ->b ->Bool )->f a ->f b ->Bool defaultliftEq ::(f ~ f' c ,Eq2 f' ,Eq c )=>(a ->b ->Bool )->f a ->f b ->Bool liftEq =(c -> c -> Bool) -> (a -> b -> Bool) -> f' c a -> f' c b -> Bool
forall a b c d.
(a -> b -> Bool) -> (c -> d -> Bool) -> f' a c -> f' b d -> Bool
forall (f :: * -> * -> *) a b c d.
Eq2 f =>
(a -> b -> Bool) -> (c -> d -> Bool) -> f a c -> f b d -> Bool
liftEq2 c -> c -> Bool
forall a. Eq a => a -> a -> Bool
(==) -- | Lift the standard @('==')@ function through the type constructor.---- @since 4.9.0.0eq1 ::(Eq1 f ,Eq a )=>f a ->f a ->Bool eq1 :: forall (f :: * -> *) a. (Eq1 f, Eq a) => f a -> f a -> Bool
eq1 =(a -> a -> Bool) -> f a -> f a -> Bool
forall a b. (a -> b -> Bool) -> f a -> f b -> Bool
forall (f :: * -> *) a b.
Eq1 f =>
(a -> b -> Bool) -> f a -> f b -> Bool
liftEq a -> a -> Bool
forall a. Eq a => a -> a -> Bool
(==) -- | 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 4.9.0.0class(Eq1 f ,foralla .Ord a =>Ord (f a ))=>Ord1 f where-- | 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 4.9.0.0liftCompare ::(a ->b ->Ordering )->f a ->f b ->Ordering defaultliftCompare ::(f ~ f' c ,Ord2 f' ,Ord c )=>(a ->b ->Ordering )->f a ->f b ->Ordering liftCompare =(c -> c -> Ordering)
-> (a -> b -> Ordering) -> f' c a -> f' c b -> Ordering
forall a b c d.
(a -> b -> Ordering)
-> (c -> d -> Ordering) -> f' a c -> f' b d -> Ordering
forall (f :: * -> * -> *) a b c d.
Ord2 f =>
(a -> b -> Ordering)
-> (c -> d -> Ordering) -> f a c -> f b d -> Ordering
liftCompare2 c -> c -> Ordering
forall a. Ord a => a -> a -> Ordering
compare -- | Lift the standard 'compare' function through the type constructor.---- @since 4.9.0.0compare1 ::(Ord1 f ,Ord a )=>f a ->f a ->Ordering compare1 :: forall (f :: * -> *) a. (Ord1 f, Ord a) => f a -> f a -> Ordering
compare1 =(a -> a -> Ordering) -> f a -> f a -> Ordering
forall a b. (a -> b -> Ordering) -> f a -> f b -> Ordering
forall (f :: * -> *) a b.
Ord1 f =>
(a -> b -> Ordering) -> f a -> f b -> Ordering
liftCompare a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare -- | 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:---- @-- instance 'Read1' T where-- 'liftReadPrec' = ...-- 'liftReadListPrec' = 'liftReadListPrecDefault'-- @---- For more information, refer to the documentation for the 'Read' class.---- @since 4.9.0.0class(foralla .Read a =>Read (f a ))=>Read1 f where{-# MINIMALliftReadsPrec |liftReadPrec #-}-- | 'readsPrec' function for an application of the type constructor-- based on 'readsPrec' and 'readList' functions for the argument type.---- @since 4.9.0.0liftReadsPrec ::(Int ->ReadS a )->ReadS [a ]->Int ->ReadS (f a )liftReadsPrec Int -> ReadS a
rp ReadS [a]
rl =ReadPrec (f a) -> Int -> ReadS (f a)
forall a. ReadPrec a -> Int -> ReadS a
readPrec_to_S (ReadPrec (f a) -> Int -> ReadS (f a))
-> ReadPrec (f a) -> Int -> ReadS (f a)
forall a b. (a -> b) -> a -> b
$ ReadPrec a -> ReadPrec [a] -> ReadPrec (f a)
forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec (f a)
forall (f :: * -> *) a.
Read1 f =>
ReadPrec a -> ReadPrec [a] -> ReadPrec (f a)
liftReadPrec ((Int -> ReadS a) -> ReadPrec a
forall a. (Int -> ReadS a) -> ReadPrec a
readS_to_Prec Int -> ReadS a
rp )((Int -> ReadS [a]) -> ReadPrec [a]
forall a. (Int -> ReadS a) -> ReadPrec a
readS_to_Prec (ReadS [a] -> Int -> ReadS [a]
forall a b. a -> b -> a
const ReadS [a]
rl ))-- | '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 4.9.0.0liftReadList ::(Int ->ReadS a )->ReadS [a ]->ReadS [f a ]liftReadList Int -> ReadS a
rp ReadS [a]
rl =ReadPrec [f a] -> Int -> ReadS [f a]
forall a. ReadPrec a -> Int -> ReadS a
readPrec_to_S (ReadPrec (f a) -> ReadPrec [f a]
forall a. ReadPrec a -> ReadPrec [a]
list (ReadPrec (f a) -> ReadPrec [f a])
-> ReadPrec (f a) -> ReadPrec [f a]
forall a b. (a -> b) -> a -> b
$ ReadPrec a -> ReadPrec [a] -> ReadPrec (f a)
forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec (f a)
forall (f :: * -> *) a.
Read1 f =>
ReadPrec a -> ReadPrec [a] -> ReadPrec (f a)
liftReadPrec ((Int -> ReadS a) -> ReadPrec a
forall a. (Int -> ReadS a) -> ReadPrec a
readS_to_Prec Int -> ReadS a
rp )((Int -> ReadS [a]) -> ReadPrec [a]
forall a. (Int -> ReadS a) -> ReadPrec a
readS_to_Prec (ReadS [a] -> Int -> ReadS [a]
forall a b. a -> b -> a
const ReadS [a]
rl )))Int
0-- | 'readPrec' function for an application of the type constructor-- based on 'readPrec' and 'readListPrec' functions for the argument type.---- @since 4.10.0.0liftReadPrec ::ReadPrec a ->ReadPrec [a ]->ReadPrec (f a )liftReadPrec ReadPrec a
rp ReadPrec [a]
rl =(Int -> ReadS (f a)) -> ReadPrec (f a)
forall a. (Int -> ReadS a) -> ReadPrec a
readS_to_Prec ((Int -> ReadS (f a)) -> ReadPrec (f a))
-> (Int -> ReadS (f a)) -> ReadPrec (f a)
forall a b. (a -> b) -> a -> b
$ (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (f a)
forall a. (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (f a)
forall (f :: * -> *) a.
Read1 f =>
(Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (f a)
liftReadsPrec (ReadPrec a -> Int -> ReadS a
forall a. ReadPrec a -> Int -> ReadS a
readPrec_to_S ReadPrec a
rp )(ReadPrec [a] -> Int -> ReadS [a]
forall a. ReadPrec a -> Int -> ReadS a
readPrec_to_S ReadPrec [a]
rl Int
0)-- | '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 4.10.0.0liftReadListPrec ::ReadPrec a ->ReadPrec [a ]->ReadPrec [f a ]liftReadListPrec ReadPrec a
rp ReadPrec [a]
rl =(Int -> ReadS [f a]) -> ReadPrec [f a]
forall a. (Int -> ReadS a) -> ReadPrec a
readS_to_Prec ((Int -> ReadS [f a]) -> ReadPrec [f a])
-> (Int -> ReadS [f a]) -> ReadPrec [f a]
forall a b. (a -> b) -> a -> b
$ \Int
_->(Int -> ReadS a) -> ReadS [a] -> ReadS [f a]
forall a. (Int -> ReadS a) -> ReadS [a] -> ReadS [f a]
forall (f :: * -> *) a.
Read1 f =>
(Int -> ReadS a) -> ReadS [a] -> ReadS [f a]
liftReadList (ReadPrec a -> Int -> ReadS a
forall a. ReadPrec a -> Int -> ReadS a
readPrec_to_S ReadPrec a
rp )(ReadPrec [a] -> Int -> ReadS [a]
forall a. ReadPrec a -> Int -> ReadS a
readPrec_to_S ReadPrec [a]
rl Int
0)-- | Lift the standard 'readsPrec' and 'readList' functions through the-- type constructor.---- @since 4.9.0.0readsPrec1 ::(Read1 f ,Read a )=>Int ->ReadS (f a )readsPrec1 :: forall (f :: * -> *) a. (Read1 f, Read a) => Int -> ReadS (f a)
readsPrec1 =(Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (f a)
forall a. (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (f a)
forall (f :: * -> *) a.
Read1 f =>
(Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (f a)
liftReadsPrec Int -> ReadS a
forall a. Read a => Int -> ReadS a
readsPrec ReadS [a]
forall a. Read a => ReadS [a]
readList -- | Lift the standard 'readPrec' and 'readListPrec' functions through the-- type constructor.---- @since 4.10.0.0readPrec1 ::(Read1 f ,Read a )=>ReadPrec (f a )readPrec1 :: forall (f :: * -> *) a. (Read1 f, Read a) => ReadPrec (f a)
readPrec1 =ReadPrec a -> ReadPrec [a] -> ReadPrec (f a)
forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec (f a)
forall (f :: * -> *) a.
Read1 f =>
ReadPrec a -> ReadPrec [a] -> ReadPrec (f a)
liftReadPrec ReadPrec a
forall a. Read a => ReadPrec a
readPrec ReadPrec [a]
forall a. Read a => ReadPrec [a]
readListPrec -- | A possible replacement definition for the 'liftReadList' method.-- This is only needed for 'Read1' instances where 'liftReadListPrec' isn't-- defined as 'liftReadListPrecDefault'.---- @since 4.10.0.0liftReadListDefault ::Read1 f =>(Int ->ReadS a )->ReadS [a ]->ReadS [f a ]liftReadListDefault :: forall (f :: * -> *) a.
Read1 f =>
(Int -> ReadS a) -> ReadS [a] -> ReadS [f a]
liftReadListDefault Int -> ReadS a
rp ReadS [a]
rl =ReadPrec [f a] -> Int -> ReadS [f a]
forall a. ReadPrec a -> Int -> ReadS a
readPrec_to_S (ReadPrec a -> ReadPrec [a] -> ReadPrec [f a]
forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec [f a]
forall (f :: * -> *) a.
Read1 f =>
ReadPrec a -> ReadPrec [a] -> ReadPrec [f a]
liftReadListPrec ((Int -> ReadS a) -> ReadPrec a
forall a. (Int -> ReadS a) -> ReadPrec a
readS_to_Prec Int -> ReadS a
rp )((Int -> ReadS [a]) -> ReadPrec [a]
forall a. (Int -> ReadS a) -> ReadPrec a
readS_to_Prec (ReadS [a] -> Int -> ReadS [a]
forall a b. a -> b -> a
const ReadS [a]
rl )))Int
0-- | A possible replacement definition for the 'liftReadListPrec' method,-- defined using 'liftReadPrec'.---- @since 4.10.0.0liftReadListPrecDefault ::Read1 f =>ReadPrec a ->ReadPrec [a ]->ReadPrec [f a ]liftReadListPrecDefault :: forall (f :: * -> *) a.
Read1 f =>
ReadPrec a -> ReadPrec [a] -> ReadPrec [f a]
liftReadListPrecDefault ReadPrec a
rp ReadPrec [a]
rl =ReadPrec (f a) -> ReadPrec [f a]
forall a. ReadPrec a -> ReadPrec [a]
list (ReadPrec a -> ReadPrec [a] -> ReadPrec (f a)
forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec (f a)
forall (f :: * -> *) a.
Read1 f =>
ReadPrec a -> ReadPrec [a] -> ReadPrec (f a)
liftReadPrec ReadPrec a
rp ReadPrec [a]
rl )-- | 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 4.9.0.0class(foralla .Show a =>Show (f a ))=>Show1 f where-- | 'showsPrec' function for an application of the type constructor-- based on 'showsPrec' and 'showList' functions for the argument type.---- @since 4.9.0.0liftShowsPrec ::(Int ->a ->ShowS )->([a ]->ShowS )->Int ->f a ->ShowS defaultliftShowsPrec ::(f ~ f' b ,Show2 f' ,Show b )=>(Int ->a ->ShowS )->([a ]->ShowS )->Int ->f a ->ShowS liftShowsPrec =(Int -> b -> ShowS)
-> ([b] -> ShowS)
-> (Int -> a -> ShowS)
-> ([a] -> ShowS)
-> Int
-> f' b a
-> ShowS
forall a b.
(Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> b -> ShowS)
-> ([b] -> ShowS)
-> Int
-> f' a b
-> ShowS
forall (f :: * -> * -> *) a b.
Show2 f =>
(Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> b -> ShowS)
-> ([b] -> ShowS)
-> Int
-> f a b
-> ShowS
liftShowsPrec2 Int -> b -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec [b] -> ShowS
forall a. Show a => [a] -> ShowS
showList -- | 'showList' function for an application of the type constructor-- based on 'showsPrec' and 'showList' functions for the argument type.-- The default implementation using standard list syntax is correct-- for most types.---- @since 4.9.0.0liftShowList ::(Int ->a ->ShowS )->([a ]->ShowS )->[f a ]->ShowS liftShowList Int -> a -> ShowS
sp [a] -> ShowS
sl =(f a -> ShowS) -> [f a] -> ShowS
forall a. (a -> ShowS) -> [a] -> ShowS
showListWith ((Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS
forall a.
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS
forall (f :: * -> *) a.
Show1 f =>
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS
liftShowsPrec Int -> a -> ShowS
sp [a] -> ShowS
sl Int
0)-- | Lift the standard 'showsPrec' and 'showList' functions through the-- type constructor.---- @since 4.9.0.0showsPrec1 ::(Show1 f ,Show a )=>Int ->f a ->ShowS showsPrec1 :: forall (f :: * -> *) a. (Show1 f, Show a) => Int -> f a -> ShowS
showsPrec1 =(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS
forall a.
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS
forall (f :: * -> *) a.
Show1 f =>
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS
liftShowsPrec Int -> a -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec [a] -> ShowS
forall a. Show a => [a] -> ShowS
showList -- | Lifting of the 'Eq' class to binary type constructors.---- @since 4.9.0.0class(foralla .Eq a =>Eq1 (f a ))=>Eq2 f where-- | 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.0liftEq2 ::(a ->b ->Bool )->(c ->d ->Bool )->f a c ->f b d ->Bool -- | Lift the standard @('==')@ function through the type constructor.---- @since 4.9.0.0eq2 ::(Eq2 f ,Eq a ,Eq b )=>f a b ->f a b ->Bool eq2 :: forall (f :: * -> * -> *) a b.
(Eq2 f, Eq a, Eq b) =>
f a b -> f a b -> Bool
eq2 =(a -> a -> Bool) -> (b -> b -> Bool) -> f a b -> f a b -> Bool
forall a b c d.
(a -> b -> Bool) -> (c -> d -> Bool) -> f a c -> f b d -> Bool
forall (f :: * -> * -> *) a b c d.
Eq2 f =>
(a -> b -> Bool) -> (c -> d -> Bool) -> f a c -> f b d -> Bool
liftEq2 a -> a -> Bool
forall a. Eq a => a -> a -> Bool
(==) b -> b -> Bool
forall a. Eq a => a -> a -> Bool
(==) -- | Lifting of the 'Ord' class to binary type constructors.---- @since 4.9.0.0class(Eq2 f ,foralla .Ord a =>Ord1 (f a ))=>Ord2 f where-- | 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 4.9.0.0liftCompare2 ::(a ->b ->Ordering )->(c ->d ->Ordering )->f a c ->f b d ->Ordering -- | Lift the standard 'compare' function through the type constructor.---- @since 4.9.0.0compare2 ::(Ord2 f ,Ord a ,Ord b )=>f a b ->f a b ->Ordering compare2 :: forall (f :: * -> * -> *) a b.
(Ord2 f, Ord a, Ord b) =>
f a b -> f a b -> Ordering
compare2 =(a -> a -> Ordering)
-> (b -> b -> Ordering) -> f a b -> f a b -> Ordering
forall a b c d.
(a -> b -> Ordering)
-> (c -> d -> Ordering) -> f a c -> f b d -> Ordering
forall (f :: * -> * -> *) a b c d.
Ord2 f =>
(a -> b -> Ordering)
-> (c -> d -> Ordering) -> f a c -> f b d -> Ordering
liftCompare2 a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare b -> b -> Ordering
forall a. Ord a => a -> a -> Ordering
compare -- | 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:---- @-- instance 'Read2' T where-- 'liftReadPrec2' = ...-- 'liftReadListPrec2' = 'liftReadListPrec2Default'-- @---- For more information, refer to the documentation for the 'Read' class.---- @since 4.9.0.0class(foralla .Read a =>Read1 (f a ))=>Read2 f where{-# MINIMALliftReadsPrec2 |liftReadPrec2 #-}-- | 'readsPrec' function for an application of the type constructor-- based on 'readsPrec' and 'readList' functions for the argument types.---- @since 4.9.0.0liftReadsPrec2 ::(Int ->ReadS a )->ReadS [a ]->(Int ->ReadS b )->ReadS [b ]->Int ->ReadS (f a b )liftReadsPrec2 Int -> ReadS a
rp1 ReadS [a]
rl1 Int -> ReadS b
rp2 ReadS [b]
rl2 =ReadPrec (f a b) -> Int -> ReadS (f a b)
forall a. ReadPrec a -> Int -> ReadS a
readPrec_to_S (ReadPrec (f a b) -> Int -> ReadS (f a b))
-> ReadPrec (f a b) -> Int -> ReadS (f a b)
forall a b. (a -> b) -> a -> b
$ ReadPrec a
-> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (f a b)
forall a b.
ReadPrec a
-> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (f a b)
forall (f :: * -> * -> *) a b.
Read2 f =>
ReadPrec a
-> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (f a b)
liftReadPrec2 ((Int -> ReadS a) -> ReadPrec a
forall a. (Int -> ReadS a) -> ReadPrec a
readS_to_Prec Int -> ReadS a
rp1 )((Int -> ReadS [a]) -> ReadPrec [a]
forall a. (Int -> ReadS a) -> ReadPrec a
readS_to_Prec (ReadS [a] -> Int -> ReadS [a]
forall a b. a -> b -> a
const ReadS [a]
rl1 ))((Int -> ReadS b) -> ReadPrec b
forall a. (Int -> ReadS a) -> ReadPrec a
readS_to_Prec Int -> ReadS b
rp2 )((Int -> ReadS [b]) -> ReadPrec [b]
forall a. (Int -> ReadS a) -> ReadPrec a
readS_to_Prec (ReadS [b] -> Int -> ReadS [b]
forall a b. a -> b -> a
const ReadS [b]
rl2 ))-- | '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 4.9.0.0liftReadList2 ::(Int ->ReadS a )->ReadS [a ]->(Int ->ReadS b )->ReadS [b ]->ReadS [f a b ]liftReadList2 Int -> ReadS a
rp1 ReadS [a]
rl1 Int -> ReadS b
rp2 ReadS [b]
rl2 =ReadPrec [f a b] -> Int -> ReadS [f a b]
forall a. ReadPrec a -> Int -> ReadS a
readPrec_to_S (ReadPrec (f a b) -> ReadPrec [f a b]
forall a. ReadPrec a -> ReadPrec [a]
list (ReadPrec (f a b) -> ReadPrec [f a b])
-> ReadPrec (f a b) -> ReadPrec [f a b]
forall a b. (a -> b) -> a -> b
$ ReadPrec a
-> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (f a b)
forall a b.
ReadPrec a
-> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (f a b)
forall (f :: * -> * -> *) a b.
Read2 f =>
ReadPrec a
-> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (f a b)
liftReadPrec2 ((Int -> ReadS a) -> ReadPrec a
forall a. (Int -> ReadS a) -> ReadPrec a
readS_to_Prec Int -> ReadS a
rp1 )((Int -> ReadS [a]) -> ReadPrec [a]
forall a. (Int -> ReadS a) -> ReadPrec a
readS_to_Prec (ReadS [a] -> Int -> ReadS [a]
forall a b. a -> b -> a
const ReadS [a]
rl1 ))((Int -> ReadS b) -> ReadPrec b
forall a. (Int -> ReadS a) -> ReadPrec a
readS_to_Prec Int -> ReadS b
rp2 )((Int -> ReadS [b]) -> ReadPrec [b]
forall a. (Int -> ReadS a) -> ReadPrec a
readS_to_Prec (ReadS [b] -> Int -> ReadS [b]
forall a b. a -> b -> a
const ReadS [b]
rl2 )))Int
0-- | 'readPrec' function for an application of the type constructor-- based on 'readPrec' and 'readListPrec' functions for the argument types.---- @since 4.10.0.0liftReadPrec2 ::ReadPrec a ->ReadPrec [a ]->ReadPrec b ->ReadPrec [b ]->ReadPrec (f a b )liftReadPrec2 ReadPrec a
rp1 ReadPrec [a]
rl1 ReadPrec b
rp2 ReadPrec [b]
rl2 =(Int -> ReadS (f a b)) -> ReadPrec (f a b)
forall a. (Int -> ReadS a) -> ReadPrec a
readS_to_Prec ((Int -> ReadS (f a b)) -> ReadPrec (f a b))
-> (Int -> ReadS (f a b)) -> ReadPrec (f a b)
forall a b. (a -> b) -> a -> b
$ (Int -> ReadS a)
-> ReadS [a]
-> (Int -> ReadS b)
-> ReadS [b]
-> Int
-> ReadS (f a b)
forall a b.
(Int -> ReadS a)
-> ReadS [a]
-> (Int -> ReadS b)
-> ReadS [b]
-> Int
-> ReadS (f a b)
forall (f :: * -> * -> *) a b.
Read2 f =>
(Int -> ReadS a)
-> ReadS [a]
-> (Int -> ReadS b)
-> ReadS [b]
-> Int
-> ReadS (f a b)
liftReadsPrec2 (ReadPrec a -> Int -> ReadS a
forall a. ReadPrec a -> Int -> ReadS a
readPrec_to_S ReadPrec a
rp1 )(ReadPrec [a] -> Int -> ReadS [a]
forall a. ReadPrec a -> Int -> ReadS a
readPrec_to_S ReadPrec [a]
rl1 Int
0)(ReadPrec b -> Int -> ReadS b
forall a. ReadPrec a -> Int -> ReadS a
readPrec_to_S ReadPrec b
rp2 )(ReadPrec [b] -> Int -> ReadS [b]
forall a. ReadPrec a -> Int -> ReadS a
readPrec_to_S ReadPrec [b]
rl2 Int
0)-- | '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 4.10.0.0liftReadListPrec2 ::ReadPrec a ->ReadPrec [a ]->ReadPrec b ->ReadPrec [b ]->ReadPrec [f a b ]liftReadListPrec2 ReadPrec a
rp1 ReadPrec [a]
rl1 ReadPrec b
rp2 ReadPrec [b]
rl2 =(Int -> ReadS [f a b]) -> ReadPrec [f a b]
forall a. (Int -> ReadS a) -> ReadPrec a
readS_to_Prec ((Int -> ReadS [f a b]) -> ReadPrec [f a b])
-> (Int -> ReadS [f a b]) -> ReadPrec [f a b]
forall a b. (a -> b) -> a -> b
$ \Int
_->(Int -> ReadS a)
-> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [f a b]
forall a b.
(Int -> ReadS a)
-> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [f a b]
forall (f :: * -> * -> *) a b.
Read2 f =>
(Int -> ReadS a)
-> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [f a b]
liftReadList2 (ReadPrec a -> Int -> ReadS a
forall a. ReadPrec a -> Int -> ReadS a
readPrec_to_S ReadPrec a
rp1 )(ReadPrec [a] -> Int -> ReadS [a]
forall a. ReadPrec a -> Int -> ReadS a
readPrec_to_S ReadPrec [a]
rl1 Int
0)(ReadPrec b -> Int -> ReadS b
forall a. ReadPrec a -> Int -> ReadS a
readPrec_to_S ReadPrec b
rp2 )(ReadPrec [b] -> Int -> ReadS [b]
forall a. ReadPrec a -> Int -> ReadS a
readPrec_to_S ReadPrec [b]
rl2 Int
0)-- | Lift the standard 'readsPrec' function through the type constructor.---- @since 4.9.0.0readsPrec2 ::(Read2 f ,Read a ,Read b )=>Int ->ReadS (f a b )readsPrec2 :: forall (f :: * -> * -> *) a b.
(Read2 f, Read a, Read b) =>
Int -> ReadS (f a b)
readsPrec2 =(Int -> ReadS a)
-> ReadS [a]
-> (Int -> ReadS b)
-> ReadS [b]
-> Int
-> ReadS (f a b)
forall a b.
(Int -> ReadS a)
-> ReadS [a]
-> (Int -> ReadS b)
-> ReadS [b]
-> Int
-> ReadS (f a b)
forall (f :: * -> * -> *) a b.
Read2 f =>
(Int -> ReadS a)
-> ReadS [a]
-> (Int -> ReadS b)
-> ReadS [b]
-> Int
-> ReadS (f a b)
liftReadsPrec2 Int -> ReadS a
forall a. Read a => Int -> ReadS a
readsPrec ReadS [a]
forall a. Read a => ReadS [a]
readList Int -> ReadS b
forall a. Read a => Int -> ReadS a
readsPrec ReadS [b]
forall a. Read a => ReadS [a]
readList -- | Lift the standard 'readPrec' function through the type constructor.---- @since 4.10.0.0readPrec2 ::(Read2 f ,Read a ,Read b )=>ReadPrec (f a b )readPrec2 :: forall (f :: * -> * -> *) a b.
(Read2 f, Read a, Read b) =>
ReadPrec (f a b)
readPrec2 =ReadPrec a
-> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (f a b)
forall a b.
ReadPrec a
-> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (f a b)
forall (f :: * -> * -> *) a b.
Read2 f =>
ReadPrec a
-> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (f a b)
liftReadPrec2 ReadPrec a
forall a. Read a => ReadPrec a
readPrec ReadPrec [a]
forall a. Read a => ReadPrec [a]
readListPrec ReadPrec b
forall a. Read a => ReadPrec a
readPrec ReadPrec [b]
forall a. Read a => ReadPrec [a]
readListPrec -- | A possible replacement definition for the 'liftReadList2' method.-- This is only needed for 'Read2' instances where 'liftReadListPrec2' isn't-- defined as 'liftReadListPrec2Default'.---- @since 4.10.0.0liftReadList2Default ::Read2 f =>(Int ->ReadS a )->ReadS [a ]->(Int ->ReadS b )->ReadS [b ]->ReadS [f a b ]liftReadList2Default :: forall (f :: * -> * -> *) a b.
Read2 f =>
(Int -> ReadS a)
-> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [f a b]
liftReadList2Default Int -> ReadS a
rp1 ReadS [a]
rl1 Int -> ReadS b
rp2 ReadS [b]
rl2 =ReadPrec [f a b] -> Int -> ReadS [f a b]
forall a. ReadPrec a -> Int -> ReadS a
readPrec_to_S (ReadPrec a
-> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [f a b]
forall a b.
ReadPrec a
-> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [f a b]
forall (f :: * -> * -> *) a b.
Read2 f =>
ReadPrec a
-> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [f a b]
liftReadListPrec2 ((Int -> ReadS a) -> ReadPrec a
forall a. (Int -> ReadS a) -> ReadPrec a
readS_to_Prec Int -> ReadS a
rp1 )((Int -> ReadS [a]) -> ReadPrec [a]
forall a. (Int -> ReadS a) -> ReadPrec a
readS_to_Prec (ReadS [a] -> Int -> ReadS [a]
forall a b. a -> b -> a
const ReadS [a]
rl1 ))((Int -> ReadS b) -> ReadPrec b
forall a. (Int -> ReadS a) -> ReadPrec a
readS_to_Prec Int -> ReadS b
rp2 )((Int -> ReadS [b]) -> ReadPrec [b]
forall a. (Int -> ReadS a) -> ReadPrec a
readS_to_Prec (ReadS [b] -> Int -> ReadS [b]
forall a b. a -> b -> a
const ReadS [b]
rl2 )))Int
0-- | A possible replacement definition for the 'liftReadListPrec2' method,-- defined using 'liftReadPrec2'.---- @since 4.10.0.0liftReadListPrec2Default ::Read2 f =>ReadPrec a ->ReadPrec [a ]->ReadPrec b ->ReadPrec [b ]->ReadPrec [f a b ]liftReadListPrec2Default :: forall (f :: * -> * -> *) a b.
Read2 f =>
ReadPrec a
-> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [f a b]
liftReadListPrec2Default ReadPrec a
rp1 ReadPrec [a]
rl1 ReadPrec b
rp2 ReadPrec [b]
rl2 =ReadPrec (f a b) -> ReadPrec [f a b]
forall a. ReadPrec a -> ReadPrec [a]
list (ReadPrec a
-> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (f a b)
forall a b.
ReadPrec a
-> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (f a b)
forall (f :: * -> * -> *) a b.
Read2 f =>
ReadPrec a
-> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (f a b)
liftReadPrec2 ReadPrec a
rp1 ReadPrec [a]
rl1 ReadPrec b
rp2 ReadPrec [b]
rl2 )-- | Lifting of the 'Show' class to binary type constructors.---- @since 4.9.0.0class(foralla .Show a =>Show1 (f a ))=>Show2 f where-- | 'showsPrec' function for an application of the type constructor-- based on 'showsPrec' and 'showList' functions for the argument types.---- @since 4.9.0.0liftShowsPrec2 ::(Int ->a ->ShowS )->([a ]->ShowS )->(Int ->b ->ShowS )->([b ]->ShowS )->Int ->f a b ->ShowS -- | 'showList' function for an application of the type constructor-- based on 'showsPrec' and 'showList' functions for the argument types.-- The default implementation using standard list syntax is correct-- for most types.---- @since 4.9.0.0liftShowList2 ::(Int ->a ->ShowS )->([a ]->ShowS )->(Int ->b ->ShowS )->([b ]->ShowS )->[f a b ]->ShowS liftShowList2 Int -> a -> ShowS
sp1 [a] -> ShowS
sl1 Int -> b -> ShowS
sp2 [b] -> ShowS
sl2 =(f a b -> ShowS) -> [f a b] -> ShowS
forall a. (a -> ShowS) -> [a] -> ShowS
showListWith ((Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> b -> ShowS)
-> ([b] -> ShowS)
-> Int
-> f a b
-> ShowS
forall a b.
(Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> b -> ShowS)
-> ([b] -> ShowS)
-> Int
-> f a b
-> ShowS
forall (f :: * -> * -> *) a b.
Show2 f =>
(Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> b -> ShowS)
-> ([b] -> ShowS)
-> Int
-> f a b
-> ShowS
liftShowsPrec2 Int -> a -> ShowS
sp1 [a] -> ShowS
sl1 Int -> b -> ShowS
sp2 [b] -> ShowS
sl2 Int
0)-- | Lift the standard 'showsPrec' function through the type constructor.---- @since 4.9.0.0showsPrec2 ::(Show2 f ,Show a ,Show b )=>Int ->f a b ->ShowS showsPrec2 :: forall (f :: * -> * -> *) a b.
(Show2 f, Show a, Show b) =>
Int -> f a b -> ShowS
showsPrec2 =(Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> b -> ShowS)
-> ([b] -> ShowS)
-> Int
-> f a b
-> ShowS
forall a b.
(Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> b -> ShowS)
-> ([b] -> ShowS)
-> Int
-> f a b
-> ShowS
forall (f :: * -> * -> *) a b.
Show2 f =>
(Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> b -> ShowS)
-> ([b] -> ShowS)
-> Int
-> f a b
-> ShowS
liftShowsPrec2 Int -> a -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec [a] -> ShowS
forall a. Show a => [a] -> ShowS
showList Int -> b -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec [b] -> ShowS
forall a. Show a => [a] -> ShowS
showList -- Instances for Prelude type constructors-- | @since 4.9.0.0instanceEq1 Maybe whereliftEq :: forall a b. (a -> b -> Bool) -> Maybe a -> Maybe b -> Bool
liftEq a -> b -> Bool
_Maybe a
Nothing Maybe b
Nothing =Bool
True liftEq a -> b -> Bool
_Maybe a
Nothing (Just b
_)=Bool
False liftEq a -> b -> Bool
_(Just a
_)Maybe b
Nothing =Bool
False liftEq a -> b -> Bool
eq (Just a
x )(Just b
y )=a -> b -> Bool
eq a
x b
y -- | @since 4.9.0.0instanceOrd1 Maybe whereliftCompare :: forall a b. (a -> b -> Ordering) -> Maybe a -> Maybe b -> Ordering
liftCompare a -> b -> Ordering
_Maybe a
Nothing Maybe b
Nothing =Ordering
EQ liftCompare a -> b -> Ordering
_Maybe a
Nothing (Just b
_)=Ordering
LT liftCompare a -> b -> Ordering
_(Just a
_)Maybe b
Nothing =Ordering
GT liftCompare a -> b -> Ordering
comp (Just a
x )(Just b
y )=a -> b -> Ordering
comp a
x b
y -- | @since 4.9.0.0instanceRead1 Maybe whereliftReadPrec :: forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec (Maybe a)
liftReadPrec ReadPrec a
rp ReadPrec [a]
_=ReadPrec (Maybe a) -> ReadPrec (Maybe a)
forall a. ReadPrec a -> ReadPrec a
parens (Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident String
"Nothing")ReadPrec () -> ReadPrec (Maybe a) -> ReadPrec (Maybe a)
forall a b. ReadPrec a -> ReadPrec b -> ReadPrec b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Maybe a -> ReadPrec (Maybe a)
forall a. a -> ReadPrec a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe a
forall a. Maybe a
Nothing )ReadPrec (Maybe a) -> ReadPrec (Maybe a) -> ReadPrec (Maybe a)
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ReadPrec (Maybe a) -> ReadPrec (Maybe a)
forall a. ReadPrec a -> ReadPrec a
readData (ReadPrec a -> String -> (a -> Maybe a) -> ReadPrec (Maybe a)
forall a t. ReadPrec a -> String -> (a -> t) -> ReadPrec t
readUnaryWith ReadPrec a
rp String
"Just"a -> Maybe a
forall a. a -> Maybe a
Just )liftReadListPrec :: forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec [Maybe a]
liftReadListPrec =ReadPrec a -> ReadPrec [a] -> ReadPrec [Maybe a]
forall (f :: * -> *) a.
Read1 f =>
ReadPrec a -> ReadPrec [a] -> ReadPrec [f a]
liftReadListPrecDefault liftReadList :: forall a. (Int -> ReadS a) -> ReadS [a] -> ReadS [Maybe a]
liftReadList =(Int -> ReadS a) -> ReadS [a] -> ReadS [Maybe a]
forall (f :: * -> *) a.
Read1 f =>
(Int -> ReadS a) -> ReadS [a] -> ReadS [f a]
liftReadListDefault -- | @since 4.9.0.0instanceShow1 Maybe whereliftShowsPrec :: forall a.
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Maybe a -> ShowS
liftShowsPrec Int -> a -> ShowS
_[a] -> ShowS
_Int
_Maybe a
Nothing =String -> ShowS
showString String
"Nothing"liftShowsPrec Int -> a -> ShowS
sp [a] -> ShowS
_Int
d (Just a
x )=(Int -> a -> ShowS) -> String -> Int -> a -> ShowS
forall a. (Int -> a -> ShowS) -> String -> Int -> a -> ShowS
showsUnaryWith Int -> a -> ShowS
sp String
"Just"Int
d a
x -- | @since 4.9.0.0instanceEq1 []whereliftEq :: forall a b. (a -> b -> Bool) -> [a] -> [b] -> Bool
liftEq a -> b -> Bool
_[][]=Bool
True liftEq a -> b -> Bool
_[](b
_: [b]
_)=Bool
False liftEq a -> b -> Bool
_(a
_: [a]
_)[]=Bool
False liftEq a -> b -> Bool
eq (a
x : [a]
xs )(b
y : [b]
ys )=a -> b -> Bool
eq a
x b
y Bool -> Bool -> Bool
&& (a -> b -> Bool) -> [a] -> [b] -> Bool
forall a b. (a -> b -> Bool) -> [a] -> [b] -> Bool
forall (f :: * -> *) a b.
Eq1 f =>
(a -> b -> Bool) -> f a -> f b -> Bool
liftEq a -> b -> Bool
eq [a]
xs [b]
ys -- | @since 4.9.0.0instanceOrd1 []whereliftCompare :: forall a b. (a -> b -> Ordering) -> [a] -> [b] -> Ordering
liftCompare a -> b -> Ordering
_[][]=Ordering
EQ liftCompare a -> b -> Ordering
_[](b
_: [b]
_)=Ordering
LT liftCompare a -> b -> Ordering
_(a
_: [a]
_)[]=Ordering
GT liftCompare a -> b -> Ordering
comp (a
x : [a]
xs )(b
y : [b]
ys )=a -> b -> Ordering
comp a
x b
y Ordering -> Ordering -> Ordering
forall a. Monoid a => a -> a -> a
`mappend` (a -> b -> Ordering) -> [a] -> [b] -> Ordering
forall a b. (a -> b -> Ordering) -> [a] -> [b] -> Ordering
forall (f :: * -> *) a b.
Ord1 f =>
(a -> b -> Ordering) -> f a -> f b -> Ordering
liftCompare a -> b -> Ordering
comp [a]
xs [b]
ys -- | @since 4.9.0.0instanceRead1 []whereliftReadPrec :: forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec [a]
liftReadPrec ReadPrec a
_ReadPrec [a]
rl =ReadPrec [a]
rl liftReadListPrec :: forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec [[a]]
liftReadListPrec =ReadPrec a -> ReadPrec [a] -> ReadPrec [[a]]
forall (f :: * -> *) a.
Read1 f =>
ReadPrec a -> ReadPrec [a] -> ReadPrec [f a]
liftReadListPrecDefault liftReadList :: forall a. (Int -> ReadS a) -> ReadS [a] -> ReadS [[a]]
liftReadList =(Int -> ReadS a) -> ReadS [a] -> ReadS [[a]]
forall (f :: * -> *) a.
Read1 f =>
(Int -> ReadS a) -> ReadS [a] -> ReadS [f a]
liftReadListDefault -- | @since 4.9.0.0instanceShow1 []whereliftShowsPrec :: forall a.
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> [a] -> ShowS
liftShowsPrec Int -> a -> ShowS
_[a] -> ShowS
sl Int
_=[a] -> ShowS
sl -- | @since 4.10.0.0instanceEq1 NonEmpty whereliftEq :: forall a b. (a -> b -> Bool) -> NonEmpty a -> NonEmpty b -> Bool
liftEq a -> b -> Bool
eq (a
a :| [a]
as )(b
b :| [b]
bs )=a -> b -> Bool
eq a
a b
b Bool -> Bool -> Bool
&& (a -> b -> Bool) -> [a] -> [b] -> Bool
forall a b. (a -> b -> Bool) -> [a] -> [b] -> Bool
forall (f :: * -> *) a b.
Eq1 f =>
(a -> b -> Bool) -> f a -> f b -> Bool
liftEq a -> b -> Bool
eq [a]
as [b]
bs -- | @since 4.10.0.0instanceOrd1 NonEmpty whereliftCompare :: forall a b.
(a -> b -> Ordering) -> NonEmpty a -> NonEmpty b -> Ordering
liftCompare a -> b -> Ordering
cmp (a
a :| [a]
as )(b
b :| [b]
bs )=a -> b -> Ordering
cmp a
a b
b Ordering -> Ordering -> Ordering
forall a. Monoid a => a -> a -> a
`mappend` (a -> b -> Ordering) -> [a] -> [b] -> Ordering
forall a b. (a -> b -> Ordering) -> [a] -> [b] -> Ordering
forall (f :: * -> *) a b.
Ord1 f =>
(a -> b -> Ordering) -> f a -> f b -> Ordering
liftCompare a -> b -> Ordering
cmp [a]
as [b]
bs -- | @since 4.10.0.0instanceRead1 NonEmpty whereliftReadsPrec :: forall a.
(Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (NonEmpty a)
liftReadsPrec Int -> ReadS a
rdP ReadS [a]
rdL Int
p String
s =Bool -> ReadS (NonEmpty a) -> ReadS (NonEmpty a)
forall a. Bool -> ReadS a -> ReadS a
readParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
5)(\String
s' ->do(a
a ,String
s'' )<-Int -> ReadS a
rdP Int
6String
s' (String
":|",String
s''' )<-ReadS String
lex String
s'' ([a]
as ,String
s'''' )<-ReadS [a]
rdL String
s''' (NonEmpty a, String) -> [(NonEmpty a, String)]
forall a. a -> [a]
forall (m :: * -> *) a. Monad m => a -> m a
return (a
a a -> [a] -> NonEmpty a
forall a. a -> [a] -> NonEmpty a
:| [a]
as ,String
s'''' ))String
s -- | @since 4.10.0.0instanceShow1 NonEmpty whereliftShowsPrec :: forall a.
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> NonEmpty a -> ShowS
liftShowsPrec Int -> a -> ShowS
shwP [a] -> ShowS
shwL Int
p (a
a :| [a]
as )=Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
5)(ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ Int -> a -> ShowS
shwP Int
6a
a ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
" :| "ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> ShowS
shwL [a]
as -- | @since 4.9.0.0instanceEq2 (,)whereliftEq2 :: forall a b c d.
(a -> b -> Bool) -> (c -> d -> Bool) -> (a, c) -> (b, d) -> Bool
liftEq2 a -> b -> Bool
e1 c -> d -> Bool
e2 (a
x1 ,c
y1 )(b
x2 ,d
y2 )=a -> b -> Bool
e1 a
x1 b
x2 Bool -> Bool -> Bool
&& c -> d -> Bool
e2 c
y1 d
y2 -- | @since 4.9.0.0instanceOrd2 (,)whereliftCompare2 :: forall a b c d.
(a -> b -> Ordering)
-> (c -> d -> Ordering) -> (a, c) -> (b, d) -> Ordering
liftCompare2 a -> b -> Ordering
comp1 c -> d -> Ordering
comp2 (a
x1 ,c
y1 )(b
x2 ,d
y2 )=a -> b -> Ordering
comp1 a
x1 b
x2 Ordering -> Ordering -> Ordering
forall a. Monoid a => a -> a -> a
`mappend` c -> d -> Ordering
comp2 c
y1 d
y2 -- | @since 4.9.0.0instanceRead2 (,)whereliftReadPrec2 :: forall a b.
ReadPrec a
-> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (a, b)
liftReadPrec2 ReadPrec a
rp1 ReadPrec [a]
_ReadPrec b
rp2 ReadPrec [b]
_=ReadPrec (a, b) -> ReadPrec (a, b)
forall a. ReadPrec a -> ReadPrec a
parens (ReadPrec (a, b) -> ReadPrec (a, b))
-> ReadPrec (a, b) -> ReadPrec (a, b)
forall a b. (a -> b) -> a -> b
$ ReadPrec (a, b) -> ReadPrec (a, b)
forall a. ReadPrec a -> ReadPrec a
paren (ReadPrec (a, b) -> ReadPrec (a, b))
-> ReadPrec (a, b) -> ReadPrec (a, b)
forall a b. (a -> b) -> a -> b
$ doa
x <-ReadPrec a
rp1 Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Punc String
",")b
y <-ReadPrec b
rp2 (a, b) -> ReadPrec (a, b)
forall a. a -> ReadPrec a
forall (m :: * -> *) a. Monad m => a -> m a
return (a
x ,b
y )liftReadListPrec2 :: forall a b.
ReadPrec a
-> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [(a, b)]
liftReadListPrec2 =ReadPrec a
-> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [(a, b)]
forall (f :: * -> * -> *) a b.
Read2 f =>
ReadPrec a
-> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [f a b]
liftReadListPrec2Default liftReadList2 :: forall a b.
(Int -> ReadS a)
-> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [(a, b)]
liftReadList2 =(Int -> ReadS a)
-> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [(a, b)]
forall (f :: * -> * -> *) a b.
Read2 f =>
(Int -> ReadS a)
-> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [f a b]
liftReadList2Default -- | @since 4.9.0.0instanceShow2 (,)whereliftShowsPrec2 :: forall a b.
(Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> b -> ShowS)
-> ([b] -> ShowS)
-> Int
-> (a, b)
-> ShowS
liftShowsPrec2 Int -> a -> ShowS
sp1 [a] -> ShowS
_Int -> b -> ShowS
sp2 [b] -> ShowS
_Int
_(a
x ,b
y )=Char -> ShowS
showChar Char
'('ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> a -> ShowS
sp1 Int
0a
x ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
','ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> b -> ShowS
sp2 Int
0b
y ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
')'-- | @since 4.15instanceEq1 Solo whereliftEq :: forall a b. (a -> b -> Bool) -> Solo a -> Solo b -> Bool
liftEq a -> b -> Bool
eq (MkSolo a
a )(MkSolo b
b )=a
a a -> b -> Bool
`eq` b
b -- | @since 4.9.0.0instance(Eq a )=>Eq1 ((,)a )whereliftEq :: forall a b. (a -> b -> Bool) -> (a, a) -> (a, b) -> Bool
liftEq =(a -> a -> Bool) -> (a -> b -> Bool) -> (a, a) -> (a, b) -> Bool
forall a b c d.
(a -> b -> Bool) -> (c -> d -> Bool) -> (a, c) -> (b, d) -> Bool
forall (f :: * -> * -> *) a b c d.
Eq2 f =>
(a -> b -> Bool) -> (c -> d -> Bool) -> f a c -> f b d -> Bool
liftEq2 a -> a -> Bool
forall a. Eq a => a -> a -> Bool
(==) -- | @since 4.15instanceOrd1 Solo whereliftCompare :: forall a b. (a -> b -> Ordering) -> Solo a -> Solo b -> Ordering
liftCompare a -> b -> Ordering
cmp (MkSolo a
a )(MkSolo b
b )=a -> b -> Ordering
cmp a
a b
b -- | @since 4.9.0.0instance(Ord a )=>Ord1 ((,)a )whereliftCompare :: forall a b. (a -> b -> Ordering) -> (a, a) -> (a, b) -> Ordering
liftCompare =(a -> a -> Ordering)
-> (a -> b -> Ordering) -> (a, a) -> (a, b) -> Ordering
forall a b c d.
(a -> b -> Ordering)
-> (c -> d -> Ordering) -> (a, c) -> (b, d) -> Ordering
forall (f :: * -> * -> *) a b c d.
Ord2 f =>
(a -> b -> Ordering)
-> (c -> d -> Ordering) -> f a c -> f b d -> Ordering
liftCompare2 a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare -- | @since 4.15instanceRead1 Solo whereliftReadPrec :: forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec (Solo a)
liftReadPrec ReadPrec a
rp ReadPrec [a]
_=ReadPrec (Solo a) -> ReadPrec (Solo a)
forall a. ReadPrec a -> ReadPrec a
readData (ReadPrec a -> String -> (a -> Solo a) -> ReadPrec (Solo a)
forall a t. ReadPrec a -> String -> (a -> t) -> ReadPrec t
readUnaryWith ReadPrec a
rp String
"MkSolo"a -> Solo a
forall a. a -> Solo a
MkSolo )liftReadListPrec :: forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec [Solo a]
liftReadListPrec =ReadPrec a -> ReadPrec [a] -> ReadPrec [Solo a]
forall (f :: * -> *) a.
Read1 f =>
ReadPrec a -> ReadPrec [a] -> ReadPrec [f a]
liftReadListPrecDefault liftReadList :: forall a. (Int -> ReadS a) -> ReadS [a] -> ReadS [Solo a]
liftReadList =(Int -> ReadS a) -> ReadS [a] -> ReadS [Solo a]
forall (f :: * -> *) a.
Read1 f =>
(Int -> ReadS a) -> ReadS [a] -> ReadS [f a]
liftReadListDefault -- | @since 4.9.0.0instance(Read a )=>Read1 ((,)a )whereliftReadPrec :: forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec (a, a)
liftReadPrec =ReadPrec a
-> ReadPrec [a] -> ReadPrec a -> ReadPrec [a] -> ReadPrec (a, a)
forall a b.
ReadPrec a
-> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (a, b)
forall (f :: * -> * -> *) a b.
Read2 f =>
ReadPrec a
-> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (f a b)
liftReadPrec2 ReadPrec a
forall a. Read a => ReadPrec a
readPrec ReadPrec [a]
forall a. Read a => ReadPrec [a]
readListPrec liftReadListPrec :: forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec [(a, a)]
liftReadListPrec =ReadPrec a -> ReadPrec [a] -> ReadPrec [(a, a)]
forall (f :: * -> *) a.
Read1 f =>
ReadPrec a -> ReadPrec [a] -> ReadPrec [f a]
liftReadListPrecDefault liftReadList :: forall a. (Int -> ReadS a) -> ReadS [a] -> ReadS [(a, a)]
liftReadList =(Int -> ReadS a) -> ReadS [a] -> ReadS [(a, a)]
forall (f :: * -> *) a.
Read1 f =>
(Int -> ReadS a) -> ReadS [a] -> ReadS [f a]
liftReadListDefault -- | @since 4.15instanceShow1 Solo whereliftShowsPrec :: forall a.
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Solo a -> ShowS
liftShowsPrec Int -> a -> ShowS
sp [a] -> ShowS
_Int
d (MkSolo a
x )=(Int -> a -> ShowS) -> String -> Int -> a -> ShowS
forall a. (Int -> a -> ShowS) -> String -> Int -> a -> ShowS
showsUnaryWith Int -> a -> ShowS
sp String
"MkSolo"Int
d a
x -- | @since 4.9.0.0instance(Show a )=>Show1 ((,)a )whereliftShowsPrec :: forall a.
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> (a, a) -> ShowS
liftShowsPrec =(Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> a -> ShowS)
-> ([a] -> ShowS)
-> Int
-> (a, a)
-> ShowS
forall a b.
(Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> b -> ShowS)
-> ([b] -> ShowS)
-> Int
-> (a, b)
-> ShowS
forall (f :: * -> * -> *) a b.
Show2 f =>
(Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> b -> ShowS)
-> ([b] -> ShowS)
-> Int
-> f a b
-> ShowS
liftShowsPrec2 Int -> a -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec [a] -> ShowS
forall a. Show a => [a] -> ShowS
showList -- | @since 4.16.0.0---- >>> eq2 ('x', True, "str") ('x', True, "str")-- True--instanceEq a =>Eq2 ((,,)a )whereliftEq2 :: forall a b c d.
(a -> b -> Bool)
-> (c -> d -> Bool) -> (a, a, c) -> (a, b, d) -> Bool
liftEq2 a -> b -> Bool
e1 c -> d -> Bool
e2 (a
u1 ,a
x1 ,c
y1 )(a
v1 ,b
x2 ,d
y2 )=a
u1 a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
v1 Bool -> Bool -> Bool
&& a -> b -> Bool
e1 a
x1 b
x2 Bool -> Bool -> Bool
&& c -> d -> Bool
e2 c
y1 d
y2 -- | @since 4.16.0.0---- >>> compare2 ('x', True, "aaa") ('x', True, "zzz")-- LTinstanceOrd a =>Ord2 ((,,)a )whereliftCompare2 :: forall a b c d.
(a -> b -> Ordering)
-> (c -> d -> Ordering) -> (a, a, c) -> (a, b, d) -> Ordering
liftCompare2 a -> b -> Ordering
comp1 c -> d -> Ordering
comp2 (a
u1 ,a
x1 ,c
y1 )(a
v1 ,b
x2 ,d
y2 )=a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare a
u1 a
v1 Ordering -> Ordering -> Ordering
forall a. Monoid a => a -> a -> a
`mappend` a -> b -> Ordering
comp1 a
x1 b
x2 Ordering -> Ordering -> Ordering
forall a. Monoid a => a -> a -> a
`mappend` c -> d -> Ordering
comp2 c
y1 d
y2 -- | @since 4.16.0.0---- >>> readPrec_to_S readPrec2 0 "('x', True, 2)" :: [((Char, Bool, Int), String)]-- [(('x',True,2),"")]--instanceRead a =>Read2 ((,,)a )whereliftReadPrec2 :: forall a b.
ReadPrec a
-> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (a, a, b)
liftReadPrec2 ReadPrec a
rp1 ReadPrec [a]
_ReadPrec b
rp2 ReadPrec [b]
_=ReadPrec (a, a, b) -> ReadPrec (a, a, b)
forall a. ReadPrec a -> ReadPrec a
parens (ReadPrec (a, a, b) -> ReadPrec (a, a, b))
-> ReadPrec (a, a, b) -> ReadPrec (a, a, b)
forall a b. (a -> b) -> a -> b
$ ReadPrec (a, a, b) -> ReadPrec (a, a, b)
forall a. ReadPrec a -> ReadPrec a
paren (ReadPrec (a, a, b) -> ReadPrec (a, a, b))
-> ReadPrec (a, a, b) -> ReadPrec (a, a, b)
forall a b. (a -> b) -> a -> b
$ doa
x1 <-ReadPrec a
forall a. Read a => ReadPrec a
readPrec Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Punc String
",")a
y1 <-ReadPrec a
rp1 Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Punc String
",")b
y2 <-ReadPrec b
rp2 (a, a, b) -> ReadPrec (a, a, b)
forall a. a -> ReadPrec a
forall (m :: * -> *) a. Monad m => a -> m a
return (a
x1 ,a
y1 ,b
y2 )liftReadListPrec2 :: forall a b.
ReadPrec a
-> ReadPrec [a]
-> ReadPrec b
-> ReadPrec [b]
-> ReadPrec [(a, a, b)]
liftReadListPrec2 =ReadPrec a
-> ReadPrec [a]
-> ReadPrec b
-> ReadPrec [b]
-> ReadPrec [(a, a, b)]
forall (f :: * -> * -> *) a b.
Read2 f =>
ReadPrec a
-> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [f a b]
liftReadListPrec2Default liftReadList2 :: forall a b.
(Int -> ReadS a)
-> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [(a, a, b)]
liftReadList2 =(Int -> ReadS a)
-> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [(a, a, b)]
forall (f :: * -> * -> *) a b.
Read2 f =>
(Int -> ReadS a)
-> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [f a b]
liftReadList2Default -- | @since 4.16.0.0---- >>> showsPrec2 0 ('x', True, 2 :: Int) ""-- "('x',True,2)"--instanceShow a =>Show2 ((,,)a )whereliftShowsPrec2 :: forall a b.
(Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> b -> ShowS)
-> ([b] -> ShowS)
-> Int
-> (a, a, b)
-> ShowS
liftShowsPrec2 Int -> a -> ShowS
sp1 [a] -> ShowS
_Int -> b -> ShowS
sp2 [b] -> ShowS
_Int
_(a
x1 ,a
y1 ,b
y2 )=Char -> ShowS
showChar Char
'('ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> a -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
0a
x1 ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
','ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> a -> ShowS
sp1 Int
0a
y1 ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
','ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> b -> ShowS
sp2 Int
0b
y2 ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
')'-- | @since 4.16.0.0instance(Eq a ,Eq b )=>Eq1 ((,,)a b )whereliftEq :: forall a b. (a -> b -> Bool) -> (a, b, a) -> (a, b, b) -> Bool
liftEq =(b -> b -> Bool)
-> (a -> b -> Bool) -> (a, b, a) -> (a, b, b) -> Bool
forall a b c d.
(a -> b -> Bool)
-> (c -> d -> Bool) -> (a, a, c) -> (a, b, d) -> Bool
forall (f :: * -> * -> *) a b c d.
Eq2 f =>
(a -> b -> Bool) -> (c -> d -> Bool) -> f a c -> f b d -> Bool
liftEq2 b -> b -> Bool
forall a. Eq a => a -> a -> Bool
(==) -- | @since 4.16.0.0instance(Ord a ,Ord b )=>Ord1 ((,,)a b )whereliftCompare :: forall a b.
(a -> b -> Ordering) -> (a, b, a) -> (a, b, b) -> Ordering
liftCompare =(b -> b -> Ordering)
-> (a -> b -> Ordering) -> (a, b, a) -> (a, b, b) -> Ordering
forall a b c d.
(a -> b -> Ordering)
-> (c -> d -> Ordering) -> (a, a, c) -> (a, b, d) -> Ordering
forall (f :: * -> * -> *) a b c d.
Ord2 f =>
(a -> b -> Ordering)
-> (c -> d -> Ordering) -> f a c -> f b d -> Ordering
liftCompare2 b -> b -> Ordering
forall a. Ord a => a -> a -> Ordering
compare -- | @since 4.16.0.0instance(Read a ,Read b )=>Read1 ((,,)a b )whereliftReadPrec :: forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec (a, b, a)
liftReadPrec =ReadPrec b
-> ReadPrec [b] -> ReadPrec a -> ReadPrec [a] -> ReadPrec (a, b, a)
forall a b.
ReadPrec a
-> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (a, a, b)
forall (f :: * -> * -> *) a b.
Read2 f =>
ReadPrec a
-> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (f a b)
liftReadPrec2 ReadPrec b
forall a. Read a => ReadPrec a
readPrec ReadPrec [b]
forall a. Read a => ReadPrec [a]
readListPrec liftReadListPrec :: forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec [(a, b, a)]
liftReadListPrec =ReadPrec a -> ReadPrec [a] -> ReadPrec [(a, b, a)]
forall (f :: * -> *) a.
Read1 f =>
ReadPrec a -> ReadPrec [a] -> ReadPrec [f a]
liftReadListPrecDefault liftReadList :: forall a. (Int -> ReadS a) -> ReadS [a] -> ReadS [(a, b, a)]
liftReadList =(Int -> ReadS a) -> ReadS [a] -> ReadS [(a, b, a)]
forall (f :: * -> *) a.
Read1 f =>
(Int -> ReadS a) -> ReadS [a] -> ReadS [f a]
liftReadListDefault -- | @since 4.16.0.0instance(Show a ,Show b )=>Show1 ((,,)a b )whereliftShowsPrec :: forall a.
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> (a, b, a) -> ShowS
liftShowsPrec =(Int -> b -> ShowS)
-> ([b] -> ShowS)
-> (Int -> a -> ShowS)
-> ([a] -> ShowS)
-> Int
-> (a, b, a)
-> ShowS
forall a b.
(Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> b -> ShowS)
-> ([b] -> ShowS)
-> Int
-> (a, a, b)
-> ShowS
forall (f :: * -> * -> *) a b.
Show2 f =>
(Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> b -> ShowS)
-> ([b] -> ShowS)
-> Int
-> f a b
-> ShowS
liftShowsPrec2 Int -> b -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec [b] -> ShowS
forall a. Show a => [a] -> ShowS
showList -- | @since 4.16.0.0---- >>> eq2 ('x', True, "str", 2) ('x', True, "str", 2 :: Int)-- True--instance(Eq a ,Eq b )=>Eq2 ((,,,)a b )whereliftEq2 :: forall a b c d.
(a -> b -> Bool)
-> (c -> d -> Bool) -> (a, b, a, c) -> (a, b, b, d) -> Bool
liftEq2 a -> b -> Bool
e1 c -> d -> Bool
e2 (a
u1 ,b
u2 ,a
x1 ,c
y1 )(a
v1 ,b
v2 ,b
x2 ,d
y2 )=a
u1 a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
v1 Bool -> Bool -> Bool
&& b
u2 b -> b -> Bool
forall a. Eq a => a -> a -> Bool
== b
v2 Bool -> Bool -> Bool
&& a -> b -> Bool
e1 a
x1 b
x2 Bool -> Bool -> Bool
&& c -> d -> Bool
e2 c
y1 d
y2 -- | @since 4.16.0.0---- >>> compare2 ('x', True, "str", 2) ('x', True, "str", 3 :: Int)-- LT--instance(Ord a ,Ord b )=>Ord2 ((,,,)a b )whereliftCompare2 :: forall a b c d.
(a -> b -> Ordering)
-> (c -> d -> Ordering) -> (a, b, a, c) -> (a, b, b, d) -> Ordering
liftCompare2 a -> b -> Ordering
comp1 c -> d -> Ordering
comp2 (a
u1 ,b
u2 ,a
x1 ,c
y1 )(a
v1 ,b
v2 ,b
x2 ,d
y2 )=a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare a
u1 a
v1 Ordering -> Ordering -> Ordering
forall a. Monoid a => a -> a -> a
`mappend` b -> b -> Ordering
forall a. Ord a => a -> a -> Ordering
compare b
u2 b
v2 Ordering -> Ordering -> Ordering
forall a. Monoid a => a -> a -> a
`mappend` a -> b -> Ordering
comp1 a
x1 b
x2 Ordering -> Ordering -> Ordering
forall a. Monoid a => a -> a -> a
`mappend` c -> d -> Ordering
comp2 c
y1 d
y2 -- | @since 4.16.0.0---- >>> readPrec_to_S readPrec2 0 "('x', True, 2, 4.5)" :: [((Char, Bool, Int, Double), String)]-- [(('x',True,2,4.5),"")]--instance(Read a ,Read b )=>Read2 ((,,,)a b )whereliftReadPrec2 :: forall a b.
ReadPrec a
-> ReadPrec [a]
-> ReadPrec b
-> ReadPrec [b]
-> ReadPrec (a, b, a, b)
liftReadPrec2 ReadPrec a
rp1 ReadPrec [a]
_ReadPrec b
rp2 ReadPrec [b]
_=ReadPrec (a, b, a, b) -> ReadPrec (a, b, a, b)
forall a. ReadPrec a -> ReadPrec a
parens (ReadPrec (a, b, a, b) -> ReadPrec (a, b, a, b))
-> ReadPrec (a, b, a, b) -> ReadPrec (a, b, a, b)
forall a b. (a -> b) -> a -> b
$ ReadPrec (a, b, a, b) -> ReadPrec (a, b, a, b)
forall a. ReadPrec a -> ReadPrec a
paren (ReadPrec (a, b, a, b) -> ReadPrec (a, b, a, b))
-> ReadPrec (a, b, a, b) -> ReadPrec (a, b, a, b)
forall a b. (a -> b) -> a -> b
$ doa
x1 <-ReadPrec a
forall a. Read a => ReadPrec a
readPrec Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Punc String
",")b
x2 <-ReadPrec b
forall a. Read a => ReadPrec a
readPrec Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Punc String
",")a
y1 <-ReadPrec a
rp1 Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Punc String
",")b
y2 <-ReadPrec b
rp2 (a, b, a, b) -> ReadPrec (a, b, a, b)
forall a. a -> ReadPrec a
forall (m :: * -> *) a. Monad m => a -> m a
return (a
x1 ,b
x2 ,a
y1 ,b
y2 )liftReadListPrec2 :: forall a b.
ReadPrec a
-> ReadPrec [a]
-> ReadPrec b
-> ReadPrec [b]
-> ReadPrec [(a, b, a, b)]
liftReadListPrec2 =ReadPrec a
-> ReadPrec [a]
-> ReadPrec b
-> ReadPrec [b]
-> ReadPrec [(a, b, a, b)]
forall (f :: * -> * -> *) a b.
Read2 f =>
ReadPrec a
-> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [f a b]
liftReadListPrec2Default liftReadList2 :: forall a b.
(Int -> ReadS a)
-> ReadS [a]
-> (Int -> ReadS b)
-> ReadS [b]
-> ReadS [(a, b, a, b)]
liftReadList2 =(Int -> ReadS a)
-> ReadS [a]
-> (Int -> ReadS b)
-> ReadS [b]
-> ReadS [(a, b, a, b)]
forall (f :: * -> * -> *) a b.
Read2 f =>
(Int -> ReadS a)
-> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [f a b]
liftReadList2Default -- | @since 4.16.0.0---- >>> showsPrec2 0 ('x', True, 2 :: Int, 4.5 :: Double) ""-- "('x',True,2,4.5)"--instance(Show a ,Show b )=>Show2 ((,,,)a b )whereliftShowsPrec2 :: forall a b.
(Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> b -> ShowS)
-> ([b] -> ShowS)
-> Int
-> (a, b, a, b)
-> ShowS
liftShowsPrec2 Int -> a -> ShowS
sp1 [a] -> ShowS
_Int -> b -> ShowS
sp2 [b] -> ShowS
_Int
_(a
x1 ,b
x2 ,a
y1 ,b
y2 )=Char -> ShowS
showChar Char
'('ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> a -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
0a
x1 ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
','ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> b -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
0b
x2 ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
','ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> a -> ShowS
sp1 Int
0a
y1 ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
','ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> b -> ShowS
sp2 Int
0b
y2 ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
')'-- | @since 4.16.0.0instance(Eq a ,Eq b ,Eq c )=>Eq1 ((,,,)a b c )whereliftEq :: forall a b.
(a -> b -> Bool) -> (a, b, c, a) -> (a, b, c, b) -> Bool
liftEq =(c -> c -> Bool)
-> (a -> b -> Bool) -> (a, b, c, a) -> (a, b, c, b) -> Bool
forall a b c d.
(a -> b -> Bool)
-> (c -> d -> Bool) -> (a, b, a, c) -> (a, b, b, d) -> Bool
forall (f :: * -> * -> *) a b c d.
Eq2 f =>
(a -> b -> Bool) -> (c -> d -> Bool) -> f a c -> f b d -> Bool
liftEq2 c -> c -> Bool
forall a. Eq a => a -> a -> Bool
(==) -- | @since 4.16.0.0instance(Ord a ,Ord b ,Ord c )=>Ord1 ((,,,)a b c )whereliftCompare :: forall a b.
(a -> b -> Ordering) -> (a, b, c, a) -> (a, b, c, b) -> Ordering
liftCompare =(c -> c -> Ordering)
-> (a -> b -> Ordering) -> (a, b, c, a) -> (a, b, c, b) -> Ordering
forall a b c d.
(a -> b -> Ordering)
-> (c -> d -> Ordering) -> (a, b, a, c) -> (a, b, b, d) -> Ordering
forall (f :: * -> * -> *) a b c d.
Ord2 f =>
(a -> b -> Ordering)
-> (c -> d -> Ordering) -> f a c -> f b d -> Ordering
liftCompare2 c -> c -> Ordering
forall a. Ord a => a -> a -> Ordering
compare -- | @since 4.16.0.0instance(Read a ,Read b ,Read c )=>Read1 ((,,,)a b c )whereliftReadPrec :: forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec (a, b, c, a)
liftReadPrec =ReadPrec c
-> ReadPrec [c]
-> ReadPrec a
-> ReadPrec [a]
-> ReadPrec (a, b, c, a)
forall a b.
ReadPrec a
-> ReadPrec [a]
-> ReadPrec b
-> ReadPrec [b]
-> ReadPrec (a, b, a, b)
forall (f :: * -> * -> *) a b.
Read2 f =>
ReadPrec a
-> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (f a b)
liftReadPrec2 ReadPrec c
forall a. Read a => ReadPrec a
readPrec ReadPrec [c]
forall a. Read a => ReadPrec [a]
readListPrec liftReadListPrec :: forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec [(a, b, c, a)]
liftReadListPrec =ReadPrec a -> ReadPrec [a] -> ReadPrec [(a, b, c, a)]
forall (f :: * -> *) a.
Read1 f =>
ReadPrec a -> ReadPrec [a] -> ReadPrec [f a]
liftReadListPrecDefault liftReadList :: forall a. (Int -> ReadS a) -> ReadS [a] -> ReadS [(a, b, c, a)]
liftReadList =(Int -> ReadS a) -> ReadS [a] -> ReadS [(a, b, c, a)]
forall (f :: * -> *) a.
Read1 f =>
(Int -> ReadS a) -> ReadS [a] -> ReadS [f a]
liftReadListDefault -- | @since 4.16.0.0instance(Show a ,Show b ,Show c )=>Show1 ((,,,)a b c )whereliftShowsPrec :: forall a.
(Int -> a -> ShowS)
-> ([a] -> ShowS) -> Int -> (a, b, c, a) -> ShowS
liftShowsPrec =(Int -> c -> ShowS)
-> ([c] -> ShowS)
-> (Int -> a -> ShowS)
-> ([a] -> ShowS)
-> Int
-> (a, b, c, a)
-> ShowS
forall a b.
(Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> b -> ShowS)
-> ([b] -> ShowS)
-> Int
-> (a, b, a, b)
-> ShowS
forall (f :: * -> * -> *) a b.
Show2 f =>
(Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> b -> ShowS)
-> ([b] -> ShowS)
-> Int
-> f a b
-> ShowS
liftShowsPrec2 Int -> c -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec [c] -> ShowS
forall a. Show a => [a] -> ShowS
showList -- | @since 4.17.0.0instance(Generic1 f ,Eq1 (Rep1 f ))=>Eq1 (Generically1 f )whereliftEq ::(a1 ->a2 ->Bool )->(Generically1 f a1 ->Generically1 f a2 ->Bool )liftEq :: forall a b.
(a -> b -> Bool) -> Generically1 f a -> Generically1 f b -> Bool
liftEq a1 -> a2 -> Bool
(===) (Generically1 f a1
as1 )(Generically1 f a2
as2 )=(a1 -> a2 -> Bool) -> Rep1 f a1 -> Rep1 f a2 -> Bool
forall a b. (a -> b -> Bool) -> Rep1 f a -> Rep1 f b -> Bool
forall (f :: * -> *) a b.
Eq1 f =>
(a -> b -> Bool) -> f a -> f b -> Bool
liftEq a1 -> a2 -> Bool
(===) (f a1 -> Rep1 f a1
forall a. f a -> Rep1 f a
forall k (f :: k -> *) (a :: k). Generic1 f => f a -> Rep1 f a
from1 f a1
as1 )(f a2 -> Rep1 f a2
forall a. f a -> Rep1 f a
forall k (f :: k -> *) (a :: k). Generic1 f => f a -> Rep1 f a
from1 f a2
as2 )-- | @since 4.17.0.0instance(Generic1 f ,Ord1 (Rep1 f ))=>Ord1 (Generically1 f )whereliftCompare ::(a1 ->a2 ->Ordering )->(Generically1 f a1 ->Generically1 f a2 ->Ordering )liftCompare :: forall a b.
(a -> b -> Ordering)
-> Generically1 f a -> Generically1 f b -> Ordering
liftCompare a1 -> a2 -> Ordering
cmp (Generically1 f a1
as1 )(Generically1 f a2
as2 )=(a1 -> a2 -> Ordering) -> Rep1 f a1 -> Rep1 f a2 -> Ordering
forall a b.
(a -> b -> Ordering) -> Rep1 f a -> Rep1 f b -> Ordering
forall (f :: * -> *) a b.
Ord1 f =>
(a -> b -> Ordering) -> f a -> f b -> Ordering
liftCompare a1 -> a2 -> Ordering
cmp (f a1 -> Rep1 f a1
forall a. f a -> Rep1 f a
forall k (f :: k -> *) (a :: k). Generic1 f => f a -> Rep1 f a
from1 f a1
as1 )(f a2 -> Rep1 f a2
forall a. f a -> Rep1 f a
forall k (f :: k -> *) (a :: k). Generic1 f => f a -> Rep1 f a
from1 f a2
as2 )-- | @since 4.9.0.0instanceEq2 Either whereliftEq2 :: forall a b c d.
(a -> b -> Bool)
-> (c -> d -> Bool) -> Either a c -> Either b d -> Bool
liftEq2 a -> b -> Bool
e1 c -> d -> Bool
_(Left a
x )(Left b
y )=a -> b -> Bool
e1 a
x b
y liftEq2 a -> b -> Bool
_c -> d -> Bool
_(Left a
_)(Right d
_)=Bool
False liftEq2 a -> b -> Bool
_c -> d -> Bool
_(Right c
_)(Left b
_)=Bool
False liftEq2 a -> b -> Bool
_c -> d -> Bool
e2 (Right c
x )(Right d
y )=c -> d -> Bool
e2 c
x d
y -- | @since 4.9.0.0instanceOrd2 Either whereliftCompare2 :: forall a b c d.
(a -> b -> Ordering)
-> (c -> d -> Ordering) -> Either a c -> Either b d -> Ordering
liftCompare2 a -> b -> Ordering
comp1 c -> d -> Ordering
_(Left a
x )(Left b
y )=a -> b -> Ordering
comp1 a
x b
y liftCompare2 a -> b -> Ordering
_c -> d -> Ordering
_(Left a
_)(Right d
_)=Ordering
LT liftCompare2 a -> b -> Ordering
_c -> d -> Ordering
_(Right c
_)(Left b
_)=Ordering
GT liftCompare2 a -> b -> Ordering
_c -> d -> Ordering
comp2 (Right c
x )(Right d
y )=c -> d -> Ordering
comp2 c
x d
y -- | @since 4.9.0.0instanceRead2 Either whereliftReadPrec2 :: forall a b.
ReadPrec a
-> ReadPrec [a]
-> ReadPrec b
-> ReadPrec [b]
-> ReadPrec (Either a b)
liftReadPrec2 ReadPrec a
rp1 ReadPrec [a]
_ReadPrec b
rp2 ReadPrec [b]
_=ReadPrec (Either a b) -> ReadPrec (Either a b)
forall a. ReadPrec a -> ReadPrec a
readData (ReadPrec (Either a b) -> ReadPrec (Either a b))
-> ReadPrec (Either a b) -> ReadPrec (Either a b)
forall a b. (a -> b) -> a -> b
$ ReadPrec a -> String -> (a -> Either a b) -> ReadPrec (Either a b)
forall a t. ReadPrec a -> String -> (a -> t) -> ReadPrec t
readUnaryWith ReadPrec a
rp1 String
"Left"a -> Either a b
forall a b. a -> Either a b
Left ReadPrec (Either a b)
-> ReadPrec (Either a b) -> ReadPrec (Either a b)
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ReadPrec b -> String -> (b -> Either a b) -> ReadPrec (Either a b)
forall a t. ReadPrec a -> String -> (a -> t) -> ReadPrec t
readUnaryWith ReadPrec b
rp2 String
"Right"b -> Either a b
forall a b. b -> Either a b
Right liftReadListPrec2 :: forall a b.
ReadPrec a
-> ReadPrec [a]
-> ReadPrec b
-> ReadPrec [b]
-> ReadPrec [Either a b]
liftReadListPrec2 =ReadPrec a
-> ReadPrec [a]
-> ReadPrec b
-> ReadPrec [b]
-> ReadPrec [Either a b]
forall (f :: * -> * -> *) a b.
Read2 f =>
ReadPrec a
-> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [f a b]
liftReadListPrec2Default liftReadList2 :: forall a b.
(Int -> ReadS a)
-> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Either a b]
liftReadList2 =(Int -> ReadS a)
-> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Either a b]
forall (f :: * -> * -> *) a b.
Read2 f =>
(Int -> ReadS a)
-> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [f a b]
liftReadList2Default -- | @since 4.9.0.0instanceShow2 Either whereliftShowsPrec2 :: forall a b.
(Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> b -> ShowS)
-> ([b] -> ShowS)
-> Int
-> Either a b
-> ShowS
liftShowsPrec2 Int -> a -> ShowS
sp1 [a] -> ShowS
_Int -> b -> ShowS
_[b] -> ShowS
_Int
d (Left a
x )=(Int -> a -> ShowS) -> String -> Int -> a -> ShowS
forall a. (Int -> a -> ShowS) -> String -> Int -> a -> ShowS
showsUnaryWith Int -> a -> ShowS
sp1 String
"Left"Int
d a
x liftShowsPrec2 Int -> a -> ShowS
_[a] -> ShowS
_Int -> b -> ShowS
sp2 [b] -> ShowS
_Int
d (Right b
x )=(Int -> b -> ShowS) -> String -> Int -> b -> ShowS
forall a. (Int -> a -> ShowS) -> String -> Int -> a -> ShowS
showsUnaryWith Int -> b -> ShowS
sp2 String
"Right"Int
d b
x -- | @since 4.9.0.0instance(Eq a )=>Eq1 (Either a )whereliftEq :: forall a b. (a -> b -> Bool) -> Either a a -> Either a b -> Bool
liftEq =(a -> a -> Bool)
-> (a -> b -> Bool) -> Either a a -> Either a b -> Bool
forall a b c d.
(a -> b -> Bool)
-> (c -> d -> Bool) -> Either a c -> Either b d -> Bool
forall (f :: * -> * -> *) a b c d.
Eq2 f =>
(a -> b -> Bool) -> (c -> d -> Bool) -> f a c -> f b d -> Bool
liftEq2 a -> a -> Bool
forall a. Eq a => a -> a -> Bool
(==) -- | @since 4.9.0.0instance(Ord a )=>Ord1 (Either a )whereliftCompare :: forall a b.
(a -> b -> Ordering) -> Either a a -> Either a b -> Ordering
liftCompare =(a -> a -> Ordering)
-> (a -> b -> Ordering) -> Either a a -> Either a b -> Ordering
forall a b c d.
(a -> b -> Ordering)
-> (c -> d -> Ordering) -> Either a c -> Either b d -> Ordering
forall (f :: * -> * -> *) a b c d.
Ord2 f =>
(a -> b -> Ordering)
-> (c -> d -> Ordering) -> f a c -> f b d -> Ordering
liftCompare2 a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare -- | @since 4.9.0.0instance(Read a )=>Read1 (Either a )whereliftReadPrec :: forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec (Either a a)
liftReadPrec =ReadPrec a
-> ReadPrec [a]
-> ReadPrec a
-> ReadPrec [a]
-> ReadPrec (Either a a)
forall a b.
ReadPrec a
-> ReadPrec [a]
-> ReadPrec b
-> ReadPrec [b]
-> ReadPrec (Either a b)
forall (f :: * -> * -> *) a b.
Read2 f =>
ReadPrec a
-> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (f a b)
liftReadPrec2 ReadPrec a
forall a. Read a => ReadPrec a
readPrec ReadPrec [a]
forall a. Read a => ReadPrec [a]
readListPrec liftReadListPrec :: forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec [Either a a]
liftReadListPrec =ReadPrec a -> ReadPrec [a] -> ReadPrec [Either a a]
forall (f :: * -> *) a.
Read1 f =>
ReadPrec a -> ReadPrec [a] -> ReadPrec [f a]
liftReadListPrecDefault liftReadList :: forall a. (Int -> ReadS a) -> ReadS [a] -> ReadS [Either a a]
liftReadList =(Int -> ReadS a) -> ReadS [a] -> ReadS [Either a a]
forall (f :: * -> *) a.
Read1 f =>
(Int -> ReadS a) -> ReadS [a] -> ReadS [f a]
liftReadListDefault -- | @since 4.9.0.0instance(Show a )=>Show1 (Either a )whereliftShowsPrec :: forall a.
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Either a a -> ShowS
liftShowsPrec =(Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> a -> ShowS)
-> ([a] -> ShowS)
-> Int
-> Either a a
-> ShowS
forall a b.
(Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> b -> ShowS)
-> ([b] -> ShowS)
-> Int
-> Either a b
-> ShowS
forall (f :: * -> * -> *) a b.
Show2 f =>
(Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> b -> ShowS)
-> ([b] -> ShowS)
-> Int
-> f a b
-> ShowS
liftShowsPrec2 Int -> a -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec [a] -> ShowS
forall a. Show a => [a] -> ShowS
showList -- Instances for other functors defined in the base package-- | @since 4.9.0.0instanceEq1 Identity whereliftEq :: forall a b. (a -> b -> Bool) -> Identity a -> Identity b -> Bool
liftEq a -> b -> Bool
eq (Identity a
x )(Identity b
y )=a -> b -> Bool
eq a
x b
y -- | @since 4.9.0.0instanceOrd1 Identity whereliftCompare :: forall a b.
(a -> b -> Ordering) -> Identity a -> Identity b -> Ordering
liftCompare a -> b -> Ordering
comp (Identity a
x )(Identity b
y )=a -> b -> Ordering
comp a
x b
y -- | @since 4.9.0.0instanceRead1 Identity whereliftReadPrec :: forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec (Identity a)
liftReadPrec ReadPrec a
rp ReadPrec [a]
_=ReadPrec (Identity a) -> ReadPrec (Identity a)
forall a. ReadPrec a -> ReadPrec a
readData (ReadPrec (Identity a) -> ReadPrec (Identity a))
-> ReadPrec (Identity a) -> ReadPrec (Identity a)
forall a b. (a -> b) -> a -> b
$ ReadPrec a -> String -> (a -> Identity a) -> ReadPrec (Identity a)
forall a t. ReadPrec a -> String -> (a -> t) -> ReadPrec t
readUnaryWith ReadPrec a
rp String
"Identity"a -> Identity a
forall a. a -> Identity a
Identity liftReadListPrec :: forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec [Identity a]
liftReadListPrec =ReadPrec a -> ReadPrec [a] -> ReadPrec [Identity a]
forall (f :: * -> *) a.
Read1 f =>
ReadPrec a -> ReadPrec [a] -> ReadPrec [f a]
liftReadListPrecDefault liftReadList :: forall a. (Int -> ReadS a) -> ReadS [a] -> ReadS [Identity a]
liftReadList =(Int -> ReadS a) -> ReadS [a] -> ReadS [Identity a]
forall (f :: * -> *) a.
Read1 f =>
(Int -> ReadS a) -> ReadS [a] -> ReadS [f a]
liftReadListDefault -- | @since 4.9.0.0instanceShow1 Identity whereliftShowsPrec :: forall a.
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Identity a -> ShowS
liftShowsPrec Int -> a -> ShowS
sp [a] -> ShowS
_Int
d (Identity a
x )=(Int -> a -> ShowS) -> String -> Int -> a -> ShowS
forall a. (Int -> a -> ShowS) -> String -> Int -> a -> ShowS
showsUnaryWith Int -> a -> ShowS
sp String
"Identity"Int
d a
x -- | @since 4.9.0.0instanceEq2 Const whereliftEq2 :: forall a b c d.
(a -> b -> Bool)
-> (c -> d -> Bool) -> Const a c -> Const b d -> Bool
liftEq2 a -> b -> Bool
eq c -> d -> Bool
_(Const a
x )(Const b
y )=a -> b -> Bool
eq a
x b
y -- | @since 4.9.0.0instanceOrd2 Const whereliftCompare2 :: forall a b c d.
(a -> b -> Ordering)
-> (c -> d -> Ordering) -> Const a c -> Const b d -> Ordering
liftCompare2 a -> b -> Ordering
comp c -> d -> Ordering
_(Const a
x )(Const b
y )=a -> b -> Ordering
comp a
x b
y -- | @since 4.9.0.0instanceRead2 Const whereliftReadPrec2 :: forall a b.
ReadPrec a
-> ReadPrec [a]
-> ReadPrec b
-> ReadPrec [b]
-> ReadPrec (Const a b)
liftReadPrec2 ReadPrec a
rp ReadPrec [a]
_ReadPrec b
_ReadPrec [b]
_=ReadPrec (Const a b) -> ReadPrec (Const a b)
forall a. ReadPrec a -> ReadPrec a
readData (ReadPrec (Const a b) -> ReadPrec (Const a b))
-> ReadPrec (Const a b) -> ReadPrec (Const a b)
forall a b. (a -> b) -> a -> b
$ ReadPrec a -> String -> (a -> Const a b) -> ReadPrec (Const a b)
forall a t. ReadPrec a -> String -> (a -> t) -> ReadPrec t
readUnaryWith ReadPrec a
rp String
"Const"a -> Const a b
forall {k} a (b :: k). a -> Const a b
Const liftReadListPrec2 :: forall a b.
ReadPrec a
-> ReadPrec [a]
-> ReadPrec b
-> ReadPrec [b]
-> ReadPrec [Const a b]
liftReadListPrec2 =ReadPrec a
-> ReadPrec [a]
-> ReadPrec b
-> ReadPrec [b]
-> ReadPrec [Const a b]
forall (f :: * -> * -> *) a b.
Read2 f =>
ReadPrec a
-> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [f a b]
liftReadListPrec2Default liftReadList2 :: forall a b.
(Int -> ReadS a)
-> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Const a b]
liftReadList2 =(Int -> ReadS a)
-> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Const a b]
forall (f :: * -> * -> *) a b.
Read2 f =>
(Int -> ReadS a)
-> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [f a b]
liftReadList2Default -- | @since 4.9.0.0instanceShow2 Const whereliftShowsPrec2 :: forall a b.
(Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> b -> ShowS)
-> ([b] -> ShowS)
-> Int
-> Const a b
-> ShowS
liftShowsPrec2 Int -> a -> ShowS
sp [a] -> ShowS
_Int -> b -> ShowS
_[b] -> ShowS
_Int
d (Const a
x )=(Int -> a -> ShowS) -> String -> Int -> a -> ShowS
forall a. (Int -> a -> ShowS) -> String -> Int -> a -> ShowS
showsUnaryWith Int -> a -> ShowS
sp String
"Const"Int
d a
x -- | @since 4.9.0.0instance(Eq a )=>Eq1 (Const a )whereliftEq :: forall a b. (a -> b -> Bool) -> Const a a -> Const a b -> Bool
liftEq =(a -> a -> Bool)
-> (a -> b -> Bool) -> Const a a -> Const a b -> Bool
forall a b c d.
(a -> b -> Bool)
-> (c -> d -> Bool) -> Const a c -> Const b d -> Bool
forall (f :: * -> * -> *) a b c d.
Eq2 f =>
(a -> b -> Bool) -> (c -> d -> Bool) -> f a c -> f b d -> Bool
liftEq2 a -> a -> Bool
forall a. Eq a => a -> a -> Bool
(==) -- | @since 4.9.0.0instance(Ord a )=>Ord1 (Const a )whereliftCompare :: forall a b.
(a -> b -> Ordering) -> Const a a -> Const a b -> Ordering
liftCompare =(a -> a -> Ordering)
-> (a -> b -> Ordering) -> Const a a -> Const a b -> Ordering
forall a b c d.
(a -> b -> Ordering)
-> (c -> d -> Ordering) -> Const a c -> Const b d -> Ordering
forall (f :: * -> * -> *) a b c d.
Ord2 f =>
(a -> b -> Ordering)
-> (c -> d -> Ordering) -> f a c -> f b d -> Ordering
liftCompare2 a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare -- | @since 4.9.0.0instance(Read a )=>Read1 (Const a )whereliftReadPrec :: forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec (Const a a)
liftReadPrec =ReadPrec a
-> ReadPrec [a]
-> ReadPrec a
-> ReadPrec [a]
-> ReadPrec (Const a a)
forall a b.
ReadPrec a
-> ReadPrec [a]
-> ReadPrec b
-> ReadPrec [b]
-> ReadPrec (Const a b)
forall (f :: * -> * -> *) a b.
Read2 f =>
ReadPrec a
-> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (f a b)
liftReadPrec2 ReadPrec a
forall a. Read a => ReadPrec a
readPrec ReadPrec [a]
forall a. Read a => ReadPrec [a]
readListPrec liftReadListPrec :: forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec [Const a a]
liftReadListPrec =ReadPrec a -> ReadPrec [a] -> ReadPrec [Const a a]
forall (f :: * -> *) a.
Read1 f =>
ReadPrec a -> ReadPrec [a] -> ReadPrec [f a]
liftReadListPrecDefault liftReadList :: forall a. (Int -> ReadS a) -> ReadS [a] -> ReadS [Const a a]
liftReadList =(Int -> ReadS a) -> ReadS [a] -> ReadS [Const a a]
forall (f :: * -> *) a.
Read1 f =>
(Int -> ReadS a) -> ReadS [a] -> ReadS [f a]
liftReadListDefault -- | @since 4.9.0.0instance(Show a )=>Show1 (Const a )whereliftShowsPrec :: forall a.
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Const a a -> ShowS
liftShowsPrec =(Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> a -> ShowS)
-> ([a] -> ShowS)
-> Int
-> Const a a
-> ShowS
forall a b.
(Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> b -> ShowS)
-> ([b] -> ShowS)
-> Int
-> Const a b
-> ShowS
forall (f :: * -> * -> *) a b.
Show2 f =>
(Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> b -> ShowS)
-> ([b] -> ShowS)
-> Int
-> f a b
-> ShowS
liftShowsPrec2 Int -> a -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec [a] -> ShowS
forall a. Show a => [a] -> ShowS
showList -- Proxy unfortunately imports this module, hence these instances are placed-- here,-- | @since 4.9.0.0instanceEq1 Proxy whereliftEq :: forall a b. (a -> b -> Bool) -> Proxy a -> Proxy b -> Bool
liftEq a -> b -> Bool
_Proxy a
_Proxy b
_=Bool
True -- | @since 4.9.0.0instanceOrd1 Proxy whereliftCompare :: forall a b. (a -> b -> Ordering) -> Proxy a -> Proxy b -> Ordering
liftCompare a -> b -> Ordering
_Proxy a
_Proxy b
_=Ordering
EQ -- | @since 4.9.0.0instanceShow1 Proxy whereliftShowsPrec :: forall a.
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Proxy a -> ShowS
liftShowsPrec Int -> a -> ShowS
_[a] -> ShowS
_Int
_Proxy a
_=String -> ShowS
showString String
"Proxy"-- | @since 4.9.0.0instanceRead1 Proxy whereliftReadPrec :: forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec (Proxy a)
liftReadPrec ReadPrec a
_ReadPrec [a]
_=ReadPrec (Proxy a) -> ReadPrec (Proxy a)
forall a. ReadPrec a -> ReadPrec a
parens (Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident String
"Proxy")ReadPrec () -> ReadPrec (Proxy a) -> ReadPrec (Proxy a)
forall a b. ReadPrec a -> ReadPrec b -> ReadPrec b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Proxy a -> ReadPrec (Proxy a)
forall a. a -> ReadPrec a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Proxy a
forall {k} (t :: k). Proxy t
Proxy )liftReadListPrec :: forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec [Proxy a]
liftReadListPrec =ReadPrec a -> ReadPrec [a] -> ReadPrec [Proxy a]
forall (f :: * -> *) a.
Read1 f =>
ReadPrec a -> ReadPrec [a] -> ReadPrec [f a]
liftReadListPrecDefault liftReadList :: forall a. (Int -> ReadS a) -> ReadS [a] -> ReadS [Proxy a]
liftReadList =(Int -> ReadS a) -> ReadS [a] -> ReadS [Proxy a]
forall (f :: * -> *) a.
Read1 f =>
(Int -> ReadS a) -> ReadS [a] -> ReadS [f a]
liftReadListDefault -- | @since 4.12.0.0instanceEq1 Down whereliftEq :: forall a b. (a -> b -> Bool) -> Down a -> Down b -> Bool
liftEq a -> b -> Bool
eq (Down a
x )(Down b
y )=a -> b -> Bool
eq a
x b
y -- | @since 4.12.0.0instanceOrd1 Down whereliftCompare :: forall a b. (a -> b -> Ordering) -> Down a -> Down b -> Ordering
liftCompare a -> b -> Ordering
comp (Down a
x )(Down b
y )=casea -> b -> Ordering
comp a
x b
y ofOrdering
LT ->Ordering
GT Ordering
EQ ->Ordering
EQ Ordering
GT ->Ordering
LT -- | @since 4.12.0.0instanceRead1 Down whereliftReadsPrec :: forall a. (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Down a)
liftReadsPrec Int -> ReadS a
rp ReadS [a]
_=(String -> ReadS (Down a)) -> Int -> ReadS (Down a)
forall a. (String -> ReadS a) -> Int -> ReadS a
readsData ((String -> ReadS (Down a)) -> Int -> ReadS (Down a))
-> (String -> ReadS (Down a)) -> Int -> ReadS (Down a)
forall a b. (a -> b) -> a -> b
$ (Int -> ReadS a)
-> String -> (a -> Down a) -> String -> ReadS (Down a)
forall a t.
(Int -> ReadS a) -> String -> (a -> t) -> String -> ReadS t
readsUnaryWith Int -> ReadS a
rp String
"Down"a -> Down a
forall a. a -> Down a
Down -- | @since 4.12.0.0instanceShow1 Down whereliftShowsPrec :: forall a.
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Down a -> ShowS
liftShowsPrec Int -> a -> ShowS
sp [a] -> ShowS
_Int
d (Down a
x )=(Int -> a -> ShowS) -> String -> Int -> a -> ShowS
forall a. (Int -> a -> ShowS) -> String -> Int -> a -> ShowS
showsUnaryWith Int -> a -> ShowS
sp String
"Down"Int
d a
x -- | @since 4.16.0.0---- >>> eq1 (1 :+ 2) (1 :+ 2)-- True---- >>> eq1 (1 :+ 2) (1 :+ 3)-- False--instanceEq1 Complex whereliftEq :: forall a b. (a -> b -> Bool) -> Complex a -> Complex b -> Bool
liftEq a -> b -> Bool
eq (a
x :+ a
y )(b
u :+ b
v )=a -> b -> Bool
eq a
x b
u Bool -> Bool -> Bool
&& a -> b -> Bool
eq a
y b
v -- | @since 4.16.0.0---- >>> readPrec_to_S readPrec1 0 "(2 % 3) :+ (3 % 4)" :: [(Complex Rational, String)]-- [(2 % 3 :+ 3 % 4,"")]--instanceRead1 Complex whereliftReadPrec :: forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec (Complex a)
liftReadPrec ReadPrec a
rp ReadPrec [a]
_=ReadPrec (Complex a) -> ReadPrec (Complex a)
forall a. ReadPrec a -> ReadPrec a
parens (ReadPrec (Complex a) -> ReadPrec (Complex a))
-> ReadPrec (Complex a) -> ReadPrec (Complex a)
forall a b. (a -> b) -> a -> b
$ Int -> ReadPrec (Complex a) -> ReadPrec (Complex a)
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
complexPrec (ReadPrec (Complex a) -> ReadPrec (Complex a))
-> ReadPrec (Complex a) -> ReadPrec (Complex a)
forall a b. (a -> b) -> a -> b
$ doa
x <-ReadPrec a -> ReadPrec a
forall a. ReadPrec a -> ReadPrec a
step ReadPrec a
rp Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Symbol String
":+")a
y <-ReadPrec a -> ReadPrec a
forall a. ReadPrec a -> ReadPrec a
step ReadPrec a
rp Complex a -> ReadPrec (Complex a)
forall a. a -> ReadPrec a
forall (m :: * -> *) a. Monad m => a -> m a
return (a
x a -> a -> Complex a
forall a. a -> a -> Complex a
:+ a
y )wherecomplexPrec :: Int
complexPrec =Int
6liftReadListPrec :: forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec [Complex a]
liftReadListPrec =ReadPrec a -> ReadPrec [a] -> ReadPrec [Complex a]
forall (f :: * -> *) a.
Read1 f =>
ReadPrec a -> ReadPrec [a] -> ReadPrec [f a]
liftReadListPrecDefault liftReadList :: forall a. (Int -> ReadS a) -> ReadS [a] -> ReadS [Complex a]
liftReadList =(Int -> ReadS a) -> ReadS [a] -> ReadS [Complex a]
forall (f :: * -> *) a.
Read1 f =>
(Int -> ReadS a) -> ReadS [a] -> ReadS [f a]
liftReadListDefault -- | @since 4.16.0.0---- >>> showsPrec1 0 (2 :+ 3) ""-- "2 :+ 3"--instanceShow1 Complex whereliftShowsPrec :: forall a.
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Complex a -> ShowS
liftShowsPrec Int -> a -> ShowS
sp [a] -> ShowS
_Int
d (a
x :+ a
y )=Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
complexPrec )(ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ Int -> a -> ShowS
sp (Int
complexPrec Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)a
x ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
" :+ "ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> a -> ShowS
sp (Int
complexPrec Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)a
y wherecomplexPrec :: Int
complexPrec =Int
6-- Building blocks-- | @'readsData' p d@ is a parser for datatypes where each alternative-- begins with a data constructor. It parses the constructor and-- passes it to @p@. Parsers for various constructors can be constructed-- with 'readsUnary', 'readsUnary1' and 'readsBinary1', and combined with-- @mappend@ from the @Monoid@ class.---- @since 4.9.0.0readsData ::(String ->ReadS a )->Int ->ReadS a readsData :: forall a. (String -> ReadS a) -> Int -> ReadS a
readsData String -> ReadS a
reader Int
d =Bool -> ReadS a -> ReadS a
forall a. Bool -> ReadS a -> ReadS a
readParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10)(ReadS a -> ReadS a) -> ReadS a -> ReadS a
forall a b. (a -> b) -> a -> b
$ \String
r ->[(a, String)
res |(String
kw ,String
s )<-ReadS String
lex String
r ,(a, String)
res <-String -> ReadS a
reader String
kw String
s ]-- | @'readData' p@ is a parser for datatypes where each alternative-- begins with a data constructor. It parses the constructor and-- passes it to @p@. Parsers for various constructors can be constructed-- with 'readUnaryWith' and 'readBinaryWith', and combined with-- '(<|>)' from the 'Alternative' class.---- @since 4.10.0.0readData ::ReadPrec a ->ReadPrec a readData :: forall a. ReadPrec a -> ReadPrec a
readData ReadPrec a
reader =ReadPrec a -> ReadPrec a
forall a. ReadPrec a -> ReadPrec a
parens (ReadPrec a -> ReadPrec a) -> ReadPrec a -> ReadPrec a
forall a b. (a -> b) -> a -> b
$ Int -> ReadPrec a -> ReadPrec a
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10ReadPrec a
reader -- | @'readsUnaryWith' rp n c n'@ matches the name of a unary data constructor-- and then parses its argument using @rp@.---- @since 4.9.0.0readsUnaryWith ::(Int ->ReadS a )->String ->(a ->t )->String ->ReadS t readsUnaryWith :: forall a t.
(Int -> ReadS a) -> String -> (a -> t) -> String -> ReadS t
readsUnaryWith Int -> ReadS a
rp String
name a -> t
cons String
kw String
s =[(a -> t
cons a
x ,String
t )|String
kw String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
name ,(a
x ,String
t )<-Int -> ReadS a
rp Int
11String
s ]-- | @'readUnaryWith' rp n c'@ matches the name of a unary data constructor-- and then parses its argument using @rp@.---- @since 4.10.0.0readUnaryWith ::ReadPrec a ->String ->(a ->t )->ReadPrec t readUnaryWith :: forall a t. ReadPrec a -> String -> (a -> t) -> ReadPrec t
readUnaryWith ReadPrec a
rp String
name a -> t
cons =doLexeme -> ReadPrec ()
expectP (Lexeme -> ReadPrec ()) -> Lexeme -> ReadPrec ()
forall a b. (a -> b) -> a -> b
$ String -> Lexeme
Ident String
name a
x <-ReadPrec a -> ReadPrec a
forall a. ReadPrec a -> ReadPrec a
step ReadPrec a
rp t -> ReadPrec t
forall a. a -> ReadPrec a
forall (m :: * -> *) a. Monad m => a -> m a
return (t -> ReadPrec t) -> t -> ReadPrec t
forall a b. (a -> b) -> a -> b
$ a -> t
cons a
x -- | @'readsBinaryWith' rp1 rp2 n c n'@ matches the name of a binary-- data constructor and then parses its arguments using @rp1@ and @rp2@-- respectively.---- @since 4.9.0.0readsBinaryWith ::(Int ->ReadS a )->(Int ->ReadS b )->String ->(a ->b ->t )->String ->ReadS t readsBinaryWith :: forall a b t.
(Int -> ReadS a)
-> (Int -> ReadS b) -> String -> (a -> b -> t) -> String -> ReadS t
readsBinaryWith Int -> ReadS a
rp1 Int -> ReadS b
rp2 String
name a -> b -> t
cons String
kw String
s =[(a -> b -> t
cons a
x b
y ,String
u )|String
kw String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
name ,(a
x ,String
t )<-Int -> ReadS a
rp1 Int
11String
s ,(b
y ,String
u )<-Int -> ReadS b
rp2 Int
11String
t ]-- | @'readBinaryWith' rp1 rp2 n c'@ matches the name of a binary-- data constructor and then parses its arguments using @rp1@ and @rp2@-- respectively.---- @since 4.10.0.0readBinaryWith ::ReadPrec a ->ReadPrec b ->String ->(a ->b ->t )->ReadPrec t readBinaryWith :: forall a b t.
ReadPrec a -> ReadPrec b -> String -> (a -> b -> t) -> ReadPrec t
readBinaryWith ReadPrec a
rp1 ReadPrec b
rp2 String
name a -> b -> t
cons =doLexeme -> ReadPrec ()
expectP (Lexeme -> ReadPrec ()) -> Lexeme -> ReadPrec ()
forall a b. (a -> b) -> a -> b
$ String -> Lexeme
Ident String
name a
x <-ReadPrec a -> ReadPrec a
forall a. ReadPrec a -> ReadPrec a
step ReadPrec a
rp1 b
y <-ReadPrec b -> ReadPrec b
forall a. ReadPrec a -> ReadPrec a
step ReadPrec b
rp2 t -> ReadPrec t
forall a. a -> ReadPrec a
forall (m :: * -> *) a. Monad m => a -> m a
return (t -> ReadPrec t) -> t -> ReadPrec t
forall a b. (a -> b) -> a -> b
$ a -> b -> t
cons a
x b
y -- | @'showsUnaryWith' sp n d x@ produces the string representation of a-- unary data constructor with name @n@ and argument @x@, in precedence-- context @d@.---- @since 4.9.0.0showsUnaryWith ::(Int ->a ->ShowS )->String ->Int ->a ->ShowS showsUnaryWith :: forall a. (Int -> a -> ShowS) -> String -> Int -> a -> ShowS
showsUnaryWith Int -> a -> ShowS
sp String
name Int
d a
x =Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10)(ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ String -> ShowS
showString String
name ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
' 'ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> a -> ShowS
sp Int
11a
x -- | @'showsBinaryWith' sp1 sp2 n d x y@ produces the string-- representation of a binary data constructor with name @n@ and arguments-- @x@ and @y@, in precedence context @d@.---- @since 4.9.0.0showsBinaryWith ::(Int ->a ->ShowS )->(Int ->b ->ShowS )->String ->Int ->a ->b ->ShowS showsBinaryWith :: forall a b.
(Int -> a -> ShowS)
-> (Int -> b -> ShowS) -> String -> Int -> a -> b -> ShowS
showsBinaryWith Int -> a -> ShowS
sp1 Int -> b -> ShowS
sp2 String
name Int
d a
x b
y =Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10)(ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ String -> ShowS
showString String
name ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
' 'ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> a -> ShowS
sp1 Int
11a
x ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
' 'ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> b -> ShowS
sp2 Int
11b
y -- Obsolete building blocks-- | @'readsUnary' n c n'@ matches the name of a unary data constructor-- and then parses its argument using 'readsPrec'.---- @since 4.9.0.0{-# DEPRECATEDreadsUnary"Use 'readsUnaryWith' to define 'liftReadsPrec'"#-}readsUnary ::(Read a )=>String ->(a ->t )->String ->ReadS t readsUnary :: forall a t. Read a => String -> (a -> t) -> String -> ReadS t
readsUnary String
name a -> t
cons String
kw String
s =[(a -> t
cons a
x ,String
t )|String
kw String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
name ,(a
x ,String
t )<-Int -> ReadS a
forall a. Read a => Int -> ReadS a
readsPrec Int
11String
s ]-- | @'readsUnary1' n c n'@ matches the name of a unary data constructor-- and then parses its argument using 'readsPrec1'.---- @since 4.9.0.0{-# DEPRECATEDreadsUnary1"Use 'readsUnaryWith' to define 'liftReadsPrec'"#-}readsUnary1 ::(Read1 f ,Read a )=>String ->(f a ->t )->String ->ReadS t readsUnary1 :: forall (f :: * -> *) a t.
(Read1 f, Read a) =>
String -> (f a -> t) -> String -> ReadS t
readsUnary1 String
name f a -> t
cons String
kw String
s =[(f a -> t
cons f a
x ,String
t )|String
kw String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
name ,(f a
x ,String
t )<-Int -> ReadS (f a)
forall (f :: * -> *) a. (Read1 f, Read a) => Int -> ReadS (f a)
readsPrec1 Int
11String
s ]-- | @'readsBinary1' n c n'@ matches the name of a binary data constructor-- and then parses its arguments using 'readsPrec1'.---- @since 4.9.0.0{-# DEPRECATEDreadsBinary1"Use 'readsBinaryWith' to define 'liftReadsPrec'"#-}readsBinary1 ::(Read1 f ,Read1 g ,Read a )=>String ->(f a ->g a ->t )->String ->ReadS t readsBinary1 :: forall (f :: * -> *) (g :: * -> *) a t.
(Read1 f, Read1 g, Read a) =>
String -> (f a -> g a -> t) -> String -> ReadS t
readsBinary1 String
name f a -> g a -> t
cons String
kw String
s =[(f a -> g a -> t
cons f a
x g a
y ,String
u )|String
kw String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
name ,(f a
x ,String
t )<-Int -> ReadS (f a)
forall (f :: * -> *) a. (Read1 f, Read a) => Int -> ReadS (f a)
readsPrec1 Int
11String
s ,(g a
y ,String
u )<-Int -> ReadS (g a)
forall (f :: * -> *) a. (Read1 f, Read a) => Int -> ReadS (f a)
readsPrec1 Int
11String
t ]-- | @'showsUnary' n d x@ produces the string representation of a unary data-- constructor with name @n@ and argument @x@, in precedence context @d@.---- @since 4.9.0.0{-# DEPRECATEDshowsUnary"Use 'showsUnaryWith' to define 'liftShowsPrec'"#-}showsUnary ::(Show a )=>String ->Int ->a ->ShowS showsUnary :: forall a. Show a => String -> Int -> a -> ShowS
showsUnary String
name Int
d a
x =Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10)(ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ String -> ShowS
showString String
name ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
' 'ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> a -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11a
x -- | @'showsUnary1' n d x@ produces the string representation of a unary data-- constructor with name @n@ and argument @x@, in precedence context @d@.---- @since 4.9.0.0{-# DEPRECATEDshowsUnary1"Use 'showsUnaryWith' to define 'liftShowsPrec'"#-}showsUnary1 ::(Show1 f ,Show a )=>String ->Int ->f a ->ShowS showsUnary1 :: forall (f :: * -> *) a.
(Show1 f, Show a) =>
String -> Int -> f a -> ShowS
showsUnary1 String
name Int
d f a
x =Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10)(ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ String -> ShowS
showString String
name ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
' 'ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> f a -> ShowS
forall (f :: * -> *) a. (Show1 f, Show a) => Int -> f a -> ShowS
showsPrec1 Int
11f a
x -- | @'showsBinary1' n d x y@ produces the string representation of a binary-- data constructor with name @n@ and arguments @x@ and @y@, in precedence-- context @d@.---- @since 4.9.0.0{-# DEPRECATEDshowsBinary1"Use 'showsBinaryWith' to define 'liftShowsPrec'"#-}showsBinary1 ::(Show1 f ,Show1 g ,Show a )=>String ->Int ->f a ->g a ->ShowS showsBinary1 :: forall (f :: * -> *) (g :: * -> *) a.
(Show1 f, Show1 g, Show a) =>
String -> Int -> f a -> g a -> ShowS
showsBinary1 String
name Int
d f a
x g a
y =Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10)(ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ String -> ShowS
showString String
name ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
' 'ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> f a -> ShowS
forall (f :: * -> *) a. (Show1 f, Show a) => Int -> f a -> ShowS
showsPrec1 Int
11f a
x ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
' 'ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> g a -> ShowS
forall (f :: * -> *) a. (Show1 f, Show a) => Int -> f a -> ShowS
showsPrec1 Int
11g a
y {- $example
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
-}

AltStyle によって変換されたページ (->オリジナル) /