File: allocate-source-allocatables-2.f90

package info (click to toggle)
llvm-toolchain-19 1%3A19.1.7-3
  • links: PTS, VCS
  • area: main
  • in suites: trixie
  • size: 1,998,520 kB
  • sloc: cpp: 6,951,680; ansic: 1,486,157; asm: 913,598; python: 232,024; f90: 80,126; objc: 75,281; lisp: 37,276; pascal: 16,990; sh: 10,009; ml: 5,058; perl: 4,724; awk: 3,523; makefile: 3,167; javascript: 2,504; xml: 892; fortran: 664; cs: 573
file content (49 lines) | stat: -rw-r--r-- 2,989 bytes parent folder | download | duplicates (5)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
! RUN: bbc -emit-hlfir %s -o - | FileCheck %s
! Test lowering of extension of SOURCE allocation (non deferred length
! of character allocate-object need not to match the SOURCE length, truncation
! and padding are performed instead as in assignments).

subroutine test()
! CHECK-LABEL:   func.func @_QPtest() {
! CHECK:           %[[VAL_4:.*]]:2 = hlfir.declare %{{.*}} {{.*}}Ec_deferred
! CHECK:           %[[VAL_9:.*]]:2 = hlfir.declare %{{.*}} typeparams %[[VAL_6:.*]] {{.*}}Ec_longer
! CHECK:           %[[VAL_14:.*]]:2 = hlfir.declare %{{.*}} typeparams %[[VAL_11:.*]] {{.*}}Ec_shorter
! CHECK:           %[[VAL_17:.*]]:2 = hlfir.declare %{{.*}} typeparams %[[VAL_16:.*]] {{{.*}}Ec_source
  character(5) :: c_source = "hello"
  character(2), allocatable :: c_shorter
  character(:), allocatable :: c_deferred
  character(7), allocatable :: c_longer
! CHECK:           %[[VAL_18:.*]] = arith.constant false
! CHECK:           %[[VAL_22:.*]] = fir.embox %[[VAL_17]]#1 : (!fir.ref<!fir.char<1,5>>) -> !fir.box<!fir.char<1,5>>

! CHECK:           %[[VAL_23:.*]] = fir.convert %[[VAL_14]]#1 : (!fir.ref<!fir.box<!fir.heap<!fir.char<1,2>>>>) -> !fir.ref<!fir.box<none>>
! CHECK:           %[[VAL_24:.*]] = fir.convert %[[VAL_22]] : (!fir.box<!fir.char<1,5>>) -> !fir.box<none>
! CHECK:           %[[VAL_26:.*]] = fir.call @_FortranAAllocatableAllocateSource(%[[VAL_23]], %[[VAL_24]], %[[VAL_18]]

! CHECK:           %[[VAL_27:.*]] = fir.convert %[[VAL_4]]#1 : (!fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>>) -> !fir.ref<!fir.box<none>>
! CHECK:           %[[VAL_28:.*]] = fir.convert %[[VAL_16]] : (index) -> i64
! CHECK:           %[[VAL_29:.*]] = arith.constant 1 : i32
! CHECK:           %[[VAL_30:.*]] = arith.constant 0 : i32
! CHECK:           %[[VAL_31:.*]] = arith.constant 0 : i32
! CHECK:           %[[VAL_32:.*]] = fir.call @_FortranAAllocatableInitCharacterForAllocate(%[[VAL_27]], %[[VAL_28]], %[[VAL_29]], %[[VAL_30]], %[[VAL_31]]
! CHECK:           %[[VAL_33:.*]] = fir.convert %[[VAL_4]]#1 : (!fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>>) -> !fir.ref<!fir.box<none>>
! CHECK:           %[[VAL_34:.*]] = fir.convert %[[VAL_22]] : (!fir.box<!fir.char<1,5>>) -> !fir.box<none>
! CHECK:           %[[VAL_36:.*]] = fir.call @_FortranAAllocatableAllocateSource(%[[VAL_33]], %[[VAL_34]], %[[VAL_18]],

! CHECK-NOT: AllocatableInitCharacterForAllocate
! CHECK:           %[[VAL_37:.*]] = fir.convert %[[VAL_9]]#1 : (!fir.ref<!fir.box<!fir.heap<!fir.char<1,7>>>>) -> !fir.ref<!fir.box<none>>
! CHECK:           %[[VAL_38:.*]] = fir.convert %[[VAL_22]] : (!fir.box<!fir.char<1,5>>) -> !fir.box<none>
! CHECK:           %[[VAL_40:.*]] = fir.call @_FortranAAllocatableAllocateSource(%[[VAL_37]], %[[VAL_38]], %[[VAL_18]],
  allocate(c_shorter, c_deferred, c_longer, source=c_source)

! Expect at runtime:
! ZZheZZ
! ZZhelloZZ
! ZZhello  ZZ
  write(*,"('ZZ',A,'ZZ')") c_shorter
  write(*,"('ZZ',A,'ZZ')") c_deferred
  write(*,"('ZZ',A,'ZZ')") c_longer
end subroutine

  call test()
end