Imported Upstream version 4.8.1
[platform/upstream/gcc48.git] / gcc / config / arm / neon-gen.ml
1 (* Auto-generate ARM Neon intrinsics header file.
2    Copyright (C) 2006-2013 Free Software Foundation, Inc.
3    Contributed by CodeSourcery.
4
5    This file is part of GCC.
6
7    GCC is free software; you can redistribute it and/or modify it under
8    the terms of the GNU General Public License as published by the Free
9    Software Foundation; either version 3, or (at your option) any later
10    version.
11
12    GCC is distributed in the hope that it will be useful, but WITHOUT ANY
13    WARRANTY; without even the implied warranty of MERCHANTABILITY or
14    FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
15    for more details.
16
17    You should have received a copy of the GNU General Public License
18    along with GCC; see the file COPYING3.  If not see
19    <http://www.gnu.org/licenses/>.
20
21    This is an O'Caml program.  The O'Caml compiler is available from:
22
23      http://caml.inria.fr/
24
25    Or from your favourite OS's friendly packaging system. Tested with version
26    3.09.2, though other versions will probably work too.
27
28    Compile with:
29      ocamlc -c neon.ml
30      ocamlc -o neon-gen neon.cmo neon-gen.ml
31
32    Run with:
33      ./neon-gen > arm_neon.h
34 *)
35
36 open Neon
37
38 (* The format codes used in the following functions are documented at:
39      http://caml.inria.fr/pub/docs/manual-ocaml/libref/Format.html\
40      #6_printflikefunctionsforprettyprinting
41    (one line, remove the backslash.)
42 *)
43
44 (* Following functions can be used to approximate GNU indentation style.  *)
45 let start_function () =
46   Format.printf "@[<v 0>";
47   ref 0
48
49 let end_function nesting =
50   match !nesting with
51     0 -> Format.printf "@;@;@]"
52   | _ -> failwith ("Bad nesting (ending function at level "
53                    ^ (string_of_int !nesting) ^ ")")
54
55 let open_braceblock nesting =
56   begin match !nesting with
57     0 -> Format.printf "@,@<0>{@[<v 2>@,"
58   | _ -> Format.printf "@,@[<v 2>  @<0>{@[<v 2>@,"
59   end;
60   incr nesting
61
62 let close_braceblock nesting =
63   decr nesting;
64   match !nesting with
65     0 -> Format.printf "@]@,@<0>}"
66   | _ -> Format.printf "@]@,@<0>}@]"
67
68 let print_function arity fnname body =
69   let ffmt = start_function () in
70   Format.printf "__extension__ static __inline ";
71   let inl = "__attribute__ ((__always_inline__))" in
72   begin match arity with
73     Arity0 ret ->
74       Format.printf "%s %s@,%s (void)" (string_of_vectype ret) inl fnname
75   | Arity1 (ret, arg0) ->
76       Format.printf "%s %s@,%s (%s __a)" (string_of_vectype ret) inl fnname
77                                         (string_of_vectype arg0)
78   | Arity2 (ret, arg0, arg1) ->
79       Format.printf "%s %s@,%s (%s __a, %s __b)"
80         (string_of_vectype ret) inl fnname (string_of_vectype arg0)
81         (string_of_vectype arg1)
82   | Arity3 (ret, arg0, arg1, arg2) ->
83       Format.printf "%s %s@,%s (%s __a, %s __b, %s __c)"
84         (string_of_vectype ret) inl fnname (string_of_vectype arg0)
85         (string_of_vectype arg1) (string_of_vectype arg2)
86   | Arity4 (ret, arg0, arg1, arg2, arg3) ->
87       Format.printf "%s %s@,%s (%s __a, %s __b, %s __c, %s __d)"
88         (string_of_vectype ret) inl fnname (string_of_vectype arg0)
89         (string_of_vectype arg1) (string_of_vectype arg2)
90         (string_of_vectype arg3)
91   end;
92   open_braceblock ffmt;
93   let rec print_lines = function
94     []       -> ()
95   | "" :: lines -> print_lines lines
96   | [line] -> Format.printf "%s" line
97   | line::lines -> Format.printf "%s@," line ; print_lines lines in
98   print_lines body;
99   close_braceblock ffmt;
100   end_function ffmt
101
102 let union_string num elts base =
103   let itype = inttype_for_array num elts in
104   let iname = string_of_inttype itype
105   and sname = string_of_vectype (T_arrayof (num, elts)) in
106   Printf.sprintf "union { %s __i; %s __o; } %s" sname iname base
107
108 let rec signed_ctype = function
109     T_uint8x8 | T_poly8x8 -> T_int8x8
110   | T_uint8x16 | T_poly8x16 -> T_int8x16
111   | T_uint16x4 | T_poly16x4 -> T_int16x4
112   | T_uint16x8 | T_poly16x8 -> T_int16x8
113   | T_uint32x2 -> T_int32x2
114   | T_uint32x4 -> T_int32x4
115   | T_uint64x1 -> T_int64x1
116   | T_uint64x2 -> T_int64x2
117   (* Cast to types defined by mode in arm.c, not random types pulled in from
118      the <stdint.h> header in use. This fixes incompatible pointer errors when
119      compiling with C++.  *)
120   | T_uint8 | T_int8 -> T_intQI
121   | T_uint16 | T_int16 -> T_intHI
122   | T_uint32 | T_int32 -> T_intSI
123   | T_uint64 | T_int64 -> T_intDI
124   | T_float32 -> T_floatSF
125   | T_poly8 -> T_intQI
126   | T_poly16 -> T_intHI
127   | T_arrayof (n, elt) -> T_arrayof (n, signed_ctype elt)
128   | T_ptrto elt -> T_ptrto (signed_ctype elt)
129   | T_const elt -> T_const (signed_ctype elt)
130   | x -> x
131
132 let add_cast ctype cval =
133   let stype = signed_ctype ctype in
134   if ctype <> stype then
135     Printf.sprintf "(%s) %s" (string_of_vectype stype) cval
136   else
137     cval
138
139 let cast_for_return to_ty = "(" ^ (string_of_vectype to_ty) ^ ")"
140
141 (* Return a tuple of a list of declarations to go at the start of the function,
142    and a list of statements needed to return THING.  *)
143 let return arity thing =
144   match arity with
145     Arity0 (ret) | Arity1 (ret, _) | Arity2 (ret, _, _) | Arity3 (ret, _, _, _)
146   | Arity4 (ret, _, _, _, _) ->
147       begin match ret with
148         T_arrayof (num, vec) ->
149           let uname = union_string num vec "__rv" in
150           [uname ^ ";"], ["__rv.__o = " ^ thing ^ ";"; "return __rv.__i;"]
151       | T_void ->
152           [], [thing ^ ";"]
153       | _ ->
154           [], ["return " ^ (cast_for_return ret) ^ thing ^ ";"]
155       end
156
157 let mask_shape_for_shuffle = function
158     All (num, reg) -> All (num, reg)
159   | Pair_result reg -> All (2, reg)
160   | _ -> failwith "mask_for_shuffle"
161
162 let mask_elems shuffle shape elttype part =
163   let elem_size = elt_width elttype in
164   let num_elems =
165     match regmap shape 0 with
166       Dreg -> 64 / elem_size
167     | Qreg -> 128 / elem_size
168     | _ -> failwith "mask_elems" in
169   shuffle elem_size num_elems part
170
171 (* Return a tuple of a list of declarations 0and a list of statements needed
172    to implement an intrinsic using __builtin_shuffle.  SHUFFLE is a function
173    which returns a list of elements suitable for using as a mask.  *)
174
175 let shuffle_fn shuffle shape arity elttype =
176   let mshape = mask_shape_for_shuffle shape in
177   let masktype = type_for_elt mshape (unsigned_of_elt elttype) 0 in
178   let masktype_str = string_of_vectype masktype in
179   let shuffle_res = type_for_elt mshape elttype 0 in
180   let shuffle_res_str = string_of_vectype shuffle_res in
181   match arity with
182     Arity0 (ret) | Arity1 (ret, _) | Arity2 (ret, _, _) | Arity3 (ret, _, _, _)
183   | Arity4 (ret, _, _, _, _) ->
184       begin match ret with
185         T_arrayof (num, vec) ->
186           let elems1 = mask_elems shuffle mshape elttype `lo
187           and elems2 = mask_elems shuffle mshape elttype `hi in
188           let mask1 = (String.concat ", " (List.map string_of_int elems1))
189           and mask2 = (String.concat ", " (List.map string_of_int elems2)) in
190           let shuf1 = Printf.sprintf
191             "__rv.val[0] = (%s) __builtin_shuffle (__a, __b, (%s) { %s });"
192             shuffle_res_str masktype_str mask1
193           and shuf2 = Printf.sprintf
194             "__rv.val[1] = (%s) __builtin_shuffle (__a, __b, (%s) { %s });"
195             shuffle_res_str masktype_str mask2 in
196           [Printf.sprintf "%s __rv;" (string_of_vectype ret);],
197           [shuf1; shuf2; "return __rv;"]
198       | _ ->
199           let elems = mask_elems shuffle mshape elttype `lo in
200           let mask =  (String.concat ", " (List.map string_of_int elems)) in
201           let shuf = Printf.sprintf
202             "return (%s) __builtin_shuffle (__a, (%s) { %s });" shuffle_res_str masktype_str mask in
203           [""],
204           [shuf]
205       end
206
207 let rec element_type ctype =
208   match ctype with
209     T_arrayof (_, v) -> element_type v
210   | _ -> ctype
211
212 let params ps =
213   let pdecls = ref [] in
214   let ptype t p =
215     match t with
216       T_arrayof (num, elts) ->
217         let uname = union_string num elts (p ^ "u") in
218         let decl = Printf.sprintf "%s = { %s };" uname p in
219         pdecls := decl :: !pdecls;
220         p ^ "u.__o"
221     | _ -> add_cast t p in
222   let plist = match ps with
223     Arity0 _ -> []
224   | Arity1 (_, t1) -> [ptype t1 "__a"]
225   | Arity2 (_, t1, t2) -> [ptype t1 "__a"; ptype t2 "__b"]
226   | Arity3 (_, t1, t2, t3) -> [ptype t1 "__a"; ptype t2 "__b"; ptype t3 "__c"]
227   | Arity4 (_, t1, t2, t3, t4) ->
228       [ptype t1 "__a"; ptype t2 "__b"; ptype t3 "__c"; ptype t4 "__d"] in
229   !pdecls, plist
230
231 let modify_params features plist =
232   let is_flipped =
233     List.exists (function Flipped _ -> true | _ -> false) features in
234   if is_flipped then
235     match plist with
236       [ a; b ] -> [ b; a ]
237     | _ ->
238       failwith ("Don't know how to flip args " ^ (String.concat ", " plist))
239   else
240     plist
241
242 (* !!! Decide whether to add an extra information word based on the shape
243    form.  *)
244 let extra_word shape features paramlist bits =
245   let use_word =
246     match shape with
247       All _ | Long | Long_noreg _ | Wide | Wide_noreg _ | Narrow
248     | By_scalar _ | Wide_scalar | Wide_lane | Binary_imm _ | Long_imm
249     | Narrow_imm -> true
250     | _ -> List.mem InfoWord features
251   in
252     if use_word then
253       paramlist @ [string_of_int bits]
254     else
255       paramlist
256
257 (* Bit 0 represents signed (1) vs unsigned (0), or float (1) vs poly (0).
258    Bit 1 represents floats & polynomials (1), or ordinary integers (0).
259    Bit 2 represents rounding (1) vs none (0).  *)
260 let infoword_value elttype features =
261   let bits01 =
262     match elt_class elttype with
263       Signed | ConvClass (Signed, _) | ConvClass (_, Signed) -> 0b001
264     | Poly -> 0b010
265     | Float -> 0b011
266     | _ -> 0b000
267   and rounding_bit = if List.mem Rounding features then 0b100 else 0b000 in
268   bits01 lor rounding_bit
269
270 (* "Cast" type operations will throw an exception in mode_of_elt (actually in
271    elt_width, called from there). Deal with that here, and generate a suffix
272    with multiple modes (<to><from>).  *)
273 let rec mode_suffix elttype shape =
274   try
275     let mode = mode_of_elt elttype shape in
276     string_of_mode mode
277   with MixedMode (dst, src) ->
278     let dstmode = mode_of_elt dst shape
279     and srcmode = mode_of_elt src shape in
280     string_of_mode dstmode ^ string_of_mode srcmode
281
282 let get_shuffle features =
283   try
284     match List.find (function Use_shuffle _ -> true | _ -> false) features with
285       Use_shuffle fn -> Some fn
286     | _ -> None
287   with Not_found -> None
288
289 let print_feature_test_start features =
290   try
291     match List.find (fun feature ->
292                        match feature with Requires_feature _ -> true
293                                         | Requires_arch _ -> true
294                                         | _ -> false)
295                      features with
296       Requires_feature feature -> 
297         Format.printf "#ifdef __ARM_FEATURE_%s@\n" feature
298     | Requires_arch arch ->
299         Format.printf "#if __ARM_ARCH >= %d@\n" arch
300     | _ -> assert false
301   with Not_found -> assert true
302
303 let print_feature_test_end features =
304   let feature =
305     List.exists (function Requires_feature x -> true
306                           | Requires_arch x -> true
307                           |  _ -> false) features in
308   if feature then Format.printf "#endif@\n"
309
310
311 let print_variant opcode features shape name (ctype, asmtype, elttype) =
312   let bits = infoword_value elttype features in
313   let modesuf = mode_suffix elttype shape in
314   let pdecls, paramlist = params ctype in
315   let rdecls, stmts =
316     match get_shuffle features with
317       Some shuffle -> shuffle_fn shuffle shape ctype elttype
318     | None ->
319         let paramlist' = modify_params features paramlist in
320         let paramlist'' = extra_word shape features paramlist' bits in
321         let parstr = String.concat ", " paramlist'' in
322         let builtin = Printf.sprintf "__builtin_neon_%s%s (%s)"
323                         (builtin_name features name) modesuf parstr in
324         return ctype builtin in
325   let body = pdecls @ rdecls @ stmts
326   and fnname = (intrinsic_name name) ^ "_" ^ (string_of_elt elttype) in
327   begin
328     print_feature_test_start features;
329     print_function ctype fnname body;
330     print_feature_test_end features;
331   end
332
333 (* When this function processes the element types in the ops table, it rewrites
334    them in a list of tuples (a,b,c):
335      a : C type as an "arity", e.g. Arity1 (T_poly8x8, T_poly8x8)
336      b : Asm type : a single, processed element type, e.g. P16. This is the
337          type which should be attached to the asm opcode.
338      c : Variant type : the unprocessed type for this variant (e.g. in add
339          instructions which don't care about the sign, b might be i16 and c
340          might be s16.)
341 *)
342
343 let print_op (opcode, features, shape, name, munge, types) =
344   let sorted_types = List.sort compare types in
345   let munged_types = List.map
346     (fun elt -> let c, asm = munge shape elt in c, asm, elt) sorted_types in
347   List.iter
348     (fun variant -> print_variant opcode features shape name variant)
349     munged_types
350
351 let print_ops ops =
352   List.iter print_op ops
353
354 (* Output type definitions. Table entries are:
355      cbase : "C" name for the type.
356      abase : "ARM" base name for the type (i.e. int in int8x8_t).
357      esize : element size.
358      enum : element count.
359 *)
360
361 let deftypes () =
362   let typeinfo = [
363     (* Doubleword vector types.  *)
364     "__builtin_neon_qi", "int", 8, 8;
365     "__builtin_neon_hi", "int", 16, 4;
366     "__builtin_neon_si", "int", 32, 2;
367     "__builtin_neon_di", "int", 64, 1;
368     "__builtin_neon_sf", "float", 32, 2;
369     "__builtin_neon_poly8", "poly", 8, 8;
370     "__builtin_neon_poly16", "poly", 16, 4;
371     "__builtin_neon_uqi", "uint", 8, 8;
372     "__builtin_neon_uhi", "uint", 16, 4;
373     "__builtin_neon_usi", "uint", 32, 2;
374     "__builtin_neon_udi", "uint", 64, 1;
375
376     (* Quadword vector types.  *)
377     "__builtin_neon_qi", "int", 8, 16;
378     "__builtin_neon_hi", "int", 16, 8;
379     "__builtin_neon_si", "int", 32, 4;
380     "__builtin_neon_di", "int", 64, 2;
381     "__builtin_neon_sf", "float", 32, 4;
382     "__builtin_neon_poly8", "poly", 8, 16;
383     "__builtin_neon_poly16", "poly", 16, 8;
384     "__builtin_neon_uqi", "uint", 8, 16;
385     "__builtin_neon_uhi", "uint", 16, 8;
386     "__builtin_neon_usi", "uint", 32, 4;
387     "__builtin_neon_udi", "uint", 64, 2
388   ] in
389   List.iter
390     (fun (cbase, abase, esize, enum) ->
391       let attr =
392         match enum with
393           1 -> ""
394         | _ -> Printf.sprintf "\t__attribute__ ((__vector_size__ (%d)))"
395                               (esize * enum / 8) in
396       Format.printf "typedef %s %s%dx%d_t%s;@\n" cbase abase esize enum attr)
397     typeinfo;
398   Format.print_newline ();
399   (* Extra types not in <stdint.h>.  *)
400   Format.printf "typedef float float32_t;\n";
401   Format.printf "typedef __builtin_neon_poly8 poly8_t;\n";
402   Format.printf "typedef __builtin_neon_poly16 poly16_t;\n"
403
404 (* Output structs containing arrays, for load & store instructions etc.  *)
405
406 let arrtypes () =
407   let typeinfo = [
408     "int", 8;    "int", 16;
409     "int", 32;   "int", 64;
410     "uint", 8;   "uint", 16;
411     "uint", 32;  "uint", 64;
412     "float", 32; "poly", 8;
413     "poly", 16
414   ] in
415   let writestruct elname elsize regsize arrsize =
416     let elnum = regsize / elsize in
417     let structname =
418       Printf.sprintf "%s%dx%dx%d_t" elname elsize elnum arrsize in
419     let sfmt = start_function () in
420     Format.printf "typedef struct %s" structname;
421     open_braceblock sfmt;
422     Format.printf "%s%dx%d_t val[%d];" elname elsize elnum arrsize;
423     close_braceblock sfmt;
424     Format.printf " %s;" structname;
425     end_function sfmt;
426   in
427     for n = 2 to 4 do
428       List.iter
429         (fun (elname, elsize) ->
430           writestruct elname elsize 64 n;
431           writestruct elname elsize 128 n)
432         typeinfo
433     done
434
435 let print_lines = List.iter (fun s -> Format.printf "%s@\n" s)
436
437 (* Do it.  *)
438
439 let _ =
440   print_lines [
441 "/* ARM NEON intrinsics include file. This file is generated automatically";
442 "   using neon-gen.ml.  Please do not edit manually.";
443 "";
444 "   Copyright (C) 2006-2013 Free Software Foundation, Inc.";
445 "   Contributed by CodeSourcery.";
446 "";
447 "   This file is part of GCC.";
448 "";
449 "   GCC is free software; you can redistribute it and/or modify it";
450 "   under the terms of the GNU General Public License as published";
451 "   by the Free Software Foundation; either version 3, or (at your";
452 "   option) any later version.";
453 "";
454 "   GCC is distributed in the hope that it will be useful, but WITHOUT";
455 "   ANY WARRANTY; without even the implied warranty of MERCHANTABILITY";
456 "   or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public";
457 "   License for more details.";
458 "";
459 "   Under Section 7 of GPL version 3, you are granted additional";
460 "   permissions described in the GCC Runtime Library Exception, version";
461 "   3.1, as published by the Free Software Foundation.";
462 "";
463 "   You should have received a copy of the GNU General Public License and";
464 "   a copy of the GCC Runtime Library Exception along with this program;";
465 "   see the files COPYING3 and COPYING.RUNTIME respectively.  If not, see";
466 "   <http://www.gnu.org/licenses/>.  */";
467 "";
468 "#ifndef _GCC_ARM_NEON_H";
469 "#define _GCC_ARM_NEON_H 1";
470 "";
471 "#ifndef __ARM_NEON__";
472 "#error You must enable NEON instructions (e.g. -mfloat-abi=softfp -mfpu=neon) to use arm_neon.h";
473 "#else";
474 "";
475 "#ifdef __cplusplus";
476 "extern \"C\" {";
477 "#endif";
478 "";
479 "#include <stdint.h>";
480 ""];
481   deftypes ();
482   arrtypes ();
483   Format.print_newline ();
484   print_ops ops;
485   Format.print_newline ();
486   print_ops reinterp;
487   print_lines [
488 "#ifdef __cplusplus";
489 "}";
490 "#endif";
491 "#endif";
492 "#endif"]