aarch64: Add vector floating point extend pattern [PR113880, PR113869]
[official-gcc.git] / gcc / testsuite / gfortran.dg / forall_5.f90
blob244917277de25efc2737aea91298d968d6c70089
1 ! { dg-do compile }
2 ! Tests the fix for PR25072, in which non-PURE functions could
3 ! be referenced inside a FORALL mask.
5 ! Contributed by Paul Thomas <pault@gcc.gnu.org>
7 module foo
8 integer, parameter :: n = 4
9 contains
10 logical function foot (i)
11 integer, intent(in) :: i
12 foot = (i == 2) .or. (i == 3)
13 end function foot
14 end module foo
16 use foo
17 integer :: i, a(n)
18 logical :: s(n)
20 a = 0
21 forall (i=1:n, foot (i)) a(i) = i ! { dg-error "impure" }
22 if (any (a .ne. (/0,2,3,0/))) STOP 1
24 forall (i=1:n, s (i) .or. t(i)) a(i) = i ! { dg-error "impure|LOGICAL" }
25 if (any (a .ne. (/0,3,2,1/))) STOP 2
27 a = 0
28 forall (i=1:n, mod (i, 2) == 0) a(i) = w (i) ! { dg-error "impure" }
29 if (any (a .ne. (/0,2,0,4/))) STOP 3
31 contains
32 logical function t(i)
33 integer, intent(in) :: i
34 t = (mod (i, 2) == 0)
35 end function t
36 integer function w(i)
37 integer, intent(in) :: i
38 w = 5 - i
39 end function w
40 end