OpenCores
URL https://opencores.org/ocsvn/openrisc/openrisc/trunk

Subversion Repositories openrisc

[/] [openrisc/] [tags/] [gnu-src/] [gcc-4.5.1/] [gcc-4.5.1-or32-1.0rc1/] [gcc/] [testsuite/] [gfortran.dg/] [derived_comp_array_ref_6.f90] - Blame information for rev 578

Go to most recent revision | Details | Compare with Previous | View Log

Line No. Rev Author Line
1 302 jeremybenn
! { dg-do compile }
2
! Check the fix for PR32129 in which the argument 'vec(vy(i, :))' was
3
! incorrectly simplified, resulting in an ICE and a missed error.
4
!
5
! Reported by Tobias Burnus 
6
!
7
    MODULE cdf_aux_mod
8
      TYPE :: the_distribution
9
        INTEGER :: parameters(1)
10
      END TYPE the_distribution
11
      TYPE (the_distribution), PARAMETER :: the_beta = the_distribution((/0/))
12
    CONTAINS
13
      SUBROUTINE set_bound(arg_name)
14
        INTEGER, INTENT (IN) :: arg_name
15
      END SUBROUTINE set_bound
16
    END MODULE cdf_aux_mod
17
    MODULE cdf_beta_mod
18
    CONTAINS
19
      SUBROUTINE cdf_beta()
20
        USE cdf_aux_mod
21
        INTEGER :: which
22
          which = 1
23
          CALL set_bound(the_beta%parameters(1:which)) ! { dg-error "Rank mismatch" }
24
      END SUBROUTINE cdf_beta
25
    END MODULE cdf_beta_mod
26
 
27
! { dg-final { cleanup-modules "cdf_aux_mod" } }

powered by: WebSVN 2.1.0

© copyright 1999-2024 OpenCores.org, equivalent to Oliscience, all rights reserved. OpenCores®, registered trademark.