OpenCores
URL https://opencores.org/ocsvn/openrisc_me/openrisc_me/trunk

Subversion Repositories openrisc_me

[/] [openrisc/] [trunk/] [gnu-src/] [gcc-4.5.1/] [gcc/] [testsuite/] [gfortran.dg/] [array_constructor_type_6.f03] - Rev 377

Go to most recent revision | Compare with Previous | Blame | View Log

! { dg-do run }
! { dg-options "-fbounds-check" }
!
! PR fortran/27997
!
! Array constructor with typespec.
!
program test
  character(15) :: a(3)
  character(10), volatile :: b(3)
  b(1) = 'Takata'
  b(2) = 'Tanaka'
  b(3) = 'Hayashi'

  a =  (/ character(len=7) :: trim(b(1)), trim(b(2)), trim(b(3)) /)
  if (a(1) /= 'Takata' .or. a(2) /= 'Tanaka' .or. a(3) /= 'Hayashi') then
    call abort ()
  end if

  a =  (/ character(len=2) :: trim(b(1)), trim(b(2)), trim(b(3)) /)
  if (a(1) /= 'Ta' .or. a(2) /= 'Ta' .or. a(3) /= 'Ha') then
    call abort ()
  end if

  a =  (/ character(len=8) :: trim(b(1)), trim(b(2)), trim(b(3)) /)
  if (a(1) /= 'Takata' .or. a(2) /= 'Tanaka' .or. a(3) /= 'Hayashi') then
    call abort ()
  end if

end program test

Go to most recent revision | Compare with Previous | Blame | View Log

powered by: WebSVN 2.1.0

© copyright 1999-2024 OpenCores.org, equivalent to Oliscience, all rights reserved. OpenCores®, registered trademark.