From ae18f1763236c4ed79f207117dc5465987f97cec Mon Sep 17 00:00:00 2001
From: "Steven G. Kargl" <kargl@gcc.gnu.org>
Date: Mon, 28 Feb 2005 00:40:03 +0000
Subject: [PATCH] ishft.f90: Remove kind suffix from BOZ constant

* gfortran.dg/ishft.f90:  Remove kind suffix from BOZ constant
* gfortran.fortran-torture/execute/intrinsic_mvbits.f90: ditto

From-SVN: r95644
---
 gcc/testsuite/ChangeLog                                  | 6 ++++++
 gcc/testsuite/gfortran.dg/ishft.f90                      | 2 +-
 .../execute/intrinsic_mvbits.f90                         | 9 +++++----
 3 files changed, 12 insertions(+), 5 deletions(-)

diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index 5c55f5ff7183..3cab286530c7 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,3 +1,9 @@
+2005-02-27  Steven G. Kargl  <kargl@gcc.gnu.org>
+
+	* gfortran.dg/ishft.f90:  Remove kind suffix from BOZ constant
+	* gfortran.fortran-torture/execute/intrinsic_mvbits.f90: ditto
+
+
 2005-02-27  Francois-Xavier Coudert  <coudert@clipper.ens.fr>
 
 	PR libfortran/20101
diff --git a/gcc/testsuite/gfortran.dg/ishft.f90 b/gcc/testsuite/gfortran.dg/ishft.f90
index d8ca3a7de731..88edd30efdde 100644
--- a/gcc/testsuite/gfortran.dg/ishft.f90
+++ b/gcc/testsuite/gfortran.dg/ishft.f90
@@ -25,7 +25,7 @@ if (ishft (1_8, 0) /= 1) call abort
 if (ishft (1_8, 1) /= 2) call abort
 if (ishft (3_8, 1) /= 6) call abort
 if (ishft (-1_8, 1) /= -2) call abort
-if (ishft (-1_8, -60) /= z'F'_8) call abort ! { dg-warning "" "" }
+if (ishft (-1_8, -60) /= z'F') call abort
 
 if (ishftc (1_1, 0) /= 1) call abort
 if (ishftc (1_1, 1) /= 2) call abort
diff --git a/gcc/testsuite/gfortran.fortran-torture/execute/intrinsic_mvbits.f90 b/gcc/testsuite/gfortran.fortran-torture/execute/intrinsic_mvbits.f90
index c9fbe7827031..3437e9f0c9dc 100644
--- a/gcc/testsuite/gfortran.fortran-torture/execute/intrinsic_mvbits.f90
+++ b/gcc/testsuite/gfortran.fortran-torture/execute/intrinsic_mvbits.f90
@@ -1,6 +1,6 @@
 ! Test the MVBITS intrinsic subroutine
 INTEGER*4 :: from, to, result
-integer*8 :: to8
+integer*8 :: from8, to8
 
 DATA from / z'0003FFFC' /
 DATA to / z'77760000' /
@@ -9,7 +9,8 @@ DATA result / z'7777FFFE' /
 CALL mvbits(from, 2, 16, to, 1)
 if (to /= result) CALL abort()
 
-to8 = 0
-call mvbits (b'1011'_8*2_8**32, 33, 3, to8, 2) ! { dg-warning "" "" }
-if (to8 /= b'10100'_8) call abort ! { dg-warning "" "" }
+to8 = 0_8
+from8 = b'1011'*2_8**32
+call mvbits (from8, 33, 3, to8, 2)
+if (to8 /= b'10100') call abort
 end
-- 
GitLab