2 ! { dg-options "-Warray-temporaries" }
3 ! PR 48231 - this used to create an unnecessary temporary.
4 module UnitValue_Module
10 module procedure ProductReal_LV
11 end interface operator(*)
13 interface assignment(=)
14 module procedure Assign_LV_Real
15 end interface assignment(=)
18 elemental
function ProductReal_LV(Multiplier
, Multiplicand
) result(P_R_LV
)
19 real, intent(in
) :: Multiplier
20 type(UnitValue
), intent(in
) :: Multiplicand
21 type(UnitValue
) :: P_R_LV
22 P_R_LV
%Value
= Multiplier
* Multiplicand
%Value
23 end function ProductReal_LV
25 elemental
subroutine Assign_LV_Real(LeftHandSide
, RightHandSide
)
26 real, intent(inout
) :: LeftHandSide
27 type(UnitValue
), intent(in
) :: RightHandSide
28 LeftHandSide
= RightHandSide
%Value
29 end subroutine Assign_LV_Real
30 end module UnitValue_Module
36 real, dimension(:,:), allocatable
:: RealData
40 type(TableForm
), pointer :: Table
43 allocate(Table
%RealData(10,5))
47 Table
%RealData(:,1) = Table
%RealData(:,1) * CENTIMETER
48 end program TestProgram