• Home
  • Line#
  • Scopes#
  • Navigate#
  • Raw
  • Download
1! RUN: %f18 -funparse %s 2>&1 | FileCheck %s
2
3! Check the analyzed form of a defined operator or assignment.
4
5! Type-bound defined assignment
6module m1
7  type :: t
8  contains
9    procedure :: b1 => s1
10    procedure, pass(y) :: b2 => s2
11    generic :: assignment(=) => b1, b2
12  end type
13contains
14  subroutine s1(x, y)
15    class(t), intent(out) :: x
16    integer, intent(in) :: y
17  end
18  subroutine s2(x, y)
19    real, intent(out) :: x
20    class(t), intent(in) :: y
21  end
22  subroutine test1(x)
23    type(t) :: x
24    real :: a
25    !CHECK: CALL s1(x,1_4)
26    x = 1
27    !CHECK: CALL s2(a,x)
28    a = x
29  end
30  subroutine test2(x)
31    class(t) :: x
32    real :: a
33    !CHECK: CALL x%b1(1_4)
34    x = 1
35    !CHECK: CALL x%b2(a)
36    a = x
37  end
38end
39
40! Type-bound operator
41module m2
42  type :: t2
43  contains
44    procedure, pass(x2) :: b2 => f
45    generic :: operator(+) => b2
46  end type
47contains
48  integer pure function f(x1, x2)
49    class(t2), intent(in) :: x1
50    class(t2), intent(in) :: x2
51  end
52  subroutine test2(x, y)
53    class(t2) :: x
54    type(t2) :: y
55    !CHECK: i=f(x,y)
56    i = x + y
57    !CHECK: i=x%b2(y)
58    i = y + x
59  end
60end module
61
62! Non-type-bound assignment and operator
63module m3
64  type t
65  end type
66  interface assignment(=)
67    subroutine s1(x, y)
68      import
69      class(t), intent(out) :: x
70      integer, intent(in) :: y
71    end
72  end interface
73  interface operator(+)
74    integer function f(x, y)
75      import
76      class(t), intent(in) :: x, y
77    end
78  end interface
79contains
80  subroutine test(x, y)
81    class(t) :: x, y
82    !CHECK: CALL s1(x,2_4)
83    x = 2
84    !CHECK: i=f(x,y)
85    i = x + y
86  end
87end
88
89