2 ! Test for errors when setting private components inside a structure constructor
3 ! or when constructing a private structure.
10 INTEGER, PRIVATE :: b = 42
18 TYPE, PRIVATE :: ispriv_t
24 SUBROUTINE testfunc ()
26 TYPE(haspriv_t) :: struct1
27 TYPE(allpriv_t) :: struct2
28 TYPE(ispriv_t) :: struct3
30 ! This should succeed from within the module, no error.
31 struct1 = haspriv_t (1, 2)
32 struct2 = allpriv_t (42)
33 struct3 = ispriv_t (42)
34 END SUBROUTINE testfunc
42 TYPE(haspriv_t) :: struct1
43 TYPE(allpriv_t) :: struct2
45 ! This should succeed, not giving value to private component
46 struct1 = haspriv_t (5)
47 struct2 = allpriv_t ()
50 struct1 = haspriv_t (1, 2) ! { dg-error "is a PRIVATE component" }
51 struct1 = haspriv_t (b = 2, a = 1) ! { dg-error "is a PRIVATE component" }
53 ! This should fail as all components are private
54 struct2 = allpriv_t (5) ! { dg-error "is a PRIVATE component" }
56 ! This should fail as the type itself is private, and the expression should
57 ! be deduced as call to an undefined function.
58 WRITE (*,*) ispriv_t (5) ! { dg-error "has no IMPLICIT type" }