OpenCores
URL https://opencores.org/ocsvn/openrisc/openrisc/trunk

Subversion Repositories openrisc

[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [structure_constructor_8.f03] - Blame information for rev 704

Go to most recent revision | Details | Compare with Previous | View Log

Line No. Rev Author Line
1 694 jeremybenn
! { dg-do compile }
2
! Test for errors when setting private components inside a structure constructor
3
! or when constructing a private structure.
4
 
5
MODULE privmod
6
  IMPLICIT NONE
7
 
8
  TYPE :: haspriv_t
9
    INTEGER :: a
10
    INTEGER, PRIVATE :: b = 42
11
  END TYPE haspriv_t
12
 
13
  TYPE :: allpriv_t
14
    PRIVATE
15
    INTEGER :: a = 25
16
  END TYPE allpriv_t
17
 
18
  TYPE, PRIVATE :: ispriv_t
19
    INTEGER :: x
20
  END TYPE ispriv_t
21
 
22
CONTAINS
23
 
24
  SUBROUTINE testfunc ()
25
    IMPLICIT NONE
26
    TYPE(haspriv_t) :: struct1
27
    TYPE(allpriv_t) :: struct2
28
    TYPE(ispriv_t) :: struct3
29
 
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
35
 
36
END MODULE privmod
37
 
38
PROGRAM test
39
  USE privmod
40
  IMPLICIT NONE
41
 
42
  TYPE(haspriv_t) :: struct1
43
  TYPE(allpriv_t) :: struct2
44
 
45
  ! This should succeed, not giving value to private component
46
  struct1 = haspriv_t (5)
47
  struct2 = allpriv_t ()
48
 
49
  ! These should fail
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" }
52
 
53
  ! This should fail as all components are private
54
  struct2 = allpriv_t (5) ! { dg-error "is a PRIVATE component" }
55
 
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" }
59
 
60
END PROGRAM test
61
! { dg-final { cleanup-modules "privmod" } }

powered by: WebSVN 2.1.0

© copyright 1999-2024 OpenCores.org, equivalent to Oliscience, all rights reserved. OpenCores®, registered trademark.