summaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/unlimited_polymorphic_25.f90
blob: 75fde896bcc138bb3ee96b1e458cc6f273f79ed1 (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
! { dg-do run }
!
! Test contributed by Valery Weber  <valeryweber@hotmail.com>

module mod

  TYPE, PUBLIC :: base_type
  END TYPE base_type

  TYPE, PUBLIC :: dict_entry_type
     CLASS( * ), ALLOCATABLE :: key
     CLASS( * ), ALLOCATABLE :: val
  END TYPE dict_entry_type


contains

  SUBROUTINE dict_put ( this, key, val )
    CLASS(dict_entry_type), INTENT(INOUT)     :: this
    CLASS(base_type), INTENT(IN)             :: key, val
    INTEGER                                  :: istat
    ALLOCATE( this%key, SOURCE=key, STAT=istat )
  end SUBROUTINE dict_put
end module mod

program test
  use mod
  type(dict_entry_type) :: t
  type(base_type) :: a, b
  call dict_put(t, a, b)

  if (.NOT. allocated(t%key)) STOP 1
  select type (x => t%key)
    type is (base_type)
    class default
      STOP 2
  end select
  deallocate(t%key)
end