OSDN Git Service

2011-09-26 Janus Weil <janus@gcc.gnu.org>
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / value_4.f90
1 ! { dg-do run }
2 ! { dg-additional-sources value_4.c }
3 ! { dg-options "-ff2c -w -O0" }
4 !
5 ! Tests the functionality of the patch for PR29642, which requested the
6 ! implementation of the F2003 VALUE attribute for gfortran, by calling
7 ! external C functions by value and by reference.  This is effectively
8 ! identical to c_by_val_1.f, which does the same for %VAL.
9 !
10 ! Contributed by Paul Thomas  <pault@gcc.gnu.org> 
11 !
12 module global
13   interface delta
14     module procedure deltai, deltar, deltac
15   end interface delta
16   real(4) :: epsi = epsilon (1.0_4)
17 contains
18   function deltai (a, b) result (c)
19     integer(4) :: a, b
20     logical :: c
21     c = (a /= b)
22   end function deltai
23
24   function deltar (a, b) result (c)
25     real(4) :: a, b
26     logical :: c
27     c = (abs (a-b) > epsi)
28   end function deltar
29
30   function deltac (a, b) result (c)
31     complex(4) :: a, b
32     logical :: c
33     c = ((abs (real (a-b)) > epsi).or.(abs (aimag (a-b)) > epsi))
34   end function deltac
35 end module global  
36
37 program value_4
38   use global
39   interface
40     function f_to_f (x, y)
41       real(4), pointer :: f_to_f
42       real(4) :: x, y
43       value :: x
44     end function f_to_f
45   end interface
46
47   interface
48     function i_to_i (x, y)
49       integer(4), pointer :: i_to_i
50       integer(4) :: x, y
51       value :: x
52     end function i_to_i
53   end interface
54
55   interface
56     complex(4) function c_to_c (x, y)
57       complex(4) :: x, y
58       value :: x
59     end function c_to_c
60   end interface
61
62   real(4)       a, b, c
63   integer(4)    i, j, k
64   complex(4)    u, v, w
65
66   a = 42.0
67   b = 0.0
68   c = a
69   b = f_to_f (a, c)
70   if (delta ((2.0 * a), b)) call abort ()
71
72   i = 99
73   j = 0
74   k = i
75   j = i_to_i (i, k)
76   if (delta ((3_4 * i), j)) call abort ()
77
78   u = (-1.0, 2.0)
79   v = (1.0, -2.0)
80   w = u
81   v = c_to_c (u, w)
82   if (delta ((4.0 * u), v)) call abort ()
83 end program value_4
84 ! { dg-final { cleanup-modules "global" } }