diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index eaf26485a1379ec6086d742c873dd2d235eb6797..a7066fb7ad1969919d0274c08de78aa0a5033291 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,3 +1,10 @@
+2017-11-27  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* cfgloop.h (struct loop): Document usage of USHRT_MAX for unroll.
+	* loop-unroll.c (decide_unroll_constant_iterations): Implement it.
+	(decide_unroll_runtime_iterations): Likewise.
+	(decide_unroll_stupid): Likewise.
+
 2017-11-27  Igor Tsimbalist  <igor.v.tsimbalist@intel.com>
 
 	PR target/83109
diff --git a/gcc/cfgloop.h b/gcc/cfgloop.h
index be2ba8cf1a16fc92235fa99e784c0c66e58d022a..dce01bdd56a355c25ee80573b7f91ecbfada4894 100644
--- a/gcc/cfgloop.h
+++ b/gcc/cfgloop.h
@@ -221,9 +221,10 @@ struct GTY ((chain_next ("%h.next"))) loop {
   /* True if the loop is part of an oacc kernels region.  */
   unsigned in_oacc_kernels_region : 1;
 
-  /* The number of times to unroll the loop.  0, means no information
-     given, just do what we always do.  A value of 1, means don't unroll
-     the loop.  */
+  /* The number of times to unroll the loop.  0 means no information given,
+     just do what we always do.  A value of 1 means do not unroll the loop.
+     A value of USHRT_MAX means unroll with no specific unrolling factor.
+     Other values means unroll with the given unrolling factor.  */
   unsigned short unroll;
 
   /* For SIMD loops, this is a unique identifier of the loop, referenced
diff --git a/gcc/loop-unroll.c b/gcc/loop-unroll.c
index bbba35fbff1e4b466051b0a3d34087a45c03f9fc..0fdecd7fde2d693a04f4a138023d923d4c9e3eda 100644
--- a/gcc/loop-unroll.c
+++ b/gcc/loop-unroll.c
@@ -395,7 +395,7 @@ decide_unroll_constant_iterations (struct loop *loop, int flags)
     }
 
   /* Check for an explicit unrolling factor.  */
-  if (loop->unroll)
+  if (loop->unroll > 0 && loop->unroll < USHRT_MAX)
     {
       /* However we cannot unroll completely at the RTL level a loop with
 	 constant number of iterations; it should have been peeled instead.  */
@@ -693,7 +693,7 @@ decide_unroll_runtime_iterations (struct loop *loop, int flags)
   if (targetm.loop_unroll_adjust)
     nunroll = targetm.loop_unroll_adjust (nunroll, loop);
 
-  if (loop->unroll)
+  if (loop->unroll > 0 && loop->unroll < USHRT_MAX)
     nunroll = loop->unroll;
 
   /* Skip big loops.  */
@@ -1177,7 +1177,7 @@ decide_unroll_stupid (struct loop *loop, int flags)
   if (targetm.loop_unroll_adjust)
     nunroll = targetm.loop_unroll_adjust (nunroll, loop);
 
-  if (loop->unroll)
+  if (loop->unroll > 0 && loop->unroll < USHRT_MAX)
     nunroll = loop->unroll;
 
   /* Skip big loops.  */
diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index 04788b638773074b269af948cdc5900d5cf3c890..cb3835b3e9de626403186cac2ec77db749629cd2 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,3 +1,14 @@
+2017-11-27  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gnat.dg/unroll1.ads: Remove alignment clause.
+	* gnat.dg/unroll2.ads: Likewise.
+	* gnat.dg/unroll3.ads: Likewise.
+	* gnat.dg/unroll1.adb: Remove bogus comment terminator.
+	* gnat.dg/unroll2.adb: Likewise.
+	* gnat.dg/unroll3.adb: Likewise.
+	* gnat.dg/unroll4.ad[sb]: New testcase.
+	* gnat.dg/unroll4_pkg.ads: New helper.
+
 2017-11-27  Igor Tsimbalist  <igor.v.tsimbalist@intel.com>
 
 	PR target/83109
diff --git a/gcc/testsuite/gnat.dg/unroll1.adb b/gcc/testsuite/gnat.dg/unroll1.adb
index ff9222de0e0208a73357533587fd5d391b4253a2..34d8a8f3f388d966483422751162341d4bedd698 100644
--- a/gcc/testsuite/gnat.dg/unroll1.adb
+++ b/gcc/testsuite/gnat.dg/unroll1.adb
@@ -23,5 +23,5 @@ package body Unroll1 is
 
 end Unroll1;
 
--- { dg-final { scan-tree-dump-times "Not unrolling loop .: user didn't want it unrolled completely" 2 "cunrolli" } } */
--- { dg-final { scan-rtl-dump-times "Not unrolling loop, user didn't want it unrolled" 2 "loop2_unroll" } } */
+-- { dg-final { scan-tree-dump-times "Not unrolling loop .: user didn't want it unrolled completely" 2 "cunrolli" } }
+-- { dg-final { scan-rtl-dump-times "Not unrolling loop, user didn't want it unrolled" 2 "loop2_unroll" } }
diff --git a/gcc/testsuite/gnat.dg/unroll1.ads b/gcc/testsuite/gnat.dg/unroll1.ads
index 28dbea8a9c0e79aec5ee62438c06520e4a809a46..b96762b0da9b8d9a62afbf2bdb489d973d4515ad 100644
--- a/gcc/testsuite/gnat.dg/unroll1.ads
+++ b/gcc/testsuite/gnat.dg/unroll1.ads
@@ -1,7 +1,6 @@
 package Unroll1 is
 
    type Sarray is array (1 .. 4) of Float;
-   for Sarray'Alignment use 16;
 
    function "+" (X, Y : Sarray) return Sarray;
    procedure Add (X, Y : Sarray; R : out Sarray);
diff --git a/gcc/testsuite/gnat.dg/unroll2.adb b/gcc/testsuite/gnat.dg/unroll2.adb
index 01af9d2b788cf7e425427ca22b96874fed064673..e4473cc05580be043ede3dce3b5ca4676c128880 100644
--- a/gcc/testsuite/gnat.dg/unroll2.adb
+++ b/gcc/testsuite/gnat.dg/unroll2.adb
@@ -23,4 +23,4 @@ package body Unroll2 is
 
 end Unroll2;
 
--- { dg-final { scan-tree-dump-times "note: loop with 3 iterations completely unrolled" 2 "cunrolli" } } */
+-- { dg-final { scan-tree-dump-times "note: loop with 3 iterations completely unrolled" 2 "cunrolli" } }
diff --git a/gcc/testsuite/gnat.dg/unroll2.ads b/gcc/testsuite/gnat.dg/unroll2.ads
index efae982c4c6640102c5f7fd471e03fec59313465..342f371f1fec59cd690db3230a6bf9dfd3103c05 100644
--- a/gcc/testsuite/gnat.dg/unroll2.ads
+++ b/gcc/testsuite/gnat.dg/unroll2.ads
@@ -1,7 +1,6 @@
 package Unroll2 is
 
    type Sarray is array (1 .. 4) of Float;
-   for Sarray'Alignment use 16;
 
    function "+" (X, Y : Sarray) return Sarray;
    procedure Add (X, Y : Sarray; R : out Sarray);
diff --git a/gcc/testsuite/gnat.dg/unroll3.adb b/gcc/testsuite/gnat.dg/unroll3.adb
index 3a0725b80931cd438875c35e34927ed7f900ab3b..ba4e122530aa2202b553f4cba438a24e7f0d13a7 100644
--- a/gcc/testsuite/gnat.dg/unroll3.adb
+++ b/gcc/testsuite/gnat.dg/unroll3.adb
@@ -23,4 +23,4 @@ package body Unroll3 is
 
 end Unroll3;
 
--- { dg-final { scan-tree-dump-times "note: loop with 3 iterations completely unrolled" 2 "cunroll" } } */
+-- { dg-final { scan-tree-dump-times "note: loop with 3 iterations completely unrolled" 2 "cunroll" } }
diff --git a/gcc/testsuite/gnat.dg/unroll3.ads b/gcc/testsuite/gnat.dg/unroll3.ads
index 8264fc7b489aeee9f4376748afceadfc72058752..8f0cae1cbfd1afd47da213d2c45f959b7a31762b 100644
--- a/gcc/testsuite/gnat.dg/unroll3.ads
+++ b/gcc/testsuite/gnat.dg/unroll3.ads
@@ -1,7 +1,6 @@
 package Unroll3 is
 
    type Sarray is array (1 .. 4) of Float;
-   for Sarray'Alignment use 16;
 
    function "+" (X, Y : Sarray) return Sarray;
    procedure Add (X, Y : Sarray; R : out Sarray);
diff --git a/gcc/testsuite/gnat.dg/unroll4.adb b/gcc/testsuite/gnat.dg/unroll4.adb
new file mode 100644
index 0000000000000000000000000000000000000000..d9b763ae4015823a1a1387f063992106b18891f6
--- /dev/null
+++ b/gcc/testsuite/gnat.dg/unroll4.adb
@@ -0,0 +1,26 @@
+-- { dg-do compile }
+-- { dg-options "-O -fdump-rtl-loop2_unroll-details" }
+
+package body Unroll4 is
+
+   function "+" (X, Y : Sarray) return Sarray is
+      R : Sarray;
+   begin
+      for I in Sarray'Range loop
+         pragma Loop_Optimize (Unroll);
+         R(I) := X(I) + Y(I);
+      end loop;
+      return R;
+   end;
+
+   procedure Add (X, Y : Sarray; R : out Sarray) is
+   begin
+      for I in Sarray'Range loop
+         pragma Loop_Optimize (Unroll);
+         R(I) := X(I) + Y(I);
+      end loop;
+   end;
+
+end Unroll4;
+
+-- { dg-final { scan-rtl-dump-times "note: loop unrolled 7 times" 2 "loop2_unroll" } }
diff --git a/gcc/testsuite/gnat.dg/unroll4.ads b/gcc/testsuite/gnat.dg/unroll4.ads
new file mode 100644
index 0000000000000000000000000000000000000000..e36bc8070bc0b9e37cb010e34fd02ab15413c853
--- /dev/null
+++ b/gcc/testsuite/gnat.dg/unroll4.ads
@@ -0,0 +1,10 @@
+with Unroll4_Pkg; use Unroll4_Pkg;
+
+package Unroll4 is
+
+   type Sarray is array (1 .. N) of Float;
+
+   function "+" (X, Y : Sarray) return Sarray;
+   procedure Add (X, Y : Sarray; R : out Sarray);
+
+end Unroll4;
diff --git a/gcc/testsuite/gnat.dg/unroll4_pkg.ads b/gcc/testsuite/gnat.dg/unroll4_pkg.ads
new file mode 100644
index 0000000000000000000000000000000000000000..a0a45b007df099d9299fed35baaf9c98181422f5
--- /dev/null
+++ b/gcc/testsuite/gnat.dg/unroll4_pkg.ads
@@ -0,0 +1,5 @@
+package Unroll4_Pkg is
+
+   function N return Positive;
+
+end Unroll4_Pkg;