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

Subversion Repositories openrisc

[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.fortran-torture/] [compile/] [pr33276.f90] - Rev 705

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

! PR fortran/33276
! this used to crash due to an uninitialized variable in expand_iterator.

module foo
   type buffer_type
   integer(kind=kind(1)) :: item_end
   character(256) :: string
   end type
   type textfile_type
   type(buffer_type) :: buffer
   end type
contains
   function rest_of_line(self) result(res)
    type(textfile_type) :: self
     intent(inout) :: self
     character(128) :: res
     res = self%buffer%string(self%buffer%item_end+1: )
   end function

   subroutine read_intvec_ptr(v)
      integer(kind=kind(1)), dimension(:), pointer :: v
      integer(kind=kind(1)) :: dim,f,l,i

     if (dim>0) then; v = (/ (i, i=f,l)    /)
     end if
   end subroutine
end

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.