-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Fast, online, error-correcting, monadic, applicative, merging, permuting, idiomatic parser combinators. -- -- New version of the Utrecht University parser combinator library, which -- provides online, error correction, annotation free, applicative style -- parser combinators. In addition to this we do provide a monadic and -- idomatic interface. Parsers do analyse themselves to avoid commonly -- made errors. A recent addition was the combinator -- <||> and associates, which generalise merging -- and permuting parsers. -- -- This version is based on the module Data.Listlike, and as a -- result a great variety of input structures (Strings, -- ByteStrings, etc.) can be handled. -- -- The modules Text.ParserCombinators.UU.Demo.Examples, -- Text.ParserCombinators.UU.Idioms and -- Text.ParserCombinators.UU.Demo.MergeAndpermute contain a -- ready-made show_examples function, which can be called (e.g. -- from ghci) to see e.g. the error correction at work. It -- contains extensive haddock documentation, so why not just take a look -- to see the correction process at work, and to get a feeling for how -- the various combinators can be used? -- -- The file Text.ParserCombinators.UU.CHANGELOG contains a log of -- the most recent changes and additions. -- -- The file Text.ParserCombinators.UU.README contains some -- references to background information. -- -- We maintain a low frequency mailing for discussing the package. You -- can subscribe at: -- https://mail.cs.uu.nl/mailman/listinfo/parsing @package uu-parsinglib @version 2.7.3.1 -- | This module contains some background information about a completely -- new version of the Utrecht parser combinator library. -- -- Background material -- -- The library is based on ideas described in the paper: -- -- @inproceedings{uuparsing:piriapolis, Author = {Swierstra, S.~Doaitse}, -- Booktitle = {Language Engineering and Rigorous Software Development}, -- Editor = {Bove, A. and Barbosa, L. and Pardo, A. and and Sousa Pinto, -- J.}, Pages = {252-300}, Place = {Piriapolis}, Publisher = {Spinger}, -- Series = {LNCS}, Title = {Combinator Parsers: a short tutorial}, -- Volume = {5520}, Year = {2009}} -- -- which is also available as a technical report from -- http://www.cs.uu.nl/research/techreps/repo/CS-2008/2008-044.pdf -- -- The first part of this report is a general introduction to parser -- combinators, whereas the second part contains the motivation for and -- documentation of the current package. -- -- We appreciate if you include a reference to the above documentation in -- any publication describing software in which you have used the library -- succesfully. -- -- Any feedback on particular use of the library, and suggestions for -- extensions, are welcome at mailto:doaitse@swierstra.net module Text.ParserCombinators.UU.README -- | This module just contains the CHANGELOG -- -- Version 2.7.3.1 -- -- fixed corner case when combining to failing parsers during grammar -- analysis; probably useful error message is now gone -- -- Version 2.7.3 -- -- better behaviour when inserting at end of input -- -- Version 2.7.2.2 -- -- fixed the case where the left hand operand of <|| starts -- with a monadic bind -- -- Version 2.7.2.1 -- -- removed a left-over from debugging -- -- Version 2.7.2 -- -- fixed a subtle bug in the merging parsers caused by name shielding -- ;-{{ -- -- Version 2.7.1.1 -- -- added pDoubleStr to the export list of the Utils module -- -- Version 2.7.1 -- -- fixed a subtle black hole which prevented computation of lengths!! You -- should upgrade. -- -- Version 2.7.0.2 -- -- -- -- Version 2.7.0.1 -- -- -- -- Version 2.7.0 -- -- Improvement: change of error correction at end of amb -- combinator, so lookahead is better taken into account -- -- Relatively large change: -- -- -- -- Version 2.6.1 -- -- -- --
--   import Text.ParserCombinators.UU.BasicInstances.String
--   
-- -- in the file header and change -- --
--   listToStr inp (0,0)
--   
-- -- to -- --
--   createStr inp
--   
-- -- -- -- Version 2.5.6.1 -- -- -- -- Version 2.5.6 -- -- -- -- Version 2.5.5.2 -- -- -- -- Version 2.5.5.1 -- -- -- -- Version 2.5.5 -- -- -- -- Version 2.5.4.2 -- -- -- -- Version 2.5.4.1 -- -- -- --
--   run ( (,)  `pMerge` ( ((++) `pSem` (pMany pa <||> pMany pb)) <||> pOne pc))  "abcaaab"
--   
--   Result: (["a","a","a","a","b","b"],"c")
--   
-- -- -- --
--    run ((((,), pc) `pMergeSep` (pMany pa <||> pMany pb))) "acbcacbc"
--   
--   Result: (["a","a","a"],["b","b"])
--   Correcting steps: 
--      Inserted 'a' at position (0,8) expecting one of ['b', 'a']
--   
-- -- Version 2.5.4 -- -- -- -- Version 2.5.3 -- -- -- -- Version 2.5.2 -- -- -- -- Version 2.5.1.1 -- -- -- -- Version 2.5.1 -- -- -- -- Version 2.5.0 -- -- -- -- Version 2.4.5 -- -- -- -- Version 2.4.4 -- -- -- -- Version 2.4.3 -- -- -- -- Version 2.4.2 -- -- -- -- Version 2.4.1 -- -- -- -- Version 2.4.0 -- -- -- -- Version 2.3.4 -- -- -- -- Version 2.3.3 -- -- -- -- Version 2.3.2 -- -- -- -- Version 2.3.1 -- -- -- -- Versions above 2.2: -- -- -- -- Versions above 2.1: * based on Control.Applicative -- -- Note that the basic parser interface will probably not change much -- when we add more features, but the calling conventions of the outer -- parser and the class structure upon which the parametrisation is based -- may change slightly module Text.ParserCombinators.UU.CHANGELOG -- | The module Core contains the basic functionality of the -- parser library. It defines the types and implementations of the -- elementary parsers and recognisers involved. module Text.ParserCombinators.UU.Core -- | In the class IsParser we assemble the basic properties we -- expect parsers to have. The class itself does not have any methods. -- Most properties come directly from the standard -- Control.Applicative module. The class ExtAlternative -- contains some extra methods we expect our parsers to have. class (Alternative p, Applicative p, ExtAlternative p) => IsParser p class Alternative p => ExtAlternative p (<<|>) :: ExtAlternative p => p a -> p a -> p a () :: ExtAlternative p => p a -> String -> p a doNotInterpret :: ExtAlternative p => p a -> p a must_be_non_empty :: ExtAlternative p => String -> p a -> c -> c must_be_non_empties :: ExtAlternative p => String -> p a -> p b -> c -> c opt :: ExtAlternative p => p a -> a -> p a -- | The class Eof contains a function eof which is used to -- check whether we have reached the end of the input and -- deletAtEnd should discard any unconsumed input at the end of -- a successful parse. class Eof state eof :: Eof state => state -> Bool deleteAtEnd :: Eof state => state -> Maybe (Cost, state) -- | The input state may maintain a location which can be used in -- generating error messages. Since we do not want to fix our input to be -- just a String we provide an interface which can be used to -- advance this location by passing information about the part -- recognised. This function is typically called in the -- splitState functions. class Show loc => IsLocationUpdatedBy loc str advance :: IsLocationUpdatedBy loc str => loc -> str -> loc -- | The class StoresErrors is used by the function pErrors -- which retrieves the generated correction steps since the last time it -- was called. class StoresErrors state error | state -> error getErrors :: StoresErrors state error => state -> ([error], state) class HasPosition state pos | state -> pos getPos :: HasPosition state pos => state -> pos data P st a -- | The data type Steps is the core data type around which the -- parsers are constructed. It describes a tree structure of streams -- containing (in an interleaved way) both the online result of the -- parsing process, and progress information. Recognising an input token -- should correspond to a certain amount of Progress, -- which tells how much of the input state was consumed. The -- Progress is used to implement the breadth-first search -- process, in which alternatives are examined in a more-or-less -- synchronised way. The meaning of the various Step -- constructors is as follows: -- -- -- -- The last two alternatives play a role in recognising ambigous -- non-terminals. For a full description see the technical report -- referred to from Text.ParserCombinators.UU.README. data Steps a Step :: Progress -> Steps a -> Steps a Apply :: (b -> a) -> Steps b -> Steps a Fail :: Strings -> [Strings -> (Cost, Steps a)] -> Steps a Micro :: Int -> Steps a -> Steps a End_h :: ([a], [a] -> Steps r) -> Steps (a, r) -> Steps (a, r) End_f :: [Steps a] -> Steps a -> Steps a type Cost = Int type Progress = Int -- | The data type Nat is used to represent the minimal -- length of a parser. Care should be taken in order to not evaluate the -- right hand side of the binary function `nat-add` more than -- necesssary. data Nat Zero :: Nat -> Nat Succ :: Nat -> Nat Infinite :: Nat Unspecified :: Nat type Strings = [String] -- | micro inserts a Cost step into the sequence representing -- the progress the parser is making; for its use see -- `Text.ParserCombinators.UU.Demos.Examples` micro :: P state a -> Int -> P state a -- | For the precise functioning of the amb combinators see the -- paper cited in the Text.ParserCombinators.UU.README; it -- converts an ambiguous parser into a parser which returns a list of -- possible recognitions, amb :: P st a -> P st [a] -- | pErrors returns the error messages that were generated since -- its last call. pErrors :: StoresErrors st error => P st [error] -- | pPos returns the current input position. pPos :: HasPosition st pos => P st pos -- | The function pEnd should be called at the end of the parsing -- process. It deletes any unconsumed input, turning it into error -- messages. pEnd :: (StoresErrors st error, Eof st) => P st [error] -- | pSwitch takes the current state and modifies it to a -- different type of state to which its argument parser is applied. The -- second component of the result is a function which converts the -- remaining state of this parser back into a value of the original type. -- For the second argument to pSwitch (say split) we -- expect the following to hold: -- --
--   let (n,f) = split st in f n == st
--   
pSwitch :: (st1 -> (st2, st2 -> st1)) -> P st2 a -> P st1 a -- | The basic recognisers are written elsewhere (e.g. in our module -- Text.ParserCombinataors.UU.BasicInstances; they (i.e. the -- parameter splitState) are lifted to ourP descriptors -- by the function pSymExt which also takes the minimal number of -- tokens recognised by the parameter spliState and an -- Maybe value describing the possibly empty value. pSymExt :: (forall a. (token -> state -> Steps a) -> state -> Steps a) -> Nat -> Maybe token -> P state token -- | The function parse shows the prototypical way of -- running a parser on some specific input. By default we use the future -- parser, since this gives us access to partal result; future parsers -- are expected to run in less space. parse :: Eof t => P t a -> t -> a -- | The function parse_h behaves like -- parse but using the history parser. This parser does -- not give online results, but might run faster. parse_h :: Eof t => P t a -> t -> a -- | getZeroP retrieves the possibly empty part from a descriptor. getZeroP :: P t a -> Maybe a -- | getOneP retrieves the non-zero part from a descriptor. getOneP :: P a b -> Maybe (P a b) -- | eval removes the progress information from a sequence -- of steps, and constructs the value embedded in it. If you are really -- desparate to see how your parsers are making progress (e.g. when you -- have written an ambiguous parser, and you cannot find the cause of the -- exponential blow-up of your parsing process), you may switch on the -- trace in the function eval (you will need to edit the -- library source code). eval :: Steps a -> a instance Show Nat instance Monad (P st) instance IsParser (P st) instance ExtAlternative (P st) instance Alternative (P state) instance Applicative (P state) instance Functor (P state) instance Show (P st a) instance Alternative (T state) instance Applicative (T state) instance Functor (T st) instance MonadPlus (P st) -- | This module contains a large variety of combinators for list-like -- structures. the extension _ng indicates that that variant is -- the non-greedy variant. See the -- Text.ParserCombinators.UU.Demo.Examples module for some -- examples of their use. module Text.ParserCombinators.UU.Derived -- | pReturn is defined for upwards compatibility pReturn :: Applicative p => a -> p a -- | pFail is defined for upwards compatibility, and is the -- unit for | pFail :: Alternative p => p a -- | pMaybe greedily recognises its argument. If not -- Nothing is returned. pMaybe :: IsParser p => p a -> p (Maybe a) -- | pEither recognises either one of its arguments. pEither :: IsParser p => p a -> p b -> p (Either a b) -- | <$$> is the version of <$> which flips the -- function argument (<$$>) :: IsParser p => (a -> b -> c) -> p b -> p (a -> c) -- | <??> parses an optional postfix element and applies its -- result to its left hand result () :: IsParser p => p a -> p (a -> a) -> p a -- | pMany is equivalent to the many from -- Control.Applicative. We want however all our parsers to start -- with a lower case p. pMany :: IsParser p => p a -> p [a] -- | pSome is equivalent to the some from -- Control.Applicative. We want however all our parsers to start -- with a lower case p. pSome :: IsParser f => f a -> f [a] -- | pPacked surrounds its third parser with the first and -- the second one, returning only the middle result pPacked :: IsParser p => p b1 -> p b2 -> p a -> p a pFoldr :: IsParser p => (a -> a1 -> a1, a1) -> p a -> p a1 pFoldr_ng :: IsParser p => (a -> a1 -> a1, a1) -> p a -> p a1 pFoldr1 :: IsParser p => (v -> b -> b, b) -> p v -> p b pFoldr1_ng :: IsParser p => (v -> b -> b, b) -> p v -> p b list_alg :: (a -> [a] -> [a], [a1]) pList :: IsParser p => p a -> p [a] pList_ng :: IsParser p => p a -> p [a] pList1 :: IsParser p => p a -> p [a] pList1_ng :: IsParser p => p a -> p [a] pFoldrSep :: IsParser p => (v -> b -> b, b) -> p a -> p v -> p b pFoldrSep_ng :: IsParser p => (v -> b -> b, b) -> p a -> p v -> p b pFoldr1Sep :: IsParser p => (a -> b -> b, b) -> p a1 -> p a -> p b pFoldr1Sep_ng :: IsParser p => (a -> b -> b, b) -> p a1 -> p a -> p b pListSep :: IsParser p => p a1 -> p a -> p [a] pListSep_ng :: IsParser p => p a1 -> p a -> p [a] pList1Sep :: IsParser p => p a1 -> p a -> p [a] pList1Sep_ng :: IsParser p => p a1 -> p a -> p [a] pChainr :: IsParser p => p (c -> c -> c) -> p c -> p c pChainr_ng :: IsParser p => p (c -> c -> c) -> p c -> p c pChainl :: IsParser p => p (c -> c -> c) -> p c -> p c pChainl_ng :: IsParser p => p (c -> c -> c) -> p c -> p c -- | pExact recognises a specified number of elements pExact :: IsParser f => Int -> f a -> f [a] pBetween :: IsParser f => Int -> Int -> f a -> f [a] pAtLeast :: IsParser f => Int -> f a -> f [a] pAtMost :: IsParser f => Int -> f a -> f [a] -- | Count the number of times p has succeeded pCount :: (IsParser p, Num b) => p a -> p b -- | Build a parser for each element in the argument list and try them all. pAny :: IsParser p => (a -> p a1) -> [a] -> p a1 -- | This module contains the additional data types, instance definitions -- and functions to run parsers in an interleaved way. If all the -- interleaved parsers recognise a single connected piece of the input -- text this incorporates the permutation parsers. For some examples see -- the module Text.ParserCombinators.UU.Demo.MergeAndPermute. module Text.ParserCombinators.UU.MergeAndPermute -- | Since we want to get access to the individual parsers which recognise -- a consecutive piece of the input text we define a new data type, which -- lifts the underlying parsers to the grammatical level, so they can be -- transformed, manipulated, and run in a piecewise way. Gram is -- defined in such a way that we can always access the first parsers to -- be ran from such a structure. We require that all the Alts do -- not recognise the empty string. These should be covered by the -- Maybe in the Gram constructor. data Gram f a Gram :: [Alt f a] -> (Maybe a) -> Gram f a data Alt f a Seq :: (f b) -> (Gram f (b -> a)) -> Alt f a Bind :: (f b) -> (b -> Gram f a) -> Alt f a -- | The function mkGram splits a simple parser into the possibly -- empty part and the non-empty part. The non-empty part recognises a -- consecutive part of the input. Here we use the functions -- getOneP and getZeroP which are provided in the -- uu-parsinglib package, but they could easily be provided by other -- packages too. mkGram :: P t a -> Gram (P t) a -- | The function <||> is the merging equivalent of -- <*>. Instead of running its two arguments consecutively, -- the input is split into parts which serve as input for the left -- operand and parts which are served to the right operand. (<||>) :: Functor f => Gram f (b -> a) -> Gram f b -> Gram f a -- | The function <<||> is a special version of -- <||>, which only starts a new instance of its right -- operand when the left operand cannot proceed. This is used in the -- function pmMany, where we want to merge as many instances of -- its argument, but no more than that. (<<||>) :: Functor f => Gram f (b -> a) -> Gram f b -> Gram f a -- | mkParserM converts a Grammar back into a parser, which -- can subsequenly be run. mkParserM :: (Monad f, Applicative f, ExtAlternative f) => Gram f a -> f a -- | mkParserS is like mkParserM, with the additional feature -- that we allow separators between the components. Only useful in the -- permuting case. mkParserS :: (Monad f, Applicative f, ExtAlternative f) => f b -> Gram f a -> f a -- | Run a sufficient number of p's in a merged fashion, but no -- more than necessary!! pmMany :: Functor f => Gram f a -> Gram f [a] instance Functor f => IsParser (Gram f) instance Monad (Gram f) instance Functor f => ExtAlternative (Gram f) instance Functor f => Alternative (Gram f) instance Functor f => Applicative (Gram f) instance Functor f => Functor (Alt f) instance Functor f => Functor (Gram f) instance Show a => Show (Gram f a) -- | This module contains basic instances for the class interface described -- in the Text.ParserCombinators.UU.Core module. It demonstates -- how to construct and maintain a state during parsing. In the state we -- store error messages, positional information and the actual input that -- is being parsed. Unless you have very specific wishes the module can -- be used as such. Since we make use of the Data.ListLike -- interface a wide variety of input structures can be handled. module Text.ParserCombinators.UU.BasicInstances -- | The data type Error describes the various kinds of errors which -- can be generated by the instances in this module data Error pos -- | String was inserted at pos-ition, where we expected -- Strings Inserted :: String -> pos -> Strings -> Error pos -- | String was deleted at pos-ition, where we expected -- Strings Deleted :: String -> pos -> Strings -> Error pos -- | for future use Replaced :: String -> String -> pos -> Strings -> Error pos -- | the unconsumed part of the input was deleted DeletedAtEnd :: String -> Error pos -- | The data type Str holds the input data to be parsed, the -- current location, the error messages generated and whether it is ok to -- delete elements from the input. Since an insert/delete action is the -- same as a delete/insert action we try to avoid the first one. So: no -- deletes after an insert. data Str a s loc Str :: s -> [Error loc] -> loc -> !Bool -> Str a s loc -- | the unconsumed part of the input input :: Str a s loc -> s -- | the accumulated error messages msgs :: Str a s loc -> [Error loc] -- | the current input position pos :: Str a s loc -> loc -- | we want to avoid deletions after insertions deleteOk :: Str a s loc -> !Bool -- | the String describes what is being inserted, the a -- parameter the value which is to be inserted and the cost the -- prices to be paid. data Insertion a Insertion :: String -> a -> Cost -> Insertion a data LineCol LineCol :: !Int -> !Int -> LineCol data LineColPos LineColPos :: !Int -> !Int -> !Int -> LineColPos -- | A Parser is a parser that is prepared to accept -- Data.Listlike input; hence we can deal with String's, -- ByteString's, etc. type Parser a = (IsLocationUpdatedBy loc Char, ListLike state Char) => P (Str Char state loc) a -- | A ParserTrafo a b maps a Parser a onto -- a Parser b. type ParserTrafo a b = (IsLocationUpdatedBy loc Char, ListLike state Char) => P (Str Char state loc) a -> P (Str Char state loc) b -- | The input state may maintain a location which can be used in -- generating error messages. Since we do not want to fix our input to be -- just a String we provide an interface which can be used to -- advance this location by passing information about the part -- recognised. This function is typically called in the -- splitState functions. class Show loc => IsLocationUpdatedBy loc str -- | createStr initialises the input stream with the input data and -- the initial position. There are no error messages yet. createStr :: ListLike s a => loc -> s -> Str a s loc show_expecting :: Show pos => pos -> [String] -> String -- | pSatisfy describes and elementary parsing step. Its first -- parameter check whether the head element of the input can be -- recognised, and the second parameter how to proceed in case an element -- recognised by this parser is absent, and parsing may proceed by -- pretending such an element was present in the input anayway. pSatisfy :: (Show a, IsLocationUpdatedBy loc a, ListLike state a) => (a -> Bool) -> (Insertion a) -> P (Str a state loc) a -- | pRangeInsert recognises an element between a lower and an upper -- bound. Furthermore it can be specified what element is to be inserted -- in case such an element is not at the head of the input. pRangeInsert :: (Ord a, Show a, IsLocationUpdatedBy loc a, ListLike state a) => (a, a) -> Insertion a -> P (Str a state loc) a -- | pRange uses the information from the bounds to compute the -- Insertion information. pRange :: (Ord a, Show a, IsLocationUpdatedBy loc a, ListLike state a) => (a, a) -> P (Str a state loc) a -- | pSymInsert recognises a specific element. Furthermore it can be -- specified what element is to be inserted in case such an element is -- not at the head of the input. pSymInsert :: (Eq a, Show a, IsLocationUpdatedBy loc a, ListLike state a) => a -> Insertion a -> P (Str a state loc) a -- | pSym recognises a specific element. Furthermore it can be -- specified what element. Information about Insertion is derived -- from the parameter. is to be inserted in case such an element is not -- at the head of the input. pSym :: (Eq a, Show a, IsLocationUpdatedBy loc a, ListLike state a) => a -> P (Str a state loc) a pToken :: (Show a, Eq a, IsLocationUpdatedBy loc a, ListLike state a) => [a] -> P (Str a state loc) [a] -- | pTokenCost succeeds if its parameter is a prefix of the input. pTokenCost :: (Show a, Eq a, IsLocationUpdatedBy loc a, ListLike state a) => [a] -> Int -> P (Str a state loc) [a] -- | pMunch recognises the longest prefix of the input for which the -- passed predicate holds. The message parameer is used when tracing has -- been switched on. pMunch :: (Show a, IsLocationUpdatedBy loc a, ListLike state a) => (a -> Bool) -> P (Str a state loc) [a] instance Show LineCol instance Show LineColPos instance HasPosition (Str a s loc) loc instance StoresErrors (Str a s loc) (Error loc) instance (Show a, ListLike s a) => Eof (Str a s loc) instance IsLocationUpdatedBy loc a => IsLocationUpdatedBy loc [a] instance IsLocationUpdatedBy LineColPos Char instance IsLocationUpdatedBy LineCol Char instance IsLocationUpdatedBy Int Word8 instance IsLocationUpdatedBy Int Char instance Show pos => Show (Error pos) -- | This module provides some higher-level types and infrastructure to -- make it easier to use. module Text.ParserCombinators.UU.Utils pCR :: Parser Char pLF :: Parser Char pLower :: Parser Char pUpper :: Parser Char pLetter :: Parser Char pAscii :: Parser Char pDigit :: Parser Char pDigitAsNum :: Num a => Parser a pAnySym :: (IsLocationUpdatedBy loc Char, ListLike state Char) => String -> P (Str Char state loc) Char pSpaces :: Parser String -- | Lexeme Parsers skip trailing whitespace (this terminology comes from -- Parsec) lexeme :: ParserTrafo a a pDot, pRBrace, pLBrace, pRBracket, pLBracket, pRParen, pLParen, pDQuote, pComma :: Parser Char pSymbol :: (IsLocationUpdatedBy loc Char, ListLike state Char) => String -> P (Str Char state loc) String pNaturalRaw :: Num a => Parser a pIntegerRaw :: Num a => Parser a pDoubleRaw :: Read a => Parser a pDoubleStr :: Parser [Char] pNatural :: Num a => Parser a pInteger :: Num a => Parser a pDouble :: Parser Double pPercent :: Parser Double pEnumRaw :: (Enum a, Show a) => Parser a pEnum :: (Enum a, Show a) => Parser a pEnumStrs :: [String] -> Parser String pParens :: ParserTrafo a a pBraces :: ParserTrafo a a pBrackets :: ParserTrafo a a -- | eg [1,2,3] listParser :: ParserTrafo a [a] -- | eg (1,2,3) tupleParser :: ParserTrafo a [a] pTuple :: (IsLocationUpdatedBy loc Char, ListLike state Char) => [P (Str Char state loc) a] -> P (Str Char state loc) [a] pDay :: Parser Day pDayMonthYear :: (Num d, Num y) => Parser (d, Int, y) pParentheticalString :: Char -> Parser String pQuotedString :: Parser String -- | Converts a UU Parser into a read-style one. -- -- This is intended to facilitate migration from read-style parsers to -- UU-based ones. parserReadsPrec :: Parser a -> Int -> ReadS a -- | The lower-level interface. Returns all errors. execParser :: Parser a -> String -> (a, [Error LineColPos]) -- | The higher-level interface. (Calls error with a simplified -- error). Runs the parser; if the complete input is accepted without -- problems return the result else fail with reporting unconsumed tokens runParser :: String -> Parser a -> String -> a instance Enum Month instance Bounded Month instance Eq Month instance Show Month instance Ord Month -- | The non-exported modules in Text.ParserCombinators.UU.Demo -- contain a list of examples of how to use the main functionality of -- this library which demonstrates: -- -- module Text.ParserCombinators.UU -- | This module contains a lot of examples of the typical use of our -- parser combinator library. We strongly encourage you to take a look at -- the source code. At the end you find a main function -- which demonstrates the main characteristics. Only the -- run function is exported since it may come in handy -- elsewhere. module Text.ParserCombinators.UU.Demo.Examples type Parser a = P (Str Char String LineColPos) a -- | Running the function show_demos should give the following -- output: -- --
--   >>> run pa  "a"
--    Result: "a"
--   
-- --
--   >>> run pa  ""
--    Result: "a"
--    Correcting steps: 
--      Inserted  'a' at position LineColPos 0 0 0 expecting 'a'
--   
-- --
--   >>> run pa  "b"
--    Result: "a"
--    Correcting steps: 
--      Deleted   'b' at position LineColPos 0 0 0 expecting 'a'
--      Inserted  'a' at position LineColPos 0 1 1 expecting 'a'
--   
-- --
--   >>> run ((++) <$> pa <*> pa)  "bbab"
--    Result: "aa"
--    Correcting steps: 
--      Deleted   'b' at position LineColPos 0 0 0 expecting 'a'
--      Deleted   'b' at position LineColPos 0 1 1 expecting 'a'
--      Deleted   'b' at position LineColPos 0 3 3 expecting 'a'
--      Inserted  'a' at position LineColPos 0 4 4 expecting 'a'
--   
-- --
--   >>> run pa  "ba"
--    Result: "a"
--    Correcting steps: 
--      Deleted   'b' at position LineColPos 0 0 0 expecting 'a'
--   
-- --
--   >>> run pa  "aa"
--    Result: "a"
--    Correcting steps: 
--      The token 'a' was not consumed by the parsing process.
--   
-- --
--   >>> run (pCount pa :: Parser Int)  "aaa"
--    Result: 3
--   
-- --
--   >>> run (do  {l <- pCount pa; pExact l pb})  "aaacabbbbb"
--    Result: ["b","b","b","b"]
--    Correcting steps: 
--      Deleted   'c' at position LineColPos 0 3 3 expecting one of ['b', 'a']
--      The token 'b' was not consumed by the parsing process.
--   
-- --
--   >>> run (amb ( (++) <$> pa2 <*> pa3 <|> (++) <$> pa3 <*> pa2))  "aaaaa"
--    Result: ["aaaaa","aaaaa"]
--   
-- --
--   >>> run (pList pLower)  "doaitse"
--    Result: "doaitse"
--   
-- --
--   >>> run paz  "abc2ez"
--    Result: "abcez"
--    Correcting steps: 
--      Deleted   '2' at position LineColPos 0 3 3 expecting 'a'..'z'
--   
-- --
--   >>> run (max <$> pParens ((+1) <$> wfp) <*> wfp `opt` 0)  "((()))()(())"
--    Result: 3
--   
-- --
--   >>> run (pa <|> pb <?> justamessage)  "c"
--    Result: "b"
--    Correcting steps: 
--      Deleted   'c' at position LineColPos 0 0 0 expecting justamessage
--      Inserted  'b' at position LineColPos 0 1 1 expecting 'b'
--   
-- --
--   >>> run (amb (pEither  parseIntString  pIntList))  "(123;456;789)"
--    Result: [Left ["123","456","789"],Right [123,456,789]]
--   
show_demos :: IO () -- | The fuction run runs the parser and shows both the -- result, and the correcting steps which were taken during the parsing -- process. run :: Show t => Parser t -> String -> IO () -- | Our first two parsers are simple; one recognises a single a -- character and the other one a single b. Since we will use -- them later we convert the recognised character into String so -- they can be easily combined. pa :: Parser String pb :: Parser String pc :: Parser String (<++>) :: Parser String -> Parser String -> Parser String paz :: Parser String -- | The applicative style makes it very easy to merge recogition and -- computing a result. As an example we parse a sequence of nested well -- formed parentheses pairs and compute the maximum nesting depth with -- wfp: wfp :: Parser Int -- | It is very easy to recognise infix expressions with any number of -- priorities and operators: -- --
--   operators       = [[('+', (+)), ('-', (-))],  [('*' , (*))], [('^', (^))]]
--   same_prio  ops  = msum [ op <$ pSym c | (c, op) <- ops]
--   expr            = foldr pChainl ( pNatural <|> pParens expr) (map same_prio operators) -- 
--   
-- -- which we can call: -- --
--   run expr "15-3*5+2^5"
--   
-- --
--   Result: 32
--   
-- -- Note that also here correction takes place: -- --
--   run expr "2 + + 3 5"
--   
-- --
--   Result: 37
--   Correcting steps: 
--      Deleted  ' ' at position 1 expecting one of ['0'..'9', '^', '*', '-', '+']
--      Deleted  ' ' at position 3 expecting one of ['(', '0'..'9']
--      Inserted '0' at position 4 expecting '0'..'9'
--      Deleted  ' ' at position 5 expecting one of ['(', '0'..'9']
--      Deleted  ' ' at position 7 expecting one of ['0'..'9', '^', '*', '-', '+']
--   
expr :: Parser Int -- | A common case where ambiguity arises is when we e.g. want to recognise -- identifiers, but only those which are not keywords. The combinator -- micro inserts steps with a specfied cost in the result of the -- parser which can be used to disambiguate: -- --
--   
--   ident ::  Parser String
--   ident = ((:) <$> pSym ('a','z') <*> pMunch (\x -> 'a' <= x && x <= 'z') `micro` 2) <* spaces
--   idents = pList1 ident
--   pKey keyw = pToken keyw `micro` 1 <* spaces
--   spaces :: Parser String
--   spaces = pMunch (==' ')
--   takes_second_alt =   pList ident 
--                  \<|> (\ c t e -> ["IfThenElse"] ++  c   ++  t  ++  e) 
--                      \<$ pKey "if"   <*> pList_ng ident 
--                      \<* pKey "then" <*> pList_ng ident
--                      \<* pKey "else" <*> pList_ng ident  
--   
-- -- A keyword is followed by a small cost 1, which makes sure -- that identifiers which have a keyword as a prefix win over the -- keyword. Identifiers are however followed by a cost 2, with -- as result that in this case the keyword wins. Note that a limitation -- of this approach is that keywords are only recognised as such when -- expected! -- --
--   test13 = run takes_second_alt "if a then if else c"
--   test14 = run takes_second_alt "ifx a then if else c"
--   
-- -- with results for test13 and test14: -- --
--   Result: ["IfThenElse","a","if","c"]
--   Result: ["ifx","a","then","if", "else","c"]
--   
-- -- A mistake which is made quite often is to construct a parser which can -- recognise a sequence of elements using one of the derived combinators -- (say pList), but where the argument parser can -- recognise the empty string. The derived combinators check whether this -- is the case and terminate the parsing process with an error message: -- --
--   run (pList spaces) ""
--   Result: *** Exception: The combinator pList
--    requires that it's argument cannot recognise the empty string
--   
-- --
--   run (pMaybe spaces) " "
--   Result: *** Exception: The combinator pMaybe
--   requires that it's argument cannot recognise the empty string
--   
test16 :: IO () spaces :: Parser String pManyTill :: P st a -> P st b -> P st [a] string :: (IsLocationUpdatedBy loc Char, ListLike state Char) => String -> P (Str Char state loc) String pAnyToken :: (IsLocationUpdatedBy loc Char, ListLike state Char) => [String] -> P (Str Char state loc) String pIntList :: Parser [Int] parseIntString :: Parser [String] demo :: Show r => String -> String -> P (Str Char String LineColPos) r -> IO () module Text.ParserCombinators.UU.Idioms data IF IF :: IF data THEN THEN :: THEN data ELSE ELSE :: ELSE data FI FI :: FI data OR OR :: OR data String' String' :: String -> String' fromStr :: String' -> String -- | The Ii is to be pronounced as stop data Ii Ii :: Ii -- | The function iI is to be pronounced as start iI :: Idiomatic i (a -> a) g => g class Idiomatic st f g | g -> f st idiomatic :: Idiomatic st f g => P st f -> g -- | The idea of the Idiom concept is that sequential composition operators -- can be inferred from the type of the various operands -- --
--   >>> run (iI (+) '(' pNatural "plus"  pNatural ')' Ii) "(2 plus 3"
--     Result: 5
--      Correcting steps: 
--        Inserted  ')' at position LineColPos 0 4 4 expecting one of [')', Whitespace, '0'..'9']
--   
pNat :: Parser Int show_demos :: IO () instance Idiomatic st f g => Idiomatic st (a -> f) (IF -> Bool -> THEN -> P st a -> ELSE -> P st a -> FI -> g) instance (Idiomatic (Str Char state loc) f g, IsLocationUpdatedBy loc Char, ListLike state Char) => Idiomatic (Str Char state loc) f (Char -> g) instance (Idiomatic (Str Char state loc) f g, IsLocationUpdatedBy loc Char, ListLike state Char) => Idiomatic (Str Char state loc) f (String -> g) instance Idiomatic st f g => Idiomatic st ((a -> b) -> f) ((a -> b) -> g) instance Idiomatic st f g => Idiomatic st (a -> f) (P st a -> g) instance Idiomatic st x (Ii -> P st x) module Text.ParserCombinators.UU.Demo.MergeAndPermute type Grammar a = Gram (P (Str Char String LineColPos)) a -- | By running the function show_demos you will get a demonstration -- of the merging parsers. -- --
--   >>> run ((,,) <$> two pA <||> three pB <||> pBetween 2 4 pC )  "cababbcccc"
--    Result: ("aa",("b","b","b"),["c","c","c","c"])
--    Correcting steps: 
--      The token 'c' was not consumed by the parsing process.
--   
-- --
--   >>> run (amb (mkParserM ((,) <$> pmMany ((,) <$>  pA <*> pC) <||> pmMany pB)))    "aabbcaabbccc"
--    Result: [([("a","c"),("a","c"),("a","c"),("a","c")],["b","b","b","b"]),([("a","c"),("a","c"),("a","c"),("a","c")],["b","b","b","b"]),
--             ([("a","c"),("a","c"),("a","c"),("a","c")],["b","b","b","b"]),([("a","c"),("a","c"),("a","c"),("a","c")],["b","b","b","b"]),
--             ([("a","c"),("a","c"),("a","c"),("a","c")],["b","b","b","b"]),([("a","c"),("a","c"),("a","c"),("a","c")],["b","b","b","b"]),
--             ([("a","c"),("a","c"),("a","c"),("a","c")],["b","b","b","b"]),([("a","c"),("a","c"),("a","c"),("a","c")],["b","b","b","b"]),
--             ([("a","c"),("a","c"),("a","c"),("a","c")],["b","b","b","b"]),([("a","c"),("a","c"),("a","c"),("a","c")],["b","b","b","b"]),
--             ([("a","c"),("a","c"),("a","c"),("a","c")],["b","b","b","b"]),([("a","c"),("a","c"),("a","c"),("a","c")],["b","b","b","b"])]
--   
-- --
--   >>> run (pmMany(pABC))                                                            "a2a1b1b2c2a3b3c1c3"
--    Result: ["2a","1a","3a"]
--   
-- --
--   >>> run ((,)    <$> pBetween 2 3 pA <||> pBetween 1 2 pB)                         "abba"
--    Result: (["a","a"],["b","b"])
--   
-- --
--   >>> run ((,)    <$> pBetween 2 3 pA <||> pBetween 1 2 pB)                         "bba"
--    Result: (["a","a"],["b","b"])
--    Correcting steps: 
--      Inserted  'a' at position LineColPos 0 3 3 expecting 'a'
--   
-- --
--   >>> run (amb (mkParserM( ((,)    <$> pBetween 2 3 pA <||> pBetween 1 2 pA))))      "aaa"
--    Result: [(["a","a"],["a"]),(["a","a"],["a"]),(["a","a"],["a"])]
--   
-- -- The a at the right hand side can b any of the three -- a-s in the input: -- --
--   >>> run ((,)    <$> pAtLeast 3 pA <||> pAtMost 3 pB)                              "aabbbb"
--    Result: (["a","a","a"],["b","b","b"])
--    Correcting steps: 
--      Deleted   'b' at position LineColPos 0 5 5 expecting 'a'
--      Inserted  'a' at position LineColPos 0 6 6 expecting 'a'
--   
-- --
--   >>> run ((,)    <$> pSome pA <||> pMany pB)                                       "abba"
--    Result: (["a","a"],["b","b"])
--   
-- --
--   >>> run ((,)    <$> pSome pA <||> pMany pB)                                       "abba"
--    Result: (["a","a"],["b","b"])
--   
-- --
--   >>> run ((,)    <$> pSome pA <||> pMany pB)                                       ""
--    Result: (["a"],[])
--    Correcting steps: 
--      Inserted  'a' at position LineColPos 0 0 0 expecting one of ['a', 'b']
--   
-- --
--   >>> run ((,)    <$> pMany pB <||> pSome pC)                                       "bcbc"
--    Result: (["b","b"],["c","c"])
--   
-- --
--   >>> run ((,)    <$> pSome pB <||> pMany pC)                                       "bcbc"
--    Result: (["b","b"],["c","c"])
--   
-- --
--   >>> run ((,,,)   <$> pSome pA <||> pMany pB <||> pC <||> (pNat `opt` 5) )         "bcab45"
--    Result: (["a"],["b","b"],"c",45)
--   
-- --
--   >>> run ((,)    <$> pMany (pA <|> pB) <||> pSome  pNat)                           "1ab12aab14"
--    Result: (["a","b","a","a","b"],[1,12,14])
--   
-- --
--   >>> run ( (,)   <$> ((++) <$> pMany pA <||> pMany pB) <||> pC)                    "abcaaab"
--    Result: (["a","a","a","a","b","b"],"c")
--   
-- --
--   >>> run (pc `mkParserS` ((,) <$> pMany pA <||> pMany pB))                         "acbcacb"
--    Result: (["a","a"],["b","b"])
--   
show_demos :: IO () pA, pC, pB :: Grammar String pNat :: Grammar Int -- | two recognises two instance of p as part of the input sequence two :: Applicative f => f [a] -> f [a] -- | three recognises two instance of p as part of the input -- sequence and concatenates the results three :: Applicative f => f a -> f (a, a, a) -- | pABC minimcs a series of events (here an a, a -- b and a c), which belong to the same transaction. -- The transaction is identified by a digit: hence a full transaction is -- a string like "a5b5c5". The third element in the body of -- show_demos below shows how the different transactions can be -- recovered from a log-file which contains all events generated by a -- collection of concurrently running transactions. pABC :: Grammar Char pABC' :: Grammar String