aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/allocate_with_typespec_4.f90
blob: cc09697f385997410b944e3d77b8fe3b95a443a1 (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
! { dg-do compile }
! { dg-options "-w" }
subroutine not_an_f03_intrinsic

   implicit none

   byte, allocatable :: x, y(:)
   real*8, allocatable :: x8, y8(:)
   double complex :: z

   type real_type
      integer mytype
   end type real_type

   type(real_type), allocatable :: b, c(:)

   allocate(byte :: x)            ! { dg-error "Error in type-spec at" }
   allocate(byte :: y(1))         ! { dg-error "Error in type-spec at" }

   allocate(real*8 :: x)          ! { dg-error "Invalid type-spec at" }
   allocate(real*8 :: y(1))       ! { dg-error "Invalid type-spec at" }
   allocate(real*4 :: x8)         ! { dg-error "Invalid type-spec at" }
   allocate(real*4 :: y8(1))      ! { dg-error "Invalid type-spec at" }
   allocate(double complex :: d1) ! { dg-error "neither a data pointer nor an allocatable" }
   allocate(real_type :: b)
   allocate(real_type :: c(1))

end subroutine not_an_f03_intrinsic