cannam@167
|
1 (*
|
cannam@167
|
2 * Copyright (c) 1997-1999 Massachusetts Institute of Technology
|
cannam@167
|
3 * Copyright (c) 2003, 2007-14 Matteo Frigo
|
cannam@167
|
4 * Copyright (c) 2003, 2007-14 Massachusetts Institute of Technology
|
cannam@167
|
5 *
|
cannam@167
|
6 * This program is free software; you can redistribute it and/or modify
|
cannam@167
|
7 * it under the terms of the GNU General Public License as published by
|
cannam@167
|
8 * the Free Software Foundation; either version 2 of the License, or
|
cannam@167
|
9 * (at your option) any later version.
|
cannam@167
|
10 *
|
cannam@167
|
11 * This program is distributed in the hope that it will be useful,
|
cannam@167
|
12 * but WITHOUT ANY WARRANTY; without even the implied warranty of
|
cannam@167
|
13 * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
cannam@167
|
14 * GNU General Public License for more details.
|
cannam@167
|
15 *
|
cannam@167
|
16 * You should have received a copy of the GNU General Public License
|
cannam@167
|
17 * along with this program; if not, write to the Free Software
|
cannam@167
|
18 * Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA
|
cannam@167
|
19 *
|
cannam@167
|
20 *)
|
cannam@167
|
21
|
cannam@167
|
22 (*
|
cannam@167
|
23 * This module contains the definition of a C-like abstract
|
cannam@167
|
24 * syntax tree, and functions to convert ML values into C
|
cannam@167
|
25 * programs
|
cannam@167
|
26 *)
|
cannam@167
|
27
|
cannam@167
|
28 open Expr
|
cannam@167
|
29 open Annotate
|
cannam@167
|
30 open List
|
cannam@167
|
31
|
cannam@167
|
32 let realtype = "R"
|
cannam@167
|
33 let realtypep = realtype ^ " *"
|
cannam@167
|
34 let extended_realtype = "E"
|
cannam@167
|
35 let constrealtype = "const " ^ realtype
|
cannam@167
|
36 let constrealtypep = constrealtype ^ " *"
|
cannam@167
|
37
|
cannam@167
|
38 let stridetype = "stride"
|
cannam@167
|
39
|
cannam@167
|
40 (***********************************
|
cannam@167
|
41 * C program structure
|
cannam@167
|
42 ***********************************)
|
cannam@167
|
43 type c_decl =
|
cannam@167
|
44 | Decl of string * string
|
cannam@167
|
45 | Tdecl of string (* arbitrary text declaration *)
|
cannam@167
|
46
|
cannam@167
|
47 and c_ast =
|
cannam@167
|
48 | Asch of annotated_schedule
|
cannam@167
|
49 | Simd_leavefun
|
cannam@167
|
50 | Return of c_ast
|
cannam@167
|
51 | For of c_ast * c_ast * c_ast * c_ast
|
cannam@167
|
52 | If of c_ast * c_ast
|
cannam@167
|
53 | Block of (c_decl list) * (c_ast list)
|
cannam@167
|
54 | Binop of string * c_ast * c_ast
|
cannam@167
|
55 | Expr_assign of c_ast * c_ast
|
cannam@167
|
56 | Stmt_assign of c_ast * c_ast
|
cannam@167
|
57 | Comma of c_ast * c_ast
|
cannam@167
|
58 | Integer of int
|
cannam@167
|
59 | CVar of string
|
cannam@167
|
60 | CCall of string * c_ast
|
cannam@167
|
61 | CPlus of c_ast list
|
cannam@167
|
62 | ITimes of c_ast * c_ast
|
cannam@167
|
63 | CUminus of c_ast
|
cannam@167
|
64 and c_fcn = Fcn of string * string * (c_decl list) * c_ast
|
cannam@167
|
65
|
cannam@167
|
66
|
cannam@167
|
67 let ctimes = function
|
cannam@167
|
68 | (Integer 1), a -> a
|
cannam@167
|
69 | a, (Integer 1) -> a
|
cannam@167
|
70 | a, b -> ITimes (a, b)
|
cannam@167
|
71
|
cannam@167
|
72 (*
|
cannam@167
|
73 * C AST unparser
|
cannam@167
|
74 *)
|
cannam@167
|
75 let foldr_string_concat l = fold_right (^) l ""
|
cannam@167
|
76
|
cannam@167
|
77 let rec unparse_expr_c =
|
cannam@167
|
78 let yes x = x and no x = "" in
|
cannam@167
|
79
|
cannam@167
|
80 let rec unparse_plus maybe =
|
cannam@167
|
81 let maybep = maybe " + " in
|
cannam@167
|
82 function
|
cannam@167
|
83 | [] -> ""
|
cannam@167
|
84 | (Uminus (Times (a, b))) :: (Uminus c) :: d ->
|
cannam@167
|
85 maybep ^ (op "FNMA" a b c) ^ (unparse_plus yes d)
|
cannam@167
|
86 | (Uminus c) :: (Uminus (Times (a, b))) :: d ->
|
cannam@167
|
87 maybep ^ (op "FNMA" a b c) ^ (unparse_plus yes d)
|
cannam@167
|
88 | (Uminus (Times (a, b))) :: c :: d ->
|
cannam@167
|
89 maybep ^ (op "FNMS" a b c) ^ (unparse_plus yes d)
|
cannam@167
|
90 | c :: (Uminus (Times (a, b))) :: d ->
|
cannam@167
|
91 maybep ^ (op "FNMS" a b c) ^ (unparse_plus yes d)
|
cannam@167
|
92 | (Times (a, b)) :: (Uminus c) :: d ->
|
cannam@167
|
93 maybep ^ (op "FMS" a b c) ^ (unparse_plus yes d)
|
cannam@167
|
94 | (Uminus c) :: (Times (a, b)) :: d ->
|
cannam@167
|
95 maybep ^ (op "FMS" a b c) ^ (unparse_plus yes d)
|
cannam@167
|
96 | (Times (a, b)) :: c :: d ->
|
cannam@167
|
97 maybep ^ (op "FMA" a b c) ^ (unparse_plus yes d)
|
cannam@167
|
98 | c :: (Times (a, b)) :: d ->
|
cannam@167
|
99 maybep ^ (op "FMA" a b c) ^ (unparse_plus yes d)
|
cannam@167
|
100 | (Uminus a :: b) ->
|
cannam@167
|
101 " - " ^ (parenthesize a) ^ (unparse_plus yes b)
|
cannam@167
|
102 | (a :: b) ->
|
cannam@167
|
103 maybep ^ (parenthesize a) ^ (unparse_plus yes b)
|
cannam@167
|
104 and parenthesize x = match x with
|
cannam@167
|
105 | (Load _) -> unparse_expr_c x
|
cannam@167
|
106 | (Num _) -> unparse_expr_c x
|
cannam@167
|
107 | _ -> "(" ^ (unparse_expr_c x) ^ ")"
|
cannam@167
|
108 and op nam a b c =
|
cannam@167
|
109 nam ^ "(" ^ (unparse_expr_c a) ^ ", " ^ (unparse_expr_c b) ^ ", " ^
|
cannam@167
|
110 (unparse_expr_c c) ^ ")"
|
cannam@167
|
111
|
cannam@167
|
112 in function
|
cannam@167
|
113 | Load v -> Variable.unparse v
|
cannam@167
|
114 | Num n -> Number.to_konst n
|
cannam@167
|
115 | Plus [] -> "0.0 /* bug */"
|
cannam@167
|
116 | Plus [a] -> " /* bug */ " ^ (unparse_expr_c a)
|
cannam@167
|
117 | Plus a -> (unparse_plus no a)
|
cannam@167
|
118 | Times (a, b) -> (parenthesize a) ^ " * " ^ (parenthesize b)
|
cannam@167
|
119 | Uminus (Plus [a; Uminus b]) -> unparse_plus no [b; Uminus a]
|
cannam@167
|
120 | Uminus a -> "- " ^ (parenthesize a)
|
cannam@167
|
121 | _ -> failwith "unparse_expr_c"
|
cannam@167
|
122
|
cannam@167
|
123 and unparse_expr_generic =
|
cannam@167
|
124 let rec u x = unparse_expr_generic x
|
cannam@167
|
125 and unary op a = Printf.sprintf "%s(%s)" op (u a)
|
cannam@167
|
126 and binary op a b = Printf.sprintf "%s(%s, %s)" op (u a) (u b)
|
cannam@167
|
127 and ternary op a b c = Printf.sprintf "%s(%s, %s, %s)" op (u a) (u b) (u c)
|
cannam@167
|
128 and quaternary op a b c d =
|
cannam@167
|
129 Printf.sprintf "%s(%s, %s, %s, %s)" op (u a) (u b) (u c) (u d)
|
cannam@167
|
130 and unparse_plus = function
|
cannam@167
|
131 | [(Uminus (Times (a, b))); Times (c, d)] -> quaternary "FNMMS" a b c d
|
cannam@167
|
132 | [Times (c, d); (Uminus (Times (a, b)))] -> quaternary "FNMMS" a b c d
|
cannam@167
|
133 | [Times (c, d); (Times (a, b))] -> quaternary "FMMA" a b c d
|
cannam@167
|
134 | [(Uminus (Times (a, b))); c] -> ternary "FNMS" a b c
|
cannam@167
|
135 | [c; (Uminus (Times (a, b)))] -> ternary "FNMS" a b c
|
cannam@167
|
136 | [(Uminus c); (Times (a, b))] -> ternary "FMS" a b c
|
cannam@167
|
137 | [(Times (a, b)); (Uminus c)] -> ternary "FMS" a b c
|
cannam@167
|
138 | [c; (Times (a, b))] -> ternary "FMA" a b c
|
cannam@167
|
139 | [(Times (a, b)); c] -> ternary "FMA" a b c
|
cannam@167
|
140 | [a; Uminus b] -> binary "SUB" a b
|
cannam@167
|
141 | [a; b] -> binary "ADD" a b
|
cannam@167
|
142 | a :: b :: c -> binary "ADD" a (Plus (b :: c))
|
cannam@167
|
143 | _ -> failwith "unparse_plus"
|
cannam@167
|
144 in function
|
cannam@167
|
145 | Load v -> Variable.unparse v
|
cannam@167
|
146 | Num n -> Number.to_konst n
|
cannam@167
|
147 | Plus a -> unparse_plus a
|
cannam@167
|
148 | Times (a, b) -> binary "MUL" a b
|
cannam@167
|
149 | Uminus a -> unary "NEG" a
|
cannam@167
|
150 | _ -> failwith "unparse_expr"
|
cannam@167
|
151
|
cannam@167
|
152 and unparse_expr x =
|
cannam@167
|
153 if !Magic.generic_arith then
|
cannam@167
|
154 unparse_expr_generic x
|
cannam@167
|
155 else
|
cannam@167
|
156 unparse_expr_c x
|
cannam@167
|
157
|
cannam@167
|
158 and unparse_assignment (Assign (v, x)) =
|
cannam@167
|
159 (Variable.unparse v) ^ " = " ^ (unparse_expr x) ^ ";\n"
|
cannam@167
|
160
|
cannam@167
|
161 and unparse_annotated force_bracket =
|
cannam@167
|
162 let rec unparse_code = function
|
cannam@167
|
163 ADone -> ""
|
cannam@167
|
164 | AInstr i -> unparse_assignment i
|
cannam@167
|
165 | ASeq (a, b) ->
|
cannam@167
|
166 (unparse_annotated false a) ^ (unparse_annotated false b)
|
cannam@167
|
167 and declare_variables l =
|
cannam@167
|
168 let rec uvar = function
|
cannam@167
|
169 [] -> failwith "uvar"
|
cannam@167
|
170 | [v] -> (Variable.unparse v) ^ ";\n"
|
cannam@167
|
171 | a :: b -> (Variable.unparse a) ^ ", " ^ (uvar b)
|
cannam@167
|
172 in let rec vvar l =
|
cannam@167
|
173 let s = if !Magic.compact then 15 else 1 in
|
cannam@167
|
174 if (List.length l <= s) then
|
cannam@167
|
175 match l with
|
cannam@167
|
176 [] -> ""
|
cannam@167
|
177 | _ -> extended_realtype ^ " " ^ (uvar l)
|
cannam@167
|
178 else
|
cannam@167
|
179 (vvar (Util.take s l)) ^ (vvar (Util.drop s l))
|
cannam@167
|
180 in vvar (List.filter Variable.is_temporary l)
|
cannam@167
|
181 in function
|
cannam@167
|
182 Annotate (_, _, decl, _, code) ->
|
cannam@167
|
183 if (not force_bracket) && (Util.null decl) then
|
cannam@167
|
184 unparse_code code
|
cannam@167
|
185 else "{\n" ^
|
cannam@167
|
186 (declare_variables decl) ^
|
cannam@167
|
187 (unparse_code code) ^
|
cannam@167
|
188 "}\n"
|
cannam@167
|
189
|
cannam@167
|
190 and unparse_decl = function
|
cannam@167
|
191 | Decl (a, b) -> a ^ " " ^ b ^ ";\n"
|
cannam@167
|
192 | Tdecl x -> x
|
cannam@167
|
193
|
cannam@167
|
194 and unparse_ast =
|
cannam@167
|
195 let rec unparse_plus = function
|
cannam@167
|
196 | [] -> ""
|
cannam@167
|
197 | (CUminus a :: b) -> " - " ^ (parenthesize a) ^ (unparse_plus b)
|
cannam@167
|
198 | (a :: b) -> " + " ^ (parenthesize a) ^ (unparse_plus b)
|
cannam@167
|
199 and parenthesize x = match x with
|
cannam@167
|
200 | (CVar _) -> unparse_ast x
|
cannam@167
|
201 | (CCall _) -> unparse_ast x
|
cannam@167
|
202 | (Integer _) -> unparse_ast x
|
cannam@167
|
203 | _ -> "(" ^ (unparse_ast x) ^ ")"
|
cannam@167
|
204
|
cannam@167
|
205 in
|
cannam@167
|
206 function
|
cannam@167
|
207 | Asch a -> (unparse_annotated true a)
|
cannam@167
|
208 | Simd_leavefun -> "" (* used only in SIMD code *)
|
cannam@167
|
209 | Return x -> "return " ^ unparse_ast x ^ ";"
|
cannam@167
|
210 | For (a, b, c, d) ->
|
cannam@167
|
211 "for (" ^
|
cannam@167
|
212 unparse_ast a ^ "; " ^ unparse_ast b ^ "; " ^ unparse_ast c
|
cannam@167
|
213 ^ ")" ^ unparse_ast d
|
cannam@167
|
214 | If (a, d) ->
|
cannam@167
|
215 "if (" ^
|
cannam@167
|
216 unparse_ast a
|
cannam@167
|
217 ^ ")" ^ unparse_ast d
|
cannam@167
|
218 | Block (d, s) ->
|
cannam@167
|
219 if (s == []) then ""
|
cannam@167
|
220 else
|
cannam@167
|
221 "{\n" ^
|
cannam@167
|
222 foldr_string_concat (map unparse_decl d) ^
|
cannam@167
|
223 foldr_string_concat (map unparse_ast s) ^
|
cannam@167
|
224 "}\n"
|
cannam@167
|
225 | Binop (op, a, b) -> (unparse_ast a) ^ op ^ (unparse_ast b)
|
cannam@167
|
226 | Expr_assign (a, b) -> (unparse_ast a) ^ " = " ^ (unparse_ast b)
|
cannam@167
|
227 | Stmt_assign (a, b) -> (unparse_ast a) ^ " = " ^ (unparse_ast b) ^ ";\n"
|
cannam@167
|
228 | Comma (a, b) -> (unparse_ast a) ^ ", " ^ (unparse_ast b)
|
cannam@167
|
229 | Integer i -> string_of_int i
|
cannam@167
|
230 | CVar s -> s
|
cannam@167
|
231 | CCall (s, x) -> s ^ "(" ^ (unparse_ast x) ^ ")"
|
cannam@167
|
232 | CPlus [] -> "0 /* bug */"
|
cannam@167
|
233 | CPlus [a] -> " /* bug */ " ^ (unparse_ast a)
|
cannam@167
|
234 | CPlus (a::b) -> (parenthesize a) ^ (unparse_plus b)
|
cannam@167
|
235 | ITimes (a, b) -> (parenthesize a) ^ " * " ^ (parenthesize b)
|
cannam@167
|
236 | CUminus a -> "- " ^ (parenthesize a)
|
cannam@167
|
237
|
cannam@167
|
238 and unparse_function = function
|
cannam@167
|
239 Fcn (typ, name, args, body) ->
|
cannam@167
|
240 let rec unparse_args = function
|
cannam@167
|
241 [Decl (a, b)] -> a ^ " " ^ b
|
cannam@167
|
242 | (Decl (a, b)) :: s -> a ^ " " ^ b ^ ", "
|
cannam@167
|
243 ^ unparse_args s
|
cannam@167
|
244 | [] -> ""
|
cannam@167
|
245 | _ -> failwith "unparse_function"
|
cannam@167
|
246 in
|
cannam@167
|
247 (typ ^ " " ^ name ^ "(" ^ unparse_args args ^ ")\n" ^
|
cannam@167
|
248 unparse_ast body)
|
cannam@167
|
249
|
cannam@167
|
250
|
cannam@167
|
251 (*************************************************************
|
cannam@167
|
252 * traverse a a function and return a list of all expressions,
|
cannam@167
|
253 * in the execution order
|
cannam@167
|
254 **************************************************************)
|
cannam@167
|
255 let rec fcn_to_expr_list = fun (Fcn (_, _, _, body)) -> ast_to_expr_list body
|
cannam@167
|
256 and acode_to_expr_list = function
|
cannam@167
|
257 AInstr (Assign (_, x)) -> [x]
|
cannam@167
|
258 | ASeq (a, b) ->
|
cannam@167
|
259 (asched_to_expr_list a) @ (asched_to_expr_list b)
|
cannam@167
|
260 | _ -> []
|
cannam@167
|
261 and asched_to_expr_list (Annotate (_, _, _, _, code)) =
|
cannam@167
|
262 acode_to_expr_list code
|
cannam@167
|
263 and ast_to_expr_list = function
|
cannam@167
|
264 Asch a -> asched_to_expr_list a
|
cannam@167
|
265 | Block (_, a) -> flatten (map ast_to_expr_list a)
|
cannam@167
|
266 | For (_, _, _, body) -> ast_to_expr_list body
|
cannam@167
|
267 | If (_, body) -> ast_to_expr_list body
|
cannam@167
|
268 | _ -> []
|
cannam@167
|
269
|
cannam@167
|
270 (***********************
|
cannam@167
|
271 * Extracting Constants
|
cannam@167
|
272 ***********************)
|
cannam@167
|
273
|
cannam@167
|
274 (* add a new key & value to a list of (key,value) pairs, where
|
cannam@167
|
275 the keys are floats and each key is unique up to almost_equal *)
|
cannam@167
|
276
|
cannam@167
|
277 let extract_constants f =
|
cannam@167
|
278 let constlist = flatten (map expr_to_constants (ast_to_expr_list f))
|
cannam@167
|
279 in map
|
cannam@167
|
280 (fun n ->
|
cannam@167
|
281 Tdecl
|
cannam@167
|
282 ("DK(" ^ (Number.to_konst n) ^ ", " ^ (Number.to_string n) ^
|
cannam@167
|
283 ");\n"))
|
cannam@167
|
284 (unique_constants constlist)
|
cannam@167
|
285
|
cannam@167
|
286 (******************************
|
cannam@167
|
287 Extracting operation counts
|
cannam@167
|
288 ******************************)
|
cannam@167
|
289
|
cannam@167
|
290 let count_stack_vars =
|
cannam@167
|
291 let rec count_acode = function
|
cannam@167
|
292 | ASeq (a, b) -> max (count_asched a) (count_asched b)
|
cannam@167
|
293 | _ -> 0
|
cannam@167
|
294 and count_asched (Annotate (_, _, decl, _, code)) =
|
cannam@167
|
295 (length decl) + (count_acode code)
|
cannam@167
|
296 and count_ast = function
|
cannam@167
|
297 | Asch a -> count_asched a
|
cannam@167
|
298 | Block (d, a) -> (length d) + (Util.max_list (map count_ast a))
|
cannam@167
|
299 | For (_, _, _, body) -> count_ast body
|
cannam@167
|
300 | If (_, body) -> count_ast body
|
cannam@167
|
301 | _ -> 0
|
cannam@167
|
302 in function (Fcn (_, _, _, body)) -> count_ast body
|
cannam@167
|
303
|
cannam@167
|
304 let count_memory_acc f =
|
cannam@167
|
305 let rec count_var v =
|
cannam@167
|
306 if (Variable.is_locative v) then 1 else 0
|
cannam@167
|
307 and count_acode = function
|
cannam@167
|
308 | AInstr (Assign (v, _)) -> count_var v
|
cannam@167
|
309 | ASeq (a, b) -> (count_asched a) + (count_asched b)
|
cannam@167
|
310 | _ -> 0
|
cannam@167
|
311 and count_asched = function
|
cannam@167
|
312 Annotate (_, _, _, _, code) -> count_acode code
|
cannam@167
|
313 and count_ast = function
|
cannam@167
|
314 | Asch a -> count_asched a
|
cannam@167
|
315 | Block (_, a) -> (Util.sum_list (map count_ast a))
|
cannam@167
|
316 | Comma (a, b) -> (count_ast a) + (count_ast b)
|
cannam@167
|
317 | For (_, _, _, body) -> count_ast body
|
cannam@167
|
318 | If (_, body) -> count_ast body
|
cannam@167
|
319 | _ -> 0
|
cannam@167
|
320 and count_acc_expr_func acc = function
|
cannam@167
|
321 | Load v -> acc + (count_var v)
|
cannam@167
|
322 | Plus a -> fold_left count_acc_expr_func acc a
|
cannam@167
|
323 | Times (a, b) -> fold_left count_acc_expr_func acc [a; b]
|
cannam@167
|
324 | Uminus a -> count_acc_expr_func acc a
|
cannam@167
|
325 | _ -> acc
|
cannam@167
|
326 in let (Fcn (typ, name, args, body)) = f
|
cannam@167
|
327 in (count_ast body) +
|
cannam@167
|
328 fold_left count_acc_expr_func 0 (fcn_to_expr_list f)
|
cannam@167
|
329
|
cannam@167
|
330 let good_for_fma = To_alist.good_for_fma
|
cannam@167
|
331
|
cannam@167
|
332 let build_fma = function
|
cannam@167
|
333 | [a; Times (b, c)] when good_for_fma (b, c) -> Some (a, b, c)
|
cannam@167
|
334 | [Times (b, c); a] when good_for_fma (b, c) -> Some (a, b, c)
|
cannam@167
|
335 | [a; Uminus (Times (b, c))] when good_for_fma (b, c) -> Some (a, b, c)
|
cannam@167
|
336 | [Uminus (Times (b, c)); a] when good_for_fma (b, c) -> Some (a, b, c)
|
cannam@167
|
337 | _ -> None
|
cannam@167
|
338
|
cannam@167
|
339 let rec count_flops_expr_func (adds, mults, fmas) = function
|
cannam@167
|
340 | Plus [] -> (adds, mults, fmas)
|
cannam@167
|
341 | Plus ([_; _] as a) ->
|
cannam@167
|
342 begin
|
cannam@167
|
343 match build_fma a with
|
cannam@167
|
344 | None ->
|
cannam@167
|
345 fold_left count_flops_expr_func
|
cannam@167
|
346 (adds + (length a) - 1, mults, fmas) a
|
cannam@167
|
347 | Some (a, b, c) ->
|
cannam@167
|
348 fold_left count_flops_expr_func (adds, mults, fmas+1) [a; b; c]
|
cannam@167
|
349 end
|
cannam@167
|
350 | Plus (a :: b) ->
|
cannam@167
|
351 count_flops_expr_func (adds, mults, fmas) (Plus [a; Plus b])
|
cannam@167
|
352 | Times (NaN MULTI_A,_) -> (adds, mults, fmas)
|
cannam@167
|
353 | Times (NaN MULTI_B,_) -> (adds, mults, fmas)
|
cannam@167
|
354 | Times (NaN I,b) -> count_flops_expr_func (adds, mults, fmas) b
|
cannam@167
|
355 | Times (NaN CONJ,b) -> count_flops_expr_func (adds, mults, fmas) b
|
cannam@167
|
356 | Times (a,b) -> fold_left count_flops_expr_func (adds, mults+1, fmas) [a; b]
|
cannam@167
|
357 | CTimes (a,b) ->
|
cannam@167
|
358 fold_left count_flops_expr_func (adds+1, mults+2, fmas) [a; b]
|
cannam@167
|
359 | CTimesJ (a,b) ->
|
cannam@167
|
360 fold_left count_flops_expr_func (adds+1, mults+2, fmas) [a; b]
|
cannam@167
|
361 | Uminus a -> count_flops_expr_func (adds, mults, fmas) a
|
cannam@167
|
362 | _ -> (adds, mults, fmas)
|
cannam@167
|
363
|
cannam@167
|
364 let count_flops f =
|
cannam@167
|
365 fold_left count_flops_expr_func (0, 0, 0) (fcn_to_expr_list f)
|
cannam@167
|
366
|
cannam@167
|
367 let count_constants f =
|
cannam@167
|
368 length (unique_constants (flatten (map expr_to_constants (fcn_to_expr_list f))))
|
cannam@167
|
369
|
cannam@167
|
370 let arith_complexity f =
|
cannam@167
|
371 let (a, m, fmas) = count_flops f
|
cannam@167
|
372 and v = count_stack_vars f
|
cannam@167
|
373 and c = count_constants f
|
cannam@167
|
374 and mem = count_memory_acc f
|
cannam@167
|
375 in (a, m, fmas, v, c, mem)
|
cannam@167
|
376
|
cannam@167
|
377 (* print the operation costs *)
|
cannam@167
|
378 let print_cost f =
|
cannam@167
|
379 let Fcn (_, _, _, _) = f
|
cannam@167
|
380 and (a, m, fmas, v, c, mem) = arith_complexity f
|
cannam@167
|
381 in
|
cannam@167
|
382 "/*\n"^
|
cannam@167
|
383 " * This function contains " ^
|
cannam@167
|
384 (string_of_int (a + fmas)) ^ " FP additions, " ^
|
cannam@167
|
385 (string_of_int (m + fmas)) ^ " FP multiplications,\n" ^
|
cannam@167
|
386 " * (or, " ^
|
cannam@167
|
387 (string_of_int a) ^ " additions, " ^
|
cannam@167
|
388 (string_of_int m) ^ " multiplications, " ^
|
cannam@167
|
389 (string_of_int fmas) ^ " fused multiply/add),\n" ^
|
cannam@167
|
390 " * " ^ (string_of_int v) ^ " stack variables, " ^
|
cannam@167
|
391 (string_of_int c) ^ " constants, and " ^
|
cannam@167
|
392 (string_of_int mem) ^ " memory accesses\n" ^
|
cannam@167
|
393 " */\n"
|
cannam@167
|
394
|
cannam@167
|
395 (*****************************************
|
cannam@167
|
396 * functions that create C arrays
|
cannam@167
|
397 *****************************************)
|
cannam@167
|
398 type stride =
|
cannam@167
|
399 | SVar of string
|
cannam@167
|
400 | SConst of string
|
cannam@167
|
401 | SInteger of int
|
cannam@167
|
402 | SNeg of stride
|
cannam@167
|
403
|
cannam@167
|
404 type sstride =
|
cannam@167
|
405 | Simple of int
|
cannam@167
|
406 | Constant of (string * int)
|
cannam@167
|
407 | Composite of (string * int)
|
cannam@167
|
408 | Negative of sstride
|
cannam@167
|
409
|
cannam@167
|
410 let rec simplify_stride stride i =
|
cannam@167
|
411 match (stride, i) with
|
cannam@167
|
412 (_, 0) -> Simple 0
|
cannam@167
|
413 | (SInteger n, i) -> Simple (n * i)
|
cannam@167
|
414 | (SConst s, i) -> Constant (s, i)
|
cannam@167
|
415 | (SVar s, i) -> Composite (s, i)
|
cannam@167
|
416 | (SNeg x, i) ->
|
cannam@167
|
417 match (simplify_stride x i) with
|
cannam@167
|
418 | Negative y -> y
|
cannam@167
|
419 | y -> Negative y
|
cannam@167
|
420
|
cannam@167
|
421 let rec cstride_to_string = function
|
cannam@167
|
422 | Simple i -> string_of_int i
|
cannam@167
|
423 | Constant (s, i) ->
|
cannam@167
|
424 if !Magic.lisp_syntax then
|
cannam@167
|
425 "(* " ^ s ^ " " ^ (string_of_int i) ^ ")"
|
cannam@167
|
426 else
|
cannam@167
|
427 s ^ " * " ^ (string_of_int i)
|
cannam@167
|
428 | Composite (s, i) ->
|
cannam@167
|
429 if !Magic.lisp_syntax then
|
cannam@167
|
430 "(* " ^ s ^ " " ^ (string_of_int i) ^ ")"
|
cannam@167
|
431 else
|
cannam@167
|
432 "WS(" ^ s ^ ", " ^ (string_of_int i) ^ ")"
|
cannam@167
|
433 | Negative x -> "-" ^ cstride_to_string x
|
cannam@167
|
434
|
cannam@167
|
435 let aref name index =
|
cannam@167
|
436 if !Magic.lisp_syntax then
|
cannam@167
|
437 Printf.sprintf "(aref %s %s)" name index
|
cannam@167
|
438 else
|
cannam@167
|
439 Printf.sprintf "%s[%s]" name index
|
cannam@167
|
440
|
cannam@167
|
441 let array_subscript name stride k =
|
cannam@167
|
442 aref name (cstride_to_string (simplify_stride stride k))
|
cannam@167
|
443
|
cannam@167
|
444 let varray_subscript name vstride stride v i =
|
cannam@167
|
445 let vindex = simplify_stride vstride v
|
cannam@167
|
446 and iindex = simplify_stride stride i
|
cannam@167
|
447 in
|
cannam@167
|
448 let index =
|
cannam@167
|
449 match (vindex, iindex) with
|
cannam@167
|
450 (Simple vi, Simple ii) -> string_of_int (vi + ii)
|
cannam@167
|
451 | (Simple 0, x) -> cstride_to_string x
|
cannam@167
|
452 | (x, Simple 0) -> cstride_to_string x
|
cannam@167
|
453 | _ -> (cstride_to_string vindex) ^ " + " ^ (cstride_to_string iindex)
|
cannam@167
|
454 in aref name index
|
cannam@167
|
455
|
cannam@167
|
456 let real_of s = "c_re(" ^ s ^ ")"
|
cannam@167
|
457 let imag_of s = "c_im(" ^ s ^ ")"
|
cannam@167
|
458
|
cannam@167
|
459 let flops_of f =
|
cannam@167
|
460 let (add, mul, fma) = count_flops f in
|
cannam@167
|
461 Printf.sprintf "{ %d, %d, %d, 0 }" add mul fma
|