final lexer
[cc1516.git] / lex.icl
diff --git a/lex.icl b/lex.icl
index cc4bc2f..e2d679a 100644 (file)
--- a/lex.icl
+++ b/lex.icl
@@ -1,32 +1,68 @@
 implementation module lex
 
-import Data.Either
-import Data.List
+import Control.Monad
+import Data.Either, Data.Maybe, Data.Map, Data.Func
 import StdString
-import System.CommandLine
-import StdFile
-import StdMisc
+import StdTuple
+import StdBool
+import StdList
+import StdChar
 
-// Misschien moeten we hier continuation style van maken
-instance toString lexerOutput where
-       toString l = "dit is een lexer output, danwel error\n"
+SingleCharTokens :: Map Char Token
+SingleCharTokens = fromList [
+       ('(', BraceOpenToken), (')', BraceCloseToken), ('{', CBraceOpenToken),
+       ('}', CBraceCloseToken), ('[', SquareOpenToken), (']', SquareCloseToken),
+       (',', CommaToken), (':', ColonToken), (';', SColonToken),
+       ('.', DotToken), ('+', PlusToken), ('*', StarToken), ('/', SlashToken),
+       ('%', PercentToken), ('=', AssignmentToken), ('<', LesserToken),
+       ('>', BiggerToken), ('!', ExclamationToken)]
+
+EscapeMap :: Map Char Char
+EscapeMap = fromList [('a', toChar 7), ('b', '\b'), ('f', '\f'), ('n', '\n'),
+       ('r', '\r'), ('t', '\t'), ('v', '\v')]
 
 lexer :: [Char] -> LexerOutput
-lexer _ = Left "Not Implemented"
+lexer [] = Right []
+lexer x = case lex x of
+       (Right t, rest) = lexer rest >>= \ts.Right [t:ts]
+       (Left e, _) = Left e
 
-Start :: *World -> *World
-Start w
-# (args, w) = getCommandLine w // We lezen nu nog standaard van stdin
-# (out, w) = stdio w
-# (toparse, out) = readEntireFile out
-# out = out <<< toString (lexer toparse)
-# (b, w) = fclose out w
-| not b = setReturnCode 1 w
-= w
-       where
-               readEntireFile :: *File -> *([Char], *File)
-               readEntireFile f
-               # (b, c, f) = freadc f
-               | not b = ([], f)
-               # (cs, f) = readEntireFile f
-               = ([c:cs], f)
+lex :: [Char] -> (Either String Token, [Char])
+lex [] = (Right EndOfFileToken, [])
+lex ['/':'/':xs] = lex $ dropWhile ((<>) '\n') xs
+lex ['/':'*':xs] =
+       lex $ tl $ map snd $ dropWhile ((<>) ('*', '/')) $ zip2 [zero:xs] xs
+lex ['v':'a':'r':xs] = (Right VarToken, xs)
+lex ['V':'o':'i':'d':xs] = (Right VoidToken, xs)
+lex ['r':'e':'t':'u':'r':'n':xs] = (Right ReturnToken, xs)
+lex ['i':'f':xs] = (Right IfToken, xs)
+lex ['e':'l':'s':'e':xs] = (Right ElseToken, xs)
+lex ['w':'h':'i':'l':'e':xs] = (Right WhileToken, xs)
+lex ['T':'r':'u':'e':xs] = (Right TrueToken, xs)
+lex ['F':'a':'l':'s':'e':xs] = (Right FalseToken, xs)
+lex ['I':'n':'t':xs] = (Right IntTypeToken, xs)
+lex ['C':'h':'a':'r':xs] = (Right CharTypeToken, xs)
+lex ['B':'o':'o':'l':xs] = (Right BoolTypeToken, xs)
+lex [':':':':xs] = (Right DoubleColonToken, xs)
+lex ['!':'=':xs] = (Right NotEqualToken, xs)
+lex ['<':'=':xs] = (Right LesserEqToken, xs)
+lex ['>':'=':xs] = (Right GreaterEqToken, xs)
+lex ['=':'=':xs] = (Right EqualsToken, xs)
+lex ['&':'&':xs] = (Right AmpersandsToken, xs)
+lex ['|':'|':xs] = (Right PipesToken, xs)
+lex ['-':'>':xs] = (Right ArrowToken, xs)
+lex ['\'':x:'\'':xs] = (Right (CharToken x), xs)
+lex ['\'':'\\':x:'\'':xs] = case get x EscapeMap of
+       Just t = (Right (CharToken t), xs)
+       _ = (Left ("Unknown escape: \\" +++ toString x), [])
+lex ['-':t=:[x:xs]]
+| isDigit x = let (i, r) = span isDigit t in (Right (NumberToken ['-':i]), r)
+| otherwise = (Right DashToken, xs)
+lex t=:[x:xs] = case get x SingleCharTokens of
+       (Just tok) = (Right tok, xs)
+       Nothing
+       | isSpace x = lex xs
+       | isDigit x = let (i, r) = span isDigit t in (Right (NumberToken i), r)
+       | isAlpha x = let (i, r) = span isIdent t in (Right (IdentToken i), r)
+               with isIdent c = isAlphanum c || c == '_'
+       | otherwise = (Left ("Unexpected character: " +++ toString x), [])