summaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/proc_ptr_11.f90
diff options
context:
space:
mode:
Diffstat (limited to 'gcc/testsuite/gfortran.dg/proc_ptr_11.f90')
-rw-r--r--gcc/testsuite/gfortran.dg/proc_ptr_11.f9017
1 files changed, 12 insertions, 5 deletions
diff --git a/gcc/testsuite/gfortran.dg/proc_ptr_11.f90 b/gcc/testsuite/gfortran.dg/proc_ptr_11.f90
index bee73f45213..61921e78ad0 100644
--- a/gcc/testsuite/gfortran.dg/proc_ptr_11.f90
+++ b/gcc/testsuite/gfortran.dg/proc_ptr_11.f90
@@ -7,16 +7,23 @@
program bsp
implicit none
-
+ intrinsic :: isign, iabs
abstract interface
subroutine up()
end subroutine up
+ ! As intrinsics but not elemental
+ pure integer function isign_interf(a, b)
+ integer, intent(in) :: a, b
+ end function isign_interf
+ pure integer function iabs_interf(x)
+ integer, intent(in) :: x
+ end function iabs_interf
end interface
procedure( up ) , pointer :: pptr
- procedure(isign), pointer :: q
+ procedure(isign_interf), pointer :: q
- procedure(iabs),pointer :: p1
+ procedure(iabs_interf),pointer :: p1
procedure(f), pointer :: p2
pointer :: p3
@@ -48,13 +55,13 @@ program bsp
contains
- function add( a, b )
+ pure function add( a, b )
integer :: add
integer, intent( in ) :: a, b
add = a + b
end function add
- integer function f(x)
+ pure integer function f(x)
integer,intent(in) :: x
f = 317 + x
end function