diff --git a/gcc/ada/ChangeLog b/gcc/ada/ChangeLog
index 68e10bf88527b8b7d6b11b34284acf302af26cb4..82fb6e56363cc4d88f9df936882bfa34c5cc2614 100644
--- a/gcc/ada/ChangeLog
+++ b/gcc/ada/ChangeLog
@@ -1,3 +1,20 @@
+2019-05-27  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/ada-builtin-types.def: New file.
+	* gcc-interface/ada-builtins.def: Likewise.
+	* gcc-interface/ada-tree.h (BUILT_IN_LIKELY): New macro.
+	(BUILT_IN_UNLIKELY): Likewise.
+	* gcc-interface/trans.c (independent_iterations_p): Initialize the
+	auto-vector to 16 elements.
+	(Call_to_gnu): Remove local variable and change the vector of actual
+	parameters to an auto-vector.  Do not convert actual parameters to
+	the argument type for front-end built-in functions.  Add support for
+	front-end built-in functions.
+	(build_noreturn_cond): Use internal instead of built-in function.
+	* gcc-interface/utils.c (c_builtin_type): Include ada-builtin-types.def
+	(install_builtin_function_types): Likewise.
+	(install_builtin_functions): Include ada-builtins.def first.
+
 2019-05-27  Eric Botcazou  <ebotcazou@adacore.com>
 
 	* gcc-interface/utils.c (maybe_pad_type): Issue the warning for the
diff --git a/gcc/ada/gcc-interface/ada-builtin-types.def b/gcc/ada/gcc-interface/ada-builtin-types.def
new file mode 100644
index 0000000000000000000000000000000000000000..f00845b5f564f88b4089f7ad7720c85a0ccb0099
--- /dev/null
+++ b/gcc/ada/gcc-interface/ada-builtin-types.def
@@ -0,0 +1,25 @@
+/* This file contains the type definitions for the builtins exclusively
+   used in the GNU Ada compiler.
+
+   Copyright (C) 2019 Free Software Foundation, Inc.
+
+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/>.  */
+
+/* See builtin-types.def for details.  */
+
+DEF_FUNCTION_TYPE_1 (BT_FN_BOOL_BOOL, BT_BOOL, BT_BOOL)
+DEF_FUNCTION_TYPE_2 (BT_FN_BOOL_BOOL_BOOL, BT_BOOL, BT_BOOL, BT_BOOL)
diff --git a/gcc/ada/gcc-interface/ada-builtins.def b/gcc/ada/gcc-interface/ada-builtins.def
new file mode 100644
index 0000000000000000000000000000000000000000..dcdc4d91891035910cb9d21c8aef6547df459820
--- /dev/null
+++ b/gcc/ada/gcc-interface/ada-builtins.def
@@ -0,0 +1,30 @@
+/* This file contains the definitions for the builtins exclusively used
+   in the GNU Ada compiler.
+
+   Copyright (C) 2019 Free Software Foundation, Inc.
+
+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/>.  */
+
+/* Before including this file, you should define a macro:
+
+     DEF_ADA_BUILTIN (ENUM, NAME, TYPE, ATTRS)
+
+   See builtins.def for details.  */
+
+DEF_ADA_BUILTIN        (BUILT_IN_EXPECT, "expect", BT_FN_BOOL_BOOL_BOOL, ATTR_CONST_NOTHROW_LEAF_LIST)
+DEF_ADA_BUILTIN        (BUILT_IN_LIKELY, "likely", BT_FN_BOOL_BOOL, ATTR_CONST_NOTHROW_LEAF_LIST)
+DEF_ADA_BUILTIN        (BUILT_IN_UNLIKELY, "unlikely", BT_FN_BOOL_BOOL, ATTR_CONST_NOTHROW_LEAF_LIST)
diff --git a/gcc/ada/gcc-interface/ada-tree.h b/gcc/ada/gcc-interface/ada-tree.h
index ea2c94559920de67903095f256f11d81be5c0d5a..2029b7c1a5275cbe1c12cb350e5a427a9b96a545 100644
--- a/gcc/ada/gcc-interface/ada-tree.h
+++ b/gcc/ada/gcc-interface/ada-tree.h
@@ -6,7 +6,7 @@
  *                                                                          *
  *                              C Header File                               *
  *                                                                          *
- *          Copyright (C) 1992-2018, Free Software Foundation, Inc.         *
+ *          Copyright (C) 1992-2019, Free Software Foundation, Inc.         *
  *                                                                          *
  * GNAT is free software;  you can  redistribute it  and/or modify it under *
  * terms of the  GNU General Public License as published  by the Free Soft- *
@@ -582,3 +582,8 @@ do {						   \
 
 #define EXIT_STMT_COND(NODE)     TREE_OPERAND_CHECK_CODE (NODE, EXIT_STMT, 0)
 #define EXIT_STMT_LABEL(NODE)    TREE_OPERAND_CHECK_CODE (NODE, EXIT_STMT, 1)
+
+/* Small kludge to be able to define Ada built-in functions locally.
+   We overload them on top of the HSAIL/BRIG builtin functions.  */
+#define BUILT_IN_LIKELY   BUILT_IN_HSAIL_WORKITEMABSID
+#define BUILT_IN_UNLIKELY BUILT_IN_HSAIL_GRIDSIZE
diff --git a/gcc/ada/gcc-interface/trans.c b/gcc/ada/gcc-interface/trans.c
index 2efc800d60eb94b0625c5846b96b9246273b9bf8..59c4c07a319b472ce2b57e58b5cf7c685096b796 100644
--- a/gcc/ada/gcc-interface/trans.c
+++ b/gcc/ada/gcc-interface/trans.c
@@ -3307,7 +3307,7 @@ independent_iterations_p (tree stmt_list)
 {
   tree_stmt_iterator tsi;
   bitmap params = BITMAP_GGC_ALLOC();
-  auto_vec<tree> rhs;
+  auto_vec<tree, 16> rhs;
   tree iter;
   int i;
 
@@ -5029,8 +5029,10 @@ Call_to_gnu (Node_Id gnat_node, tree *gnu_result_type_p, tree gnu_target,
   tree gnu_subprog_type = TREE_TYPE (gnu_subprog);
   /* The return type of the FUNCTION_TYPE.  */
   tree gnu_result_type = TREE_TYPE (gnu_subprog_type);
-  tree gnu_subprog_addr = build_unary_op (ADDR_EXPR, NULL_TREE, gnu_subprog);
-  vec<tree, va_gc> *gnu_actual_vec = NULL;
+  const bool frontend_builtin
+    = (TREE_CODE (gnu_subprog) == FUNCTION_DECL
+       && DECL_BUILT_IN_CLASS (gnu_subprog) == BUILT_IN_FRONTEND);
+  auto_vec<tree, 16> gnu_actual_vec;
   tree gnu_name_list = NULL_TREE;
   tree gnu_stmt_list = NULL_TREE;
   tree gnu_after_list = NULL_TREE;
@@ -5487,16 +5489,56 @@ Call_to_gnu (Node_Id gnat_node, tree *gnu_result_type_p, tree gnu_target,
 				     build_int_cst (type_for_size, 0),
 				     false);
 	    }
-	  else
+
+	  /* If this is a front-end built-in function, there is no need to
+	     convert to the type used to pass the argument.  */
+	  else if (!frontend_builtin)
 	    gnu_actual = convert (DECL_ARG_TYPE (gnu_formal), gnu_actual);
 	}
 
-      vec_safe_push (gnu_actual_vec, gnu_actual);
+      gnu_actual_vec.safe_push (gnu_actual);
+    }
+
+  if (frontend_builtin)
+    {
+      tree pred_cst = build_int_cst (integer_type_node, PRED_BUILTIN_EXPECT);
+      enum internal_fn icode = IFN_BUILTIN_EXPECT;
+
+      switch (DECL_FUNCTION_CODE (gnu_subprog))
+	{
+	case BUILT_IN_EXPECT:
+	  break;
+	case BUILT_IN_LIKELY:
+	  gnu_actual_vec.safe_push (boolean_true_node);
+	  break;
+	case BUILT_IN_UNLIKELY:
+	  gnu_actual_vec.safe_push (boolean_false_node);
+	  break;
+	default:
+	  gcc_unreachable ();
+	}
+
+      gnu_actual_vec.safe_push (pred_cst);
+
+      gnu_call
+	= build_call_expr_internal_loc_array (UNKNOWN_LOCATION,
+					      icode,
+					      gnu_result_type,
+					      gnu_actual_vec.length (),
+					      gnu_actual_vec.begin ());
+    }
+  else
+    {
+      gnu_call
+        = build_call_array_loc (UNKNOWN_LOCATION,
+				gnu_result_type,
+				build_unary_op (ADDR_EXPR, NULL_TREE,
+						gnu_subprog),
+				gnu_actual_vec.length (),
+			        gnu_actual_vec.begin ());
+      CALL_EXPR_BY_DESCRIPTOR (gnu_call) = by_descriptor;
     }
 
-  gnu_call
-    = build_call_vec (gnu_result_type, gnu_subprog_addr, gnu_actual_vec);
-  CALL_EXPR_BY_DESCRIPTOR (gnu_call) = by_descriptor;
   set_expr_location_from_node (gnu_call, gnat_node);
 
   /* If we have created a temporary for the return value, initialize it.  */
@@ -6320,24 +6362,17 @@ Compilation_Unit_to_gnu (Node_Id gnat_node)
 
    The compiler will automatically predict the last edge leading to a call
    to a noreturn function as very unlikely taken.  This function makes it
-   possible to expand the prediction to predecessors in case the condition
+   possible to extend the prediction to predecessors in case the condition
    is made up of several short-circuit operators.  */
 
 static tree
 build_noreturn_cond (tree cond)
 {
-  tree fn = builtin_decl_explicit (BUILT_IN_EXPECT);
-  tree arg_types = TYPE_ARG_TYPES (TREE_TYPE (fn));
-  tree pred_type = TREE_VALUE (arg_types);
-  tree expected_type = TREE_VALUE (TREE_CHAIN (arg_types));
-
-  tree t = build_call_expr (fn, 3,
-			    fold_convert (pred_type, cond),
-			    build_int_cst (expected_type, 0),
-			    build_int_cst (integer_type_node,
-					   PRED_NORETURN));
-
-  return build1 (NOP_EXPR, boolean_type_node, t);
+  tree pred_cst = build_int_cst (integer_type_node, PRED_NORETURN);
+  return
+    build_call_expr_internal_loc (UNKNOWN_LOCATION, IFN_BUILTIN_EXPECT,
+				  boolean_type_node, 3, cond,
+				  boolean_false_node, pred_cst);
 }
 
 /* Subroutine of gnat_to_gnu to translate GNAT_RANGE, a node representing a
diff --git a/gcc/ada/gcc-interface/utils.c b/gcc/ada/gcc-interface/utils.c
index ab8b93abf5ff2ea1b2708f193403541896490e3e..4d3facca55aa8b6c272c029f61e259799aabd69d 100644
--- a/gcc/ada/gcc-interface/utils.c
+++ b/gcc/ada/gcc-interface/utils.c
@@ -5877,6 +5877,7 @@ enum c_builtin_type
 				ARG6, ARG7) NAME,
 #define DEF_POINTER_TYPE(NAME, TYPE) NAME,
 #include "builtin-types.def"
+#include "ada-builtin-types.def"
 #undef DEF_PRIMITIVE_TYPE
 #undef DEF_FUNCTION_TYPE_0
 #undef DEF_FUNCTION_TYPE_1
@@ -6025,6 +6026,7 @@ install_builtin_function_types (void)
   builtin_types[(int) ENUM] = build_pointer_type (builtin_types[(int) TYPE]);
 
 #include "builtin-types.def"
+#include "ada-builtin-types.def"
 
 #undef DEF_PRIMITIVE_TYPE
 #undef DEF_FUNCTION_TYPE_0
@@ -6574,7 +6576,10 @@ static int flag_isoc94 = 0;
 static int flag_isoc99 = 0;
 static int flag_isoc11 = 0;
 
-/* Install what the common builtins.def offers.  */
+/* Install what the common builtins.def offers plus our local additions.
+
+   Note that ada-builtins.def is included first so that locally redefined
+   built-in functions take precedence over the commonly defined ones.  */
 
 static void
 install_builtin_functions (void)
@@ -6587,6 +6592,10 @@ install_builtin_functions (void)
                    builtin_types[(int) LIBTYPE],                        \
                    BOTH_P, FALLBACK_P, NONANSI_P,                       \
                    built_in_attributes[(int) ATTRS], IMPLICIT);
+#define DEF_ADA_BUILTIN(ENUM, NAME, TYPE, ATTRS)		\
+  DEF_BUILTIN (ENUM, "__builtin_" NAME, BUILT_IN_FRONTEND, TYPE, BT_LAST, \
+	       false, false, false, ATTRS, true, true)
+#include "ada-builtins.def"
 #include "builtins.def"
 }
 
diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index 56084cc83f35e51645b8b0d8580812d994c8ff38..2884de12cc855f79d005877e8dd6e0206f3dc666 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,3 +1,8 @@
+2019-05-27  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gnat.dg/expect2.adb: New test.
+	* gnat.dg/expect2_pkg.ads: New helper.
+
 2019-05-27  Eric Botcazou  <ebotcazou@adacore.com>
 
 	* gnat.dg/aliased2.adb: New test.
diff --git a/gcc/testsuite/gnat.dg/expect2.adb b/gcc/testsuite/gnat.dg/expect2.adb
new file mode 100644
index 0000000000000000000000000000000000000000..fb50bd8c7f165ec865148b618d62e8b61928400e
--- /dev/null
+++ b/gcc/testsuite/gnat.dg/expect2.adb
@@ -0,0 +1,24 @@
+-- { dg-do compile }
+
+with Text_IO; use Text_IO;
+with Expect2_Pkg; use Expect2_Pkg;
+
+procedure Expect2 is
+begin
+  if Unlikely (I = 0) then
+    Put_Line ("Zero was passed");
+    return;
+  end if;
+
+  if Likely (I > 0) then
+    Put_Line ("A positive number was passed");
+  else
+    Put_Line ("A negative number was passed");
+  end if;
+
+  if Expect ((I rem 2) = 0, False) then
+    Put_Line ("An even number was passed");
+  else
+    Put_Line ("An odd number was passed");
+  end if;
+end;
diff --git a/gcc/testsuite/gnat.dg/expect2_pkg.ads b/gcc/testsuite/gnat.dg/expect2_pkg.ads
new file mode 100644
index 0000000000000000000000000000000000000000..7cb0dd3aaab915d050446956ee041409137f5635
--- /dev/null
+++ b/gcc/testsuite/gnat.dg/expect2_pkg.ads
@@ -0,0 +1,15 @@
+package Expect2_Pkg is
+
+  I : Integer;
+  pragma Volatile (I);
+
+  function Expect (Condition : Boolean; Outcome : Boolean) return Boolean;
+  pragma Import (Intrinsic, Expect, "__builtin_expect");
+
+  function Likely (Condition : Boolean) return Boolean;
+  pragma Import (Intrinsic, Likely, "__builtin_likely");
+
+  function Unlikely (Condition : Boolean) return Boolean;
+  pragma Import (Intrinsic, Unlikely, "__builtin_unlikely");
+
+end Expect2_Pkg;