aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/structure_constructor_8.f03
blob: 1c0ecd1c1a46a5faf146586781d5526ac178817f (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
! { dg-do compile }
! Test for errors when setting private components inside a structure constructor
! or when constructing a private structure.

MODULE privmod
  IMPLICIT NONE

  TYPE :: haspriv_t
    INTEGER :: a
    INTEGER, PRIVATE :: b = 42
  END TYPE haspriv_t

  TYPE :: allpriv_t
    PRIVATE
    INTEGER :: a = 25
  END TYPE allpriv_t

  TYPE, PRIVATE :: ispriv_t
    INTEGER :: x
  END TYPE ispriv_t

CONTAINS
  
  SUBROUTINE testfunc ()
    IMPLICIT NONE
    TYPE(haspriv_t) :: struct1
    TYPE(allpriv_t) :: struct2
    TYPE(ispriv_t) :: struct3

    ! This should succeed from within the module, no error.
    struct1 = haspriv_t (1, 2)
    struct2 = allpriv_t (42)
    struct3 = ispriv_t (42)
  END SUBROUTINE testfunc

END MODULE privmod

PROGRAM test
  USE privmod
  IMPLICIT NONE

  TYPE(haspriv_t) :: struct1
  TYPE(allpriv_t) :: struct2

  ! This should succeed, not giving value to private component
  struct1 = haspriv_t (5)
  struct2 = allpriv_t ()

  ! These should fail
  struct1 = haspriv_t (1, 2) ! { dg-error "is a PRIVATE component" }
  struct1 = haspriv_t (b = 2, a = 1) ! { dg-error "is a PRIVATE component" }

  ! This should fail as all components are private
  struct2 = allpriv_t (5) ! { dg-error "is a PRIVATE component" }

  ! This should fail as the type itself is private, and the expression should
  ! be deduced as call to an undefined function.
  WRITE (*,*) ispriv_t (5) ! { dg-error "has no IMPLICIT type" }

END PROGRAM test