OSDN Git Service

PR rtl-optimization/44787
[pf3gnuchains/gcc-fork.git] / gcc / config / arm / neon-testgen.ml
1 (* Auto-generate ARM Neon intrinsics tests.
2    Copyright (C) 2006, 2007, 2008, 2009, 2010 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-testgen neon.cmo neon-testgen.ml
31
32    Run with:
33      cd /path/to/gcc/testsuite/gcc.target/arm/neon
34      /path/to/neon-testgen
35 *)
36
37 open Neon
38
39 type c_type_flags = Pointer | Const
40
41 (* Open a test source file.  *)
42 let open_test_file dir name =
43   try
44     open_out (dir ^ "/" ^ name ^ ".c")
45   with Sys_error str ->
46     failwith ("Could not create test source file " ^ name ^ ": " ^ str)
47
48 (* Emit prologue code to a test source file.  *)
49 let emit_prologue chan test_name =
50   Printf.fprintf chan "/* Test the `%s' ARM Neon intrinsic.  */\n" test_name;
51   Printf.fprintf chan "/* This file was autogenerated by neon-testgen.  */\n\n";
52   Printf.fprintf chan "/* { dg-do assemble } */\n";
53   Printf.fprintf chan "/* { dg-require-effective-target arm_neon_ok } */\n";
54   Printf.fprintf chan "/* { dg-options \"-save-temps -O0\" } */\n";
55   Printf.fprintf chan "/* { dg-add-options arm_neon } */\n";
56   Printf.fprintf chan "\n#include \"arm_neon.h\"\n\n";
57   Printf.fprintf chan "void test_%s (void)\n{\n" test_name
58
59 (* Emit declarations of local variables that are going to be passed
60    to an intrinsic, together with one to take a returned value if needed.  *)
61 let emit_automatics chan c_types features =
62   let emit () =
63     ignore (
64       List.fold_left (fun arg_number -> fun (flags, ty) ->
65                         let pointer_bit =
66                           if List.mem Pointer flags then "*" else ""
67                         in
68                           (* Const arguments to builtins are directly
69                              written in as constants.  *)
70                           if not (List.mem Const flags) then
71                             Printf.fprintf chan "  %s %sarg%d_%s;\n"
72                                            ty pointer_bit arg_number ty;
73                         arg_number + 1)
74                      0 (List.tl c_types))
75   in
76     match c_types with
77       (_, return_ty) :: tys ->
78         if return_ty <> "void" then begin
79           (* The intrinsic returns a value.  We need to do explict register
80              allocation for vget_low tests or they fail because of copy
81              elimination.  *)
82           ((if List.mem Fixed_return_reg features then
83               Printf.fprintf chan "  register %s out_%s asm (\"d18\");\n"
84                              return_ty return_ty
85             else
86               Printf.fprintf chan "  %s out_%s;\n" return_ty return_ty);
87            emit ())
88         end else
89           (* The intrinsic does not return a value.  *)
90           emit ()
91     | _ -> assert false
92
93 (* Emit code to call an intrinsic.  *)
94 let emit_call chan const_valuator c_types name elt_ty =
95   (if snd (List.hd c_types) <> "void" then
96      Printf.fprintf chan "  out_%s = " (snd (List.hd c_types))
97    else
98      Printf.fprintf chan "  ");
99   Printf.fprintf chan "%s_%s (" (intrinsic_name name) (string_of_elt elt_ty);
100   let print_arg chan arg_number (flags, ty) =
101     (* If the argument is of const type, then directly write in the
102        constant now.  *)
103     if List.mem Const flags then
104       match const_valuator with
105         None ->
106           if List.mem Pointer flags then
107             Printf.fprintf chan "0"
108           else
109             Printf.fprintf chan "1"
110       | Some f -> Printf.fprintf chan "%s" (string_of_int (f arg_number))
111     else
112       Printf.fprintf chan "arg%d_%s" arg_number ty
113   in
114   let rec print_args arg_number tys =
115     match tys with
116       [] -> ()
117     | [ty] -> print_arg chan arg_number ty
118     | ty::tys ->
119       print_arg chan arg_number ty;
120       Printf.fprintf chan ", ";
121       print_args (arg_number + 1) tys
122   in
123     print_args 0 (List.tl c_types);
124     Printf.fprintf chan ");\n"
125
126 (* Emit epilogue code to a test source file.  *)
127 let emit_epilogue chan features regexps =
128   let no_op = List.exists (fun feature -> feature = No_op) features in
129     Printf.fprintf chan "}\n\n";
130     (if not no_op then
131        List.iter (fun regexp ->
132                    Printf.fprintf chan
133                      "/* { dg-final { scan-assembler \"%s\" } } */\n" regexp)
134                 regexps
135      else
136        ()
137     );
138     Printf.fprintf chan "/* { dg-final { cleanup-saved-temps } } */\n"
139
140 (* Check a list of C types to determine which ones are pointers and which
141    ones are const.  *)
142 let check_types tys =
143   let tys' =
144     List.map (fun ty ->
145                 let len = String.length ty in
146                   if len > 2 && String.get ty (len - 2) = ' '
147                              && String.get ty (len - 1) = '*'
148                   then ([Pointer], String.sub ty 0 (len - 2))
149                   else ([], ty)) tys
150   in
151     List.map (fun (flags, ty) ->
152                 if String.length ty > 6 && String.sub ty 0 6 = "const "
153                 then (Const :: flags, String.sub ty 6 ((String.length ty) - 6))
154                 else (flags, ty)) tys'
155
156 (* Given an intrinsic shape, produce a regexp that will match
157    the right-hand sides of instructions generated by an intrinsic of
158    that shape.  *)
159 let rec analyze_shape shape =
160   let rec n_things n thing =
161     match n with
162       0 -> []
163     | n -> thing :: (n_things (n - 1) thing)
164   in
165   let rec analyze_shape_elt elt =
166     match elt with
167       Dreg -> "\\[dD\\]\\[0-9\\]+"
168     | Qreg -> "\\[qQ\\]\\[0-9\\]+"
169     | Corereg -> "\\[rR\\]\\[0-9\\]+"
170     | Immed -> "#\\[0-9\\]+"
171     | VecArray (1, elt) ->
172         let elt_regexp = analyze_shape_elt elt in
173           "((\\\\\\{" ^ elt_regexp ^ "\\\\\\})|(" ^ elt_regexp ^ "))"
174     | VecArray (n, elt) ->
175       let elt_regexp = analyze_shape_elt elt in
176       let alt1 = elt_regexp ^ "-" ^ elt_regexp in
177       let alt2 = commas (fun x -> x) (n_things n elt_regexp) "" in
178         "\\\\\\{((" ^ alt1 ^ ")|(" ^ alt2 ^ "))\\\\\\}"
179     | (PtrTo elt | CstPtrTo elt) ->
180       "\\\\\\[" ^ (analyze_shape_elt elt) ^ "\\\\\\]"
181     | Element_of_dreg -> (analyze_shape_elt Dreg) ^ "\\\\\\[\\[0-9\\]+\\\\\\]"
182     | Element_of_qreg -> (analyze_shape_elt Qreg) ^ "\\\\\\[\\[0-9\\]+\\\\\\]"
183     | All_elements_of_dreg -> (analyze_shape_elt Dreg) ^ "\\\\\\[\\\\\\]"
184     | Alternatives (elts) -> "(" ^ (String.concat "|" (List.map analyze_shape_elt elts)) ^ ")"
185   in
186     match shape with
187       All (n, elt) -> commas analyze_shape_elt (n_things n elt) ""
188     | Long -> (analyze_shape_elt Qreg) ^ ", " ^ (analyze_shape_elt Dreg) ^
189               ", " ^ (analyze_shape_elt Dreg)
190     | Long_noreg elt -> (analyze_shape_elt elt) ^ ", " ^ (analyze_shape_elt elt)
191     | Wide -> (analyze_shape_elt Qreg) ^ ", " ^ (analyze_shape_elt Qreg) ^
192               ", " ^ (analyze_shape_elt Dreg)
193     | Wide_noreg elt -> analyze_shape (Long_noreg elt)
194     | Narrow -> (analyze_shape_elt Dreg) ^ ", " ^ (analyze_shape_elt Qreg) ^
195                 ", " ^ (analyze_shape_elt Qreg)
196     | Use_operands elts -> commas analyze_shape_elt (Array.to_list elts) ""
197     | By_scalar Dreg ->
198         analyze_shape (Use_operands [| Dreg; Dreg; Element_of_dreg |])
199     | By_scalar Qreg ->
200         analyze_shape (Use_operands [| Qreg; Qreg; Element_of_dreg |])
201     | By_scalar _ -> assert false
202     | Wide_lane ->
203         analyze_shape (Use_operands [| Qreg; Dreg; Element_of_dreg |])
204     | Wide_scalar ->
205         analyze_shape (Use_operands [| Qreg; Dreg; Element_of_dreg |])
206     | Pair_result elt ->
207       let elt_regexp = analyze_shape_elt elt in
208         elt_regexp ^ ", " ^ elt_regexp
209     | Unary_scalar _ -> "FIXME Unary_scalar"
210     | Binary_imm elt -> analyze_shape (Use_operands [| elt; elt; Immed |])
211     | Narrow_imm -> analyze_shape (Use_operands [| Dreg; Qreg; Immed |])
212     | Long_imm -> analyze_shape (Use_operands [| Qreg; Dreg; Immed |])
213
214 (* Generate tests for one intrinsic.  *)
215 let test_intrinsic dir opcode features shape name munge elt_ty =
216   (* Open the test source file.  *)
217   let test_name = name ^ (string_of_elt elt_ty) in
218   let chan = open_test_file dir test_name in
219   (* Work out what argument and return types the intrinsic has.  *)
220   let c_arity, new_elt_ty = munge shape elt_ty in
221   let c_types = check_types (strings_of_arity c_arity) in
222   (* Extract any constant valuator (a function specifying what constant
223      values are to be written into the intrinsic call) from the features
224      list.  *)
225   let const_valuator =
226     try
227       match (List.find (fun feature -> match feature with
228                                          Const_valuator _ -> true
229                                        | _ -> false) features) with
230         Const_valuator f -> Some f
231       | _ -> assert false
232     with Not_found -> None
233   in
234   (* Work out what instruction name(s) to expect.  *)
235   let insns = get_insn_names features name in
236   let no_suffix = (new_elt_ty = NoElts) in
237   let insns =
238     if no_suffix then insns
239                  else List.map (fun insn ->
240                                   let suffix = string_of_elt_dots new_elt_ty in
241                                     insn ^ "\\." ^ suffix) insns
242   in
243   (* Construct a regexp to match against the expected instruction name(s).  *)
244   let insn_regexp =
245     match insns with
246       [] -> assert false
247     | [insn] -> insn
248     | _ ->
249       let rec calc_regexp insns cur_regexp =
250         match insns with
251           [] -> cur_regexp
252         | [insn] -> cur_regexp ^ "(" ^ insn ^ "))"
253         | insn::insns -> calc_regexp insns (cur_regexp ^ "(" ^ insn ^ ")|")
254       in calc_regexp insns "("
255   in
256   (* Construct regexps to match against the instructions that this
257      intrinsic expands to.  Watch out for any writeback character and
258      comments after the instruction.  *)
259   let regexps = List.map (fun regexp -> insn_regexp ^ "\\[ \t\\]+" ^ regexp ^
260                           "!?\\(\\[ \t\\]+@\\[a-zA-Z0-9 \\]+\\)?\\n")
261                          (analyze_all_shapes features shape analyze_shape)
262   in
263     (* Emit file and function prologues.  *)
264     emit_prologue chan test_name;
265     (* Emit local variable declarations.  *)
266     emit_automatics chan c_types features;
267     Printf.fprintf chan "\n";
268     (* Emit the call to the intrinsic.  *)
269     emit_call chan const_valuator c_types name elt_ty;
270     (* Emit the function epilogue and the DejaGNU scan-assembler directives.  *)
271     emit_epilogue chan features regexps;
272     (* Close the test file.  *)
273     close_out chan
274
275 (* Generate tests for one element of the "ops" table.  *)
276 let test_intrinsic_group dir (opcode, features, shape, name, munge, types) =
277   List.iter (test_intrinsic dir opcode features shape name munge) types
278
279 (* Program entry point.  *)
280 let _ =
281   let directory = if Array.length Sys.argv <> 1 then Sys.argv.(1) else "." in
282     List.iter (test_intrinsic_group directory) (reinterp @ ops)
283