{-# LANGUAGE Trustworthy #-}{-# LANGUAGE CPP, NoImplicitPrelude, StandaloneDeriving, ScopedTypeVariables #-}{-# OPTIONS_HADDOCK not-home #-}------------------------------------------------------------------------------- |-- Module : GHC.Read-- Copyright : (c) The University of Glasgow, 1994-2002-- License : see libraries/base/LICENSE---- Maintainer : cvs-ghc@haskell.org-- Stability : internal-- Portability : non-portable (GHC Extensions)---- The 'Read' class and instances for basic data types.-------------------------------------------------------------------------------moduleGHC.Read(Read (..)-- class-- ReadS type,ReadS -- H2010 compatibility,lex ,lexLitChar ,readLitChar ,lexDigits -- defining readers,lexP ,expectP ,paren ,parens ,list ,choose ,readListDefault ,readListPrecDefault ,readNumber ,readField ,readFieldHash ,readSymField -- Temporary,readParen )where #include "MachDeps.h" importqualifiedText.ParserCombinators.ReadP asPimportText.ParserCombinators.ReadP (ReadS ,readP_to_S )importqualifiedText.Read.Lex asL-- Lex exports 'lex', which is also defined here,-- hence the qualified import.-- We can't import *anything* unqualified, because that-- confuses Haddock.importText.ParserCombinators.ReadPrec importData.Maybe importGHC.Unicode importGHC.Num importGHC.Real importGHC.Float importGHC.Show importGHC.Base importGHC.Arr importGHC.Word importGHC.List (filter )-- | @'readParen' 'True' p@ parses what @p@ parses, but surrounded with-- parentheses.---- @'readParen' 'False' p@ parses what @p@ parses, but optionally-- surrounded with parentheses.readParen ::Bool->ReadS a ->ReadS a -- A Haskell 2010 functionreadParen :: Bool -> ReadS a -> ReadS a readParen b :: Bool b g :: ReadS a g =ifBool b thenReadS a mandatory elseReadS a optional whereoptional :: ReadS a optional r :: 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 r :: String r =do("(",s :: String s )<-ReadS String lex String r (x :: a x ,t :: String t )<-ReadS a optional String s (")",u :: String u )<-ReadS String lex String t (a, String) -> [(a, String)] forall (m :: * -> *) a. Monad m => a -> m a return (a x ,String u )-- | Parsing of 'String's, producing values.---- Derived instances of 'Read' make the following assumptions, which-- derived instances of 'Text.Show.Show' obey:---- * If the constructor is defined to be an infix operator, then the-- derived 'Read' instance will parse only infix applications of-- the constructor (not the prefix form).---- * Associativity is not used to reduce the occurrence of parentheses,-- although precedence may be.---- * If the constructor is defined using record syntax, the derived 'Read'-- will parse only the record-syntax form, and furthermore, the fields-- must be given in the same order as the original declaration.---- * The derived 'Read' instance allows arbitrary Haskell whitespace-- between tokens of the input string. Extra parentheses are also-- allowed.---- For example, given the declarations---- > infixr 5 :^:-- > data Tree a = Leaf a | Tree a :^: Tree a---- the derived instance of 'Read' in Haskell 2010 is equivalent to---- > instance (Read a) => Read (Tree a) where-- >-- > readsPrec d r = readParen (d > app_prec)-- > (\r -> [(Leaf m,t) |-- > ("Leaf",s) <- lex r,-- > (m,t) <- readsPrec (app_prec+1) s]) r-- >-- > ++ readParen (d > up_prec)-- > (\r -> [(u:^:v,w) |-- > (u,s) <- readsPrec (up_prec+1) r,-- > (":^:",t) <- lex s,-- > (v,w) <- readsPrec (up_prec+1) t]) r-- >-- > where app_prec = 10-- > up_prec = 5---- Note that right-associativity of @:^:@ is unused.---- The derived instance in GHC is equivalent to---- > instance (Read a) => Read (Tree a) where-- >-- > readPrec = parens $ (prec app_prec $ do-- > Ident "Leaf" <- lexP-- > m <- step readPrec-- > return (Leaf m))-- >-- > +++ (prec up_prec $ do-- > u <- step readPrec-- > Symbol ":^:" <- lexP-- > v <- step readPrec-- > return (u :^: v))-- >-- > where app_prec = 10-- > up_prec = 5-- >-- > readListPrec = readListPrecDefault---- Why do both 'readsPrec' and 'readPrec' exist, and why does GHC opt to-- implement 'readPrec' in derived 'Read' instances instead of 'readsPrec'?-- The reason is that 'readsPrec' is based on the 'ReadS' type, and although-- 'ReadS' is mentioned in the Haskell 2010 Report, it is not a very efficient-- parser data structure.---- 'readPrec', on the other hand, is based on a much more efficient 'ReadPrec'-- datatype (a.k.a \"new-style parsers\"), but its definition relies on the use-- of the @RankNTypes@ language extension. Therefore, 'readPrec' (and its-- cousin, 'readListPrec') are marked as GHC-only. Nevertheless, it is-- recommended to use 'readPrec' instead of 'readsPrec' whenever possible-- for the efficiency improvements it brings.---- As mentioned above, derived 'Read' instances in GHC will implement-- 'readPrec' instead of 'readsPrec'. The default implementations of-- 'readsPrec' (and its cousin, 'readList') will simply use 'readPrec' under-- the hood. If you are writing a 'Read' instance by hand, it is recommended-- to write it like so:---- @-- instance 'Read' T where-- 'readPrec' = ...-- 'readListPrec' = 'readListPrecDefault'-- @classRead a where{-# MINIMALreadsPrec |readPrec #-}-- | attempts to parse a value from the front of the string, returning-- a list of (parsed value, remaining string) pairs. If there is no-- successful parse, the returned list is empty.---- Derived instances of 'Read' and 'Text.Show.Show' satisfy the following:---- * @(x,\"\")@ is an element of-- @('readsPrec' d ('Text.Show.showsPrec' d x \"\"))@.---- That is, 'readsPrec' parses the string produced by-- 'Text.Show.showsPrec', and delivers the value that-- 'Text.Show.showsPrec' started with.readsPrec ::Int-- ^ the operator precedence of the enclosing-- context (a number from @0@ to @11@).-- Function application has precedence @10@.->ReadS a -- | The method 'readList' is provided to allow the programmer to-- give a specialised way of parsing lists of values.-- For example, this is used by the predefined 'Read' instance of-- the 'Char' type, where values of type 'String' should be are-- expected to use double quotes, rather than square brackets.readList ::ReadS [a ]-- | Proposed replacement for 'readsPrec' using new-style parsers (GHC only).readPrec ::ReadPrec a -- | Proposed replacement for 'readList' using new-style parsers (GHC only).-- The default definition uses 'readList'. Instances that define 'readPrec'-- should also define 'readListPrec' as 'readListPrecDefault'.readListPrec ::ReadPrec [a ]-- default definitionsreadsPrec =ReadPrec a -> Int -> ReadS a forall a. ReadPrec a -> Int -> ReadS a readPrec_to_S ReadPrec a forall a. Read a => ReadPrec 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 readPrec )0readPrec =(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 readsPrec readListPrec =(Int -> ReadS [a]) -> ReadPrec [a] forall a. (Int -> ReadS a) -> ReadPrec a readS_to_Prec (\_->ReadS [a] forall a. Read a => ReadS [a] readList )readListDefault ::Read a =>ReadS [a ]-- ^ A possible replacement definition for the 'readList' method (GHC only).-- This is only needed for GHC, and even then only for 'Read' instances-- where 'readListPrec' isn't defined as 'readListPrecDefault'.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] readListPrec 0readListPrecDefault ::Read a =>ReadPrec [a ]-- ^ A possible replacement definition for the 'readListPrec' method,-- defined using 'readPrec' (GHC only).readListPrecDefault :: ReadPrec [a] readListPrecDefault =ReadPrec a -> ReadPrec [a] forall a. ReadPrec a -> ReadPrec [a] list ReadPrec a forall a. Read a => ReadPrec a readPrec -------------------------------------------------------------------------- H2010 compatibility-- | The 'lex' function reads a single lexeme from the input, discarding-- initial white space, and returning the characters that constitute the-- lexeme. If the input string contains only white space, 'lex' returns a-- single successful \`lexeme\' consisting of the empty string. (Thus-- @'lex' \"\" = [(\"\",\"\")]@.) If there is no legal lexeme at the-- beginning of the input string, 'lex' fails (i.e. returns @[]@).---- This lexer is not completely faithful to the Haskell lexical syntax-- in the following respects:---- * Qualified names are not handled properly---- * Octal and hexadecimal numerics are not recognized as a single token---- * Comments are not treated properlylex ::ReadS String -- As defined by H2010lex :: ReadS String lex s :: String s =ReadP String -> ReadS String forall a. ReadP a -> ReadS a readP_to_S ReadP String L.hsLex String s -- | Read a string representation of a character, using Haskell-- source-language escape conventions. For example:---- > lexLitChar "\\nHello" = [("\\n", "Hello")]--lexLitChar ::ReadS String -- As defined by H2010lexLitChar :: ReadS String lexLitChar =ReadP String -> ReadS String forall a. ReadP a -> ReadS a readP_to_S (do{(s :: String s ,_)<-ReadP Char -> ReadP (String, Char) forall a. ReadP a -> ReadP (String, a) P.gather ReadP Char L.lexChar ;lets' :: String s' =String -> String removeNulls String s inString -> ReadP String forall (m :: * -> *) a. Monad m => a -> m a return String s' })where-- remove nulls from end of the character if they existremoveNulls :: String -> String removeNulls []=[]removeNulls ('\\':'&':xs :: String xs )=String -> String removeNulls String xs removeNulls (first :: Char first :rest :: String rest )=Char first Char -> String -> String forall a. a -> [a] -> [a] :String -> String removeNulls String rest -- There was a skipSpaces before the P.gather L.lexChar,-- but that seems inconsistent with readLitChar-- | Read a string representation of a character, using Haskell-- source-language escape conventions, and convert it to the character-- that it encodes. For example:---- > readLitChar "\\nHello" = [('\n', "Hello")]--readLitChar ::ReadS Char-- As defined by H2010readLitChar :: ReadS Char readLitChar =ReadP Char -> ReadS Char forall a. ReadP a -> ReadS a readP_to_S ReadP Char L.lexChar -- | Reads a non-empty string of decimal digits.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 )-------------------------------------------------------------------------- utility parserslexP ::ReadPrec L.Lexeme -- ^ Parse a single lexemelexP :: 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 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 c :: Char c a :: ReadPrec a a =doChar q <-ReadPrec Char get ifChar q Char -> Char -> Bool forall a. Eq a => a -> a -> Bool ==Char c thenReadPrec a a elseReadPrec a forall a. ReadPrec a pfail {-# INLINEexpectCharP #-}skipSpacesThenP ::ReadPrec a ->ReadPrec a skipSpacesThenP :: ReadPrec a -> ReadPrec a skipSpacesThenP m :: ReadPrec a m =doString s <-ReadPrec String look String -> ReadPrec a skip String s whereskip :: String -> ReadPrec a skip (c :: Char c :s :: 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 *> String -> ReadPrec a skip String s skip _=ReadPrec a m paren ::ReadPrec a ->ReadPrec a -- ^ @(paren p)@ parses \"(P0)\"-- where @p@ parses \"P0\" in precedence context zeroparen :: ReadPrec a -> ReadPrec a paren p :: 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' p :: ReadPrec a p =Char -> ReadPrec a -> ReadPrec a forall a. Char -> ReadPrec a -> ReadPrec a expectCharP '('(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 >>= \x :: 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 ')'(a -> ReadPrec a forall (f :: * -> *) a. Applicative f => a -> f a pure a x ))parens ::ReadPrec a ->ReadPrec a -- ^ @(parens p)@ parses \"P\", \"(P0)\", \"((P0))\", etc,-- where @p@ parses \"P\" in the current precedence context-- and parses \"P0\" in precedence context zeroparens :: ReadPrec a -> ReadPrec a parens p :: ReadPrec a p =ReadPrec a optional whereoptional :: 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 p)@ parses a list of things parsed by @p@,-- using the usual square-bracket syntax.list :: ReadPrec a -> ReadPrec [a] list readx :: ReadPrec a readx =ReadPrec [a] -> ReadPrec [a] forall a. ReadPrec a -> ReadPrec a parens (doLexeme -> ReadPrec () expectP (String -> Lexeme L.Punc "[")(Bool -> ReadPrec [a] listRest Bool FalseReadPrec [a] -> ReadPrec [a] -> ReadPrec [a] forall a. ReadPrec a -> ReadPrec a -> ReadPrec a +++ ReadPrec [a] listNext ))wherelistRest :: Bool -> ReadPrec [a] listRest started :: Bool started =doL.Punc c :: String c <-ReadPrec Lexeme lexP caseString c of"]"->[a] -> ReadPrec [a] forall (m :: * -> *) a. Monad m => a -> m a return []","|Bool started ->ReadPrec [a] listNext _->ReadPrec [a] forall a. ReadPrec a pfail listNext :: ReadPrec [a] listNext =doa 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 return (a x a -> [a] -> [a] forall a. a -> [a] -> [a] :[a] xs )choose ::[(String ,ReadPrec a )]->ReadPrec a -- ^ Parse the specified lexeme and continue as specified.-- Esp useful for nullary constructors; e.g.-- @choose [(\"A\", return A), (\"B\", return B)]@-- We match both Ident and Symbol because the constructor-- might be an operator eg @(:~:)@choose :: [(String, ReadPrec a)] -> ReadPrec a choose sps :: [(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 wheretry_one :: (String, ReadPrec b) -> ReadPrec b try_one (s :: String s ,p :: ReadPrec b p )=do{Lexeme token <-ReadPrec Lexeme lexP ;caseLexeme token ofL.Ident s' :: String s' |String s String -> String -> Bool forall a. Eq a => a -> a -> Bool ==String s' ->ReadPrec b p L.Symbol s' :: String s' |String s String -> String -> Bool forall a. Eq a => a -> a -> Bool ==String s' ->ReadPrec b p _other :: Lexeme _other ->ReadPrec b forall a. ReadPrec a pfail }-- See Note [Why readField]-- | 'Read' parser for a record field, of the form @fieldName=value@. The-- @fieldName@ must be an alphanumeric identifier; for symbols (operator-style)-- field names, e.g. @(#)@, use 'readSymField'). The second argument is a-- parser for the field value.readField ::String ->ReadPrec a ->ReadPrec a readField :: String -> ReadPrec a -> ReadPrec a readField fieldName :: String fieldName readVal :: ReadPrec a readVal =doLexeme -> ReadPrec () expectP (String -> Lexeme L.Ident String fieldName )Lexeme -> ReadPrec () expectP (String -> Lexeme L.Punc "=")ReadPrec a readVal {-# NOINLINEreadField #-}-- See Note [Why readField]-- | 'Read' parser for a record field, of the form @fieldName#=value@. That is,-- an alphanumeric identifier @fieldName@ followed by the symbol @#@. The-- second argument is a parser for the field value.---- Note that 'readField' does not suffice for this purpose due to-- <https://ghc.haskell.org/trac/ghc/ticket/5041 Trac #5041>.readFieldHash ::String ->ReadPrec a ->ReadPrec a readFieldHash :: String -> ReadPrec a -> ReadPrec a readFieldHash fieldName :: String fieldName readVal :: ReadPrec a readVal =doLexeme -> ReadPrec () expectP (String -> Lexeme L.Ident String fieldName )Lexeme -> ReadPrec () expectP (String -> Lexeme L.Symbol "#")Lexeme -> ReadPrec () expectP (String -> Lexeme L.Punc "=")ReadPrec a readVal {-# NOINLINEreadFieldHash #-}-- See Note [Why readField]-- | 'Read' parser for a symbol record field, of the form @(###)=value@ (where-- @###@ is the field name). The field name must be a symbol (operator-style),-- e.g. @(#)@. For regular (alphanumeric) field names, use 'readField'. The-- second argument is a parser for the field value.readSymField ::String ->ReadPrec a ->ReadPrec a readSymField :: String -> ReadPrec a -> ReadPrec a readSymField fieldName :: String fieldName readVal :: ReadPrec a readVal =doLexeme -> ReadPrec () expectP (String -> Lexeme L.Punc "(")Lexeme -> ReadPrec () expectP (String -> Lexeme L.Symbol String fieldName )Lexeme -> ReadPrec () expectP (String -> Lexeme L.Punc ")")Lexeme -> ReadPrec () expectP (String -> Lexeme L.Punc "=")ReadPrec a readVal {-# NOINLINEreadSymField #-}-- Note [Why readField]---- Previously, the code for automatically deriving Read instance (in-- typecheck/TcGenDeriv.hs) would generate inline code for parsing fields;-- this, however, turned out to produce massive amounts of intermediate code,-- and produced a considerable performance hit in the code generator.-- Since Read instances are not generally supposed to be perfomance critical,-- the readField and readSymField functions have been factored out, and the-- code generator now just generates calls rather than manually inlining the-- parsers. For large record types (e.g. 500 fields), this produces a-- significant performance boost.---- See also Trac #14364.---------------------------------------------------------------- Simple instances of Read---------------------------------------------------------------- | @since 2.01derivinginstanceRead GeneralCategory -- | @since 2.01instanceRead CharwherereadPrec :: ReadPrec Char readPrec =ReadPrec Char -> ReadPrec Char forall a. ReadPrec a -> ReadPrec a parens (doL.Char c :: Char c <-ReadPrec Lexeme lexP Char -> ReadPrec Char forall (m :: * -> *) a. Monad m => a -> m a return Char c )readListPrec :: ReadPrec String readListPrec =ReadPrec String -> ReadPrec String forall a. ReadPrec a -> ReadPrec a parens (doL.String s :: String s <-ReadPrec Lexeme lexP -- Looks for "foo"String -> ReadPrec String forall (m :: * -> *) a. Monad m => a -> m a 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] readListPrecDefault -- Looks for ['f','o','o'])-- (more generous than H2010 spec)readList :: ReadS String readList =ReadS String forall a. Read a => ReadS [a] readListDefault -- | @since 2.01instanceRead BoolwherereadPrec :: ReadPrec Bool readPrec =ReadPrec Bool -> ReadPrec Bool forall a. ReadPrec a -> ReadPrec a parens (doL.Ident s :: String s <-ReadPrec Lexeme lexP caseString s of"True"->Bool -> ReadPrec Bool forall (m :: * -> *) a. Monad m => a -> m a return Bool True"False"->Bool -> ReadPrec Bool forall (m :: * -> *) a. Monad m => a -> m a return Bool False_->ReadPrec Bool forall a. ReadPrec a pfail )readListPrec :: ReadPrec [Bool] readListPrec =ReadPrec [Bool] forall a. Read a => ReadPrec [a] readListPrecDefault readList :: ReadS [Bool] readList =ReadS [Bool] forall a. Read a => ReadS [a] readListDefault -- | @since 2.01instanceRead OrderingwherereadPrec :: ReadPrec Ordering readPrec =ReadPrec Ordering -> ReadPrec Ordering forall a. ReadPrec a -> ReadPrec a parens (doL.Ident s :: String s <-ReadPrec Lexeme lexP caseString s of"LT"->Ordering -> ReadPrec Ordering forall (m :: * -> *) a. Monad m => a -> m a return Ordering LT"EQ"->Ordering -> ReadPrec Ordering forall (m :: * -> *) a. Monad m => a -> m a return Ordering EQ"GT"->Ordering -> ReadPrec Ordering forall (m :: * -> *) a. Monad m => a -> m a return Ordering GT_->ReadPrec Ordering forall a. ReadPrec a pfail )readListPrec :: ReadPrec [Ordering] readListPrec =ReadPrec [Ordering] forall a. Read a => ReadPrec [a] readListPrecDefault readList :: ReadS [Ordering] readList =ReadS [Ordering] forall a. Read a => ReadS [a] readListDefault -- | @since 4.11.0.0derivinginstanceRead a =>Read (NonEmpty a )---------------------------------------------------------------- Structure instances of Read: Maybe, List etc--------------------------------------------------------------{- For structured instances of Read we start using the precedences. The idea is then that 'parens (prec k p)' will fail immediately when trying to parse it in a context with a higher precedence level than k. But if there is one parenthesis parsed, then the required precedence level drops to 0 again, and parsing inside p may succeed. 'appPrec' is just the precedence level of function application. So, if we are parsing function application, we'd better require the precedence level to be at least 'appPrec'. Otherwise, we have to put parentheses around it. 'step' is used to increase the precedence levels inside a parser, and can be used to express left- or right- associativity. For example, % is defined to be left associative, so we only increase precedence on the right hand side. Note how step is used in for example the Maybe parser to increase the precedence beyond appPrec, so that basically only literals and parenthesis-like objects such as (...) and [...] can be an argument to 'Just'. -}-- | @since 2.01instanceRead a =>Read (Maybe a )wherereadPrec :: ReadPrec (Maybe a) readPrec =ReadPrec (Maybe a) -> ReadPrec (Maybe a) forall a. ReadPrec a -> ReadPrec a parens (doLexeme -> ReadPrec () expectP (String -> Lexeme L.Ident "Nothing")Maybe a -> ReadPrec (Maybe a) forall (m :: * -> *) a. Monad m => a -> m a 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 (doLexeme -> ReadPrec () expectP (String -> Lexeme L.Ident "Just")a x <-ReadPrec a -> ReadPrec a forall a. ReadPrec a -> ReadPrec a step ReadPrec a forall a. Read a => ReadPrec a readPrec Maybe a -> ReadPrec (Maybe a) forall (m :: * -> *) a. Monad m => a -> m a 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] readListPrecDefault readList :: ReadS [Maybe a] readList =ReadS [Maybe a] forall a. Read a => ReadS [a] readListDefault -- | @since 2.01instanceRead a =>Read [a ]where{-# SPECIALISEinstanceRead [String ]#-}{-# SPECIALISEinstanceRead [Char]#-}{-# SPECIALISEinstanceRead [Int]#-}readPrec :: ReadPrec [a] readPrec =ReadPrec [a] forall a. Read a => ReadPrec [a] readListPrec readListPrec :: ReadPrec [[a]] readListPrec =ReadPrec [[a]] forall a. Read a => ReadPrec [a] readListPrecDefault readList :: ReadS [[a]] readList =ReadS [[a]] forall a. Read a => ReadS [a] readListDefault -- | @since 2.01instance(Ix a ,Read a ,Read b )=>Read (Array a b )wherereadPrec :: 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 $ doLexeme -> ReadPrec () expectP (String -> Lexeme L.Ident "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 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 readPrec Array a b -> ReadPrec (Array a b) forall (m :: * -> *) a. Monad m => a -> m a return ((a, a) -> [(a, b)] -> Array a b forall i e. Ix i => (i, i) -> [(i, e)] -> Array i e array (a, a) theBounds [(a, b)] vals )readListPrec :: ReadPrec [Array a b] readListPrec =ReadPrec [Array a b] forall a. Read a => ReadPrec [a] readListPrecDefault readList :: ReadS [Array a b] readList =ReadS [Array a b] forall a. Read a => ReadS [a] readListDefault -- | @since 2.01instanceRead L.Lexeme wherereadPrec :: ReadPrec Lexeme readPrec =ReadPrec Lexeme lexP readListPrec :: ReadPrec [Lexeme] readListPrec =ReadPrec [Lexeme] forall a. Read a => ReadPrec [a] readListPrecDefault readList :: ReadS [Lexeme] readList =ReadS [Lexeme] forall a. Read a => ReadS [a] readListDefault ---------------------------------------------------------------- Numeric instances of Read--------------------------------------------------------------readNumber ::Num a =>(L.Lexeme ->ReadPrec a )->ReadPrec a -- Read a signed numberreadNumber :: (Lexeme -> ReadPrec a) -> ReadPrec a readNumber convert :: Lexeme -> ReadPrec a convert =ReadPrec a -> ReadPrec a forall a. ReadPrec a -> ReadPrec a parens (doLexeme x <-ReadPrec Lexeme lexP caseLexeme x ofL.Symbol "-"->doLexeme y <-ReadPrec Lexeme lexP a n <-Lexeme -> ReadPrec a convert Lexeme y a -> ReadPrec a forall (m :: * -> *) a. Monad m => a -> m a return (a -> a forall a. Num a => a -> a negate a n )_->Lexeme -> ReadPrec a convert Lexeme x )convertInt ::Num a =>L.Lexeme ->ReadPrec a convertInt :: Lexeme -> ReadPrec a convertInt (L.Number n :: Number n )|Just i :: Integer i <-Number -> Maybe Integer L.numberToInteger Number n =a -> ReadPrec a forall (m :: * -> *) a. Monad m => a -> m a return (Integer -> a forall a. Num a => Integer -> a fromInteger Integer i )convertInt _=ReadPrec a forall a. ReadPrec a pfail convertFrac ::foralla .RealFloat a =>L.Lexeme ->ReadPrec a convertFrac :: Lexeme -> ReadPrec a convertFrac (L.Ident "NaN")=a -> ReadPrec a forall (m :: * -> *) a. Monad m => a -> m a return (0a -> a -> a forall a. Fractional a => a -> a -> a / 0)convertFrac (L.Ident "Infinity")=a -> ReadPrec a forall (m :: * -> *) a. Monad m => a -> m a return (1a -> a -> a forall a. Fractional a => a -> a -> a / 0)convertFrac (L.Number n :: Number n )=letresRange :: (Int, Int) resRange =a -> (Int, Int) forall a. RealFloat a => a -> (Int, Int) floatRange (a forall a. HasCallStack => a undefined ::a )incase(Int, Int) -> Number -> Maybe Rational L.numberToRangedRational (Int, Int) resRange Number n ofNothing ->a -> ReadPrec a forall (m :: * -> *) a. Monad m => a -> m a return (1a -> a -> a forall a. Fractional a => a -> a -> a / 0)Just rat :: Rational rat ->a -> ReadPrec a forall (m :: * -> *) a. Monad m => a -> m a return (a -> ReadPrec a) -> a -> ReadPrec a forall a b. (a -> b) -> a -> b $ Rational -> a forall a. Fractional a => Rational -> a fromRational Rational rat convertFrac _=ReadPrec a forall a. ReadPrec a pfail -- | @since 2.01instanceRead IntwherereadPrec :: ReadPrec Int readPrec =(Lexeme -> ReadPrec Int) -> ReadPrec Int forall a. Num a => (Lexeme -> ReadPrec a) -> ReadPrec a readNumber Lexeme -> ReadPrec Int forall a. Num a => Lexeme -> ReadPrec a convertInt readListPrec :: ReadPrec [Int] readListPrec =ReadPrec [Int] forall a. Read a => ReadPrec [a] readListPrecDefault readList :: ReadS [Int] readList =ReadS [Int] forall a. Read a => ReadS [a] readListDefault -- | @since 4.5.0.0instanceRead WordwherereadsPrec :: Int -> ReadS Word readsPrec p :: Int p s :: String s =[(Integer -> Word forall a. Num a => Integer -> a fromInteger Integer x ,String r )|(x :: Integer x ,r :: String r )<-Int -> ReadS Integer forall a. Read a => Int -> ReadS a readsPrec Int p String s ]-- | @since 2.01instanceRead Word8 wherereadsPrec :: Int -> ReadS Word8 readsPrec p :: Int p s :: String s =[(Int -> Word8 forall a b. (Integral a, Num b) => a -> b fromIntegral (Int x ::Int),String r )|(x :: Int x ,r :: String r )<-Int -> ReadS Int forall a. Read a => Int -> ReadS a readsPrec Int p String s ]-- | @since 2.01instanceRead Word16 wherereadsPrec :: Int -> ReadS Word16 readsPrec p :: Int p s :: String s =[(Int -> Word16 forall a b. (Integral a, Num b) => a -> b fromIntegral (Int x ::Int),String r )|(x :: Int x ,r :: String r )<-Int -> ReadS Int forall a. Read a => Int -> ReadS a readsPrec Int p String s ]-- | @since 2.01instanceRead Word32 where #if WORD_SIZE_IN_BITS < 33 readsPrecps=[(fromIntegerx,r)|(x,r)<-readsPrecps] #else readsPrec :: Int -> ReadS Word32 readsPrec p :: Int p s :: String s =[(Int -> Word32 forall a b. (Integral a, Num b) => a -> b fromIntegral (Int x ::Int),String r )|(x :: Int x ,r :: String r )<-Int -> ReadS Int forall a. Read a => Int -> ReadS a readsPrec Int p String s ] #endif -- | @since 2.01instanceRead Word64 wherereadsPrec :: Int -> ReadS Word64 readsPrec p :: Int p s :: String s =[(Integer -> Word64 forall a. Num a => Integer -> a fromInteger Integer x ,String r )|(x :: Integer x ,r :: String r )<-Int -> ReadS Integer forall a. Read a => Int -> ReadS a readsPrec Int p String s ]-- | @since 2.01instanceRead IntegerwherereadPrec :: ReadPrec Integer readPrec =(Lexeme -> ReadPrec Integer) -> ReadPrec Integer forall a. Num a => (Lexeme -> ReadPrec a) -> ReadPrec a readNumber Lexeme -> ReadPrec Integer forall a. Num a => Lexeme -> ReadPrec a convertInt readListPrec :: ReadPrec [Integer] readListPrec =ReadPrec [Integer] forall a. Read a => ReadPrec [a] readListPrecDefault readList :: ReadS [Integer] readList =ReadS [Integer] forall a. Read a => ReadS [a] readListDefault -- | @since 4.8.0.0instanceRead Natural wherereadsPrec :: Int -> ReadS Natural readsPrec d :: Int d =((Integer, String) -> (Natural, String)) -> [(Integer, String)] -> [(Natural, String)] forall a b. (a -> b) -> [a] -> [b] map (\(n :: Integer n ,s :: String s )->(Integer -> Natural forall a. Num a => Integer -> a 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 >=0)(Integer -> Bool) -> ((Integer, String) -> Integer) -> (Integer, String) -> Bool forall b c a. (b -> c) -> (a -> b) -> a -> c . (\(x :: Integer x ,_)->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 readsPrec Int d -- | @since 2.01instanceRead FloatwherereadPrec :: ReadPrec Float readPrec =(Lexeme -> ReadPrec Float) -> ReadPrec Float forall a. Num a => (Lexeme -> ReadPrec a) -> ReadPrec a readNumber Lexeme -> ReadPrec Float forall a. RealFloat a => Lexeme -> ReadPrec a convertFrac readListPrec :: ReadPrec [Float] readListPrec =ReadPrec [Float] forall a. Read a => ReadPrec [a] readListPrecDefault readList :: ReadS [Float] readList =ReadS [Float] forall a. Read a => ReadS [a] readListDefault -- | @since 2.01instanceRead DoublewherereadPrec :: ReadPrec Double readPrec =(Lexeme -> ReadPrec Double) -> ReadPrec Double forall a. Num a => (Lexeme -> ReadPrec a) -> ReadPrec a readNumber Lexeme -> ReadPrec Double forall a. RealFloat a => Lexeme -> ReadPrec a convertFrac readListPrec :: ReadPrec [Double] readListPrec =ReadPrec [Double] forall a. Read a => ReadPrec [a] readListPrecDefault readList :: ReadS [Double] readList =ReadS [Double] forall a. Read a => ReadS [a] readListDefault -- | @since 2.01instance(Integral a ,Read a )=>Read (Ratio a )wherereadPrec :: 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 (doa x <-ReadPrec a -> ReadPrec a forall a. ReadPrec a -> ReadPrec a step ReadPrec a forall a. Read a => ReadPrec a readPrec Lexeme -> ReadPrec () expectP (String -> Lexeme L.Symbol "%")a y <-ReadPrec a -> ReadPrec a forall a. ReadPrec a -> ReadPrec a step ReadPrec a forall a. Read a => ReadPrec a readPrec Ratio a -> ReadPrec (Ratio a) forall (m :: * -> *) a. Monad m => a -> m a return (a x a -> a -> Ratio a forall a. Integral a => a -> a -> Ratio a % a y )))readListPrec :: ReadPrec [Ratio a] readListPrec =ReadPrec [Ratio a] forall a. Read a => ReadPrec [a] readListPrecDefault readList :: ReadS [Ratio a] readList =ReadS [Ratio a] forall a. Read a => ReadS [a] readListDefault -------------------------------------------------------------------------- Tuple instances of Read, up to size 15-------------------------------------------------------------------------- | @since 2.01instanceRead ()wherereadPrec :: 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 return ()))readListPrec :: ReadPrec [()] readListPrec =ReadPrec [()] forall a. Read a => ReadPrec [a] readListPrecDefault readList :: ReadS [()] readList =ReadS [()] forall a. Read a => ReadS [a] readListDefault -- | @since 2.01instance(Read a ,Read b )=>Read (a ,b )wherereadPrec :: 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) read_tup2 readListPrec :: ReadPrec [(a, b)] readListPrec =ReadPrec [(a, b)] forall a. Read a => ReadPrec [a] readListPrecDefault readList :: ReadS [(a, b)] readList =ReadS [(a, b)] forall a. Read a => ReadS [a] readListDefault wrap_tup ::ReadPrec a ->ReadPrec a wrap_tup :: ReadPrec a -> ReadPrec a wrap_tup p :: 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 ",")read_tup2 ::(Read a ,Read b )=>ReadPrec (a ,b )-- Reads "a , b" no parens!read_tup2 :: ReadPrec (a, b) read_tup2 =doa x <-ReadPrec a forall a. Read a => ReadPrec a readPrec ReadPrec () read_comma b y <-ReadPrec b forall a. Read a => ReadPrec a readPrec (a, b) -> ReadPrec (a, b) forall (m :: * -> *) a. Monad m => a -> m a 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 a ,b :: b b )<-ReadPrec (a, b) forall a b. (Read a, Read b) => ReadPrec (a, b) read_tup2 ReadPrec () read_comma (c :: c c ,d :: d d )<-ReadPrec (c, d) forall a b. (Read a, Read b) => ReadPrec (a, b) read_tup2 (a, b, c, d) -> ReadPrec (a, b, c, d) forall (m :: * -> *) a. Monad m => a -> m a 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 a ,b :: b b ,c :: c c ,d :: 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) read_tup4 ReadPrec () read_comma (e :: e e ,f :: f f ,g :: g g ,h :: 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) 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 return (a a ,b b ,c c ,d d ,e e ,f f ,g g ,h h )-- | @since 2.01instance(Read a ,Read b ,Read c )=>Read (a ,b ,c )wherereadPrec :: ReadPrec (a, b, c) readPrec =ReadPrec (a, b, c) -> ReadPrec (a, b, c) forall a. ReadPrec a -> ReadPrec a wrap_tup (do{(a :: a a ,b :: b b )<-ReadPrec (a, b) forall a b. (Read a, Read b) => ReadPrec (a, b) read_tup2 ;ReadPrec () read_comma ;c c <-ReadPrec c forall a. Read a => ReadPrec a readPrec ;(a, b, c) -> ReadPrec (a, b, c) forall (m :: * -> *) a. Monad m => a -> m a return (a a ,b b ,c c )})readListPrec :: ReadPrec [(a, b, c)] readListPrec =ReadPrec [(a, b, c)] forall a. Read a => ReadPrec [a] readListPrecDefault readList :: ReadS [(a, b, c)] readList =ReadS [(a, b, c)] forall a. Read a => ReadS [a] readListDefault -- | @since 2.01instance(Read a ,Read b ,Read c ,Read d )=>Read (a ,b ,c ,d )wherereadPrec :: 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) read_tup4 readListPrec :: ReadPrec [(a, b, c, d)] readListPrec =ReadPrec [(a, b, c, d)] forall a. Read a => ReadPrec [a] readListPrecDefault readList :: ReadS [(a, b, c, d)] readList =ReadS [(a, b, c, d)] forall a. Read a => ReadS [a] readListDefault -- | @since 2.01instance(Read a ,Read b ,Read c ,Read d ,Read e )=>Read (a ,b ,c ,d ,e )wherereadPrec :: 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 a ,b :: b b ,c :: c c ,d :: 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) read_tup4 ;ReadPrec () read_comma ;e e <-ReadPrec e forall a. Read a => ReadPrec a readPrec ;(a, b, c, d, e) -> ReadPrec (a, b, c, d, e) forall (m :: * -> *) a. Monad m => a -> m a 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] readListPrecDefault readList :: ReadS [(a, b, c, d, e)] readList =ReadS [(a, b, c, d, e)] forall a. Read a => ReadS [a] readListDefault -- | @since 2.01instance(Read a ,Read b ,Read c ,Read d ,Read e ,Read f )=>Read (a ,b ,c ,d ,e ,f )wherereadPrec :: 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 a ,b :: b b ,c :: c c ,d :: 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) read_tup4 ;ReadPrec () read_comma ;(e :: e e ,f :: f f )<-ReadPrec (e, f) forall a b. (Read a, Read b) => ReadPrec (a, b) read_tup2 ;(a, b, c, d, e, f) -> ReadPrec (a, b, c, d, e, f) forall (m :: * -> *) a. Monad m => a -> m a 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] readListPrecDefault readList :: ReadS [(a, b, c, d, e, f)] readList =ReadS [(a, b, c, d, e, f)] forall a. Read a => ReadS [a] readListDefault -- | @since 2.01instance(Read a ,Read b ,Read c ,Read d ,Read e ,Read f ,Read g )=>Read (a ,b ,c ,d ,e ,f ,g )wherereadPrec :: 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 a ,b :: b b ,c :: c c ,d :: 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) read_tup4 ;ReadPrec () read_comma ;(e :: e e ,f :: f f )<-ReadPrec (e, f) forall a b. (Read a, Read b) => ReadPrec (a, b) read_tup2 ;ReadPrec () read_comma ;g g <-ReadPrec g forall a. Read a => ReadPrec a readPrec ;(a, b, c, d, e, f, g) -> ReadPrec (a, b, c, d, e, f, g) forall (m :: * -> *) a. Monad m => a -> m a 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] 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] readListDefault -- | @since 2.01instance(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 )wherereadPrec :: 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) 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] 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] readListDefault -- | @since 2.01instance(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 )wherereadPrec :: 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 a ,b :: b b ,c :: c c ,d :: d d ,e :: e e ,f :: f f ,g :: g g ,h :: 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) read_tup8 ;ReadPrec () read_comma ;i i <-ReadPrec i forall a. Read a => ReadPrec a 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 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] 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] readListDefault -- | @since 2.01instance(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 )wherereadPrec :: 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 a ,b :: b b ,c :: c c ,d :: d d ,e :: e e ,f :: f f ,g :: g g ,h :: 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) read_tup8 ;ReadPrec () read_comma ;(i :: i i ,j :: j j )<-ReadPrec (i, j) forall a b. (Read a, Read b) => ReadPrec (a, b) 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 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] 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] readListDefault -- | @since 2.01instance(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 )wherereadPrec :: 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 a ,b :: b b ,c :: c c ,d :: d d ,e :: e e ,f :: f f ,g :: g g ,h :: 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) read_tup8 ;ReadPrec () read_comma ;(i :: i i ,j :: j j )<-ReadPrec (i, j) forall a b. (Read a, Read b) => ReadPrec (a, b) read_tup2 ;ReadPrec () read_comma ;k k <-ReadPrec k forall a. Read a => ReadPrec a 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 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] 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] readListDefault -- | @since 2.01instance(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 )wherereadPrec :: 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 a ,b :: b b ,c :: c c ,d :: d d ,e :: e e ,f :: f f ,g :: g g ,h :: 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) read_tup8 ;ReadPrec () read_comma ;(i :: i i ,j :: j j ,k :: k k ,l :: 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) 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 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] 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] readListDefault -- | @since 2.01instance(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 )wherereadPrec :: 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 a ,b :: b b ,c :: c c ,d :: d d ,e :: e e ,f :: f f ,g :: g g ,h :: 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) read_tup8 ;ReadPrec () read_comma ;(i :: i i ,j :: j j ,k :: k k ,l :: 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) read_tup4 ;ReadPrec () read_comma ;m m <-ReadPrec m forall a. Read a => ReadPrec a 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 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] 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] readListDefault -- | @since 2.01instance(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 )wherereadPrec :: 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 a ,b :: b b ,c :: c c ,d :: d d ,e :: e e ,f :: f f ,g :: g g ,h :: 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) read_tup8 ;ReadPrec () read_comma ;(i :: i i ,j :: j j ,k :: k k ,l :: 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) read_tup4 ;ReadPrec () read_comma ;(m :: m m ,n :: n n )<-ReadPrec (m, n) forall a b. (Read a, Read b) => ReadPrec (a, b) 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 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] 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] readListDefault -- | @since 2.01instance(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 )wherereadPrec :: 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 a ,b :: b b ,c :: c c ,d :: d d ,e :: e e ,f :: f f ,g :: g g ,h :: 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) read_tup8 ;ReadPrec () read_comma ;(i :: i i ,j :: j j ,k :: k k ,l :: 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) read_tup4 ;ReadPrec () read_comma ;(m :: m m ,n :: n n )<-ReadPrec (m, n) forall a b. (Read a, Read b) => ReadPrec (a, b) read_tup2 ;ReadPrec () read_comma ;o o <-ReadPrec o forall a. Read a => ReadPrec a 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 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] 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] readListDefault