aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/c_by_val_5.f90
blob: 3a8bc3bf750c90aa1200eb0cd62c9cb982be99f9 (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
! { dg-do run }
! Overwrite -pedantic setting:
! { dg-options "-Wall" }
!
! Tests the fix for PR31668, in which %VAL was rejected for
! module and internal procedures.
! 

subroutine bmp_write(nx)
  implicit none
  integer, value :: nx
  if(nx /= 10) call abort()
  nx = 11
  if(nx /= 11) call abort()
end subroutine bmp_write

module x
 implicit none
 ! The following interface does in principle
 ! not match the procedure (missing VALUE attribute)
 ! However, this occures in real-world code calling
 ! C routines where an interface is better than
 ! "external" only.
 interface
   subroutine bmp_write(nx)
     integer, value :: nx
   end subroutine bmp_write
 end interface
contains
   SUBROUTINE Grid2BMP(NX)
     INTEGER, INTENT(IN) :: NX
     if(nx /= 10) call abort()
     call bmp_write(%val(nx))
     if(nx /= 10) call abort()
   END SUBROUTINE Grid2BMP
END module x

! The following test is possible and
! accepted by other compilers, but
! does not make much sense.
! Either one uses VALUE then %VAL is
! not needed or the function will give
! wrong results.
!
!subroutine test()
!    implicit none
!    integer :: n
!    n = 5
!    if(n /= 5) call abort()
!    call test2(%VAL(n))
!    if(n /= 5) call abort()
!  contains
!    subroutine test2(a)
!      integer, value :: a
!      if(a /= 5) call abort()
!      a = 2
!      if(a /= 2) call abort()
!    end subroutine test2
!end subroutine test

program main
  use x
  implicit none
!  external test
  call Grid2BMP(10)
!  call test()
end program main