derp-0.1.6: Derivative Parsing

Safe HaskellSafe-Infered

Text.Derp

Contents

Synopsis

Data Types

data Parser t a Source

Represents both a formal context-free language and the reduction of a member of that language to a value of type a.

Instances

Show (Parser t a) 

data Token t Source

Constructors

Token 

Fields

tokenClass :: t
 
tokenValue :: String
 

Instances

Eq t => Eq (Token t) 
Ord t => Ord (Token t) 
Show t => Show (Token t) 

Parser construction

(<|>) :: (Ord t, Ord a) => Parser t a -> Parser t a -> Parser t aSource

Alternation.

(<~>) :: (Ord t, Ord a, Ord b) => Parser t a -> Parser t b -> Parser t (a, b)Source

Concatenation.

(==>) :: (Ord t, Ord a, Ord b) => Parser t a -> (a -> b) -> Parser t bSource

Reduction.

nul :: (Ord t, Ord a) => Parser t a -> Parser t aSource

Null-parse extraction.

ter :: Ord t => t -> Parser t StringSource

Terminal.

eps :: (Ord t, Ord a) => a -> Parser t aSource

Epsilon/empty-string.

emp :: (Ord t, Ord a) => Parser t aSource

The empty language.

Parser computation steps

derive :: Parser t a -> Token t -> Parser t aSource

The main derivative function.

compact :: Parser t a -> Parser t aSource

The optimization step of the algorithm.

parseNull :: (Ord t, Ord a) => Parser t a -> Set aSource

Extract the parse-null set of a parser.

Full parsing and result extraction

defaultCompactSteps :: IntSource

The number of compact steps that usually keeps a parser constant in size while parsing.

compactNum :: Int -> Parser t a -> Parser t aSource

A specified number of compactions.

deriveStepNum :: Int -> Parser t a -> Token t -> Parser t aSource

Derivation followed by a specified number of compactions.

runParseNum :: (Ord t, Ord a) => Int -> Parser t a -> [Token t] -> Set aSource

Parse using a specified number of intermediate compactions.

runParseStagesNum :: (Ord t, Ord a) => Int -> Parser t a -> [Token t] -> [(Parser t a, Set a, [Token t])]Source

runParseStages :: (Ord t, Ord a) => Parser t a -> [Token t] -> [(Parser t a, Set a, [Token t])]Source

runParseLongestMatchNum :: (Ord t, Ord a) => Int -> Parser t a -> [Token t] -> Maybe (Int, Set a, [Token t])Source

runParseLongestMatch :: (Ord t, Ord a) => Parser t a -> [Token t] -> Maybe (Int, Set a, [Token t])Source

deriveStep :: Parser t a -> Token t -> Parser t aSource

Derivation followed by the default number of compactions.

runParse :: (Ord t, Ord a) => Parser t a -> [Token t] -> Set aSource

Parse using the default number of intermediate compactions. This is the main parsing function. Examples:

 let e =     ter "num"
         <|> e <~> ter "+" <~> e ==> (\(x1,(o,x2)) -> "(" ++ x1 ++ o ++ x2 ++ ")")
 in runParse e [Token "num" "1", Token "+" "+", Token "num" 3", Token "+" "+", Token "num" "5"]

evaluates to:

 Set.fromList ["((1+3)+5)", "(1+(3+5))"]
 let e =     ter "num" ==> read 
         <|> e <~> ter "+" <~> e ==> (\(x1,(_,x2)) -> x1 + x2)
 in runParse e [Token "num" "1", Token "+" "+", Token "num" 3", Token "+" "+", Token "num" "5"]

evaluates to:

 Set.fromList [9]

Demos