little-earley-0.2.0.0: Simple implementation of Earley parsing
Safe HaskellSafe-Inferred
LanguageHaskell2010

Little.Earley.Internal.Tree

Synopsis

Documentation

data TreeT f n t c Source #

Generalized parse tree.

A basic parse tree (Tree) consists of leaves labeled terminal symbols t (Leaf) and nodes labeled with grammar rules associated to nonterminal symbols ((Brch)).

Other variants of parse trees (TreeSet, TruncatedTreeSet) can be represented using extension nodes (Ext).

Trees may be infinite due to an input string matching infinitely many parse trees. Note that even though StrictData is enabled, we get laziness via the list type [] and tuple type (,).

Constructors

Leaf Int t c

The Int field is the position of the token in the input.

Brch (RuleId n) Int Int [TreeT f n t c]

The Int fields are the endpoints of this subtree in the input.

Ext (f (TreeT f n t c)) 

Instances

Instances details
(Eq n, Eq t, Eq c, Eq (f (TreeT f n t c))) => Eq (TreeT f n t c) Source # 
Instance details

Defined in Little.Earley.Internal.Tree

Methods

(==) :: TreeT f n t c -> TreeT f n t c -> Bool #

(/=) :: TreeT f n t c -> TreeT f n t c -> Bool #

(Show n, Show t, Show c, Show (f (TreeT f n t c))) => Show (TreeT f n t c) Source # 
Instance details

Defined in Little.Earley.Internal.Tree

Methods

showsPrec :: Int -> TreeT f n t c -> ShowS #

show :: TreeT f n t c -> String #

showList :: [TreeT f n t c] -> ShowS #

type Tree = TreeT NoExt Source #

Basic parse tree.

type TreeSet = TreeT Choice Source #

A set of Tree, using a compact encoding.

type TruncatedTree = TreeT (Sum Ellipsis NoExt) Source #

Result of truncateTree applied to a Tree.

Functors for extending TreeT

data NoExt a Source #

No extensions.

Instances

Instances details
Functor NoExt Source # 
Instance details

Defined in Little.Earley.Internal.Tree

Methods

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

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

Eq (NoExt a) Source # 
Instance details

Defined in Little.Earley.Internal.Tree

Methods

(==) :: NoExt a -> NoExt a -> Bool #

(/=) :: NoExt a -> NoExt a -> Bool #

Show (NoExt a) Source # 
Instance details

Defined in Little.Earley.Internal.Tree

Methods

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

show :: NoExt a -> String #

showList :: [NoExt a] -> ShowS #

data Choice a Source #

Choice constructor to represent TreeSet.

Constructors

a :|: a infixr 1 

Instances

Instances details
Functor Choice Source # 
Instance details

Defined in Little.Earley.Internal.Tree

Methods

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

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

HasChoice Choice Source # 
Instance details

Defined in Little.Earley.Internal.Tree

Methods

(.:|:) :: a -> a -> Choice a Source #

Eq a => Eq (Choice a) Source # 
Instance details

Defined in Little.Earley.Internal.Tree

Methods

(==) :: Choice a -> Choice a -> Bool #

(/=) :: Choice a -> Choice a -> Bool #

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

Defined in Little.Earley.Internal.Tree

Methods

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

show :: Choice a -> String #

showList :: [Choice a] -> ShowS #

HasChoice (Sum f Choice) Source # 
Instance details

Defined in Little.Earley.Internal.Tree

Methods

(.:|:) :: a -> a -> Sum f Choice a Source #

class HasChoice f where Source #

Overloaded version of (:|:).

Methods

(.:|:) :: a -> a -> f a Source #

Instances

Instances details
HasChoice Choice Source # 
Instance details

Defined in Little.Earley.Internal.Tree

Methods

(.:|:) :: a -> a -> Choice a Source #

HasChoice (Sum f Choice) Source # 
Instance details

Defined in Little.Earley.Internal.Tree

Methods

(.:|:) :: a -> a -> Sum f Choice a Source #

(|:) :: HasChoice f => TreeT f n t c -> TreeT f n t c -> TreeT f n t c infixr 1 Source #

Construct the disjunction of two trees featuring the Choice functor.

data Ellipsis a Source #

Ellided by truncateTree.

Constructors

Ellipsis 

Instances

Instances details
Functor Ellipsis Source # 
Instance details

Defined in Little.Earley.Internal.Tree

Methods

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

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

Eq (Ellipsis a) Source # 
Instance details

Defined in Little.Earley.Internal.Tree

Methods

(==) :: Ellipsis a -> Ellipsis a -> Bool #

(/=) :: Ellipsis a -> Ellipsis a -> Bool #

Show (Ellipsis a) Source # 
Instance details

Defined in Little.Earley.Internal.Tree

Methods

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

show :: Ellipsis a -> String #

showList :: [Ellipsis a] -> ShowS #

ellipsis :: TreeT (Sum Ellipsis f) n t c Source #

Empty tree.

data Sum f g a Source #

Like Sum from Data.Functor.Sum but with more basic instances

Constructors

InL (f a) 
InR (g a) 

Instances

Instances details
(Functor f, Functor g) => Functor (Sum f g) Source # 
Instance details

Defined in Little.Earley.Internal.Tree

Methods

fmap :: (a -> b) -> Sum f g a -> Sum f g b #

(<$) :: a -> Sum f g b -> Sum f g a #

HasChoice (Sum f Choice) Source # 
Instance details

Defined in Little.Earley.Internal.Tree

Methods

(.:|:) :: a -> a -> Sum f Choice a Source #

(Eq (f a), Eq (g a)) => Eq (Sum f g a) Source # 
Instance details

Defined in Little.Earley.Internal.Tree

Methods

(==) :: Sum f g a -> Sum f g a -> Bool #

(/=) :: Sum f g a -> Sum f g a -> Bool #

(Show (f a), Show (g a)) => Show (Sum f g a) Source # 
Instance details

Defined in Little.Earley.Internal.Tree

Methods

showsPrec :: Int -> Sum f g a -> ShowS #

show :: Sum f g a -> String #

showList :: [Sum f g a] -> ShowS #

parseTreeSet :: (Ord n, Ord t) => Grammar n t c -> n -> [c] -> Maybe (TreeSet n t c) Source #

Parse a chain of tokens [c] into a parse tree. Simplified variant of parse.

parseTreeSet_ :: (Ord n, Ord t) => Grammar n t c -> n -> [c] -> (Seq1 (Set (Item n t)), Maybe (TreeSet n t c)) Source #

lookupSeq1 :: Int -> Seq1 a -> a Source #

growTree :: (Ord n, Ord t) => Grammar n t c -> Seq c -> Seq1 (Set (Item n t)) -> n -> Int -> Int -> Maybe (TreeSet n t c) Source #

matchItems :: (Ord n, Ord t) => Seq1 (Set (Item n t)) -> n -> Int -> [Item n t] Source #

unionTrees :: [TreeSet n t c] -> Maybe (TreeSet n t c) Source #

growBranches :: (Ord n, Ord t) => Grammar n t c -> Seq c -> Seq1 (Set (Item n t)) -> RuleId n -> Int -> Int -> [TreeSet n t c] Source #

sortAndGroupBy :: Ord b => (a -> b) -> [a] -> [[a]] Source #

growBranchesFrom :: (Ord n, Ord t) => Grammar n t c -> Seq c -> Seq1 (Set (Item n t)) -> Int -> Int -> [Atom n t] -> [TreeSet n t c] -> [[TreeSet n t c]] Source #

truncateTree :: Functor f => Int -> TreeT f n t c -> TreeT (Sum Ellipsis f) n t c Source #

Truncate a tree to finite depth.

truncateTree :: Int -> TreeSet n t c -> TruncatedTreeSet n t c
truncateTree :: Int -> Tree n t c -> TruncatedTree n t c

fromSingleton :: TreeSet n t c -> Maybe (Tree n t c) Source #

Return Just if the given TreeSet represents a single Tree, Nothing otherwise (ambiguous parse tree).

data Lazy a Source #

Constructors

Now a 
Later ~(Lazy a) 

Instances

Instances details
Functor Lazy Source # 
Instance details

Defined in Little.Earley.Internal.Tree

Methods

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

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

Applicative Lazy Source # 
Instance details

Defined in Little.Earley.Internal.Tree

Methods

pure :: a -> Lazy a #

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

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

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

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

Alternative Lazy Source # 
Instance details

Defined in Little.Earley.Internal.Tree

Methods

empty :: Lazy a #

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

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

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

arbTree :: TreeSet n t c -> Tree n t c Source #

Get an arbitrary Tree from a TreeSet, even if it is ambiguous.

arbTree_ :: TreeSet n t c -> Lazy (Tree n t c) Source #

data Range Source #

An interval in some input sequence.

Constructors

Range 

Fields

Instances

Instances details
Eq Range Source # 
Instance details

Defined in Little.Earley.Internal.Tree

Methods

(==) :: Range -> Range -> Bool #

(/=) :: Range -> Range -> Bool #

Ord Range Source # 
Instance details

Defined in Little.Earley.Internal.Tree

Methods

compare :: Range -> Range -> Ordering #

(<) :: Range -> Range -> Bool #

(<=) :: Range -> Range -> Bool #

(>) :: Range -> Range -> Bool #

(>=) :: Range -> Range -> Bool #

max :: Range -> Range -> Range #

min :: Range -> Range -> Range #

Show Range Source # 
Instance details

Defined in Little.Earley.Internal.Tree

Methods

showsPrec :: Int -> Range -> ShowS #

show :: Range -> String #

showList :: [Range] -> ShowS #

mkRange :: Int -> Int -> Range Source #

Construt a range from its end points.

leftEnd :: Tree n t c -> Int Source #

rightEnd :: Tree n t c -> Int Source #

data Ambiguity n t c Source #

Evidence of ambiguity: two parse trees for the same input.

Constructors

Ambiguity (Tree n t c) (Tree n t c) 

Instances

Instances details
(Eq n, Eq t, Eq c) => Eq (Ambiguity n t c) Source #

This instance treats Ambiguity as an unordered pair.

Instance details

Defined in Little.Earley.Internal.Tree

Methods

(==) :: Ambiguity n t c -> Ambiguity n t c -> Bool #

(/=) :: Ambiguity n t c -> Ambiguity n t c -> Bool #

(Show n, Show t, Show c) => Show (Ambiguity n t c) Source # 
Instance details

Defined in Little.Earley.Internal.Tree

Methods

showsPrec :: Int -> Ambiguity n t c -> ShowS #

show :: Ambiguity n t c -> String #

showList :: [Ambiguity n t c] -> ShowS #

type LocAmbiguity n t c = (Range, Ambiguity n t c) Source #

Ambiguity at a given location.

(><) :: [a] -> [a] -> [a] Source #

Interleave two lists together. This combines enumerations somewhat fairly.

ambiguities :: TreeSet n t c -> [LocAmbiguity n t c] Source #

Enumerate (some) ambiguous parses.

If there are multiple ambiguities at the same location, we just pick an arbitrary example.