2 ! { dg-options "-finline-matmul-limit=0 -fdump-tree-original" }
4 ! Test the fix for PR36932 and PR36933, in which unnecessary
5 ! temporaries were being generated. The module m2 tests the
6 ! additional testcase in comment #3 of PR36932.
8 ! Contributed by Joost VandeVondele <jv244@cam.ac.uk>
17 TYPE(particle
), POINTER, DIMENSION(:) :: p
36 TYPE(cell_type
), POINTER :: cell
38 REAL :: b(3) = [1, 2, 3]
40 if (ANY (INT (a
) .ne
. [30, 36, 42])) call abort
45 TYPE(cell_type
), POINTER :: cell
47 cell
%h
= reshape ([(real(i
), i
= 1, 9)], [3, 3])
50 ! { dg-final { scan-tree-dump-times "&a" 1 "original" } }
51 ! { dg-final { scan-tree-dump-times "pack" 0 "original" } }