[RISCV][VLOPT] Add vector narrowing integer right shift instructions to isSupportedIn...
[llvm-project.git] / flang / test / Fir / non-trivial-procedure-binding-description.f90
blob668928600157b1510c2e0d635bed533d70d03c5a
1 ! RUN: %flang_fc1 -emit-mlir %s -o - | FileCheck %s --check-prefix=BEFORE
2 ! RUN: %flang_fc1 -emit-mlir %s -o - | fir-opt --abstract-result | FileCheck %s --check-prefix=AFTER
3 module a
4 type f
5 contains
6 ! BEFORE: fir.address_of(@_QMaPfoo) : (!fir.ref<!fir.type<_QMaTf>>) -> !fir.box<!fir.heap<!fir.char<1,?>>>
7 ! AFTER: [[ADDRESS:%.*]] = fir.address_of(@_QMaPfoo) : (!fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>>, !fir.ref<!fir.type<_QMaTf>>) -> ()
8 ! AFTER: fir.convert [[ADDRESS]] : ((!fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>>, !fir.ref<!fir.type<_QMaTf>>) -> ()) -> ((!fir.ref<!fir.type<_QMaTf>>) -> !fir.box<!fir.heap<!fir.char<1,?>>>)
9 ! AFTER-NOT: fir.address_of(@_QMaPfoo) : (!fir.ref<!fir.type<_QMaTf>>) -> !fir.box<!fir.heap<!fir.char<1,?>>>
10 procedure, nopass :: foo
11 end type f
12 contains
13 function foo(obj) result(bar)
14 type(f) :: obj
15 character(len=:), allocatable :: bar
17 if (.TRUE.) then
18 bar = "true"
19 else
20 bar = "false"
21 endif
22 end function foo
23 end module a
25 program main
26 use a
28 type(f) :: obj
29 print *, obj%foo(obj)
30 end program