aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/dependency_37.f90
blob: 12900c74f76f9407267702a258d938bb3577063a (plain)
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
! { dg-do compile }
! { dg-options "-Warray-temporaries" }
! PR 48231 - this used to create an unnecessary temporary.
module UnitValue_Module
  type :: UnitValue
    real          :: Value = 1.0
  end type

  interface operator(*)
    module procedure ProductReal_LV
  end interface operator(*)

  interface assignment(=)
    module procedure Assign_LV_Real
  end interface assignment(=)
contains

  elemental function ProductReal_LV(Multiplier, Multiplicand) result(P_R_LV)
    real, intent(in)            :: Multiplier
    type(UnitValue), intent(in) :: Multiplicand
    type(UnitValue)             :: P_R_LV
    P_R_LV%Value = Multiplier * Multiplicand%Value
  end function ProductReal_LV

  elemental subroutine Assign_LV_Real(LeftHandSide, RightHandSide)
    real, intent(inout)         :: LeftHandSide
    type(UnitValue), intent(in) :: RightHandSide
    LeftHandSide = RightHandSide%Value
  end subroutine Assign_LV_Real
end module UnitValue_Module

program TestProgram
  use UnitValue_Module

  type :: TableForm
    real, dimension(:,:), allocatable :: RealData
  end type TableForm

  REAL :: CENTIMETER
  type(TableForm), pointer :: Table

  allocate(Table)
  allocate(Table%RealData(10,5))

  CENTIMETER = 42
  Table%RealData = 1
  Table%RealData(:,1) = Table%RealData(:,1) * CENTIMETER
end program TestProgram