OSDN Git Service

2010-04-24 Kai Tietz <kai.tietz@onevision.com>
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / interface_assignment_1.f90
1 ! { dg-do run }
2 ! Checks the fix for PR31205, in which temporaries were not
3 ! written for the interface assignment and the parentheses below.
4 !
5 ! Contributed by Joost VandeVondele <jv244@cam.ac.uk>
6 !
7 MODULE TT
8  TYPE data_type
9    INTEGER :: I=2
10  END TYPE data_type
11  INTERFACE ASSIGNMENT (=)
12    MODULE PROCEDURE set
13  END INTERFACE
14 CONTAINS
15   PURE SUBROUTINE set(x1,x2)
16     TYPE(data_type), INTENT(IN) :: x2
17     TYPE(data_type), INTENT(OUT) :: x1
18     CALL S1(x1,x2)
19   END SUBROUTINE
20   PURE SUBROUTINE S1(x1,x2)
21     TYPE(data_type), INTENT(IN) :: x2
22     TYPE(data_type), INTENT(OUT) :: x1
23     x1%i=x2%i
24   END SUBROUTINE
25 END MODULE
26
27 USE TT
28 TYPE(data_type) :: D,E
29
30 D%I=4
31 D=D
32
33 E%I=4
34 CALL set(E,(E))
35
36 IF (D%I.NE.4) call abort ()
37 IF (4.NE.E%I) call abort ()
38 END
39 ! { dg-final { cleanup-modules "TT" } }