2 ! Test the fix for PR42736, in which an excessively rigorous dependency
3 ! checking for the assignment generated an unnecessary temporary, whose
4 ! rank was wrong. When accessed by the scalarizer, a segfault ensued.
6 ! Contributed by Tobias Burnus <burnus@gcc.gnu.org>
7 ! Reported by Armelius Cameron <armeliusc@gmail.com>
9 module UnitValue_Module
18 type, public
:: UnitValue
26 module procedure ProductReal_LV
27 end interface operator(*)
29 interface assignment(=)
30 module procedure Assign_LV_Real
31 end interface assignment(=)
35 elemental
function ProductReal_LV(Multiplier
, Multiplicand
) result(P_R_LV
)
39 type(UnitValue
), intent(in
) :: &
44 P_R_LV
%Value
= Multiplier
* Multiplicand
%Value
45 P_R_LV
%Label
= Multiplicand
%Label
47 end function ProductReal_LV
50 elemental
subroutine Assign_LV_Real(LeftHandSide
, RightHandSide
)
52 real, intent(inout
) :: &
54 type(UnitValue
), intent(in
) :: &
57 LeftHandSide
= RightHandSide
%Value
59 end subroutine Assign_LV_Real
61 end module UnitValue_Module
70 real, dimension(:,:), allocatable
:: &
77 type(TableForm
), pointer :: &
81 allocate(Table
%RealData(10,5))
85 Table
%RealData(:,1) = Table
%RealData(:,1) * CENTIMETER
86 Table
%RealData(:,2) = Table
%RealData(:,2) * CENTIMETER
87 Table
%RealData(:,3) = Table
%RealData(:,3) * CENTIMETER
88 Table
%RealData(:,5) = Table
%RealData(:,5) * CENTIMETER
90 ! print *, Table%RealData
91 if (any (abs(Table
%RealData(:,4) - 1) > epsilon(1.0))) call abort ()
92 if (any (abs(Table
%RealData(:,[1,2,3,5]) - 42) > epsilon(1.0))) call abort ()
93 end program TestProgram
95 ! { dg-final { cleanup-modules "UnitValue_Module" } }