PR target/83368
[official-gcc.git] / gcc / testsuite / gfortran.dg / submodule_31.f08
blob72594d05df39c50e19b95649a1c2bac1a655929a
1 ! { dg-do run }
3 ! Test the fix for PR82814 in which an ICE occurred for the submodule allocation.
5 ! Contributed by "Werner Blokbuster"  <werner.blokbuster@gmail.com>
7 module u
9     implicit none
11     interface unique
12         module function uniq_char(input) result(uniq)
13             character(*), intent(in) :: input(:)
14             character(size(input)), allocatable :: uniq(:)
15         end function uniq_char
16     end interface unique
18 contains
20     module function uniq2(input) result(uniq)
21         character(*), intent(in) :: input(:)
22         character(size(input)), allocatable :: uniq(:)
23             allocate(uniq(1))
24             uniq = 'A'
25     end function uniq2
27 end module u
30 submodule (u) z
32     implicit none
34 contains
36     module function uniq_char(input) result(uniq)
37         character(*), intent(in) :: input(:)
38         character(size(input)), allocatable :: uniq(:)
39             allocate(uniq(1)) ! This used to ICE
40             uniq = 'A'
41     end function uniq_char
43 end submodule z
46 program test_uniq
47     use u
48     implicit none
49     character(1), dimension(4) :: chr = ['1','2','1','2']
51     write(*,*) unique(chr)
52     write(*,*) uniq2(chr)
54 end program test_uniq