+ All Categories
Home > Documents > Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression...

Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression...

Date post: 14-Mar-2018
Category:
Upload: dolien
View: 223 times
Download: 4 times
Share this document with a friend
55
Parsing Functionally Bill Harrison CS 4430, Spring 2018
Transcript
Page 1: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

ParsingFunctionallyBillHarrison

CS4430,Spring2018

Page 2: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

Today *  “Parsing” or grammatical analysis

* discovers the real structure of a program and represents it in a computationally useful way

*  “Predictive” parsing *  also called “recursive descent” parsing

Page 3: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

Compiler phases

Source

fnmain(){lety=4;letx=7+y;}

Target

movR0,R8calllabel4…

FN ID(main) LPAREN RPAREN LBRACK … EOF

Lex

Output of lexer is unstructured stream of symbols – how do we recognize the program structure in this stream?

Parse

Page 4: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

Thus far… *  A language is a set of strings *  Some languages may be described with a context-free grammar *  Terminals: tokens from the lexer *  Non-terminals: have production rules in our grammar

*  A parser for a grammar/language determines whether a string belongs to a language or not *  Parsing discovers a derivation (if one exists). *  This derivation will let us build our parse tree.

*  Grammars can be ambiguous *  Admit several valid parses *  Can transform grammar to *  remove ambiguity (if necessary) *  make it easier to parse

Page 5: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

Review: Simple CFG

S à if E then S else S S à begin S L S à print E L à end L à; S L E à num = num

Page 6: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

Review: Derivation

S à if E then S else S S à begin S L S à print E L à end L à; S L E à num = num

S à begin S L à begin print E L à begin print 1=1 L à begin print 1=1 end

Page 7: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

Review: Derivation

S à if E then S else S S à begin S L S à print E L à end L à; S L E à num = num

S à begin S L à begin print E L à begin print 1=1 L à begin print 1=1 end

∴ this string is in language(S)

Page 8: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

Review: Parse Trees from Derivations

S à if E then S else S S à begin S L S à print E L à end L à; S L E à num = num

S à begin S L à begin print E L à begin print 1=1 L à begin print 1=1 end

S

begin S L

print E end

1 = 1

Parse Tree Associated with Derivation

Page 9: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

* Recursive descent renders a readable parser. *  depends on the first terminal symbol of each sub-

expression providing enough information to choose which production to use.

*  But consider a rec. des. parser for this grammar

Shortcomings of LL Parsers

void E(){switch(tok) { case ?: E(); eat(TIMES); T(); ç no way of choosing production case ?: T(); … } void T(){eat(ID);}

E à E + T E à T T à id

Page 10: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

*  Terminalsymbols(a.k.a."tokens")*  + * - /

*  Non-terminalsymbols*  Op Exp

*  Productions*  Op à + *  Exp à ( Exp Op Exp )

ExampleCFG

Op à + | * | - | / Exp à int | ( Exp Op Exp )

Page 11: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

Exp à ( Exp Op Exp ) à ( 1 Op Exp ) à ( 1 Op 2 ) à ( 1 * 2 )

ExampleDerivation

Op à + | * | - | / Exp à int | ( Exp Op Exp )

Therefore,( 1 * 2 ) isinthelanguageofExp

eachstepappliesoneproduction

endsinstringofterminal

symbolsonly

Page 12: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

AbstractSyntaxinHaskell

Op à + | * | - | / Exp à int | ( Exp Op Exp )

data Op = Plus | Times | Minus | Div deriving Show data Exp = Const Int | Aexp Op Exp Exp deriving Show

straightforwardrepresentationinHaskell

CheckoutthesnapshotSimpleExpParser.zipoffofthecoursepage

Page 13: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

13

Building Parsers using Monads

Page 14: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

14

Announcements ❚  Today: the Parsing Domain-specific Language ❙  We’ll start describing the parsing operators in

Parsing.lhs ❙  …and how they are used to construct parsers, lexers,

etc ❙  Those who know Lex/Flex and Yacc/Bison will

appreciate the ease with which parsers are constructed this way

Page 15: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

15

Page 16: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

16

Page 17: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

17

Page 18: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

18

Page 19: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

19

Page 20: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

20

What is a Parser?

A parser is a program that analyses a piece of text to determine its syntactic structure.

2*3+4 means 4

+

2

*

3 2

Page 21: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

21

What a front-end does

c l a s s p u b l i c F o o { i n t …

class public name(“Foo”) left-brack type-int …

lexer

ascii form

symbolic form

“Lexing”

CLASSDECL

public name(“Foo”) …

abstract syntax

tree

parser “Parsing”

Page 22: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

22

Multiple Parse Trees

PLEASE PUT A RED BLOCK ON THE BLOCK IN THE BOX •  could mean "Look on the [previously mentioned] block, find a red block there, and put it in the box" •  or it could mean "Look for a red block and put it on the only block in the box. "The syntax is ambiguous, but by looking at the positions of the blocks, we can deduce that one of the possible parses is nonsense, and therefore use the other one.”

…have Artificial Intelligence applications; for Programming Languages, not so much

Page 23: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

23

Where Are They Used?

Almost every real life program uses some form of parser to pre-process its input.

Haskell programs Shell scripts HTML documents

GHCi Unix Explorer

parses

Page 24: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

24

The Parser Type

In a functional language such as Haskell, parsers can naturally be viewed as functions.

type Parser = String → Tree

A parser is a function that takes a string and returns some form of tree.

Page 25: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

25

However, a parser might not require all of its input string, so we also return any unused input:

type Parser = String → (Tree,String)

A string might be parsable in many ways, including none, so we generalize to a list of results:

type Parser = String → [(Tree,String)]

Page 26: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

26

Finally, a parser might not always produce a tree, so we generalize to a value of any type:

data Parser a = P (String → [(a,String)])

Note:

❚  For simplicity, we will only consider parsers that either fail and return the empty list of results, or succeed and return a singleton list.

Page 27: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

27

Basic Parsers

❚  The parser item fails if the input is empty, and consumes the first character otherwise:

item :: Parser Char

item = P (λinp → case inp of

[] → []

(x:xs) → [(x,xs)])

String → [(Char,String)]

Page 28: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

28

❚  The parser failure always fails:

failure :: Parser a

failure = P (λinp → [])

❚  The parser return v always succeeds, returning the value v without consuming any input:

return :: a → Parser a

return v = P (λinp → [(v,inp)])

Page 29: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

29

❚  The parser (p +++ q) behaves as the parser p if it succeeds, and as the parser q otherwise:

(+++) :: Parser a → Parser a → Parser a

p +++ q = P(λinp → case p inp of

[] → parse q inp

[(v,out)] → [(v,out)])

❚  The function parse applies a parser to a string:

parse :: Parser a → String → [(a,String)]

parse (P p) inp = p inp

Page 30: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

30

Examples

% ghci Parsing > parse item "" [] > parse item "abc" [('a',"bc")]

The behavior of the five parsing primitives can be illustrated with some simple examples:

Page 31: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

31

> parse failure "abc"

[]

> parse (return 1) "abc"

[(1,"abc")]

> parse (item +++ return 'd') "abc"

[('a',"bc")]

> parse (failure +++ return 'd') "abc"

[('d',"abc")]

Page 32: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

32

Note:

❚  The library file Parsing is available on the web from the course home page.

❚  The Parser type is a monad, a mathematical structure that has proved useful for modeling many different kinds of computations.

Page 33: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

33

A sequence of parsers can be combined as a single composite parser using the keyword do. For example:

Sequencing

p :: Parser (Char,Char)

p = do x ← item

item

y ← item

return (x,y)

Page 34: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

34

Note:

❚  Each parser must begin in precisely the same column. That is, the layout rule applies.

❚  The values returned by intermediate parsers are discarded by default, but if required can be named using the ← operator.

❚  The value returned by the last parser is the value returned by the sequence as a whole.

Page 35: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

35

❚  If any parser in a sequence of parsers fails, then the sequence as a whole fails. For example:

> parse p "abcdef" [((’a’,’c’),"def")] > parse p "ab" []

❚  The do notation is not specific to the Parser type, but can be used with any monadic type.

Page 36: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

36

Derived Primitives

sat :: (Char → Bool) → Parser Char

sat p = do x ← item

if p x then

return x

else

failure

❚  Parsing a character that satisfies a predicate:

Page 37: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

37

digit :: Parser Char

digit = sat isDigit

char :: Char → Parser Char

char x = sat (x ==)

❚  Parsing a digit and specific characters:

❚  Applying a parser zero or more times:

many :: Parser a → Parser [a]

many p = many1 p +++ return []

Page 38: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

38

many1 :: Parser a -> Parser [a] many1 p = do v ← p vs ← many p return (v:vs)

❚  Applying a parser one or more times:

❚  Parsing a specific string of characters:

string :: String → Parser String string [] = return [] string (x:xs) = do char x string xs return (x:xs)

Page 39: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

39

Example

We can now define a parser that consumes a list of one or more digits from a string:

p :: Parser String p = do char '[' d ← digit ds ← many (do char ',' digit) char ']' return (d:ds)

Page 40: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

40

For example:

> parse p "[1,2,3,4]"

[("1234","")]

> parse p "[1,2,3,4"

[]

Note:

❚  More sophisticated parsing libraries can indicate and/or recover from errors in the input string.

Page 41: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

41

Review: from Parsing.lhs

> sat :: (Char -> Bool) -> Parser Char > sat p = do x <- item > if p x then return x else failure > > digit :: Parser Char > digit = sat isDigit > > lower :: Parser Char > lower = sat isLower

Page 42: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

42

> ident :: Parser String > ident = do x <- lower > xs <- many alphanum > return (x:xs)

Page 43: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

43

Example: ExpParser.hs*

module ExpParser where import Parsing data Op = Plus | Minus | Times | Div deriving Show data Exp = Const Int | Aexp Op Exp Exp deriving Show

* Available at the course website

“deriving Show” means automatically define the instance

Hutton’s Parsing library; also at the course website

Page 44: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

44

Parsing Ops and Consts parseOp = do isym <- (symbol "+" +++ symbol "-" +++ symbol "*" +++ symbol "/”) return (tr isym) where tr "+" = Plus tr "-" = Minus tr "*" = Times tr "/" = Div parseConst = do i <- integer return (Const i)

*Red = defined in Parser.lhs

Page 45: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

45

Running Parsers

ExpParser> parse parseOp "*" [(Times,"")] ExpParser> :t parse parseConst "99" parse parseConst "99" :: [(Exp,String)] ExpParser> parse parseConst "99" [(Const 99,"")]

Page 46: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

46

Parsing Aexps and Exp

parseAexp = do symbol "(" op <- parseOp space e1 <- parseExp space e2 <- parseExp symbol ")" return (Aexp op e1 e2) parseExp = parseConst +++ parseAexp

Page 47: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

47

Parsing Exps

ExpParser> parse parseExp "(+ 1 2)" [(Aexp Plus (Const 1) (Const 2),"")] ExpParser> parse parseExp "99" [(Const 99,"")]

N.b., SimpleExpParser assumes infix expressions, unlike above

Page 48: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

48

Arithmetic Expressions

Consider a simple form of expressions built up from single digits using the operations of addition + and multiplication *, together with parentheses. We also assume that:

❚  * and + associate to the right;

❚  * has higher priority than +.

Page 49: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

49

Formally, the syntax of such expressions is defined by the following context free grammar:

expr → term '+' expr ⏐ term

term → factor '*' term ⏐ factor

factor → digit ⏐ '(' expr ')‘

digit → '0' ⏐ '1' ⏐ … ⏐ '9'

Page 50: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

50

However, for reasons of efficiency, one might factorise the rules for expr and term:

expr → term ('+' expr ⏐ ε)

term → factor ('*' term ⏐ ε)

Note:

❚  The symbol ε denotes the empty string.

Page 51: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

51

It is now easy to translate the grammar into a parser that evaluates expressions, by simply rewriting the grammar rules using the parsing primitives. That is, we will define:

expr :: Parser Int

expr = …

term :: Parser Int

term = …

factor :: Parser Int

factor = …

Page 52: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

52

It is now easy to translate the grammar into a parser that evaluates expressions, by simply rewriting the grammar rules using the parsing primitives. That is, we have:

expr :: Parser Int

expr = do t ← term

(do char '+'

e ← expr

return (t + e))

+++ return t

expr → term ('+' expr ⏐ ε)

Page 53: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

53

factor :: Parser Int factor = (do d ← digit return (digitToInt d)) +++ (do char '(' e ← expr char ')' return e)

term :: Parser Int term = do f ← factor (do char '*' t ← term return (f * t)) +++ (return f)

factor → digit ⏐ '(' expr ')‘

term → factor ('*' term ⏐ ε)

Page 54: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

54

Finally, if we define

eval :: String → Int

eval xs = fst (head (parse expr xs))

then we try out some examples:

> eval "2*3+4"

10

> eval "2*(3+4)"

14

Page 55: Parsing Functionally - harrisonwl.github.io the program structure in this stream? ... expression providing enough information to choose ... Those who know Lex/Flex and Yacc/Bison will

55

Exercises

(2) Extend the expression parser to allow the use of subtraction and division, based upon the following extensions to the grammar:

expr → term ('+' expr ⏐ '-' expr ⏐ ε)

term → factor ('*' term ⏐ '/' term ⏐ ε)

(1) Why does factorising the expression grammar make the resulting parser more efficient?


Recommended