+2009-01-29 H.J. Lu <hongjiu.lu@intel.com>
+
+ 2009-01-28 Richard Guenther <rguenther@suse.de>
+
+ PR middle-end/38908
+ * g++.dg/warn/Wuninitialized-2.C: New testcase.
+
+ 2009-01-27 Daniel Kraft <d@domob.eu>
+
+ PR fortran/38883
+ * gfortran.dg/mvbits_6.f90: New test.
+ * gfortran.dg/mvbits_7.f90: New test.
+ * gfortran.dg/mvbits_8.f90: New test.
+
+ 2009-01-21 Daniel Kraft <d@domob.eu>
+
+ PR fortran/38887
+ * gfortran.dg/mvbits_5.f90: New test.
+
2009-01-29 H.J. Lu <hongjiu.lu@intel.com>
Backport from mainline:
--- /dev/null
+/* { dg-do compile } */
+/* { dg-options "-O -Wuninitialized" } */
+
+struct S8 { template<typename T> S8(T) { } };
+
+template<typename T> struct S10;
+template<typename T> struct S10<T()> { typedef T S12; typedef S8 S1(); };
+
+template<typename T> struct S3 { };
+template<typename T> struct S11 { S11(S3<T>); };
+
+struct S2
+{
+ template<typename T> operator S11<T>() { return S11<T>(S5<T>()); }
+ template<typename T> struct S5:public S3<T>
+ {
+ virtual typename S10<T>::S12 S13() {
+ return 0;
+ }
+ };
+};
+
+template<typename T> S11<T> S6(S3<T>) { return S11<T>(S3<T>()); }
+template<typename S12> struct S7 { typedef S12 S15(); };
+
+struct S4
+{
+ template<typename T> operator S11<T>()
+ {
+ struct S14:public S3<T>
+ {
+ S14(S2 x):S11_(x) { }
+ S11<typename S7<typename S10<T>::S12>::S15> S11_;
+ };
+ return S6(S14(S11_));
+ }
+ S2 S11_;
+};
+
+struct S9
+{
+ template<typename F> operator S11<F>() { return S11<F>(S14<F>(S11_)); }
+ template<typename F> struct S14:public S3<F>
+ {
+ S14(S4 x):S11_(x) { }
+ S11<typename S10<F>::S1> S11_;
+ };
+ S4 S11_;
+};
+
+void S15(S11<void()>);
+void S16() { S9 x; S15(x); }
+
--- /dev/null
+! { dg-do run }
+
+! PR fortran/38887
+! This aborted at runtime for the runtime zero-sized array arguments.
+
+! Contributed by Dick Hendrickson <dick.hendrickson@gmail.com>
+
+program try_ya0013
+ integer ida(9)
+ call ya0013(ida,1,5,6)
+end program
+
+SUBROUTINE YA0013(IDA,nf1,nf5,nf6)
+ INTEGER IDA(9)
+ IDA = 1
+ CALL MVBITS(IDA(NF5:NF1), 0, 1, IDA(NF6:NF1),2)
+END SUBROUTINE
--- /dev/null
+! { dg-do compile }
+
+! PR fortran/38883
+! This ICE'd because the temporary-creation in the MVBITS call was wrong.
+! This is the original test from the PR, the complicated version.
+
+! Contributed by Dick Hendrickson <dick.hendrickson@gmail.com>
+
+ module yg0009_stuff
+
+ type unseq
+ integer I
+ end type
+
+ contains
+
+ SUBROUTINE YG0009(TDA2L,NF4,NF3,NF1,MF1,MF4,MF3)
+ TYPE(UNSEQ) TDA2L(NF4,NF3)
+
+ CALL MVBITS (TDA2L(NF4:NF1:MF1,NF1:NF3)%I,2, &
+ 4, TDA2L(-MF4:-MF1:-NF1,-MF1:-MF3)%I, 3)
+
+ END SUBROUTINE
+
+ end module yg0009_stuff
+
+ program try_yg0009
+ use yg0009_stuff
+ type(unseq) tda2l(4,3)
+
+ call yg0009(tda2l,4,3,1,-1,-4,-3)
+
+ end
--- /dev/null
+! { dg-do run }
+
+! PR fortran/38883
+! This ICE'd because the temporary-creation in the MVBITS call was wrong.
+
+! Contributed by Paul Richard Thomas <paul.richard.thomas@gmail.com>
+
+ type t
+ integer :: I
+ character(9) :: chr
+ end type
+ type(t) :: x(4,3)
+ type(t) :: y(4,3)
+ x = reshape ([((t (i*j, "a"),i = 1,4), j=1,3)], [4,3])
+ call foo (x)
+ y = reshape ([((t (i*j*2, "a"),i = 1,4), j=1,3)], [4,3])
+ call bar(y, 4, 3, 1, -1, -4, -3)
+ if (any (x%i .ne. y%i)) call abort
+contains
+ SUBROUTINE foo (x)
+ TYPE(t) x(4, 3) ! No dependency at all
+ CALL MVBITS (x%i, 0, 6, x%i, 8)
+ x%i = x%i * 2
+ END SUBROUTINE
+ SUBROUTINE bar (x, NF4, NF3, NF1, MF1, MF4, MF3)
+ TYPE(t) x(NF4, NF3) ! Dependency through variable indices
+ CALL MVBITS (x(NF4:NF1:MF1, NF1:NF3)%i, 1, &
+ 6, x(-MF4:-MF1:-NF1, -MF1:-MF3)%i, 9)
+ END SUBROUTINE
+end
--- /dev/null
+! { dg-do run }
+
+! PR fortran/38883
+! This ICE'd because the temporary-creation in the MVBITS call was wrong.
+
+PROGRAM main
+ IMPLICIT NONE
+
+ TYPE inner
+ INTEGER :: i
+ INTEGER :: j
+ END TYPE inner
+
+ TYPE outer
+ TYPE(inner) :: comp(2)
+ END TYPE outer
+
+ TYPE(outer) :: var
+
+ var%comp%i = (/ 1, 2 /)
+ var%comp%j = (/ 3, 4 /)
+
+ CALL foobar (var, 1, 2)
+
+ IF (ANY (var%comp%i /= (/ 1, 2 /))) CALL abort ()
+ IF (ANY (var%comp%j /= (/ 3, 4 /))) CALL abort ()
+
+CONTAINS
+
+ SUBROUTINE foobar (x, lower, upper)
+ TYPE(outer), INTENT(INOUT) :: x
+ INTEGER, INTENT(IN) :: lower, upper
+ CALL MVBITS (x%comp%i, 1, 2, x%comp(lower:upper)%i, 1)
+ END SUBROUTINE foobar
+
+END PROGRAM main