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

Copyright(c) Edward Kmett 2011-2015
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 # 

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 # 

Methods

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

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

MonadFail Parser Source # 

Methods

fail :: String -> Parser a #

Applicative Parser Source # 

Methods

pure :: a -> Parser a #

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

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

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

Alternative Parser Source # 

Methods

empty :: Parser a #

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

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

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

MonadPlus Parser Source # 

Methods

mzero :: Parser a #

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

TokenParsing Parser Source # 
CharParsing Parser Source # 
LookAheadParsing Parser Source # 

Methods

lookAhead :: Parser a -> Parser a #

Parsing Parser Source # 

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 # 

Methods

raiseErr :: Err -> Parser a Source #

DeltaParsing Parser Source # 
MarkParsing Delta Parser Source # 
Semigroup a => Semigroup (Parser a) Source # 

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 # 

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 #

Constructors

StepDone !Rope a 
StepFail !Rope ErrInfo 
StepCont !Rope (Result a) (Rope -> Step a) 

Instances

Functor Step Source # 

Methods

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

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

Show a => Show (Step a) Source # 

Methods

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

show :: Step a -> String #

showList :: [Step a] -> ShowS #

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

Parsing

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)

parseByteString :: Parser a -> Delta -> ByteString -> Result a Source #

parseByteString p delta i runs a parser p on i.

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