[LV] Remove hard-coded VPValue numbers in test check lines. (NFC)
[llvm-project.git] / flang / test / Lower / user-defined-operators.f90
blobcf900a5f28919c548bd991586280438c9ab76f7e
1 ! Test use defined operators/assignment
2 ! RUN: bbc -emit-fir -hlfir=false %s -o - | FileCheck %s
4 ! Test user defined assignment
5 ! CHECK-LABEL: func @_QPuser_assignment(
6 ! CHECK-SAME: %[[arg0:.*]]: !fir.ref<!fir.type<{{.*}}>>{{.*}}, %[[arg1:.*]]: !fir.ref<i32>{{.*}}) {
7 subroutine user_assignment(a, i)
8 type t
9 real :: x
10 integer :: i
11 end type
12 interface assignment(=)
13 subroutine my_assign(b, j)
14 import :: t
15 type(t), INTENT(OUT) :: b
16 integer, INTENT(IN) :: j
17 end subroutine
18 end interface
19 type(t) :: a
20 ! CHECK: %[[V_0:[0-9]+]] = fir.alloca i32
21 ! CHECK: %[[V_1:[0-9]+]] = fir.load %arg1 : !fir.ref<i32>
22 ! CHECK: %[[V_2:[0-9]+]] = fir.no_reassoc %[[V_1:[0-9]+]] : i32
23 ! CHECK: fir.store %[[V_2]] to %[[V_0:[0-9]+]] : !fir.ref<i32>
24 ! CHECK: fir.call @_QPmy_assign(%arg0, %[[V_0]]) fastmath<contract> : (!fir.ref<!fir.type<_QFuser_assignmentTt{x:f32,i:i32}>>, !fir.ref<i32>) -> ()
25 a = i
26 end subroutine