aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/elemental_subroutine_1.f90
blob: a19a7807c16bb1f3093ab8ff9c3c450c55de95c0 (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
49
50
51
52
53
54
55
56
57
58
59
60
! { dg-do run }
! Test the fix for pr22146, where and elemental subroutine with
! array actual arguments would cause an ICE in gfc_conv_function_call.
! The module is the original test case and the rest is a basic
! functional test of the scalarization of the function call.
!
! Contributed by Erik Edelmann  <erik.edelmann@iki.fi>
!             and Paul Thomas   <pault@gcc.gnu.org>

  module pr22146

contains

    elemental subroutine foo(a)
      integer, intent(out) :: a
      a = 0
    end subroutine foo

    subroutine bar()
      integer :: a(10)
      call foo(a)
    end subroutine bar

end module pr22146

  use pr22146
  real, dimension (2)  :: x, y
  real :: u, v
  x = (/1.0, 2.0/)
  u = 42.0

  call bar ()

! Check the various combinations of scalar and array.
  call foobar (x, y)
  if (any(y.ne.-x)) call abort ()

  call foobar (u, y)
  if (any(y.ne.-42.0)) call abort ()

  call foobar (u, v)
  if (v.ne.-42.0) call abort ()

  v = 2.0
  call foobar (v, x)
  if (any(x /= -2.0)) call abort ()

! Test an expression in the INTENT(IN) argument
  x = (/1.0, 2.0/)
  call foobar (cos (x) + u, y)
  if (any(abs (y + cos (x) + u) .gt. 4.0e-6)) call abort ()

contains

  elemental subroutine foobar (a, b)
    real, intent(IN) :: a
    real, intent(out) :: b
    b = -a
  end subroutine foobar
end