aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/unlimited_polymorphic_12.f90
blob: c583c6bbf5e1b724dbed58de6db7db03b2c682b0 (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
! { dg-do compile }
!
! PR fortran/58652
!
! Contributed by Vladimir Fuka
!
! The passing of a CLASS(*) to a CLASS(*) was reject before
!
module gen_lists
  type list_node
    class(*),allocatable :: item
    contains
      procedure :: move_alloc => list_move_alloc
  end type

  contains

    subroutine list_move_alloc(self,item)
      class(list_node),intent(inout) :: self
      class(*),intent(inout),allocatable :: item

      call move_alloc(item, self%item)
    end subroutine
end module

module lists
  use gen_lists, only: node => list_node
end module lists


module sexp
  use lists
contains
 subroutine parse(ast)
    class(*), allocatable, intent(out) :: ast
    class(*), allocatable :: expr
    integer :: ierr
    allocate(node::ast)
    select type (ast)
      type is (node)
        call ast%move_alloc(expr)
    end select
  end subroutine
end module