SCM Repository
Annotation of /branches/vis12/src/compiler/cl-target/cl-target.sml
Parent Directory
|
Revision Log
Revision 1870 - (view) (download)
1 : | jhr | 1671 | (* cl-target.sml |
2 : | * | ||
3 : | * COPYRIGHT (c) 2011 The Diderot Project (http://diderot-language.cs.uchicago.edu) | ||
4 : | * All rights reserved. | ||
5 : | *) | ||
6 : | |||
7 : | structure CLTarget : TARGET = | ||
8 : | struct | ||
9 : | |||
10 : | structure IL = TreeIL | ||
11 : | structure V = IL.Var | ||
12 : | structure Ty = IL.Ty | ||
13 : | structure CL = CLang | ||
14 : | structure RN = RuntimeNames | ||
15 : | jhr | 1853 | structure N = CNames |
16 : | jhr | 1671 | structure ToCL = TreeToCL |
17 : | structure P = Paths | ||
18 : | structure HF = CLHeaderFrag | ||
19 : | structure SF = CLSchedFrag | ||
20 : | |||
21 : | (* revmap f l == List.rev(List.map f l) *) | ||
22 : | fun revmap f = let | ||
23 : | fun rmap ([], l) = l | ||
24 : | | rmap (x::r, l) = rmap (r, f x :: l) | ||
25 : | in | ||
26 : | fn l => rmap (l, []) | ||
27 : | end | ||
28 : | |||
29 : | (* common arithmetic *) | ||
30 : | fun #+# (a, b) = CL.mkBinOp(a, CL.#+, b) | ||
31 : | fun #*# (a, b) = CL.mkBinOp(a, CL.#*, b) | ||
32 : | infix 5 #+# | ||
33 : | infix 6 #*# | ||
34 : | |||
35 : | (* translate TreeIL types to shadow types *) | ||
36 : | fun shadowTy ty = (case ty | ||
37 : | of Ty.BoolTy => CL.T_Named "cl_uint" | ||
38 : | | Ty.IntTy => CL.T_Named(RN.shadowIntTy ()) | ||
39 : | | Ty.TensorTy[] => CL.T_Named(RN.shadowRealTy ()) | ||
40 : | | Ty.TensorTy[n] => CL.T_Named(RN.shadowVecTy n) | ||
41 : | | Ty.TensorTy[n, m] => CL.T_Named(RN.shadowMatTy(n,m)) | ||
42 : | jhr | 1793 | | Ty.ImageTy info => CL.T_Named(RN.shadowImageTy(ImageInfo.dim info)) |
43 : | jhr | 1671 | | _ => raise Fail(concat["TreeToC.trType(", Ty.toString ty, ")"]) |
44 : | (* end case *)) | ||
45 : | |||
46 : | (* FIXME: add comments that more clearly explain the difference between convertToShadow and | ||
47 : | * convertStrandToShadow | ||
48 : | *) | ||
49 : | (* translate TreeIL types to shadow types *) | ||
50 : | fun convertToShadow (ty, name) = (case ty | ||
51 : | of Ty.IntTy => CL.mkAssign( | ||
52 : | CL.mkSelect(CL.mkVar RN.shadowGlaobalsName, name), | ||
53 : | CL.mkIndirect(CL.mkVar RN.globalsVarName, name)) | ||
54 : | | Ty.TensorTy[n]=> CL.mkCall(RN.convertToShadowVec n, [ | ||
55 : | CL.mkUnOp(CL.%&, CL.mkSelect(CL.mkVar RN.shadowGlaobalsName, name)), | ||
56 : | CL.mkIndirect(CL.mkVar RN.globalsVarName, name) | ||
57 : | ]) | ||
58 : | jhr | 1793 | | Ty.ImageTy info => CL.mkCall(RN.shadowImageFunc(ImageInfo.dim info), [ |
59 : | jhr | 1671 | CL.mkVar "context", |
60 : | CL.mkUnOp(CL.%&, CL.mkSelect(CL.mkVar RN.shadowGlaobalsName, name)), | ||
61 : | CL.mkIndirect(CL.mkVar RN.globalsVarName, name) | ||
62 : | ]) | ||
63 : | | Ty.TensorTy[n, m] => CL.mkCall(RN.convertToShadowMat(m,n), [ | ||
64 : | CL.mkSelect(CL.mkVar RN.shadowGlaobalsName, name), | ||
65 : | CL.mkIndirect(CL.mkVar RN.globalsVarName, name) | ||
66 : | ]) | ||
67 : | | _ => CL.mkAssign( | ||
68 : | CL.mkSelect(CL.mkVar RN.shadowGlaobalsName,name), | ||
69 : | CL.mkIndirect(CL.mkVar RN.globalsVarName, name)) | ||
70 : | (* end case *)) | ||
71 : | |||
72 : | (* generate code to convert strand TreeIL types to shadow types *) | ||
73 : | fun convertStrandToShadow (ty, name, selfIn, selfOut) = (case ty | ||
74 : | of Ty.IntTy => CL.mkAssign( | ||
75 : | CL.mkIndirect(CL.mkVar selfIn, name), | ||
76 : | CL.mkIndirect(CL.mkVar selfOut, name)) | ||
77 : | | Ty.TensorTy[n]=> CL.mkCall(RN.convertToShadowVec n, [ | ||
78 : | CL.mkUnOp(CL.%&, CL.mkIndirect(CL.mkVar selfIn, name)), | ||
79 : | CL.mkIndirect(CL.mkVar selfOut, name) | ||
80 : | ]) | ||
81 : | | Ty.TensorTy[n, m] => CL.mkCall(RN.convertToShadowMat(m,n), [ | ||
82 : | CL.mkUnOp(CL.%&, CL.mkIndirect(CL.mkVar selfIn, name)), | ||
83 : | CL.mkIndirect(CL.mkVar selfOut, name) | ||
84 : | ]) | ||
85 : | | _ => CL.mkAssign( | ||
86 : | CL.mkIndirect(CL.mkVar selfIn, name), | ||
87 : | CL.mkIndirect(CL.mkVar selfOut, name)) | ||
88 : | (* end case *)) | ||
89 : | |||
90 : | (* helper functions for specifying parameters in various address spaces *) | ||
91 : | jhr | 1853 | fun clParam spc (ty, x) = CL.PARAM([spc], ty, x) |
92 : | val globalParam = clParam "__global" | ||
93 : | val constantParam = clParam "__constant" | ||
94 : | val localParam = clParam "__local" | ||
95 : | val privateParam = clParam "__private" | ||
96 : | jhr | 1671 | |
97 : | (* OpenCL global pointer type *) | ||
98 : | fun globalPtr ty = CL.T_Qual("__global", CL.T_Ptr ty) | ||
99 : | |||
100 : | (* lvalue/rvalue state variable *) | ||
101 : | fun lvalueSV name = CL.mkIndirect(CL.mkVar "selfOut", name) | ||
102 : | fun rvalueSV name = CL.mkIndirect(CL.mkVar "selfIn", name) | ||
103 : | |||
104 : | (* C variable translation *) | ||
105 : | structure TrCVar = | ||
106 : | struct | ||
107 : | type env = CL.typed_var TreeIL.Var.Map.map | ||
108 : | fun lookup (env, x) = (case V.Map.find (env, x) | ||
109 : | of SOME(CL.V(_, x')) => x' | ||
110 : | | NONE => raise Fail(concat["TrCVar.lookup(_, ", V.name x, ")"]) | ||
111 : | (* end case *)) | ||
112 : | (* translate a variable that occurs in an l-value context (i.e., as the target of an assignment) *) | ||
113 : | fun lvalueVar (env, x) = (case V.kind x | ||
114 : | jhr | 1706 | of IL.VK_Local => CL.mkVar(lookup(env, x)) |
115 : | | _ => CL.mkIndirect(CL.mkVar RN.globalsVarName, lookup(env, x)) | ||
116 : | jhr | 1671 | (* end case *)) |
117 : | (* translate a variable that occurs in an r-value context *) | ||
118 : | fun rvalueVar (env, x) = (case V.kind x | ||
119 : | jhr | 1706 | of IL.VK_Local => CL.mkVar(lookup(env, x)) |
120 : | | _ => CL.mkIndirect(CL.mkVar RN.globalsVarName, lookup(env, x)) | ||
121 : | jhr | 1671 | (* end case *)) |
122 : | (* translate a strand state variable that occurs in an l-value context *) | ||
123 : | fun lvalueStateVar (IL.SV{name, ...}) = lvalueSV name | ||
124 : | (* translate a strand state variable that occurs in an r-value context *) | ||
125 : | fun rvalueStateVar (IL.SV{name, ...}) = rvalueSV name | ||
126 : | end | ||
127 : | |||
128 : | structure ToC = TreeToCFn (TrCVar) | ||
129 : | |||
130 : | type var = CL.typed_var | ||
131 : | type exp = CL.exp | ||
132 : | type stm = CL.stm | ||
133 : | |||
134 : | (* OpenCL specific types *) | ||
135 : | val clIntTy = CL.T_Named "cl_int" | ||
136 : | val clProgramTy = CL.T_Named "cl_program" | ||
137 : | val clKernelTy = CL.T_Named "cl_kernel" | ||
138 : | val clCmdQueueTy = CL.T_Named "cl_command_queue" | ||
139 : | val clContextTy = CL.T_Named "cl_context" | ||
140 : | val clDeviceIdTy = CL.T_Named "cl_device_id" | ||
141 : | val clPlatformIdTy = CL.T_Named "cl_platform_id" | ||
142 : | val clMemoryTy = CL.T_Named "cl_mem" | ||
143 : | val globPtrTy = CL.T_Ptr(CL.T_Named RN.globalsTy) | ||
144 : | (* FIXME: what are these for? *) | ||
145 : | datatype shadow_env = STRAND_SHADOW | GLOBAL_SHADOW | ||
146 : | |||
147 : | (* variable or field that is mirrored between host and GPU *) | ||
148 : | type mirror_var = { | ||
149 : | (* FIXME: perhaps it would be cleaner to just track the TreeIL type of the variable? *) | ||
150 : | hostTy : CL.ty, (* variable type on Host (i.e., C type) *) | ||
151 : | shadowTy : CL.ty, (* host-side shadow type of GPU type *) | ||
152 : | gpuTy : CL.ty, (* variable's type on GPU (i.e., OpenCL type) *) | ||
153 : | hToS: stm, (* the statement that converts the variable to its *) | ||
154 : | (* shadow representation *) | ||
155 : | var : CL.var (* variable name *) | ||
156 : | } | ||
157 : | |||
158 : | datatype strand = Strand of { | ||
159 : | name : string, | ||
160 : | tyName : string, | ||
161 : | state : mirror_var list, | ||
162 : | output : (Ty.ty * CL.var), (* the strand's output variable (only one for now) *) | ||
163 : | code : CL.decl list ref, | ||
164 : | init_code: CL.decl ref | ||
165 : | } | ||
166 : | |||
167 : | datatype program = Prog of { | ||
168 : | jhr | 1705 | tgt : TargetUtil.target_desc, (* info about target *) |
169 : | jhr | 1671 | globals : mirror_var list ref, |
170 : | topDecls : CL.decl list ref, | ||
171 : | strands : strand AtomTable.hash_table, | ||
172 : | initially : CL.decl ref, | ||
173 : | numDims: int ref, (* number of dimensions in initially iteration *) | ||
174 : | imgGlobals: (string * int) list ref, | ||
175 : | prFn: CL.decl ref, | ||
176 : | outFn: CL.decl ref | ||
177 : | } | ||
178 : | |||
179 : | datatype env = ENV of { | ||
180 : | info : env_info, | ||
181 : | vMap : var V.Map.map, | ||
182 : | scope : scope | ||
183 : | } | ||
184 : | |||
185 : | and env_info = INFO of { | ||
186 : | prog : program | ||
187 : | } | ||
188 : | |||
189 : | and scope | ||
190 : | = NoScope | ||
191 : | | GlobalScope | ||
192 : | | InitiallyScope | ||
193 : | | StrandScope (* strand initialization *) | ||
194 : | | MethodScope of StrandUtil.method_name (* method body; vars are state variables *) | ||
195 : | |||
196 : | (* the supprted widths of vectors of reals on the target. *) | ||
197 : | (* FIXME: for OpenCL 1.1, 3 is also valid *) | ||
198 : | fun vectorWidths () = [2, 4, 8, 16] | ||
199 : | |||
200 : | (* we do not support printing on the OpenCL target *) | ||
201 : | val supportsPrinting = false | ||
202 : | |||
203 : | (* tests for whether various expression forms can appear inline *) | ||
204 : | fun inlineCons n = (n < 2) (* vectors are inline, but not matrices *) | ||
205 : | val inlineMatrixExp = false (* can matrix-valued expressions appear inline? *) | ||
206 : | |||
207 : | (* TreeIL to target translations *) | ||
208 : | structure Tr = | ||
209 : | struct | ||
210 : | fun fragment (ENV{info, vMap, scope}, blk) = let | ||
211 : | val (vMap, stms) = (case scope | ||
212 : | of GlobalScope => ToC.trFragment (vMap, blk) | ||
213 : | | InitiallyScope => ToC.trFragment (vMap, blk) | ||
214 : | | _ => ToCL.trFragment (vMap, blk) | ||
215 : | (* end case *)) | ||
216 : | in | ||
217 : | (ENV{info=info, vMap=vMap, scope=scope}, stms) | ||
218 : | end | ||
219 : | fun block (ENV{vMap, scope, ...}, blk) = (case scope | ||
220 : | of StrandScope => ToC.trBlock (vMap, blk) | ||
221 : | | MethodScope name => ToCL.trBlock (vMap, blk) | ||
222 : | | InitiallyScope => ToCL.trBlock (vMap, blk) | ||
223 : | | _ => ToC.trBlock (vMap, blk) | ||
224 : | (* end case *)) | ||
225 : | nseltzer | 1870 | fun free (ENV{vMap, ...}, blk) = ToC.trFree (vMap, blk) |
226 : | jhr | 1671 | fun exp (ENV{vMap, ...}, e) = ToCL.trExp(vMap, e) |
227 : | end | ||
228 : | |||
229 : | (* variables *) | ||
230 : | structure Var = | ||
231 : | struct | ||
232 : | fun mirror (ty, name, shadowEnv) = { | ||
233 : | hostTy = ToC.trType ty, | ||
234 : | shadowTy = shadowTy ty, | ||
235 : | gpuTy = ToCL.trType ty, | ||
236 : | hToS = case shadowEnv | ||
237 : | of GLOBAL_SHADOW => convertToShadow (ty, name) | ||
238 : | | STRAND_SHADOW => convertStrandToShadow(ty, name, "selfIn", "selfOut") | ||
239 : | (* end case *), | ||
240 : | var = name | ||
241 : | } | ||
242 : | fun name (ToCL.V(_, name)) = name | ||
243 : | fun global (Prog{globals, imgGlobals, ...}, name, ty) = let | ||
244 : | val x = mirror (ty, name, GLOBAL_SHADOW) | ||
245 : | jhr | 1793 | fun isImgGlobal (Ty.ImageTy info, name) = |
246 : | imgGlobals := (name, ImageInfo.dim info) :: !imgGlobals | ||
247 : | jhr | 1671 | | isImgGlobal _ = () |
248 : | in | ||
249 : | globals := x :: !globals; | ||
250 : | isImgGlobal (ty, name); | ||
251 : | ToCL.V(#gpuTy x, name) | ||
252 : | end | ||
253 : | fun param x = ToCL.V(ToCL.trType(V.ty x), V.name x) | ||
254 : | end | ||
255 : | |||
256 : | (* environments *) | ||
257 : | structure Env = | ||
258 : | struct | ||
259 : | (* create a new environment *) | ||
260 : | fun new prog = ENV{ | ||
261 : | info=INFO{prog = prog}, | ||
262 : | vMap = V.Map.empty, | ||
263 : | scope = NoScope | ||
264 : | } | ||
265 : | (* define the current translation context *) | ||
266 : | fun setScope scope (ENV{info, vMap, ...}) = ENV{info=info, vMap=vMap, scope=scope} | ||
267 : | val scopeGlobal = setScope GlobalScope | ||
268 : | val scopeInitially = setScope InitiallyScope | ||
269 : | fun scopeStrand env = setScope StrandScope env | ||
270 : | fun scopeMethod (env, name) = setScope (MethodScope name) env | ||
271 : | (* bind a TreeIL varaiable to a target variable *) | ||
272 : | fun bind (ENV{info, vMap, scope}, x, x') = ENV{ | ||
273 : | info = info, | ||
274 : | vMap = V.Map.insert(vMap, x, x'), | ||
275 : | scope = scope | ||
276 : | } | ||
277 : | end | ||
278 : | |||
279 : | jhr | 1853 | (* strands *) |
280 : | structure Strand = | ||
281 : | struct | ||
282 : | |||
283 : | fun define (Prog{strands, ...}, strandId, state) = let | ||
284 : | val name = Atom.toString strandId | ||
285 : | (* the output state variable *) | ||
286 : | val outputVar = (case List.filter IL.StateVar.isOutput state | ||
287 : | of [] => raise Fail("no output specified for strand " ^ name) | ||
288 : | | [x] => (IL.StateVar.ty x, IL.StateVar.name x) | ||
289 : | | _ => raise Fail("multiple outputs in " ^ name) | ||
290 : | (* end case *)) | ||
291 : | (* the state variables *) | ||
292 : | val state = let | ||
293 : | fun cvt x = Var.mirror (IL.StateVar.ty x, IL.StateVar.name x, STRAND_SHADOW) | ||
294 : | in | ||
295 : | List.map cvt state | ||
296 : | end | ||
297 : | val strand = Strand{ | ||
298 : | name = name, | ||
299 : | tyName = RN.strandTy name, | ||
300 : | state = state, | ||
301 : | output = outputVar, | ||
302 : | code = ref [], | ||
303 : | init_code = ref (CL.D_Comment(["no init code"])) | ||
304 : | } | ||
305 : | in | ||
306 : | AtomTable.insert strands (strandId, strand); | ||
307 : | strand | ||
308 : | end | ||
309 : | |||
310 : | (* return the strand with the given name *) | ||
311 : | fun lookup (Prog{strands, ...}, strandId) = AtomTable.lookup strands strandId | ||
312 : | |||
313 : | (* register the strand-state initialization code. The variables are the strand | ||
314 : | * parameters. | ||
315 : | *) | ||
316 : | fun init (Strand{name, tyName, code, init_code, ...}, params, init) = let | ||
317 : | val fName = RN.strandInit name | ||
318 : | val params = | ||
319 : | clParam "" (CL.T_Ptr(CL.T_Named tyName), "selfOut") :: | ||
320 : | List.map (fn (ToCL.V(ty, x)) => CL.PARAM([], ty, x)) params | ||
321 : | val initFn = CL.D_Func([], CL.voidTy, fName, params, init) | ||
322 : | in | ||
323 : | init_code := initFn | ||
324 : | end | ||
325 : | |||
326 : | (* register a strand method *) | ||
327 : | fun method (Strand{name, tyName, code,...}, methName, body) = let | ||
328 : | val params = [ | ||
329 : | globalParam (CL.T_Ptr(CL.T_Named tyName), "selfIn"), | ||
330 : | globalParam (CL.T_Ptr(CL.T_Named tyName), "selfOut"), | ||
331 : | globalParam (CL.T_Ptr(CL.T_Named (RN.globalsTy)), RN.globalsVarName), | ||
332 : | clParam "" (CL.T_Named(RN.imageDataType), RN.globalImageDataName) | ||
333 : | ] | ||
334 : | val (fName,resTy) = (case methName | ||
335 : | of StrandUtil.Update => (RN.strandUpdate,CL.T_Named "StrandStatus_t") | ||
336 : | | StrandUtil.Stabilize => (name ^ StrandUtil.nameToString methName, CL.voidTy) | ||
337 : | (* end case *)) | ||
338 : | val methFn = CL.D_Func([], resTy, fName, params, body) | ||
339 : | in | ||
340 : | code := methFn :: !code | ||
341 : | end | ||
342 : | |||
343 : | end (* Strand *) | ||
344 : | |||
345 : | jhr | 1671 | (* programs *) |
346 : | structure Program = | ||
347 : | struct | ||
348 : | jhr | 1705 | fun new (tgt : TargetUtil.target_desc) = ( |
349 : | RN.initTargetSpec (#double tgt); | ||
350 : | CNames.initTargetSpec {double = #double tgt, long = false}; | ||
351 : | jhr | 1671 | Prog{ |
352 : | jhr | 1705 | tgt = tgt, |
353 : | jhr | 1671 | globals = ref [], |
354 : | topDecls = ref [], | ||
355 : | strands = AtomTable.mkTable (16, Fail "strand table"), | ||
356 : | initially = ref(CL.D_Comment["missing initially"]), | ||
357 : | numDims = ref 0, | ||
358 : | imgGlobals = ref[], | ||
359 : | prFn = ref(CL.D_Comment(["No Print Function"])), | ||
360 : | outFn = ref(CL.D_Comment(["No Output Function"])) | ||
361 : | }) | ||
362 : | |||
363 : | (* register the code that is used to register command-line options for input variables *) | ||
364 : | jhr | 1803 | fun inputs (Prog{topDecls, ...}, env, blk) = let |
365 : | jhr | 1671 | val inputsFn = CL.D_Func( |
366 : | [], CL.voidTy, RN.registerOpts, | ||
367 : | [CL.PARAM([], CL.T_Ptr(CL.T_Named RN.optionsTy), "opts")], | ||
368 : | jhr | 1803 | Tr.block (env, blk)) |
369 : | jhr | 1671 | in |
370 : | topDecls := inputsFn :: !topDecls | ||
371 : | end | ||
372 : | |||
373 : | (* register the global initialization part of a program *) | ||
374 : | fun init (Prog{topDecls, ...}, init) = let | ||
375 : | val globalsDecl = CL.mkAssign(CL.mkVar RN.globalsVarName, | ||
376 : | CL.mkApply("malloc", [CL.mkSizeof(CL.T_Named RN.globalsTy)])) | ||
377 : | val initFn = CL.D_Func( | ||
378 : | [], CL.voidTy, RN.initGlobals, [], | ||
379 : | CL.mkBlock[ | ||
380 : | globalsDecl, | ||
381 : | CL.mkCall(RN.initGlobalsHelper, [CL.mkVar RN.globalsVarName]) | ||
382 : | ]) | ||
383 : | val initHelperFn = CL.D_Func( | ||
384 : | [], CL.voidTy, RN.initGlobalsHelper, | ||
385 : | [CL.PARAM([], globPtrTy, RN.globalsVarName)], | ||
386 : | init) | ||
387 : | val shutdownFn = CL.D_Func( | ||
388 : | [], CL.voidTy, RN.shutdown, | ||
389 : | [CL.PARAM([], CL.T_Ptr(CL.T_Named RN.worldTy), "wrld")], | ||
390 : | CL.S_Block[]) | ||
391 : | in | ||
392 : | topDecls := shutdownFn :: initFn :: initHelperFn :: !topDecls | ||
393 : | end | ||
394 : | nseltzer | 1870 | (* register the global destruction part of a program *) |
395 : | fun free (Prog{tgt, topDecls, ...}, free) = let | ||
396 : | val worldTy = CL.T_Ptr(CL.T_Named(N.worldTy tgt)) | ||
397 : | val globTy = CL.T_Ptr(CL.T_Named(N.globalTy tgt)) | ||
398 : | val free = CL.mkBlock( | ||
399 : | CL.mkDeclInit(globTy, "glob", CL.mkIndirect(CL.mkVar "wrld", "globals")) :: | ||
400 : | CL.unBlock free @ [CL.mkReturn(SOME(CL.mkVar "false"))]) | ||
401 : | val freeFn = CL.D_Func( | ||
402 : | ["static"], CL.boolTy, N.freeGlobals, | ||
403 : | [CL.PARAM([], worldTy, "wrld")], | ||
404 : | free) | ||
405 : | in | ||
406 : | topDecls := freeFn :: !topDecls | ||
407 : | end | ||
408 : | jhr | 1671 | |
409 : | (* create and register the initially function for a program *) | ||
410 : | fun initially { | ||
411 : | jhr | 1718 | prog = Prog{tgt, strands, initially, numDims, ...}, |
412 : | jhr | 1671 | isArray : bool, |
413 : | iterPrefix : stm list, | ||
414 : | iters : (var * exp * exp) list, | ||
415 : | createPrefix : stm list, | ||
416 : | strand : Atom.atom, | ||
417 : | args : exp list | ||
418 : | } = let | ||
419 : | val name = Atom.toString strand | ||
420 : | val nDims = List.length iters | ||
421 : | jhr | 1718 | val worldTy = CL.T_Ptr(CL.T_Named(N.worldTy tgt)) |
422 : | jhr | 1671 | fun mapi f xs = let |
423 : | fun mapf (_, []) = [] | ||
424 : | | mapf (i, x::xs) = f(i, x) :: mapf(i+1, xs) | ||
425 : | in | ||
426 : | mapf (0, xs) | ||
427 : | end | ||
428 : | val baseInit = mapi (fn (i, (_, e, _)) => (i, CL.I_Exp e)) iters | ||
429 : | val sizeInit = mapi | ||
430 : | (fn (i, (CL.V(ty, _), lo, hi)) => | ||
431 : | (i, CL.I_Exp(CL.mkBinOp(hi, CL.#-, lo) #+# CL.mkIntTy(1, ty))) | ||
432 : | ) iters | ||
433 : | (* code to allocate the world and initial strands *) | ||
434 : | val wrld = "wrld" | ||
435 : | val allocCode = [ | ||
436 : | CL.mkComment["allocate initial block of strands"], | ||
437 : | CL.mkDecl(CL.T_Array(CL.int32, SOME nDims), "base", SOME(CL.I_Array baseInit)), | ||
438 : | CL.mkDecl(CL.T_Array(CL.uint32, SOME nDims), "size", SOME(CL.I_Array sizeInit)), | ||
439 : | CL.mkDecl(worldTy, wrld, | ||
440 : | SOME(CL.I_Exp(CL.mkApply(N.allocInitially, [ | ||
441 : | CL.mkVar "ProgramName", | ||
442 : | CL.mkUnOp(CL.%&, CL.mkVar(N.strandDesc name)), | ||
443 : | CL.mkBool isArray, | ||
444 : | CL.mkIntTy(IntInf.fromInt nDims, CL.int32), | ||
445 : | CL.mkVar "base", | ||
446 : | CL.mkVar "size" | ||
447 : | ])))) | ||
448 : | ] | ||
449 : | (* create the loop nest for the initially iterations *) | ||
450 : | val indexVar = "ix" | ||
451 : | val strandTy = CL.T_Ptr(CL.T_Named(N.strandTy name)) | ||
452 : | fun mkLoopNest [] = CL.mkBlock(createPrefix @ [ | ||
453 : | CL.mkDecl(strandTy, "sp", | ||
454 : | SOME(CL.I_Exp( | ||
455 : | CL.mkCast(strandTy, | ||
456 : | CL.mkApply(N.inState, [CL.mkVar "wrld", CL.mkVar indexVar]))))), | ||
457 : | CL.mkCall(N.strandInit name, CL.mkVar "sp" :: args), | ||
458 : | CL.mkAssign(CL.mkVar indexVar, CL.mkVar indexVar #+# CL.mkIntTy(1, CL.uint32)) | ||
459 : | ]) | ||
460 : | | mkLoopNest ((CL.V(ty, param), lo, hi)::iters) = let | ||
461 : | val body = mkLoopNest iters | ||
462 : | in | ||
463 : | CL.mkFor( | ||
464 : | [(ty, param, lo)], | ||
465 : | CL.mkBinOp(CL.mkVar param, CL.#<=, hi), | ||
466 : | [CL.mkPostOp(CL.mkVar param, CL.^++)], | ||
467 : | body) | ||
468 : | end | ||
469 : | val iterCode = [ | ||
470 : | CL.mkComment["initially"], | ||
471 : | CL.mkDecl(CL.uint32, indexVar, SOME(CL.I_Exp(CL.mkIntTy(0, CL.uint32)))), | ||
472 : | mkLoopNest iters | ||
473 : | ] | ||
474 : | val body = CL.mkBlock( | ||
475 : | iterPrefix @ | ||
476 : | allocCode @ | ||
477 : | iterCode @ | ||
478 : | [CL.mkReturn(SOME(CL.mkVar "wrld"))]) | ||
479 : | jhr | 1718 | val initFn = CL.D_Func([], worldTy, N.initially tgt, [], body) |
480 : | jhr | 1671 | in |
481 : | numDims := nDims; | ||
482 : | initially := initFn | ||
483 : | end | ||
484 : | |||
485 : | |||
486 : | (***** OUTPUT *****) | ||
487 : | |||
488 : | fun genStrandPrint (Strand{name, tyName, state, output, code, ...}) = let | ||
489 : | (* the print function *) | ||
490 : | val prFnName = concat[name, "Print"] | ||
491 : | val prFn = let | ||
492 : | val params = [ | ||
493 : | CL.PARAM([], CL.T_Ptr(CL.T_Named "FILE"), "outS"), | ||
494 : | CL.PARAM([], CL.T_Ptr(CL.T_Named(RN.strandShadowTy tyName)), "self") | ||
495 : | ] | ||
496 : | val (ty, x) = output | ||
497 : | val outState = CL.mkIndirect(CL.mkVar "self", x) | ||
498 : | val prArgs = (case ty | ||
499 : | of Ty.IntTy => [CL.mkStr(!N.gIntFormat ^ "\n"), outState] | ||
500 : | | Ty.SeqTy(Ty.IntTy, d) => let | ||
501 : | fun sel i = CL.mkApply( | ||
502 : | "VSUB", | ||
503 : | [outState, CL.mkInt(IntInf.fromInt i)]) | ||
504 : | val fmt = CL.mkStr( | ||
505 : | String.concatWith " " (List.tabulate(d, fn _ => !N.gIntFormat)) | ||
506 : | ^ "\n") | ||
507 : | val args = List.tabulate (d, sel) | ||
508 : | in | ||
509 : | fmt :: args | ||
510 : | end | ||
511 : | | Ty.TensorTy[] => [CL.mkStr "%f\n", outState] | ||
512 : | | Ty.TensorTy[d] => let | ||
513 : | fun sel i = CL.mkApply( | ||
514 : | "VSUB", | ||
515 : | [outState, CL.mkInt(IntInf.fromInt i)]) | ||
516 : | val fmt = CL.mkStr( | ||
517 : | String.concatWith " " (List.tabulate(d, fn _ => "%f")) | ||
518 : | ^ "\n") | ||
519 : | val args = List.tabulate (d, sel) | ||
520 : | in | ||
521 : | fmt :: args | ||
522 : | end | ||
523 : | | _ => raise Fail("genStrand: unsupported output type " ^ Ty.toString ty) | ||
524 : | (* end case *)) | ||
525 : | in | ||
526 : | CL.D_Func(["static"], CL.voidTy, prFnName, params, | ||
527 : | CL.mkCall("fprintf", CL.mkVar "outS" :: prArgs)) | ||
528 : | end | ||
529 : | in | ||
530 : | prFn | ||
531 : | end | ||
532 : | |||
533 : | jhr | 1705 | fun genStrandTyDef (targetTy,Strand{state,...}, tyName) = (case state |
534 : | of [] => CL.D_Comment(["No Strand Defintiion Included"]) | ||
535 : | jhr | 1716 | | _ => CL.D_StructDef( |
536 : | NONE, | ||
537 : | revmap (fn x => (targetTy x, #var x)) state, | ||
538 : | SOME tyName) | ||
539 : | jhr | 1705 | (* end case *)) |
540 : | jhr | 1671 | |
541 : | (* generates the globals buffers and arguments function *) | ||
542 : | fun genConvertShadowTypes (Strand{name, tyName, state,...}) = let | ||
543 : | jhr | 1705 | (* Declare opencl setup objects *) |
544 : | jhr | 1671 | val errVar = "err" |
545 : | val params = [ | ||
546 : | CL.PARAM([], CL.T_Ptr(CL.T_Named tyName), "selfOut"), | ||
547 : | CL.PARAM([], CL.T_Ptr(CL.T_Named(RN.strandShadowTy tyName)), "selfIn") | ||
548 : | ] | ||
549 : | val body = List.map (fn (x:mirror_var) => #hToS x) state | ||
550 : | in | ||
551 : | CL.D_Func([], CL.voidTy, RN.strandConvertName name, params, CL.mkBlock body) | ||
552 : | end | ||
553 : | |||
554 : | (* generates the opencl buffers for the image data *) | ||
555 : | fun getGlobalDataBuffers (globals, imgGlobals, contextVar, errVar) = let | ||
556 : | val globalBuffErr = "error creating OpenCL global buffer\n" | ||
557 : | fun errorFn msg = CL.mkIfThen(CL.mkBinOp(CL.mkVar errVar, CL.#!=, CL.mkVar "CL_SUCCESS"), | ||
558 : | CL.mkBlock([CL.mkCall("fprintf",[CL.mkVar "stderr", CL.mkStr msg]), | ||
559 : | CL.mkCall("exit",[CL.mkInt 1])])) | ||
560 : | val shadowTypeDecl = | ||
561 : | CL.mkDecl(CL.T_Named(RN.shadowGlobalsTy), RN.shadowGlaobalsName, NONE) | ||
562 : | val globalToShadowStms = List.map (fn (x:mirror_var) => #hToS x) globals | ||
563 : | val globalBufferDecl = CL.mkDecl(clMemoryTy,concat[RN.globalsVarName,"_cl"],NONE) | ||
564 : | val globalBuffer = CL.mkAssign(CL.mkVar(concat[RN.globalsVarName,"_cl"]), | ||
565 : | CL.mkApply("clCreateBuffer", [ | ||
566 : | CL.mkVar contextVar, | ||
567 : | CL.mkBinOp(CL.mkVar "CL_MEM_READ_ONLY", CL.#|, CL.mkVar "CL_MEM_COPY_HOST_PTR"), | ||
568 : | CL.mkSizeof(CL.T_Named RN.shadowGlobalsTy), | ||
569 : | CL.mkUnOp(CL.%&,CL.mkVar RN.shadowGlaobalsName), | ||
570 : | CL.mkUnOp(CL.%&,CL.mkVar errVar) | ||
571 : | ])) | ||
572 : | fun genDataBuffers ([],_,_,_) = [] | ||
573 : | | genDataBuffers ((var,nDims)::globals, contextVar, errVar,errFn) = let | ||
574 : | val hostVar = CL.mkIndirect(CL.mkVar RN.globalsVarName, var) | ||
575 : | val size = CL.mkIndirect(hostVar, "dataSzb") | ||
576 : | in | ||
577 : | CL.mkDecl(clMemoryTy, RN.addBufferSuffixData var ,NONE) :: | ||
578 : | CL.mkAssign(CL.mkVar(RN.addBufferSuffixData var), | ||
579 : | CL.mkApply("clCreateBuffer", [ | ||
580 : | CL.mkVar contextVar, | ||
581 : | CL.mkVar "CL_MEM_READ_ONLY | CL_MEM_COPY_HOST_PTR", | ||
582 : | size, | ||
583 : | CL.mkIndirect(hostVar, "data"), | ||
584 : | CL.mkUnOp(CL.%&,CL.mkVar errVar) | ||
585 : | ])) :: | ||
586 : | errFn(concat["error in creating ",RN.addBufferSuffixData var, " global buffer\n"]) :: | ||
587 : | genDataBuffers(globals,contextVar,errVar,errFn) | ||
588 : | end | ||
589 : | in | ||
590 : | [shadowTypeDecl] @ globalToShadowStms | ||
591 : | @ [globalBufferDecl, globalBuffer,errorFn(globalBuffErr)] | ||
592 : | @ genDataBuffers(imgGlobals,contextVar,errVar,errorFn) | ||
593 : | end | ||
594 : | |||
595 : | (* generates the kernel arguments for the image data *) | ||
596 : | fun genGlobalArguments (globals, count, kernelVar, errVar) = let | ||
597 : | val globalArgErr = "error creating OpenCL global argument\n" | ||
598 : | fun errorFn msg = CL.mkIfThen(CL.mkBinOp(CL.mkVar errVar, CL.#!=, CL.mkVar "CL_SUCCESS"), | ||
599 : | CL.mkBlock([CL.mkCall("fprintf",[CL.mkVar "stderr", CL.mkStr msg]), | ||
600 : | CL.mkCall("exit",[CL.mkInt 1])])) | ||
601 : | val globalArgument = CL.mkExpStm(CL.mkAssignOp(CL.mkVar errVar,CL.&=, | ||
602 : | CL.mkApply("clSetKernelArg", | ||
603 : | [CL.mkVar kernelVar, | ||
604 : | CL.mkPostOp(CL.mkVar count, CL.^++), | ||
605 : | CL.mkApply("sizeof",[CL.mkVar "cl_mem"]), | ||
606 : | CL.mkUnOp(CL.%&,CL.mkVar(concat[RN.globalsVarName,"_cl"]))]))) | ||
607 : | fun genDataArguments ([],_,_,_,_) = [] | ||
608 : | | genDataArguments ((var,nDims)::globals,count,kernelVar,errVar,errFn) = | ||
609 : | CL.mkExpStm(CL.mkAssignOp(CL.mkVar errVar,CL.$=, | ||
610 : | CL.mkApply("clSetKernelArg", | ||
611 : | [CL.mkVar kernelVar, | ||
612 : | CL.mkPostOp(CL.mkVar count, CL.^++), | ||
613 : | CL.mkApply("sizeof",[CL.mkVar "cl_mem"]), | ||
614 : | CL.mkUnOp(CL.%&,CL.mkVar(RN.addBufferSuffixData var))]))) :: | ||
615 : | errFn(concat["error in creating ",RN.addBufferSuffixData var, " argument\n"]) :: | ||
616 : | genDataArguments (globals,count,kernelVar,errVar,errFn) | ||
617 : | in | ||
618 : | globalArgument :: errorFn globalArgErr :: | ||
619 : | genDataArguments(globals, count, kernelVar, errVar,errorFn) | ||
620 : | end | ||
621 : | |||
622 : | (* generates the globals buffers and arguments function *) | ||
623 : | fun genGlobalBuffersArgs (globals,imgGlobals) = let | ||
624 : | (* Delcare opencl setup objects *) | ||
625 : | val errVar = "err" | ||
626 : | val params = [ | ||
627 : | CL.PARAM([],CL.T_Named("cl_context"), "context"), | ||
628 : | CL.PARAM([],CL.T_Named("cl_kernel"), "kernel"), | ||
629 : | CL.PARAM([],CL.T_Named("cl_command_queue"), "cmdQ"), | ||
630 : | CL.PARAM([],CL.T_Named("int"), "argStart") | ||
631 : | ] | ||
632 : | val body = (case globals | ||
633 : | of [] => [CL.mkReturn(NONE)] | ||
634 : | | _ => let | ||
635 : | val clGlobalBuffers = | ||
636 : | getGlobalDataBuffers(globals, !imgGlobals, "context", errVar) | ||
637 : | val clGlobalArguments = | ||
638 : | genGlobalArguments(!imgGlobals, "argStart", "kernel", errVar) | ||
639 : | in | ||
640 : | (* Body: put all the statments together *) | ||
641 : | CL.mkDecl(clIntTy, errVar, SOME(CL.I_Exp(CL.mkInt 0))) | ||
642 : | :: clGlobalBuffers @ clGlobalArguments | ||
643 : | end | ||
644 : | (*end of case*)) | ||
645 : | in | ||
646 : | CL.D_Func([],CL.voidTy,RN.globalsSetupName,params,CL.mkBlock(body)) | ||
647 : | end | ||
648 : | |||
649 : | (* generate the global image meta-data and data parameters *) | ||
650 : | fun genKeneralGlobalParams ((name,tyname)::[],line) = | ||
651 : | concat[line, "__global void *", RN.addBufferSuffixData name] | ||
652 : | | genKeneralGlobalParams ([],line) = line | ||
653 : | | genKeneralGlobalParams ((name,tyname)::rest, line) = | ||
654 : | genKeneralGlobalParams(rest, concat[line, "__global void *", RN.addBufferSuffixData name, ",\n"]) | ||
655 : | |||
656 : | fun genUpdateMethod (Strand{name, tyName, state,...}, globals, imgGlobals) = let | ||
657 : | val imageDataStms = List.map | ||
658 : | (fn (x,_) => concat[ | ||
659 : | RN.globalImageDataName, ".", RN.imageDataName x, " = ", | ||
660 : | RN.addBufferSuffixData x, ";","\n" | ||
661 : | ]) | ||
662 : | (!imgGlobals) | ||
663 : | fun select ([], a, _) = a | ||
664 : | | select (_, _, b) = b | ||
665 : | val placeHolders = [ | ||
666 : | (RN.place_holders, tyName), | ||
667 : | (RN.p_addDatPtr, select (!imgGlobals, "", ",")), | ||
668 : | (RN.p_addGlobals, select (!globals, "", ",")), | ||
669 : | (RN.p_globals, select (!globals, "", "__global Diderot_Globals_t *diderotGlobals")), | ||
670 : | (RN.p_globalVar, select (!globals, "0", RN.globalsVarName)), | ||
671 : | (RN.p_dataVar, select (!globals, "0", RN.globalImageDataName)), | ||
672 : | (RN.p_dataPtr, genKeneralGlobalParams (!imgGlobals, "")), | ||
673 : | (RN.p_dataAssign, select (!imgGlobals, "", | ||
674 : | String.concat("Diderot_data_ptr_t diderotDataPtrs;\n" :: imageDataStms))) | ||
675 : | ] | ||
676 : | in | ||
677 : | CL.verbatim [CLUpdateFrag.text] placeHolders | ||
678 : | end | ||
679 : | |||
680 : | fun genStrandCopy(Strand{tyName,name,state,...}) = let | ||
681 : | val params = [ | ||
682 : | CL.PARAM(["__global"], CL.T_Ptr(CL.T_Named tyName), "selfIn"), | ||
683 : | CL.PARAM(["__global"], CL.T_Ptr(CL.T_Named tyName), "selfOut") | ||
684 : | ] | ||
685 : | val assignStms = List.rev( | ||
686 : | List.map | ||
687 : | (fn x => CL.mkAssign(lvalueSV(#var x), rvalueSV(#var x))) | ||
688 : | state) | ||
689 : | in | ||
690 : | CL.D_Func([""], CL.voidTy, RN.strandCopy, params,CL.mkBlock(assignStms)) | ||
691 : | end | ||
692 : | |||
693 : | (* generate a global structure type definition from the list of globals *) | ||
694 : | fun genGlobalStruct (_, [], _) = CL.D_Comment(["No Global Definition"]) | ||
695 : | | genGlobalStruct (targetTy, globals, tyName) = let | ||
696 : | val globs = List.map (fn (x : mirror_var) => (targetTy x, #var x)) globals | ||
697 : | in | ||
698 : | jhr | 1716 | CL.D_StructDef(NONE, globs, SOME tyName) |
699 : | jhr | 1671 | end |
700 : | |||
701 : | (* generate a global structure type definition from the image data of the image globals *) | ||
702 : | fun genImageDataStruct ([], _) = CL.D_Comment(["No Image Data Ptrs Definition"]) | ||
703 : | | genImageDataStruct (imgGlobals, tyName) = let | ||
704 : | val globs = List.map | ||
705 : | (fn (x, _) => (globalPtr CL.voidTy, RN.imageDataName x)) | ||
706 : | imgGlobals | ||
707 : | in | ||
708 : | jhr | 1716 | CL.D_StructDef(NONE, globs, SOME tyName) |
709 : | jhr | 1671 | end |
710 : | |||
711 : | fun genGlobals (declFn, targetTy, globals) = let | ||
712 : | fun doVar (x : mirror_var) = declFn (CL.D_Var([], targetTy x, #var x, NONE)) | ||
713 : | in | ||
714 : | List.app doVar globals | ||
715 : | end | ||
716 : | |||
717 : | fun genOutputFun(Strand{name, output,tyName, state, code,...}) = let | ||
718 : | (* the output function *) | ||
719 : | val outFnName = concat[name, "_Output"] | ||
720 : | val outFun = let | ||
721 : | val params = [ | ||
722 : | CL.PARAM([], CL.T_Ptr CL.voidTy, "outS"), | ||
723 : | CL.PARAM([], CL.T_Ptr(CL.T_Named tyName), "self") | ||
724 : | ] | ||
725 : | (* the type and access expression for the strand's output variable *) | ||
726 : | val (outTy, outState) = (#1 output, CL.mkIndirect(CL.mkVar "self", #2 output)) | ||
727 : | val outState = CL.mkUnOp(CL.%&, outState) | ||
728 : | in | ||
729 : | CL.D_Func(["static"], CL.voidTy, outFnName, params, | ||
730 : | CL.mkCall("memcpy", [CL.mkVar "outS", outState, CL.mkSizeof(shadowTy outTy)] )) | ||
731 : | end | ||
732 : | in | ||
733 : | outFun | ||
734 : | end | ||
735 : | |||
736 : | fun genStrandDesc (outFn,Strand{name, output,tyName, state, code,...}) = let | ||
737 : | (* the output function *) | ||
738 : | val outFnName = concat[name, "_Output"] | ||
739 : | (* the strand's descriptor object *) | ||
740 : | val descI = let | ||
741 : | fun fnPtr (ty, f) = CL.I_Exp(CL.mkCast(CL.T_Named ty, CL.mkVar f)) | ||
742 : | val (outTy, _) = output | ||
743 : | in | ||
744 : | CL.I_Struct[ | ||
745 : | ("name", CL.I_Exp(CL.mkStr name)), | ||
746 : | ("stateSzb", CL.I_Exp(CL.mkSizeof(CL.T_Named(RN.strandTy name)))), | ||
747 : | ("shadowStrandSzb", CL.I_Exp(CL.mkSizeof(CL.T_Named(RN.strandShadowTy (RN.strandTy name))))), | ||
748 : | (* FIXME: we may need to add a shadowOutputSzb field too for OpenCL *) | ||
749 : | ("outputSzb", CL.I_Exp(CL.mkSizeof(shadowTy outTy))), | ||
750 : | jhr | 1789 | (* DEPRECATED |
751 : | jhr | 1671 | ("nrrdType", CL.I_Exp(CL.mkInt (NrrdTypes.toNrrdType outTy))), |
752 : | jhr | 1789 | ("nrrdSzb", CL.I_Exp(CL.mkInt (NrrdTypes.toNrrdSize outTy))), |
753 : | *) | ||
754 : | jhr | 1671 | ("update", fnPtr("update_method_t", "0")), |
755 : | ("strandCopy", fnPtr("convert_method_t", RN.strandConvertName name)), | ||
756 : | ("print", fnPtr("print_method_t", RN.strandPrintName name)), | ||
757 : | ("output", fnPtr("output_method_t", outFnName)) (* FIXME *) | ||
758 : | ] | ||
759 : | end | ||
760 : | val desc = CL.D_Var([], CL.T_Named N.strandDescTy, N.strandDesc name, SOME descI) | ||
761 : | in | ||
762 : | desc | ||
763 : | end | ||
764 : | |||
765 : | (* generate the table of strand descriptors *) | ||
766 : | fun genStrandTable (declFn, strands) = let | ||
767 : | val nStrands = length strands | ||
768 : | fun genInit (Strand{name, ...}) = CL.I_Exp(CL.mkUnOp(CL.%&, CL.mkVar(N.strandDesc name))) | ||
769 : | fun genInits (_, []) = [] | ||
770 : | | genInits (i, s::ss) = (i, genInit s) :: genInits(i+1, ss) | ||
771 : | in | ||
772 : | declFn (CL.D_Var([], CL.int32, N.numStrands, | ||
773 : | SOME(CL.I_Exp(CL.mkIntTy(IntInf.fromInt nStrands, CL.int32))))); | ||
774 : | declFn (CL.D_Var([], | ||
775 : | CL.T_Array(CL.T_Ptr(CL.T_Named N.strandDescTy), SOME nStrands), | ||
776 : | N.strands, | ||
777 : | SOME(CL.I_Array(genInits (0, strands))))) | ||
778 : | end | ||
779 : | |||
780 : | fun genSrc (baseName, prog) = let | ||
781 : | val Prog{ | ||
782 : | jhr | 1713 | tgt, |
783 : | jhr | 1705 | globals, topDecls, strands, initially, |
784 : | jhr | 1671 | imgGlobals, numDims,outFn, ... |
785 : | } = prog | ||
786 : | val clFileName = OS.Path.joinBaseExt{base=baseName, ext=SOME "cl"} | ||
787 : | val cFileName = OS.Path.joinBaseExt{base=baseName, ext=SOME "c"} | ||
788 : | val clOutS = TextIO.openOut clFileName | ||
789 : | val cOutS = TextIO.openOut cFileName | ||
790 : | val clppStrm = PrintAsCL.new clOutS | ||
791 : | val cppStrm = PrintAsC.new cOutS | ||
792 : | fun cppDecl dcl = PrintAsC.output(cppStrm, dcl) | ||
793 : | fun clppDecl dcl = PrintAsCL.output(clppStrm, dcl) | ||
794 : | val strands = AtomTable.listItems strands | ||
795 : | val [strand as Strand{name, tyName, code, init_code, ...}] = strands | ||
796 : | in | ||
797 : | (* Generate the OpenCL file *) | ||
798 : | (* Retrieve the header information *) | ||
799 : | clppDecl (CL.verbatim [HF.text] [ | ||
800 : | ("OUTFILE", clFileName), | ||
801 : | ("SRCFILE", OS.Path.joinBaseExt{base=baseName, ext=SOME "diderot"}), | ||
802 : | jhr | 1713 | ("DIDEROT_FLOAT_PRECISION", TargetUtil.floatPrecisionDef tgt), |
803 : | ("DIDEROT_INT_PRECISION", TargetUtil.intPrecisionDef tgt) | ||
804 : | jhr | 1671 | ]); |
805 : | (* if there are no globals, then define a dummy type *) | ||
806 : | if List.null(!globals) | ||
807 : | then clppDecl (CL.D_Verbatim["typedef void ", RN.globalsTy, ";\n"]) | ||
808 : | else (); | ||
809 : | (* if there are no images, then define a dummy type *) | ||
810 : | if List.null(!imgGlobals) | ||
811 : | then clppDecl (CL.D_Verbatim["typedef void * ", RN.imageDataType, ";\n"]) | ||
812 : | else (); | ||
813 : | (* Retrieve the scheduler kernels and functions *) | ||
814 : | clppDecl (CL.D_Verbatim[SF.text]); | ||
815 : | clppDecl (CL.D_Verbatim[CLEigen2x2Frag.text]); | ||
816 : | clppDecl (CL.D_Verbatim[CLEigen3x3Frag.text]); | ||
817 : | clppDecl (genGlobalStruct (#gpuTy, !globals, RN.globalsTy)); | ||
818 : | clppDecl (genImageDataStruct(!imgGlobals, RN.imageDataType)); | ||
819 : | clppDecl (genStrandTyDef(#gpuTy, strand, tyName)); | ||
820 : | List.app clppDecl (!code); | ||
821 : | clppDecl (genStrandCopy strand); | ||
822 : | clppDecl (genUpdateMethod(strand, globals, imgGlobals)); | ||
823 : | (* Generate the Host C file *) | ||
824 : | cppDecl (CL.D_Verbatim[ | ||
825 : | jhr | 1713 | concat["#define " ^ TargetUtil.floatPrecisionDef tgt, "\n"], |
826 : | concat["#define " ^ TargetUtil.intPrecisionDef tgt, "\n"], | ||
827 : | concat["#define " ^ TargetUtil.targetDef tgt, "\n"], | ||
828 : | jhr | 1671 | "#include \"Diderot/diderot.h\"\n" |
829 : | jhr | 1705 | ]); |
830 : | case !globals | ||
831 : | of [] => cppDecl (CL.D_Verbatim[concat["typedef void ", RN.globalsTy, ";\n"] ]) | ||
832 : | | _ => () | ||
833 : | (* end case *); | ||
834 : | jhr | 1671 | cppDecl (CL.D_Var(["static"], CL.charPtr, "ProgramName", |
835 : | jhr | 1713 | SOME(CL.I_Exp(CL.mkStr(#srcFile tgt))))); |
836 : | jhr | 1671 | cppDecl (genGlobalStruct (#hostTy, !globals, RN.globalsTy)); |
837 : | cppDecl (genGlobalStruct (#shadowTy, !globals, RN.shadowGlobalsTy)); | ||
838 : | (* FIXME: does this really need to be a global? *) | ||
839 : | cppDecl (CL.D_Var(["static"], globPtrTy, RN.globalsVarName, NONE)); | ||
840 : | cppDecl (genStrandTyDef (#hostTy, strand, tyName)); | ||
841 : | cppDecl (genStrandTyDef (#shadowTy, strand, RN.strandShadowTy tyName)); | ||
842 : | cppDecl (genConvertShadowTypes strand); | ||
843 : | cppDecl (!init_code); | ||
844 : | cppDecl (genStrandPrint strand); | ||
845 : | cppDecl (genOutputFun strand); | ||
846 : | List.app cppDecl (List.rev (!topDecls)); | ||
847 : | cppDecl (genGlobalBuffersArgs (!globals,imgGlobals)); | ||
848 : | List.app (fn strand => cppDecl (genStrandDesc (outFn,strand))) strands; | ||
849 : | genStrandTable (cppDecl, strands); | ||
850 : | cppDecl (!initially); | ||
851 : | PrintAsC.close cppStrm; | ||
852 : | PrintAsCL.close clppStrm; | ||
853 : | TextIO.closeOut cOutS; | ||
854 : | TextIO.closeOut clOutS | ||
855 : | end | ||
856 : | |||
857 : | (* output the code to the filesystem. The string is the basename of the source file *) | ||
858 : | jhr | 1705 | fun generate (prog as Prog{tgt, ...}) = let |
859 : | val {outDir, outBase, exec, double, parallel, debug, ...} = tgt | ||
860 : | jhr | 1671 | fun condCons (true, x, xs) = x::xs |
861 : | | condCons (false, _, xs) = xs | ||
862 : | (* generate the C compiler flags *) | ||
863 : | val cflags = ["-I" ^ Paths.diderotInclude, "-I" ^ Paths.teemInclude] | ||
864 : | jhr | 1843 | val cflags = condCons (#cl Paths.cflags <> "", #cl Paths.cflags, cflags) |
865 : | jhr | 1671 | val cflags = condCons (parallel, #pthread Paths.cflags, cflags) |
866 : | val cflags = if debug | ||
867 : | then #debug Paths.cflags :: cflags | ||
868 : | else #ndebug Paths.cflags :: cflags | ||
869 : | val cflags = #base Paths.cflags :: cflags | ||
870 : | (* generate the loader flags *) | ||
871 : | val extraLibs = condCons (parallel, #pthread Paths.extraLibs, []) | ||
872 : | val extraLibs = Paths.teemLinkFlags @ #base Paths.extraLibs :: extraLibs | ||
873 : | val extraLibs = #cl Paths.extraLibs :: extraLibs | ||
874 : | jhr | 1706 | val rtLib = TargetUtil.runtimeName tgt |
875 : | jhr | 1671 | val ldOpts = rtLib :: extraLibs |
876 : | jhr | 1705 | val basename = OS.Path.joinDirFile{dir=outDir, file=outBase} |
877 : | jhr | 1671 | in |
878 : | genSrc (basename, prog); | ||
879 : | RunCC.compile (basename, cflags); | ||
880 : | jhr | 1714 | RunCC.linkExec (basename, ldOpts) |
881 : | jhr | 1671 | end |
882 : | |||
883 : | end (* Program *) | ||
884 : | |||
885 : | end | ||
886 : | |||
887 : | structure CLBackEnd = CodeGenFn(CLTarget) |
root@smlnj-gforge.cs.uchicago.edu | ViewVC Help |
Powered by ViewVC 1.0.0 |