xref: /llvm-project/flang/test/Semantics/defined-ops.f90 (revision 01e22dfb104e7ab4737e512d4e1bbc609962b13e)
196d229c9SAndrzej Warzynski! RUN: %flang_fc1 -fdebug-unparse %s 2>&1 | FileCheck %s
2ce6dd973STim Keith
3ce6dd973STim Keith! Check the analyzed form of a defined operator or assignment.
4ce6dd973STim Keith
5ce6dd973STim Keith! Type-bound defined assignment
6ce6dd973STim Keithmodule m1
7ce6dd973STim Keith  type :: t
8ce6dd973STim Keith  contains
9ce6dd973STim Keith    procedure :: b1 => s1
10ce6dd973STim Keith    procedure, pass(y) :: b2 => s2
11ce6dd973STim Keith    generic :: assignment(=) => b1, b2
12ce6dd973STim Keith  end type
13ce6dd973STim Keithcontains
14ce6dd973STim Keith  subroutine s1(x, y)
15ce6dd973STim Keith    class(t), intent(out) :: x
16*01e22dfbSPeter Klausler    integer, intent(in), value :: y
17ce6dd973STim Keith  end
18ce6dd973STim Keith  subroutine s2(x, y)
19ce6dd973STim Keith    real, intent(out) :: x
20ce6dd973STim Keith    class(t), intent(in) :: y
21ce6dd973STim Keith  end
22ce6dd973STim Keith  subroutine test1(x)
23ce6dd973STim Keith    type(t) :: x
24ce6dd973STim Keith    real :: a
25*01e22dfbSPeter Klausler    integer :: j
26ce6dd973STim Keith    !CHECK: CALL s1(x,1_4)
27ce6dd973STim Keith    x = 1
28*01e22dfbSPeter Klausler    j = 1
29*01e22dfbSPeter Klausler    !CHECK: CALL s1(x,j)
30*01e22dfbSPeter Klausler    x = j ! no parentheses due to VALUE
31*01e22dfbSPeter Klausler    !CHECK: CALL s2(a,(x))
32ce6dd973STim Keith    a = x
33ce6dd973STim Keith  end
34ce6dd973STim Keith  subroutine test2(x)
35ce6dd973STim Keith    class(t) :: x
36ce6dd973STim Keith    real :: a
37ce6dd973STim Keith    !CHECK: CALL x%b1(1_4)
38ce6dd973STim Keith    x = 1
39*01e22dfbSPeter Klausler    !CHECK: CALL (x)%b2(a)
40ce6dd973STim Keith    a = x
41ce6dd973STim Keith  end
42ce6dd973STim Keithend
43ce6dd973STim Keith
44ce6dd973STim Keith! Type-bound operator
45ce6dd973STim Keithmodule m2
46ce6dd973STim Keith  type :: t2
47ce6dd973STim Keith  contains
48ce6dd973STim Keith    procedure, pass(x2) :: b2 => f
49ce6dd973STim Keith    generic :: operator(+) => b2
50ce6dd973STim Keith  end type
51ce6dd973STim Keithcontains
52ce6dd973STim Keith  integer pure function f(x1, x2)
53ce6dd973STim Keith    class(t2), intent(in) :: x1
54ce6dd973STim Keith    class(t2), intent(in) :: x2
55ce6dd973STim Keith  end
56ce6dd973STim Keith  subroutine test2(x, y)
57ce6dd973STim Keith    class(t2) :: x
58ce6dd973STim Keith    type(t2) :: y
59ce6dd973STim Keith    !CHECK: i=f(x,y)
60ce6dd973STim Keith    i = x + y
61ce6dd973STim Keith    !CHECK: i=x%b2(y)
62ce6dd973STim Keith    i = y + x
63ce6dd973STim Keith  end
64ce6dd973STim Keithend module
65ce6dd973STim Keith
66ce6dd973STim Keith! Non-type-bound assignment and operator
67ce6dd973STim Keithmodule m3
68ce6dd973STim Keith  type t
69ce6dd973STim Keith  end type
70ce6dd973STim Keith  interface assignment(=)
71ce6dd973STim Keith    subroutine s1(x, y)
72ce6dd973STim Keith      import
73ce6dd973STim Keith      class(t), intent(out) :: x
74ce6dd973STim Keith      integer, intent(in) :: y
75ce6dd973STim Keith    end
7648a8a3ebSPeter Klausler    subroutine s2(x, y)
7748a8a3ebSPeter Klausler      real, intent(out) :: x
7848a8a3ebSPeter Klausler      class(*), intent(in) :: y
7948a8a3ebSPeter Klausler    end
80*01e22dfbSPeter Klausler    subroutine s3(x, y)
81*01e22dfbSPeter Klausler      integer, intent(out) :: x
82*01e22dfbSPeter Klausler      class(*), intent(in), value :: y
83*01e22dfbSPeter Klausler    end
84ce6dd973STim Keith  end interface
85ce6dd973STim Keith  interface operator(+)
86ce6dd973STim Keith    integer function f(x, y)
87ce6dd973STim Keith      import
88ce6dd973STim Keith      class(t), intent(in) :: x, y
89ce6dd973STim Keith    end
90ce6dd973STim Keith  end interface
91ce6dd973STim Keithcontains
9248a8a3ebSPeter Klausler  subroutine test(x, y, z)
93ce6dd973STim Keith    class(t) :: x, y
9448a8a3ebSPeter Klausler    class(*), intent(in) :: z
9548a8a3ebSPeter Klausler    real :: a
96ce6dd973STim Keith    !CHECK: CALL s1(x,2_4)
97ce6dd973STim Keith    x = 2
98ce6dd973STim Keith    !CHECK: i=f(x,y)
99ce6dd973STim Keith    i = x + y
100*01e22dfbSPeter Klausler    !CHECK: CALL s2(a,(z))
10148a8a3ebSPeter Klausler    a = z
102*01e22dfbSPeter Klausler    !CHECK: CALL s3(i,z)
103*01e22dfbSPeter Klausler    i = z
104ce6dd973STim Keith  end
105ce6dd973STim Keithend
106