Presentation is loading. Please wait.

Presentation is loading. Please wait.

Workshop: Towards Highly Portable Software Jakarta, 21 – 23 January 2003 Diselenggarakan oleh Universitas IndonesiaUniversitas Indonesia Part 1 : Programming.

Similar presentations


Presentation on theme: "Workshop: Towards Highly Portable Software Jakarta, 21 – 23 January 2003 Diselenggarakan oleh Universitas IndonesiaUniversitas Indonesia Part 1 : Programming."— Presentation transcript:

1 Workshop: Towards Highly Portable Software Jakarta, 21 – 23 January 2003 Diselenggarakan oleh Universitas IndonesiaUniversitas Indonesia Part 1 : Programming and Abstraction Dr. Ir. I.S.W.B. Prasetyawishnu@cs.uu.nl A. Azurat S.Kom.ade@cs.uu.nl Lecture 2: Grammar and Parsing

2 2 Transformation Transformation: Transforming one form of structured information to another form. Any kind of information processing is transformation. Information with complicated structure: program, specification, formula Example of applications : –compiler, interpreter, translator –HTML tool –Y2K tool –Oracle code generator

3 3 Describing structure Example: 1.27601 e -10 Grammar : SignedFloat  Sign Float | Float Float  Pdigit. Pint e SignedExp SignedExpr  Sign Pint | Pint Pdigit  1 | 2 | 3 | 4 | 5 | 6 | 7 | 8 | 9 Pint  Digit | Digit Pint Digit  0 | Pdigit

4 4 Terminology Float  Pdigit. Pint e SignedExp This is called a production rule A grammar is a collection of a production rules. A grammar is context free (CGF) if the left hand side of all its rules consists of only one non-termimal. Non-terminal symbol Terminal symbols

5 5 Deriving sentences P   | APA | BPB | CPC A  a B  b C  c with start P as the symbol. A sentence s is a sentence of G, if it can be derived from the start symbol of G. Example: P   P  APA  AA ...  aa P  APA  ABPBA ...  abba

6 6 Language P   | APA | BPB | CPC A  a B  b C  c with start P as the symbol. L(G) = the set of all (terminal) sentences of G Example: for the above grammar L(G) = the set of all even length palindromes over {a,b,c}

7 7 Bigger Example Program  Identifier (ParameterList) Decl Body ParameterList  Parameter | Parameter, ParameterList Parameter  Identifier : Type... Body  { Statement } Statement  skip | Assignment |... Assignment  Identifier := Expression...

8 8 Transformation sentence transformation result "abba" P A P A P B B a a b b parse tree parser semantic function

9 9 Parse Tree Program Identifier ( ) ParameterList Decl Body x*y+1 Statement Assignment Identifier Expression poo x:int,y:int { } x :=

10 10 Representing Parse Tree data Pal = Empty | A Pal | B Pal | C Pal Example: A (B (A Empty)) represents abaaba

11 11 Representing Parse Tree Form  Form /\ Form | Form \/ Form | Form ==> Form | ~ Form | Var | Const Var ... Const  T | F

12 12 Representing Parse Tree a b a b \/ ~ ==> Expr Var Expr

13 13 Representing Parse Tree data Form = Form `AND` Form | Form `OR` Form | Form `IMP` Form | NOT Form | Var String | Const Bool Example: (Var "a" `OR` Var "b") `IMP` Var "a" Notice also similarty between data type definition and CFG.

14 14 Semantic Function Example: simple tautology checker (a /\ T) \/ ~a  taulogy we won't do this (a /\ F) ==> ~a  taulogy Represent result with Maybe Bool data Maybe a = Just a | nothing staut :: Form -> Maybe Bool

15 15 Semantic Function staut (Var a)= Nothing staut (Const c)= Just c staut (p `AND` q)= case (staut p, staut q) of (Just False, _) -> Just False (_, Just False) -> Just False (Just True, Just True) -> Just True otherwise -> Nothing

16 16 Semantic Function Anopther example: (simple) simplifier (a \/ T) /\ ~a  ~a simp :: Form -> Form

17 17 Semantic Function simp (Var a)= Var a simp (Const c)= Const c simp (p `AND` q)= case (simp p, simp q) of (Const False, _) -> Const False (_, Const False) -> Const False (Const True, q') -> q' (p', Const True)-> p' otherwise -> Nothing

18 18 Parser Parser: Take a string, and tries to build a parse tree. For our example grammar of formula: parser :: String -> Form –type Parser result = String -> result –type Parser result = String -> (result,String) –type Parser result = String -> [(result,String)] –type Parser sym res= [sym] -> [(res,[sym])]

19 19 Several Primitive Parsers symbol :: Eq s => s -> Parser s s symbol a [ ] = [ ] symbol a (x : xs) | x == a = [(x,xs)] | otherwise = [ ] Example: symbol 'C' :: Parser Char Char symbol 'C' "CLASS" = [('C', "LASS")]

20 20 Several Primitive Parsers satisfy :: (s -> Bool) -> Parser s s satisfy p [ ] = [ ] satisfy p (x : xs) | p x = [(x,xs)] | otherwise = [ ] Example: satisfy isDigit :: Parser Char Char satisfy isDigit "100" = [('1', "00")]

21 21 Several Primitive Parsers token :: Eq s => [s] -> Parser s [s] Example: token "class" "class A { } " = [("class", " A { } ")] token "class" "cla <= 0"= [ ]

22 22 Several Primitive Parsers failp :: Parser s a failp xs = [ ] succeed :: a -> Parser s a succeed r xs = [(r,xs)]

23 23 Parser Combinators ( ) :: Parser s a -> Parser s a -> Parser s a (p q) xs = p xs ++ q xs Example: pSign = symbol '+' symbol '-'

24 24 Parser Combinators ( ) :: Parser s (b -> a) -> Parser s b -> Parser s a (p q) xs = [ (f x, zs) | (f,ys) <- p xs, ( x, zs) <- q ys ] Example: (pSign succeed '+') satisfy isDigit symbol '.' pDigits

25 25 Parser Combinators ( ) :: (a -> b) -> Parser s a -> Parser s b (f p) xs = [ (f y, ys) | (y, ys) <- p xs ] Example: p = f satisfy isDigit where f :: String -> Int f c = read [c]

26 26 Priority and Associativity pDigits :: Parser Char String pDigits = pDigit ( (f pDigit) pDigits) where f digit = (\theRest -> digit : theRest) f digit theRest = digit : theRest or.... f is simply (:)

27 27 Priority and Associativity infixl 7 infixl 6 infixr 4 pDigits = pDigit (:) pDigit pDigits pDigits = read (pDigit (:) pDigit pDigits)

28 28 Example pIdentifier = (:) satisfy isLower pIdentifier sing satisfy isLower pVar :: Parser Char Form pVar = Var pIdentifier

29 29 Example pConst = mk_True symbol 'T' mk_False token 'F' where mk_True s = Const True mk_False s = Const False

30 30 Example pForm = mk_And pForm token "/\" pForm pVar pConst... left recursive!!

31 31 Removing Left Recursion Form  Atom /\ Form | Atom \/ Form | Atom ==> Form | ~ Form Atom  | Var | Const Var ... Const  T | F

32 32 Example pForm = mk_And pAtom token "/\" pForm... pAtom = pVar pConst where mk_And a _ f = a `AND` f

33 33 Greed pDigits = pDigit (:) pDigit pDigits Example: pDigit "123" = [("1","23"), ("12","3"), ("123", "") ] pDigits = (:) pDigit pDigits pDigit Example: pDigit "123" = [("123",""), ("12","3"), ("1", "23") ]

34 34 list x s = x : s Many many :: Parser s a -> Parser s [a] many p = list p many p succeed [ ] many1 :: Parser s a -> Parser s [a] many1 p = list p many p

35 35 Greedy greedy, greedy1 :: Parser s b -> Parser s [b] greedy = first. many greedy1 = first. many1 Example: pDigits = many1 (satisfy isDigit) pDigits = greedy1 (satisfy isDigit)


Download ppt "Workshop: Towards Highly Portable Software Jakarta, 21 – 23 January 2003 Diselenggarakan oleh Universitas IndonesiaUniversitas Indonesia Part 1 : Programming."

Similar presentations


Ads by Google