1 |
(* c-target.sml |
(* cl-target.sml |
2 |
* |
* |
3 |
* COPYRIGHT (c) 2011 The Diderot Project (http://diderot-language.cs.uchicago.edu) |
* COPYRIGHT (c) 2011 The Diderot Project (http://diderot-language.cs.uchicago.edu) |
4 |
* All rights reserved. |
* All rights reserved. |
15 |
structure ToCL = TreeToCL |
structure ToCL = TreeToCL |
16 |
structure N = CNames |
structure N = CNames |
17 |
|
|
18 |
(* variable translation *) |
(* helper functions for specifying parameters in various address spaces *) |
19 |
structure TrVar = |
fun clParam (spc, ty, x) = CL.PARAM([spc], ty, x) |
20 |
struct |
fun globalParam (ty, x) = CL.PARAM(["__global"], ty, x) |
21 |
type env = CL.typed_var TreeIL.Var.Map.map |
fun constantParam (ty, x) = CL.PARAM(["__constant"], ty, x) |
22 |
fun lookup (env, x) = (case V.Map.find (env, x) |
fun localParam (ty, x) = CL.PARAM(["__local"], ty, x) |
23 |
of SOME(CL.V(_, x')) => x' |
fun privateParam (ty, x) = CL.PARAM(["__private"], ty, x) |
|
| NONE => raise Fail(concat["lookup(_, ", V.name x, ")"]) |
|
|
(* end case *)) |
|
|
(* translate a variable that occurs in an l-value context (i.e., as the target of an assignment) *) |
|
|
fun lvalueVar (env, x) = (case V.kind x |
|
|
of IL.VK_Global => CL.mkVar(lookup(env, x)) |
|
|
| IL.VK_State strand => CL.mkIndirect(CL.mkVar "selfOut", lookup(env, x)) |
|
|
| IL.VK_Local => CL.mkVar(lookup(env, x)) |
|
|
(* end case *)) |
|
|
(* translate a variable that occurs in an r-value context *) |
|
|
fun rvalueVar (env, x) = (case V.kind x |
|
|
of IL.VK_Global => CL.mkVar(lookup(env, x)) |
|
|
| IL.VK_State strand => CL.mkIndirect(CL.mkVar "selfIn", lookup(env, x)) |
|
|
| IL.VK_Local => CL.mkVar(lookup(env, x)) |
|
|
(* end case *)) |
|
|
end |
|
|
|
|
|
structure ToC = TreeToCFn (TrVar) |
|
24 |
|
|
25 |
(* C variable translation *) |
(* C variable translation *) |
26 |
structure TrCVar = |
structure TrCVar = |
33 |
(* translate a variable that occurs in an l-value context (i.e., as the target of an assignment) *) |
(* translate a variable that occurs in an l-value context (i.e., as the target of an assignment) *) |
34 |
fun lvalueVar (env, x) = (case V.kind x |
fun lvalueVar (env, x) = (case V.kind x |
35 |
of IL.VK_Global => CL.mkIndirect(CL.mkVar RN.globalsVarName, lookup(env, x)) |
of IL.VK_Global => CL.mkIndirect(CL.mkVar RN.globalsVarName, lookup(env, x)) |
36 |
| IL.VK_State strand => raise Fail "unexpected strand context" |
| IL.VK_State strand => CL.mkIndirect(CL.mkVar "selfOut", lookup(env, x)) |
37 |
| IL.VK_Local => CL.mkVar(lookup(env, x)) |
| IL.VK_Local => CL.mkVar(lookup(env, x)) |
38 |
(* end case *)) |
(* end case *)) |
39 |
(* translate a variable that occurs in an r-value context *) |
(* translate a variable that occurs in an r-value context *) |
40 |
val rvalueVar = lvalueVar |
fun rvalueVar (env, x) = (case V.kind x |
41 |
|
of IL.VK_Global => CL.mkIndirect(CL.mkVar RN.globalsVarName, lookup(env, x)) |
42 |
|
| IL.VK_State strand => CL.mkIndirect(CL.mkVar "selfIn", lookup(env, x)) |
43 |
|
| IL.VK_Local => CL.mkVar(lookup(env, x)) |
44 |
|
(* end case *)) |
45 |
end |
end |
46 |
|
|
47 |
structure ToC = TreeToCFn (TrCVar) |
structure ToC = TreeToCFn (TrCVar) |
51 |
type stm = CL.stm |
type stm = CL.stm |
52 |
|
|
53 |
(* OpenCL specific types *) |
(* OpenCL specific types *) |
54 |
|
val clIntTy = CL.T_Named "cl_int" |
55 |
val clProgramTy = CL.T_Named "cl_program" |
val clProgramTy = CL.T_Named "cl_program" |
56 |
val clKernelTy = CL.T_Named "cl_kernel" |
val clKernelTy = CL.T_Named "cl_kernel" |
57 |
val clCmdQueueTy = CL.T_Named "cl_command_queue" |
val clCmdQueueTy = CL.T_Named "cl_command_queue" |
59 |
val clDeviceIdTy = CL.T_Named "cl_device_id" |
val clDeviceIdTy = CL.T_Named "cl_device_id" |
60 |
val clPlatformIdTy = CL.T_Named "cl_platform_id" |
val clPlatformIdTy = CL.T_Named "cl_platform_id" |
61 |
val clMemoryTy = CL.T_Named "cl_mem" |
val clMemoryTy = CL.T_Named "cl_mem" |
62 |
|
val globPtrTy = CL.T_Ptr(CL.T_Named RN.globalsTy) |
63 |
|
|
64 |
(* variable or field that is mirrored between host and GPU *) |
(* variable or field that is mirrored between host and GPU *) |
65 |
type mirror_var = { |
type mirror_var = { |
86 |
topDecls : CL.decl list ref, |
topDecls : CL.decl list ref, |
87 |
strands : strand AtomTable.hash_table, |
strands : strand AtomTable.hash_table, |
88 |
initially : CL.decl ref, |
initially : CL.decl ref, |
89 |
numDims: int ref, |
numDims: int ref, (* number of dimensions in initially iteration *) |
90 |
imgGlobals: (string * int) list ref, |
imgGlobals: (string * int) list ref, |
91 |
prFn: CL.decl ref |
prFn: CL.decl ref |
92 |
} |
} |
119 |
(* TreeIL to target translations *) |
(* TreeIL to target translations *) |
120 |
structure Tr = |
structure Tr = |
121 |
struct |
struct |
|
(* this function is used for the initially clause, so it generates OpenCL *) |
|
122 |
fun fragment (ENV{info, vMap, scope}, blk) = let |
fun fragment (ENV{info, vMap, scope}, blk) = let |
123 |
val (vMap, stms) = ToCL.trFragment (vMap, blk) |
val (vMap, stms) = (case scope |
124 |
|
of GlobalScope => ToC.trFragment (vMap, blk) |
125 |
|
(* NOTE: if we move strand initialization to the GPU, then we'll have to change the following code! *) |
126 |
|
| InitiallyScope => ToC.trFragment (vMap, blk) |
127 |
|
| _ => ToCL.trFragment (vMap, blk) |
128 |
|
(* end case *)) |
129 |
in |
in |
130 |
(ENV{info=info, vMap=vMap, scope=scope}, stms) |
(ENV{info=info, vMap=vMap, scope=scope}, stms) |
131 |
end |
end |
132 |
fun saveState cxt stateVars (env, args, stm) = ( |
fun block (ENV{vMap, scope, ...}, blk) = let |
133 |
|
fun saveState cxt stateVars trAssign (env, args, stm) = ( |
134 |
ListPair.foldrEq |
ListPair.foldrEq |
135 |
(fn (x, e, stms) => ToCL.trAssign(env, x, e)@stms) |
(fn (x, e, stms) => trAssign(env, x, e)@stms) |
136 |
[stm] |
[stm] |
137 |
(stateVars, args) |
(stateVars, args) |
138 |
) handle ListPair.UnequalLengths => ( |
) handle ListPair.UnequalLengths => ( |
139 |
print(concat["saveState ", cxt, ": length mismatch; ", Int.toString(List.length args), " args\n"]); |
print(concat["saveState ", cxt, ": length mismatch; ", Int.toString(List.length args), " args\n"]); |
140 |
raise Fail(concat["saveState ", cxt, ": length mismatch"])) |
raise Fail(concat["saveState ", cxt, ": length mismatch"])) |
141 |
fun block (ENV{vMap, scope, ...}, blk) = (case scope |
in |
142 |
of StrandScope stateVars => ToCL.trBlock (vMap, saveState "StrandScope" stateVars, blk) |
case scope |
143 |
| MethodScope stateVars => ToCL.trBlock (vMap, saveState "MethodScope" stateVars, blk) |
(* NOTE: if we move strand initialization to the GPU, then we'll have to change the following code! *) |
144 |
|
of StrandScope stateVars => |
145 |
|
ToCL.trBlock (vMap, saveState "StrandScope" stateVars ToC.trAssign, blk) |
146 |
|
| MethodScope stateVars => |
147 |
|
ToCL.trBlock (vMap, saveState "MethodScope" stateVars ToCL.trAssign, blk) |
148 |
| InitiallyScope => ToCL.trBlock (vMap, fn (_, _, stm) => [stm], blk) |
| InitiallyScope => ToCL.trBlock (vMap, fn (_, _, stm) => [stm], blk) |
149 |
| _ => ToC.trBlock (vMap, fn (_, _, stm) => [stm], blk) |
| _ => ToC.trBlock (vMap, fn (_, _, stm) => [stm], blk) |
150 |
(* end case *)) |
(* end case *) |
151 |
|
end |
152 |
fun exp (ENV{vMap, ...}, e) = ToCL.trExp(vMap, e) |
fun exp (ENV{vMap, ...}, e) = ToCL.trExp(vMap, e) |
153 |
end |
end |
154 |
|
|
212 |
topDecls = ref [], |
topDecls = ref [], |
213 |
strands = AtomTable.mkTable (16, Fail "strand table"), |
strands = AtomTable.mkTable (16, Fail "strand table"), |
214 |
initially = ref(CL.D_Comment["missing initially"]), |
initially = ref(CL.D_Comment["missing initially"]), |
215 |
numDims = ref(0), |
numDims = ref 0, |
216 |
imgGlobals = ref[], |
imgGlobals = ref[], |
217 |
prFn = ref(CL.D_Comment(["No Print Function"])) |
prFn = ref(CL.D_Comment(["No Print Function"])) |
218 |
}) |
}) |
219 |
(* register the global initialization part of a program *) |
(* register the global initialization part of a program *) |
220 |
|
(* FIXME: unused code; can this be removed?? |
221 |
fun globalIndirects (globals,stms) = let |
fun globalIndirects (globals,stms) = let |
222 |
fun getGlobals ({name,target as TargetUtil.TARGET_CL}::rest) = |
fun getGlobals ({name,target as TargetUtil.TARGET_CL}::rest) = |
223 |
CL.mkAssign(CL.mkIndirect(CL.mkVar RN.globalsVarName,name),CL.mkVar name) |
CL.mkAssign(CL.mkIndirect(CL.mkVar RN.globalsVarName,name),CL.mkVar name) |
227 |
in |
in |
228 |
stms @ getGlobals globals |
stms @ getGlobals globals |
229 |
end |
end |
230 |
|
*) |
231 |
(* register the code that is used to register command-line options for input variables *) |
(* register the code that is used to register command-line options for input variables *) |
232 |
fun inputs (Prog{topDecls, ...}, stm) = let |
fun inputs (Prog{topDecls, ...}, stm) = let |
233 |
val inputsFn = CL.D_Func( |
val inputsFn = CL.D_Func( |
240 |
|
|
241 |
(* register the global initialization part of a program *) |
(* register the global initialization part of a program *) |
242 |
fun init (Prog{topDecls, ...}, init) = let |
fun init (Prog{topDecls, ...}, init) = let |
243 |
val globPtrTy = CL.T_Ptr(CL.T_Named RN.globalsTy) |
val globalsDecl = CL.mkAssign(CL.E_Var RN.globalsVarName, |
244 |
|
CL.mkApply("malloc", [CL.mkApply("sizeof",[CL.mkVar RN.globalsTy])])) |
245 |
|
val initGlobalsCall = CL.mkCall(RN.initGlobalsHelper,[]) |
246 |
val initFn = CL.D_Func( |
val initFn = CL.D_Func( |
247 |
[], CL.voidTy, RN.initGlobals, [CL.PARAM([], globPtrTy, RN.globalsVarName)], |
[], CL.voidTy, RN.initGlobals, [], |
248 |
|
CL.mkBlock([globalsDecl,initGlobalsCall])) |
249 |
|
val initFn_helper = CL.D_Func( |
250 |
|
[], CL.voidTy, RN.initGlobalsHelper, [], |
251 |
init) |
init) |
252 |
val shutdownFn = CL.D_Func( |
val shutdownFn = CL.D_Func( |
253 |
[], CL.voidTy, RN.shutdown, |
[], CL.voidTy, RN.shutdown, |
254 |
[CL.PARAM([], CL.T_Ptr(CL.T_Named RN.worldTy), "wrld")], |
[CL.PARAM([], CL.T_Ptr(CL.T_Named RN.worldTy), "wrld")], |
255 |
CL.S_Block[]) |
CL.S_Block[]) |
256 |
in |
in |
257 |
topDecls := shutdownFn :: initFn :: !topDecls |
topDecls := shutdownFn :: initFn :: initFn_helper :: !topDecls |
258 |
end |
end |
259 |
(* create and register the initially function for a program *) |
(* create and register the initially function for a program *) |
260 |
fun initially { |
fun initially { |
261 |
prog = Prog{name=progName, strands, initially, ...}, |
prog = Prog{name=progName, strands, initially, numDims, ...}, |
262 |
isArray : bool, |
isArray : bool, |
263 |
iterPrefix : stm list, |
iterPrefix : stm list, |
264 |
iters : (var * exp * exp) list, |
iters : (var * exp * exp) list, |
287 |
CL.mkDecl(CL.T_Array(CL.int32, SOME nDims), "base", SOME(CL.I_Array baseInit)), |
CL.mkDecl(CL.T_Array(CL.int32, SOME nDims), "base", SOME(CL.I_Array baseInit)), |
288 |
CL.mkDecl(CL.T_Array(CL.uint32, SOME nDims), "size", SOME(CL.I_Array sizeInit)), |
CL.mkDecl(CL.T_Array(CL.uint32, SOME nDims), "size", SOME(CL.I_Array sizeInit)), |
289 |
CL.mkDecl(worldTy, wrld, |
CL.mkDecl(worldTy, wrld, |
290 |
SOME(CL.I_Exp(CL.E_Apply(N.allocInitially, [ |
SOME(CL.I_Exp(CL.E_Apply(RN.allocInitially, [ |
291 |
CL.mkVar "ProgramName", |
CL.mkVar "ProgramName", |
292 |
CL.mkUnOp(CL.%&, CL.E_Var(N.strandDesc name)), |
CL.mkUnOp(CL.%&, CL.E_Var(N.strandDesc name)), |
293 |
|
CL.mkApply("sizeof",[CL.E_Var (N.strandTy name)]), |
294 |
CL.E_Bool isArray, |
CL.E_Bool isArray, |
295 |
CL.E_Int(IntInf.fromInt nDims, CL.int32), |
CL.E_Int(IntInf.fromInt nDims, CL.int32), |
296 |
CL.E_Var "base", |
CL.E_Var "base", |
297 |
CL.E_Var "size" |
CL.E_Var "size" |
298 |
])))) |
])))) |
299 |
] |
] |
300 |
(* create the loop nest for the initially iterations *) |
(* create the loop nest for the initially iterations |
301 |
val indexVar = "ix" |
val indexVar = "ix" |
302 |
val strandTy = CL.T_Ptr(CL.T_Named(N.strandTy name)) |
val strandTy = CL.T_Ptr(CL.T_Named(N.strandTy name)) |
303 |
fun mkLoopNest [] = CL.mkBlock(createPrefix @ [ |
fun mkLoopNest [] = CL.mkBlock(createPrefix @ [ |
305 |
SOME(CL.I_Exp( |
SOME(CL.I_Exp( |
306 |
CL.E_Cast(strandTy, |
CL.E_Cast(strandTy, |
307 |
CL.E_Apply(N.inState, [CL.E_Var "wrld", CL.E_Var indexVar]))))), |
CL.E_Apply(N.inState, [CL.E_Var "wrld", CL.E_Var indexVar]))))), |
308 |
CL.mkCall(N.strandInit name, CL.E_Var "sp" :: args), |
CL.mkCall(N.strandInit name, |
309 |
|
CL.E_Var RN.globalsVarName :: CL.E_Var "sp" :: args), |
310 |
CL.mkAssign(CL.E_Var indexVar, CL.mkBinOp(CL.E_Var indexVar, CL.#+, CL.E_Int(1, CL.uint32))) |
CL.mkAssign(CL.E_Var indexVar, CL.mkBinOp(CL.E_Var indexVar, CL.#+, CL.E_Int(1, CL.uint32))) |
311 |
]) |
]) |
312 |
| mkLoopNest ((CL.V(ty, param), lo, hi)::iters) = let |
| mkLoopNest ((CL.V(ty, param), lo, hi)::iters) = let |
322 |
CL.mkComment["initially"], |
CL.mkComment["initially"], |
323 |
CL.mkDecl(CL.uint32, indexVar, SOME(CL.I_Exp(CL.E_Int(0, CL.uint32)))), |
CL.mkDecl(CL.uint32, indexVar, SOME(CL.I_Exp(CL.E_Int(0, CL.uint32)))), |
324 |
mkLoopNest iters |
mkLoopNest iters |
325 |
] |
] *) |
326 |
val body = CL.mkBlock( |
val body = CL.mkBlock( |
327 |
iterPrefix @ |
iterPrefix @ |
328 |
allocCode @ |
allocCode @ |
|
iterCode @ |
|
329 |
[CL.mkReturn(SOME(CL.E_Var "wrld"))]) |
[CL.mkReturn(SOME(CL.E_Var "wrld"))]) |
330 |
val initFn = CL.D_Func([], worldTy, N.initially, [], body) |
val initFn = CL.D_Func([], worldTy, N.initially, [], body) |
331 |
in |
in |
332 |
|
numDims := nDims; |
333 |
initially := initFn |
initially := initFn |
334 |
end |
end |
335 |
|
|
347 |
val prArgs = (case ty |
val prArgs = (case ty |
348 |
of Ty.IVecTy 1 => [CL.E_Str(!N.gIntFormat ^ "\n"), outState] |
of Ty.IVecTy 1 => [CL.E_Str(!N.gIntFormat ^ "\n"), outState] |
349 |
| Ty.IVecTy d => let |
| Ty.IVecTy d => let |
350 |
val fmt = CL.E_Str( |
val fmt = CL.mkStr( |
351 |
String.concatWith " " (List.tabulate(d, fn _ => !N.gIntFormat)) |
String.concatWith " " (List.tabulate(d, fn _ => !N.gIntFormat)) |
352 |
^ "\n") |
^ "\n") |
353 |
val args = List.tabulate (d, fn i => ToC.ivecIndex(outState, d, i)) |
val args = List.tabulate (d, fn i => ToC.ivecIndex(outState, d, i)) |
354 |
in |
in |
355 |
fmt :: args |
fmt :: args |
356 |
end |
end |
357 |
| Ty.TensorTy[] => [CL.E_Str "%f\n", outState] |
| Ty.TensorTy[] => [CL.mkStr "%f\n", outState] |
358 |
| Ty.TensorTy[d] => let |
| Ty.TensorTy[d] => let |
359 |
val fmt = CL.E_Str( |
val fmt = CL.mkStr( |
360 |
String.concatWith " " (List.tabulate(d, fn _ => "%f")) |
String.concatWith " " (List.tabulate(d, fn _ => "%f")) |
361 |
^ "\n") |
^ "\n") |
362 |
val args = List.tabulate (d, fn i => ToC.vecIndex(outState, d, i)) |
val args = List.tabulate (d, fn i => ToC.vecIndex(outState, d, i)) |
379 |
List.rev (List.map (fn x => (targetTy x, #var x)) (!state)), |
List.rev (List.map (fn x => (targetTy x, #var x)) (!state)), |
380 |
tyName) |
tyName) |
381 |
|
|
|
|
|
382 |
(* generates the load kernel function *) |
(* generates the load kernel function *) |
383 |
|
|
384 |
(* generates the opencl buffers for the image data *) |
(* generates the opencl buffers for the image data *) |
385 |
fun getGlobalDataBuffers(globals,contextVar,errVar) = let |
fun getGlobalDataBuffers(globals,contextVar,errVar) = let |
386 |
|
val globalBuffErr = "error creating OpenCL global buffer" |
387 |
|
fun errorFn msg = CL.mkIfThen(CL.mkBinOp(CL.E_Var errVar, CL.#!=, CL.E_Var "CL_SUCCESS"), |
388 |
|
CL.mkBlock([CL.mkCall("fprintf",[CL.E_Var "stderr", CL.E_Str msg]), |
389 |
|
CL.mkCall("exit",[CL.mkInt 1])])) |
390 |
val globalBufferDecl = CL.mkDecl(clMemoryTy,concat[RN.globalsVarName,"_cl"],NONE) |
val globalBufferDecl = CL.mkDecl(clMemoryTy,concat[RN.globalsVarName,"_cl"],NONE) |
391 |
val globalBuffer = CL.mkAssign(CL.mkVar(concat[RN.globalsVarName,"_cl"]), |
val globalBuffer = CL.mkAssign(CL.mkVar(concat[RN.globalsVarName,"_cl"]), |
392 |
CL.mkApply("clCreateBuffer", [ |
CL.mkApply("clCreateBuffer", [ |
393 |
CL.mkVar contextVar, |
CL.mkVar contextVar, |
394 |
CL.mkVar "CL_MEM_COPY_HOST_PTR", |
CL.mkVar "CL_MEM_READ_WRITE | CL_MEM_COPY_HOST_PTR", |
395 |
CL.mkApply("sizeof",[CL.mkVar RN.globalsTy]), |
CL.mkApply("sizeof",[CL.mkVar RN.globalsTy]), |
396 |
CL.mkVar RN.globalsVarName, |
CL.mkVar RN.globalsVarName, |
397 |
CL.mkUnOp(CL.%&,CL.mkVar errVar) |
CL.mkUnOp(CL.%&,CL.mkVar errVar) |
398 |
])) |
])) |
399 |
|
fun genDataBuffers ([],_,_,_) = [] |
400 |
fun genDataBuffers([],_,_) = [] |
| genDataBuffers ((var,nDims)::globals, contextVar, errVar,errFn) = let |
401 |
| genDataBuffers((var,nDims)::globals,contextVar,errVar) = let |
val hostVar = CL.mkIndirect(CL.mkVar RN.globalsVarName, var) |
402 |
(* FIXME: use CL constructors to build expressions (not strings) *) |
(* FIXME: use CL constructors to build expressions (not strings) *) |
403 |
val size = if nDims = 1 |
fun sizeExp i = CL.mkSubscript(CL.mkIndirect(hostVar, "size"), CL.mkInt i) |
404 |
then CL.mkBinOp(CL.mkApply("sizeof",[CL.mkVar "float"]), CL.#*, |
val size = CL.mkBinOp(CL.mkApply("sizeof",[CL.mkVar "float"]), CL.#*, sizeExp 0) |
405 |
CL.mkIndirect(CL.mkVar var, "size[0]")) |
val size = if (nDims > 1) |
406 |
else if nDims = 2 then |
then CL.mkBinOp(size, CL.#*, sizeExp 1) |
407 |
CL.mkBinOp(CL.mkApply("sizeof",[CL.mkVar "float"]), CL.#*, |
else size |
408 |
CL.mkIndirect(CL.mkVar var, concat["size[0]", " * ", var, "->size[1]"])) |
val size = if (nDims > 2) |
409 |
else |
then CL.mkBinOp(size, CL.#*, sizeExp 2) |
410 |
CL.mkBinOp(CL.mkApply("sizeof",[CL.mkVar "float"]), CL.#*, |
else size |
|
CL.mkIndirect(CL.mkVar var,concat["size[0]", " * ", var, "->size[1] * ", var, "->size[2]"])) |
|
|
|
|
411 |
in |
in |
412 |
CL.mkDecl(clMemoryTy, RN.addBufferSuffix var ,NONE):: |
CL.mkDecl(clMemoryTy, RN.addBufferSuffix var ,NONE):: |
413 |
CL.mkDecl(clMemoryTy, RN.addBufferSuffixData var ,NONE):: |
CL.mkDecl(clMemoryTy, RN.addBufferSuffixData var ,NONE):: |
414 |
CL.mkAssign(CL.mkVar(RN.addBufferSuffix var), CL.mkApply("clCreateBuffer", |
CL.mkAssign(CL.mkVar(RN.addBufferSuffix var), |
415 |
[CL.mkVar contextVar, |
CL.mkApply("clCreateBuffer", [ |
416 |
|
CL.mkVar contextVar, |
417 |
CL.mkVar "CL_MEM_COPY_HOST_PTR", |
CL.mkVar "CL_MEM_COPY_HOST_PTR", |
418 |
CL.mkApply("sizeof",[CL.mkVar (RN.imageTy nDims)]), |
CL.mkApply("sizeof",[CL.mkVar (RN.imageTy nDims)]), |
419 |
CL.mkVar var, |
hostVar, |
420 |
CL.mkUnOp(CL.%&,CL.mkVar errVar)])) :: |
CL.mkUnOp(CL.%&,CL.mkVar errVar) |
421 |
CL.mkAssign(CL.mkVar(RN.addBufferSuffixData var), CL.mkApply("clCreateBuffer", |
])) :: |
422 |
[CL.mkVar contextVar, |
errFn(concat["error in creating ",RN.addBufferSuffix var, " global buffer"]) :: |
423 |
|
CL.mkAssign(CL.mkVar(RN.addBufferSuffixData var), |
424 |
|
CL.mkApply("clCreateBuffer", [ |
425 |
|
CL.mkVar contextVar, |
426 |
CL.mkVar "CL_MEM_COPY_HOST_PTR", |
CL.mkVar "CL_MEM_COPY_HOST_PTR", |
427 |
size, |
size, |
428 |
CL.mkIndirect(CL.mkVar var,"data"), |
CL.mkIndirect(hostVar, "data"), |
429 |
CL.mkUnOp(CL.%&,CL.mkVar errVar)])):: genDataBuffers(globals,contextVar,errVar) |
CL.mkUnOp(CL.%&,CL.mkVar errVar) |
430 |
|
])) :: |
431 |
|
errFn(concat["error in creating ",RN.addBufferSuffixData var, " global buffer"]) :: |
432 |
|
genDataBuffers(globals,contextVar,errVar,errFn) |
433 |
end |
end |
434 |
in |
in |
435 |
[globalBufferDecl] @ [globalBuffer] @ genDataBuffers(globals,contextVar,errVar) |
globalBufferDecl |
436 |
|
:: globalBuffer |
437 |
|
:: errorFn(globalBuffErr) |
438 |
|
:: genDataBuffers(globals,contextVar,errVar,errorFn) |
439 |
end |
end |
440 |
|
|
|
|
|
441 |
(* generates the kernel arguments for the image data *) |
(* generates the kernel arguments for the image data *) |
442 |
fun genGlobalArguments(globals,count,kernelVar,errVar) = let |
fun genGlobalArguments(globals,count,kernelVar,errVar) = let |
443 |
val globalArgument = CL.mkExpStm(CL.mkAssignOp(CL.mkVar errVar,CL.|=,CL.mkApply("clSetKernelArg", |
val globalArgErr = "error creating OpenCL global argument" |
444 |
|
fun errorFn msg = CL.mkIfThen(CL.mkBinOp(CL.E_Var errVar, CL.#!=, CL.E_Var "CL_SUCCESS"), |
445 |
|
CL.mkBlock([CL.mkCall("fprintf",[CL.E_Var "stderr", CL.E_Str msg]), |
446 |
|
CL.mkCall("exit",[CL.mkInt 1])])) |
447 |
|
val globalArgument = CL.mkExpStm(CL.mkAssignOp(CL.mkVar errVar,CL.|=, |
448 |
|
CL.mkApply("clSetKernelArg", |
449 |
[CL.mkVar kernelVar, |
[CL.mkVar kernelVar, |
450 |
CL.mkPostOp(CL.E_Var count, CL.^++), |
CL.mkPostOp(CL.E_Var count, CL.^++), |
451 |
CL.mkApply("sizeof",[CL.mkVar "cl_mem"]), |
CL.mkApply("sizeof",[CL.mkVar "cl_mem"]), |
452 |
CL.mkUnOp(CL.%&,CL.mkVar(concat[RN.globalsVarName,"_cl"]))]))) |
CL.mkUnOp(CL.%&,CL.mkVar(concat[RN.globalsVarName,"_cl"]))]))) |
453 |
|
fun genDataArguments ([],_,_,_,_) = [] |
454 |
fun genDataArguments([],_,_,_) = [] |
| genDataArguments ((var,nDims)::globals,count,kernelVar,errVar,errFn) = |
455 |
| genDataArguments((var,nDims)::globals,count,kernelVar,errVar) = |
CL.mkExpStm(CL.mkAssignOp(CL.mkVar errVar,CL.$=, |
456 |
|
CL.mkApply("clSetKernelArg", |
|
CL.mkExpStm(CL.mkAssignOp(CL.mkVar errVar,CL.|=, CL.mkApply("clSetKernelArg", |
|
457 |
[CL.mkVar kernelVar, |
[CL.mkVar kernelVar, |
458 |
CL.mkPostOp(CL.E_Var count, CL.^++), |
CL.mkPostOp(CL.E_Var count, CL.^++), |
459 |
CL.mkApply("sizeof",[CL.mkVar "cl_mem"]), |
CL.mkApply("sizeof",[CL.mkVar "cl_mem"]), |
460 |
CL.mkUnOp(CL.%&,CL.mkVar(RN.addBufferSuffix var))]))):: |
CL.mkUnOp(CL.%&,CL.mkVar(RN.addBufferSuffix var))]))):: |
461 |
|
errFn(concat["error in creating ",RN.addBufferSuffix var, " argument"]) :: |
462 |
CL.mkExpStm(CL.mkAssignOp(CL.mkVar errVar,CL.|=,CL.mkApply("clSetKernelArg", |
CL.mkExpStm(CL.mkAssignOp(CL.mkVar errVar,CL.$=, |
463 |
|
CL.mkApply("clSetKernelArg", |
464 |
[CL.mkVar kernelVar, |
[CL.mkVar kernelVar, |
465 |
CL.mkPostOp(CL.E_Var count, CL.^++), |
CL.mkPostOp(CL.E_Var count, CL.^++), |
466 |
CL.mkApply("sizeof",[CL.mkVar "cl_mem"]), |
CL.mkApply("sizeof",[CL.mkVar "cl_mem"]), |
467 |
CL.mkUnOp(CL.%&,CL.mkVar(RN.addBufferSuffixData var))]))):: genDataArguments (globals,count,kernelVar,errVar) |
CL.mkUnOp(CL.%&,CL.mkVar(RN.addBufferSuffixData var))]))) :: |
468 |
|
errFn(concat["error in creating ",RN.addBufferSuffixData var, " argument"]) :: |
469 |
|
genDataArguments (globals,count,kernelVar,errVar,errFn) |
470 |
in |
in |
471 |
|
[globalArgument,errorFn(globalArgErr)] @ genDataArguments(globals, count, kernelVar, errVar,errorFn) |
|
[globalArgument] @ genDataArguments(globals,count,kernelVar,errVar) |
|
|
|
|
472 |
end |
end |
473 |
|
|
474 |
(* generates the globals buffers and arguments function *) |
(* generates the globals buffers and arguments function *) |
479 |
val params = [ |
val params = [ |
480 |
CL.PARAM([],CL.T_Named("cl_context"), "context"), |
CL.PARAM([],CL.T_Named("cl_context"), "context"), |
481 |
CL.PARAM([],CL.T_Named("cl_kernel"), "kernel"), |
CL.PARAM([],CL.T_Named("cl_kernel"), "kernel"), |
482 |
|
CL.PARAM([],CL.T_Named("cl_command_queue"), "cmdQ"), |
483 |
CL.PARAM([],CL.T_Named("int"), "argStart") |
CL.PARAM([],CL.T_Named("int"), "argStart") |
484 |
] |
] |
485 |
val clGlobalBuffers = getGlobalDataBuffers(!imgGlobals, "context", "err") |
val clGlobalBuffers = getGlobalDataBuffers(!imgGlobals, "context", errVar) |
486 |
val clGlobalArguments = genGlobalArguments(!imgGlobals, "argStart", "kernel", "err") |
val clGlobalArguments = genGlobalArguments(!imgGlobals, "argStart", "kernel", errVar) |
487 |
(* Body put all the statments together *) |
(* Body put all the statments together *) |
488 |
val body = clGlobalBuffers @ clGlobalArguments |
val body = CL.mkDecl(clIntTy, errVar, SOME(CL.I_Exp(CL.mkInt 0))) |
489 |
|
:: clGlobalBuffers @ clGlobalArguments |
490 |
in |
in |
491 |
CL.D_Func([],CL.voidTy,RN.globalsSetupName,params,CL.mkBlock(body)) |
CL.D_Func([],CL.voidTy,RN.globalsSetupName,params,CL.mkBlock(body)) |
492 |
end |
end |
493 |
|
|
494 |
(* generate the data and global parameters *) |
(* generate the data and global parameters *) |
495 |
fun genKeneralGlobalParams ((name,tyname)::rest) = |
fun genKeneralGlobalParams ((name,tyname)::rest) = |
496 |
CL.PARAM([], CL.T_Ptr(CL.T_Named RN.globalsTy), concat[RN.globalsVarName]) :: |
globalParam (CL.T_Ptr(CL.T_Named (RN.imageTy tyname)), RN.addBufferSuffix name) :: |
497 |
CL.PARAM([], CL.T_Ptr(CL.T_Named (RN.imageTy tyname)),RN.addBufferSuffix name) :: |
globalParam (CL.T_Ptr(CL.voidTy), RN.addBufferSuffixData name) :: |
|
CL.PARAM([], CL.T_Ptr(CL.voidTy),RN.addBufferSuffixData name) :: |
|
498 |
genKeneralGlobalParams rest |
genKeneralGlobalParams rest |
499 |
| genKeneralGlobalParams [] = [] |
| genKeneralGlobalParams [] = [] |
500 |
|
|
501 |
(*generate code for intilizing kernel global data *) |
(*generate code for intilizing kernel global data *) |
|
fun initKernelGlobals (globals, imgGlobals) = let |
|
502 |
(* FIXME: should use List.map here *) |
(* FIXME: should use List.map here *) |
|
fun initGlobalStruct ({hostTy, gpuTy, var}::rest) = |
|
|
CL.mkAssign(CL.mkVar var, CL.mkIndirect(CL.mkVar RN.globalsVarName, var)) :: |
|
|
initGlobalStruct rest |
|
|
| initGlobalStruct [] = [] |
|
503 |
fun initGlobalImages ((name, tyname)::rest) = |
fun initGlobalImages ((name, tyname)::rest) = |
504 |
CL.mkAssign(CL.mkVar name, CL.mkVar (RN.addBufferSuffix name)) :: |
CL.mkAssign(CL.mkIndirect(CL.E_Var RN.globalsVarName, name), CL.mkVar (RN.addBufferSuffix name)) :: |
505 |
CL.mkAssign(CL.mkIndirect(CL.mkVar name,"data"),CL.mkVar (RN.addBufferSuffixData name)) :: |
CL.mkAssign(CL.mkIndirect(CL.E_Var RN.globalsVarName,concat[name,"->","data"]),CL.mkVar (RN.addBufferSuffixData name)) :: |
506 |
initGlobalImages rest |
initGlobalImages rest |
507 |
| initGlobalImages [] = [] |
| initGlobalImages [] = [] |
|
in |
|
|
initGlobalStruct globals @ initGlobalImages(imgGlobals) |
|
|
end |
|
508 |
|
|
509 |
(* generate the main kernel function for the .cl file *) |
(* generate the main kernel function for the .cl file *) |
510 |
fun genKernelFun (strand, nDims, globals, imgGlobals) = let |
fun genKernelFun (strand, nDims, globals, imgGlobals) = let |
512 |
val fName = RN.kernelFuncName; |
val fName = RN.kernelFuncName; |
513 |
val inState = "strand_in" |
val inState = "strand_in" |
514 |
val outState = "strand_out" |
val outState = "strand_out" |
515 |
|
val tempVar = "tmp" |
516 |
val params = [ |
val params = [ |
517 |
CL.PARAM(["__global"], CL.T_Ptr(CL.T_Named tyName), "selfIn"), |
globalParam (CL.T_Ptr(CL.T_Named tyName), "selfIn"), |
518 |
CL.PARAM(["__global"], CL.T_Ptr(CL.T_Named tyName), "selfOut"), |
globalParam (CL.T_Ptr(CL.T_Named tyName), "selfOut"), |
519 |
CL.PARAM(["__global"], CL.intTy, "width") |
globalParam (CL.intTy, "width"), |
520 |
|
globalParam (CL.T_Ptr(CL.T_Named RN.globalsTy), RN.globalsVarName) |
521 |
] @ genKeneralGlobalParams(!imgGlobals) |
] @ genKeneralGlobalParams(!imgGlobals) |
522 |
val thread_ids = if nDims = 1 |
val thread_ids = if nDims = 1 |
523 |
then [ |
then [ |
524 |
CL.mkDecl(CL.intTy, "x", SOME(CL.I_Exp(CL.mkInt(0, CL.intTy)))), |
CL.mkDecl(CL.intTy, "x", |
525 |
CL.mkAssign(CL.mkVar "x",CL.mkApply(RN.getGlobalThreadId,[CL.mkInt(0,CL.intTy)])) |
SOME(CL.I_Exp(CL.mkApply(RN.getGlobalThreadId,[CL.mkInt 0])))) |
526 |
] |
] |
527 |
else [ |
else if nDims = 2 |
528 |
CL.mkDecl(CL.intTy, "x", SOME(CL.I_Exp(CL.mkInt(0, CL.intTy)))), |
then [ |
529 |
CL.mkDecl(CL.intTy, "y", SOME(CL.I_Exp(CL.mkInt(0, CL.intTy)))), |
CL.mkDecl(CL.intTy, "x", |
530 |
CL.mkAssign(CL.mkVar "x", CL.mkApply(RN.getGlobalThreadId,[CL.mkInt(0,CL.intTy)])), |
SOME(CL.I_Exp(CL.mkApply(RN.getGlobalThreadId,[CL.mkInt 0])))), |
531 |
CL.mkAssign(CL.mkVar "y",CL.mkApply(RN.getGlobalThreadId,[CL.mkInt(1,CL.intTy)])) |
CL.mkDecl(CL.intTy, "y", |
532 |
|
SOME(CL.I_Exp(CL.mkApply(RN.getGlobalThreadId,[CL.mkInt 1])))) |
533 |
] |
] |
534 |
|
else raise Fail "nDims > 2" |
535 |
val strandDecl = [ |
val strandDecl = [ |
536 |
CL.mkDecl(CL.T_Named tyName, inState, NONE), |
CL.mkDecl(CL.T_Ptr(CL.T_Named (concat["__global ",tyName])), inState, NONE), |
537 |
CL.mkDecl(CL.T_Named tyName, outState,NONE)] |
CL.mkDecl(CL.T_Ptr(CL.T_Named (concat["__global ",tyName])), outState, NONE), |
538 |
|
CL.mkDecl(CL.T_Ptr(CL.T_Named (concat["__global ",tyName])), tempVar, NONE) |
539 |
|
] |
540 |
|
val swapStms = [ |
541 |
|
CL.mkAssign(CL.E_Var tempVar, CL.E_Var inState), |
542 |
|
CL.mkAssign(CL.E_Var inState, CL.E_Var outState), |
543 |
|
CL.mkAssign(CL.E_Var outState, CL.E_Var tempVar) |
544 |
|
] |
545 |
val strandObjects = if nDims = 1 |
val strandObjects = if nDims = 1 |
546 |
then [ |
then [ |
547 |
CL.mkAssign( CL.mkVar inState, CL.mkSubscript(CL.mkVar "selfIn", CL.mkStr "x")), |
CL.mkAssign( CL.mkVar inState, CL.mkUnOp(CL.%&,CL.mkSubscript(CL.mkVar "selfIn", CL.mkStr "x"))), |
548 |
CL.mkAssign(CL.mkVar outState,CL.mkSubscript(CL.mkVar "selfOut", CL.mkStr "x")) |
CL.mkAssign(CL.mkVar outState, CL.mkUnOp(CL.%&,CL.mkSubscript(CL.mkVar "selfOut", CL.mkStr "x"))) |
549 |
] |
] |
550 |
else let |
else let |
551 |
val index = CL.mkBinOp(CL.mkBinOp(CL.mkVar "x",CL.#*,CL.mkVar "width"),CL.#+,CL.mkVar "y") |
val index = CL.mkBinOp( |
552 |
in |
CL.mkBinOp(CL.mkVar "x", CL.#*, CL.mkVar "width"), CL.#+, CL.mkVar "y") |
553 |
[CL.mkAssign(CL.mkVar inState, CL.mkSubscript(CL.mkVar "selfIn",index)), |
in [ |
554 |
CL.mkAssign(CL.mkVar outState,CL.mkSubscript(CL.mkVar "selfOut",index))] |
CL.mkAssign(CL.mkVar inState, CL.mkUnOp(CL.%&,CL.mkSubscript(CL.mkVar "selfIn",index))), |
555 |
end |
CL.mkAssign(CL.mkVar outState, CL.mkUnOp(CL.%&,CL.mkSubscript(CL.mkVar "selfOut",index))) |
556 |
val status = CL.mkDecl(CL.intTy, "status", SOME(CL.I_Exp(CL.mkInt(0, CL.intTy)))) |
] end |
557 |
val local_vars = thread_ids @ initKernelGlobals(!globals,!imgGlobals) @ strandDecl @ strandObjects @ [status] |
val status = CL.mkDecl(CL.intTy, "status", SOME(CL.I_Exp(CL.mkInt 0))) |
558 |
val while_exp = CL.mkBinOp(CL.mkBinOp(CL.mkVar "status",CL.#!=, CL.mkVar RN.kStabilize),CL.#||,CL.mkBinOp(CL.mkVar "status", CL.#!=, CL.mkVar RN.kDie)) |
val strandInitStm = CL.mkCall(RN.strandInit name, [ |
559 |
val whileBody = CL.mkBlock [ |
CL.E_Var RN.globalsVarName, |
560 |
|
CL.E_Var inState, |
561 |
|
CL.E_Var "x", |
562 |
|
(* FIXME: if nDims = 1, then "y" is not defined! the arguments to this call should really come from |
563 |
|
* the initially code! |
564 |
|
*) |
565 |
|
CL.E_Var "y"]) |
566 |
|
val local_vars = thread_ids |
567 |
|
@ initGlobalImages(!imgGlobals) |
568 |
|
@ strandDecl |
569 |
|
@ strandObjects |
570 |
|
@ [strandInitStm,status] |
571 |
|
val while_exp = CL.mkBinOp( |
572 |
|
CL.mkBinOp(CL.mkVar "status",CL.#!=, CL.mkVar RN.kStabilize), |
573 |
|
CL.#&&, |
574 |
|
CL.mkBinOp(CL.mkVar "status", CL.#!=, CL.mkVar RN.kDie)) |
575 |
|
val whileBody = CL.mkBlock (swapStms @ [ |
576 |
|
(* FIXME: need a barrier synchronization at beginning of loop *) |
577 |
CL.mkAssign(CL.mkVar "status", |
CL.mkAssign(CL.mkVar "status", |
578 |
CL.mkApply(RN.strandUpdate name, |
CL.mkApply(RN.strandUpdate name, |
579 |
[CL.mkUnOp(CL.%&,CL.mkVar inState), CL.mkUnOp(CL.%&,CL.mkVar outState)])), |
[CL.mkVar inState, CL.mkVar outState,CL.E_Var RN.globalsVarName]))] ) |
|
CL.mkCall(RN.strandStabilize name, |
|
|
[CL.mkUnOp(CL.%&,CL.mkVar inState), CL.mkUnOp(CL.%&,CL.mkVar outState)]) |
|
|
] |
|
580 |
val whileBlock = [CL.mkWhile(while_exp, whileBody)] |
val whileBlock = [CL.mkWhile(while_exp, whileBody)] |
581 |
val body = CL.mkBlock(local_vars @ whileBlock) |
val body = CL.mkBlock(local_vars @ whileBlock) |
582 |
in |
in |
588 |
in |
in |
589 |
CL.D_StructDef(globs, RN.globalsTy) |
CL.D_StructDef(globs, RN.globalsTy) |
590 |
end |
end |
591 |
|
|
592 |
fun genGlobals (declFn, targetTy, globals) = let |
fun genGlobals (declFn, targetTy, globals) = let |
593 |
fun doVar (x : mirror_var) = declFn (CL.D_Var([], targetTy x, #var x, NONE)) |
fun doVar (x : mirror_var) = declFn (CL.D_Var([], targetTy x, #var x, NONE)) |
594 |
in |
in |
595 |
List.app doVar globals |
List.app doVar globals |
596 |
end |
end |
597 |
|
|
598 |
fun genSrc (baseName, Prog{double,globals, topDecls, strands, initially,imgGlobals,numDims,...}) = let |
fun genStrandDesc (Strand{name, output, ...}) = let |
599 |
|
(* the strand's descriptor object *) |
600 |
|
val descI = let |
601 |
|
fun fnPtr (ty, f) = CL.I_Exp(CL.mkCast(CL.T_Named ty, CL.mkVar f)) |
602 |
|
val SOME(outTy, _) = !output |
603 |
|
in |
604 |
|
CL.I_Struct[ |
605 |
|
("name", CL.I_Exp(CL.mkStr name)), |
606 |
|
("stateSzb", CL.I_Exp(CL.mkSizeof(CL.T_Named(N.strandTy name)))), |
607 |
|
(* |
608 |
|
("outputSzb", CL.I_Exp(CL.mkSizeof(ToC.trTy outTy))), |
609 |
|
*) |
610 |
|
("update", fnPtr("update_method_t", "0")), |
611 |
|
("print", fnPtr("print_method_t", name ^ "_print")) |
612 |
|
] |
613 |
|
end |
614 |
|
val desc = CL.D_Var([], CL.T_Named N.strandDescTy, N.strandDesc name, SOME descI) |
615 |
|
in |
616 |
|
desc |
617 |
|
end |
618 |
|
|
619 |
|
(* generate the table of strand descriptors *) |
620 |
|
fun genStrandTable (declFn, strands) = let |
621 |
|
val nStrands = length strands |
622 |
|
fun genInit (Strand{name, ...}) = CL.I_Exp(CL.mkUnOp(CL.%&, CL.E_Var(N.strandDesc name))) |
623 |
|
fun genInits (_, []) = [] |
624 |
|
| genInits (i, s::ss) = (i, genInit s) :: genInits(i+1, ss) |
625 |
|
in |
626 |
|
declFn (CL.D_Var([], CL.int32, N.numStrands, |
627 |
|
SOME(CL.I_Exp(CL.E_Int(IntInf.fromInt nStrands, CL.int32))))); |
628 |
|
declFn (CL.D_Var([], |
629 |
|
CL.T_Array(CL.T_Ptr(CL.T_Named N.strandDescTy), SOME nStrands), |
630 |
|
N.strands, |
631 |
|
SOME(CL.I_Array(genInits (0, strands))))) |
632 |
|
end |
633 |
|
|
634 |
|
fun genSrc (baseName, prog) = let |
635 |
|
val Prog{name,double, globals, topDecls, strands, initially, imgGlobals, numDims, ...} = prog |
636 |
val clFileName = OS.Path.joinBaseExt{base=baseName, ext=SOME "cl"} |
val clFileName = OS.Path.joinBaseExt{base=baseName, ext=SOME "cl"} |
637 |
val cFileName = OS.Path.joinBaseExt{base=baseName, ext=SOME "c"} |
val cFileName = OS.Path.joinBaseExt{base=baseName, ext=SOME "c"} |
638 |
val clOutS = TextIO.openOut clFileName |
val clOutS = TextIO.openOut clFileName |
639 |
val cOutS = TextIO.openOut cFileName |
val cOutS = TextIO.openOut cFileName |
|
(* FIXME: need to use PrintAsC and PrintAsCL *) |
|
640 |
val clppStrm = PrintAsCL.new clOutS |
val clppStrm = PrintAsCL.new clOutS |
641 |
val cppStrm = PrintAsC.new cOutS |
val cppStrm = PrintAsC.new cOutS |
642 |
|
val progName = name |
643 |
fun cppDecl dcl = PrintAsC.output(cppStrm, dcl) |
fun cppDecl dcl = PrintAsC.output(cppStrm, dcl) |
644 |
fun clppDecl dcl = PrintAsCL.output(clppStrm, dcl) |
fun clppDecl dcl = PrintAsCL.output(clppStrm, dcl) |
645 |
val strands = AtomTable.listItems strands |
val strands = AtomTable.listItems strands |
653 |
"#define DIDEROT_TARGET_CL", |
"#define DIDEROT_TARGET_CL", |
654 |
"#include \"Diderot/cl-diderot.h\"" |
"#include \"Diderot/cl-diderot.h\"" |
655 |
])); |
])); |
|
genGlobals (clppDecl, #gpuTy, !globals); |
|
656 |
clppDecl (genGlobalStruct (#gpuTy, !globals)); |
clppDecl (genGlobalStruct (#gpuTy, !globals)); |
657 |
clppDecl (genStrandTyDef(#gpuTy, strand)); |
clppDecl (genStrandTyDef(#gpuTy, strand)); |
658 |
|
clppDecl (!init_code); |
659 |
List.app clppDecl (!code); |
List.app clppDecl (!code); |
660 |
clppDecl (genKernelFun (strand, !numDims, globals, imgGlobals)); |
clppDecl (genKernelFun (strand, !numDims, globals, imgGlobals)); |
|
|
|
661 |
(* Generate the Host C file *) |
(* Generate the Host C file *) |
662 |
cppDecl (CL.D_Verbatim([ |
cppDecl (CL.D_Verbatim([ |
663 |
if double |
if double |
666 |
"#define DIDEROT_TARGET_CL", |
"#define DIDEROT_TARGET_CL", |
667 |
"#include \"Diderot/diderot.h\"" |
"#include \"Diderot/diderot.h\"" |
668 |
])); |
])); |
669 |
genGlobals (cppDecl, #hostTy, !globals); |
cppDecl (CL.D_Var(["static"], CL.charPtr, "ProgramName", |
670 |
|
SOME(CL.I_Exp(CL.mkStr progName)))); |
671 |
cppDecl (genGlobalStruct (#hostTy, !globals)); |
cppDecl (genGlobalStruct (#hostTy, !globals)); |
672 |
cppDecl (genStrandTyDef (#gpuTy, strand)); |
cppDecl (CL.D_Var(["static"], CL.T_Ptr(CL.T_Named RN.globalsTy), RN.globalsVarName, NONE)); |
673 |
cppDecl (!init_code); |
cppDecl (genStrandTyDef (#hostTy, strand)); |
674 |
cppDecl (genStrandPrint strand); |
cppDecl (genStrandPrint strand); |
675 |
List.app cppDecl (List.rev (!topDecls)); |
List.app cppDecl (List.rev (!topDecls)); |
676 |
cppDecl (genGlobalBuffersArgs (imgGlobals)); |
cppDecl (genGlobalBuffersArgs imgGlobals); |
677 |
|
List.app (fn strand => cppDecl (genStrandDesc strand)) strands; |
678 |
|
genStrandTable (cppDecl, strands); |
679 |
cppDecl (!initially); |
cppDecl (!initially); |
680 |
PrintAsC.close cppStrm; |
PrintAsC.close cppStrm; |
681 |
PrintAsCL.close clppStrm; |
PrintAsCL.close clppStrm; |
740 |
fun init (Strand{name, tyName, code,init_code, ...}, params, init) = let |
fun init (Strand{name, tyName, code,init_code, ...}, params, init) = let |
741 |
val fName = RN.strandInit name |
val fName = RN.strandInit name |
742 |
val params = |
val params = |
743 |
CL.PARAM([], CL.T_Ptr(CL.T_Named tyName), "selfOut") :: |
globalParam (globPtrTy, RN.globalsVarName) :: |
744 |
|
globalParam (CL.T_Ptr(CL.T_Named tyName), "selfOut") :: |
745 |
List.map (fn (ToCL.V(ty, x)) => CL.PARAM([], ty, x)) params |
List.map (fn (ToCL.V(ty, x)) => CL.PARAM([], ty, x)) params |
746 |
val initFn = CL.D_Func([], CL.voidTy, fName, params, init) |
val initFn = CL.D_Func([], CL.voidTy, fName, params, init) |
747 |
in |
in |
752 |
fun method (Strand{name, tyName, code,...}, methName, body) = let |
fun method (Strand{name, tyName, code,...}, methName, body) = let |
753 |
val fName = concat[name, "_", methName] |
val fName = concat[name, "_", methName] |
754 |
val params = [ |
val params = [ |
755 |
CL.PARAM([], CL.T_Ptr(CL.T_Named tyName), "selfIn"), |
globalParam (CL.T_Ptr(CL.T_Named tyName), "selfIn"), |
756 |
CL.PARAM([], CL.T_Ptr(CL.T_Named tyName), "selfOut") |
globalParam (CL.T_Ptr(CL.T_Named tyName), "selfOut"), |
757 |
|
globalParam (CL.T_Ptr(CL.T_Named (RN.globalsTy)), RN.globalsVarName) |
758 |
] |
] |
759 |
val methFn = CL.D_Func([], CL.int32, fName, params, body) |
val methFn = CL.D_Func([], CL.int32, fName, params, body) |
760 |
in |
in |