OSDN Git Service

2010-02-10 Joost VandeVondele <jv244@cam.ac.uk>
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / c_by_val_2.f90
1 ! { dg-do compile }
2 ! { dg-options "-w" }
3
4 program c_by_val_2
5   external bar
6   real (4) :: bar, ar(2) = (/1.0,2.0/)
7   type     :: mytype
8     integer  :: i
9   end type mytype
10   type(mytype)  :: z
11   character(8)  :: c = "blooey"
12   real :: stmfun, x
13   stmfun(x)=x**2
14
15   x = 5
16   print *, stmfun(%VAL(x))   ! { dg-error "not allowed in this context" }
17   print *, sin (%VAL(2.0))   ! { dg-error "not allowed in this context" }
18   print *, foo (%VAL(1.0))   ! { dg-error "not allowed in this context" }
19   call  foobar (%VAL(0.5))   ! { dg-error "not allowed in this context" }
20   print *, bar (%VAL(z))     ! { dg-error "not of numeric type" }
21   print *, bar (%VAL(c))     ! { dg-error "not of numeric type" }
22   print *, bar (%VAL(ar))    ! { dg-error "cannot be an array" }
23   print *, bar (%VAL(0.0))
24 contains
25   function foo (a)
26     real(4) :: a, foo
27     foo = cos (a)
28   end function foo
29   subroutine foobar (a)
30     real(4) :: a
31     print *, a
32   end subroutine foobar
33 end program c_by_val_2
34