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
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
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
91
92
93
94
95
96
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
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
|
module DSL where
import Data.Char (isDigit, isSpace)
import Data.Foldable (foldlM)
import Parsers
------------------------------------------------------------------------------
-- Data types / instances
------------------------------------------------------------------------------
data StackData
= StackInt Integer
| StackBool Bool
instance Show StackData where
show (StackInt x) = show x
show (StackBool True) = "true"
show (StackBool False) = "false"
type TypeCheck = StackData -> Bool
type Stack = [StackData]
data Intrinsic
-- core stack operations
= I_DUMP
| I_DROP
| I_SWAP
| I_DUP
| I_OVER
| I_ROT
-- core arithmetic operations
| I_PLUS
| I_MINUS
| I_TIMES
| I_DIVMOD
deriving (Show, Eq)
data Operation
= OpPushData StackData
| OpIntrinsic Intrinsic
deriving (Show)
data StackModifier = StackModifier { smName :: String
, smTypes :: [TypeCheck]
, smFunc :: Stack -> IO Stack
}
data Block
= BLinear [Operation]
deriving (Show)
type Program = [Block]
data Machine = Machine { ok :: Bool
, stack :: Stack
}
data TokenData
= T_WHITESPACE
| T_INT_LITERAL Integer
| T_INTRINSIC Intrinsic
deriving (Show, Eq)
data DSLToken = DSLToken { tStr :: String -- original text
, tData :: TokenData -- actual data
} deriving (Show)
type DSLLexer = Parser Char DSLToken
type DSLParser = Parser DSLToken
------------------------------------------------------------------------------
-- Lexing
------------------------------------------------------------------------------
buildDSLLexer :: (Parser Char [Char]) -> ([Char] -> TokenData) -> DSLLexer
buildDSLLexer p f = do
str <- p
return DSLToken { tStr=str
, tData=f str
}
intrinsicL :: String -> Intrinsic -> DSLLexer
intrinsicL s i = buildDSLLexer (list s) (const $ T_INTRINSIC i)
wsL :: DSLLexer
wsL = buildDSLLexer (mult1 $ satisfy isSpace) (const T_WHITESPACE)
intLiteralL :: DSLLexer
intLiteralL = buildDSLLexer go (T_INT_LITERAL . read)
where
go = do
sign <- optional $ token '-'
digits <- mult1 $ satisfy isDigit
result $ maybe digits (:digits) sign
mainLexer :: Parser Char [DSLToken]
mainLexer = phrase $ mult1 $ firstOf subLexers
where
subLexers = [wsL] ++ literals ++ intrinsics
literals = [ intLiteralL
]
intrinsics = map (uncurry intrinsicL) [ (".", I_DUMP)
, ("DROP", I_DROP)
, ("SWAP", I_SWAP)
, ("DUP", I_DUP)
, ("OVER", I_OVER)
, ("ROT", I_ROT)
, ("+", I_PLUS)
, ("-", I_MINUS)
, ("*", I_TIMES)
, ("/%", I_DIVMOD)
]
------------------------------------------------------------------------------
-- Parsing
------------------------------------------------------------------------------
wsP :: DSLParser ()
wsP = do
t <- anyToken
case tData t of
T_WHITESPACE -> result ()
_ -> flunk
dataLiteralP :: DSLParser StackData
dataLiteralP = do
t <- anyToken
case tData t of
T_INT_LITERAL x -> result $ StackInt x
_ -> flunk
pushDataP :: DSLParser Operation
pushDataP = OpPushData <$> dataLiteralP
intrinsicP :: DSLParser Operation
intrinsicP = do
t <- anyToken
case tData t of
T_INTRINSIC i -> result $ OpIntrinsic i
_ -> flunk
operationP :: DSLParser Operation
operationP = firstOf [ pushDataP
, intrinsicP
]
linearP :: DSLParser Block
linearP = do
ops <- optional wsP *> operationP `sepBy1` wsP <* optional wsP
eof
return $ BLinear ops
blockP :: DSLParser Block
blockP = firstOf [linearP]
programP :: DSLParser Program
programP = phrase $ mult1 blockP
stringToProgram :: String -> Maybe Program
stringToProgram str = do
(_, tokens) <- parse mainLexer str
(_, program) <- parse programP tokens
return program
------------------------------------------------------------------------------
-- Type checking
------------------------------------------------------------------------------
tAny :: TypeCheck
tAny = const True
tBool :: TypeCheck
tBool (StackBool _) = True
tBool _ = False
tInt :: TypeCheck
tInt (StackInt _) = True
tInt _ = False
runChecks :: [TypeCheck] -> Stack -> Maybe String
runChecks fs s
| length fs > length s = Just "stack underflow"
| not (and $ zipWith id fs s) = Just "type mis-match"
| otherwise = Nothing
------------------------------------------------------------------------------
-- Intrinsics
------------------------------------------------------------------------------
dump :: StackModifier
dump = StackModifier { smName="DUMP", smTypes=ts, smFunc=f }
where
ts = [tAny]
f (x:xs) = putStrLn (show x) >> return xs
f _ = unreachable
drop' :: StackModifier
drop' = StackModifier { smName="DROP", smTypes=ts, smFunc=f }
where
ts = [tAny]
f (_:xs) = return xs
f _ = unreachable
swap :: StackModifier
swap = StackModifier { smName="SWAP", smTypes=ts, smFunc=f }
where
ts = [tAny, tAny]
f (x:y:xs) = return $ y:x:xs
f _ = unreachable
dup :: StackModifier
dup = StackModifier { smName="DUP", smTypes=ts, smFunc=f }
where
ts = [tAny]
f (x:xs) = return $ x:x:xs
f _ = unreachable
over :: StackModifier
over = StackModifier { smName="OVER", smTypes=ts, smFunc=f }
where
ts = [tAny, tAny]
f (x:y:xs) = return $ y:x:y:xs
f _ = unreachable
rot :: StackModifier
rot = StackModifier { smName="ROT", smTypes=ts, smFunc=f }
where
ts = [tAny, tAny, tAny]
f (x:y:z:xs) = return $ y:z:x:xs
f _ = unreachable
binArithmetic :: String -> (Integer -> Integer -> [Integer]) -> StackModifier
binArithmetic name f = StackModifier { smName=name, smTypes=ts, smFunc=f' }
where
ts = [tInt, tInt]
f' (StackInt x:StackInt y:xs) = return $ (StackInt <$> f x y) ++ xs
f' _ = unreachable
plus :: StackModifier
plus = binArithmetic "PLUS" $ \ x y -> [x + y]
minus :: StackModifier
minus = binArithmetic "MINUS" $ \ x y -> [x - y]
times :: StackModifier
times = binArithmetic "TIMES" $ \ x y -> [x * y]
divMod' :: StackModifier
divMod' = binArithmetic "DIVMOD" $ \ x y -> [mod x y, div x y]
------------------------------------------------------------------------------
-- Core operations
------------------------------------------------------------------------------
-- "halt and catch fire"
hcf :: Machine -> String -> IO Machine
hcf m msg = putStrLn msg >> return m{ ok=False }
unreachable :: a
unreachable = error "this branch should be unreachable"
pushData :: Machine -> StackData -> Machine
pushData m@Machine{ stack=xs } x = m{ stack=x:xs }
runModifier :: StackModifier -> Stack -> IO (Either String Stack)
runModifier sm s = case runChecks (smTypes sm) s of
Just err -> return $ Left $ smName sm ++ ": " ++ err
Nothing -> Right <$> smFunc sm s
applyIntrinsic :: Intrinsic -> Machine -> IO Machine
applyIntrinsic i m = do
res <- runModifier sm (stack m)
case res of
Left err -> hcf m err
Right s' -> return m{ stack=s' }
where
sm = case i of
I_DUMP -> dump
I_DROP -> drop'
I_SWAP -> swap
I_DUP -> dup
I_OVER -> over
I_ROT -> rot
I_PLUS -> plus
I_MINUS -> minus
I_TIMES -> times
I_DIVMOD -> divMod'
------------------------------------------------------------------------------
-- Interpretation
------------------------------------------------------------------------------
newMachine :: Machine
newMachine = Machine { ok=True, stack=[] }
applyOperation :: Machine -> Operation -> IO Machine
-- take no action if a previous step failed
applyOperation m@Machine{ ok=False } _ = return m
applyOperation m (OpPushData x) = return $ pushData m x
applyOperation m (OpIntrinsic i) = applyIntrinsic i m
applyLinear :: Machine -> [Operation] -> IO Machine
applyLinear = foldlM applyOperation
evalBlocks :: [Block] -> Machine -> IO Machine
evalBlocks _ m@Machine{ ok=False } = return m
evalBlocks [] m = return m
evalBlocks (BLinear b:bs) m = applyLinear m b >>= evalBlocks bs
interpret :: Program -> IO ()
interpret p = evalBlocks p newMachine >> return ()
interpretFromString :: String -> IO ()
interpretFromString = maybe err interpret . stringToProgram
where
err = putStrLn "Unable to parse program"
interpretFromFile :: FilePath -> IO ()
interpretFromFile path = readFile path >>= interpretFromString
|