aboutsummaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/equiv_6.f90
diff options
context:
space:
mode:
authorPaul Thomas <pault@gcc.gnu.org>2006-02-24 10:51:42 +0000
committerPaul Thomas <pault@gcc.gnu.org>2006-02-24 10:51:42 +0000
commit8a0b57b3c7a133c91bb9375635909472749ca954 (patch)
treedc27777b618a359e0083f3498fafe574f05d1710 /gcc/testsuite/gfortran.dg/equiv_6.f90
parent8097c268b057a760157ee16d3bd6ec436f7e5cfe (diff)
downloadgcc-8a0b57b3c7a133c91bb9375635909472749ca954.zip
gcc-8a0b57b3c7a133c91bb9375635909472749ca954.tar.gz
gcc-8a0b57b3c7a133c91bb9375635909472749ca954.tar.bz2
re PR fortran/24519 (gfortran slow because of incomplete dependency checking)
2006-02-24 Paul Thomas <pault@gcc.gnu.org> PR fortran/24519 * dependency.c (gfc_is_same_range): Correct typo. (gfc_check_section_vs_section): Call gfc_is_same_range. PR fortran/25395 * trans-common.c (add_equivalences): Add a new flag that is set when an equivalence is seen that prevents more from being reset until the start of a new traversal of the list, thus ensuring completion of all the equivalences. 2006-02-24 Paul Thomas <pault@gcc.gnu.org> PR fortran/24519 * gfortran.dg/dependency_3.f90: New test. * gfortran.fortran-torture/execute/vect-3.f90: Remove two of the XFAILs. PR fortran/25395 * gfortran.dg/equiv_6.f90: New test. From-SVN: r111416
Diffstat (limited to 'gcc/testsuite/gfortran.dg/equiv_6.f90')
-rw-r--r--gcc/testsuite/gfortran.dg/equiv_6.f9063
1 files changed, 63 insertions, 0 deletions
diff --git a/gcc/testsuite/gfortran.dg/equiv_6.f90 b/gcc/testsuite/gfortran.dg/equiv_6.f90
new file mode 100644
index 0000000..92ba769
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/equiv_6.f90
@@ -0,0 +1,63 @@
+! { dg-do run }
+! This checks the patch for PR25395, in which equivalences within one
+! segment were broken by indirect equivalences, depending on the
+! offset of the variable that bridges the indirect equivalence.
+!
+! This is a fortran95 version of the original testcase, which was
+! contributed by Harald Vogt <harald.vogt@desy.de>
+program check_6
+ common /abc/ mwkx(80)
+ common /cde/ lischk(20)
+ dimension listpr(20),lisbit(10),lispat(8)
+! This was badly compiled in the PR:
+ equivalence (listpr(10),lisbit(1),mwkx(10)), &
+ (lispat(1),listpr(10))
+ lischk = (/0, 0, 0, 0, 0, 0, 0, 0, 0, 1, &
+ 2, 0, 0, 5, 6, 7, 8, 9,10, 0/)
+ call set_arrays (listpr, lisbit)
+ if (any (listpr.ne.lischk)) call abort ()
+ call sub1
+ call sub2
+ call sub3
+end
+subroutine sub1
+ common /abc/ mwkx(80)
+ common /cde/ lischk(20)
+ dimension listpr(20),lisbit(10),lispat(8)
+! This workaround was OK
+ equivalence (listpr(10),lisbit(1)), &
+ (listpr(10),mwkx(10)), &
+ (listpr(10),lispat(1))
+ call set_arrays (listpr, lisbit)
+ if (any (listpr .ne. lischk)) call abort ()
+end
+!
+! Equivalences not in COMMON
+!___________________________
+! This gave incorrect results for the same reason as in MAIN.
+subroutine sub2
+ dimension mwkx(80)
+ common /cde/ lischk(20)
+ dimension listpr(20),lisbit(10),lispat(8)
+ equivalence (lispat(1),listpr(10)), &
+ (mwkx(10),lisbit(1),listpr(10))
+ call set_arrays (listpr, lisbit)
+ if (any (listpr .ne. lischk)) call abort ()
+end
+! This gave correct results because the order in which the
+! equivalences are taken is different and was given in the PR.
+subroutine sub3
+ dimension mwkx(80)
+ common /cde/ lischk(20)
+ dimension listpr(20),lisbit(10),lispat(8)
+ equivalence (listpr(10),lisbit(1),mwkx(10)), &
+ (lispat(1),listpr(10))
+ call set_arrays (listpr, lisbit)
+ if (any (listpr .ne. lischk)) call abort ()
+end
+subroutine set_arrays (listpr, lisbit)
+ dimension listpr(20),lisbit(10)
+ listpr = 0
+ lisbit = (/(i, i = 1, 10)/)
+ lisbit((/3,4/)) = 0
+end