trifecta-2.1: A modern parser combinator library with convenient diagnostics

Copyright(c) Edward Kmett 2011-2019
LicenseBSD3
Maintainerekmett@gmail.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Text.Trifecta.Parser

Contents

Description

 
Synopsis

Documentation

newtype Parser a Source #

The type of a trifecta parser

The first four arguments are behavior continuations:

  • epsilon success: the parser has consumed no input and has a result as well as a possible Err; the position and chunk are unchanged (see pure)
  • epsilon failure: the parser has consumed no input and is failing with the given Err; the position and chunk are unchanged (see empty)
  • committed success: the parser has consumed input and is yielding the result, set of expected strings that would have permitted this parse to continue, new position, and residual chunk to the continuation.
  • committed failure: the parser has consumed input and is failing with a given ErrInfo (user-facing error message)

The remaining two arguments are

  • the current position
  • the chunk of input currently under analysis

Parser is an Alternative; trifecta's backtracking behavior encoded as <|> is to behave as the leftmost parser which yields a value (regardless of any input being consumed) or which consumes input and fails. That is, a choice of parsers will only yield an epsilon failure if *all* parsers in the choice do. If that is not the desired behavior, see try, which turns a committed parser failure into an epsilon failure (at the cost of error information).

Constructors

Parser 

Fields

Instances
Monad Parser Source # 
Instance details

Defined in Text.Trifecta.Parser

Methods

(>>=) :: Parser a -> (a -> Parser b) -> Parser b #

(>>) :: Parser a -> Parser b -> Parser b #

return :: a -> Parser a #

fail :: String -> Parser a #

Functor Parser Source # 
Instance details

Defined in Text.Trifecta.Parser

Methods

fmap :: (a -> b) -> Parser a -> Parser b #

(<$) :: a -> Parser b -> Parser a #

MonadFail Parser Source # 
Instance details

Defined in Text.Trifecta.Parser

Methods

fail :: String -> Parser a #

Applicative Parser Source # 
Instance details

Defined in Text.Trifecta.Parser

Methods

pure :: a -> Parser a #

(<*>) :: Parser (a -> b) -> Parser a -> Parser b #

liftA2 :: (a -> b -> c) -> Parser a -> Parser b -> Parser c #

(*>) :: Parser a -> Parser b -> Parser b #

(<*) :: Parser a -> Parser b -> Parser a #

Alternative Parser Source # 
Instance details

Defined in Text.Trifecta.Parser

Methods

empty :: Parser a #

(<|>) :: Parser a -> Parser a -> Parser a #

some :: Parser a -> Parser [a] #

many :: Parser a -> Parser [a] #

MonadPlus Parser Source # 
Instance details

Defined in Text.Trifecta.Parser

Methods

mzero :: Parser a #

mplus :: Parser a -> Parser a -> Parser a #

TokenParsing Parser Source # 
Instance details

Defined in Text.Trifecta.Parser

LookAheadParsing Parser Source # 
Instance details

Defined in Text.Trifecta.Parser

Methods

lookAhead :: Parser a -> Parser a #

CharParsing Parser Source # 
Instance details

Defined in Text.Trifecta.Parser

Parsing Parser Source # 
Instance details

Defined in Text.Trifecta.Parser

Methods

try :: Parser a -> Parser a #

(<?>) :: Parser a -> String -> Parser a #

skipMany :: Parser a -> Parser () #

skipSome :: Parser a -> Parser () #

unexpected :: String -> Parser a #

eof :: Parser () #

notFollowedBy :: Show a => Parser a -> Parser () #

Errable Parser Source # 
Instance details

Defined in Text.Trifecta.Parser

Methods

raiseErr :: Err -> Parser a Source #

DeltaParsing Parser Source # 
Instance details

Defined in Text.Trifecta.Parser

MarkParsing Delta Parser Source # 
Instance details

Defined in Text.Trifecta.Parser

Semigroup a => Semigroup (Parser a) Source # 
Instance details

Defined in Text.Trifecta.Parser

Methods

(<>) :: Parser a -> Parser a -> Parser a #

sconcat :: NonEmpty (Parser a) -> Parser a #

stimes :: Integral b => b -> Parser a -> Parser a #

(Semigroup a, Monoid a) => Monoid (Parser a) Source # 
Instance details

Defined in Text.Trifecta.Parser

Methods

mempty :: Parser a #

mappend :: Parser a -> Parser a -> Parser a #

mconcat :: [Parser a] -> Parser a #

manyAccum :: (a -> [a] -> [a]) -> Parser a -> Parser [a] Source #

Feeding a parser more more input

data Step a Source #

A Step allows for incremental parsing, since the parser

  • can be done with a final result
  • have errored
  • can have yielded a partial result with possibly more to come

Constructors

StepDone !Rope a

Parsing is done and has converted the Rope to a final result

StepFail !Rope ErrInfo

Parsing the Rope has failed with an error

StepCont !Rope (Result a) (Rope -> Step a)

The Rope has been partially consumed and already yielded a Result, and if more input is provided, more results can be produced.

One common scenario for this is to parse log files: after parsing a single line, that data can already be worked with, but there may be more lines to come.

Instances
Functor Step Source # 
Instance details

Defined in Text.Trifecta.Parser

Methods

fmap :: (a -> b) -> Step a -> Step b #

(<$) :: a -> Step b -> Step a #

Show a => Show (Step a) Source # 
Instance details

Defined in Text.Trifecta.Parser

Methods

showsPrec :: Int -> Step a -> ShowS #

show :: Step a -> String #

showList :: [Step a] -> ShowS #

feed :: Reducer t Rope => t -> Step r -> Step r Source #

Feed some additional input to a Step to continue parsing a bit further.

starve :: Step a -> Result a Source #

Assume all possible input has been given to the parser, execute it to yield a final result.

stepParser Source #

Arguments

:: Parser a 
-> Delta

Starting cursor position. Usually mempty for the beginning of the file.

-> Step a 

Incremental parsing. A Step can be supplied with new input using feed, the final Result is obtained using starve.

Parsing

runParser Source #

Arguments

:: Reducer t Rope 
=> Parser a 
-> Delta

Starting cursor position. Usually mempty for the beginning of the file.

-> t 
-> Result a 

Run a Parser on input that can be reduced to a Rope, e.g. String, or ByteString. See also the monomorphic versions parseString and parseByteString.

parseFromFile :: MonadIO m => Parser a -> String -> m (Maybe a) Source #

(parseFromFile p filePath) runs a parser p on the input read from filePath using readFile. All diagnostic messages emitted over the course of the parse attempt are shown to the user on the console.

main = do
  result <- parseFromFile numbers "digits.txt"
  case result of
    Nothing -> return ()
    Just a  -> print $ sum a

parseFromFileEx :: MonadIO m => Parser a -> String -> m (Result a) Source #

(parseFromFileEx p filePath) runs a parser p on the input read from filePath using readFile. Returns all diagnostic messages emitted over the course of the parse and the answer if the parse was successful.

main = do
  result <- parseFromFileEx (many number) "digits.txt"
  case result of
    Failure xs -> displayLn xs
    Success a  -> print (sum a)

parseString Source #

Arguments

:: Parser a 
-> Delta

Starting cursor position. Usually mempty for the beginning of the file.

-> String 
-> Result a 

Fully parse a String to a Result.

parseByteString p delta i runs a parser p on i.

parseByteString Source #

Arguments

:: Parser a 
-> Delta

Starting cursor position. Usually mempty for the beginning of the file.

-> ByteString 
-> Result a 

Fully parse a ByteString to a Result.

parseByteString p delta i runs a parser p on i.

parseTest :: (MonadIO m, Show a) => Parser a -> String -> m () Source #