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

Subversion Repositories openrisc

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

Details | Compare with Previous | View Log

Line No. Rev Author Line
1 694 jeremybenn
! { dg-do compile }
2
 
3
! Abstract Types.
4
! Check for errors when using abstract types in an inappropriate way.
5
 
6
MODULE m
7
  USE ISO_C_BINDING
8
  IMPLICIT NONE
9
 
10
  TYPE, ABSTRACT, BIND(C) :: bindc_t ! { dg-error "must not be ABSTRACT" }
11
    INTEGER(C_INT) :: x
12
  END TYPE bindc_t
13
 
14
  TYPE, ABSTRACT :: sequence_t ! { dg-error "must not be ABSTRACT" }
15
    SEQUENCE
16
    INTEGER :: x
17
  END TYPE sequence_t
18
 
19
  TYPE, ABSTRACT :: abst_t
20
    INTEGER :: x = 0
21
  END TYPE abst_t
22
 
23
  TYPE, EXTENDS(abst_t) :: concrete_t
24
    INTEGER :: y = 1
25
  END TYPE concrete_t
26
 
27
  TYPE :: myt
28
    TYPE(abst_t) :: comp ! { dg-error "is of the ABSTRACT type 'abst_t'" }
29
  END TYPE myt
30
 
31
  ! This should be ok.
32
  TYPE, ABSTRACT, EXTENDS(concrete_t) :: again_abst_t
33
    INTEGER :: z = 2
34
  END TYPE again_abst_t
35
 
36
CONTAINS
37
 
38
  TYPE(abst_t) FUNCTION func () ! { dg-error "of the ABSTRACT type 'abst_t'" }
39
  END FUNCTION func
40
 
41
  SUBROUTINE sub (arg) ! { dg-error "is of the ABSTRACT type 'again_abst_t'" }
42
    IMPLICIT NONE
43
    TYPE(again_abst_t) :: arg
44
    arg = again_abst_t () ! { dg-error "Can't construct ABSTRACT type 'again_abst_t'" }
45
  END SUBROUTINE sub
46
 
47
  SUBROUTINE impl ()
48
    IMPLICIT TYPE(abst_t) (a-z) ! { dg-error "ABSTRACT type 'abst_t' used" }
49
  END SUBROUTINE impl
50
 
51
END MODULE m
52
! { dg-final { cleanup-modules "m" } }

powered by: WebSVN 2.1.0

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