2018-05-13 Paul Thomas <pault@gcc.gnu.org>
[official-gcc.git] / gcc / testsuite / gfortran.dg / assumed_type_9.f90
blobc4a93fe7c657f31232f5253e806e880088196233
1 ! { dg-do run }
3 ! Test the fix for PR85742 in which the descriptors, passed to alsize,
4 ! for 'a' and 'b' had the wrong element length.
6 ! Contributed by Cesar Philippidis <cesar@gcc.gnu.org>
8 program main
9 implicit none
10 integer, allocatable :: a
11 real, pointer :: b
12 integer, allocatable :: am(:,:)
13 real, pointer :: bm(:,:)
15 allocate (a)
16 allocate (b)
17 allocate (am(3,3))
18 allocate (bm(4,4))
20 if (sizeof (a) /= alsize (a)) stop 1
21 if (sizeof (b) /= alsize (b)) stop 2
22 if (sizeof (am) /= alsize (am)) stop 3
23 if (sizeof (bm) /= alsize (bm)) stop 4
25 deallocate (b)
26 deallocate (bm)
27 contains
28 function alsize (a)
29 integer alsize
30 type (*), dimension (..), contiguous :: a
31 alsize = sizeof(a)
32 end function
33 end program main