summaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/interface_operator_3.f90
blob: 6a580b2f1cf18fa6c5793f916496b9b282ecd7d8 (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
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
! { dg-do compile }
! PR fortran/65454 - accept both old and new-style relational operators

module m
  implicit none
  private :: t1
  type t1
     integer :: i
  end type t1
  interface operator (==)
     module procedure :: my_cmp
  end interface
  interface operator (/=)
     module procedure :: my_cmp
  end interface
  interface operator (<=)
     module procedure :: my_cmp
  end interface
  interface operator (<)
     module procedure :: my_cmp
  end interface
  interface operator (>=)
     module procedure :: my_cmp
  end interface
  interface operator (>)
     module procedure :: my_cmp
  end interface
contains
  elemental function my_cmp (a, b) result (c)
    type(t1), intent(in) :: a, b
    logical              :: c
    c = a%i == b%i
  end function my_cmp
end module m

module m_os
  implicit none
  private :: t2
  type t2
     integer :: i
  end type t2
  interface operator (.eq.)
     module procedure :: my_cmp
  end interface
  interface operator (.ne.)
     module procedure :: my_cmp
  end interface
  interface operator (.le.)
     module procedure :: my_cmp
  end interface
  interface operator (.lt.)
     module procedure :: my_cmp
  end interface
  interface operator (.ge.)
     module procedure :: my_cmp
  end interface
  interface operator (.gt.)
     module procedure :: my_cmp
  end interface
contains
  elemental function my_cmp (a, b) result (c)
    type(t2), intent(in) :: a, b
    logical              :: c
    c = a%i .eq. b%i
  end function my_cmp
end module m_os

! new style only
module m1
  use m,    only: operator(==), operator(/=)
  use m,    only: operator(<=), operator(<)
  use m,    only: operator(>=), operator(>)
end module m1

! old -> new style
module m2
  use m_os, only: operator(==), operator(/=)
  use m_os, only: operator(<=), operator(<)
  use m_os, only: operator(>=), operator(>)
end module m2

! new -> old style
module m3
  use m,    only: operator(.eq.), operator(.ne.)
  use m,    only: operator(.le.), operator(.lt.)
  use m,    only: operator(.ge.), operator(.gt.)
end module m3

! old style only
module m4
  use m_os, only: operator(.eq.), operator(.ne.)
  use m_os, only: operator(.le.), operator(.lt.)
  use m_os, only: operator(.ge.), operator(.gt.)
end module m4

! new -> all styles
module m5
  use m,    only: operator(.eq.), operator(.ne.), operator(==), operator(/=)
  use m,    only: operator(.le.), operator(.lt.), operator(<=), operator(<)
  use m,    only: operator(.ge.), operator(.gt.), operator(>=), operator(>)
end module m5

! old -> all styles
module m6
  use m_os, only: operator(.eq.), operator(.ne.), operator(==), operator(/=)
  use m_os, only: operator(.le.), operator(.lt.), operator(<=), operator(<)
  use m_os, only: operator(.ge.), operator(.gt.), operator(>=), operator(>)
end module m6

! all -> all styles
module m7
  use m,    only: operator(.eq.), operator(.ne.), operator(==), operator(/=)
  use m,    only: operator(.le.), operator(.lt.), operator(<=), operator(<)
  use m,    only: operator(.ge.), operator(.gt.), operator(>=), operator(>)
  use m_os, only: operator(.eq.), operator(.ne.), operator(==), operator(/=)
  use m_os, only: operator(.le.), operator(.lt.), operator(<=), operator(<)
  use m_os, only: operator(.ge.), operator(.gt.), operator(>=), operator(>)
end module m7

module m_eq
  implicit none
  private :: t3
  type t3
     integer :: i
  end type t3
  interface operator (==)
     module procedure :: my_cmp
  end interface
contains
  elemental function my_cmp (a, b) result (c)
    type(t3), intent(in) :: a, b
    logical              :: c
    c = a%i == b%i
  end function my_cmp
end module m_eq

module m8
  use m_eq, only: operator(==), operator(.eq.)
  use m_eq, only: operator(/=)   ! { dg-error "operator ./=. referenced" }
  use m_eq, only: operator(.ne.) ! { dg-error "operator .\.ne\.. referenced" }
end module m8