OSDN Git Service

2007-07-09 Thomas Koenig <tkoenig@gcc.gnu.org>
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / operator_4.f90
1 ! PR 17711 : Verify error message text meets operator in source
2 ! { dg-do compile }
3
4 MODULE mod_t
5   type :: t
6     integer :: x
7   end type
8
9   INTERFACE OPERATOR(==)
10     MODULE PROCEDURE t_eq
11   END INTERFACE
12
13   INTERFACE OPERATOR(/=)
14     MODULE PROCEDURE t_ne
15   END INTERFACE
16
17   INTERFACE OPERATOR(>)
18     MODULE PROCEDURE t_gt
19   END INTERFACE
20
21   INTERFACE OPERATOR(>=)
22     MODULE PROCEDURE t_ge
23   END INTERFACE
24
25   INTERFACE OPERATOR(<)
26     MODULE PROCEDURE t_lt
27   END INTERFACE
28
29   INTERFACE OPERATOR(<=)
30     MODULE PROCEDURE t_le
31   END INTERFACE
32
33 CONTAINS
34   LOGICAL FUNCTION t_eq(this, other)
35     TYPE(t), INTENT(in) :: this, other
36     t_eq = (this%x == other%x)
37   END FUNCTION
38
39   LOGICAL FUNCTION t_ne(this, other)
40     TYPE(t), INTENT(in) :: this, other
41     t_ne = (this%x /= other%x)
42   END FUNCTION
43
44   LOGICAL FUNCTION t_gt(this, other)
45     TYPE(t), INTENT(in) :: this, other
46     t_gt = (this%x > other%x)
47   END FUNCTION
48
49   LOGICAL FUNCTION t_ge(this, other)
50     TYPE(t), INTENT(in) :: this, other
51     t_ge = (this%x >= other%x)
52   END FUNCTION
53
54   LOGICAL FUNCTION t_lt(this, other)
55     TYPE(t), INTENT(in) :: this, other
56     t_lt = (this%x < other%x)
57   END FUNCTION
58
59   LOGICAL FUNCTION t_le(this, other)
60     TYPE(t), INTENT(in) :: this, other
61     t_le = (this%x <= other%x)
62   END FUNCTION
63 END MODULE
64
65 PROGRAM pr17711
66   USE mod_t
67
68   LOGICAL :: A
69   INTEGER :: B
70   TYPE(t) :: C
71
72   A = (A == B)   ! { dg-error "comparison operator '=='" }
73   A = (A.EQ.B)   ! { dg-error "comparison operator '.eq.'" }
74   A = (A /= B)   ! { dg-error "comparison operator '/='" }
75   A = (A.NE.B)   ! { dg-error "comparison operator '.ne.'" }
76   A = (A <= B)   ! { dg-error "comparison operator '<='" }
77   A = (A.LE.B)   ! { dg-error "comparison operator '.le.'" }
78   A = (A <  B)   ! { dg-error "comparison operator '<'" }
79   A = (A.LT.B)   ! { dg-error "comparison operator '.lt.'" }
80   A = (A >= B)   ! { dg-error "comparison operator '>='" }
81   A = (A.GE.B)   ! { dg-error "comparison operator '.ge.'" }
82   A = (A >  B)   ! { dg-error "comparison operator '>'" }
83   A = (A.GT.B)   ! { dg-error "comparison operator '.gt.'" }
84
85   ! this should also work with user defined operators
86   A = (A == C)   ! { dg-error "comparison operator '=='" }
87   A = (A.EQ.C)   ! { dg-error "comparison operator '.eq.'" }
88   A = (A /= C)   ! { dg-error "comparison operator '/='" }
89   A = (A.NE.C)   ! { dg-error "comparison operator '.ne.'" }
90   A = (A <= C)   ! { dg-error "comparison operator '<='" }
91   A = (A.LE.C)   ! { dg-error "comparison operator '.le.'" }
92   A = (A <  C)   ! { dg-error "comparison operator '<'" }
93   A = (A.LT.C)   ! { dg-error "comparison operator '.lt.'" }
94   A = (A >= C)   ! { dg-error "comparison operator '>='" }
95   A = (A.GE.C)   ! { dg-error "comparison operator '.ge.'" }
96   A = (A >  C)   ! { dg-error "comparison operator '>'" }
97   A = (A.GT.C)   ! { dg-error "comparison operator '.gt.'" }
98 END PROGRAM
99
100 ! { dg-final { cleanup-modules "mod_t" } }