view gcc/testsuite/gfortran.dg/pr83874.f90 @ 145:1830386684a0

gcc-9.2.0
author anatofuz
date Thu, 13 Feb 2020 11:34:05 +0900
parents 84e7813d76e9
children
line wrap: on
line source

! { dg-do run }
! PR fortran/83874
! There was an ICE while initializing the character arrays
!
! Contributed by Harald Anlauf <anlauf@gmx.de>
!
program charinit
  implicit none
  type t
     character(len=1) :: name
  end type t
  type(t), parameter :: z(2)= [ t ('a'), t ('b') ]
  character(len=1), parameter :: names1(*) = z% name
  character(len=*), parameter :: names2(2) = z% name
  character(len=*), parameter :: names3(*) = z% name
  if (.not. (names1(1) == "a" .and. names1(2) == "b")) STOP 1
  if (.not. (names2(1) == "a" .and. names2(2) == "b")) STOP 2
  if (.not. (names3(1) == "a" .and. names3(2) == "b")) STOP 3
end program charinit