JustParse-1.0: A simple and comprehensive Haskell parsing library

Portabilityportable
Stabilityexperimental
Maintainergrantslatton@gmail.com
Safe HaskellSafe

Data.JustParse

Contents

Description

A simple and comprehensive Haskell parsing library.

Synopsis

Overview

  • Allows for parsing arbitrary Stream types
  • Makes extensive use of combinators
  • Returns relatively verbose Failure messages.
  • Allows one to rename a Parser.
  • Allows for a parser to return a Partial Result
  • Non-greedy parsing
  • Returns a list of all possible parses
  • Allows for conversion of a regex to a parser

Quickstart Examples

Simple char and string parsing

This parser will only accept the string "hello world"

p = do                
    h <- char 'h'                   --Parses the character 'h'
    rest <- string "ello world"     --Parses the string "ello world"
    exp <- char '!'                 --Parses the character '!'
    return ([h]++rest++[exp])       --Returns all of the above concatenated together

Basic combinatorial parsing

This parser will accept the string "hello woooooorld" with any number of o's. It returns the number of o's.

p = do
    first <- string "hello w"         --Parses the string "hello w"
    os <- many1 (char 'o')            --Applies the parser "char 'o'" one or more times
    second <- string "rld"            --Parses the string "rld"
    return (length os)                --Return the number of o's parsed

Recursive combinatorial parsing

This parser will turn a string of comma separated values into a list of them

csv = do  
    v <- greedy (many (noneOf ","))       --Parses as many non-comma characters as possible
    vs <- option [] (char ',' >> csv)     --Optionally parses a comma and a csv, returning the empty list upon failure
    return (v:vs)                         --Concatenates and returns the full list

General Parsing

class (Eq s, Monoid s) => Stream s t | s -> t whereSource

A Stream instance has a stream of type s, made up of tokens of type t, which must be determinable by the stream.

Methods

uncons :: Stream s t => s -> Maybe (t, s)Source

uncons returns Nothing if the Stream is empty, otherwise it returns the first token of the stream, followed by the remainder of the stream, wrapped in a Just.

length :: Stream s t => s -> IntSource

The default length implementation is O(n). If your stream provides a more efficient method for determining the length, it is wise to override this. The length method is only used by the greedy parser.

Instances

Eq t => Stream [t] t

Makes common types such as Strings into a Stream.

data Result s a Source

Constructors

Partial

A Partial wraps the same function as a Parser. Supply it with a Just and it will continue parsing, or with a Nothing and it will terminate.

Fields

continue :: Maybe s -> [Result s a]
 
Done

A Done contains the resultant value, and the leftover stream, if any.

Fields

value :: a
 
leftover :: Maybe s
 
Fail

A Fail contains a stack of error messages, and the lftover stream, if any.

Fields

messages :: [String]
 
leftover :: Maybe s
 

Instances

Functor (Result s) 
Show a => Show (Result s a) 

data Parser s a Source

Instances

Monad (Parser s) 
Functor (Parser s) 
MonadPlus (Parser s) 
Applicative (Parser s) 
Alternative (Parser s) 
Monoid (Parser s a) 

justParse :: Stream s t => Parser s a -> s -> Maybe aSource

This is a "newbie" command that one should probably only use out of frustration. It runs the Parser greedily over the input, finalizes all the results, and returns the first successful result. If there are no successful results, it returns Nothing.

runParser :: Parser s a -> s -> [Result s a]Source

Supplies the input to the Parser. Returns all Result types, including Partial and Fail types.

finalize :: (Eq s, Monoid s) => [Result s a] -> [Result s a]Source

finalize takes a list of results (presumably returned from a Parser or Partial, and supplies Nothing to any remaining Partial values, so that only Fail and Done values remain.

extend :: (Eq s, Monoid s) => Maybe s -> [Result s a] -> [Result s a]Source

extend takes a Maybe s as input, and supplies the input to all values in the Result list. For Done and Fail values, it appends the stream to the leftover portion, and for Partial values, it runs the continuation, adding in any new Result values to the output.

isDone :: Result s a -> BoolSource

isFail :: Result s a -> BoolSource

isPartial :: Result s a -> BoolSource

rename :: String -> Parser s a -> Parser s aSource

rename pushes a new error message onto the stack in case of failure. This is particularly useful when debugging a complex Parser.

(<?>) :: Parser s a -> String -> Parser s aSource

The infix version of rename

Generic Parsers

test :: Parser s a -> Parser s BoolSource

Return True if the Parser would succeed if one were to apply it, otherwise, False.

greedy :: Stream s t => Parser s a -> Parser s aSource

Modifies a Parser so that it will ony return the most consumptive succesful results. If there are no successful results, it will only return the most consumptive failures. One can use greedy to emulate parsers from Parsec or attoparsec.

option :: a -> Parser s a -> Parser s aSource

Attempts to apply a parser and returns a default value if it fails.

satisfy :: Stream s t => (t -> Bool) -> Parser s tSource

Parse a token that satisfies a predicate.

mN :: Int -> Int -> Parser s a -> Parser s [a]Source

Parse from m to n occurences of a Parser. Let n be negative if one wishes for no upper bound.

many :: Parser s a -> Parser s [a]Source

Parse any number of occurences of the Parser. Equivalent to mN 0 (-1).

many1 :: Parser s a -> Parser s [a]Source

Parse one or more occurence of the Parser. Equivalent to mN 1 (-1).

manyN :: Int -> Parser s a -> Parser s [a]Source

Parse at least n occurences of the Parser. Equivalent to mN n (-1).

atLeast :: Int -> Parser s a -> Parser s [a]Source

Identical to manyN, just a more intuitive name.

exactly :: Int -> Parser s a -> Parser s [a]Source

Parse exactly n occurences of the Parser. Equivalent to mN n n.

eof :: (Eq s, Monoid s) => Parser s ()Source

Only succeeds when supplied with Nothing.

oneOf :: (Eq t, Stream s t) => [t] -> Parser s tSource

noneOf :: (Eq t, Stream s t) => [t] -> Parser s tSource

lookAhead :: Parser s a -> Parser s aSource

Applies the parser and returns its result, but resets the leftovers as if it consumed nothing.

Char Parsers

char :: Stream s Char => Char -> Parser s CharSource

Parse a specic char.

anyChar :: Stream s Char => Parser s CharSource

ascii :: Stream s Char => Parser s CharSource

latin1 :: Stream s Char => Parser s CharSource

control :: Stream s Char => Parser s CharSource

space :: Stream s Char => Parser s CharSource

lower :: Stream s Char => Parser s CharSource

upper :: Stream s Char => Parser s CharSource

alpha :: Stream s Char => Parser s CharSource

alphaNum :: Stream s Char => Parser s CharSource

print :: Stream s Char => Parser s CharSource

digit :: Stream s Char => Parser s CharSource

octDigit :: Stream s Char => Parser s CharSource

hexDigit :: Stream s Char => Parser s CharSource

eol :: Stream s Char => Parser s StringSource

Parses until a newline, carriage return + newline, or newline + carriage return.

String Parsers

string :: Stream s Char => String -> Parser s StringSource

Parse a specific string.

Regex Parsers

regex :: Stream s Char => String -> Parser s MatchSource

regex takes a regular expression in the form of a String and, if the regex is valid, returns a Parser that parses that regex. If the regex is invalid, it returns a Parser that will only return Fail with an "Invalid Regex" message.

regex' :: Stream s Char => String -> Parser s StringSource

The same as regex, but only returns the full matched text.

data Match Source

The result of a regex

Constructors

Match 

Fields

matched :: String

The complete text matched within the regex

groups :: [Match]

Any submatches created by using capture groups

Instances

Show Match 
Monoid Match