view gcc/testsuite/gfortran.dg/asynchronous_4.f90 @ 118:fd00160c1b76

ifdef TARGET_64BIT
author mir3636
date Tue, 27 Feb 2018 15:01:35 +0900
parents 04ced10e8804
children
line wrap: on
line source

! { dg-do compile }
!
! PR 59228: ICE with assumed type and ASYNCHRONOUS
!
! Contributed by Valery Weber <valeryweber@hotmail.com>

  IMPLICIT NONE

  interface
     subroutine test(base)
       TYPE(*), ASYNCHRONOUS :: base
     end subroutine
  end interface

CONTAINS

  SUBROUTINE foo ( data )
    REAL, DIMENSION( : ), ASYNCHRONOUS :: data
    CALL test ( data )                ! { dg-error "Rank mismatch in argument" }
  END SUBROUTINE

END