view gcc/testsuite/gfortran.dg/derived_constructor_char_3.f90 @ 158:494b0b89df80 default tip

...
author Shinji KONO <kono@ie.u-ryukyu.ac.jp>
date Mon, 25 May 2020 18:13:55 +0900
parents 84e7813d76e9
children
line wrap: on
line source

! { dg-do compile }
!
! PR fortran/51966
!
! Contributed by Peter Wind
!

  type :: Deriv
    character(len=10) :: name
  end type
  character(len=8), dimension(2), parameter :: &
       DEF_ECOSYSTEMS = (/ "Gridxxxx", "StringYY" /)

  type(Deriv), save :: DepEcoSystem = Deriv(DEF_ECOSYSTEMS(1))

  if (DepEcoSystem%name /= "Gridxxxx" &
      .or. DepEcoSystem%name(9:9) /= ' ' &
      .or. DepEcoSystem%name(10:10) /= ' ') STOP 1
  DepEcoSystem%name = 'ABCDEFGHIJ'
  call Init_EcoSystems()
  if (DepEcoSystem%name /= "StringYY" &
      .or. DepEcoSystem%name(9:9) /= ' ' &
      .or. DepEcoSystem%name(10:10) /= ' ') STOP 2

contains
  subroutine Init_EcoSystems()
    integer :: i =2
    DepEcoSystem = Deriv(DEF_ECOSYSTEMS(i))
  end subroutine Init_EcoSystems
end