Merge branch 'master' of git.martlubbers.net:msc-thesis1617
[msc-thesis1617.git] / mtaskext.bytecode.tex
1 The \gls{mTask}-\glspl{Task} are sent to the device in bytecode and are saved
2 in the memory of the device. To compile the \gls{EDSL} code to bytecode, a view
3 is added to the \gls{mTask}-system encapsulated in the type \CI{ByteCode}. As
4 shown in Listing~\ref{lst:bcview}, the \CI{ByteCode} view is a boxed \gls{RWST}
5 that writes bytecode instructions (\CI{BC}, Subsection~\ref{sec:instruction})
6 while carrying around a \CI{BCState}. The state is kept between compilations
7 and is unique to a device. The state contains fresh variable names and a
8 register of \glspl{SDS} that are used.
9
10 Types implementing the \gls{mTask} classes must have two free type variables.
11 Therefore the \gls{RWST} is wrapped with a constructor and two phantom type
12 variables are added. This means that the programmer has to unbox the
13 \CI{ByteCode} object to be able to make use of the \gls{RWST} functionality
14 such as return values. Tailor made access functions are used to achieve this
15 with ease. The fresh variable stream in a compiler using a \gls{RWST} is often
16 put into the \emph{Reader} part of the monad. However, not all code is compiled
17 immediately and later on the fresh variable stream cannot contain variables
18 that were used before. Therefore this information is put in the state which is
19 kept between compilations.
20
21 Not all types are suitable for usage in bytecode compiled programs. Every value
22 used in the bytecode view must fit in the \CI{BCValue} type which restricts
23 the content. Most notably, the type must be bytecode encodable. A \CI{BCValue}
24 must be encodable and decodable without losing type or value information. At
25 the moment a simple encoding scheme is used that uses single byte prefixes to
26 detect the type of the value. The devices know these prefixes and can apply the
27 same detection if necessary. Note that \CI{BCValue} uses existentially
28 quantified type variables and therefore it is not possible to derive class
29 instances such as \CI{iTasks}. Tailor-made instances for these functions have
30 been made.
31
32 \begin{lstlisting}[language=Clean,label={lst:bcview},caption={Bytecode view}]
33 :: ByteCode a p = BC (RWS () [BC] BCState ())
34 :: BCValue = E.e: BCValue e & mTaskType, TC e
35 :: BCShare =
36 { sdsi :: Int
37 , sdsval :: BCValue
38 , sdsname :: String
39 }
40 :: BCState =
41 { freshl :: Int
42 , freshs :: Int
43 , sdss :: [BCShare]
44 }
45
46 class toByteCode a :: a -> String
47 class fromByteCode a :: String -> a
48 class mTaskType a | toByteCode, fromByteCode, iTask, TC a
49
50 instance toByteCode Int, ... , UserLED, BCValue
51 instance fromByteCode Int, ... , UserLED, BCValue
52
53 instance arith ByteCode
54 ...
55 instance serial ByteCode
56 \end{lstlisting}
57
58 \subsection{Instruction Set}\label{sec:instruction}
59 The instruction set is given in Listing~\ref{bc:instr}. The instruction set is
60 kept large, but the number of instructions stays under $255$ to get as much
61 expressive power while keeping all instruction within one byte.
62
63 The interpreter running in the client is a stack machine. The virtual
64 instruction \CI{BCLab} is added to allow for an easy implementation of jumping.
65 However, this is not a real instruction and the labels are resolved to actual
66 program memory addresses in the final step of compilation to save instructions
67 and avoid label lookups at runtime.
68
69 \begin{lstlisting}[language=Clean,label={bc:instr},%
70 caption={Bytecode instruction set}]
71 :: BC = BCNop
72 | BCLab Int | BCPush BCValue | BCPop
73 //SDS functions
74 | BCSdsStore BCShare | BCSdsFetch BCShare | BCSdsPublish BCShare
75 //Unary ops
76 | BCNot
77 //Binary Int ops
78 | BCAdd | BCSub | BCMul
79 | BCDiv
80 //Binary Bool ops
81 | BCAnd | BCOr
82 //Binary ops
83 | BCEq | BCNeq | BCLes | BCGre
84 | BCLeq | BCGeq
85 //Conditionals and jumping
86 | BCJmp Int | BCJmpT Int | BCJmpF Int
87 //UserLED
88 | BCLedOn | BCLedOff
89 //Pins
90 | BCAnalogRead Pin | BCAnalogWrite Pin | BCDigitalRead Pin | BCDigitalWrite Pin
91 //Return
92 | BCReturn
93 \end{lstlisting}
94
95 All single byte instructions are converted automatically using a generic
96 function which returns the index of the constructor. The index of the
97 constructor is the byte value for all instructions. Added to this single byte
98 value are the encoded parameters of the instruction. The last step of the
99 compilation is transforming the list of bytecode instructions to actual bytes.
100
101 \subsection{Helper functions}
102 Since the \CI{ByteCode} type is just a boxed \gls{RWST}, access to the whole
103 range of \gls{RWST} functions is available. However, to use this, the type must
104 be unboxed. After application the type must be boxed again. To achieve this,
105 several helper functions have been created. They are given in
106 Listing~\ref{lst:helpers}. The \CI{op} and \CI{op2} functions is hand-crafted
107 to make operators that pop one or two values off the stack respectively. The
108 \CI{tell`} function is a wrapper around the \gls{RWST} function \CI{tell} that
109 appends the argument to the \emph{Writer} value.
110
111 \begin{lstlisting}[language=Clean,label={lst:helpers},caption={Some helper functions}]
112 op2 :: (ByteCode a p1) (ByteCode a p2) BC -> ByteCode b Expr
113 op2 (BC x) (BC y) bc = BC (x >>| y >>| tell [bc])
114
115 op :: (ByteCode a p) BC -> ByteCode b c
116 op (BC x) bc = BC (x >>| tell [bc])
117
118 tell` :: [BC] -> (ByteCode a p)
119 tell` x = BC (tell x)
120
121 unBC :: (ByteCode a p) -> RWS () [BC] BCState ()
122 unBC (BC x) = x
123 \end{lstlisting}
124
125 \subsection{Arithmetics \& Peripherals}
126 Almost all of the code from the simple classes exclusively use helper
127 functions. Listing~\ref{lst:arithview} shows some implementations. The
128 \CI{boolExpr} class and the classes for the peripherals are implemented using
129 the same strategy.
130
131 \begin{lstlisting}[language=Clean,label={lst:arithview},caption={%
132 Bytecode view implementation for arithmetic and peripheral classes}]
133 instance arith ByteCode where
134 lit x = tell` [BCPush (BCValue x)]
135 (+.) x y = op2 x y BCAdd
136 ...
137
138 instance userLed ByteCode where
139 ledOn l = op l BCLedOn
140 ledOff l = op l BCLedOff
141 \end{lstlisting}
142
143 \subsection{Control Flow}\label{ssec:control}
144 Implementing the sequence operator is very straightforward in the bytecode
145 view. The function just sequences the two \glspl{RWST}. The
146 implementation for the \emph{If} statement speaks for itself in
147 Listing~\ref{lst:controlflow}. First, all the labels are gathered after which
148 they are placed in the correct order in the bytecode sequence. It can happen
149 that multiple labels appear consecutively in the code. This is not a problem
150 since the labels are resolved to real addresses later on anyway.
151
152 \begin{lstlisting}[language=Clean,label={lst:controlflow},%
153 caption={Bytecode view for the \texttt{IF} class}]
154 freshlabel = get >>= \st=:{freshl}->put {st & freshl=freshl+1} >>| tell freshl
155
156 instance IF ByteCode where
157 IF b t e = BCIfStmt b t e
158 (?) b t = BCIfStmt b t (tell` [])
159
160 BCIfStmt (BC b) (BC t) (BC e) = BC (
161 freshlabel >>= \else->freshlabel >>= \endif->
162 b >>| tell [BCJmpF else] >>|
163 t >>| tell [BCJmp endif, BCLab else] >>|
164 e >>| tell [BCLab endif]
165 )
166
167 instance noOp ByteCode where
168 noOp = BC (pure ())
169 \end{lstlisting}
170
171 The scheduling in the \gls{mTask}-\glspl{Task} bytecode view is different from
172 the scheduling in the \gls{C} view. \glspl{Task} in the \gls{C} view can start
173 new \glspl{Task} or even start themselves to continue, while in the bytecode
174 view, \glspl{Task} run indefinitely, one-shot or on interrupt. To allow
175 interval and interrupt \glspl{Task} to terminate, a return instruction is
176 added. This class was not available in the original system and is thus added.
177 It just writes a single instruction so that the interpreter knows to stop
178 execution. Listing~\ref{lst:return} shows the classes and implementation for
179 the return expression.
180
181 \begin{lstlisting}[language=Clean,label={lst:return},%
182 caption={Bytecode view for the return instruction}]
183 class retrn v where
184 retrn :: v () Expr
185
186 instance retrn ByteCode where
187 retrn = tell` [BCReturn]
188 \end{lstlisting}
189
190 \subsection{Shared Data Sources \& Assignment}
191 Fresh \gls{SDS} are generated using the state and constructing one involves
192 multiple steps. First, a fresh identifier is grabbed from the state. Then a
193 \CI{BCShare} record is created with that identifier. A \CI{BCSdsFetch}
194 instruction is written and the body is generated to finally add the \gls{SDS}
195 to the actual state with the value obtained from the function. The exact
196 implementation is shown in Listing~\ref{lst:shareview}. The implementation for
197 the \CI{namedsds} class is exactly the same other than that it stores the given
198 name in the \CI{BCShare} structure as well.
199
200 \begin{lstlisting}[language=Clean,label={lst:shareview},%
201 caption={Bytecode view for \texttt{arith}}]
202 freshshare = get >>= \st=:{freshs}->put {st & freshs=freshs+1} >>| pure freshs
203
204 instance sds ByteCode where
205 sds f = {main = BC (freshshare
206 >>= \sdsi->pure {BCShare|sdsname="",sdsi=sdsi,sdsval=BCValue 0}
207 >>= \sds->pure (f (tell` [BCSdsFetch sds]))
208 >>= \(v In bdy)->modify (addSDS sds v)
209 >>| unBC (unMain bdy))
210 }
211 instance sdspub ByteCode where
212 pub (BC x) = BC (censor (\[BCSdsFetch s]->[BCSdsPublish s]) x)
213
214 addSDS sds v s = {s & sdss=[{sds & sdsval=BCValue v}:s.sdss]}
215 \end{lstlisting}
216
217 All assignable types compile to an \gls{RWST} which writes the specific fetch
218 instruction(s). For example, using an \gls{SDS} always results in % chktex 36
219 an expression of the form \CI{sds \x=4 In ...}. The actual \CI{x} is the
220 \gls{RWST} that always writes one \CI{BCSdsFetch} instruction with the
221 correctly embedded \gls{SDS}. Assigning to an analog pin will result in the
222 \gls{RWST} containing the \CI{BCAnalogRead} instruction. When the operation on
223 the assignable is not a read operation from but an assign operation, the
224 instruction(s) will be rewritten accordingly. This results in a %chktex 36
225 \CI{BCSdsStore} or \CI{BCAnalogWrite} instruction respectively. The
226 implementation for this is given in Listing~\ref{lst:assignmentview}.
227
228 \begin{lstlisting}[language=Clean,label={lst:assignmentview},%
229 caption={Bytecode view implementation for assignment.}]
230 instance assign ByteCode where
231 (=.) (BC v) (BC e) = BC (e >>| censor makeStore v)
232
233 makeStore [BCSdsFetch i] = [BCSdsStore i]
234 makeStore [BCDigitalRead i] = [BCDigitalWrite i]
235 makeStore [...] = [...]
236 \end{lstlisting}
237
238 \subsection{Actual Compilation}
239 All the previous functions are tied together with the \CI{toMessages} function.
240 This function compiles the bytecode and transforms the \gls{Task} to a message.
241 The \glspl{SDS} that were not already sent to the device are also added as
242 messages to be sent to the device. This functionality is shown in
243 Listing~\ref{lst:compilation}. The compilation process consists of two steps.
244 First, the \gls{RWST} is executed. Then, the \emph{Jump} statements that
245 jump to labels are transformed to jump to program memory addresses. The
246 translation of labels to program addresses is straightforward. The function
247 consumes the instructions one by one while incrementing the address counter
248 with the length of the instruction. The generic function \CI{consNum} is used
249 which gives the arity of the constructor. However, when it encounters a
250 \CI{BCLab} instruction, the counter is not increased because the label will not
251 result in an actual instruction. The label is removed and the position of the
252 label is stored in the resulting map. When all labels are removed, the jump
253 instructions are transformed using the \CI{implGotos} function that looks up
254 the correct program address in the map resulting from the aforementioned
255 function. This step is followed by comparing the old compiler state to the new
256 one to find new instantiated \glspl{SDS}. The compilation concludes with
257 converting the bytecode and \glspl{SDS} to actual messages ready to send to the
258 client.
259
260 \begin{lstlisting}[language=Clean,label={lst:compilation},%
261 caption={Actual compilation.}]
262 bclength :: BC -> Int
263 bclength (BCPush s) = 1 + size (toByteCode s)
264 bclength ... = ...
265 bclength x = 1 + consNum{|*|} x
266
267 computeGotos :: [BC] Int -> ([BC], Map Int Int)
268 computeGotos [] _ = ([], newMap)
269 computeGotos [BCLab l:xs] i
270 # (bc, i) = computeGotos xs i
271 = (bc, put l i)
272 computeGotos [x:xs] i
273 # (bc, i) = computeGotos xs (i + bclength x)
274 = ([x:bc], i)
275
276 toRealByteCode :: (ByteCode a b) BCState -> (String, BCState)
277 toRealByteCode x s
278 # (s, bc) = runBC x s
279 # (bc, gtmap) = computeGotos bc 1
280 = (concat (map (toString o toByteVal) (map (implGotos gtmap) bc)), s)
281
282 implGotos map (BCJmp t) = BCJmp $ fromJust (get t map)
283 implGotos map (BCJmpT t) = BCJmpT $ fromJust (get t map)
284 implGotos map (BCJmpF t) = BCJmpF $ fromJust (get t map)
285 implGotos _ i = i
286
287 toMessages :: MTaskInterval (Main (ByteCode a b)) BCState -> ([MTaskMSGSend], BCState)
288 toMessages interval x oldstate
289 # (bc, newstate) = toRealByteCode (unMain x) oldstate
290 # newsdss = difference newstate.sdss oldstate.sdss
291 = ([MTSds sdsi e\\{sdsi,sdsval=e}<-newsdss] ++ [MTTask interval bc], newstate)
292 \end{lstlisting}