Files
clang-p2996/flang/test/Evaluate/rewrite06.f90
jeanPerier 73cf014223 [flang] harden TypeAndShape for assumed-ranks (#96234)
SIZEOF and C_SIZEOF were broken for assumed-ranks because
`TypeAndShape::MeasureSizeInBytes` behaved as a scalar because the
`TypeAndShape::shape_` member was the same for scalar and assumed-ranks.

The easy fix would have been to add special handling in
`MeasureSizeInBytes` for assumed-ranks using the TypeAndShape
attributes, but I think this solution would leave `TypeAndShape::shape_`
manipulation fragile to future developers. Hence, I went for the
solution that turn shape_ into a `std::optional<Shape>`.
2024-06-24 10:21:04 +02:00

40 lines
1018 B
Fortran

! RUN: %flang_fc1 -fdebug-unparse %s 2>&1 | FileCheck %s
subroutine test_storage_size(n)
interface
function return_char(l)
integer :: l
character(l) :: return_char
end function
end interface
integer n
!CHECK: PRINT *, storage_size(return_char(n))
print*, storage_size(return_char(n))
!CHECK: PRINT *, sizeof(return_char(n))
print*, sizeof(return_char(n))
end subroutine
module pdts
type t(l)
integer, len :: l
character(l) :: c
end type
contains
function return_pdt(n)
type(t(n)) :: return_pdt
end function
subroutine test(k)
! NOTE: flang design for length parametrized derived type
! is to use allocatables for the automatic components. Hence,
! their size is independent from the length parameters and is
! a compile time constant.
!CHECK: PRINT *, 192_4
print *, storage_size(return_pdt(k))
end subroutine
end module
subroutine test_assumed_rank(x)
real :: x(..)
!CHECK: PRINT *, sizeof(x)
print *, sizeof(x)
end subroutine