public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/103394] New: Bad object code for structure constructor
@ 2021-11-23 19:30 neil.n.carlson at gmail dot com
  2021-11-23 23:39 ` [Bug fortran/103394] " neil.n.carlson at gmail dot com
  0 siblings, 1 reply; 2+ messages in thread
From: neil.n.carlson at gmail dot com @ 2021-11-23 19:30 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103394

            Bug ID: 103394
           Summary: Bad object code for structure constructor
           Product: gcc
           Version: 12.0
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
          Assignee: unassigned at gcc dot gnu.org
          Reporter: neil.n.carlson at gmail dot com
  Target Milestone: ---

Bad object code is being generated for the structure constructor expression in
the example below. This occurs for the current 12.0 trunk and any of the
earlier 9.x, 10.x and 11.x versions I've tried. It seems that things go wrong
with the expression foo_vector_func(this) when both the foo_vector_func type is
an extension and the variable this is also polymorphic.

module foo_type

  type :: foo
  contains
    procedure :: alloc_foo_vector_func
  end type

  type, abstract :: vector_func
  end type

  type, extends(vector_func) :: foo_vector_func
    type(foo), pointer :: ptr
  end type

contains

  subroutine alloc_foo_vector_func(this, vf)
    class(foo), intent(in), target :: this
    class(vector_func), allocatable, intent(out) :: vf
    allocate(vf, source=foo_vector_func(this))  ! DOESN'T WORK CORRECTLY
    !vf = foo_vector_func(this)  ! DOESN'T WORK EITHER
  end subroutine

end module

program main
  use foo_type
  type(foo), target :: x
  class(vector_func), allocatable :: vf
  call x%alloc_foo_vector_func(vf)
  select type (vf)
  type is (foo_vector_func)
    if (.not.associated(vf%ptr, x)) stop 1  ! SHOULD NOT EXIT HERE
  end select
end program

^ permalink raw reply	[flat|nested] 2+ messages in thread

* [Bug fortran/103394] Bad object code for structure constructor
  2021-11-23 19:30 [Bug fortran/103394] New: Bad object code for structure constructor neil.n.carlson at gmail dot com
@ 2021-11-23 23:39 ` neil.n.carlson at gmail dot com
  0 siblings, 0 replies; 2+ messages in thread
From: neil.n.carlson at gmail dot com @ 2021-11-23 23:39 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103394

--- Comment #1 from Neil Carlson <neil.n.carlson at gmail dot com> ---
I've experimented some more and have reduced things further to this example.
I'm not positive it captures everything that is going wrong in the original.

program example

type :: foo
end type

type :: bar
  type(foo), pointer :: fptr
end type

class(foo), pointer :: f
allocate(foo :: f)

call sub(bar(f))

contains

  subroutine sub(b)
    type(bar), intent(in) :: b
    if (.not.associated(b%fptr, f)) stop 1
  end subroutine

end program

The example works correctly if "class(foo), pointer :: f" is replaced by
"type(foo), pointer :: f", so it seems pretty clear that intrinsic structure
constructor is not properly making the assignment "bar%fptr => f".

^ permalink raw reply	[flat|nested] 2+ messages in thread

end of thread, other threads:[~2021-11-23 23:39 UTC | newest]

Thread overview: 2+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2021-11-23 19:30 [Bug fortran/103394] New: Bad object code for structure constructor neil.n.carlson at gmail dot com
2021-11-23 23:39 ` [Bug fortran/103394] " neil.n.carlson at gmail dot com

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for read-only IMAP folder(s) and NNTP newsgroup(s).