aboutsummaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/optional_absent_5.f90
blob: 42f1a91bcb17fcdfdca2a47941518450dd51d771 (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
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
! { dg-do run }
! PR 82995 - segfault passing on an optional argument;
! this tests the library versions.
module z
  implicit none
contains
  subroutine sum_1 (input, res, mask)
    logical, intent(in), optional :: mask(:,:)
    integer, intent(in) :: input(:,:)
    integer, dimension(:), intent(out) :: res
    res = sum (input, dim=1, mask=mask)
  end subroutine sum_1

  subroutine sum_2 (input, res, mask)
    logical, intent(in), optional :: mask
    integer, intent(in) :: input(:,:)
    integer, dimension(:), intent(out) :: res
    res = sum (input, dim=1, mask=mask)
  end subroutine sum_2

  subroutine maxloc_1 (input, res, mask)
    logical, intent(in), optional :: mask(:,:)
    integer, intent(in) :: input(:,:)
    integer, dimension(:), intent(out) :: res
    res = maxloc (input, dim=1, mask=mask)
  end subroutine maxloc_1

  subroutine minloc_1 (input, res, mask)
    logical, intent(in), optional :: mask
    integer, intent(in) :: input(:,:)
    integer, dimension(:), intent(out) :: res
    res = minloc (input, dim=1, mask=mask)
  end subroutine minloc_1

  subroutine maxloc_2 (input, res, mask)
    logical, intent(in), optional :: mask(:,:)
    integer, intent(in) :: input(:,:)
    integer, dimension(:), intent(out) :: res
    integer :: n
    n = 1
    res = maxloc (input, dim=n, mask=mask)
  end subroutine maxloc_2

  subroutine findloc_1 (input, val, res, mask)
    logical, intent(in), optional :: mask(:,:)
    integer, intent(in) :: input(:,:)
    integer, dimension(:), intent(out) :: res
    integer, intent(in) :: val
    res = findloc(input, val)
  end subroutine findloc_1

  subroutine findloc_2 (input, val, res, mask)
    logical, intent(in), optional :: mask
    integer, intent(in) :: input(:,:)
    integer, dimension(:), intent(out) :: res
    integer, intent(in) :: val
    res = findloc(input, val)
  end subroutine findloc_2

  subroutine findloc_3 (input, val, res, mask)
    logical, intent(in), optional :: mask(:,:)
    integer, intent(in) :: input(:,:)
    integer, dimension(:), intent(out) :: res
    integer, intent(in) :: val
    res = findloc(input, val, dim=1)
  end subroutine findloc_3

  subroutine findloc_4 (input, val, res, mask)
    logical, intent(in), optional :: mask(:,:)
    integer, intent(in) :: input(:,:)
    integer, dimension(:), intent(out) :: res
    integer, intent(in) :: val
    integer :: n = 1
    res = findloc(input, val, dim=n)
  end subroutine findloc_4

  subroutine maxval_1 (input, res, mask)
    logical, intent(in), optional :: mask
    integer, intent(in) :: input(:,:)
    integer, dimension(:), intent(out) :: res
    res = maxval (input, dim=1, mask=mask)
  end subroutine maxval_1

  subroutine maxval_2 (input, res, mask)
    logical, intent(in), optional :: mask
    integer, intent(in) :: input(:,:)
    integer, dimension(:), intent(out) :: res
    integer :: n = 1
    res = maxval (input, dim=n, mask=mask)
  end subroutine maxval_2

  subroutine minval_1 (input, res, mask)
    logical, intent(in), optional :: mask(:,:)
    integer, intent(in) :: input(:,:)
    integer, dimension(:), intent(out) :: res
    res = minval (input, dim=1, mask=mask)
  end subroutine minval_1

  subroutine minval_2 (input, res, mask)
    logical, intent(in), optional :: mask(:,:)
    integer, intent(in) :: input(:,:)
    integer, dimension(:), intent(out) :: res
    integer :: n = 1
    res = minval (input, dim=n, mask=mask)
  end subroutine minval_2

end module z

program main
  use z
  implicit none
  integer :: i2(2,3) = reshape([1,2,4,8,16,32], [2,3])
  integer, dimension(3) :: res3
  integer, dimension(2) :: res2
  call sum_1 (i2, res3)
  if (any (res3 /= [3, 12, 48])) stop 1
  res3 = -2
  call sum_2 (i2, res3)
  if (any (res3 /= [3, 12, 48])) stop 2
  call maxloc_1 (i2, res3)
  if (any (res3 /= 2)) stop 3
  call minloc_1 (i2, res3)
  if (any (res3 /= 1)) stop 4
  call maxloc_2 (i2, res3)
  if (any (res3 /= 2)) stop 5
  call findloc_1 (i2, 4, res2)
  if (any(res2 /= [1,2])) stop 6
  res2 = -1234
  call findloc_2 (i2, 4, res2)
  if (any(res2 /= [1,2])) stop 7
  call findloc_3 (i2, 4, res3)
  if (any(res3 /= [0,1,0])) stop 8
  call findloc_4 (i2, 4, res3)
  if (any(res3 /= [0,1,0])) stop 9
  call maxval_1 (i2, res3)
  if (any (res3 /= [2,8,32])) stop 10
  call minval_1 (i2, res3)
  if (any (res3 /= [1,4,16])) stop 11
  call maxval_2 (i2, res3)
  if (any (res3 /= [2,8,32])) stop 12
  call minval_2 (i2, res3)
  if (any (res3 /= [1,4,16])) stop 13

end program main