ported Yard to clean
[cc1516.git] / lex.icl
1 implementation module lex
2
3 import Data.Either
4 import Data.List
5 import StdString
6 import System.CommandLine
7 import StdFile
8 import StdMisc
9 from StdFunc import id, const
10 import Data.Maybe
11 import Control.Applicative
12 import Control.Monad
13 import Control.Monad.State
14 from Data.Func import $
15
16 // Misschien moeten we hier continuation style van maken
17 instance toString lexerOutput where
18 toString l = "dit is een lexer output, danwel error\n"
19
20 lexer :: [Char] -> LexerOutput [Token]
21 lexer _ = Left "Not Implemented"
22
23 Start :: *World -> *World
24 Start w
25 # (args, w) = getCommandLine w // We lezen nu nog standaard van stdin
26 # (out, w) = stdio w
27 # (toparse, out) = readEntireFile out
28 # out = out <<< toString (lexer toparse)
29 # (b, w) = fclose out w
30 | not b = setReturnCode 1 w
31 = w
32 where
33 readEntireFile :: *File -> *([Char], *File)
34 readEntireFile f
35 # (b, c, f) = freadc f
36 | not b = ([], f)
37 # (cs, f) = readEntireFile f
38 = ([c:cs], f)
39
40
41
42 // Clean adaption of Yard, a parsec like parser combinator
43 :: Parser a = Parser ([Char] -> (LexerOutput a, [Char]))
44
45 runParser :: (Parser a) [Char] -> (LexerOutput a, [Char])
46 runParser (Parser p) s = p s
47
48 instance Functor Parser where
49 fmap f s = liftM f s
50
51 instance Applicative Parser where
52 pure a = Parser $ \s -> (Right a, s)
53 (<*>) sf s = ap sf s
54
55 instance Monad Parser where
56 bind p f = Parser $ \s -> let (out, rest) = runParser p s in case out of
57 Left e = (Left e, rest)
58 Right t = runParser (f t) rest
59
60 //gives us some, many and optional
61 instance Alternative Parser where
62 empty = zero
63 (<|>) p1 p2 = parserAlternative p1 p2
64 parserAlternative p1 p2 = Parser $ \s -> let (out, rest) = runParser p1 s in case out of
65 Left e = runParser p2 s
66 Right t = (Right t, rest)
67
68 //parser that fails with error
69 fail :: String -> Parser a
70 fail e = Parser $ \s -> (Left e, s)
71
72 //parser that always fails
73 zero :: Parser a
74 zero = fail "Zero parser"
75
76 //matches exactly one Char
77 item :: Parser Char
78 item = Parser $ \s -> case s of
79 [] = (Left "Unexpected empty input", s)
80 [x:xs] = (Right x, xs)
81
82 //matches any char which satisfies f
83 satisfy :: (Char -> Bool) -> Parser Char
84 satisfy f = item >>= (\r -> if (f r) (return r) zero)
85
86 //tries a parser, if it fails returns a default value
87 optionalDef :: a (Parser a) -> Parser a
88 optionalDef def p = parserAlternative p (return def)
89
90 //matched given char
91 char :: Char -> Parser Char
92 char c = satisfy (\i -> c==i) //I hate that we can't do: satisfy (==c)
93
94 alpha :: Parser Char
95 alpha = satisfy isAlpha
96
97 digit :: Parser Char
98 digit = satisfy isDigit
99
100 //matches a given String
101 string :: [Char] -> Parser [Char]
102 string s = mapM_ char s >>| return s