aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/typebound_proc_13.f03
blob: 98caac69245ab3b5dbd4fa33c9368e7873dc0aaf (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
! { dg-do compile }

! PR fortran/41177
! Test for additional errors with type-bound procedure bindings.
! Namely that non-scalar base objects are rejected for TBP calls which are
! NOPASS, and that passed-object dummy arguments must be scalar, non-POINTER
! and non-ALLOCATABLE.

MODULE m
  IMPLICIT NONE

  TYPE t
  CONTAINS
    PROCEDURE, NOPASS :: myproc
  END TYPE t

  TYPE t2
  CONTAINS
    PROCEDURE, PASS :: nonscalar ! { dg-error "must be scalar" }
    PROCEDURE, PASS :: is_pointer ! { dg-error "must not be POINTER" }
    PROCEDURE, PASS :: is_allocatable ! { dg-error "must not be ALLOCATABLE" }
  END TYPE t2

CONTAINS

  SUBROUTINE myproc ()
  END SUBROUTINE myproc

  SUBROUTINE nonscalar (me)
    CLASS(t2), INTENT(IN) :: me(:)
  END SUBROUTINE nonscalar

  SUBROUTINE is_pointer (me)
    CLASS(t2), POINTER, INTENT(IN) :: me
  END SUBROUTINE is_pointer

  SUBROUTINE is_allocatable (me)
    CLASS(t2), ALLOCATABLE, INTENT(IN) :: me
  END SUBROUTINE is_allocatable

  SUBROUTINE test ()
    TYPE(t) :: arr(2)
    CALL arr%myproc () ! { dg-error "must be scalar" }
  END SUBROUTINE test

END MODULE m