blob: c439e0c7f7e93066a054901dec22c5c281bbbae5 [file] [log] [blame]
! Like array_constructor_6.f90, but check constructors that apply
! an elemental function to an array.
! { dg-do run }
program main
implicit none
call build (200)
contains
subroutine build (order)
integer :: order, i
call test (order, (/ (abs ((/ i, -i, -i * 2 /)), i = 1, order) /))
call test (order, abs ((/ ((/ -i, -i, i * 2 /), i = 1, order) /)))
call test (order, (/ abs ((/ ((/ i, i, -i * 2 /), i = 1, order) /)) /))
end subroutine build
subroutine test (order, values)
integer, dimension (3:) :: values
integer :: order, i
if (size (values, dim = 1) .ne. order * 3) call abort
do i = 1, order
if (values (i * 3) .ne. i) call abort
if (values (i * 3 + 1) .ne. i) call abort
if (values (i * 3 + 2) .ne. i * 2) call abort
end do
end subroutine test
end program main