refactoors
[mTask.git] / mTaskCode.icl
1 implementation module mTaskCode
2
3 import Generics.gdynamic
4 import Generics.gCons
5 import StdEnv
6
7 //import iTasks
8 import GenEq, StdMisc, StdArray
9 import mTask
10
11 instance toCode MTask where toCode (MTask x) = "Task " + toCode x
12
13 argType :: (((Code a p)->Code b q)->In ((Code a p)->Code b q) (Code c s)) -> a | type a
14 argType f = undef
15
16 instance argTypes (Code a p) | showType a where argTypes f = showType
17 instance argTypes (Code a p, Code b q) | showType a & showType b where argTypes f = (showType, showType)
18 instance argTypes (Code a p, Code b q, Code c r) | showType a & showType b & showType c where argTypes f = (showType, showType, showType)
19
20 resType :: ((t->Code b Expr)->In (t->Code b q) (Main (Code c s))) -> Code b q | showType b
21 resType f = showType
22
23 var2Type :: (Code t p) -> Code t p | showType t
24 var2Type x = showType
25
26 resType2 :: ((t->Code b Expr)->In (t->Code b q) (Main (Code c s))) -> SV b | showType2 b
27 resType2 f = showType2
28
29 instance toCode (SV t) where toCode (SV s) = s
30
31 instance arith Code where
32 lit a = embed (c a)
33 (+.) x y = codeOp2 x " + " y
34 (-.) x y = codeOp2 x " - " y
35 (*.) x y = codeOp2 x " * " y
36 (/.) x y = codeOp2 x " / " y
37 instance boolExpr Code where
38 (&.) x y = codeOp2 x " && " y
39 (|.) x y = codeOp2 x " || " y
40 Not x = embed (brac (c "! " +.+ brac x))
41 (==.) x y = codeOp2 x " == " y
42 (!=.) x y = codeOp2 x " != " y
43 (<.) x y = codeOp2 x " < " y
44 (<=.) x y = codeOp2 x " <= " y
45 (>.) x y = codeOp2 x " > " y
46 (>=.) x y = codeOp2 x " >= " y
47 instance If Code Stmt Stmt Stmt where If c t e = IfStmt c t e
48 instance If Code e Stmt Stmt where If c t e = IfStmt c t e
49 instance If Code Stmt e Stmt where If c t e = IfStmt c t e
50 instance If Code x y Expr where If c t e = IfExpr c t e
51 IfExpr b t e = embed (brac (b +.+ indent +.+ nl +.+ c " ? " +.+ t +.+ nl +.+ c " : " +.+ e +.+ unindent))
52 IfStmt b t e =
53 getMode \mode.
54 let
55 v = varName t
56 newMode =
57 case mode of
58 Return s = Return s
59 Assign v = Assign v
60 _ = if (v == "") NoReturn (Assign v)
61 in
62 setMode SubExp +.+
63 c "if " +.+ brac b +.+ c " {" +.+
64 indent +.+ nl +.+ setMode newMode +.+ t +.+ unindent +.+ nl +.+ c "} else {" +.+
65 indent +.+ nl +.+ setMode newMode +.+ e +.+ unindent +.+ nl +.+ c "}"
66 instance IF Code where
67 IF b t e = IfStmt b t e
68 (?) b t =
69 getMode \mode.
70 c "if " +.+ setMode SubExp +.+ brac b +.+ c " {" +.+
71 indent +.+ nl +.+ setMode mode +.+ t +.+ c ";" +.+ unindent +.+ nl +.+ c "}"
72
73 instance sds Code where
74 sds f = // defCode f
75 {main = fresh \n.
76 let name = "sds"+toCode n
77 (v In body) = f (C (var name))
78 in setCode Var +.+ c (type2string v + " " + name + " = " + toCode v +
79 ";\n") +.+ setCode Setup +.+ unMain body}
80 con f = defCode f
81
82 defCode :: ((Code t p) -> In t (Main (Code u q))) -> Main (Code u r) | type t
83 defCode f =
84 {main = fresh \n.
85 let name = "sds"+toCode n
86 (v In body) = f (C (var name))
87 in setCode Var +.+ c (type2string v + " " + name + " = " + toCode v +
88 ";\n") +.+ setCode Setup +.+ unMain body}
89
90 var :: String (ReadWrite (Code v q)) CODE -> CODE
91 var sds Rd s = unC (embed (c sds)) Rd s
92 var sds (Wrt v) s = unC (embed (c ("(" + sds + " = ") +.+ v +.+ c ")")) Rd s
93
94 instance assign Code where
95 (=.) (C v) e = embed (setMode SubExp +.+ C \rw c.v (Wrt (toExpr e)) c)
96 instance seq Code where
97 (>>=.) x f =
98 getMode \mode. fresh \n. let v = "b" + toCode n in
99 addBinds v +.+ var2Type x +.+ c (v + ";") +.+ nl +.+
100 setMode (Assign v) +.+ x +.+ nl +.+ setMode mode +.+ f (embed (c v))
101 (:.) x y = getMode \mode. setMode NoReturn +.+ embed x +.+ nl +.+ setMode mode +.+ y
102 instance step` Code where
103 (>>*.) x f =
104 getMode \mode. fresh \n.
105 let v = "s" + toCode n in
106 c "while(true) {" +.+ indent +.+ nl +.+
107 var2Type x +.+ c (v + ";") +.+ nl +.+
108 setMode (Assign v) +.+ x +.+ nl +.+
109 setMode mode +.+ codeSteps (f (c v)) +.+
110 unindent +.+ nl +.+ c "}"
111 codeSteps :: [Step Code t] -> Code u p
112 codeSteps [] = C \rw c.c
113 codeSteps [Cond b e:x] =
114 getMode \mode. setMode SubExp +.+
115 c "if (" +.+ b +.+ c ") {" +.+ indent +.+ nl +.+
116 setMode mode +.+ e +.+
117 optBreak mode +.+ unindent +.+ nl +.+ c "}" +.+ nl +.+ setMode mode +.+ codeSteps x
118 codeSteps [Ever e:x] =
119 getMode \mode. e +.+ optBreak mode
120
121 optBreak :: Mode -> Code u p
122 optBreak mode =
123 case mode of
124 Return s = C \rw c.c
125 _ = nl +.+ c "break;"
126
127 instance setDelay Code where
128 setDelay d t = embed (c "setDelay" +.+ brac (t +.+ c ", " +.+ d))
129 instance mtask Code a | taskImp2 a & types a where
130 task f =
131 {main = freshMTask \n.
132 let (app, a) = taskImp2 n types
133 (b In main) = f (\d a.app (long d) a)
134 in codeMTaskBody (loopCode n (b a)) (unMain main)}
135 instance mtasks Code a b | taskImp2 a & types a & taskImp2 b & types b where
136 tasks f =
137 {main =
138 freshMTask \t1.
139 freshMTask \t2.
140 let (app1, a1) = taskImp2 t1 types
141 (app2, a2) = taskImp2 t2 types
142 ((b1, b2) In main) = f ((\d a.app1 (long d) a),(\d a.app2 (long d) a))
143 in codeMTaskBody (loopCode t2 (b2 a2)) (codeMTaskBody (loopCode t1 (b1 a1)) (unMain main))}
144
145 loopCode :: Int (Code a b) -> Code c d
146 loopCode n b =
147 nl +.+ c "case " +.+ c n +.+ c ": {" +.+ indent +.+ nl +.+
148 setMode NoReturn +.+ b +.+ nl +.+ c "break;" +.+
149 unindent +.+ nl +.+ c "} "
150
151 instance taskImp2 () where
152 taskImp2 n () = (app, ())
153 where app d a = setBinds [] +.+ embed (c "newTask(" +.+ c n +.+ c ", " +.+ d +.+ c ")")
154 instance taskImp2 (Code t p) where
155 taskImp2 n type1 = (app, ta)
156 where
157 n0 = "t0p->a[0]"
158 ta = c n0 +.+ type1
159 app d a =
160 setBinds [n0] +.+ embed (c "newTask(" +.+
161 c n +.+ c ", " +.+
162 d +.+ c ", " +.+
163 a +.+ c ")")
164 instance taskImp2 (Code a p, Code b q) where
165 taskImp2 n (type1, type2) = (app, (ta1, ta2)) where
166 n0 = "t0p->a[0]"
167 n1 = "t0p->a[1]"
168 ta1 = c n0 +.+ type1
169 ta2 = c n1 +.+ type2
170 app d (a1, a2) =
171 setBinds [n0,n1] +.+ embed (c "newTask(" +.+ c n +.+ c ", " +.+ long d +.+
172 c ", " +.+ a1 +.+ c ", " +.+ a2 +.+ c ")")
173 instance taskImp2 (Code a p, Code b q, Code c r) where
174 taskImp2 n (type1, type2, type3) = (app, (ta1, ta2, ta3))
175 where
176 n0 = "t0p->a[0]"
177 n1 = "t0p->a[1]"
178 n2 = "t0p->a[2]"
179 ta1 = c n0 +.+ type1
180 ta2 = c n1 +.+ type2
181 ta3 = c n2 +.+ type3
182 app d (a1, a2, a3) =
183 setBinds [n0,n1,n2] +.+ embed (c "newTask(" +.+
184 c n +.+ c ", " +.+
185 d +.+ c ", " +.+
186 a1 +.+ c ", " +.+
187 a2 +.+ c ", " +.+
188 a3 +.+ c ", 0)")
189 instance taskImp2 (Code a p, Code b q, Code c r, Code d s) where
190 taskImp2 n (type1, type2, type3, type4) = (app, (ta1, ta2, ta3, ta4))
191 where
192 n0 = "t0p->a[0]"
193 n1 = "t0p->a[1]"
194 n2 = "t0p->a[2]"
195 n3 = "t0p->a[3]"
196 ta1 = c n0 +.+ type1
197 ta2 = c n1 +.+ type2
198 ta3 = c n2 +.+ type3
199 ta4 = c n3 +.+ type4
200 app d (a1, a2, a3, a4) =
201 setBinds [n0,n1,n2,n3] +.+ embed (c "newTask(" +.+
202 c n +.+ c ", " +.+
203 d +.+ c ", " +.+
204 a1 +.+ c ", " +.+
205 a2 +.+ c ", " +.+
206 a3 +.+ c ", " +.+
207 a4 +.+ c ")")
208
209 class taskImp a :: Int a -> (Int a->Code MTask Expr, a)
210 instance taskImp () where
211 taskImp n () = (app, ())
212 where app i a = embed (c "newTask(" +.+ c n +.+ c ", " +.+ c i +.+ c ")")
213 instance taskImp (Code t p) where
214 taskImp n type1 = (app, ta)
215 where
216 ta = c "t0p->a[0]" +.+ type1
217 app i a =
218 embed (c "newTask(" +.+
219 c n +.+ c ", " +.+
220 c i +.+ c ", " +.+
221 a +.+ c ")")
222 instance taskImp (Code a p, Code b q) where
223 taskImp n (type1, type2) = (app, (ta1, ta2)) where
224 ta1 = c "t0p->a[0]" +.+ type1
225 ta2 = c "t0p->a[1]" +.+ type2
226 app i (a1, a2) =
227 embed (c "newTask(" +.+ c n +.+ c ", " +.+ c i +.+
228 c ", " +.+ a1 +.+ c ", " +.+ a2 +.+ c ")")
229 instance taskImp (Code a p, Code b q, Code c r) where
230 taskImp n (type1, type2, type3) = (app, (ta1, ta2, ta3))
231 where
232 ta1 = c "t0p->a[0]" +.+ type1
233 ta2 = c "t0p->a[1]" +.+ type2
234 ta3 = c "t0p->a[2]" +.+ type3
235 app i (a1, a2, a3) =
236 embed (c "newTask(" +.+
237 c n +.+ c ", " +.+
238 c i +.+ c ", " +.+
239 a1 +.+ c ", " +.+
240 a2 +.+ c ", " +.+
241 a3 +.+ c ")")
242 instance taskImp (Code a p, Code b q, Code c r, Code d s) where
243 taskImp n (type1, type2, type3, type4) = (app, (ta1, ta2, ta3, ta4))
244 where
245 ta1 = c "t0p->a[0]" +.+ type1
246 ta2 = c "t0p->a[1]" +.+ type2
247 ta3 = c "t0p->a[2]" +.+ type3
248 ta4 = c "t0p->a[3]" +.+ type4
249 app i (a1, a2, a3, a4) =
250 embed (c "newTask(" +.+
251 c n +.+ c ", " +.+
252 c i +.+ c ", " +.+
253 a1 +.+ c ", " +.+
254 a2 +.+ c ", " +.+
255 a3 +.+ c ", " +.+
256 a4 +.+ c ")")
257
258 tasksMain :: Int Int ((a->Code MTask Expr,b->Code MTask Expr) -> In (a->Code c d,b->Code e f) (Main (Code g h))) -> Main (Code i j) | taskImp a & types a & taskImp b & types b
259 tasksMain i j f =
260 { main =
261 freshMTask \n. freshMTask \m.
262 let
263 (app1, a1) = taskImp n types
264 (app2, a2) = taskImp m types
265 ((b1, b2) In {main = e}) = f (app1 i, app2 j)
266 in
267 codeMTaskBody (loopCode n (b1 a1) +.+ setMode NoReturn +.+ loopCode m (b2 a2)) e
268 }
269 class types a :: a
270 instance types () where types = ()
271 instance types (Code a p) | typeSelector a & isExpr p
272 where types = typeSelector
273 instance types (Code a p, Code b q) | typeSelector a & isExpr p & typeSelector b & isExpr q
274 where types = (typeSelector, typeSelector)
275 instance types (Code a p, Code b q, Code c r) | typeSelector a & isExpr p & typeSelector b & isExpr q & typeSelector c & isExpr r
276 where types = (typeSelector, typeSelector, typeSelector)
277 instance types (Code a p, Code b q, Code c r, Code d s) | typeSelector a & isExpr p & typeSelector b & isExpr q & typeSelector c & isExpr r & typeSelector d & isExpr s
278 where types = (typeSelector, typeSelector, typeSelector, typeSelector)
279
280 codeMTaskBody :: (Code v w) (Code c d) -> Code e f
281 codeMTaskBody loop e =
282 getMode \mode.
283 setMode NoReturn +.+
284 setCode Loop +.+ loop +.+
285 setMode mode +.+ setCode Setup +.+ embed e
286 instance fun Code () where
287 fun f =
288 {main = getMode \mode. fresh \n.
289 let fname = c ("f" + toCode n)
290 (g In {main=e}) = f (\x.embed (fname +.+ c " ()"))
291 in setCode Fun +.+ c "\n" +.+ resType f +.+ c " " +.+ fname +.+ c " () " +.+
292 funBody (setMode (Return (toCode (resType2 f))) +.+ setBinds [] +.+ g ()) +.+ setCode Setup +.+ setMode mode +.+ e
293 }
294 instance fun Code (Code t p) | type, showType t & isExpr p where
295 fun f =
296 {main =
297 getMode \mode. fresh \n.
298 let fname = c ("f" + toCode n)
299 aname = "a" + toCode n
300 (g In {main=e}) = f (\x.embed (fname +.+ c " " +.+ brac x))
301 in setCode Fun +.+ c "\n" +.+ resType f +.+ c " " +.+ fname +.+ c " " +.+
302 brac (argTypes f +.+ c (" " + aname)) +.+
303 funBody (setMode (Return (toCode (resType2 f))) +.+ setBinds [aname] +.+ g (embed (c aname))) +.+ setCode Setup +.+ setMode mode +.+ e
304 }
305 instance fun Code (Code a p, Code b q) | showType a & showType b where
306 fun f =
307 {main =
308 getMode \mode. fresh \n.
309 let fname = c ("f" + toCode n + " ")
310 aname = "a" + toCode n //+ " "
311 bname = "b" + toCode n //+ " "
312 (atype, btype) = argTypes f
313 (g In main)
314 = f (\(x,y).embed (fname +.+ codeOp2 x ", " y))
315 in setCode Fun +.+ nl +.+ resType f +.+ fname +.+
316 codeOp2 (atype +.+ c aname) ", " (btype +.+ c bname) +.+
317 funBody (setMode (Return (toCode (resType2 f))) +.+
318 setBinds [aname,bname] +.+ g (embed (c aname), embed (c bname))) +.+
319 setCode Setup +.+ setMode mode +.+ unMain main
320 }
321 instance fun Code (Code a p, Code b q, Code c r) | showType a & showType b & showType c where
322 fun f =
323 {main =
324 getMode \mode. fresh \n.
325 let fname = c ("f" + toCode n)
326 aname = "a" + toCode n
327 bname = "b" + toCode n
328 cname = "c" + toCode n
329 (atype,btype,ctype) = argTypes f
330 (g In {main=e}) = f (\(x,y,z).embed (fname +.+ c " " +.+ brac (x +.+ c ", " +.+ y +.+ c ", " +.+ z)))
331 in setCode Fun +.+ c "\n" +.+ resType f +.+ c " " +.+ fname +.+ c " " +.+
332 brac (atype +.+ c (" " + aname + ", ") +.+ btype +.+ c (" " + bname + ", ") +.+ ctype +.+ c (" " + cname)) +.+
333 funBody (setMode (Return (toCode (resType2 f))) +.+
334 setBinds [aname,bname,cname] +.+ g (embed (c aname), embed (c bname), embed (c cname))) +.+ setCode Setup +.+ setMode mode +.+ e
335 }
336 instance output Code where
337 output x = embed (c "Serial.println(" +.+ x +.+ c ")")
338 instance pinMode Code where
339 pinmode p m = embed (c ("pinMode(" + toCode p + ", " + consName{|*|} m + ")"))
340 instance digitalIO Code where
341 digitalRead p = embed (c ("digitalRead(" + toCode p + ")"))
342 digitalWrite p b = embed (c ("digitalWrite(" + toCode p + ", ") +.+ b +.+ c ")")
343 instance dIO Code where
344 dIO p = C (ioc p) where
345 ioc :: p (ReadWrite (Code t q)) CODE -> CODE | pin, readPinD p
346 ioc p Rd s = f Rd s where (C f) = embed (c ("digitalRead(" + toCode p + ")"))
347 ioc p (Wrt v) s = f Rd s where (C f) = embed (c ("pWrite(" + toCode p + ", ") +.+ v +.+ c ")")
348 instance aIO Code where
349 aIO p = C (ioc p) where
350 ioc :: p (ReadWrite (Code t q)) CODE -> CODE | pin p
351 ioc p Rd s = unC (embed (c ("analogRead(" + toCode p + ")"))) Rd s
352 ioc p (Wrt v) s = unC (embed (c ("pWrite(" + toCode p + ", ") +.+ v +.+ c ")")) Rd s
353 instance analogIO Code where
354 analogRead p = embed (c ("analogRead(" + toCode p + ")"))
355 analogWrite p b = embed (c ("analogWrite(" + toCode p + ", ") +.+ b +.+ c ")")
356 instance noOp Code where noOp = C \rw c.c
357
358 :: Code a p = C ((ReadWrite (Code a Expr)) CODE -> CODE)
359 unC :: (Code a p) -> ((ReadWrite (Code a Expr)) CODE -> CODE)
360 unC (C f) = f
361
362 :: Def = Var | Fun | Setup | Loop
363 :: Mode = /*MainMode |*/ NoReturn | Return String | SubExp | Assign String
364
365 setMode :: Mode -> Code a p
366 setMode m = C \rw c.{CODE|c & mode` = m}
367
368 getMode :: (Mode -> Code a p) -> Code a p
369 getMode f = C \rw c.unC (f c.mode`) rw c
370
371 embed :: (Code a p) -> Code a p
372 embed e =
373 getMode \m. case m of
374 NoReturn = setMode SubExp +.+ e +.+ c ";"
375 Return "void" = setMode SubExp +.+ e +.+ c ";"
376 Return t = c "return " +.+ setMode SubExp +.+ e +.+ c ";"
377 Assign s = c (s + " = ") +.+ setMode SubExp +.+ e +.+ c ";"
378 SubExp = e
379 _ = abort "\n\nembed: unknown mode.\n"
380
381 (+.+) infixl 5 :: (Code a p) (Code b q) -> Code c r
382 (+.+) (C f) (C g) = C \rw c.g Rd (f Rd c)
383
384 fresh :: (Int -> (Code a p)) -> (Code a p)
385 fresh f = C \rw c.unC (f c.fresh) rw {CODE | c & fresh = c.fresh + 1}
386
387 freshMTask :: (Int -> (Code a p)) -> (Code a p)
388 freshMTask f = C \rw c.unC (f c.freshMTask) rw {CODE | c & freshMTask = c.freshMTask + 1}
389
390 setCode :: Def -> (Code a p)
391 setCode d = C \rw c.{c & def = d}
392
393 getCode :: (Def -> Code a p) -> (Code a p)
394 getCode f = C \rw c.unC (f c.def) rw c
395
396 brac :: (Code a p) -> Code b q
397 brac e = c "(" +.+ e +.+ c ")"
398
399 funBody :: (Code a p) -> Code b q
400 funBody e = c "{" +.+ indent +.+ nl +.+ e +.+ unindent +.+ nl +.+ c "}" +.+ nl
401
402 codeOp2 :: (Code a p) String (Code b q) -> Code c r
403 codeOp2 x n y = embed (brac (x +.+ c n +.+ y))
404
405 include :: String -> Code a b
406 include lib = C \rw c.{c & includes = [lib:c.includes]}
407
408 argList :: [a] -> String | toCode a
409 argList [a] = toCode a
410 argList [a:x] = toCode a + "," + argList x
411 argList [] = ""
412
413 c :: a -> Code b p | toCode a
414 c a = C \rw c.case c.def of
415 Fun = {c & funs = [toCode a: c.funs]}
416 Var = {c & vars = [toCode a: c.vars]}
417 Setup = {c & setup = [toCode a: c.setup]}
418 Loop = {c & loop = [toCode a: c.loop]}
419
420 indent :: Code a p
421 indent =
422 C \rw c.case c.def of
423 Fun = {c & ifuns = inc c.ifuns}
424 Var = {c & ivars = inc c.ivars}
425 Setup = {c & isetup = inc c.isetup}
426 Loop = {c & iloop = inc c.iloop}
427
428 unindent :: Code a p
429 unindent =
430 C \rw c.case c.def of
431 Fun = {c & ifuns = dec c.ifuns}
432 Var = {c & ivars = dec c.ivars}
433 Setup = {c & isetup = dec c.isetup}
434 Loop = {c & iloop = dec c.iloop}
435 where
436 dec n | n > 1
437 = n - 1
438 = 0
439
440 nl :: Code a p
441 nl =
442 C \rw c.case c.def of
443 Fun = {c & funs = [str c.ifuns: c.funs]}
444 Var = {c & vars = [str c.ivars: c.vars]}
445 Setup = {c & setup = [str c.isetup: c.setup]}
446 Loop = {c & loop = [str c.iloop: c.loop]}
447 where
448 str n = toString ['\n':repeatn (tabSize * n) ' ']
449
450 setBinds :: [String] -> Code a p
451 setBinds list = C \rw c.{c & binds = list}
452
453 addBinds :: String -> Code a p
454 addBinds name = C \rw c.{c & binds = [name:c.binds]}
455
456 getBinds :: ([String] -> Code a p) -> (Code a p)
457 getBinds f = C \rw c.unC (f c.binds) rw c
458
459 // ----- driver ----- //
460
461 compile :: (Main (Code a p)) -> [String]
462 compile {main=(C f)} =
463 ["/*\n"
464 ," Generated code for Arduino\n"
465 ," Pieter Koopman, pieter@cs.ru.nl\n"
466 ,"*/\n"
467 ,"\n"
468 ,"#define MAX_ARGS 4\n"
469 ,"#define MAX_TASKS 20\n"
470 ,"#define MAX_TASK_NO MAX_TASKS - 1\n"
471 ,"#define NEXT_TASK(n) ((n) == MAX_TASK_NO ? 0 : (n) + 1)\n"
472 ,"\n"
473 ,"typedef union Arg {\n"
474 ," int i;\n"
475 ," bool b;\n"
476 ," char c;\n"
477 // ," float f;\n" // requires 4 bytes
478 ," word w;\n"
479 ,"} ARG;\n"
480 ,"\n"
481 ,"typedef struct Task {\n"
482 ," byte id;\n"
483 ," long wait;\n"
484 ," ARG a[MAX_ARGS];\n"
485 ,"} TASK;\n"
486 ,"\n"
487 ] ++
488 foldr (\lib c.["#include <":lib:".h>\n":c]) [] (mkset c.includes) ++
489 ["\n// --- variables ---\n"
490 ,"TASK tasks[MAX_TASKS];\n"
491 ,"byte t0 = 0, tc = 0, tn = 0;\n"
492 ,"long delta;\n"
493 ,"\n"
494 ,"int vInt;\n"
495 ,"bool vBool;\n"
496 ,"char vChar;\n"
497 ,"float vFloat;\n"
498 ,"unsigned long time = 0;\n"
499 :reverse c.vars
500 ] ++
501 ["\n// --- functions ---\n"
502 ,"byte newTask(byte id, long wait, word a0 = 0, word a1 = 0, word a2 = 0, word a3 = 0) {\n"
503 ," TASK *tnp = &tasks[tn];\n"
504 ," tnp->id = id;\n"
505 ," tnp->wait = wait;\n"
506 ," tnp->a[0].w = a0;\n"
507 ," tnp->a[1].w = a1;\n"
508 ," tnp->a[2].w = a2;\n"
509 ," tnp->a[3].w = a3;\n"
510 ," byte r = tn;\n"
511 ," tn = NEXT_TASK(tn);\n"
512 ," return r;\n"
513 ,"}\n"
514 ,"\n"
515 ,"byte setDelay(byte t, long d) {\n"
516 ," tasks[t].wait = d;\n"
517 ," return t;\n"
518 ,"}\n"
519 ,"boolean pressed(int b) {\n"
520 ," pinMode(A0, INPUT);\n"
521 ," int a0 = analogRead(A0);\n"
522 ," switch (b) {\n"
523 ," case 0: return a0 < ",toString RightBound,"; // right\n"
524 ," case 1: return ",toString RightBound," < a0 && a0 < ",toString UpBound,"; // up\n"
525 ," case 2: return ",toString UpBound," < a0 && a0 < ",toString DownBound,";// down\n"
526 ," case 3: return ",toString DownBound," < a0 && a0 < ",toString LeftBound,";//left\n"
527 ," case 4: return ",toString LeftBound," < a0 && a0 < ",toString SelectBound,";//select\n"
528 ," default: return ",toString SelectBound," < a0; //no button\n"
529 ," }\n"
530 ,"}\n"
531 ,"boolean pWrite (int pin, boolean b) {\n"
532 ," pinMode(pin, OUTPUT);\n"
533 ," digitalWrite(pin, b);\n"
534 ," return b;\n"
535 ,"}\n"
536 ,"int pWrite (int pin, int i) {\n"
537 ," pinMode(pin, OUTPUT);\n"
538 ," analogWrite(pin, i);\n"
539 ," return i;\n"
540 ,"}\n"
541 :reverse c.funs
542 ] ++
543 ["\n// --- setup --- \n"
544 ,"void setup () {\n"
545 ," Serial.begin(9600);\n"
546 ," "
547 :reverse c.setup
548 ] ++
549 ["\n}\n"
550 ,"\n// --- loop --- \n"
551 ,"void loop () {\n"
552 ," if (t0 != tn) {\n"
553 ," if (t0 == tc) {\n"
554 ," unsigned long time2 = millis();\n"
555 ," delta = time2 - time;\n"
556 ," time = time2;\n"
557 ," tc = tn;\n"
558 ," };\n"
559 ," TASK* t0p = &tasks[t0];\n"
560 ," t0p->wait -= delta;\n"
561 ," if (t0p->wait > 0L) {\n"
562 ," newTask(t0p->id, t0p->wait, t0p->a[0].w, t0p->a[1].w, t0p->a[2].w, t0p->a[3].w);\n"
563 ," } else {\n"
564 ," switch (t0p->id) {"
565 :reverse c.loop
566 ] ++
567 ["\n"
568 ," default:\n"
569 ," Serial.println(\"stopped\");\n"
570 ," t0 = tn; // no known task: force termination of tasks\n"
571 ," return;\n"
572 ," };\n"
573 ," }\n"
574 ," t0 = NEXT_TASK(t0);\n"
575 ," }\n"
576 ,"}\n"
577 ]
578 where c = f Rd newCode
579
580 mkset :: [a] -> [a] | Eq a
581 mkset [a:x] = [a:mkset (filter ((<>) a) x)]
582 mkset [] = []
583
584 newCode :: CODE
585 newCode =
586 { fresh = 0
587 , freshMTask = 0
588 , funs = []
589 , ifuns = 0
590 , vars = []
591 , ivars = 0
592 , setup = []
593 , isetup = 1
594 , loop = []
595 , iloop = 4
596 , includes = []
597 , def = Setup
598 , mode` = NoReturn
599 , binds = []
600 }
601
602
603 //Tools
604 instance toCode () where toCode _ = ""
605
606 class toCode a :: a -> String
607
608 instance toCode Long where toCode (L i) = toCode i + "L"
609
610 instance toCode Bool where toCode b = if b "true" "false"
611 instance toCode Int where toCode a = toString a
612 instance toCode Real where toCode a = toString a
613 instance toCode Char where
614 toCode '\0' = "'\\0'"
615 toCode '\n' = "'\\n'"
616 toCode '\\' = "\\"
617 toCode a = "'" + toString a + "'"
618 instance toCode String where toCode s = s
619 instance toCode DigitalPin where toCode x = s%(1, size s - 1) where s = consName{|*|} x
620 instance toCode AnalogPin where toCode x = consName{|*|} x
621
622 instance toCode Pin where
623 toCode (Digital p) = toCode p
624 toCode (Analog p) = toCode p
625 instance toCode UserLED where
626 toCode LED1 = toCode 1
627 toCode LED2 = toCode 2
628 toCode LED3 = toCode 3
629