1178476Sjb! { dg-do compile }
2178476Sjb! Test the patch for PR30084 in which the reference to SIZE
3178476Sjb! in function diag caused a segfault in module.c.
4178476Sjb!
5178476Sjb! Contributed by Troban Trumsko <trumsko@yahoo.com>
6178476Sjb! and reduced by Steve Kargl <kargl@gcc.gnu.org>
7178476Sjb!
8178476Sjbmodule tao_random_numbers
9178476Sjb  integer, dimension(10) :: s_buffer
10178476Sjb  integer :: s_last = size (s_buffer)
11178476Sjbend module tao_random_numbers
12178476Sjb
13178476Sjbmodule linalg
14178476Sjb  contains
15178476Sjb  function diag (a) result (d)
16178476Sjb    real, dimension(:,:), intent(in) :: a
17178476Sjb    real, dimension(min(size(a,dim=1),size(a,dim=2))) :: d
18178476Sjb    integer :: i
19178476Sjb    do i = 1, min(size(a, dim = 1), size(a, dim = 2))
20178476Sjb       d(i) = a(i,i)
21178476Sjb    end do
22178476Sjb  end function diag
23178476Sjbend module linalg
24178476Sjb
25178476Sjbmodule vamp_rest
26178476Sjb  use tao_random_numbers
27178476Sjb  use linalg
28178476Sjbend module vamp_rest
29178476Sjb
30178476Sjb  use vamp_rest
31178476Sjb  real :: x(2, 2) = reshape ([1.,2.,3.,4.], [2,2])
32178476Sjb  print *, s_last
33178476Sjb  print *, diag (x)
34178476Sjbend
35178476Sjb