view gcc/testsuite/gfortran.dg/pointer_target_2.f90 @ 128:fe568345ddd5

fix CbC-example
author mir3636
date Wed, 11 Apr 2018 19:32:28 +0900
parents 04ced10e8804
children 84e7813d76e9
line wrap: on
line source

! { dg-do compile }
! { dg-options "-std=f2003" }
!
! TARGET actual to POINTER dummy with INTENT(IN)
!
program test
  implicit none
  integer, target :: a
  a = 66
  call foo(a) ! { dg-error "Fortran 2008: Non-pointer actual argument" }
  if (a /= 647) call abort()
contains
  subroutine foo(p)
    integer, pointer, intent(in) :: p
    if (a /= 66) call abort()
    if (p /= 66) call abort()
    p = 647
    if (p /= 647) call abort()
    if (a /= 647) call abort()
  end subroutine foo
end program test