1(* Auto-generate ARM Neon intrinsics tests.
2   Copyright (C) 2006-2015 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
37open Neon
38
39type c_type_flags = Pointer | Const
40
41(* Open a test source file.  *)
42let 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.  *)
49let emit_prologue chan test_name effective_target compile_test_optim =
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 %s_ok } */\n"
54                 effective_target;
55  Printf.fprintf chan "/* { dg-options \"-save-temps %s\" } */\n" compile_test_optim;
56  Printf.fprintf chan "/* { dg-add-options %s } */\n" effective_target;
57  Printf.fprintf chan "\n#include \"arm_neon.h\"\n\n"
58
59(* Emit declarations of variables that are going to be passed
60   to an intrinsic, together with one to take a returned value if needed.  *)
61let emit_variables chan c_types features spaces =
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%s %sarg%d_%s;\n"
72                                           spaces 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_vector_reg features then
83              Printf.fprintf chan "%sregister %s out_%s asm (\"d18\");\n"
84                             spaces return_ty return_ty
85            else if List.mem Fixed_core_reg features then
86              Printf.fprintf chan "%sregister %s out_%s asm (\"r0\");\n"
87                             spaces return_ty return_ty
88            else
89              Printf.fprintf chan "%s%s out_%s;\n" spaces return_ty return_ty);
90	   emit ())
91        end else
92          (* The intrinsic does not return a value.  *)
93          emit ()
94    | _ -> assert false
95
96(* Emit code to call an intrinsic.  *)
97let emit_call chan const_valuator c_types name elt_ty =
98  (if snd (List.hd c_types) <> "void" then
99     Printf.fprintf chan "  out_%s = " (snd (List.hd c_types))
100   else
101     Printf.fprintf chan "  ");
102  Printf.fprintf chan "%s_%s (" (intrinsic_name name) (string_of_elt elt_ty);
103  let print_arg chan arg_number (flags, ty) =
104    (* If the argument is of const type, then directly write in the
105       constant now.  *)
106    if List.mem Const flags then
107      match const_valuator with
108        None ->
109          if List.mem Pointer flags then
110            Printf.fprintf chan "0"
111          else
112            Printf.fprintf chan "1"
113      | Some f -> Printf.fprintf chan "%s" (string_of_int (f arg_number))
114    else
115      Printf.fprintf chan "arg%d_%s" arg_number ty
116  in
117  let rec print_args arg_number tys =
118    match tys with
119      [] -> ()
120    | [ty] -> print_arg chan arg_number ty
121    | ty::tys ->
122      print_arg chan arg_number ty;
123      Printf.fprintf chan ", ";
124      print_args (arg_number + 1) tys
125  in
126    print_args 0 (List.tl c_types);
127    Printf.fprintf chan ");\n"
128
129(* Emit epilogue code to a test source file.  *)
130let emit_epilogue chan features regexps =
131  let no_op = List.exists (fun feature -> feature = No_op) features in
132    Printf.fprintf chan "}\n\n";
133    (if not no_op then
134       List.iter (fun regexp ->
135                   Printf.fprintf chan
136                     "/* { dg-final { scan-assembler \"%s\" } } */\n" regexp)
137                regexps
138     else
139       ()
140    );
141    Printf.fprintf chan "/* { dg-final { cleanup-saved-temps } } */\n"
142
143(* Check a list of C types to determine which ones are pointers and which
144   ones are const.  *)
145let check_types tys =
146  let tys' =
147    List.map (fun ty ->
148                let len = String.length ty in
149                  if len > 2 && String.get ty (len - 2) = ' '
150                             && String.get ty (len - 1) = '*'
151                  then ([Pointer], String.sub ty 0 (len - 2))
152                  else ([], ty)) tys
153  in
154    List.map (fun (flags, ty) ->
155                if String.length ty > 6 && String.sub ty 0 6 = "const "
156                then (Const :: flags, String.sub ty 6 ((String.length ty) - 6))
157                else (flags, ty)) tys'
158
159(* Work out what the effective target should be.  *)
160let effective_target features =
161  try
162    match List.find (fun feature ->
163                       match feature with Requires_feature _ -> true
164                                        | Requires_arch _ -> true
165                                        | Requires_FP_bit 1 -> true
166                                        | _ -> false)
167                     features with
168      Requires_feature "FMA" -> "arm_neonv2"
169    | Requires_feature "CRYPTO" -> "arm_crypto"
170    | Requires_arch 8 -> "arm_v8_neon"
171    | Requires_FP_bit 1 -> "arm_neon_fp16"
172    | _ -> assert false
173  with Not_found -> "arm_neon"
174
175(* Work out what the testcase optimization level should be, default to -O0.  *)
176let compile_test_optim features =
177  try
178    match List.find (fun feature ->
179                       match feature with Compiler_optim _ -> true
180                                        | _ -> false)
181                     features with
182      Compiler_optim opt -> opt
183    | _ -> assert false
184  with Not_found -> "-O0"
185
186(* Given an intrinsic shape, produce a regexp that will match
187   the right-hand sides of instructions generated by an intrinsic of
188   that shape.  *)
189let rec analyze_shape shape =
190  let rec n_things n thing =
191    match n with
192      0 -> []
193    | n -> thing :: (n_things (n - 1) thing)
194  in
195  let rec analyze_shape_elt elt =
196    match elt with
197      Dreg -> "\\[dD\\]\\[0-9\\]+"
198    | Qreg -> "\\[qQ\\]\\[0-9\\]+"
199    | Corereg -> "\\[rR\\]\\[0-9\\]+"
200    | Immed -> "#\\[0-9\\]+"
201    | VecArray (1, elt) ->
202        let elt_regexp = analyze_shape_elt elt in
203          "((\\\\\\{" ^ elt_regexp ^ "\\\\\\})|(" ^ elt_regexp ^ "))"
204    | VecArray (n, elt) ->
205      let elt_regexp = analyze_shape_elt elt in
206      let alt1 = elt_regexp ^ "-" ^ elt_regexp in
207      let alt2 = commas (fun x -> x) (n_things n elt_regexp) "" in
208        "\\\\\\{((" ^ alt1 ^ ")|(" ^ alt2 ^ "))\\\\\\}"
209    | (PtrTo elt | CstPtrTo elt) ->
210      "\\\\\\[" ^ (analyze_shape_elt elt) ^ "\\(:\\[0-9\\]+\\)?\\\\\\]"
211    | Element_of_dreg -> (analyze_shape_elt Dreg) ^ "\\\\\\[\\[0-9\\]+\\\\\\]"
212    | Element_of_qreg -> (analyze_shape_elt Qreg) ^ "\\\\\\[\\[0-9\\]+\\\\\\]"
213    | All_elements_of_dreg -> (analyze_shape_elt Dreg) ^ "\\\\\\[\\\\\\]"
214    | Alternatives (elts) -> "(" ^ (String.concat "|" (List.map analyze_shape_elt elts)) ^ ")"
215  in
216    match shape with
217      All (n, elt) -> commas analyze_shape_elt (n_things n elt) ""
218    | Long -> (analyze_shape_elt Qreg) ^ ", " ^ (analyze_shape_elt Dreg) ^
219              ", " ^ (analyze_shape_elt Dreg)
220    | Long_noreg elt -> (analyze_shape_elt elt) ^ ", " ^ (analyze_shape_elt elt)
221    | Wide -> (analyze_shape_elt Qreg) ^ ", " ^ (analyze_shape_elt Qreg) ^
222              ", " ^ (analyze_shape_elt Dreg)
223    | Wide_noreg elt -> analyze_shape (Long_noreg elt)
224    | Narrow -> (analyze_shape_elt Dreg) ^ ", " ^ (analyze_shape_elt Qreg) ^
225                ", " ^ (analyze_shape_elt Qreg)
226    | Use_operands elts -> commas analyze_shape_elt (Array.to_list elts) ""
227    | By_scalar Dreg ->
228        analyze_shape (Use_operands [| Dreg; Dreg; Element_of_dreg |])
229    | By_scalar Qreg ->
230        analyze_shape (Use_operands [| Qreg; Qreg; Element_of_dreg |])
231    | By_scalar _ -> assert false
232    | Wide_lane ->
233        analyze_shape (Use_operands [| Qreg; Dreg; Element_of_dreg |])
234    | Wide_scalar ->
235        analyze_shape (Use_operands [| Qreg; Dreg; Element_of_dreg |])
236    | Pair_result elt ->
237      let elt_regexp = analyze_shape_elt elt in
238        elt_regexp ^ ", " ^ elt_regexp
239    | Unary_scalar _ -> "FIXME Unary_scalar"
240    | Binary_imm elt -> analyze_shape (Use_operands [| elt; elt; Immed |])
241    | Narrow_imm -> analyze_shape (Use_operands [| Dreg; Qreg; Immed |])
242    | Long_imm -> analyze_shape (Use_operands [| Qreg; Dreg; Immed |])
243
244(* Generate tests for one intrinsic.  *)
245let test_intrinsic dir opcode features shape name munge elt_ty =
246  (* Open the test source file.  *)
247  let test_name = name ^ (string_of_elt elt_ty) in
248  let chan = open_test_file dir test_name in
249  (* Work out what argument and return types the intrinsic has.  *)
250  let c_arity, new_elt_ty = munge shape elt_ty in
251  let c_types = check_types (strings_of_arity c_arity) in
252  (* Extract any constant valuator (a function specifying what constant
253     values are to be written into the intrinsic call) from the features
254     list.  *)
255  let const_valuator =
256    try
257      match (List.find (fun feature -> match feature with
258                                         Const_valuator _ -> true
259				       | _ -> false) features) with
260        Const_valuator f -> Some f
261      | _ -> assert false
262    with Not_found -> None
263  in
264  (* Work out what instruction name(s) to expect.  *)
265  let insns = get_insn_names features name in
266  let no_suffix = (new_elt_ty = NoElts) in
267  let insns =
268    if no_suffix then insns
269                 else List.map (fun insn ->
270                                  let suffix = string_of_elt_dots new_elt_ty in
271                                    insn ^ "\\." ^ suffix) insns
272  in
273  (* Construct a regexp to match against the expected instruction name(s).  *)
274  let insn_regexp =
275    match insns with
276      [] -> assert false
277    | [insn] -> insn
278    | _ ->
279      let rec calc_regexp insns cur_regexp =
280        match insns with
281          [] -> cur_regexp
282        | [insn] -> cur_regexp ^ "(" ^ insn ^ "))"
283        | insn::insns -> calc_regexp insns (cur_regexp ^ "(" ^ insn ^ ")|")
284      in calc_regexp insns "("
285  in
286  (* Construct regexps to match against the instructions that this
287     intrinsic expands to.  Watch out for any writeback character and
288     comments after the instruction.  *)
289  let regexps = List.map (fun regexp -> insn_regexp ^ "\\[ \t\\]+" ^ regexp ^
290			  "!?\\(\\[ \t\\]+@\\[a-zA-Z0-9 \\]+\\)?\\n")
291                         (analyze_all_shapes features shape analyze_shape)
292  in
293  let effective_target = effective_target features in
294  let compile_test_optim = compile_test_optim features
295  in
296    (* Emit file and function prologues.  *)
297    emit_prologue chan test_name effective_target compile_test_optim;
298
299    if (compare compile_test_optim "-O0") <> 0 then
300        (* Emit variable declarations.  *)
301        emit_variables chan c_types features "";
302
303    Printf.fprintf chan "void test_%s (void)\n{\n" test_name;
304
305    if compare compile_test_optim "-O0" = 0 then
306        (* Emit variable declarations.  *)
307        emit_variables chan c_types features "  ";
308
309    Printf.fprintf chan "\n";
310    (* Emit the call to the intrinsic.  *)
311    emit_call chan const_valuator c_types name elt_ty;
312    (* Emit the function epilogue and the DejaGNU scan-assembler directives.  *)
313    emit_epilogue chan features regexps;
314    (* Close the test file.  *)
315    close_out chan
316
317(* Generate tests for one element of the "ops" table.  *)
318let test_intrinsic_group dir (opcode, features, shape, name, munge, types) =
319  List.iter (test_intrinsic dir opcode features shape name munge) types
320
321(* Program entry point.  *)
322let _ =
323  let directory = if Array.length Sys.argv <> 1 then Sys.argv.(1) else "." in
324    List.iter (test_intrinsic_group directory) (reinterp @ reinterpq @ ops)
325
326