grammatical-parsers: parsers that combine into grammars

[ bsd3, library, parsing, program, text ] [ Propose Tags ]

Grammatical-parsers, or Grampa for short, is a library of parser types whose values are meant to be assigned to grammar record fields. All parser types support the same set of parser combinators, but have different semantics and performance characteristics.


[Skip to Readme]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.1, 0.2, 0.2.1, 0.2.2, 0.3, 0.3.1, 0.3.2, 0.4, 0.4.0.1, 0.4.1, 0.4.1.1, 0.4.1.2, 0.5, 0.5.1, 0.5.2, 0.6, 0.7, 0.7.0.1, 0.7.1
Change log CHANGELOG.md
Dependencies attoparsec (>=0.13 && <0.14), base (>=4.9 && <5), bytestring (>=0.10 && <0.11), containers (>=0.5.7.0 && <0.7), grammatical-parsers, input-parsers (<0.2), monoid-subclasses (>=1.0 && <1.1), parsers (<0.13), rank2classes (>=1.0.2 && <1.5), transformers (>=0.5 && <0.6) [details]
License BSD-3-Clause
Copyright (c) 2017 Mario Blažević
Author Mario Blažević
Maintainer Mario Blažević <blamario@protonmail.com>
Category Text, Parsing
Home page https://github.com/blamario/grampa/tree/master/grammatical-parsers
Bug tracker https://github.com/blamario/grampa/issues
Source repo head: git clone https://github.com/blamario/grampa
Uploaded by MarioBlazevic at 2020-11-11T04:08:17Z
Distributions
Reverse Dependencies 3 direct, 1 indirect [details]
Executables boolean-transformations, arithmetic
Downloads 7531 total (54 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2020-11-11 [all 1 reports]

Readme for grammatical-parsers-0.5

[back to package description]

Grammatical Parsers

Behold, yet another parser combinator library in Haskell. Except this one is capable of working with grammars rather than mere parsers. A more in-depth description is available in the paper from Haskell Symposium 2017, what follows is a short tutorial.

You can apply the usual Applicative, Alternative, and Monad operators to combine primitive parsers into larger ones. The combinators from the parsers library type classes are also available. Here are some typical imports you may need:

{-# LANGUAGE RecordWildCards, ScopedTypeVariables, TemplateHaskell #-}
module README where
import Control.Applicative
import Data.Char (isDigit)
import Data.Functor.Classes (Show1, showsPrec1)
import Text.Grampa
import Text.Grampa.ContextFree.LeftRecursive (Parser)
import qualified Rank2.TH

What puts this library apart from most is that these parsers are grammatical, just as the library name says. Instead of writing the parser definitions as top-level bindings, you can and should group them into a grammar record definition, like this:

arithmetic :: GrammarBuilder Arithmetic g Parser String
arithmetic Arithmetic{..} = Arithmetic{
   sum= product
         <|> string "-" *> (negate <$> product)
         <|> (+) <$> sum <* string "+" <*> product
         <|> (-) <$> sum <* string "-" <*> product,
   product= factor
         <|> (*) <$> product <* string "*" <*> factor
         <|> div <$> product <* string "/" <*> factor,
   factor= read <$> number
           <|> string "(" *> sum <* string ")",
   number= takeCharsWhile1 isDigit <?> "number"}

What on Earth for? One good reason is that these parser definitions can then be left-recursive, which is normally a death knell for parser libraries. There are other benefits like memoization and grammar composability, and the main downside is the obligation to declare the grammar record:

data Arithmetic f = Arithmetic{sum     :: f Int,
                               product :: f Int,
                               factor  :: f Int,
                               number  :: f String}

and to make it an instance of several rank 2 type classes:

$(Rank2.TH.deriveAll ''Arithmetic)

Optionally, you may also be inclined to declare a proper Show instance, as it's often handy:

instance Show1 f => Show (Arithmetic f) where
   show Arithmetic{..} =
      "Arithmetic{\n  sum=" ++ showsPrec1 0 sum
           (",\n  product=" ++ showsPrec1 0 factor
           (",\n  factor=" ++ showsPrec1 0 factor
           (",\n  number=" ++ showsPrec1 0 number "}")))

Once that's done, use fixGrammar to, well, fix the grammar

grammar = fixGrammar arithmetic

and then parseComplete or parsePrefix to parse some input.

-- |
-- >>> parseComplete grammar "42"
-- Arithmetic{
--   sum=Compose (Right [42]),
--   product=Compose (Right [42]),
--   factor=Compose (Right [42]),
--   number=Compose (Right ["42"])}
-- >>> parseComplete grammar "1+2*3"
-- Arithmetic{
--   sum=Compose (Right [7]),
--   product=Compose (Left (ParseFailure 1 [Expected "end of input"])),
--   factor=Compose (Left (ParseFailure 1 [Expected "end of input"])),
--   number=Compose (Left (ParseFailure 1 [Expected "end of input"]))}
-- >>> parsePrefix grammar "1+2*3 apples"
-- Arithmetic{
--   sum=Compose (Compose (Right [("+2*3 apples",1),("*3 apples",3),(" apples",7)])),
--   product=Compose (Compose (Right [("+2*3 apples",1)])),
--   factor=Compose (Compose (Right [("+2*3 apples",1)])),
--   number=Compose (Compose (Right [("+2*3 apples","1")]))}

To see more grammar examples, go straight to the examples directory that builds up several smaller grammars and combines them all together in the Combined module.

For more conventional tastes there are monolithic examples of Lua and Oberon grammars as well.