
Some snippets from the Tutorial [1] to give an idea of the grammar-combinator library's approach, its functional style and its additional power (e.g. the transformations used): Defining a simple expresssions grammar: grammarArith :: ExtendedContextFreeGrammar ArithDomain Char grammarArith Line = LineF $>> ref Expr >>>* endOfInput grammarArith Expr = SubtractionF $>> ref Expr >>>* token '-' >>> ref Term ||| SumF $>> ref Expr >>>* token '+' >>> ref Term ||| SingleTermF $>> ref Term grammarArith Term = SingleFactorF $>> ref Factor ||| QuotientF $>> ref Term >>>* token '/' >>> ref Factor ||| ProductF $>> ref Term >>>* token '*' >>> ref Factor grammarArith Factor = NumberF $>> many1Ref Digit ||| ParenthesizedF $>>* token '(' >>> ref Expr >>>* token ')' grammarArith Digit = DigitF $>> tokenRange ['0' .. '9'] A semantic processor: data family ArithValue ix newtype instance ArithValue Line = ArithValueL Int deriving (Show) newtype instance ArithValue Expr = ArithValueE Int deriving (Show) newtype instance ArithValue Term = ArithValueT Int deriving (Show) newtype instance ArithValue Factor = ArithValueF Int deriving (Show) newtype instance ArithValue Digit = ArithValueD Char deriving (Show) calcArith :: Processor ArithDomain ArithValue calcArith Line (LineF (ArithValueE e)) = ArithValueL e calcArith Expr (SumF (ArithValueE e) (ArithValueT t)) = ArithValueE $ e + t calcArith Expr (SingleTermF (ArithValueT t)) = ArithValueE t calcArith Term (ProductF (ArithValueT e) (ArithValueF t)) = ArithValueT $ e * t calcArith Term (SingleFactorF (ArithValueF t)) = ArithValueT t calcArith Factor (ParenthesizedF (ArithValueE e)) = ArithValueF e calcArith Factor (NumberF ds) = ArithValueF $ read $ map unArithValueD ds calcArith Digit (DigitF c) = ArithValueD c unArithValueD :: ArithValue Digit -> Char unArithValueD (ArithValueD c) = c Transforming the grammar: calcGrammarArith :: ProcessingExtendedContextFreeGrammar ArithDomain Char ArithValue calcGrammarArith = applyProcessorE grammarArith calcArith calcGrammarArithTP :: ProcessingExtendedContextFreeGrammar (UPDomain ArithDomain) Char (UPValue ArithValue) calcGrammarArithTP = transformUniformPaullE calcGrammarArith calcGrammarArithTPF :: ProcessingExtendedContextFreeGrammar (UPDomain ArithDomain) Char (UPValue ArithValue) calcGrammarArithTPF = filterDiesE (unfoldDeadE calcGrammarArithTP) calcGrammarArithTPFF :: ProcessingContextFreeGrammar (FoldLoopsDomain (UPDomain ArithDomain)) Char (FoldLoopsValue (UPValue ArithValue)) calcGrammarArithTPFF = foldAndProcessLoops calcGrammarArithTPF Parsing: *Main> parsePackrat calcGrammarArithTPFF (FLBase (UPBase Line)) "123" Parsed FLBV {unFLBV = UPBV {unUPBV = ArithValueL 123}} _ *Main> parsePackrat calcGrammarArithTPFF (FLBase (UPBase Line)) "123+" NoParse *Main> parsePackrat calcGrammarArithTPFF (FLBase (UPBase Line)) "123+12" Parsed FLBV {unFLBV = UPBV {unUPBV = ArithValueL 135}} _ *Main> parseParsec calcGrammarArithTPFF (FLBase (UPBase Line)) "" "123+12" Right (FLBV {unFLBV = UPBV {unUPBV = ArithValueL 135}}) *Main> parseUU calcGrammarArithTPFF (FLBase (UPBase Line)) "123+12" FLBV {unFLBV = UPBV {unUPBV = ArithValueL 135}} Dominique Footnotes: [1] http://projects.haskell.org/grammar-combinators/tutorial.html