Dear Andre,
I have bootstrapped and regtested successfully r221474 with your set of
patches. I am seeing some more fixes, but also some new ICEs and segfaults
(some of them being regressions):
(1) The patches fix pr63230.
(2) The test in pr51550 compiles, but segfaults at run time.
(3) The original test in pr64787 segfaults at run time.
(4) I get a new ICE for the following test (from pr51946):
module integrable_model_module
implicit none
type, abstract, public :: integrable_model
contains
procedure(default_constructor), deferred :: empty_instance
end type
abstract interface
function default_constructor(this) result(blank_slate)
import :: integrable_model
class(integrable_model), intent(in) :: this
class(integrable_model), allocatable :: blank_slate
end function
end interface
contains
subroutine integrate(this)
class(integrable_model), intent(inout) :: this
class(integrable_model), allocatable :: residual
allocate(residual, source=this%empty_instance())
end subroutine
end module integrable_model_module
pr51946.f90:23:0:
allocate(residual, source=this%empty_instance())
1
internal compiler error: in conv_function_val, at fortran/trans-expr.c:3462
(5) The tests in pr51208 comment 1 segfault at run time (IMO they are
invalid: SUM of unallocated arrays).
(6) The following variant of pr64125 now compiles (duplicate of pr63230)
module test
type t_string
private
character(len=:), allocatable :: chars
end type t_string
contains
pure subroutine string_assign_from_array( left, right )
! The target string
type(t_string), intent(out) :: left
! The source string
character, dimension(:), intent(in) :: right
! Copy memory
allocate( character(len=size(right)) :: left%chars )
left%chars = transfer( right, left%chars )
end subroutine string_assign_from_array
end module test
(7) The following variant of pr54070 gives an ICE (it compiles without the
patches, but segfaults at run time)
interface
function f(a)
character(len=*) :: a
character(len=:),allocatable :: f(:)
end function
end interface
character(len=10) :: tmp(2)
tmp = f('abc')
!print *, f('abc')
end
function f(a)
character(len=*) :: a
character(len=:),allocatable :: f(:)
allocate(f(2),source=a)
print *, a
! f = a
! print *, f
end function
pr54070_1_db_1.f90:14:0:
allocate(f(2),source=a)
1
internal compiler error: Segmentation fault: 11
pr54070_1_db_1.f90:14:0: internal compiler error: Abort trap: 6
(8) The following variant of pr55901 now compiles, but segfault at run time
class (*), allocatable :: a
type :: mytype
integer :: i
class(*), allocatable :: c
end type
type(mytype) :: b
allocate (a, source = "hello")
select type (a)
type is (character(*))
print *, a, len (a)
end select
if (allocated (a)) deallocate (a)
allocate (a, source = "goodbye")
select type (a)
type is (character(*))
print *, a, len (a)
end select
call foo (b%c, a)
select type (z => b%c)
type is (character(*))
print *, z, len (z)
z = "it is nice to meet you"
end select
select type (z => b%c)
type is (character(*))
print *, z, len (z)
end select
if (allocated (b%c)) deallocate (b%c)
allocate (b%c, source = "goodbye")
select type (z => b%c)
type is (character(*))
print *, z, len (z)
end select
if (allocated (b%c)) deallocate (b%c)
call foo (b%c, 42)
select type (z => b%c)
type is (INTEGER)
print *, z
end select
contains
subroutine foo (dest, src)
class (*), allocatable :: dest
class (*) :: src
allocate (dest, source = src)
end subroutine
end
I may have missed some other failure/success in my tests, but I think the
above is enough for now.
Thanks for working on this problem,
Dominique