blob: 7df6cfc4231efc56a1517266096c3c54d5b52a04 [file] [log] [blame]
! RUN: %python %S/test_errors.py %s %flang_fc1
! Error tests for structure constructors.
! Errors caught by name resolution are tested elsewhere; these are the
! errors meant to be caught by expression semantic analysis, as well as
! acceptable use cases.
! Type parameters are used here to make the parses unambiguous.
! C796 (R756) The derived-type-spec shall not specify an abstract type (7.5.7).
! This refers to a derived-type-spec used in a structure constructor
module module1
type :: type1(j)
integer, kind :: j
integer :: n = 1
end type type1
type, extends(type1) :: type2(k)
integer, kind :: k
integer :: m
end type type2
type, abstract :: abstract(j)
integer, kind :: j
integer :: n
end type abstract
type :: privaten(j)
integer, kind :: j
integer, private :: n
end type privaten
contains
subroutine type1arg(x)
type(type1(0)), intent(in) :: x
end subroutine type1arg
subroutine type2arg(x)
type(type2(0,0)), intent(in) :: x
end subroutine type2arg
subroutine abstractarg(x)
class(abstract(0)), intent(in) :: x
end subroutine abstractarg
subroutine errors
call type1arg(type1(0)())
call type1arg(type1(0)(1))
call type1arg(type1(0)(n=1))
!ERROR: Type parameter 'j' may not appear as a component of a structure constructor
call type1arg(type1(0)(j=1))
!ERROR: Component 'n' conflicts with another component earlier in this structure constructor
call type1arg(type1(0)(1,n=2))
!ERROR: Value in structure constructor lacks a component name
call type1arg(type1(0)(n=1,2))
!ERROR: Component 'n' conflicts with another component earlier in this structure constructor
call type1arg(type1(0)(n=1,n=2))
!ERROR: Unexpected value in structure constructor
call type1arg(type1(0)(1,2))
call type2arg(type2(0,0)(n=1,m=2))
call type2arg(type2(0,0)(m=2))
!ERROR: Structure constructor lacks a value for component 'm'
call type2arg(type2(0,0)())
call type2arg(type2(0,0)(type1=type1(0)(n=1),m=2))
call type2arg(type2(0,0)(type1=type1(0)(),m=2))
!ERROR: Component 'type1' conflicts with another component earlier in this structure constructor
call type2arg(type2(0,0)(n=1,type1=type1(0)(n=2),m=3))
!ERROR: Component 'n' conflicts with another component earlier in this structure constructor
call type2arg(type2(0,0)(type1=type1(0)(n=1),n=2,m=3))
!ERROR: Component 'n' conflicts with another component earlier in this structure constructor
call type2arg(type2(0,0)(type1=type1(0)(1),n=2,m=3))
!ERROR: Type parameter 'j' may not appear as a component of a structure constructor
call type2arg(type2(0,0)(j=1, &
!ERROR: Type parameter 'k' may not appear as a component of a structure constructor
k=2,m=3))
!ERROR: ABSTRACT derived type 'abstract' may not be used in a structure constructor
call abstractarg(abstract(0)(n=1))
!This case is ok
end subroutine errors
subroutine polycomponent
type :: poly
class(*), allocatable :: p
end type poly
type(poly) :: x
type :: poly2
class(type1(1)), allocatable :: p1
type(type1(1)), allocatable :: p2
end type poly2
type(type1(1)) :: t1val
type(poly2) :: x2
! These cases are not errors
x = poly(1)
x = poly('hello')
x = poly(type1(1)(123))
x2 = poly2(t1val, t1val)
!ERROR: Value in structure constructor is incompatible with component 'p' of type CLASS(*)
x = poly(z'feedface')
end subroutine
end module module1