flatparse-0.3.5.1: High-performance parsing from strict bytestrings
Safe HaskellNone
LanguageHaskell2010

FlatParse.Examples.BasicLambda.Parser

Description

This module contains a simple lambda calculus parser. This parser is not optimized for maximum performance; instead it's written in a style which emulates the look and feel of conventional monadic parsers. An optimized implementation would use low-level switch expressions more often.

Synopsis

Documentation

data Tm Source #

A term in the language. The precedences of different constructs are the following, in decreasing order of strength:

  • Identifiers, literals and parenthesized expressions
  • Function application (left assoc)
  • Multiplication (left assoc)
  • Addition (left assoc)
  • Equality, less-than (non-assoc)
  • lam, let, if (right assoc)

Constructors

Var Name
x
App Tm Tm
t u
Lam Name Tm
lam x. t
Let Name Tm Tm
let x = t in u
BoolLit Bool

true or false.

IntLit Int

A positive Int literal.

If Tm Tm Tm
if t then u else v
Add Tm Tm
t + u
Mul Tm Tm
t * u
Eq Tm Tm
t == u
Lt Tm Tm
t < u

Instances

Instances details
Show Tm Source # 
Instance details

Defined in FlatParse.Examples.BasicLambda.Parser

Methods

showsPrec :: Int -> Tm -> ShowS #

show :: Tm -> String #

showList :: [Tm] -> ShowS #

ident :: Parser Name Source #

Parse an identifier. This parser uses isKeyword to check that an identifier is not a keyword.

ident' :: Parser Name Source #

Parse an identifier, throw a precise error on failure.

atom :: Parser Tm Source #

Parse a literal, identifier or parenthesized expression.

app' :: Parser Tm Source #

Parse an App-level expression.

mul' :: Parser Tm Source #

Parse a Mul-level expression.

add' :: Parser Tm Source #

Parse an Add-level expression.

eqLt' :: Parser Tm Source #

Parse an Eq or Lt-level expression.

pLet :: Parser Tm Source #

Parse a Let.

lam :: Parser Tm Source #

Parse a Lam.

pIf :: Parser Tm Source #

Parse an If.

tm' :: Parser Tm Source #

Parse any Tm.

src' :: Parser Tm Source #

Parse a complete source file.