Skip to content

Commit e48d07a

Browse files
committed
except handling for alex lexer
1 parent 534f229 commit e48d07a

File tree

6 files changed

+56
-51
lines changed

6 files changed

+56
-51
lines changed

008_extended_parser.md

+32-17
Original file line numberDiff line numberDiff line change
@@ -193,7 +193,11 @@ tokens :-
193193
Happy
194194
-----
195195

196-
We'll parse into a small untyped lambda calculus for our frontend language.
196+
Using Happy and our previosly defind lexer we'll write down the production rules
197+
for our simple untyped lambda calculus.
198+
199+
We start by defining a ``Syntax`` module where we define the AST we'll generate
200+
from running over the token stream to produce the program graph structure.
197201

198202
```haskell
199203
module Syntax where
@@ -243,7 +247,9 @@ production rules.
243247
```
244248

245249
The parser itself will live inside of a custom monad of our choosing. In this
246-
simple case we'll just add error handling with the ``Except`` monad.
250+
case we'll add error handling with the ``Except`` monad that will break out of
251+
the parsing process if an invalid production or token is found and return a
252+
``Left`` value which we'll handle inside of our toplevel logic.
247253

248254
```haskell
249255
-- Parser monad
@@ -252,8 +258,15 @@ simple case we'll just add error handling with the ``Except`` monad.
252258
```
253259

254260
And finally our production rules, the toplevel entry point for our parser will
255-
be the ``expr`` rule. Notice how naturally we can write a left recursive
256-
grammar for our infix operators.
261+
be the ``expr`` rule. The left hand side of the production is a Happy production
262+
rule which can be mutually recursive, while the right hand side is a Haskell
263+
expression with several metavariable indicated by the dollar sign variables that
264+
map to the nth expression on the left hand side.
265+
266+
```
267+
$0 $1 $2 $3 $4 $5
268+
let VAR '=' Expr in Expr { App (Lam $2 $6) $4 }
269+
```
257270

258271
```haskell
259272
-- Entry point
@@ -283,6 +296,9 @@ Atom : '(' Expr ')' { $2 }
283296
| false { Lit (LBool False) }
284297
```
285298

299+
Notice how naturally we can write a left recursive grammar for our binary infix
300+
operators.
301+
286302
Syntax Errors
287303
-------------
288304

@@ -324,7 +340,7 @@ Type Error Provenance
324340

325341
Before our type inference engine would generate somewhat typical type inference
326342
error messages. If two terms couldn't be unified it simply told us this and some
327-
information about the toplevel declaration where it occurred, leaving us with a
343+
information about the top-level declaration where it occurred, leaving us with a
328344
bit of a riddle about how exactly this error came to be.
329345

330346
```haskell
@@ -337,14 +353,13 @@ in the definition of 'foo'
337353

338354
Effective error reporting in the presence of type inference is a difficult task,
339355
effectively our typechecker takes our frontend AST and transforms it into a
340-
large constraint problem, destroying position
341-
information in the process. Even if the position information were tracked, the
342-
nature of unification is that a cascade of several unifications can lead to
343-
unsolvability and the immediate two syntactic constructs that gave rise to a
344-
unification failure are not necessarily the two that map back to human intuition
345-
about how the type error arose. Very little research has done on this topic and
346-
it remains an open topic with very immediate and applicable results to
347-
programming.
356+
large constraint problem, destroying position information in the process. Even
357+
if the position information were tracked, the nature of unification is that
358+
a cascade of several unifications can lead to unsolvability and the immediate
359+
two syntactic constructs that gave rise to a unification failure are not
360+
necessarily the two that map back to human intuition about how the type error
361+
arose. Very little research has done on this topic and it remains an open
362+
topic with very immediate and applicable results to programming.
348363

349364
To do simple provenance tracking we will use a technique of tracking the "flow"
350365
of type information through our typechecker and associate position information
@@ -473,10 +488,10 @@ with
473488
let f x y = x y
474489
```
475490

476-
This is of course the simplest implementation of the tracking method and
477-
could be further extended by giving a weighted ordering to the constraints
478-
based on their likelihood of importance and proximity and then choosing which
479-
location to report based on this information. This remains an open area of work.
491+
This is of course the simplest implementation of the tracking method and could
492+
be further extended by giving a weighted ordering to the constraints based on
493+
their likelihood of importance and proximity and then choosing which location to
494+
report based on this information. This remains an open area of work.
480495

481496
Indentation
482497
-----------

chapter9/happy/Eval.hs

+8-7
Original file line numberDiff line numberDiff line change
@@ -34,13 +34,14 @@ eval env expr = case expr of
3434
Op op a b -> do
3535
x <- eval env a
3636
y <- eval env b
37-
return $ binop op x y
38-
39-
binop :: Binop -> Value -> Value -> Value
40-
binop Add (VInt a) (VInt b) = VInt (a+b)
41-
binop Sub (VInt a) (VInt b) = VInt (a-b)
42-
binop Mul (VInt a) (VInt b) = VInt (a*b)
43-
binop Eql (VInt a) (VInt b) = VBool (a==b)
37+
binop op x y
38+
39+
binop :: Binop -> Value -> Value -> Eval Value
40+
binop Add (VInt a) (VInt b) = return $ VInt (a+b)
41+
binop Sub (VInt a) (VInt b) = return $ VInt (a-b)
42+
binop Mul (VInt a) (VInt b) = return $ VInt (a*b)
43+
binop Eql (VInt a) (VInt b) = return $ VBool (a==b)
44+
binop _ _ _ = throwError "Tried to do arithmetic operation over non-number"
4445

4546
extend :: Scope -> String -> Value -> Scope
4647
extend env v t = Map.insert v t env

chapter9/happy/LICENSE

-19
This file was deleted.

chapter9/happy/Lexer.x

+11-2
Original file line numberDiff line numberDiff line change
@@ -61,7 +61,16 @@ data Token
6161
| TokenEOF
6262
deriving (Eq,Show)
6363

64-
scanTokens :: String -> [Token]
65-
scanTokens = alexScanTokens
64+
scanTokens :: String -> Except String [Token]
65+
scanTokens str = go ('\n',[],str) where
66+
go inp@(_,_bs,str) =
67+
case alexScan inp 0 of
68+
AlexEOF -> return []
69+
AlexError _ -> throwError "Invalid lexeme."
70+
AlexSkip inp' len -> go inp'
71+
AlexToken inp' len act -> do
72+
res <- go inp'
73+
let rest = act (take len str)
74+
return (rest : res)
6675

6776
}

chapter9/happy/Parser.y

+5-5
Original file line numberDiff line numberDiff line change
@@ -73,11 +73,11 @@ parseError (l:ls) = throwError (show l)
7373
parseError [] = throwError "Unexpected end of Input"
7474

7575
parseExpr :: String -> Either String Expr
76-
parseExpr input =
77-
let tokenStream = scanTokens input in
78-
runExcept (expr tokenStream)
76+
parseExpr input = runExcept $ do
77+
tokenStream <- scanTokens input
78+
expr tokenStream
7979

80-
parseTokens :: String -> [Token]
81-
parseTokens = scanTokens
80+
parseTokens :: String -> Either String [Token]
81+
parseTokens = runExcept . scanTokens
8282

8383
}

chapter9/happy/happyParser.cabal

-1
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,6 @@
11
name: happyParser
22
version: 0.1.0.0
33
license: MIT
4-
license-file: LICENSE
54
author: Stephen Diehl
65
maintainer: stephen.m.diehl@gmail.com
76
build-type: Simple

0 commit comments

Comments
 (0)