From 554fd8c5195424bdbcabf5de30fdc183aba391bd Mon Sep 17 00:00:00 2001 From: upstream source tree Date: Sun, 15 Mar 2015 20:14:05 -0400 Subject: obtained gcc-4.6.4.tar.bz2 from upstream website; verified gcc-4.6.4.tar.bz2.sig; imported gcc-4.6.4 source tree from verified upstream tarball. downloading a git-generated archive based on the 'upstream' tag should provide you with a source tree that is binary identical to the one extracted from the above tarball. if you have obtained the source via the command 'git clone', however, do note that line-endings of files in your working directory might differ from line-endings of the respective files in the upstream repository. --- gcc/testsuite/gfortran.dg/transfer_simplify_1.f90 | 88 +++++++++++++++++++++++ 1 file changed, 88 insertions(+) create mode 100644 gcc/testsuite/gfortran.dg/transfer_simplify_1.f90 (limited to 'gcc/testsuite/gfortran.dg/transfer_simplify_1.f90') diff --git a/gcc/testsuite/gfortran.dg/transfer_simplify_1.f90 b/gcc/testsuite/gfortran.dg/transfer_simplify_1.f90 new file mode 100644 index 000000000..4f92121a5 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/transfer_simplify_1.f90 @@ -0,0 +1,88 @@ +! { dg-do run } +! { dg-options "-O2" } +! { dg-skip-if "NaN not supported" { spu-*-* } { "*" } { "" } } +! Tests that the PRs caused by the lack of gfc_simplify_transfer are +! now fixed. These were brought together in the meta-bug PR31237 +! (TRANSFER intrinsic). +! Remaining PRs on 20070409 :-18769 30881 31194 31216 31424 31427 +! +program simplify_transfer + CHARACTER(LEN=100) :: buffer="1.0 3.0" + call pr18769 () + call pr30881 () + call pr31194 () + call pr31216 () + call pr31427 () +contains + subroutine pr18769 () +! +! Contributed by Joost VandeVondele +! + implicit none + type t + integer :: i + end type t + type (t), parameter :: u = t (42) + integer, parameter :: idx_list(1) = (/ 1 /) + integer :: j(1) = transfer (u, idx_list) + if (j(1) .ne. 42) call abort () + end subroutine pr18769 + + subroutine pr30881 () +! +! Contributed by Joost VandeVondele +! + INTEGER, PARAMETER :: K=1 + INTEGER :: I + I=TRANSFER(.TRUE.,K) + SELECT CASE(I) + CASE(TRANSFER(.TRUE.,K)) + CASE(TRANSFER(.FALSE.,K)) + CALL ABORT() + CASE DEFAULT + CALL ABORT() + END SELECT + I=TRANSFER(.FALSE.,K) + SELECT CASE(I) + CASE(TRANSFER(.TRUE.,K)) + CALL ABORT() + CASE(TRANSFER(.FALSE.,K)) + CASE DEFAULT + CALL ABORT() + END SELECT + END subroutine pr30881 + + subroutine pr31194 () +! +! Contributed by Tobias Burnus +! + real(kind(0d0)) :: NaN = transfer(ishft(int(z'FFF80000',8),32),0d0) + write (buffer,'(e12.5)') NaN + if (buffer(10:12) .ne. "NaN") call abort () + end subroutine pr31194 + + subroutine pr31216 () +! +! Contributed by Joost VandeVondele +! + INTEGER :: I + REAL :: C,D + buffer = " 1.0 3.0" + READ(buffer,*) C,D + I=TRANSFER(C/D,I) + SELECT CASE(I) + CASE (TRANSFER(1.0/3.0,1)) + CASE DEFAULT + CALL ABORT() + END SELECT + END subroutine pr31216 + + subroutine pr31427 () +! +! Contributed by Michael Richmond +! + INTEGER(KIND=1) :: i(1) + i = (/ TRANSFER("a", 0_1) /) + if (i(1) .ne. ichar ("a")) call abort () + END subroutine pr31427 +end program simplify_transfer -- cgit v1.2.3