OSDN Git Service

2011-08-18 Tobias Burnus <burnus@net-b.de>
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / class_9.f03
1 ! { dg-do run }
2 ! Test the fix for PR41706, in which arguments of class methods that
3 ! were themselves class methods did not work.
4 !
5 ! Contributed by Janus Weil <janus@gcc.gnu.org>
6 !
7 module m
8 type :: t
9   real :: v = 1.5
10 contains
11   procedure, nopass :: a
12   procedure, nopass :: b
13   procedure, pass :: c
14   procedure, nopass :: d
15 end type
16
17 contains
18
19   real function a (x)
20     real :: x
21     a = 2.*x
22   end function
23
24   real function b (x)
25     real :: x
26     b = 3.*x
27   end function
28
29   real function c (x)
30     class (t) :: x
31     c = 4.*x%v
32   end function
33
34   subroutine d (x)
35     real :: x
36     if (abs(x-3.0)>1E-3) call abort()
37   end subroutine
38
39   subroutine s (x)
40     class(t) :: x
41     real :: r
42     r = x%a (1.1)       ! worked
43     if (r .ne. a (1.1)) call abort
44
45     r = x%a (b (1.2))   ! worked
46     if (r .ne. a(b (1.2))) call abort
47
48     r = b ( x%a (1.3))  ! worked
49     if (r .ne. b(a (1.3))) call abort
50
51     r = x%a(x%b (1.4))   ! failed
52     if (r .ne. a(b (1.4))) call abort
53
54     r = x%a(x%c ())   ! failed
55     if (r .ne. a(c (x))) call abort
56
57     call x%d (x%a(1.5))  ! failed
58
59   end subroutine
60
61 end
62
63   use m
64   class(t),allocatable :: x
65   allocate(x)
66   call s (x)
67 end
68 ! { dg-final { cleanup-modules "m" } }