c: Fix up pointer types to may_alias structures [PR114493]
[official-gcc.git] / gcc / testsuite / gfortran.dg / pr41229.f90
blob9f6e566fc9b48f835e06cc8c698cecb0405dd31c
1 ! { dg-do compile }
2 ! { dg-options "-O2 -g" }
3 SUBROUTINE cp_fm_triangular_multiply()
4 INTEGER, PARAMETER :: dp=KIND(0.0D0)
5 REAL(dp), ALLOCATABLE, DIMENSION(:) :: tau, work
6 REAL(KIND=dp), DIMENSION(:, :), POINTER :: a
7 ndim = SIZE(a,2)
8 ALLOCATE(tau(ndim),STAT=istat)
9 ALLOCATE(work(2*ndim),STAT=istat)
10 END SUBROUTINE