3 ! { dg-skip-if "NaN not supported" { spu-*-* } { "*" } { "" } }
4 ! Tests that the PRs caused by the lack of gfc_simplify_transfer are
5 ! now fixed. These were brought together in the meta-bug PR31237
6 ! (TRANSFER intrinsic).
7 ! Remaining PRs on 20070409 :-18769 30881 31194 31216 31424 31427
9 program simplify_transfer
10 CHARACTER(LEN
=100) :: buffer
="1.0 3.0"
19 ! Contributed by Joost VandeVondele <jv244@cam.ac.uk>
25 type (t
), parameter :: u
= t (42)
26 integer, parameter :: idx_list(1) = (/ 1 /)
27 integer :: j(1) = transfer (u
, idx_list
)
28 if (j(1) .ne
. 42) call abort ()
29 end subroutine pr18769
33 ! Contributed by Joost VandeVondele <jv244@cam.ac.uk>
35 INTEGER, PARAMETER :: K
=1
39 CASE(TRANSFER(.TRUE
.,K
))
40 CASE(TRANSFER(.FALSE
.,K
))
47 CASE(TRANSFER(.TRUE
.,K
))
49 CASE(TRANSFER(.FALSE
.,K
))
53 END subroutine pr30881
57 ! Contributed by Tobias Burnus <burnus@gcc.gnu.org>
59 real(kind(0d0)) :: NaN
= transfer(ishft(int(z
'FFF80000',8),32),0d0)
60 write (buffer
,'(e12.5)') NaN
61 if (buffer(10:12) .ne
. "NaN") call abort ()
62 end subroutine pr31194
66 ! Contributed by Joost VandeVondele <jv244@cam.ac.uk>
74 CASE (TRANSFER(1.0/3.0,1))
78 END subroutine pr31216
82 ! Contributed by Michael Richmond <michael.a.richmond@nasa.gov>
84 INTEGER(KIND
=1) :: i(1)
85 i
= (/ TRANSFER("a", 0_1) /)
86 if (i(1) .ne
. ichar ("a")) call abort ()
87 END subroutine pr31427
88 end program simplify_transfer