{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE CPP, NoImplicitPrelude, StandaloneDeriving, ScopedTypeVariables #-}
{-# OPTIONS_HADDOCK not-home #-}
module GHC.Read
( Read(..)
, ReadS
, lex
, lexLitChar
, readLitChar
, lexDigits
, lexP, expectP
, paren
, parens
, list
, choose
, readListDefault, readListPrecDefault
, readNumber
, readField
, readFieldHash
, readSymField
, readParen
)
where
#include "MachDeps.h"
import qualified Text.ParserCombinators.ReadP as P
import Text.ParserCombinators.ReadP
( ReadS
, readP_to_S
)
import qualified Text.Read.Lex as L
import Text.ParserCombinators.ReadPrec
import Data.Maybe
import GHC.Unicode
import GHC.Num
import GHC.Real
import GHC.Float
import GHC.Show
import GHC.Base
import GHC.Arr
import GHC.Word
import GHC.List (filter)
readParen :: Bool -> ReadS a -> ReadS a
readParen :: Bool -> ReadS a -> ReadS a
readParen Bool
b ReadS a
g = if Bool
b then ReadS a
mandatory else ReadS a
optional
where optional :: ReadS a
optional String
r = ReadS a
g String
r [(a, String)] -> [(a, String)] -> [(a, String)]
forall a. [a] -> [a] -> [a]
++ ReadS a
mandatory String
r
mandatory :: ReadS a
mandatory String
r = do
(String
"(",String
s) <- ReadS String
lex String
r
(a
x,String
t) <- ReadS a
optional String
s
(String
")",String
u) <- ReadS String
lex String
t
(a, String) -> [(a, String)]
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad []
return (a
x,String
u)
class Read a where
{-# MINIMAL readsPrec | readPrec #-}
readsPrec :: Int
-> ReadS a
readList :: ReadS [a]
readPrec :: ReadPrec a
readListPrec :: ReadPrec [a]
readsPrec = ReadPrec a -> Int -> ReadS a
forall a. ReadPrec a -> Int -> ReadS a
readPrec_to_S ReadPrec a
forall a. Read a => ReadPrec a
Evidence bound by a type signature of the constraint type Read a
readPrec
readList = ReadPrec [a] -> Int -> ReadS [a]
forall a. ReadPrec a -> Int -> ReadS a
readPrec_to_S (ReadPrec a -> ReadPrec [a]
forall a. ReadPrec a -> ReadPrec [a]
list ReadPrec a
forall a. Read a => ReadPrec a
Evidence bound by a type signature of the constraint type Read a
readPrec) Int
0
readPrec = (Int -> ReadS a) -> ReadPrec a
forall a. (Int -> ReadS a) -> ReadPrec a
readS_to_Prec Int -> ReadS a
forall a. Read a => Int -> ReadS a
Evidence bound by a type signature of the constraint type Read a
readsPrec
readListPrec = (Int -> ReadS [a]) -> ReadPrec [a]
forall a. (Int -> ReadS a) -> ReadPrec a
readS_to_Prec (\Int
_ -> ReadS [a]
forall a. Read a => ReadS [a]
Evidence bound by a type signature of the constraint type Read a
readList)
readListDefault :: Read a => ReadS [a]
readListDefault :: ReadS [a]
readListDefault = ReadPrec [a] -> Int -> ReadS [a]
forall a. ReadPrec a -> Int -> ReadS a
readPrec_to_S ReadPrec [a]
forall a. Read a => ReadPrec [a]
Evidence bound by a type signature of the constraint type Read a
readListPrec Int
0
readListPrecDefault :: Read a => ReadPrec [a]
readListPrecDefault :: ReadPrec [a]
readListPrecDefault = ReadPrec a -> ReadPrec [a]
forall a. ReadPrec a -> ReadPrec [a]
list ReadPrec a
forall a. Read a => ReadPrec a
Evidence bound by a type signature of the constraint type Read a
readPrec
lex :: ReadS String
lex :: ReadS String
lex String
s = ReadP String -> ReadS String
forall a. ReadP a -> ReadS a
readP_to_S ReadP String
L.hsLex String
s
lexLitChar :: ReadS String
lexLitChar :: ReadS String
lexLitChar = ReadP String -> ReadS String
forall a. ReadP a -> ReadS a
readP_to_S (do { (String
s, Char
_) <- ReadP Char -> ReadP (String, Char)
forall a. ReadP a -> ReadP (String, a)
P.gather ReadP Char
L.lexChar ;
let s' :: String
s' = String -> String
removeNulls String
s in
String -> ReadP String
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ReadP
return String
s' })
where
removeNulls :: String -> String
removeNulls [] = []
removeNulls (Char
'\\':Char
'&':String
xs) = String -> String
removeNulls String
xs
removeNulls (Char
first:String
rest) = Char
first Char -> String -> String
forall a. a -> [a] -> [a]
: String -> String
removeNulls String
rest
readLitChar :: ReadS Char
readLitChar :: ReadS Char
readLitChar = ReadP Char -> ReadS Char
forall a. ReadP a -> ReadS a
readP_to_S ReadP Char
L.lexChar
lexDigits :: ReadS String
lexDigits :: ReadS String
lexDigits = ReadP String -> ReadS String
forall a. ReadP a -> ReadS a
readP_to_S ((Char -> Bool) -> ReadP String
P.munch1 Char -> Bool
isDigit)
lexP :: ReadPrec L.Lexeme
lexP :: ReadPrec Lexeme
lexP = ReadP Lexeme -> ReadPrec Lexeme
forall a. ReadP a -> ReadPrec a
lift ReadP Lexeme
L.lex
expectP :: L.Lexeme -> ReadPrec ()
expectP :: Lexeme -> ReadPrec ()
expectP Lexeme
lexeme = ReadP () -> ReadPrec ()
forall a. ReadP a -> ReadPrec a
lift (Lexeme -> ReadP ()
L.expect Lexeme
lexeme)
expectCharP :: Char -> ReadPrec a -> ReadPrec a
expectCharP :: Char -> ReadPrec a -> ReadPrec a
expectCharP Char
c ReadPrec a
a = do
Char
q <- ReadPrec Char
get
if Char
q Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Char
== Char
c
then ReadPrec a
a
else ReadPrec a
forall a. ReadPrec a
pfail
{-# INLINE expectCharP #-}
skipSpacesThenP :: ReadPrec a -> ReadPrec a
skipSpacesThenP :: ReadPrec a -> ReadPrec a
skipSpacesThenP ReadPrec a
m =
do String
s <- ReadPrec String
look
String -> ReadPrec a
skip String
s
where
skip :: String -> ReadPrec a
skip (Char
c:String
s) | Char -> Bool
isSpace Char
c = ReadPrec Char
get ReadPrec Char -> ReadPrec a -> ReadPrec a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
External instance of the constraint type Applicative ReadPrec
*> String -> ReadPrec a
skip String
s
skip String
_ = ReadPrec a
m
paren :: ReadPrec a -> ReadPrec a
paren :: ReadPrec a -> ReadPrec a
paren ReadPrec a
p = ReadPrec a -> ReadPrec a
forall a. ReadPrec a -> ReadPrec a
skipSpacesThenP (ReadPrec a -> ReadPrec a
forall a. ReadPrec a -> ReadPrec a
paren' ReadPrec a
p)
paren' :: ReadPrec a -> ReadPrec a
paren' :: ReadPrec a -> ReadPrec a
paren' ReadPrec a
p = Char -> ReadPrec a -> ReadPrec a
forall a. Char -> ReadPrec a -> ReadPrec a
expectCharP Char
'(' (ReadPrec a -> ReadPrec a) -> ReadPrec a -> ReadPrec a
forall a b. (a -> b) -> a -> b
$ ReadPrec a -> ReadPrec a
forall a. ReadPrec a -> ReadPrec a
reset ReadPrec a
p ReadPrec a -> (a -> ReadPrec a) -> ReadPrec a
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
External instance of the constraint type Monad ReadPrec
>>= \a
x ->
ReadPrec a -> ReadPrec a
forall a. ReadPrec a -> ReadPrec a
skipSpacesThenP (Char -> ReadPrec a -> ReadPrec a
forall a. Char -> ReadPrec a -> ReadPrec a
expectCharP Char
')' (a -> ReadPrec a
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type Applicative ReadPrec
pure a
x))
parens :: ReadPrec a -> ReadPrec a
parens :: ReadPrec a -> ReadPrec a
parens ReadPrec a
p = ReadPrec a
optional
where
optional :: ReadPrec a
optional = ReadPrec a -> ReadPrec a
forall a. ReadPrec a -> ReadPrec a
skipSpacesThenP (ReadPrec a
p ReadPrec a -> ReadPrec a -> ReadPrec a
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++ ReadPrec a
mandatory)
mandatory :: ReadPrec a
mandatory = ReadPrec a -> ReadPrec a
forall a. ReadPrec a -> ReadPrec a
paren' ReadPrec a
optional
list :: ReadPrec a -> ReadPrec [a]
list :: ReadPrec a -> ReadPrec [a]
list ReadPrec a
readx =
ReadPrec [a] -> ReadPrec [a]
forall a. ReadPrec a -> ReadPrec a
parens
( do Lexeme -> ReadPrec ()
expectP (String -> Lexeme
L.Punc String
"[")
(Bool -> ReadPrec [a]
listRest Bool
False ReadPrec [a] -> ReadPrec [a] -> ReadPrec [a]
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++ ReadPrec [a]
listNext)
)
where
listRest :: Bool -> ReadPrec [a]
listRest Bool
started =
do L.Punc String
c <- ReadPrec Lexeme
lexP
case String
c of
String
"]" -> [a] -> ReadPrec [a]
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ReadPrec
return []
String
"," | Bool
started -> ReadPrec [a]
listNext
String
_ -> ReadPrec [a]
forall a. ReadPrec a
pfail
listNext :: ReadPrec [a]
listNext =
do a
x <- ReadPrec a -> ReadPrec a
forall a. ReadPrec a -> ReadPrec a
reset ReadPrec a
readx
[a]
xs <- Bool -> ReadPrec [a]
listRest Bool
True
[a] -> ReadPrec [a]
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ReadPrec
return (a
xa -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
xs)
choose :: [(String, ReadPrec a)] -> ReadPrec a
choose :: [(String, ReadPrec a)] -> ReadPrec a
choose [(String, ReadPrec a)]
sps = ((String, ReadPrec a) -> ReadPrec a -> ReadPrec a)
-> ReadPrec a -> [(String, ReadPrec a)] -> ReadPrec a
forall a b. (a -> b -> b) -> b -> [a] -> b
foldr (ReadPrec a -> ReadPrec a -> ReadPrec a
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
(+++) (ReadPrec a -> ReadPrec a -> ReadPrec a)
-> ((String, ReadPrec a) -> ReadPrec a)
-> (String, ReadPrec a)
-> ReadPrec a
-> ReadPrec a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String, ReadPrec a) -> ReadPrec a
forall {b}. (String, ReadPrec b) -> ReadPrec b
try_one) ReadPrec a
forall a. ReadPrec a
pfail [(String, ReadPrec a)]
sps
where
try_one :: (String, ReadPrec b) -> ReadPrec b
try_one (String
s,ReadPrec b
p) = do { Lexeme
token <- ReadPrec Lexeme
lexP ;
case Lexeme
token of
L.Ident String
s' | String
sString -> String -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
==String
s' -> ReadPrec b
p
L.Symbol String
s' | String
sString -> String -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
==String
s' -> ReadPrec b
p
Lexeme
_other -> ReadPrec b
forall a. ReadPrec a
pfail }
readField :: String -> ReadPrec a -> ReadPrec a
readField :: String -> ReadPrec a -> ReadPrec a
readField String
fieldName ReadPrec a
readVal = do
Lexeme -> ReadPrec ()
expectP (String -> Lexeme
L.Ident String
fieldName)
Lexeme -> ReadPrec ()
expectP (String -> Lexeme
L.Punc String
"=")
ReadPrec a
readVal
{-# NOINLINE readField #-}
readFieldHash :: String -> ReadPrec a -> ReadPrec a
readFieldHash :: String -> ReadPrec a -> ReadPrec a
readFieldHash String
fieldName ReadPrec a
readVal = do
Lexeme -> ReadPrec ()
expectP (String -> Lexeme
L.Ident String
fieldName)
Lexeme -> ReadPrec ()
expectP (String -> Lexeme
L.Symbol String
"#")
Lexeme -> ReadPrec ()
expectP (String -> Lexeme
L.Punc String
"=")
ReadPrec a
readVal
{-# NOINLINE readFieldHash #-}
readSymField :: String -> ReadPrec a -> ReadPrec a
readSymField :: String -> ReadPrec a -> ReadPrec a
readSymField String
fieldName ReadPrec a
readVal = do
Lexeme -> ReadPrec ()
expectP (String -> Lexeme
L.Punc String
"(")
Lexeme -> ReadPrec ()
expectP (String -> Lexeme
L.Symbol String
fieldName)
Lexeme -> ReadPrec ()
expectP (String -> Lexeme
L.Punc String
")")
Lexeme -> ReadPrec ()
expectP (String -> Lexeme
L.Punc String
"=")
ReadPrec a
readVal
{-# NOINLINE readSymField #-}
deriving instance Read GeneralCategory
instance Read Char where
readPrec :: ReadPrec Char
readPrec =
ReadPrec Char -> ReadPrec Char
forall a. ReadPrec a -> ReadPrec a
parens
( do L.Char Char
c <- ReadPrec Lexeme
lexP
Char -> ReadPrec Char
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ReadPrec
return Char
c
)
readListPrec :: ReadPrec String
readListPrec =
ReadPrec String -> ReadPrec String
forall a. ReadPrec a -> ReadPrec a
parens
( do L.String String
s <- ReadPrec Lexeme
lexP
String -> ReadPrec String
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ReadPrec
return String
s
ReadPrec String -> ReadPrec String -> ReadPrec String
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
ReadPrec String
forall a. Read a => ReadPrec [a]
Instance of class: Read of the constraint type Read Char
readListPrecDefault
)
readList :: ReadS String
readList = ReadS String
forall a. Read a => ReadS [a]
Instance of class: Read of the constraint type Read Char
readListDefault
instance Read Bool where
readPrec :: ReadPrec Bool
readPrec =
ReadPrec Bool -> ReadPrec Bool
forall a. ReadPrec a -> ReadPrec a
parens
( do L.Ident String
s <- ReadPrec Lexeme
lexP
case String
s of
String
"True" -> Bool -> ReadPrec Bool
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ReadPrec
return Bool
True
String
"False" -> Bool -> ReadPrec Bool
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ReadPrec
return Bool
False
String
_ -> ReadPrec Bool
forall a. ReadPrec a
pfail
)
readListPrec :: ReadPrec [Bool]
readListPrec = ReadPrec [Bool]
forall a. Read a => ReadPrec [a]
Instance of class: Read of the constraint type Read Bool
readListPrecDefault
readList :: ReadS [Bool]
readList = ReadS [Bool]
forall a. Read a => ReadS [a]
Instance of class: Read of the constraint type Read Bool
readListDefault
instance Read Ordering where
readPrec :: ReadPrec Ordering
readPrec =
ReadPrec Ordering -> ReadPrec Ordering
forall a. ReadPrec a -> ReadPrec a
parens
( do L.Ident String
s <- ReadPrec Lexeme
lexP
case String
s of
String
"LT" -> Ordering -> ReadPrec Ordering
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ReadPrec
return Ordering
LT
String
"EQ" -> Ordering -> ReadPrec Ordering
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ReadPrec
return Ordering
EQ
String
"GT" -> Ordering -> ReadPrec Ordering
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ReadPrec
return Ordering
GT
String
_ -> ReadPrec Ordering
forall a. ReadPrec a
pfail
)
readListPrec :: ReadPrec [Ordering]
readListPrec = ReadPrec [Ordering]
forall a. Read a => ReadPrec [a]
Instance of class: Read of the constraint type Read Ordering
readListPrecDefault
readList :: ReadS [Ordering]
readList = ReadS [Ordering]
forall a. Read a => ReadS [a]
Instance of class: Read of the constraint type Read Ordering
readListDefault
deriving instance Read a => Read (NonEmpty a)
instance Read a => Read (Maybe a) where
readPrec :: ReadPrec (Maybe a)
readPrec =
ReadPrec (Maybe a) -> ReadPrec (Maybe a)
forall a. ReadPrec a -> ReadPrec a
parens
(do Lexeme -> ReadPrec ()
expectP (String -> Lexeme
L.Ident String
"Nothing")
Maybe a -> ReadPrec (Maybe a)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ReadPrec
return Maybe a
forall a. Maybe a
Nothing
ReadPrec (Maybe a) -> ReadPrec (Maybe a) -> ReadPrec (Maybe a)
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
Int -> ReadPrec (Maybe a) -> ReadPrec (Maybe a)
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
appPrec (
do Lexeme -> ReadPrec ()
expectP (String -> Lexeme
L.Ident String
"Just")
a
x <- ReadPrec a -> ReadPrec a
forall a. ReadPrec a -> ReadPrec a
step ReadPrec a
forall a. Read a => ReadPrec a
Evidence bound by a type signature of the constraint type Read a
readPrec
Maybe a -> ReadPrec (Maybe a)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ReadPrec
return (a -> Maybe a
forall a. a -> Maybe a
Just a
x))
)
readListPrec :: ReadPrec [Maybe a]
readListPrec = ReadPrec [Maybe a]
forall a. Read a => ReadPrec [a]
Instance of class: Read of the constraint type forall a. Read a => Read (Maybe a)
Evidence bound by a type signature of the constraint type Read a
readListPrecDefault
readList :: ReadS [Maybe a]
readList = ReadS [Maybe a]
forall a. Read a => ReadS [a]
Instance of class: Read of the constraint type forall a. Read a => Read (Maybe a)
Evidence bound by a type signature of the constraint type Read a
readListDefault
instance Read a => Read [a] where
{-# SPECIALISE instance Read [String] #-}
{-# SPECIALISE instance Read [Char] #-}
{-# SPECIALISE instance Read [Int] #-}
readPrec :: ReadPrec [a]
readPrec = ReadPrec [a]
forall a. Read a => ReadPrec [a]
Evidence bound by a type signature of the constraint type Read a
readListPrec
readListPrec :: ReadPrec [[a]]
readListPrec = ReadPrec [[a]]
forall a. Read a => ReadPrec [a]
Instance of class: Read of the constraint type forall a. Read a => Read [a]
Evidence bound by a type signature of the constraint type Read a
readListPrecDefault
readList :: ReadS [[a]]
readList = ReadS [[a]]
forall a. Read a => ReadS [a]
Instance of class: Read of the constraint type forall a. Read a => Read [a]
Evidence bound by a type signature of the constraint type Read a
readListDefault
instance (Ix a, Read a, Read b) => Read (Array a b) where
readPrec :: ReadPrec (Array a b)
readPrec = ReadPrec (Array a b) -> ReadPrec (Array a b)
forall a. ReadPrec a -> ReadPrec a
parens (ReadPrec (Array a b) -> ReadPrec (Array a b))
-> ReadPrec (Array a b) -> ReadPrec (Array a b)
forall a b. (a -> b) -> a -> b
$ Int -> ReadPrec (Array a b) -> ReadPrec (Array a b)
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
appPrec (ReadPrec (Array a b) -> ReadPrec (Array a b))
-> ReadPrec (Array a b) -> ReadPrec (Array a b)
forall a b. (a -> b) -> a -> b
$
do Lexeme -> ReadPrec ()
expectP (String -> Lexeme
L.Ident String
"array")
(a, a)
theBounds <- ReadPrec (a, a) -> ReadPrec (a, a)
forall a. ReadPrec a -> ReadPrec a
step ReadPrec (a, a)
forall a. Read a => ReadPrec a
Instance of class: Read of the constraint type forall a b. (Read a, Read b) => Read (a, b)
Evidence bound by a type signature of the constraint type Read a
readPrec
[(a, b)]
vals <- ReadPrec [(a, b)] -> ReadPrec [(a, b)]
forall a. ReadPrec a -> ReadPrec a
step ReadPrec [(a, b)]
forall a. Read a => ReadPrec a
Instance of class: Read of the constraint type forall a. Read a => Read [a]
Instance of class: Read of the constraint type forall a b. (Read a, Read b) => Read (a, b)
Evidence bound by a type signature of the constraint type Read a
Evidence bound by a type signature of the constraint type Read b
readPrec
Array a b -> ReadPrec (Array a b)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ReadPrec
return ((a, a) -> [(a, b)] -> Array a b
forall i e. Ix i => (i, i) -> [(i, e)] -> Array i e
Evidence bound by a type signature of the constraint type Ix a
array (a, a)
theBounds [(a, b)]
vals)
readListPrec :: ReadPrec [Array a b]
readListPrec = ReadPrec [Array a b]
forall a. Read a => ReadPrec [a]
Instance of class: Read of the constraint type forall a b. (Ix a, Read a, Read b) => Read (Array a b)
Evidence bound by a type signature of the constraint type Ix a
Evidence bound by a type signature of the constraint type Read a
Evidence bound by a type signature of the constraint type Read b
readListPrecDefault
readList :: ReadS [Array a b]
readList = ReadS [Array a b]
forall a. Read a => ReadS [a]
Instance of class: Read of the constraint type forall a b. (Ix a, Read a, Read b) => Read (Array a b)
Evidence bound by a type signature of the constraint type Ix a
Evidence bound by a type signature of the constraint type Read a
Evidence bound by a type signature of the constraint type Read b
readListDefault
instance Read L.Lexeme where
readPrec :: ReadPrec Lexeme
readPrec = ReadPrec Lexeme
lexP
readListPrec :: ReadPrec [Lexeme]
readListPrec = ReadPrec [Lexeme]
forall a. Read a => ReadPrec [a]
Instance of class: Read of the constraint type Read Lexeme
readListPrecDefault
readList :: ReadS [Lexeme]
readList = ReadS [Lexeme]
forall a. Read a => ReadS [a]
Instance of class: Read of the constraint type Read Lexeme
readListDefault
readNumber :: Num a => (L.Lexeme -> ReadPrec a) -> ReadPrec a
readNumber :: (Lexeme -> ReadPrec a) -> ReadPrec a
readNumber Lexeme -> ReadPrec a
convert =
ReadPrec a -> ReadPrec a
forall a. ReadPrec a -> ReadPrec a
parens
( do Lexeme
x <- ReadPrec Lexeme
lexP
case Lexeme
x of
L.Symbol String
"-" -> do Lexeme
y <- ReadPrec Lexeme
lexP
a
n <- Lexeme -> ReadPrec a
convert Lexeme
y
a -> ReadPrec a
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ReadPrec
return (a -> a
forall a. Num a => a -> a
Evidence bound by a type signature of the constraint type Num a
negate a
n)
Lexeme
_ -> Lexeme -> ReadPrec a
convert Lexeme
x
)
convertInt :: Num a => L.Lexeme -> ReadPrec a
convertInt :: Lexeme -> ReadPrec a
convertInt (L.Number Number
n)
| Just Integer
i <- Number -> Maybe Integer
L.numberToInteger Number
n = a -> ReadPrec a
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ReadPrec
return (Integer -> a
forall a. Num a => Integer -> a
Evidence bound by a type signature of the constraint type Num a
fromInteger Integer
i)
convertInt Lexeme
_ = ReadPrec a
forall a. ReadPrec a
pfail
convertFrac :: forall a . RealFloat a => L.Lexeme -> ReadPrec a
convertFrac :: Lexeme -> ReadPrec a
convertFrac (L.Ident String
"NaN") = a -> ReadPrec a
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ReadPrec
return (a
0 a -> a -> a
forall a. Fractional a => a -> a -> a
External instance of the constraint type forall a. RealFrac a => Fractional a
External instance of the constraint type forall a. RealFloat a => RealFrac a
Evidence bound by a type signature of the constraint type RealFloat a
/ a
0)
convertFrac (L.Ident String
"Infinity") = a -> ReadPrec a
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ReadPrec
return (a
1 a -> a -> a
forall a. Fractional a => a -> a -> a
External instance of the constraint type forall a. RealFrac a => Fractional a
External instance of the constraint type forall a. RealFloat a => RealFrac a
Evidence bound by a type signature of the constraint type RealFloat a
/ a
0)
convertFrac (L.Number Number
n) = let resRange :: (Int, Int)
resRange = a -> (Int, Int)
forall a. RealFloat a => a -> (Int, Int)
Evidence bound by a type signature of the constraint type RealFloat a
floatRange (a
forall a. HasCallStack => a
undefined :: a)
in case (Int, Int) -> Number -> Maybe Rational
L.numberToRangedRational (Int, Int)
resRange Number
n of
Maybe Rational
Nothing -> a -> ReadPrec a
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ReadPrec
return (a
1 a -> a -> a
forall a. Fractional a => a -> a -> a
External instance of the constraint type forall a. RealFrac a => Fractional a
External instance of the constraint type forall a. RealFloat a => RealFrac a
Evidence bound by a type signature of the constraint type RealFloat a
/ a
0)
Just Rational
rat -> a -> ReadPrec a
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ReadPrec
return (a -> ReadPrec a) -> a -> ReadPrec a
forall a b. (a -> b) -> a -> b
$ Rational -> a
forall a. Fractional a => Rational -> a
External instance of the constraint type forall a. RealFrac a => Fractional a
External instance of the constraint type forall a. RealFloat a => RealFrac a
Evidence bound by a type signature of the constraint type RealFloat a
fromRational Rational
rat
convertFrac Lexeme
_ = ReadPrec a
forall a. ReadPrec a
pfail
instance Read Int where
readPrec :: ReadPrec Int
readPrec = (Lexeme -> ReadPrec Int) -> ReadPrec Int
forall a. Num a => (Lexeme -> ReadPrec a) -> ReadPrec a
External instance of the constraint type Num Int
readNumber Lexeme -> ReadPrec Int
forall a. Num a => Lexeme -> ReadPrec a
External instance of the constraint type Num Int
convertInt
readListPrec :: ReadPrec [Int]
readListPrec = ReadPrec [Int]
forall a. Read a => ReadPrec [a]
Instance of class: Read of the constraint type Read Int
readListPrecDefault
readList :: ReadS [Int]
readList = ReadS [Int]
forall a. Read a => ReadS [a]
Instance of class: Read of the constraint type Read Int
readListDefault
instance Read Word where
readsPrec :: Int -> ReadS Word
readsPrec Int
p String
s = [(Integer -> Word
forall a. Num a => Integer -> a
External instance of the constraint type Num Word
fromInteger Integer
x, String
r) | (Integer
x, String
r) <- Int -> ReadS Integer
forall a. Read a => Int -> ReadS a
Instance of class: Read of the constraint type Read Integer
readsPrec Int
p String
s]
instance Read Word8 where
readsPrec :: Int -> ReadS Word8
readsPrec Int
p String
s = [(Int -> Word8
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Word8
External instance of the constraint type Integral Int
fromIntegral (Int
x::Int), String
r) | (Int
x, String
r) <- Int -> ReadS Int
forall a. Read a => Int -> ReadS a
Instance of class: Read of the constraint type Read Int
readsPrec Int
p String
s]
instance Read Word16 where
readsPrec :: Int -> ReadS Word16
readsPrec Int
p String
s = [(Int -> Word16
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Word16
External instance of the constraint type Integral Int
fromIntegral (Int
x::Int), String
r) | (Int
x, String
r) <- Int -> ReadS Int
forall a. Read a => Int -> ReadS a
Instance of class: Read of the constraint type Read Int
readsPrec Int
p String
s]
instance Read Word32 where
#if WORD_SIZE_IN_BITS < 33
readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]
#else
readsPrec :: Int -> ReadS Word32
readsPrec Int
p String
s = [(Int -> Word32
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Word32
External instance of the constraint type Integral Int
fromIntegral (Int
x::Int), String
r) | (Int
x, String
r) <- Int -> ReadS Int
forall a. Read a => Int -> ReadS a
Instance of class: Read of the constraint type Read Int
readsPrec Int
p String
s]
#endif
instance Read Word64 where
readsPrec :: Int -> ReadS Word64
readsPrec Int
p String
s = [(Integer -> Word64
forall a. Num a => Integer -> a
External instance of the constraint type Num Word64
fromInteger Integer
x, String
r) | (Integer
x, String
r) <- Int -> ReadS Integer
forall a. Read a => Int -> ReadS a
Instance of class: Read of the constraint type Read Integer
readsPrec Int
p String
s]
instance Read Integer where
readPrec :: ReadPrec Integer
readPrec = (Lexeme -> ReadPrec Integer) -> ReadPrec Integer
forall a. Num a => (Lexeme -> ReadPrec a) -> ReadPrec a
External instance of the constraint type Num Integer
readNumber Lexeme -> ReadPrec Integer
forall a. Num a => Lexeme -> ReadPrec a
External instance of the constraint type Num Integer
convertInt
readListPrec :: ReadPrec [Integer]
readListPrec = ReadPrec [Integer]
forall a. Read a => ReadPrec [a]
Instance of class: Read of the constraint type Read Integer
readListPrecDefault
readList :: ReadS [Integer]
readList = ReadS [Integer]
forall a. Read a => ReadS [a]
Instance of class: Read of the constraint type Read Integer
readListDefault
instance Read Natural where
readsPrec :: Int -> ReadS Natural
readsPrec Int
d = ((Integer, String) -> (Natural, String))
-> [(Integer, String)] -> [(Natural, String)]
forall a b. (a -> b) -> [a] -> [b]
map (\(Integer
n, String
s) -> (Integer -> Natural
forall a. Num a => Integer -> a
External instance of the constraint type Num Natural
fromInteger Integer
n, String
s))
([(Integer, String)] -> [(Natural, String)])
-> ReadS Integer -> ReadS Natural
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Integer, String) -> Bool)
-> [(Integer, String)] -> [(Integer, String)]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Integer
>= Integer
0) (Integer -> Bool)
-> ((Integer, String) -> Integer) -> (Integer, String) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (\(Integer
x,String
_)->Integer
x)) ([(Integer, String)] -> [(Integer, String)])
-> ReadS Integer -> ReadS Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ReadS Integer
forall a. Read a => Int -> ReadS a
Instance of class: Read of the constraint type Read Integer
readsPrec Int
d
instance Read Float where
readPrec :: ReadPrec Float
readPrec = (Lexeme -> ReadPrec Float) -> ReadPrec Float
forall a. Num a => (Lexeme -> ReadPrec a) -> ReadPrec a
External instance of the constraint type Num Float
readNumber Lexeme -> ReadPrec Float
forall a. RealFloat a => Lexeme -> ReadPrec a
External instance of the constraint type RealFloat Float
convertFrac
readListPrec :: ReadPrec [Float]
readListPrec = ReadPrec [Float]
forall a. Read a => ReadPrec [a]
Instance of class: Read of the constraint type Read Float
readListPrecDefault
readList :: ReadS [Float]
readList = ReadS [Float]
forall a. Read a => ReadS [a]
Instance of class: Read of the constraint type Read Float
readListDefault
instance Read Double where
readPrec :: ReadPrec Double
readPrec = (Lexeme -> ReadPrec Double) -> ReadPrec Double
forall a. Num a => (Lexeme -> ReadPrec a) -> ReadPrec a
External instance of the constraint type Num Double
readNumber Lexeme -> ReadPrec Double
forall a. RealFloat a => Lexeme -> ReadPrec a
External instance of the constraint type RealFloat Double
convertFrac
readListPrec :: ReadPrec [Double]
readListPrec = ReadPrec [Double]
forall a. Read a => ReadPrec [a]
Instance of class: Read of the constraint type Read Double
readListPrecDefault
readList :: ReadS [Double]
readList = ReadS [Double]
forall a. Read a => ReadS [a]
Instance of class: Read of the constraint type Read Double
readListDefault
instance (Integral a, Read a) => Read (Ratio a) where
readPrec :: ReadPrec (Ratio a)
readPrec =
ReadPrec (Ratio a) -> ReadPrec (Ratio a)
forall a. ReadPrec a -> ReadPrec a
parens
( Int -> ReadPrec (Ratio a) -> ReadPrec (Ratio a)
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
ratioPrec
( do a
x <- ReadPrec a -> ReadPrec a
forall a. ReadPrec a -> ReadPrec a
step ReadPrec a
forall a. Read a => ReadPrec a
Evidence bound by a type signature of the constraint type Read a
readPrec
Lexeme -> ReadPrec ()
expectP (String -> Lexeme
L.Symbol String
"%")
a
y <- ReadPrec a -> ReadPrec a
forall a. ReadPrec a -> ReadPrec a
step ReadPrec a
forall a. Read a => ReadPrec a
Evidence bound by a type signature of the constraint type Read a
readPrec
Ratio a -> ReadPrec (Ratio a)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ReadPrec
return (a
x a -> a -> Ratio a
forall a. Integral a => a -> a -> Ratio a
Evidence bound by a type signature of the constraint type Integral a
% a
y)
)
)
readListPrec :: ReadPrec [Ratio a]
readListPrec = ReadPrec [Ratio a]
forall a. Read a => ReadPrec [a]
Instance of class: Read of the constraint type forall a. (Integral a, Read a) => Read (Ratio a)
Evidence bound by a type signature of the constraint type Integral a
Evidence bound by a type signature of the constraint type Read a
readListPrecDefault
readList :: ReadS [Ratio a]
readList = ReadS [Ratio a]
forall a. Read a => ReadS [a]
Instance of class: Read of the constraint type forall a. (Integral a, Read a) => Read (Ratio a)
Evidence bound by a type signature of the constraint type Integral a
Evidence bound by a type signature of the constraint type Read a
readListDefault
instance Read () where
readPrec :: ReadPrec ()
readPrec =
ReadPrec () -> ReadPrec ()
forall a. ReadPrec a -> ReadPrec a
parens
( ReadPrec () -> ReadPrec ()
forall a. ReadPrec a -> ReadPrec a
paren
( () -> ReadPrec ()
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ReadPrec
return ()
)
)
readListPrec :: ReadPrec [()]
readListPrec = ReadPrec [()]
forall a. Read a => ReadPrec [a]
Instance of class: Read of the constraint type Read ()
readListPrecDefault
readList :: ReadS [()]
readList = ReadS [()]
forall a. Read a => ReadS [a]
Instance of class: Read of the constraint type Read ()
readListDefault
instance (Read a, Read b) => Read (a,b) where
readPrec :: ReadPrec (a, b)
readPrec = ReadPrec (a, b) -> ReadPrec (a, b)
forall a. ReadPrec a -> ReadPrec a
wrap_tup ReadPrec (a, b)
forall a b. (Read a, Read b) => ReadPrec (a, b)
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read a
read_tup2
readListPrec :: ReadPrec [(a, b)]
readListPrec = ReadPrec [(a, b)]
forall a. Read a => ReadPrec [a]
Instance of class: Read of the constraint type forall a b. (Read a, Read b) => Read (a, b)
Evidence bound by a type signature of the constraint type Read a
Evidence bound by a type signature of the constraint type Read b
readListPrecDefault
readList :: ReadS [(a, b)]
readList = ReadS [(a, b)]
forall a. Read a => ReadS [a]
Instance of class: Read of the constraint type forall a b. (Read a, Read b) => Read (a, b)
Evidence bound by a type signature of the constraint type Read a
Evidence bound by a type signature of the constraint type Read b
readListDefault
wrap_tup :: ReadPrec a -> ReadPrec a
wrap_tup :: ReadPrec a -> ReadPrec a
wrap_tup ReadPrec a
p = ReadPrec a -> ReadPrec a
forall a. ReadPrec a -> ReadPrec a
parens (ReadPrec a -> ReadPrec a
forall a. ReadPrec a -> ReadPrec a
paren ReadPrec a
p)
read_comma :: ReadPrec ()
read_comma :: ReadPrec ()
read_comma = Lexeme -> ReadPrec ()
expectP (String -> Lexeme
L.Punc String
",")
read_tup2 :: (Read a, Read b) => ReadPrec (a,b)
read_tup2 :: ReadPrec (a, b)
read_tup2 = do a
x <- ReadPrec a
forall a. Read a => ReadPrec a
Evidence bound by a type signature of the constraint type Read a
readPrec
ReadPrec ()
read_comma
b
y <- ReadPrec b
forall a. Read a => ReadPrec a
Evidence bound by a type signature of the constraint type Read b
readPrec
(a, b) -> ReadPrec (a, b)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ReadPrec
return (a
x,b
y)
read_tup4 :: (Read a, Read b, Read c, Read d) => ReadPrec (a,b,c,d)
read_tup4 :: ReadPrec (a, b, c, d)
read_tup4 = do (a
a,b
b) <- ReadPrec (a, b)
forall a b. (Read a, Read b) => ReadPrec (a, b)
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read a
read_tup2
ReadPrec ()
read_comma
(c
c,d
d) <- ReadPrec (c, d)
forall a b. (Read a, Read b) => ReadPrec (a, b)
Evidence bound by a type signature of the constraint type Read d
Evidence bound by a type signature of the constraint type Read c
read_tup2
(a, b, c, d) -> ReadPrec (a, b, c, d)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ReadPrec
return (a
a,b
b,c
c,d
d)
read_tup8 :: (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h)
=> ReadPrec (a,b,c,d,e,f,g,h)
read_tup8 :: ReadPrec (a, b, c, d, e, f, g, h)
read_tup8 = do (a
a,b
b,c
c,d
d) <- ReadPrec (a, b, c, d)
forall a b c d.
(Read a, Read b, Read c, Read d) =>
ReadPrec (a, b, c, d)
Evidence bound by a type signature of the constraint type Read d
Evidence bound by a type signature of the constraint type Read c
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read a
read_tup4
ReadPrec ()
read_comma
(e
e,f
f,g
g,h
h) <- ReadPrec (e, f, g, h)
forall a b c d.
(Read a, Read b, Read c, Read d) =>
ReadPrec (a, b, c, d)
Evidence bound by a type signature of the constraint type Read h
Evidence bound by a type signature of the constraint type Read g
Evidence bound by a type signature of the constraint type Read f
Evidence bound by a type signature of the constraint type Read e
read_tup4
(a, b, c, d, e, f, g, h) -> ReadPrec (a, b, c, d, e, f, g, h)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ReadPrec
return (a
a,b
b,c
c,d
d,e
e,f
f,g
g,h
h)
instance (Read a, Read b, Read c) => Read (a, b, c) where
readPrec :: ReadPrec (a, b, c)
readPrec = ReadPrec (a, b, c) -> ReadPrec (a, b, c)
forall a. ReadPrec a -> ReadPrec a
wrap_tup (do { (a
a,b
b) <- ReadPrec (a, b)
forall a b. (Read a, Read b) => ReadPrec (a, b)
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read a
read_tup2; ReadPrec ()
read_comma
; c
c <- ReadPrec c
forall a. Read a => ReadPrec a
Evidence bound by a type signature of the constraint type Read c
readPrec
; (a, b, c) -> ReadPrec (a, b, c)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ReadPrec
return (a
a,b
b,c
c) })
readListPrec :: ReadPrec [(a, b, c)]
readListPrec = ReadPrec [(a, b, c)]
forall a. Read a => ReadPrec [a]
Instance of class: Read of the constraint type forall a b c. (Read a, Read b, Read c) => Read (a, b, c)
Evidence bound by a type signature of the constraint type Read a
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read c
readListPrecDefault
readList :: ReadS [(a, b, c)]
readList = ReadS [(a, b, c)]
forall a. Read a => ReadS [a]
Instance of class: Read of the constraint type forall a b c. (Read a, Read b, Read c) => Read (a, b, c)
Evidence bound by a type signature of the constraint type Read a
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read c
readListDefault
instance (Read a, Read b, Read c, Read d) => Read (a, b, c, d) where
readPrec :: ReadPrec (a, b, c, d)
readPrec = ReadPrec (a, b, c, d) -> ReadPrec (a, b, c, d)
forall a. ReadPrec a -> ReadPrec a
wrap_tup ReadPrec (a, b, c, d)
forall a b c d.
(Read a, Read b, Read c, Read d) =>
ReadPrec (a, b, c, d)
Evidence bound by a type signature of the constraint type Read d
Evidence bound by a type signature of the constraint type Read c
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read a
read_tup4
readListPrec :: ReadPrec [(a, b, c, d)]
readListPrec = ReadPrec [(a, b, c, d)]
forall a. Read a => ReadPrec [a]
Instance of class: Read of the constraint type forall a b c d.
(Read a, Read b, Read c, Read d) =>
Read (a, b, c, d)
Evidence bound by a type signature of the constraint type Read a
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read c
Evidence bound by a type signature of the constraint type Read d
readListPrecDefault
readList :: ReadS [(a, b, c, d)]
readList = ReadS [(a, b, c, d)]
forall a. Read a => ReadS [a]
Instance of class: Read of the constraint type forall a b c d.
(Read a, Read b, Read c, Read d) =>
Read (a, b, c, d)
Evidence bound by a type signature of the constraint type Read a
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read c
Evidence bound by a type signature of the constraint type Read d
readListDefault
instance (Read a, Read b, Read c, Read d, Read e) => Read (a, b, c, d, e) where
readPrec :: ReadPrec (a, b, c, d, e)
readPrec = ReadPrec (a, b, c, d, e) -> ReadPrec (a, b, c, d, e)
forall a. ReadPrec a -> ReadPrec a
wrap_tup (do { (a
a,b
b,c
c,d
d) <- ReadPrec (a, b, c, d)
forall a b c d.
(Read a, Read b, Read c, Read d) =>
ReadPrec (a, b, c, d)
Evidence bound by a type signature of the constraint type Read d
Evidence bound by a type signature of the constraint type Read c
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read a
read_tup4; ReadPrec ()
read_comma
; e
e <- ReadPrec e
forall a. Read a => ReadPrec a
Evidence bound by a type signature of the constraint type Read e
readPrec
; (a, b, c, d, e) -> ReadPrec (a, b, c, d, e)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ReadPrec
return (a
a,b
b,c
c,d
d,e
e) })
readListPrec :: ReadPrec [(a, b, c, d, e)]
readListPrec = ReadPrec [(a, b, c, d, e)]
forall a. Read a => ReadPrec [a]
Instance of class: Read of the constraint type forall a b c d e.
(Read a, Read b, Read c, Read d, Read e) =>
Read (a, b, c, d, e)
Evidence bound by a type signature of the constraint type Read a
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read c
Evidence bound by a type signature of the constraint type Read d
Evidence bound by a type signature of the constraint type Read e
readListPrecDefault
readList :: ReadS [(a, b, c, d, e)]
readList = ReadS [(a, b, c, d, e)]
forall a. Read a => ReadS [a]
Instance of class: Read of the constraint type forall a b c d e.
(Read a, Read b, Read c, Read d, Read e) =>
Read (a, b, c, d, e)
Evidence bound by a type signature of the constraint type Read a
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read c
Evidence bound by a type signature of the constraint type Read d
Evidence bound by a type signature of the constraint type Read e
readListDefault
instance (Read a, Read b, Read c, Read d, Read e, Read f)
=> Read (a, b, c, d, e, f) where
readPrec :: ReadPrec (a, b, c, d, e, f)
readPrec = ReadPrec (a, b, c, d, e, f) -> ReadPrec (a, b, c, d, e, f)
forall a. ReadPrec a -> ReadPrec a
wrap_tup (do { (a
a,b
b,c
c,d
d) <- ReadPrec (a, b, c, d)
forall a b c d.
(Read a, Read b, Read c, Read d) =>
ReadPrec (a, b, c, d)
Evidence bound by a type signature of the constraint type Read d
Evidence bound by a type signature of the constraint type Read c
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read a
read_tup4; ReadPrec ()
read_comma
; (e
e,f
f) <- ReadPrec (e, f)
forall a b. (Read a, Read b) => ReadPrec (a, b)
Evidence bound by a type signature of the constraint type Read f
Evidence bound by a type signature of the constraint type Read e
read_tup2
; (a, b, c, d, e, f) -> ReadPrec (a, b, c, d, e, f)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ReadPrec
return (a
a,b
b,c
c,d
d,e
e,f
f) })
readListPrec :: ReadPrec [(a, b, c, d, e, f)]
readListPrec = ReadPrec [(a, b, c, d, e, f)]
forall a. Read a => ReadPrec [a]
Instance of class: Read of the constraint type forall a b c d e f.
(Read a, Read b, Read c, Read d, Read e, Read f) =>
Read (a, b, c, d, e, f)
Evidence bound by a type signature of the constraint type Read a
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read c
Evidence bound by a type signature of the constraint type Read d
Evidence bound by a type signature of the constraint type Read e
Evidence bound by a type signature of the constraint type Read f
readListPrecDefault
readList :: ReadS [(a, b, c, d, e, f)]
readList = ReadS [(a, b, c, d, e, f)]
forall a. Read a => ReadS [a]
Instance of class: Read of the constraint type forall a b c d e f.
(Read a, Read b, Read c, Read d, Read e, Read f) =>
Read (a, b, c, d, e, f)
Evidence bound by a type signature of the constraint type Read a
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read c
Evidence bound by a type signature of the constraint type Read d
Evidence bound by a type signature of the constraint type Read e
Evidence bound by a type signature of the constraint type Read f
readListDefault
instance (Read a, Read b, Read c, Read d, Read e, Read f, Read g)
=> Read (a, b, c, d, e, f, g) where
readPrec :: ReadPrec (a, b, c, d, e, f, g)
readPrec = ReadPrec (a, b, c, d, e, f, g) -> ReadPrec (a, b, c, d, e, f, g)
forall a. ReadPrec a -> ReadPrec a
wrap_tup (do { (a
a,b
b,c
c,d
d) <- ReadPrec (a, b, c, d)
forall a b c d.
(Read a, Read b, Read c, Read d) =>
ReadPrec (a, b, c, d)
Evidence bound by a type signature of the constraint type Read d
Evidence bound by a type signature of the constraint type Read c
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read a
read_tup4; ReadPrec ()
read_comma
; (e
e,f
f) <- ReadPrec (e, f)
forall a b. (Read a, Read b) => ReadPrec (a, b)
Evidence bound by a type signature of the constraint type Read f
Evidence bound by a type signature of the constraint type Read e
read_tup2; ReadPrec ()
read_comma
; g
g <- ReadPrec g
forall a. Read a => ReadPrec a
Evidence bound by a type signature of the constraint type Read g
readPrec
; (a, b, c, d, e, f, g) -> ReadPrec (a, b, c, d, e, f, g)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ReadPrec
return (a
a,b
b,c
c,d
d,e
e,f
f,g
g) })
readListPrec :: ReadPrec [(a, b, c, d, e, f, g)]
readListPrec = ReadPrec [(a, b, c, d, e, f, g)]
forall a. Read a => ReadPrec [a]
Instance of class: Read of the constraint type forall a b c d e f g.
(Read a, Read b, Read c, Read d, Read e, Read f, Read g) =>
Read (a, b, c, d, e, f, g)
Evidence bound by a type signature of the constraint type Read a
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read c
Evidence bound by a type signature of the constraint type Read d
Evidence bound by a type signature of the constraint type Read e
Evidence bound by a type signature of the constraint type Read f
Evidence bound by a type signature of the constraint type Read g
readListPrecDefault
readList :: ReadS [(a, b, c, d, e, f, g)]
readList = ReadS [(a, b, c, d, e, f, g)]
forall a. Read a => ReadS [a]
Instance of class: Read of the constraint type forall a b c d e f g.
(Read a, Read b, Read c, Read d, Read e, Read f, Read g) =>
Read (a, b, c, d, e, f, g)
Evidence bound by a type signature of the constraint type Read a
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read c
Evidence bound by a type signature of the constraint type Read d
Evidence bound by a type signature of the constraint type Read e
Evidence bound by a type signature of the constraint type Read f
Evidence bound by a type signature of the constraint type Read g
readListDefault
instance (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h)
=> Read (a, b, c, d, e, f, g, h) where
readPrec :: ReadPrec (a, b, c, d, e, f, g, h)
readPrec = ReadPrec (a, b, c, d, e, f, g, h)
-> ReadPrec (a, b, c, d, e, f, g, h)
forall a. ReadPrec a -> ReadPrec a
wrap_tup ReadPrec (a, b, c, d, e, f, g, h)
forall a b c d e f g h.
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h) =>
ReadPrec (a, b, c, d, e, f, g, h)
Evidence bound by a type signature of the constraint type Read h
Evidence bound by a type signature of the constraint type Read g
Evidence bound by a type signature of the constraint type Read f
Evidence bound by a type signature of the constraint type Read e
Evidence bound by a type signature of the constraint type Read d
Evidence bound by a type signature of the constraint type Read c
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read a
read_tup8
readListPrec :: ReadPrec [(a, b, c, d, e, f, g, h)]
readListPrec = ReadPrec [(a, b, c, d, e, f, g, h)]
forall a. Read a => ReadPrec [a]
Instance of class: Read of the constraint type forall a b c d e f g h.
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h) =>
Read (a, b, c, d, e, f, g, h)
Evidence bound by a type signature of the constraint type Read a
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read c
Evidence bound by a type signature of the constraint type Read d
Evidence bound by a type signature of the constraint type Read e
Evidence bound by a type signature of the constraint type Read f
Evidence bound by a type signature of the constraint type Read g
Evidence bound by a type signature of the constraint type Read h
readListPrecDefault
readList :: ReadS [(a, b, c, d, e, f, g, h)]
readList = ReadS [(a, b, c, d, e, f, g, h)]
forall a. Read a => ReadS [a]
Instance of class: Read of the constraint type forall a b c d e f g h.
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h) =>
Read (a, b, c, d, e, f, g, h)
Evidence bound by a type signature of the constraint type Read a
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read c
Evidence bound by a type signature of the constraint type Read d
Evidence bound by a type signature of the constraint type Read e
Evidence bound by a type signature of the constraint type Read f
Evidence bound by a type signature of the constraint type Read g
Evidence bound by a type signature of the constraint type Read h
readListDefault
instance (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
Read i)
=> Read (a, b, c, d, e, f, g, h, i) where
readPrec :: ReadPrec (a, b, c, d, e, f, g, h, i)
readPrec = ReadPrec (a, b, c, d, e, f, g, h, i)
-> ReadPrec (a, b, c, d, e, f, g, h, i)
forall a. ReadPrec a -> ReadPrec a
wrap_tup (do { (a
a,b
b,c
c,d
d,e
e,f
f,g
g,h
h) <- ReadPrec (a, b, c, d, e, f, g, h)
forall a b c d e f g h.
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h) =>
ReadPrec (a, b, c, d, e, f, g, h)
Evidence bound by a type signature of the constraint type Read h
Evidence bound by a type signature of the constraint type Read g
Evidence bound by a type signature of the constraint type Read f
Evidence bound by a type signature of the constraint type Read e
Evidence bound by a type signature of the constraint type Read d
Evidence bound by a type signature of the constraint type Read c
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read a
read_tup8; ReadPrec ()
read_comma
; i
i <- ReadPrec i
forall a. Read a => ReadPrec a
Evidence bound by a type signature of the constraint type Read i
readPrec
; (a, b, c, d, e, f, g, h, i) -> ReadPrec (a, b, c, d, e, f, g, h, i)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ReadPrec
return (a
a,b
b,c
c,d
d,e
e,f
f,g
g,h
h,i
i) })
readListPrec :: ReadPrec [(a, b, c, d, e, f, g, h, i)]
readListPrec = ReadPrec [(a, b, c, d, e, f, g, h, i)]
forall a. Read a => ReadPrec [a]
Instance of class: Read of the constraint type forall a b c d e f g h i.
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
Read i) =>
Read (a, b, c, d, e, f, g, h, i)
Evidence bound by a type signature of the constraint type Read a
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read c
Evidence bound by a type signature of the constraint type Read d
Evidence bound by a type signature of the constraint type Read e
Evidence bound by a type signature of the constraint type Read f
Evidence bound by a type signature of the constraint type Read g
Evidence bound by a type signature of the constraint type Read h
Evidence bound by a type signature of the constraint type Read i
readListPrecDefault
readList :: ReadS [(a, b, c, d, e, f, g, h, i)]
readList = ReadS [(a, b, c, d, e, f, g, h, i)]
forall a. Read a => ReadS [a]
Instance of class: Read of the constraint type forall a b c d e f g h i.
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
Read i) =>
Read (a, b, c, d, e, f, g, h, i)
Evidence bound by a type signature of the constraint type Read a
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read c
Evidence bound by a type signature of the constraint type Read d
Evidence bound by a type signature of the constraint type Read e
Evidence bound by a type signature of the constraint type Read f
Evidence bound by a type signature of the constraint type Read g
Evidence bound by a type signature of the constraint type Read h
Evidence bound by a type signature of the constraint type Read i
readListDefault
instance (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
Read i, Read j)
=> Read (a, b, c, d, e, f, g, h, i, j) where
readPrec :: ReadPrec (a, b, c, d, e, f, g, h, i, j)
readPrec = ReadPrec (a, b, c, d, e, f, g, h, i, j)
-> ReadPrec (a, b, c, d, e, f, g, h, i, j)
forall a. ReadPrec a -> ReadPrec a
wrap_tup (do { (a
a,b
b,c
c,d
d,e
e,f
f,g
g,h
h) <- ReadPrec (a, b, c, d, e, f, g, h)
forall a b c d e f g h.
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h) =>
ReadPrec (a, b, c, d, e, f, g, h)
Evidence bound by a type signature of the constraint type Read h
Evidence bound by a type signature of the constraint type Read g
Evidence bound by a type signature of the constraint type Read f
Evidence bound by a type signature of the constraint type Read e
Evidence bound by a type signature of the constraint type Read d
Evidence bound by a type signature of the constraint type Read c
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read a
read_tup8; ReadPrec ()
read_comma
; (i
i,j
j) <- ReadPrec (i, j)
forall a b. (Read a, Read b) => ReadPrec (a, b)
Evidence bound by a type signature of the constraint type Read j
Evidence bound by a type signature of the constraint type Read i
read_tup2
; (a, b, c, d, e, f, g, h, i, j)
-> ReadPrec (a, b, c, d, e, f, g, h, i, j)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ReadPrec
return (a
a,b
b,c
c,d
d,e
e,f
f,g
g,h
h,i
i,j
j) })
readListPrec :: ReadPrec [(a, b, c, d, e, f, g, h, i, j)]
readListPrec = ReadPrec [(a, b, c, d, e, f, g, h, i, j)]
forall a. Read a => ReadPrec [a]
Instance of class: Read of the constraint type forall a b c d e f g h i j.
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
Read i, Read j) =>
Read (a, b, c, d, e, f, g, h, i, j)
Evidence bound by a type signature of the constraint type Read a
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read c
Evidence bound by a type signature of the constraint type Read d
Evidence bound by a type signature of the constraint type Read e
Evidence bound by a type signature of the constraint type Read f
Evidence bound by a type signature of the constraint type Read g
Evidence bound by a type signature of the constraint type Read h
Evidence bound by a type signature of the constraint type Read i
Evidence bound by a type signature of the constraint type Read j
readListPrecDefault
readList :: ReadS [(a, b, c, d, e, f, g, h, i, j)]
readList = ReadS [(a, b, c, d, e, f, g, h, i, j)]
forall a. Read a => ReadS [a]
Instance of class: Read of the constraint type forall a b c d e f g h i j.
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
Read i, Read j) =>
Read (a, b, c, d, e, f, g, h, i, j)
Evidence bound by a type signature of the constraint type Read a
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read c
Evidence bound by a type signature of the constraint type Read d
Evidence bound by a type signature of the constraint type Read e
Evidence bound by a type signature of the constraint type Read f
Evidence bound by a type signature of the constraint type Read g
Evidence bound by a type signature of the constraint type Read h
Evidence bound by a type signature of the constraint type Read i
Evidence bound by a type signature of the constraint type Read j
readListDefault
instance (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
Read i, Read j, Read k)
=> Read (a, b, c, d, e, f, g, h, i, j, k) where
readPrec :: ReadPrec (a, b, c, d, e, f, g, h, i, j, k)
readPrec = ReadPrec (a, b, c, d, e, f, g, h, i, j, k)
-> ReadPrec (a, b, c, d, e, f, g, h, i, j, k)
forall a. ReadPrec a -> ReadPrec a
wrap_tup (do { (a
a,b
b,c
c,d
d,e
e,f
f,g
g,h
h) <- ReadPrec (a, b, c, d, e, f, g, h)
forall a b c d e f g h.
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h) =>
ReadPrec (a, b, c, d, e, f, g, h)
Evidence bound by a type signature of the constraint type Read h
Evidence bound by a type signature of the constraint type Read g
Evidence bound by a type signature of the constraint type Read f
Evidence bound by a type signature of the constraint type Read e
Evidence bound by a type signature of the constraint type Read d
Evidence bound by a type signature of the constraint type Read c
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read a
read_tup8; ReadPrec ()
read_comma
; (i
i,j
j) <- ReadPrec (i, j)
forall a b. (Read a, Read b) => ReadPrec (a, b)
Evidence bound by a type signature of the constraint type Read j
Evidence bound by a type signature of the constraint type Read i
read_tup2; ReadPrec ()
read_comma
; k
k <- ReadPrec k
forall a. Read a => ReadPrec a
Evidence bound by a type signature of the constraint type Read k
readPrec
; (a, b, c, d, e, f, g, h, i, j, k)
-> ReadPrec (a, b, c, d, e, f, g, h, i, j, k)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ReadPrec
return (a
a,b
b,c
c,d
d,e
e,f
f,g
g,h
h,i
i,j
j,k
k) })
readListPrec :: ReadPrec [(a, b, c, d, e, f, g, h, i, j, k)]
readListPrec = ReadPrec [(a, b, c, d, e, f, g, h, i, j, k)]
forall a. Read a => ReadPrec [a]
Instance of class: Read of the constraint type forall a b c d e f g h i j k.
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
Read i, Read j, Read k) =>
Read (a, b, c, d, e, f, g, h, i, j, k)
Evidence bound by a type signature of the constraint type Read a
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read c
Evidence bound by a type signature of the constraint type Read d
Evidence bound by a type signature of the constraint type Read e
Evidence bound by a type signature of the constraint type Read f
Evidence bound by a type signature of the constraint type Read g
Evidence bound by a type signature of the constraint type Read h
Evidence bound by a type signature of the constraint type Read i
Evidence bound by a type signature of the constraint type Read j
Evidence bound by a type signature of the constraint type Read k
readListPrecDefault
readList :: ReadS [(a, b, c, d, e, f, g, h, i, j, k)]
readList = ReadS [(a, b, c, d, e, f, g, h, i, j, k)]
forall a. Read a => ReadS [a]
Instance of class: Read of the constraint type forall a b c d e f g h i j k.
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
Read i, Read j, Read k) =>
Read (a, b, c, d, e, f, g, h, i, j, k)
Evidence bound by a type signature of the constraint type Read a
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read c
Evidence bound by a type signature of the constraint type Read d
Evidence bound by a type signature of the constraint type Read e
Evidence bound by a type signature of the constraint type Read f
Evidence bound by a type signature of the constraint type Read g
Evidence bound by a type signature of the constraint type Read h
Evidence bound by a type signature of the constraint type Read i
Evidence bound by a type signature of the constraint type Read j
Evidence bound by a type signature of the constraint type Read k
readListDefault
instance (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
Read i, Read j, Read k, Read l)
=> Read (a, b, c, d, e, f, g, h, i, j, k, l) where
readPrec :: ReadPrec (a, b, c, d, e, f, g, h, i, j, k, l)
readPrec = ReadPrec (a, b, c, d, e, f, g, h, i, j, k, l)
-> ReadPrec (a, b, c, d, e, f, g, h, i, j, k, l)
forall a. ReadPrec a -> ReadPrec a
wrap_tup (do { (a
a,b
b,c
c,d
d,e
e,f
f,g
g,h
h) <- ReadPrec (a, b, c, d, e, f, g, h)
forall a b c d e f g h.
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h) =>
ReadPrec (a, b, c, d, e, f, g, h)
Evidence bound by a type signature of the constraint type Read h
Evidence bound by a type signature of the constraint type Read g
Evidence bound by a type signature of the constraint type Read f
Evidence bound by a type signature of the constraint type Read e
Evidence bound by a type signature of the constraint type Read d
Evidence bound by a type signature of the constraint type Read c
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read a
read_tup8; ReadPrec ()
read_comma
; (i
i,j
j,k
k,l
l) <- ReadPrec (i, j, k, l)
forall a b c d.
(Read a, Read b, Read c, Read d) =>
ReadPrec (a, b, c, d)
Evidence bound by a type signature of the constraint type Read l
Evidence bound by a type signature of the constraint type Read k
Evidence bound by a type signature of the constraint type Read j
Evidence bound by a type signature of the constraint type Read i
read_tup4
; (a, b, c, d, e, f, g, h, i, j, k, l)
-> ReadPrec (a, b, c, d, e, f, g, h, i, j, k, l)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ReadPrec
return (a
a,b
b,c
c,d
d,e
e,f
f,g
g,h
h,i
i,j
j,k
k,l
l) })
readListPrec :: ReadPrec [(a, b, c, d, e, f, g, h, i, j, k, l)]
readListPrec = ReadPrec [(a, b, c, d, e, f, g, h, i, j, k, l)]
forall a. Read a => ReadPrec [a]
Instance of class: Read of the constraint type forall a b c d e f g h i j k l.
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
Read i, Read j, Read k, Read l) =>
Read (a, b, c, d, e, f, g, h, i, j, k, l)
Evidence bound by a type signature of the constraint type Read a
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read c
Evidence bound by a type signature of the constraint type Read d
Evidence bound by a type signature of the constraint type Read e
Evidence bound by a type signature of the constraint type Read f
Evidence bound by a type signature of the constraint type Read g
Evidence bound by a type signature of the constraint type Read h
Evidence bound by a type signature of the constraint type Read i
Evidence bound by a type signature of the constraint type Read j
Evidence bound by a type signature of the constraint type Read k
Evidence bound by a type signature of the constraint type Read l
readListPrecDefault
readList :: ReadS [(a, b, c, d, e, f, g, h, i, j, k, l)]
readList = ReadS [(a, b, c, d, e, f, g, h, i, j, k, l)]
forall a. Read a => ReadS [a]
Instance of class: Read of the constraint type forall a b c d e f g h i j k l.
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
Read i, Read j, Read k, Read l) =>
Read (a, b, c, d, e, f, g, h, i, j, k, l)
Evidence bound by a type signature of the constraint type Read a
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read c
Evidence bound by a type signature of the constraint type Read d
Evidence bound by a type signature of the constraint type Read e
Evidence bound by a type signature of the constraint type Read f
Evidence bound by a type signature of the constraint type Read g
Evidence bound by a type signature of the constraint type Read h
Evidence bound by a type signature of the constraint type Read i
Evidence bound by a type signature of the constraint type Read j
Evidence bound by a type signature of the constraint type Read k
Evidence bound by a type signature of the constraint type Read l
readListDefault
instance (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
Read i, Read j, Read k, Read l, Read m)
=> Read (a, b, c, d, e, f, g, h, i, j, k, l, m) where
readPrec :: ReadPrec (a, b, c, d, e, f, g, h, i, j, k, l, m)
readPrec = ReadPrec (a, b, c, d, e, f, g, h, i, j, k, l, m)
-> ReadPrec (a, b, c, d, e, f, g, h, i, j, k, l, m)
forall a. ReadPrec a -> ReadPrec a
wrap_tup (do { (a
a,b
b,c
c,d
d,e
e,f
f,g
g,h
h) <- ReadPrec (a, b, c, d, e, f, g, h)
forall a b c d e f g h.
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h) =>
ReadPrec (a, b, c, d, e, f, g, h)
Evidence bound by a type signature of the constraint type Read h
Evidence bound by a type signature of the constraint type Read g
Evidence bound by a type signature of the constraint type Read f
Evidence bound by a type signature of the constraint type Read e
Evidence bound by a type signature of the constraint type Read d
Evidence bound by a type signature of the constraint type Read c
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read a
read_tup8; ReadPrec ()
read_comma
; (i
i,j
j,k
k,l
l) <- ReadPrec (i, j, k, l)
forall a b c d.
(Read a, Read b, Read c, Read d) =>
ReadPrec (a, b, c, d)
Evidence bound by a type signature of the constraint type Read l
Evidence bound by a type signature of the constraint type Read k
Evidence bound by a type signature of the constraint type Read j
Evidence bound by a type signature of the constraint type Read i
read_tup4; ReadPrec ()
read_comma
; m
m <- ReadPrec m
forall a. Read a => ReadPrec a
Evidence bound by a type signature of the constraint type Read m
readPrec
; (a, b, c, d, e, f, g, h, i, j, k, l, m)
-> ReadPrec (a, b, c, d, e, f, g, h, i, j, k, l, m)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ReadPrec
return (a
a,b
b,c
c,d
d,e
e,f
f,g
g,h
h,i
i,j
j,k
k,l
l,m
m) })
readListPrec :: ReadPrec [(a, b, c, d, e, f, g, h, i, j, k, l, m)]
readListPrec = ReadPrec [(a, b, c, d, e, f, g, h, i, j, k, l, m)]
forall a. Read a => ReadPrec [a]
Instance of class: Read of the constraint type forall a b c d e f g h i j k l m.
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
Read i, Read j, Read k, Read l, Read m) =>
Read (a, b, c, d, e, f, g, h, i, j, k, l, m)
Evidence bound by a type signature of the constraint type Read a
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read c
Evidence bound by a type signature of the constraint type Read d
Evidence bound by a type signature of the constraint type Read e
Evidence bound by a type signature of the constraint type Read f
Evidence bound by a type signature of the constraint type Read g
Evidence bound by a type signature of the constraint type Read h
Evidence bound by a type signature of the constraint type Read i
Evidence bound by a type signature of the constraint type Read j
Evidence bound by a type signature of the constraint type Read k
Evidence bound by a type signature of the constraint type Read l
Evidence bound by a type signature of the constraint type Read m
readListPrecDefault
readList :: ReadS [(a, b, c, d, e, f, g, h, i, j, k, l, m)]
readList = ReadS [(a, b, c, d, e, f, g, h, i, j, k, l, m)]
forall a. Read a => ReadS [a]
Instance of class: Read of the constraint type forall a b c d e f g h i j k l m.
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
Read i, Read j, Read k, Read l, Read m) =>
Read (a, b, c, d, e, f, g, h, i, j, k, l, m)
Evidence bound by a type signature of the constraint type Read a
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read c
Evidence bound by a type signature of the constraint type Read d
Evidence bound by a type signature of the constraint type Read e
Evidence bound by a type signature of the constraint type Read f
Evidence bound by a type signature of the constraint type Read g
Evidence bound by a type signature of the constraint type Read h
Evidence bound by a type signature of the constraint type Read i
Evidence bound by a type signature of the constraint type Read j
Evidence bound by a type signature of the constraint type Read k
Evidence bound by a type signature of the constraint type Read l
Evidence bound by a type signature of the constraint type Read m
readListDefault
instance (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
Read i, Read j, Read k, Read l, Read m, Read n)
=> Read (a, b, c, d, e, f, g, h, i, j, k, l, m, n) where
readPrec :: ReadPrec (a, b, c, d, e, f, g, h, i, j, k, l, m, n)
readPrec = ReadPrec (a, b, c, d, e, f, g, h, i, j, k, l, m, n)
-> ReadPrec (a, b, c, d, e, f, g, h, i, j, k, l, m, n)
forall a. ReadPrec a -> ReadPrec a
wrap_tup (do { (a
a,b
b,c
c,d
d,e
e,f
f,g
g,h
h) <- ReadPrec (a, b, c, d, e, f, g, h)
forall a b c d e f g h.
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h) =>
ReadPrec (a, b, c, d, e, f, g, h)
Evidence bound by a type signature of the constraint type Read h
Evidence bound by a type signature of the constraint type Read g
Evidence bound by a type signature of the constraint type Read f
Evidence bound by a type signature of the constraint type Read e
Evidence bound by a type signature of the constraint type Read d
Evidence bound by a type signature of the constraint type Read c
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read a
read_tup8; ReadPrec ()
read_comma
; (i
i,j
j,k
k,l
l) <- ReadPrec (i, j, k, l)
forall a b c d.
(Read a, Read b, Read c, Read d) =>
ReadPrec (a, b, c, d)
Evidence bound by a type signature of the constraint type Read l
Evidence bound by a type signature of the constraint type Read k
Evidence bound by a type signature of the constraint type Read j
Evidence bound by a type signature of the constraint type Read i
read_tup4; ReadPrec ()
read_comma
; (m
m,n
n) <- ReadPrec (m, n)
forall a b. (Read a, Read b) => ReadPrec (a, b)
Evidence bound by a type signature of the constraint type Read n
Evidence bound by a type signature of the constraint type Read m
read_tup2
; (a, b, c, d, e, f, g, h, i, j, k, l, m, n)
-> ReadPrec (a, b, c, d, e, f, g, h, i, j, k, l, m, n)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ReadPrec
return (a
a,b
b,c
c,d
d,e
e,f
f,g
g,h
h,i
i,j
j,k
k,l
l,m
m,n
n) })
readListPrec :: ReadPrec [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)]
readListPrec = ReadPrec [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)]
forall a. Read a => ReadPrec [a]
Instance of class: Read of the constraint type forall a b c d e f g h i j k l m n.
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
Read i, Read j, Read k, Read l, Read m, Read n) =>
Read (a, b, c, d, e, f, g, h, i, j, k, l, m, n)
Evidence bound by a type signature of the constraint type Read a
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read c
Evidence bound by a type signature of the constraint type Read d
Evidence bound by a type signature of the constraint type Read e
Evidence bound by a type signature of the constraint type Read f
Evidence bound by a type signature of the constraint type Read g
Evidence bound by a type signature of the constraint type Read h
Evidence bound by a type signature of the constraint type Read i
Evidence bound by a type signature of the constraint type Read j
Evidence bound by a type signature of the constraint type Read k
Evidence bound by a type signature of the constraint type Read l
Evidence bound by a type signature of the constraint type Read m
Evidence bound by a type signature of the constraint type Read n
readListPrecDefault
readList :: ReadS [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)]
readList = ReadS [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)]
forall a. Read a => ReadS [a]
Instance of class: Read of the constraint type forall a b c d e f g h i j k l m n.
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
Read i, Read j, Read k, Read l, Read m, Read n) =>
Read (a, b, c, d, e, f, g, h, i, j, k, l, m, n)
Evidence bound by a type signature of the constraint type Read a
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read c
Evidence bound by a type signature of the constraint type Read d
Evidence bound by a type signature of the constraint type Read e
Evidence bound by a type signature of the constraint type Read f
Evidence bound by a type signature of the constraint type Read g
Evidence bound by a type signature of the constraint type Read h
Evidence bound by a type signature of the constraint type Read i
Evidence bound by a type signature of the constraint type Read j
Evidence bound by a type signature of the constraint type Read k
Evidence bound by a type signature of the constraint type Read l
Evidence bound by a type signature of the constraint type Read m
Evidence bound by a type signature of the constraint type Read n
readListDefault
instance (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
Read i, Read j, Read k, Read l, Read m, Read n, Read o)
=> Read (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) where
readPrec :: ReadPrec (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)
readPrec = ReadPrec (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)
-> ReadPrec (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)
forall a. ReadPrec a -> ReadPrec a
wrap_tup (do { (a
a,b
b,c
c,d
d,e
e,f
f,g
g,h
h) <- ReadPrec (a, b, c, d, e, f, g, h)
forall a b c d e f g h.
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h) =>
ReadPrec (a, b, c, d, e, f, g, h)
Evidence bound by a type signature of the constraint type Read h
Evidence bound by a type signature of the constraint type Read g
Evidence bound by a type signature of the constraint type Read f
Evidence bound by a type signature of the constraint type Read e
Evidence bound by a type signature of the constraint type Read d
Evidence bound by a type signature of the constraint type Read c
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read a
read_tup8; ReadPrec ()
read_comma
; (i
i,j
j,k
k,l
l) <- ReadPrec (i, j, k, l)
forall a b c d.
(Read a, Read b, Read c, Read d) =>
ReadPrec (a, b, c, d)
Evidence bound by a type signature of the constraint type Read l
Evidence bound by a type signature of the constraint type Read k
Evidence bound by a type signature of the constraint type Read j
Evidence bound by a type signature of the constraint type Read i
read_tup4; ReadPrec ()
read_comma
; (m
m,n
n) <- ReadPrec (m, n)
forall a b. (Read a, Read b) => ReadPrec (a, b)
Evidence bound by a type signature of the constraint type Read n
Evidence bound by a type signature of the constraint type Read m
read_tup2; ReadPrec ()
read_comma
; o
o <- ReadPrec o
forall a. Read a => ReadPrec a
Evidence bound by a type signature of the constraint type Read o
readPrec
; (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)
-> ReadPrec (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ReadPrec
return (a
a,b
b,c
c,d
d,e
e,f
f,g
g,h
h,i
i,j
j,k
k,l
l,m
m,n
n,o
o) })
readListPrec :: ReadPrec [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)]
readListPrec = ReadPrec [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)]
forall a. Read a => ReadPrec [a]
Instance of class: Read of the constraint type forall a b c d e f g h i j k l m n o.
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
Read i, Read j, Read k, Read l, Read m, Read n, Read o) =>
Read (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)
Evidence bound by a type signature of the constraint type Read a
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read c
Evidence bound by a type signature of the constraint type Read d
Evidence bound by a type signature of the constraint type Read e
Evidence bound by a type signature of the constraint type Read f
Evidence bound by a type signature of the constraint type Read g
Evidence bound by a type signature of the constraint type Read h
Evidence bound by a type signature of the constraint type Read i
Evidence bound by a type signature of the constraint type Read j
Evidence bound by a type signature of the constraint type Read k
Evidence bound by a type signature of the constraint type Read l
Evidence bound by a type signature of the constraint type Read m
Evidence bound by a type signature of the constraint type Read n
Evidence bound by a type signature of the constraint type Read o
readListPrecDefault
readList :: ReadS [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)]
readList = ReadS [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)]
forall a. Read a => ReadS [a]
Instance of class: Read of the constraint type forall a b c d e f g h i j k l m n o.
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
Read i, Read j, Read k, Read l, Read m, Read n, Read o) =>
Read (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)
Evidence bound by a type signature of the constraint type Read a
Evidence bound by a type signature of the constraint type Read b
Evidence bound by a type signature of the constraint type Read c
Evidence bound by a type signature of the constraint type Read d
Evidence bound by a type signature of the constraint type Read e
Evidence bound by a type signature of the constraint type Read f
Evidence bound by a type signature of the constraint type Read g
Evidence bound by a type signature of the constraint type Read h
Evidence bound by a type signature of the constraint type Read i
Evidence bound by a type signature of the constraint type Read j
Evidence bound by a type signature of the constraint type Read k
Evidence bound by a type signature of the constraint type Read l
Evidence bound by a type signature of the constraint type Read m
Evidence bound by a type signature of the constraint type Read n
Evidence bound by a type signature of the constraint type Read o
readListDefault