Skip to content
GitLab
Menu
Projects
Groups
Snippets
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in
Toggle navigation
Menu
Open sidebar
Jeanne-Marie Musca
gg-proto
Commits
4b00dde6
Commit
4b00dde6
authored
Feb 24, 2016
by
matthew-eads
Browse files
first commit
parents
Changes
7
Expand all
Hide whitespace changes
Inline
Side-by-side
AST
0 → 100755
View file @
4b00dde6
File added
AST.hs
0 → 100644
View file @
4b00dde6
This diff is collapsed.
Click to expand it.
AST.y
0 → 100644
View file @
4b00dde6
{
module Main where
}
%name grammar
%tokentype { Token }
%token
int { TokenInt }
id { TokenID $$ }
binop { TokenBinop }
set { TokenSet }
if { TokenIf}
while { TokenWhile }
begin { TokenBegin }
var { TokenVar }
userdef { TokenUserDef }
builtin { TokenBuiltin }
custom { TokenCustom }
string { TokenString $$ }
eof { TokenEOF }
nl { TokenNL }
line { TokenLine $$ }
%error {parseError}
%%
Prog: Grammar Prog { $1:$2 }
| nl Prog { $2 }
| eof {[]}
Grammar: set nl { SET }
| if nl { IF }
| while nl { WHILE }
| begin nl { BEGIN }
| var nl { VAR }
| userdef { USERDEF }
| int { INT }
| binop string nl { BINOP $2 }
| builtin id string nl { BUILTIN $2 $3 }
| custom id line { CUSTOM $2 $3 }
ID : id { $1 }
String : string { $1 }
{
parseError :: [Token] -> a
parseError t = error ("Parse Error on token(s) " ++ (show t))
data Grammar = SET
| IF
| WHILE
| BEGIN
| VAR
| USERDEF
| INT
| BINOP String
| BUILTIN String String
| CUSTOM String String
deriving Show
type Prog = [Grammar]
type ID = String
--type _String = String
data Token = TokenBinop
| TokenID String
| TokenSet
| TokenIf
| TokenWhile
| TokenBegin
| TokenInt
| TokenVar
| TokenUserDef
| TokenBuiltin
| TokenCustom
| TokenString String
| TokenEOF
| TokenNL
| TokenLine String
deriving (Eq, Show)
data State = Ignore | Gdef | Line
lexer :: String -> [Token] -> State -> [Token]
lexer ('-':'-':'>':rest) acc Ignore = lexer rest acc Gdef
lexer ('b':'i':'n':'o':'p':rest) acc Gdef = lexer rest (TokenBinop:acc) Gdef
lexer ('s':'e':'t':rest) acc Gdef = lexer rest (TokenSet:acc) Gdef
lexer ('i':'f':rest) acc Gdef = lexer rest (TokenIf:acc) Gdef
lexer ('w':'h':'i':'l':'e':rest) acc Gdef = lexer rest (TokenWhile:acc) Gdef
lexer ('b':'e':'g':'i':'n':rest) acc Gdef = lexer rest (TokenBegin:acc) Gdef
lexer ('i':'n':'t':rest) acc Gdef = lexer rest (TokenInt:acc) Gdef
lexer ('v':'a':'r':rest) acc Gdef = lexer rest (TokenVar:acc) Gdef
lexer ('u':'s':'e':'r':'d':'e':'f':rest) acc Gdef = lexer rest (TokenUserDef:acc) Gdef
lexer ('b':'u':'i':'l':'t':'i':'n':rest) acc Gdef = lexer rest (TokenBuiltin:acc) Gdef
lexer ('c':'u':'s':'t':'o':'m':rest) acc Gdef = lexer rest (TokenCustom:acc) Line
lexer ('"':rest) acc Gdef =
let str = takeWhile (\c -> c /= '"') rest
rst = tail (dropWhile (\c -> c /= '"') rest)
in lexer rst ((TokenString str):acc) Gdef
lexer (' ':rest) acc Gdef = lexer rest acc Gdef
lexer ('\t':rest) acc Gdef = lexer rest acc Gdef
lexer ('\n':rest) acc Gdef = lexer rest (TokenNL:acc) Ignore
lexer ('\r':rest) acc Gdef = lexer rest (TokenNL:acc) Ignore
lexer s acc Gdef =
let str = takeWhile (\c -> (c /= ' ') && (c /= '\n')) s
rest = tail (dropWhile (\c -> (c /= ' ') && (c /= '\n')) s)
in lexer rest ((TokenID str):acc) Gdef
lexer s acc Line =
let s' = (dropWhile (\c -> c == ' ')) s
(id, s'') = ((takeWhile (\c -> (c /= ' ') && (c /= '\n')) s'),
(dropWhile (\c -> (c /= ' ') && (c /= '\n')) s'))
str = takeWhile (\c -> (c /= '\n') && (c /= '\r')) s''
rest = tail (dropWhile (\c -> (c /= '\n') && (c /= '\r')) s'')
in lexer rest ((TokenLine str):(TokenID id):acc) Ignore
lexer (x:s) acc Ignore = lexer s acc Ignore
lexer [] acc Ignore = reverse (TokenEOF:acc)
writeHeader :: IO ()
writeHeader = do {
putStr ("{\nmodule Main where\n\nimport Lexer\n}\n" ++
"%name imp\n%tokentype { Token }\n%token \n" ++
"if { TokenIf }\nwhile { TokenWhile }\n" ++
"begin { TokenBegin }\nset { TokenSet }\n" ++
"'+' { TokenSym $$ }\n'-' { TokenSym $$ }\n" ++
"'/' { TokenSym $$ }\n'*' { TokenSym $$ }\n" ++
"'(' { TokenLParen }\n')' { TokenRParen }\n" ++
"int { TokenInt $$ }\nvar { TokenVar $$ }\n" ++
"'@' { TokenSym $$ }\n'!' { TokenSym $$ }\n'$' { TokenSym $$ }\n'%' { TokenSym $$ }\n'^' { TokenSym $$ }\n'&' { TokenSym $$ }\n'_' { TokenSym $$ }\n'`' { TokenSym $$ }\n'~' { TokenSym $$ }\n'=' { TokenSym $$ }\n'[' { TokenSym $$ }\n']' { TokenSym $$ }\n'{' { TokenSym $$ }\n'}' { TokenSym $$ }\n':' { TokenSym $$ }\n';' { TokenSym $$ }\n'<' { TokenSym $$ }\n'>' { TokenSym $$ }\n" ++
"%error {parseError}\n%%\n\n" ++
"Prog: AST Prog { $1:$2 }\n\t| AST { [$1] }\n\n" ++
"AST: ");
}
writeFooter :: IO ()
writeFooter = do {
putStr("\nMultiExpr : AST MultiExpr {$1:$2}\n | AST {[$1]}\n\n{\n\nparseError :: [Token] -> a\nparseError t = error (\"Parse Error on token \" ++ (show t))\nhappyError = parseError\n\ndata AST = Lit Int\n | Id String\n | Builtin String [AST]\n | UserDef String [AST]\n | IfThenElse AST AST AST\n | While AST AST\n | Do [AST]\n deriving Show\n\ntype MultiExpr = [AST]\n\ntype Prog = [AST]\n\n\nmain = do {\n s <- getContents;\n putStrLn (show (imp (alexScanTokens s)));\n}\n");}
ruleToString :: Grammar -> String
ruleToString SET =" | '(' set var AST ')' {Builtin \"set\" [(Id $3), $4]}\n"
ruleToString IF = " | '(' if AST AST AST ')' {IfThenElse $3 $4 $5}\n"
ruleToString WHILE = " | '(' while AST AST ')' {While $3 $4}\n"
ruleToString BEGIN = " | '(' begin MultiExpr ')' {Builtin \"begin\" $3}\n"
ruleToString VAR = " | var { Id $1 }\n"
ruleToString INT = " | int { Lit $1 }\n"
ruleToString USERDEF = " | '(' var MultiExpr ')' {UserDef $2 $3}\n"
ruleToString (BINOP s) = " | '(' '" ++ s ++ "' AST AST ')' {Builtin $2 [$3, $4]}\n"
ruleToString (BUILTIN s1 s2) = " | '(' " ++ s2 ++ " MultiExp ')' { Builtin \"" ++ s2 ++ "\" $3}\n"
ruleToString (CUSTOM s1 s2) = undefined
printFirstRule :: Grammar -> String
printFirstRule g = let str = ruleToString g
in tail (dropWhile (\c -> (c == ' ')) str)
makeParser :: [Grammar] -> IO ()
makeParser g = do {
writeHeader;
putStrLn (printFirstRule (head g));
putStr (foldl (++) [] (map ruleToString (tail g)));
writeFooter;
}
main = do {
s <- getContents;
let tokes = lexer s [] Ignore
gram = grammar tokes in
do {
-- putStrLn ("tokes: " ++ (show tokes));
-- putStrLn ("\n\ngrammar" ++ (show gram));
-- putStr "\n\n";
makeParser gram;
}
}
}
Imp.ast
0 → 100644
View file @
4b00dde6
module AST where
type ID = String
data AST = Expression Exp AST
| TopLevlDec Dec AST
data Exp = SET ID Exp --> set
| IF SimpleExp Exp Exp --> if
| WHILE SimpleExp Exp --> while
| BEGIN [Exp] --> begin
| SimpleExp SimpleExp
data BinOp = Plus SimpleExp SimpleExp --> binop "+"
| Mult SimpleExp SimpleExp --> binop "*"
| Div SimpleExp SimpleExp --> binop "/"
| Minus SimpleExp SimpleExp --> binop "-"
| CheckExpect SimpleExp SimpleExp --> binop "check-expect"
data SimpleExp =
Lit Int --> int
| Var ID --> var
| Apply ID [SimpleExp] --> userdef
| BinOp BinOp
| AGet SimpleExp SimpleExp -- > custom Aget AST "[" AST "]"
--(arr[i])
| ASet SimpleExp SimpleExp SimpleExp -- > custom Aset "set" AST "[" AST "]" AST
--(set arr[i] j)
| AMake ID SimpleExp --> builtin Amake "new"
--(new arr size)
data Dec = Val ID Exp
Lexer.hs
0 → 100644
View file @
4b00dde6
{-# OPTIONS_GHC -fno-warn-unused-binds -fno-warn-missing-signatures #-}
{-# LANGUAGE CPP #-}
{-# LINE 1 "Lexer.x" #-}
module
Lexer
where
#
if
__GLASGOW_HASKELL__
>=
603
#
include
"ghcconfig.h"
#
elif
defined
(
__GLASGOW_HASKELL__
)
#
include
"config.h"
#
endif
#
if
__GLASGOW_HASKELL__
>=
503
import
Data.Array
import
Data.Array.Base
(
unsafeAt
)
#
else
import
Array
#
endif
{-# LINE 1 "templates/wrappers.hs" #-}
{-# LINE 1 "templates/wrappers.hs" #-}
{-# LINE 1 "<built-in>" #-}
{-# LINE 1 "<command-line>" #-}
#
1
"/usr/include/stdc-predef.h"
1
3
4
#
17
"/usr/include/stdc-predef.h"
3
4
{-# LINE 6 "<command-line>" #-}
{-# LINE 1 "templates/wrappers.hs" #-}
-- -----------------------------------------------------------------------------
-- Alex wrapper code.
--
-- This code is in the PUBLIC DOMAIN; you may copy it freely and use
-- it for any purpose whatsoever.
import
Data.Word
(
Word8
)
{-# LINE 28 "templates/wrappers.hs" #-}
import
Data.Char
(
ord
)
import
qualified
Data.Bits
-- | Encode a Haskell String to a list of Word8 values, in UTF8 format.
utf8Encode
::
Char
->
[
Word8
]
utf8Encode
=
map
fromIntegral
.
go
.
ord
where
go
oc
|
oc
<=
0x7f
=
[
oc
]
|
oc
<=
0x7ff
=
[
0xc0
+
(
oc
`
Data
.
Bits
.
shiftR
`
6
)
,
0x80
+
oc
Data
.
Bits
..&.
0x3f
]
|
oc
<=
0xffff
=
[
0xe0
+
(
oc
`
Data
.
Bits
.
shiftR
`
12
)
,
0x80
+
((
oc
`
Data
.
Bits
.
shiftR
`
6
)
Data
.
Bits
..&.
0x3f
)
,
0x80
+
oc
Data
.
Bits
..&.
0x3f
]
|
otherwise
=
[
0xf0
+
(
oc
`
Data
.
Bits
.
shiftR
`
18
)
,
0x80
+
((
oc
`
Data
.
Bits
.
shiftR
`
12
)
Data
.
Bits
..&.
0x3f
)
,
0x80
+
((
oc
`
Data
.
Bits
.
shiftR
`
6
)
Data
.
Bits
..&.
0x3f
)
,
0x80
+
oc
Data
.
Bits
..&.
0x3f
]
type
Byte
=
Word8
-- -----------------------------------------------------------------------------
-- The input type
{-# LINE 79 "templates/wrappers.hs" #-}
{-# LINE 101 "templates/wrappers.hs" #-}
{-# LINE 119 "templates/wrappers.hs" #-}
{-# LINE 137 "templates/wrappers.hs" #-}
-- -----------------------------------------------------------------------------
-- Token positions
-- `Posn' records the location of a token in the input text. It has three
-- fields: the address (number of chacaters preceding the token), line number
-- and column of a token within the file. `start_pos' gives the position of the
-- start of the file and `eof_pos' a standard encoding for the end of file.
-- `move_pos' calculates the new position after traversing a given character,
-- assuming the usual eight character tab stops.
{-# LINE 160 "templates/wrappers.hs" #-}
-- -----------------------------------------------------------------------------
-- Default monad
{-# LINE 271 "templates/wrappers.hs" #-}
-- -----------------------------------------------------------------------------
-- Monad (with ByteString input)
{-# LINE 374 "templates/wrappers.hs" #-}
-- -----------------------------------------------------------------------------
-- Basic wrapper
type
AlexInput
=
(
Char
,[
Byte
],
String
)
alexInputPrevChar
::
AlexInput
->
Char
alexInputPrevChar
(
c
,
_
,
_
)
=
c
-- alexScanTokens :: String -> [token]
alexScanTokens
str
=
go
(
'
\n
'
,
[]
,
str
)
where
go
inp
@
(
_
,
_bs
,
s
)
=
case
alexScan
inp
0
of
AlexEOF
->
[]
AlexError
_
->
error
"lexical error"
AlexSkip
inp'
len
->
go
inp'
AlexToken
inp'
len
act
->
act
(
take
len
s
)
:
go
inp'
alexGetByte
::
AlexInput
->
Maybe
(
Byte
,
AlexInput
)
alexGetByte
(
c
,(
b
:
bs
),
s
)
=
Just
(
b
,(
c
,
bs
,
s
))
alexGetByte
(
c
,
[]
,
[]
)
=
Nothing
alexGetByte
(
_
,
[]
,(
c
:
s
))
=
case
utf8Encode
c
of
(
b
:
bs
)
->
Just
(
b
,
(
c
,
bs
,
s
))
[]
->
Nothing
-- -----------------------------------------------------------------------------
-- Basic wrapper, ByteString version
{-# LINE 421 "templates/wrappers.hs" #-}
{-# LINE 437 "templates/wrappers.hs" #-}
-- -----------------------------------------------------------------------------
-- Posn wrapper
-- Adds text positions to the basic model.
{-# LINE 454 "templates/wrappers.hs" #-}
-- -----------------------------------------------------------------------------
-- Posn wrapper, ByteString version
{-# LINE 470 "templates/wrappers.hs" #-}
-- -----------------------------------------------------------------------------
-- GScan wrapper
-- For compatibility with previous versions of Alex, and because we can.
alex_tab_size
::
Int
alex_tab_size
=
8
alex_base
::
Array
Int
Int
alex_base
=
listArray
(
0
,
23
)
[
-
8
,
-
3
,
50
,
108
,
166
,
224
,
0
,
-
28
,
-
27
,
0
,
0
,
-
35
,
282
,
340
,
398
,
456
,
514
,
572
,
630
,
688
,
746
,
804
,
862
,
920
]
alex_table
::
Array
Int
Int
alex_table
=
listArray
(
0
,
1175
)
[
0
,
1
,
1
,
1
,
1
,
1
,
1
,
1
,
1
,
1
,
1
,
7
,
7
,
11
,
11
,
11
,
11
,
11
,
11
,
11
,
11
,
11
,
11
,
0
,
1
,
0
,
0
,
0
,
0
,
1
,
0
,
8
,
9
,
10
,
6
,
6
,
0
,
6
,
0
,
6
,
11
,
11
,
11
,
11
,
11
,
11
,
11
,
11
,
11
,
11
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
18
,
17
,
18
,
18
,
18
,
18
,
18
,
18
,
22
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
13
,
18
,
18
,
18
,
19
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
0
,
0
,
0
,
0
,
18
,
0
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
0
,
0
,
0
,
0
,
18
,
0
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
0
,
0
,
0
,
0
,
18
,
0
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
0
,
0
,
0
,
0
,
18
,
0
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
0
,
0
,
0
,
0
,
18
,
0
,
18
,
18
,
18
,
18
,
4
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
0
,
0
,
0
,
0
,
18
,
0
,
18
,
18
,
18
,
18
,
23
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
0
,
0
,
0
,
0
,
18
,
0
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
21
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
0
,
0
,
0
,
0
,
18
,
0
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
20
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
0
,
0
,
0
,
0
,
18
,
0
,
18
,
18
,
18
,
18
,
18
,
18
,
14
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
0
,
0
,
0
,
0
,
18
,
0
,
18
,
18
,
18
,
18
,
16
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
0
,
0
,
0
,
0
,
18
,
0
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
0
,
0
,
0
,
0
,
18
,
0
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
15
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
0
,
0
,
0
,
0
,
18
,
0
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
12
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
0
,
0
,
0
,
0
,
18
,
0
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
5
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
0
,
0
,
0
,
0
,
18
,
0
,
18
,
18
,
18
,
18
,
18
,
3
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
0
,
0
,
0
,
0
,
18
,
0
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
18
,
2
,
18
,
18
,
18
,
18
,
18
,
18
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
,
0
]
alex_check
::
Array
Int
Int
alex_check
=
listArray
(
0
,
1175
)
[
-
1
,
9
,
10
,
11
,
12
,
13
,
9
,
10
,
11
,
12
,
13
,
39
,
39
,
48
,
49
,
50
,
51
,
52
,
53
,
54
,
55
,
56
,
57
,
-
1
,
32
,
-
1
,
-
1
,
-
1
,
-
1
,
32
,
-
1
,
39
,
40
,
41
,
42
,
43
,
-
1
,
45
,
-
1
,
47
,
48
,
49
,
50
,
51
,
52
,
53
,
54
,
55
,
56
,
57
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
97
,
98
,
99
,
100
,
101
,
102
,
103
,
104
,
105
,
106
,
107
,
108
,
109
,
110
,
111
,
112
,
113
,
114
,
115
,
116
,
117
,
118
,
119
,
120
,
121
,
122
,
65
,
66
,
67
,
68
,
69
,
70
,
71
,
72
,
73
,
74
,
75
,
76
,
77
,
78
,
79
,
80
,
81
,
82
,
83
,
84
,
85
,
86
,
87
,
88
,
89
,
90
,
-
1
,
-
1
,
-
1
,
-
1
,
95
,
-
1
,
97
,
98
,
99
,
100
,
101
,
102
,
103
,
104
,
105
,
106
,
107
,
108
,
109
,
110
,
111
,
112
,
113
,
114
,
115
,
116
,
117
,
118
,
119
,
120
,
121
,
122
,
65
,
66
,
67
,
68
,
69
,
70
,
71
,
72
,
73
,
74
,
75
,
76
,
77
,
78
,
79
,
80
,
81
,
82
,
83
,
84
,
85
,
86
,
87
,
88
,
89
,
90
,
-
1
,
-
1
,
-
1
,
-
1
,
95
,
-
1
,
97
,
98
,
99
,
100
,
101
,
102
,
103
,
104
,
105
,
106
,
107
,
108
,
109
,
110
,
111
,
112
,
113
,
114
,
115
,
116
,
117
,
118
,
119
,
120
,
121
,
122
,
65
,
66
,
67
,
68
,
69
,
70
,
71
,
72
,
73
,
74
,
75
,
76
,
77
,
78
,
79
,
80
,
81
,
82
,
83
,
84
,
85
,
86
,
87
,
88
,
89
,
90
,
-
1
,
-
1
,
-
1
,
-
1
,
95
,
-
1
,
97
,
98
,
99
,
100
,
101
,
102
,
103
,
104
,
105
,
106
,
107
,
108
,
109
,
110
,
111
,
112
,
113
,
114
,
115
,
116
,
117
,
118
,
119
,
120
,
121
,
122
,
65
,
66
,
67
,
68
,
69
,
70
,
71
,
72
,
73
,
74
,
75
,
76
,
77
,
78
,
79
,
80
,
81
,
82
,
83
,
84
,
85
,
86
,
87
,
88
,
89
,
90
,
-
1
,
-
1
,
-
1
,
-
1
,
95
,
-
1
,
97
,
98
,
99
,
100
,
101
,
102
,
103
,
104
,
105
,
106
,
107
,
108
,
109
,
110
,
111
,
112
,
113
,
114
,
115
,
116
,
117
,
118
,
119
,
120
,
121
,
122
,
65
,
66
,
67
,
68
,
69
,
70
,
71
,
72
,
73
,
74
,
75
,
76
,
77
,
78
,
79
,
80
,
81
,
82
,
83
,
84
,
85
,
86
,
87
,
88
,
89
,
90
,
-
1
,
-
1
,
-
1
,
-
1
,
95
,
-
1
,
97
,
98
,
99
,
100
,
101
,
102
,
103
,
104
,
105
,
106
,
107
,
108
,
109
,
110
,
111
,
112
,
113
,
114
,
115
,
116
,
117
,
118
,
119
,
120
,
121
,
122
,
65
,
66
,
67
,
68
,
69
,
70
,
71
,
72
,
73
,
74
,
75
,
76
,
77
,
78
,
79
,
80
,
81
,
82
,
83
,
84
,
85
,
86
,
87
,
88
,
89
,
90
,
-
1
,
-
1
,
-
1
,
-
1
,
95
,
-
1
,
97
,
98
,
99
,
100
,
101
,
102
,
103
,
104
,
105
,
106
,
107
,
108
,
109
,
110
,
111
,
112
,
113
,
114
,
115
,
116
,
117
,
118
,
119
,
120
,
121
,
122
,
65
,
66
,
67
,
68
,
69
,
70
,
71
,
72
,
73
,
74
,
75
,
76
,
77
,
78
,
79
,
80
,
81
,
82
,
83
,
84
,
85
,
86
,
87
,
88
,
89
,
90
,
-
1
,
-
1
,
-
1
,
-
1
,
95
,
-
1
,
97
,
98
,
99
,
100
,
101
,
102
,
103
,
104
,
105
,
106
,
107
,
108
,
109
,
110
,
111
,
112
,
113
,
114
,
115
,
116
,
117
,
118
,
119
,
120
,
121
,
122
,
65
,
66
,
67
,
68
,
69
,
70
,
71
,
72
,
73
,
74
,
75
,
76
,
77
,
78
,
79
,
80
,
81
,
82
,
83
,
84
,
85
,
86
,
87
,
88
,
89
,
90
,
-
1
,
-
1
,
-
1
,
-
1
,
95
,
-
1
,
97
,
98
,
99
,
100
,
101
,
102
,
103
,
104
,
105
,
106
,
107
,
108
,
109
,
110
,
111
,
112
,
113
,
114
,
115
,
116
,
117
,
118
,
119
,
120
,
121
,
122
,
65
,
66
,
67
,
68
,
69
,
70
,
71
,
72
,
73
,
74
,
75
,
76
,
77
,
78
,
79
,
80
,
81
,
82
,
83
,
84
,
85
,
86
,
87
,
88
,
89
,
90
,
-
1
,
-
1
,
-
1
,
-
1
,
95
,
-
1
,
97
,
98
,
99
,
100
,
101
,
102
,
103
,
104
,
105
,
106
,
107
,
108
,
109
,
110
,
111
,
112
,
113
,
114
,
115
,
116
,
117
,
118
,
119
,
120
,
121
,
122
,
65
,
66
,
67
,
68
,
69
,
70
,
71
,
72
,
73
,
74
,
75
,
76
,
77
,
78
,
79
,
80
,
81
,
82
,
83
,
84
,
85
,
86
,
87
,
88
,
89
,
90
,
-
1
,
-
1
,
-
1
,
-
1
,
95
,
-
1
,
97
,
98
,
99
,
100
,
101
,
102
,
103
,
104
,
105
,
106
,
107
,
108
,
109
,
110
,
111
,
112
,
113
,
114
,
115
,
116
,
117
,
118
,
119
,
120
,
121
,
122
,
65
,
66
,
67
,
68
,
69
,
70
,
71
,
72
,
73
,
74
,
75
,
76
,
77
,
78
,
79
,
80
,
81
,
82
,
83
,
84
,
85
,
86
,
87
,
88
,
89
,
90
,
-
1
,
-
1
,
-
1
,
-
1
,
95
,
-
1
,
97
,
98
,
99
,
100
,
101
,
102
,
103
,
104
,
105
,
106
,
107
,
108
,
109
,
110
,
111
,
112
,
113
,
114
,
115
,
116
,
117
,
118
,
119
,
120
,
121
,
122
,
65
,
66
,
67
,
68
,
69
,
70
,
71
,
72
,
73
,
74
,
75
,
76
,
77
,
78
,
79
,
80
,
81
,
82
,
83
,
84
,
85
,
86
,
87
,
88
,
89
,
90
,
-
1
,
-
1
,
-
1
,
-
1
,
95
,
-
1
,
97
,
98
,
99
,
100
,
101
,
102
,
103
,
104
,
105
,
106
,
107
,
108
,
109
,
110
,
111
,
112
,
113
,
114
,
115
,
116
,
117
,
118
,
119
,
120
,
121
,
122
,
65
,
66
,
67
,
68
,
69
,
70
,
71
,
72
,
73
,
74
,
75
,
76
,
77
,
78
,
79
,
80
,
81
,
82
,
83
,
84
,
85
,
86
,
87
,
88
,
89
,
90
,
-
1
,
-
1
,
-
1
,
-
1
,
95
,
-
1
,
97
,
98
,
99
,
100
,
101
,
102
,
103
,
104
,
105
,
106
,
107
,
108
,
109
,
110
,
111
,
112
,
113
,
114
,
115
,
116
,
117
,
118
,
119
,
120
,
121
,
122
,
65
,
66
,
67
,
68
,
69
,
70
,
71
,
72
,
73
,
74
,
75
,
76
,
77
,
78
,
79
,
80
,
81
,
82
,
83
,
84
,
85
,
86
,
87
,
88
,
89
,
90
,
-
1
,
-
1
,
-
1
,
-
1
,
95
,
-
1
,
97
,
98
,
99
,
100
,
101
,
102
,
103
,
104
,
105
,
106
,
107
,
108
,
109
,
110
,
111
,
112
,
113
,
114
,
115
,
116
,
117
,
118
,
119
,
120
,
121
,
122
,
65
,
66
,
67
,
68
,
69
,
70
,
71
,
72
,
73
,
74
,
75
,
76
,
77
,
78
,
79
,
80
,
81
,
82
,
83
,
84
,
85
,
86
,
87
,
88
,
89
,
90
,
-
1
,
-
1
,
-
1
,
-
1
,
95
,
-
1
,
97
,
98
,
99
,
100
,
101
,
102
,
103
,
104
,
105
,
106
,
107
,
108
,
109
,
110
,
111
,
112
,
113
,
114
,
115
,
116
,
117
,
118
,
119
,
120
,
121
,
122
,
65
,
66
,
67
,
68
,
69
,
70
,
71
,
72
,
73
,
74
,
75
,
76
,
77
,
78
,
79
,
80
,
81
,
82
,
83
,
84
,
85
,
86
,
87
,
88
,
89
,
90
,
-
1
,
-
1
,
-
1
,
-
1
,
95
,
-
1
,
97
,
98
,
99
,
100
,
101
,
102
,
103
,
104
,
105
,
106
,
107
,
108
,
109
,
110
,
111
,
112
,
113
,
114
,
115
,
116
,
117
,
118
,
119
,
120
,
121
,
122
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
]
alex_deflt
::
Array
Int
Int
alex_deflt
=
listArray
(
0
,
23
)
[
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
,
-
1
]
alex_accept
=
listArray
(
0
::
Int
,
23
)
[
AlexAccNone
,
AlexAccSkip
,
AlexAcc
(
alex_action_1
),
AlexAcc
(
alex_action_2
),
AlexAcc
(
alex_action_3
),
AlexAcc
(
alex_action_4
),
AlexAcc
(
alex_action_5
),
AlexAcc
(
alex_action_6
),
AlexAcc
(
alex_action_7
),
AlexAcc
(
alex_action_10
),
AlexAcc
(
alex_action_11
),
AlexAcc
(
alex_action_12
),
AlexAcc
(
alex_action_13
),
AlexAcc
(
alex_action_13
),
AlexAcc
(
alex_action_13
),
AlexAcc
(
alex_action_13
),
AlexAcc
(
alex_action_13
),
AlexAcc
(
alex_action_13
),
AlexAcc
(
alex_action_13
),
AlexAcc
(
alex_action_13
),
AlexAcc
(
alex_action_13
),
AlexAcc
(
alex_action_13
),
AlexAcc
(
alex_action_13
),
AlexAcc
(
alex_action_13
)]
{-# LINE 28 "Lexer.x" #-}
data
Token
=
TokenSet
|
TokenIf
|
TokenWhile
|
TokenBegin
|
TokenSym
Char
|
TokenPlus
|
TokenMult
|
TokenDiv
|
TokenMinus
|
TokenLParen
|
TokenRParen
|
TokenInt
Int
|
TokenVar
String
deriving
(
Eq
,
Show
)
alex_action_1
=
\
s
->
TokenSet
alex_action_2
=
\
s
->
TokenIf
alex_action_3
=
\
s
->
TokenWhile
alex_action_4
=
\
s
->
TokenBegin
alex_action_5
=
\
s
->
TokenSym
(
head
s
)
alex_action_6
=
\
s
->
TokenPlus
alex_action_7
=
\
s
->
TokenMinus
alex_action_8
=
\
s
->
TokenDiv
alex_action_9
=
\
s
->
TokenMult
alex_action_10
=
\
s
->
TokenLParen
alex_action_11
=
\
s
->
TokenRParen
alex_action_12
=
\
s
->
TokenInt
(
read
s
)
alex_action_13
=
\
s
->
TokenVar
s
{-# LINE 1 "templates/GenericTemplate.hs" #-}
{-# LINE 1 "templates/GenericTemplate.hs" #-}
{-# LINE 1 "<built-in>" #-}
{-# LINE 1 "<command-line>" #-}
#
1
"/usr/include/stdc-predef.h"
1
3
4
#
17
"/usr/include/stdc-predef.h"
3
4
{-# LINE 5 "<command-line>" #-}
{-# LINE 1 "templates/GenericTemplate.hs" #-}
-- -----------------------------------------------------------------------------
-- ALEX TEMPLATE
--
-- This code is in the PUBLIC DOMAIN; you may copy it freely and use
-- it for any purpose whatsoever.
-- -----------------------------------------------------------------------------
-- INTERNALS and main scanner engine
{-# LINE 21 "templates/GenericTemplate.hs" #-}
{-# LINE 51 "templates/GenericTemplate.hs" #-}
{-# LINE 72 "templates/GenericTemplate.hs" #-}
alexIndexInt16OffAddr
arr
off
=
arr
!
off
{-# LINE 93 "templates/GenericTemplate.hs" #-}
alexIndexInt32OffAddr
arr
off
=
arr
!
off
{-# LINE 105 "templates/GenericTemplate.hs" #-}
quickIndex
arr
i
=
arr
!
i
-- -----------------------------------------------------------------------------
-- Main lexing routines
data
AlexReturn
a
=
AlexEOF
|
AlexError
!
AlexInput
|
AlexSkip
!
AlexInput
!
Int
|
AlexToken
!
AlexInput
!
Int
a
-- alexScan :: AlexInput -> StartCode -> AlexReturn a
alexScan
input
(
sc
)
=
alexScanUser
undefined
input
(
sc
)
alexScanUser
user
input
(
sc
)
=
case
alex_scan_tkn
user
input
(
0
)
input
sc
AlexNone
of
(
AlexNone
,
input'
)
->
case
alexGetByte
input
of
Nothing
->
AlexEOF
Just
_
->
AlexError
input'