OpenCores
URL https://opencores.org/ocsvn/openrisc/openrisc/trunk

Subversion Repositories openrisc

[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [used_types_16.f90] - Blame information for rev 704

Go to most recent revision | Details | Compare with Previous | View Log

Line No. Rev Author Line
1 694 jeremybenn
! { dg-do compile }
2
! Tests the fix for PR31550 in which pointers to derived type components
3
! were being TREE-SSA declared in the wrong order and so in the incorrect
4
! context.
5
!
6
! Contributed by Daniel Franke 
7
!
8
MODULE class_dummy_atom_types
9
TYPE :: dummy_atom_list
10
  TYPE(dummy_atom), DIMENSION(:), POINTER :: table
11
  INTEGER                                 :: nused
12
END TYPE
13
 
14
TYPE :: dummy_atom
15
  TYPE(dummy_atom_private), POINTER :: p
16
END TYPE
17
 
18
TYPE :: dummy_atom_private
19
  TYPE(dummy_atom_list)       :: neighbours
20
END TYPE
21
END MODULE
22
 
23
MODULE class_dummy_atom_list
24
USE class_dummy_atom_types, ONLY: dummy_atom_list
25
 
26
INTERFACE
27
  SUBROUTINE dummy_atom_list_init_copy(this, other)
28
    USE class_dummy_atom_types, ONLY: dummy_atom_list
29
    TYPE(dummy_atom_list), INTENT(out) :: this
30
    TYPE(dummy_atom_list), INTENT(in)  :: other
31
  END SUBROUTINE
32
END INTERFACE
33
 
34
INTERFACE
35
  SUBROUTINE dummy_atom_list_merge(this, other)
36
    USE class_dummy_atom_types, ONLY: dummy_atom_list
37
    TYPE(dummy_atom_list), INTENT(inout) :: this
38
    TYPE(dummy_atom_list), INTENT(in)    :: other
39
  END SUBROUTINE
40
END INTERFACE
41
END MODULE
42
 
43
SUBROUTINE dummy_atom_list_init_copy(this, other)
44
  USE class_dummy_atom_list, ONLY: dummy_atom_list, dummy_atom_list_merge
45
 
46
  TYPE(dummy_atom_list), INTENT(out) :: this
47
  TYPE(dummy_atom_list), INTENT(in)  :: other
48
 
49
  this%table(1:this%nused) = other%table(1:other%nused)
50
END SUBROUTINE
51
! { dg-final { cleanup-modules "class_dummy_atom_types class_dummy_atom_list" } }

powered by: WebSVN 2.1.0

© copyright 1999-2024 OpenCores.org, equivalent to Oliscience, all rights reserved. OpenCores®, registered trademark.