-- | Utilities for interpreting context-free grammars as Earley parsers -- and for processing parse trees. -- -- The library is parameterized by types for non-terminal symbols @n@, -- terminal symbols @t@, and tokens @c@. -- -- - Non-terminal symbols @n@ are associated with production rules. -- - Terminal symbols @t@ denote sets of tokens @c@. -- - Lists of tokens @[c]@ form the actual inputs. -- -- = Example -- -- @ -- import Data.Char (isDigit) -- import Little.Earley -- -- data Ns = SUM | PRODUCT | FACTOR | NUMBER deriving (Eq, Ord, Enum, Bounded, Show) -- data Ts = Digit | OneOf [Char] deriving (Eq, Ord, Show) -- -- arithRules :: Ns -> ['Rule' Ns Ts] -- arithRules n = case n of -- SUM -> -- [ [ 'N' PRODUCT ] -- , [ 'N' SUM, 'T' (OneOf [\'+\', \'-\']), 'N' PRODUCT ] ] -- PRODUCT -> -- [ [ 'N' FACTOR ] -- , [ 'N' PRODUCT, 'T' (OneOf [\'*\', \'/\']), 'N' FACTOR ] ] -- FACTOR -> -- [ [ 'N' NUMBER ] -- , [ 'T' (OneOf [\'(\']), 'N' SUM, 'T' (OneOf [\')\']) ] ] -- NUMBER -> -- [ [ 'T' Digit ] -- , [ 'T' Digit, 'N' NUMBER ] ] -- -- matchTs :: Ts -> Char -> Bool -- matchTs Digit = isDigit -- matchTs (OneOf s) = (\`elem\` s) -- -- arithG :: 'Grammar' Ns Ts Char -- arithG = 'mkGrammar' arithRules matchTs -- @ -- -- Load that file in GHCi, then parse a string using that grammar: -- -- @ -- > 'pparse' arithG SUM \"1+2*3\" -- @ -- -- See also "Little.Earley.Examples" for some examples of grammars. module Little.Earley ( -- * Basic interface parse , pparse , parseTreeSet , accepts , Result(..) , ParsedResult(..) , Error(..) -- * Grammars , Grammar(..) , mkGrammar , Rule , Atom(..) , RuleId(..) -- * Parse trees , TreeT(..) , Tree , TreeSet , TruncatedTree , TruncatedTreeSet -- ** Parse tree modifiers , NoExt , Choice(..) , HasChoice() , (|:) , Ellipsis(..) , ellipsis , Sum(..) -- ** Operations on parse trees , fromSingleton , arbTree , truncateTree , ambiguities , Range(..) , Ambiguity(..) , LocAmbiguity -- * Pretty-printing , PrettyPrint(..) , Pretty(..) , drawTree , prettyTree ) where import Little.Earley.Internal.Core import Little.Earley.Internal.Tree import Little.Earley.Internal.Pretty import Little.Earley.Internal.Render import Little.Earley.Internal.Result import Little.Earley.Internal.PrettyOrphan ()