You can not select more than 25 topics
Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.
58 lines
1.8 KiB
58 lines
1.8 KiB
! RUN: %S/test_errors.sh %s %t %f18
|
|
! Test specification expressions
|
|
|
|
module m
|
|
type :: t(n)
|
|
integer, len :: n = 1
|
|
character(len=n) :: c
|
|
end type
|
|
interface
|
|
integer function foo()
|
|
end function
|
|
pure real function realfunc(x)
|
|
real, intent(in) :: x
|
|
end function
|
|
pure integer function hasProcArg(p)
|
|
import realfunc
|
|
procedure(realfunc) :: p
|
|
end function
|
|
end interface
|
|
integer :: coarray[*]
|
|
contains
|
|
pure integer function modulefunc1(n)
|
|
integer, value :: n
|
|
modulefunc1 = n
|
|
end function
|
|
subroutine test(out, optional)
|
|
!ERROR: Invalid specification expression: reference to impure function 'foo'
|
|
type(t(foo())) :: x1
|
|
integer :: local
|
|
!ERROR: Invalid specification expression: reference to local entity 'local'
|
|
type(t(local)) :: x2
|
|
!ERROR: The internal function 'internal' may not be referenced in a specification expression
|
|
type(t(internal(0))) :: x3
|
|
integer, intent(out) :: out
|
|
!ERROR: Invalid specification expression: reference to INTENT(OUT) dummy argument 'out'
|
|
type(t(out)) :: x4
|
|
integer, intent(in), optional :: optional
|
|
!ERROR: Invalid specification expression: reference to OPTIONAL dummy argument 'optional'
|
|
type(t(optional)) :: x5
|
|
!ERROR: Invalid specification expression: dummy procedure argument
|
|
type(t(hasProcArg(realfunc))) :: x6
|
|
!ERROR: Invalid specification expression: coindexed reference
|
|
type(t(coarray[1])) :: x7
|
|
type(t(kind(foo()))) :: x101 ! ok
|
|
type(t(modulefunc1(0))) :: x102 ! ok
|
|
type(t(modulefunc2(0))) :: x103 ! ok
|
|
contains
|
|
pure integer function internal(n)
|
|
integer, value :: n
|
|
internal = n
|
|
end function
|
|
end subroutine
|
|
pure integer function modulefunc2(n)
|
|
integer, value :: n
|
|
modulefunc2 = n
|
|
end function
|
|
end module
|