2 Copyright (c) 2009, ETH Zurich.
5 This file is distributed under the terms in the attached LICENSE file.
6 If you do not find this file, copies can be found by writing to:
7 ETH Zurich D-INFK, Haldeneggsteig 4, CH-8092 Zurich. Attn: Systems Group.
14 > module IL.Paka.Builders where
16 > import Text.PrettyPrint.HughesPJ hiding (first)
17 > import qualified Data.Map as Map
20 > import PureExpressions
22 > import IL.Paka.Syntax
26 \section{Paka building blocks}
28 I'm particularly proud of the Paka code generation architecture. To
29 build a Paka term, we simply call some builders functions which are
30 chained up together with the |#| operator. These builders take care of
31 inserting the definitions in the right place in |PakaCode|,
32 |PakaIntra|, or sequentially extend the |ILPaka| code. Thanks to that
33 machinery, we don't have to explicitly build these data-structures, we
36 Hence, a builder is just putting a brick in the |PakaBuilding| wall:
38 > type PakaBuilding = (ILPaka -> ILPaka, PakaCode, PakaIntra)
40 That is, operations taking some arguments and extending a
41 |PakaBuilding| into a new one.
44 \subsection{Low-level machinery}
46 To give a feeling of ``sequential code'', the |#| operator is simply
47 an inversed composition operation:
49 > f # g = \x -> g (f x)
51 Using |#|, we will compose our builders with a sequential feeling.
53 Because most, if not all, operations modify one element of the
54 |PakaBuilding| triple, we define the following combinators:
56 > first :: (a -> b) -> (a, c, d) -> (b, c, d)
57 > first f (a,b,c) = (f a, b, c)
59 > second :: (a -> b) -> (c, a, d) -> (c, b, d)
60 > second f (a,b,c) = (a, f b, c)
62 > third :: (a -> b) -> (c, d, a) -> (c, d, b)
63 > third f (a,b,c) = (a,b,f c)
66 \subsection{Building |PakaCode|}
68 We can add new C includes:
70 > include :: String -> PakaBuilding -> PakaBuilding
71 > include id = second $ include' id
72 > where include' id globalEnv
73 > = case id `Map.lookup` incls of
74 > Nothing -> globalEnv { includes = Map.insert id decl incls }
76 > where incls = includes globalEnv
77 > decl = text "#include" <+> text id
79 We can declare new C types:
81 > declare :: String -> Doc -> Doc -> PakaBuilding -> PakaBuilding
82 > declare id typ decl = second $ declare' id typ decl
83 > where declare' id typ decl globalEnv =
84 > case id `Map.lookup` typs of
85 > Nothing -> globalEnv { declarations = (id,decl) : decls,
86 > types = Map.insert id typ typs }
88 > where decls = declarations globalEnv
89 > typs = types globalEnv
91 We can declare global variables:
93 > globalVar :: String -> Doc -> PakaBuilding -> PakaBuilding
94 > globalVar id def = second $ globalVar' id def
95 > where globalVar' id def globalEnv =
96 > case id `lookup` vars of
97 > Nothing -> globalEnv { globalVars = (id,def) : vars }
99 > where vars = globalVars globalEnv
101 We can add function prototypes:
103 > prototype :: String -> Doc -> PakaBuilding -> PakaBuilding
104 > prototype id proto = second $ prototype' id proto
105 > where prototype' id proto globalEnv =
106 > case id `Map.lookup` protos of
107 > Nothing -> globalEnv { prototypes = Map.insert id proto protos }
108 > Just _ -> globalEnv
109 > where protos = prototypes globalEnv
111 And we can define new functions:
113 > function :: Doc -> Doc -> String -> Doc -> PakaIntra -> ILPaka -> PakaBuilding -> PakaBuilding
114 > function returnT attrs funName funArgs lEnv body =
115 > second $ function' returnT attrs funName funArgs lEnv body
116 > where function' returnT attrs funName funArgs lEnv body gEnv =
117 > case funName `Map.lookup` functions' of
118 > Nothing -> gEnv { functions = Map.insert funName (returnT, attrs, funName, funArgs, lEnv, body) functions' }
120 > where functions' = functions gEnv
123 \subsection{Building |PakaIntra|}
125 As for global variables in the |PakaCode|, we can add local variables
126 in the |PakaIntra| environment:
128 > localVar :: String -> Doc -> PakaBuilding -> PakaBuilding
129 > localVar id def = third $ localVar' id def
130 > where localVar' id def localEnv
131 > = case id `Map.lookup` vars of
132 > Nothing -> localEnv { localVars = Map.insert id def vars }
134 > where vars = localVars localEnv
136 And we can bring a constant in the |PakaIntra|:
138 > constant :: PureExpr -> PakaBuilding -> PakaBuilding
139 > constant e = third $ constant' e
140 > where constant' e lEnv = lEnv { expr = Just e }
142 \subsection{Building |ILPaka|}
144 Obviously, the serious stuff happens in |ILPaka|, or more precisely
145 |ILPaka -> ILPaka|: this code is seriously continuation-passing. The
146 plan is that we want to build a |ILPaka| value. However, we note that,
147 for instance, to build a |PStatement| value, we need to know the
148 remaining code. But we don't know it yet, as we are compiling it! So,
149 we return a continuation that waits for that uncompiled chunk and plug
150 it in the right place. Continuation-passing style, yay!
152 As an example of that technique in action, take a look at |instr| and
153 |assgn| below. Apart from that CPS detail, they are computationally
154 trivial, bringing their arguments in the right place of the
155 constructor and returning by calling the continuation.
157 > instr :: Term -> [PakaVarName] -> PakaBuilding -> PakaBuilding
158 > instr instruction vars = first $ instr' instruction vars
159 > where instr' instruction varNames k
161 > k $ PStatement (PInstruction instruction varNames) c
163 > assgn :: PakaVarName -> Term -> [PakaVarName] -> PakaBuilding -> PakaBuilding
164 > assgn wVarName assgnmt rVarNames = first $ assgn' wVarName assgnmt rVarNames
165 > where assgn' wVarName assgnmt rVarNames k
167 > k $ PStatement (PAssign wVarName assgnmt rVarNames) c
169 As you can expect, we need to stop ``continuating'' at some
170 point. This naturally fits with the role of closing terms:
172 > close :: PakaClosing -> PakaBuilding -> PakaBuilding
173 > close c = first $ close' c
174 > where close' c = \k _ -> k (PClosing c)
176 Similarly, the control-flow operators closes all their branches and
177 only continue downward:
179 > pif :: ILPaka -> PureExpr -> ILPaka -> ILPaka -> PakaBuilding -> PakaBuilding
180 > pif cond test ifTrue ifFalse = first $ pif' cond test ifTrue ifFalse
181 > where pif' cond test ifTrue ifFalse cont = \c ->
182 > cont $ PIf cond test ifTrue ifFalse c
184 > pwhile :: ILPaka -> PureExpr -> ILPaka -> PakaBuilding -> PakaBuilding
185 > pwhile cond test loop = first $ pwhile' cond test loop
186 > where pwhile' cond test loop cont = \c ->
187 > cont $ PWhile cond test loop c
189 > pdoWhile :: ILPaka -> ILPaka -> PureExpr -> PakaBuilding -> PakaBuilding
190 > pdoWhile loop cond test = first $ pdoWhile' loop cond test
191 > where pdoWhile' loop cond test cont = \c ->
192 > cont $ PDoWhile loop cond test c
194 > pswitch :: PureExpr -> [(PureExpr,ILPaka)] -> ILPaka -> PakaBuilding -> PakaBuilding
195 > pswitch test cases defaultCase = first $ pswitch' test cases defaultCase
196 > where pswitch' test cases defaultCase cont = \c ->
197 > cont $ PSwitch test cases defaultCase c