yapb: Yet Another Parser Builder (YAPB)

[ bsd3, library, parser-builder, program ] [ Propose Tags ]

A programmable LALR(1) parser builder system. Please see the README on GitHub at https://github.com/kwanghoon/yapb#readme


[Skip to Readme]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.1.0, 0.1.1, 0.1.3, 0.1.3.1, 0.1.3.2, 0.2, 0.2.1, 0.2.2, 0.2.3, 0.2.4, 0.2.5, 0.2.6, 0.2.7
Change log ChangeLog.md
Dependencies aeson (>=1.4.7 && <1.5), aeson-pretty (>=0.8.8 && <0.9), base (>=4.7 && <5), bytestring (>=0.10.8 && <0.11), containers (>=0.6.0 && <0.7), directory (>=1.3.3 && <1.4), hashable (>=1.3.0 && <1.4), json (>=0.10 && <0.11), network (>=3.1.1 && <3.2), pretty (>=1.1.3 && <1.2), prettyprinter (>=1.6.1 && <1.7), process (>=1.6.5 && <1.7), regex-tdfa (>=1.3.1 && <1.4), yapb [details]
License BSD-3-Clause
Copyright 2020 Kwanghoon Choi
Author Kwanghoon Choi
Maintainer lazyswamp@gmail.com
Category parser builder
Home page https://github.com/kwanghoon/yapb#readme
Bug tracker https://github.com/kwanghoon/yapb/issues
Source repo head: git clone https://github.com/kwanghoon/yapb
Uploaded by lazyswamp at 2020-06-26T12:16:03Z
Distributions
Executables yapb-exe, syncomp-exe, polyrpc-exe, parser-exe, conv-exe
Downloads 938 total (42 in the last 30 days)
Rating 2.0 (votes: 1) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2020-06-26 [all 1 reports]

Readme for yapb-0.1.0

[back to package description]

YAPB: Yet Another Parser Builder

A programmable parser builder system

  • Allows to write LALR(1) parser specifications in Haskell
  • Provides an automatic syntax completion method

Library, tools, and examples

  • yapb: a library for a programmable parser builder system
  • yapb-exe: a wrapper interface to YAPB
  • conv-exe: a grammar format utility for conversion of a readable grammar (.lgrm) format into the Haskell data format (.grm)
  • syncomp-exe: a syntax completion server for Emacs
  • Examples:
    • parser-exe: an arithmetic parser
    • polyrpc-exe: a polyrpc programming language system including a parser, a poly rpc type checker, a slicing compiler, a poly cs type checker, and a poly cs interpter.

Download and build

  $ git clone https://github.com/kwanghoon/yapb
  $ cd yapb
  $ stack build

How to write and run a parser

  $ ls app/parser/*.hs
  app/parser/Lexer.hs  app/parser/Main.hs  app/parser/Parser.hs  app/parser/Token.hs

  $ cat app/parser/Lexer.hs
  module Lexer(lexerSpec) where

  import Prelude hiding (EQ)
  import CommonParserUtil
  import Token

  mkFn :: Token -> (String -> Maybe Token)
  mkFn tok = \text -> Just tok

  skip :: String -> Maybe Token
  skip = \text -> Nothing

  lexerSpec :: LexerSpec Token
  lexerSpec = LexerSpec
    {
      endOfToken    = END_OF_TOKEN,
      lexerSpecList = 
        [ ("[ \t\n]", skip),
          ("[0-9]+" , mkFn INTEGER_NUMBER),
          ("\\("    , mkFn OPEN_PAREN),
          ("\\)"    , mkFn CLOSE_PAREN),
          ("\\+"    , mkFn ADD),
          ("\\-"    , mkFn SUB),
          ("\\*"    , mkFn MUL),
          ("\\/"    , mkFn DIV),
          ("\\="    , mkFn EQ),
          ("\\;"    , mkFn SEMICOLON),
          ("[a-zA-Z][a-zA-Z0-9]*"    , mkFn IDENTIFIER)
        ]
    } 


  $ cat app/parser/Parser.hs
  module Parser where

  import CommonParserUtil
  import Token
  import Expr


  parserSpec :: ParserSpec Token AST
  parserSpec = ParserSpec
    {
      startSymbol = "SeqExpr'",
    
      parserSpecList =
      [
        ("SeqExpr' -> SeqExpr", \rhs -> get rhs 1),
      
        ("SeqExpr -> SeqExpr ; AssignExpr",
          \rhs -> toAstSeq (
            fromAstSeq (get rhs 1) ++ [fromAstExpr (get rhs 3)]) ),
      
        ("SeqExpr -> AssignExpr", \rhs -> toAstSeq [fromAstExpr (get rhs 1)]),
      
        ("AssignExpr -> identifier = AssignExpr",
          \rhs -> toAstExpr (Assign (getText rhs 1) (fromAstExpr (get rhs 3))) ),
      
        ("AssignExpr -> AdditiveExpr", \rhs -> get rhs 1),

        ("AdditiveExpr -> AdditiveExpr + MultiplicativeExpr",
          \rhs -> toAstExpr (
            BinOp Expr.ADD (fromAstExpr (get rhs 1)) (fromAstExpr (get rhs 3))) ),

        ("AdditiveExpr -> AdditiveExpr - MultiplicativeExpr",
          \rhs -> toAstExpr (
            BinOp Expr.SUB (fromAstExpr (get rhs 1)) (fromAstExpr (get rhs 3))) ),

        ("AdditiveExpr -> MultiplicativeExpr", \rhs -> get rhs 1),

        ("MultiplicativeExpr -> MultiplicativeExpr * PrimaryExpr",
          \rhs -> toAstExpr (
            BinOp Expr.MUL (fromAstExpr (get rhs 1)) (fromAstExpr (get rhs 3))) ),

        ("MultiplicativeExpr -> MultiplicativeExpr / PrimaryExpr",
          \rhs -> toAstExpr (
            BinOp Expr.DIV (fromAstExpr (get rhs 1)) (fromAstExpr (get rhs 3))) ),

        ("MultiplicativeExpr -> PrimaryExpr", \rhs -> get rhs 1),
      
        ("PrimaryExpr -> identifier", \rhs -> toAstExpr (Var (getText rhs 1)) ),

        ("PrimaryExpr -> integer_number",
          \rhs -> toAstExpr (Lit (read (getText rhs 1))) ),

        ("PrimaryExpr -> ( AssignExpr )", \rhs -> get rhs 2)
      ],
    
      baseDir = "./",
      actionTblFile = "action_table.txt",  
      gotoTblFile = "goto_table.txt",
      grammarFile = "prod_rules.txt",
      parserSpecFile = "mygrammar.grm",
      genparserexe = "yapb-exe"
    }

  $ cat app/parser/example/oneline.arith
  1 + 2 - 3 * 4 / 5
  
  $ cat app/parser/example/multiline.arith
  x = 123;
  x = x + 1;
  y = x; 
  y = y - 1 * 2 / 3;
  z = y = x

  $ stack exec parser-exe
  Enter your file: app/parser/example/oneline.arith
  Lexing...
  Parsing...
  done.
  Pretty Printing...
  ((1 + 2) - ((3 * 4) / 5))
  
  $ stack exec parser-exe
  Enter your file: app/parser/example/multiline.arith
  Lexing...
  Parsing...
  done.
  Pretty Printing...
  (x = 123); (x = (x + 1)); (y = x); (y = (y - ((1 * 2) / 3))); (z = (y = x))

Documents