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

Portabilitynon-portable
Stabilityexperimental
Maintainerekmett@gmail.com
Safe HaskellNone

Text.Trifecta.Parser

Contents

Description

 

Synopsis

Documentation

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 Doc 
StepCont !Rope (Result a) (Rope -> Step a) 

Instances

Functor Step 
Show a => Show (Step a) 

feed :: Reducer t Rope => t -> Step r -> Step rSource

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 aSource

parseByteString p delta i runs a parser p on i.

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