diff mbox

[4.8,ARM] Backport r210219: "Neon Intrinsics TLC - remove ML"

Message ID 539EE8A0.3010908@arm.com
State New
Headers show

Commit Message

Alan Lawrence June 16, 2014, 12:52 p.m. UTC
I'm about to backport the ZIP/UZP/TRN fix for ARM big-endian in r211369, that 
patches arm_neon.h, before that we need to remove the OCAML code that 
autogenerates arm_neon.h...ok?

--Alan
diff mbox

Patch

commit 458ddd61009cef4f3bc0d02c6ea74a1da7a4b505
Author: ramana <ramana@138bc75d-0d04-0410-961f-82ee72b054a4>
Date:   Thu May 8 14:35:40 2014 +0000

    Backport r210219 from mainline: "Neon intrinsics TLC - remove ML"
    
    	2014-05-08  Ramana Radhakrishnan  <ramana.radhakrishnan@arm.com>
    
    	* config/arm/arm_neon.h: Update comment.
    	* config/arm/neon-docgen.ml: Delete.
    	* config/arm/neon-gen.ml: Delete.
    	* doc/arm-neon-intrinsics.texi: Update comment.

diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index c9ab54f..80fa36b 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,3 +1,14 @@ 
+2014-06-16  Alan Lawrence  <alan.lawrence@arm.com>
+
+	Backport r210219 from mainline
+
+	2014-05-08  Ramana Radhakrishnan  <ramana.radhakrishnan@arm.com>
+
+	* config/arm/arm_neon.h: Update comment.
+	* config/arm/neon-docgen.ml: Delete.
+	* config/arm/neon-gen.ml: Delete.
+	* doc/arm-neon-intrinsics.texi: Update comment.
+
 2014-06-13  Peter Bergner  <bergner@vnet.ibm.com>
 
 	Backport from mainline
diff --git a/gcc/config/arm/arm_neon.h b/gcc/config/arm/arm_neon.h
index 4d945ce..4381c2a 100644
--- a/gcc/config/arm/arm_neon.h
+++ b/gcc/config/arm/arm_neon.h
@@ -1,5 +1,4 @@ 
-/* ARM NEON intrinsics include file. This file is generated automatically
-   using neon-gen.ml.  Please do not edit manually.
+/* ARM NEON intrinsics include file.
 
    Copyright (C) 2006-2013 Free Software Foundation, Inc.
    Contributed by CodeSourcery.
diff --git a/gcc/config/arm/neon-docgen.ml b/gcc/config/arm/neon-docgen.ml
deleted file mode 100644
index f17314f..0000000
--- a/gcc/config/arm/neon-docgen.ml
+++ /dev/null
@@ -1,344 +0,0 @@ 
-(* ARM NEON documentation generator.
-
-   Copyright (C) 2006-2013 Free Software Foundation, Inc.
-   Contributed by CodeSourcery.
-
-   This file is part of GCC.
-
-   GCC is free software; you can redistribute it and/or modify it under
-   the terms of the GNU General Public License as published by the Free
-   Software Foundation; either version 3, or (at your option) any later
-   version.
-
-   GCC is distributed in the hope that it will be useful, but WITHOUT ANY
-   WARRANTY; without even the implied warranty of MERCHANTABILITY or
-   FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
-   for more details.
-
-   You should have received a copy of the GNU General Public License
-   along with GCC; see the file COPYING3.  If not see
-   <http://www.gnu.org/licenses/>.
-
-   This is an O'Caml program.  The O'Caml compiler is available from:
-
-     http://caml.inria.fr/
-
-   Or from your favourite OS's friendly packaging system. Tested with version
-   3.09.2, though other versions will probably work too.
-
-   Compile with:
-     ocamlc -c neon.ml
-     ocamlc -o neon-docgen neon.cmo neon-docgen.ml
-
-   Run with:
-     /path/to/neon-docgen /path/to/gcc/doc/arm-neon-intrinsics.texi
-*)
-
-open Neon
-
-(* The combined "ops" and "reinterp" table.  *)
-let ops_reinterp = reinterp @ ops
-
-(* Helper functions for extracting things from the "ops" table.  *)
-let single_opcode desired_opcode () =
-  List.fold_left (fun got_so_far ->
-                  fun row ->
-                    match row with
-                      (opcode, _, _, _, _, _) ->
-                        if opcode = desired_opcode then row :: got_so_far
-                                                   else got_so_far
-                 ) [] ops_reinterp
-
-let multiple_opcodes desired_opcodes () =
-  List.fold_left (fun got_so_far ->
-                  fun desired_opcode ->
-                    (single_opcode desired_opcode ()) @ got_so_far)
-                 [] desired_opcodes
-
-let ldx_opcode number () =
-  List.fold_left (fun got_so_far ->
-                  fun row ->
-                    match row with
-                      (opcode, _, _, _, _, _) ->
-                        match opcode with
-                          Vldx n | Vldx_lane n | Vldx_dup n when n = number ->
-                            row :: got_so_far
-                          | _ -> got_so_far
-                 ) [] ops_reinterp
-
-let stx_opcode number () =
-  List.fold_left (fun got_so_far ->
-                  fun row ->
-                    match row with
-                      (opcode, _, _, _, _, _) ->
-                        match opcode with
-                          Vstx n | Vstx_lane n when n = number ->
-                            row :: got_so_far
-                          | _ -> got_so_far
-                 ) [] ops_reinterp
-
-let tbl_opcode () =
-  List.fold_left (fun got_so_far ->
-                  fun row ->
-                    match row with
-                      (opcode, _, _, _, _, _) ->
-                        match opcode with
-                          Vtbl _ -> row :: got_so_far
-                          | _ -> got_so_far
-                 ) [] ops_reinterp
-
-let tbx_opcode () =
-  List.fold_left (fun got_so_far ->
-                  fun row ->
-                    match row with
-                      (opcode, _, _, _, _, _) ->
-                        match opcode with
-                          Vtbx _ -> row :: got_so_far
-                          | _ -> got_so_far
-                 ) [] ops_reinterp
-
-(* The groups of intrinsics.  *)
-let intrinsic_groups =
-  [ "Addition", single_opcode Vadd;
-    "Multiplication", single_opcode Vmul;
-    "Multiply-accumulate", single_opcode Vmla;
-    "Multiply-subtract", single_opcode Vmls;
-    "Fused-multiply-accumulate", single_opcode Vfma;
-    "Fused-multiply-subtract", single_opcode Vfms;
-    "Round to integral (to nearest, ties to even)", single_opcode Vrintn;
-    "Round to integral (to nearest, ties away from zero)", single_opcode Vrinta;
-    "Round to integral (towards +Inf)", single_opcode Vrintp;
-    "Round to integral (towards -Inf)", single_opcode Vrintm;
-    "Round to integral (towards 0)", single_opcode Vrintz;
-    "Subtraction", single_opcode Vsub;
-    "Comparison (equal-to)", single_opcode Vceq;
-    "Comparison (greater-than-or-equal-to)", single_opcode Vcge;
-    "Comparison (less-than-or-equal-to)", single_opcode Vcle;
-    "Comparison (greater-than)", single_opcode Vcgt;
-    "Comparison (less-than)", single_opcode Vclt;
-    "Comparison (absolute greater-than-or-equal-to)", single_opcode Vcage;
-    "Comparison (absolute less-than-or-equal-to)", single_opcode Vcale;
-    "Comparison (absolute greater-than)", single_opcode Vcagt;
-    "Comparison (absolute less-than)", single_opcode Vcalt;
-    "Test bits", single_opcode Vtst;
-    "Absolute difference", single_opcode Vabd;
-    "Absolute difference and accumulate", single_opcode Vaba;
-    "Maximum", single_opcode Vmax;
-    "Minimum", single_opcode Vmin;
-    "Pairwise add", single_opcode Vpadd;
-    "Pairwise add, single_opcode widen and accumulate", single_opcode Vpada;
-    "Folding maximum", single_opcode Vpmax;
-    "Folding minimum", single_opcode Vpmin;
-    "Reciprocal step", multiple_opcodes [Vrecps; Vrsqrts];
-    "Vector shift left", single_opcode Vshl;
-    "Vector shift left by constant", single_opcode Vshl_n;
-    "Vector shift right by constant", single_opcode Vshr_n;
-    "Vector shift right by constant and accumulate", single_opcode Vsra_n;
-    "Vector shift right and insert", single_opcode Vsri;
-    "Vector shift left and insert", single_opcode Vsli;
-    "Absolute value", single_opcode Vabs;
-    "Negation", single_opcode Vneg;
-    "Bitwise not", single_opcode Vmvn;
-    "Count leading sign bits", single_opcode Vcls;
-    "Count leading zeros", single_opcode Vclz;
-    "Count number of set bits", single_opcode Vcnt;
-    "Reciprocal estimate", single_opcode Vrecpe;
-    "Reciprocal square-root estimate", single_opcode Vrsqrte;
-    "Get lanes from a vector", single_opcode Vget_lane;
-    "Set lanes in a vector", single_opcode Vset_lane;
-    "Create vector from literal bit pattern", single_opcode Vcreate;
-    "Set all lanes to the same value",
-      multiple_opcodes [Vdup_n; Vmov_n; Vdup_lane];
-    "Combining vectors", single_opcode Vcombine;
-    "Splitting vectors", multiple_opcodes [Vget_high; Vget_low];
-    "Conversions", multiple_opcodes [Vcvt; Vcvt_n];
-    "Move, single_opcode narrowing", single_opcode Vmovn;
-    "Move, single_opcode long", single_opcode Vmovl;
-    "Table lookup", tbl_opcode;
-    "Extended table lookup", tbx_opcode;
-    "Multiply, lane", single_opcode Vmul_lane;
-    "Long multiply, lane", single_opcode Vmull_lane;
-    "Saturating doubling long multiply, lane", single_opcode Vqdmull_lane;
-    "Saturating doubling multiply high, lane", single_opcode Vqdmulh_lane;
-    "Multiply-accumulate, lane", single_opcode Vmla_lane;
-    "Multiply-subtract, lane", single_opcode Vmls_lane;
-    "Vector multiply by scalar", single_opcode Vmul_n;
-    "Vector long multiply by scalar", single_opcode Vmull_n;
-    "Vector saturating doubling long multiply by scalar",
-      single_opcode Vqdmull_n;
-    "Vector saturating doubling multiply high by scalar",
-      single_opcode Vqdmulh_n;
-    "Vector multiply-accumulate by scalar", single_opcode Vmla_n;
-    "Vector multiply-subtract by scalar", single_opcode Vmls_n;
-    "Vector extract", single_opcode Vext;
-    "Reverse elements", multiple_opcodes [Vrev64; Vrev32; Vrev16];
-    "Bit selection", single_opcode Vbsl;
-    "Transpose elements", single_opcode Vtrn;
-    "Zip elements", single_opcode Vzip;
-    "Unzip elements", single_opcode Vuzp;
-    "Element/structure loads, VLD1 variants", ldx_opcode 1;
-    "Element/structure stores, VST1 variants", stx_opcode 1;
-    "Element/structure loads, VLD2 variants", ldx_opcode 2;
-    "Element/structure stores, VST2 variants", stx_opcode 2;
-    "Element/structure loads, VLD3 variants", ldx_opcode 3;
-    "Element/structure stores, VST3 variants", stx_opcode 3;
-    "Element/structure loads, VLD4 variants", ldx_opcode 4;
-    "Element/structure stores, VST4 variants", stx_opcode 4;
-    "Logical operations (AND)", single_opcode Vand;
-    "Logical operations (OR)", single_opcode Vorr;
-    "Logical operations (exclusive OR)", single_opcode Veor;
-    "Logical operations (AND-NOT)", single_opcode Vbic;
-    "Logical operations (OR-NOT)", single_opcode Vorn;
-    "Reinterpret casts", single_opcode Vreinterp ]
-
-(* Given an intrinsic shape, produce a string to document the corresponding
-   operand shapes.  *)
-let rec analyze_shape shape =
-  let rec n_things n thing =
-    match n with
-      0 -> []
-    | n -> thing :: (n_things (n - 1) thing)
-  in
-  let rec analyze_shape_elt reg_no elt =
-    match elt with
-      Dreg -> "@var{d" ^ (string_of_int reg_no) ^ "}"
-    | Qreg -> "@var{q" ^ (string_of_int reg_no) ^ "}"
-    | Corereg -> "@var{r" ^ (string_of_int reg_no) ^ "}"
-    | Immed -> "#@var{0}"
-    | VecArray (1, elt) ->
-        let elt_regexp = analyze_shape_elt 0 elt in
-          "@{" ^ elt_regexp ^ "@}"
-    | VecArray (n, elt) ->
-      let rec f m =
-        match m with
-          0 -> []
-        | m -> (analyze_shape_elt (m - 1) elt) :: (f (m - 1))
-      in
-      let ops = List.rev (f n) in
-        "@{" ^ (commas (fun x -> x) ops "") ^ "@}"
-    | (PtrTo elt | CstPtrTo elt) ->
-      "[" ^ (analyze_shape_elt reg_no elt) ^ "]"
-    | Element_of_dreg -> (analyze_shape_elt reg_no Dreg) ^ "[@var{0}]"
-    | Element_of_qreg -> (analyze_shape_elt reg_no Qreg) ^ "[@var{0}]"
-    | All_elements_of_dreg -> (analyze_shape_elt reg_no Dreg) ^ "[]"
-    | Alternatives alts -> (analyze_shape_elt reg_no (List.hd alts))
-  in
-    match shape with
-      All (n, elt) -> commas (analyze_shape_elt 0) (n_things n elt) ""
-    | Long -> (analyze_shape_elt 0 Qreg) ^ ", " ^ (analyze_shape_elt 0 Dreg) ^
-              ", " ^ (analyze_shape_elt 0 Dreg)
-    | Long_noreg elt -> (analyze_shape_elt 0 elt) ^ ", " ^
-              (analyze_shape_elt 0 elt)
-    | Wide -> (analyze_shape_elt 0 Qreg) ^ ", " ^ (analyze_shape_elt 0 Qreg) ^
-              ", " ^ (analyze_shape_elt 0 Dreg)
-    | Wide_noreg elt -> analyze_shape (Long_noreg elt)
-    | Narrow -> (analyze_shape_elt 0 Dreg) ^ ", " ^ (analyze_shape_elt 0 Qreg) ^
-                ", " ^ (analyze_shape_elt 0 Qreg)
-    | Use_operands elts -> commas (analyze_shape_elt 0) (Array.to_list elts) ""
-    | By_scalar Dreg ->
-        analyze_shape (Use_operands [| Dreg; Dreg; Element_of_dreg |])
-    | By_scalar Qreg ->
-        analyze_shape (Use_operands [| Qreg; Qreg; Element_of_dreg |])
-    | By_scalar _ -> assert false
-    | Wide_lane ->
-        analyze_shape (Use_operands [| Qreg; Dreg; Element_of_dreg |])
-    | Wide_scalar ->
-        analyze_shape (Use_operands [| Qreg; Dreg; Element_of_dreg |])
-    | Pair_result elt ->
-      let elt_regexp = analyze_shape_elt 0 elt in
-      let elt_regexp' = analyze_shape_elt 1 elt in
-        elt_regexp ^ ", " ^ elt_regexp'
-    | Unary_scalar _ -> "FIXME Unary_scalar"
-    | Binary_imm elt -> analyze_shape (Use_operands [| elt; elt; Immed |])
-    | Narrow_imm -> analyze_shape (Use_operands [| Dreg; Qreg; Immed |])
-    | Long_imm -> analyze_shape (Use_operands [| Qreg; Dreg; Immed |])
-
-(* Document a single intrinsic.  *)
-let describe_intrinsic first chan
-                       (elt_ty, (_, features, shape, name, munge, _)) =
-  let c_arity, new_elt_ty = munge shape elt_ty in
-  let c_types = strings_of_arity c_arity in
-  Printf.fprintf chan "@itemize @bullet\n";
-  let item_code = if first then "@item" else "@itemx" in
-    Printf.fprintf chan "%s %s %s_%s (" item_code (List.hd c_types)
-                   (intrinsic_name name) (string_of_elt elt_ty);
-    Printf.fprintf chan "%s)\n" (commas (fun ty -> ty) (List.tl c_types) "");
-    if not (List.exists (fun feature -> feature = No_op) features) then
-    begin
-      let print_one_insn name =
-        Printf.fprintf chan "@code{";
-        let no_suffix = (new_elt_ty = NoElts) in
-        let name_with_suffix =
-          if no_suffix then name
-          else name ^ "." ^ (string_of_elt_dots new_elt_ty)
-        in
-        let possible_operands = analyze_all_shapes features shape
-                                                   analyze_shape
-        in
-	let rec print_one_possible_operand op =
-	  Printf.fprintf chan "%s %s}" name_with_suffix op
-        in
-          (* If the intrinsic expands to multiple instructions, we assume
-             they are all of the same form.  *)
-          print_one_possible_operand (List.hd possible_operands)
-      in
-      let rec print_insns names =
-        match names with
-          [] -> ()
-        | [name] -> print_one_insn name
-        | name::names -> (print_one_insn name;
-                          Printf.fprintf chan " @emph{or} ";
-                          print_insns names)
-      in
-      let insn_names = get_insn_names features name in
-        Printf.fprintf chan "@*@emph{Form of expected instruction(s):} ";
-        print_insns insn_names;
-        Printf.fprintf chan "\n"
-    end;
-    Printf.fprintf chan "@end itemize\n";
-    Printf.fprintf chan "\n\n"
-
-(* Document a group of intrinsics.  *)
-let document_group chan (group_title, group_extractor) =
-  (* Extract the rows in question from the ops table and then turn them
-     into a list of intrinsics.  *)
-  let intrinsics =
-    List.fold_left (fun got_so_far ->
-                    fun row ->
-                      match row with
-                        (_, _, _, _, _, elt_tys) ->
-                          List.fold_left (fun got_so_far' ->
-                                          fun elt_ty ->
-                                            (elt_ty, row) :: got_so_far')
-                                         got_so_far elt_tys
-                   ) [] (group_extractor ())
-  in
-    (* Emit the title for this group.  *)
-    Printf.fprintf chan "@subsubsection %s\n\n" group_title;
-    (* Emit a description of each intrinsic.  *)
-    List.iter (describe_intrinsic true chan) intrinsics;
-    (* Close this group.  *)
-    Printf.fprintf chan "\n\n"
-
-let gnu_header chan =
-  List.iter (fun s -> Printf.fprintf chan "%s\n" s) [
-  "@c Copyright (C) 2006-2013 Free Software Foundation, Inc.";
-  "@c This is part of the GCC manual.";
-  "@c For copying conditions, see the file gcc.texi.";
-  "";
-  "@c This file is generated automatically using gcc/config/arm/neon-docgen.ml";
-  "@c Please do not edit manually."]
-
-(* Program entry point.  *)
-let _ =
-  if Array.length Sys.argv <> 2 then
-    failwith "Usage: neon-docgen <output filename>"
-  else
-  let file = Sys.argv.(1) in
-    try
-      let chan = open_out file in
-        gnu_header chan;
-        List.iter (document_group chan) intrinsic_groups;
-        close_out chan
-    with Sys_error sys ->
-      failwith ("Could not create output file " ^ file ^ ": " ^ sys)
diff --git a/gcc/config/arm/neon-gen.ml b/gcc/config/arm/neon-gen.ml
deleted file mode 100644
index a811e15..0000000
--- a/gcc/config/arm/neon-gen.ml
+++ /dev/null
@@ -1,492 +0,0 @@ 
-(* Auto-generate ARM Neon intrinsics header file.
-   Copyright (C) 2006-2013 Free Software Foundation, Inc.
-   Contributed by CodeSourcery.
-
-   This file is part of GCC.
-
-   GCC is free software; you can redistribute it and/or modify it under
-   the terms of the GNU General Public License as published by the Free
-   Software Foundation; either version 3, or (at your option) any later
-   version.
-
-   GCC is distributed in the hope that it will be useful, but WITHOUT ANY
-   WARRANTY; without even the implied warranty of MERCHANTABILITY or
-   FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
-   for more details.
-
-   You should have received a copy of the GNU General Public License
-   along with GCC; see the file COPYING3.  If not see
-   <http://www.gnu.org/licenses/>.
-
-   This is an O'Caml program.  The O'Caml compiler is available from:
-
-     http://caml.inria.fr/
-
-   Or from your favourite OS's friendly packaging system. Tested with version
-   3.09.2, though other versions will probably work too.
-
-   Compile with:
-     ocamlc -c neon.ml
-     ocamlc -o neon-gen neon.cmo neon-gen.ml
-
-   Run with:
-     ./neon-gen > arm_neon.h
-*)
-
-open Neon
-
-(* The format codes used in the following functions are documented at:
-     http://caml.inria.fr/pub/docs/manual-ocaml/libref/Format.html\
-     #6_printflikefunctionsforprettyprinting
-   (one line, remove the backslash.)
-*)
-
-(* Following functions can be used to approximate GNU indentation style.  *)
-let start_function () =
-  Format.printf "@[<v 0>";
-  ref 0
-
-let end_function nesting =
-  match !nesting with
-    0 -> Format.printf "@;@;@]"
-  | _ -> failwith ("Bad nesting (ending function at level "
-                   ^ (string_of_int !nesting) ^ ")")
-
-let open_braceblock nesting =
-  begin match !nesting with
-    0 -> Format.printf "@,@<0>{@[<v 2>@,"
-  | _ -> Format.printf "@,@[<v 2>  @<0>{@[<v 2>@,"
-  end;
-  incr nesting
-
-let close_braceblock nesting =
-  decr nesting;
-  match !nesting with
-    0 -> Format.printf "@]@,@<0>}"
-  | _ -> Format.printf "@]@,@<0>}@]"
-
-let print_function arity fnname body =
-  let ffmt = start_function () in
-  Format.printf "__extension__ static __inline ";
-  let inl = "__attribute__ ((__always_inline__))" in
-  begin match arity with
-    Arity0 ret ->
-      Format.printf "%s %s@,%s (void)" (string_of_vectype ret) inl fnname
-  | Arity1 (ret, arg0) ->
-      Format.printf "%s %s@,%s (%s __a)" (string_of_vectype ret) inl fnname
-                                        (string_of_vectype arg0)
-  | Arity2 (ret, arg0, arg1) ->
-      Format.printf "%s %s@,%s (%s __a, %s __b)"
-        (string_of_vectype ret) inl fnname (string_of_vectype arg0)
-	(string_of_vectype arg1)
-  | Arity3 (ret, arg0, arg1, arg2) ->
-      Format.printf "%s %s@,%s (%s __a, %s __b, %s __c)"
-        (string_of_vectype ret) inl fnname (string_of_vectype arg0)
-	(string_of_vectype arg1) (string_of_vectype arg2)
-  | Arity4 (ret, arg0, arg1, arg2, arg3) ->
-      Format.printf "%s %s@,%s (%s __a, %s __b, %s __c, %s __d)"
-        (string_of_vectype ret) inl fnname (string_of_vectype arg0)
-	(string_of_vectype arg1) (string_of_vectype arg2)
-        (string_of_vectype arg3)
-  end;
-  open_braceblock ffmt;
-  let rec print_lines = function
-    []       -> ()
-  | "" :: lines -> print_lines lines
-  | [line] -> Format.printf "%s" line
-  | line::lines -> Format.printf "%s@," line ; print_lines lines in
-  print_lines body;
-  close_braceblock ffmt;
-  end_function ffmt
-
-let union_string num elts base =
-  let itype = inttype_for_array num elts in
-  let iname = string_of_inttype itype
-  and sname = string_of_vectype (T_arrayof (num, elts)) in
-  Printf.sprintf "union { %s __i; %s __o; } %s" sname iname base
-
-let rec signed_ctype = function
-    T_uint8x8 | T_poly8x8 -> T_int8x8
-  | T_uint8x16 | T_poly8x16 -> T_int8x16
-  | T_uint16x4 | T_poly16x4 -> T_int16x4
-  | T_uint16x8 | T_poly16x8 -> T_int16x8
-  | T_uint32x2 -> T_int32x2
-  | T_uint32x4 -> T_int32x4
-  | T_uint64x1 -> T_int64x1
-  | T_uint64x2 -> T_int64x2
-  (* Cast to types defined by mode in arm.c, not random types pulled in from
-     the <stdint.h> header in use. This fixes incompatible pointer errors when
-     compiling with C++.  *)
-  | T_uint8 | T_int8 -> T_intQI
-  | T_uint16 | T_int16 -> T_intHI
-  | T_uint32 | T_int32 -> T_intSI
-  | T_uint64 | T_int64 -> T_intDI
-  | T_float32 -> T_floatSF
-  | T_poly8 -> T_intQI
-  | T_poly16 -> T_intHI
-  | T_arrayof (n, elt) -> T_arrayof (n, signed_ctype elt)
-  | T_ptrto elt -> T_ptrto (signed_ctype elt)
-  | T_const elt -> T_const (signed_ctype elt)
-  | x -> x
-
-let add_cast ctype cval =
-  let stype = signed_ctype ctype in
-  if ctype <> stype then
-    Printf.sprintf "(%s) %s" (string_of_vectype stype) cval
-  else
-    cval
-
-let cast_for_return to_ty = "(" ^ (string_of_vectype to_ty) ^ ")"
-
-(* Return a tuple of a list of declarations to go at the start of the function,
-   and a list of statements needed to return THING.  *)
-let return arity thing =
-  match arity with
-    Arity0 (ret) | Arity1 (ret, _) | Arity2 (ret, _, _) | Arity3 (ret, _, _, _)
-  | Arity4 (ret, _, _, _, _) ->
-      begin match ret with
-	T_arrayof (num, vec) ->
-          let uname = union_string num vec "__rv" in
-          [uname ^ ";"], ["__rv.__o = " ^ thing ^ ";"; "return __rv.__i;"]
-      | T_void ->
-	  [], [thing ^ ";"]
-      | _ ->
-	  [], ["return " ^ (cast_for_return ret) ^ thing ^ ";"]
-      end
-
-let mask_shape_for_shuffle = function
-    All (num, reg) -> All (num, reg)
-  | Pair_result reg -> All (2, reg)
-  | _ -> failwith "mask_for_shuffle"
-
-let mask_elems shuffle shape elttype part =
-  let elem_size = elt_width elttype in
-  let num_elems =
-    match regmap shape 0 with
-      Dreg -> 64 / elem_size
-    | Qreg -> 128 / elem_size
-    | _ -> failwith "mask_elems" in
-  shuffle elem_size num_elems part
-
-(* Return a tuple of a list of declarations 0and a list of statements needed
-   to implement an intrinsic using __builtin_shuffle.  SHUFFLE is a function
-   which returns a list of elements suitable for using as a mask.  *)
-
-let shuffle_fn shuffle shape arity elttype =
-  let mshape = mask_shape_for_shuffle shape in
-  let masktype = type_for_elt mshape (unsigned_of_elt elttype) 0 in
-  let masktype_str = string_of_vectype masktype in
-  let shuffle_res = type_for_elt mshape elttype 0 in
-  let shuffle_res_str = string_of_vectype shuffle_res in
-  match arity with
-    Arity0 (ret) | Arity1 (ret, _) | Arity2 (ret, _, _) | Arity3 (ret, _, _, _)
-  | Arity4 (ret, _, _, _, _) ->
-      begin match ret with
-        T_arrayof (num, vec) ->
-	  let elems1 = mask_elems shuffle mshape elttype `lo
-	  and elems2 = mask_elems shuffle mshape elttype `hi in
-	  let mask1 = (String.concat ", " (List.map string_of_int elems1))
-	  and mask2 = (String.concat ", " (List.map string_of_int elems2)) in
-	  let shuf1 = Printf.sprintf
-	    "__rv.val[0] = (%s) __builtin_shuffle (__a, __b, (%s) { %s });"
-	    shuffle_res_str masktype_str mask1
-	  and shuf2 = Printf.sprintf
-	    "__rv.val[1] = (%s) __builtin_shuffle (__a, __b, (%s) { %s });"
-	    shuffle_res_str masktype_str mask2 in
-	  [Printf.sprintf "%s __rv;" (string_of_vectype ret);],
-	  [shuf1; shuf2; "return __rv;"]
-      | _ ->
-          let elems = mask_elems shuffle mshape elttype `lo in
-          let mask =  (String.concat ", " (List.map string_of_int elems)) in
-	  let shuf = Printf.sprintf
-	    "return (%s) __builtin_shuffle (__a, (%s) { %s });" shuffle_res_str masktype_str mask in
-	  [""],
-	  [shuf]
-      end
-
-let rec element_type ctype =
-  match ctype with
-    T_arrayof (_, v) -> element_type v
-  | _ -> ctype
-
-let params ps =
-  let pdecls = ref [] in
-  let ptype t p =
-    match t with
-      T_arrayof (num, elts) ->
-        let uname = union_string num elts (p ^ "u") in
-        let decl = Printf.sprintf "%s = { %s };" uname p in
-        pdecls := decl :: !pdecls;
-        p ^ "u.__o"
-    | _ -> add_cast t p in
-  let plist = match ps with
-    Arity0 _ -> []
-  | Arity1 (_, t1) -> [ptype t1 "__a"]
-  | Arity2 (_, t1, t2) -> [ptype t1 "__a"; ptype t2 "__b"]
-  | Arity3 (_, t1, t2, t3) -> [ptype t1 "__a"; ptype t2 "__b"; ptype t3 "__c"]
-  | Arity4 (_, t1, t2, t3, t4) ->
-      [ptype t1 "__a"; ptype t2 "__b"; ptype t3 "__c"; ptype t4 "__d"] in
-  !pdecls, plist
-
-let modify_params features plist =
-  let is_flipped =
-    List.exists (function Flipped _ -> true | _ -> false) features in
-  if is_flipped then
-    match plist with
-      [ a; b ] -> [ b; a ]
-    | _ ->
-      failwith ("Don't know how to flip args " ^ (String.concat ", " plist))
-  else
-    plist
-
-(* !!! Decide whether to add an extra information word based on the shape
-   form.  *)
-let extra_word shape features paramlist bits =
-  let use_word =
-    match shape with
-      All _ | Long | Long_noreg _ | Wide | Wide_noreg _ | Narrow
-    | By_scalar _ | Wide_scalar | Wide_lane | Binary_imm _ | Long_imm
-    | Narrow_imm -> true
-    | _ -> List.mem InfoWord features
-  in
-    if use_word then
-      paramlist @ [string_of_int bits]
-    else
-      paramlist
-
-(* Bit 0 represents signed (1) vs unsigned (0), or float (1) vs poly (0).
-   Bit 1 represents floats & polynomials (1), or ordinary integers (0).
-   Bit 2 represents rounding (1) vs none (0).  *)
-let infoword_value elttype features =
-  let bits01 =
-    match elt_class elttype with
-      Signed | ConvClass (Signed, _) | ConvClass (_, Signed) -> 0b001
-    | Poly -> 0b010
-    | Float -> 0b011
-    | _ -> 0b000
-  and rounding_bit = if List.mem Rounding features then 0b100 else 0b000 in
-  bits01 lor rounding_bit
-
-(* "Cast" type operations will throw an exception in mode_of_elt (actually in
-   elt_width, called from there). Deal with that here, and generate a suffix
-   with multiple modes (<to><from>).  *)
-let rec mode_suffix elttype shape =
-  try
-    let mode = mode_of_elt elttype shape in
-    string_of_mode mode
-  with MixedMode (dst, src) ->
-    let dstmode = mode_of_elt dst shape
-    and srcmode = mode_of_elt src shape in
-    string_of_mode dstmode ^ string_of_mode srcmode
-
-let get_shuffle features =
-  try
-    match List.find (function Use_shuffle _ -> true | _ -> false) features with
-      Use_shuffle fn -> Some fn
-    | _ -> None
-  with Not_found -> None
-
-let print_feature_test_start features =
-  try
-    match List.find (fun feature ->
-                       match feature with Requires_feature _ -> true
-                                        | Requires_arch _ -> true
-                                        | _ -> false)
-                     features with
-      Requires_feature feature -> 
-        Format.printf "#ifdef __ARM_FEATURE_%s@\n" feature
-    | Requires_arch arch ->
-        Format.printf "#if __ARM_ARCH >= %d@\n" arch
-    | _ -> assert false
-  with Not_found -> assert true
-
-let print_feature_test_end features =
-  let feature =
-    List.exists (function Requires_feature x -> true
-                          | Requires_arch x -> true
-                          |  _ -> false) features in
-  if feature then Format.printf "#endif@\n"
-
-
-let print_variant opcode features shape name (ctype, asmtype, elttype) =
-  let bits = infoword_value elttype features in
-  let modesuf = mode_suffix elttype shape in
-  let pdecls, paramlist = params ctype in
-  let rdecls, stmts =
-    match get_shuffle features with
-      Some shuffle -> shuffle_fn shuffle shape ctype elttype
-    | None ->
-	let paramlist' = modify_params features paramlist in
-	let paramlist'' = extra_word shape features paramlist' bits in
-	let parstr = String.concat ", " paramlist'' in
-	let builtin = Printf.sprintf "__builtin_neon_%s%s (%s)"
-                	(builtin_name features name) modesuf parstr in
-	return ctype builtin in
-  let body = pdecls @ rdecls @ stmts
-  and fnname = (intrinsic_name name) ^ "_" ^ (string_of_elt elttype) in
-  begin
-    print_feature_test_start features;
-    print_function ctype fnname body;
-    print_feature_test_end features;
-  end
-
-(* When this function processes the element types in the ops table, it rewrites
-   them in a list of tuples (a,b,c):
-     a : C type as an "arity", e.g. Arity1 (T_poly8x8, T_poly8x8)
-     b : Asm type : a single, processed element type, e.g. P16. This is the
-         type which should be attached to the asm opcode.
-     c : Variant type : the unprocessed type for this variant (e.g. in add
-         instructions which don't care about the sign, b might be i16 and c
-         might be s16.)
-*)
-
-let print_op (opcode, features, shape, name, munge, types) =
-  let sorted_types = List.sort compare types in
-  let munged_types = List.map
-    (fun elt -> let c, asm = munge shape elt in c, asm, elt) sorted_types in
-  List.iter
-    (fun variant -> print_variant opcode features shape name variant)
-    munged_types
-
-let print_ops ops =
-  List.iter print_op ops
-
-(* Output type definitions. Table entries are:
-     cbase : "C" name for the type.
-     abase : "ARM" base name for the type (i.e. int in int8x8_t).
-     esize : element size.
-     enum : element count.
-*)
-
-let deftypes () =
-  let typeinfo = [
-    (* Doubleword vector types.  *)
-    "__builtin_neon_qi", "int", 8, 8;
-    "__builtin_neon_hi", "int", 16, 4;
-    "__builtin_neon_si", "int", 32, 2;
-    "__builtin_neon_di", "int", 64, 1;
-    "__builtin_neon_sf", "float", 32, 2;
-    "__builtin_neon_poly8", "poly", 8, 8;
-    "__builtin_neon_poly16", "poly", 16, 4;
-    "__builtin_neon_uqi", "uint", 8, 8;
-    "__builtin_neon_uhi", "uint", 16, 4;
-    "__builtin_neon_usi", "uint", 32, 2;
-    "__builtin_neon_udi", "uint", 64, 1;
-
-    (* Quadword vector types.  *)
-    "__builtin_neon_qi", "int", 8, 16;
-    "__builtin_neon_hi", "int", 16, 8;
-    "__builtin_neon_si", "int", 32, 4;
-    "__builtin_neon_di", "int", 64, 2;
-    "__builtin_neon_sf", "float", 32, 4;
-    "__builtin_neon_poly8", "poly", 8, 16;
-    "__builtin_neon_poly16", "poly", 16, 8;
-    "__builtin_neon_uqi", "uint", 8, 16;
-    "__builtin_neon_uhi", "uint", 16, 8;
-    "__builtin_neon_usi", "uint", 32, 4;
-    "__builtin_neon_udi", "uint", 64, 2
-  ] in
-  List.iter
-    (fun (cbase, abase, esize, enum) ->
-      let attr =
-        match enum with
-          1 -> ""
-        | _ -> Printf.sprintf "\t__attribute__ ((__vector_size__ (%d)))"
-                              (esize * enum / 8) in
-      Format.printf "typedef %s %s%dx%d_t%s;@\n" cbase abase esize enum attr)
-    typeinfo;
-  Format.print_newline ();
-  (* Extra types not in <stdint.h>.  *)
-  Format.printf "typedef float float32_t;\n";
-  Format.printf "typedef __builtin_neon_poly8 poly8_t;\n";
-  Format.printf "typedef __builtin_neon_poly16 poly16_t;\n"
-
-(* Output structs containing arrays, for load & store instructions etc.  *)
-
-let arrtypes () =
-  let typeinfo = [
-    "int", 8;    "int", 16;
-    "int", 32;   "int", 64;
-    "uint", 8;   "uint", 16;
-    "uint", 32;  "uint", 64;
-    "float", 32; "poly", 8;
-    "poly", 16
-  ] in
-  let writestruct elname elsize regsize arrsize =
-    let elnum = regsize / elsize in
-    let structname =
-      Printf.sprintf "%s%dx%dx%d_t" elname elsize elnum arrsize in
-    let sfmt = start_function () in
-    Format.printf "typedef struct %s" structname;
-    open_braceblock sfmt;
-    Format.printf "%s%dx%d_t val[%d];" elname elsize elnum arrsize;
-    close_braceblock sfmt;
-    Format.printf " %s;" structname;
-    end_function sfmt;
-  in
-    for n = 2 to 4 do
-      List.iter
-        (fun (elname, elsize) ->
-          writestruct elname elsize 64 n;
-          writestruct elname elsize 128 n)
-        typeinfo
-    done
-
-let print_lines = List.iter (fun s -> Format.printf "%s@\n" s)
-
-(* Do it.  *)
-
-let _ =
-  print_lines [
-"/* ARM NEON intrinsics include file. This file is generated automatically";
-"   using neon-gen.ml.  Please do not edit manually.";
-"";
-"   Copyright (C) 2006-2013 Free Software Foundation, Inc.";
-"   Contributed by CodeSourcery.";
-"";
-"   This file is part of GCC.";
-"";
-"   GCC is free software; you can redistribute it and/or modify it";
-"   under the terms of the GNU General Public License as published";
-"   by the Free Software Foundation; either version 3, or (at your";
-"   option) any later version.";
-"";
-"   GCC is distributed in the hope that it will be useful, but WITHOUT";
-"   ANY WARRANTY; without even the implied warranty of MERCHANTABILITY";
-"   or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public";
-"   License for more details.";
-"";
-"   Under Section 7 of GPL version 3, you are granted additional";
-"   permissions described in the GCC Runtime Library Exception, version";
-"   3.1, as published by the Free Software Foundation.";
-"";
-"   You should have received a copy of the GNU General Public License and";
-"   a copy of the GCC Runtime Library Exception along with this program;";
-"   see the files COPYING3 and COPYING.RUNTIME respectively.  If not, see";
-"   <http://www.gnu.org/licenses/>.  */";
-"";
-"#ifndef _GCC_ARM_NEON_H";
-"#define _GCC_ARM_NEON_H 1";
-"";
-"#ifndef __ARM_NEON__";
-"#error You must enable NEON instructions (e.g. -mfloat-abi=softfp -mfpu=neon) to use arm_neon.h";
-"#else";
-"";
-"#ifdef __cplusplus";
-"extern \"C\" {";
-"#endif";
-"";
-"#include <stdint.h>";
-""];
-  deftypes ();
-  arrtypes ();
-  Format.print_newline ();
-  print_ops ops;
-  Format.print_newline ();
-  print_ops reinterp;
-  print_lines [
-"#ifdef __cplusplus";
-"}";
-"#endif";
-"#endif";
-"#endif"]
diff --git a/gcc/doc/arm-neon-intrinsics.texi b/gcc/doc/arm-neon-intrinsics.texi
index af8eff0..8413549 100644
--- a/gcc/doc/arm-neon-intrinsics.texi
+++ b/gcc/doc/arm-neon-intrinsics.texi
@@ -2,8 +2,6 @@ 
 @c This is part of the GCC manual.
 @c For copying conditions, see the file gcc.texi.
 
-@c This file is generated automatically using gcc/config/arm/neon-docgen.ml
-@c Please do not edit manually.
 @subsubsection Addition
 
 @itemize @bullet