aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/power_4.f90
blob: 1d5325966492030c274bafe66496c03113a8fc5e (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
! { dg-do run }
! { dg-options "-ffrontend-optimize -fdump-tree-original" }
! PR 57071 - Check that 2**k is transformed into ishift(1,k).
program main
  implicit none
  integer :: i,m,v
  integer, parameter :: n=30
  integer, dimension(-n:n) :: a,b,c,d,e
  m = n

  v = 2
  ! Test scalar expressions.
  do i=-n,n
     if (2**i /= v**i) call abort
  end do

  ! Test array constructors
  b = [(2**i,i=-m,m)]
  c = [(v**i,i=-m,m)]
  if (any(b /= c)) call abort

  ! Test array expressions
  a = [(i,i=-m,m)]
  d = 2**a
  e = v**a
  if (any(d /= e)) call abort
end program main
! { dg-final { scan-tree-dump-times "_gfortran_pow_i4_i4" 3 "original" } }
! { dg-final { cleanup-tree-dump "original" } }