summaryrefslogtreecommitdiff
path: root/utils/hpc/HpcLexer.hs
blob: 74bec5dd4c1abaf7893828ad1dd3bb44f012db2f (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
module HpcLexer where

import Data.Char

data Token 
	= ID String
        | SYM Char
        | INT Int
        | STR String
	deriving (Eq,Show)

initLexer :: String -> [Token]
initLexer str = [ t | (_,_,t) <- lexer str 1 0 ]

lexer :: String -> Int -> Int ->  [(Int,Int,Token)]
lexer (c:cs) line column
  | c == '\n' = lexer cs (succ line) 0
  | c == '\"' = lexerSTR cs line (succ column)
  | c `elem` "{};-:" 
              = (line,column,SYM c) : lexer cs line (succ column)
  | isSpace c = lexer cs        line (succ column)
  | isAlpha c = lexerKW  cs [c] line (succ column)
  | isDigit c = lexerINT cs [c] line (succ column)
  | otherwise = error "lexer failure"
lexer [] line colunm = []

lexerKW  (c:cs) s line column
  | isAlpha c = lexerKW cs (s ++ [c]) line (succ column)
lexerKW  other s line column = (line,column,ID s) : lexer other line column

lexerINT  (c:cs) s line column
  | isDigit c = lexerINT cs (s ++ [c]) line (succ column)
lexerINT  other s line column = (line,column,INT (read s)) : lexer other line column

-- not technically correct for the new column count, but a good approximation.
lexerSTR cs line column
  = case lex ('"' : cs) of
      [(str,rest)] -> (line,succ column,STR str) 
                   : lexer rest line (length (show str) + column + 1)
      _ -> error "bad string"

test = do
          t <- readFile "EXAMPLE.tc"
          print (initLexer t)