OSDN Git Service

2011-04-29 Jerry DeLisle <jvdelisle@gcc.gnu.org>
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / dependency_36.f90
1 ! { dg-do compile }
2 ! { dg-options "-O -Warray-temporaries" }
3 ! PR 45744 - this used to ICE because of type mismatch
4 !            in the generated temporary.
5 MODULE m
6 CONTAINS
7   FUNCTION rnd(n)
8     INTEGER, INTENT(in) :: n
9     REAL(8), DIMENSION(n) :: rnd
10     CALL RANDOM_NUMBER(rnd)
11   END FUNCTION rnd
12
13   SUBROUTINE GeneticOptimize(n)
14     INTEGER :: n
15     LOGICAL :: mask(n)
16     REAL(8) :: popcross=0
17     REAL(4) :: foo(n)
18     real(4) :: a(n,n), b(n,n)
19     real(8) :: c(n,n)
20     integer(4) :: x(n,n)
21     integer(8) :: bar(n)
22     mask = (rnd(n) < popcross)  ! { dg-warning "Creating array temporary" }
23     foo = rnd(n)                ! { dg-warning "Creating array temporary" }
24     bar = rnd(n)                ! { dg-warning "Creating array temporary" }
25     c = matmul(a,b)             ! { dg-warning "Creating array temporary" }
26     x = matmul(a,b)             ! { dg-warning "Creating array temporary" }
27   END SUBROUTINE GeneticOptimize
28 END MODULE m