File: resolve70.f90

package info (click to toggle)
llvm-toolchain-11 1%3A11.0.1-2
  • links: PTS, VCS
  • area: main
  • in suites: bullseye
  • size: 995,808 kB
  • sloc: cpp: 4,767,656; ansic: 760,916; asm: 477,436; python: 170,940; objc: 69,804; lisp: 29,914; sh: 23,855; f90: 18,173; pascal: 7,551; perl: 7,471; ml: 5,603; awk: 3,489; makefile: 2,573; xml: 915; cs: 573; fortran: 503; javascript: 452
file content (75 lines) | stat: -rw-r--r-- 2,319 bytes parent folder | download | duplicates (2)
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
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
! RUN: %S/test_errors.sh %s %t %f18
! C703 (R702) The derived-type-spec shall not specify an abstract type (7.5.7).
! This constraint refers to the derived-type-spec in a type-spec.  A type-spec
! can appear in an ALLOCATE statement, an ac-spec for an array constructor, and
! in the type specifier of a TYPE GUARD statement
!
! C706 TYPE(derived-type-spec) shall not specify an abstract type (7.5.7).
!   This is for a declaration-type-spec
!
! C796 (R756) The derived-type-spec shall not specify an abstract type (7.5.7).
!
! C705 (R703) In a declaration-type-spec that uses the CLASS keyword, 
! derived-type-spec shall specify an extensible type (7.5.7).
subroutine s()
  type, abstract :: abstractType
  end type abstractType

  type, extends(abstractType) :: concreteType
  end type concreteType

  ! declaration-type-spec
  !ERROR: ABSTRACT derived type may not be used here
  type (abstractType), allocatable :: abstractVar

  ! ac-spec for an array constructor
  !ERROR: ABSTRACT derived type may not be used here
  !ERROR: ABSTRACT derived type may not be used here
  type (abstractType), parameter :: abstractArray(*) = (/ abstractType :: /)

  class(*), allocatable :: selector

  ! Structure constructor
  !ERROR: ABSTRACT derived type may not be used here
  !ERROR: ABSTRACT derived type 'abstracttype' may not be used in a structure constructor
  type (abstractType) :: abstractVar1 = abstractType()

  ! Allocate statement
  !ERROR: ABSTRACT derived type may not be used here
  allocate(abstractType :: abstractVar)

  select type(selector)
    ! Type specifier for a type guard statement
    !ERROR: ABSTRACT derived type may not be used here
    type is (abstractType)
  end select
end subroutine s

subroutine s1()
  type :: extensible
  end type
  type, bind(c) :: inextensible
  end type

  ! This one's OK
  class(extensible), allocatable :: y

  !ERROR: Non-extensible derived type 'inextensible' may not be used with CLASS keyword
  class(inextensible), allocatable :: x
end subroutine s1

subroutine s2()
  type t
    integer i
  end type t
  type, extends(t) :: t2
    real x
  end type t2
contains
  function f1(dummy)
    class(*) dummy
    type(t) f1(1)
    !ERROR: Cannot have an unlimited polymorphic value in an array constructor
    f1 = [ (dummy) ]
  end function f1
end subroutine s2