summaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/array_constructor_51.f90
blob: 4c3cdf71fcfa691b2d23927489cd2de92d468e51 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
! { dg-do compile }
! { dg-additional-options "-ffrontend-optimize -fdump-tree-original" }
! PR 82567 - long compile times caused by large constant constructors
! multiplied by variables

  SUBROUTINE sub()
  IMPLICIT NONE
  
  INTEGER, PARAMETER :: n = 1000
  REAL, ALLOCATABLE :: x(:)
  REAL :: xc, h
  INTEGER :: i
 
  ALLOCATE( x(n) )
  xc = 100.
  h = xc/n
  x = h*[(i,i=1,n)]
  
end
! { dg-final { scan-tree-dump-times "__var" 0 "original" } }