public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/66409] New: Reporting ambiguous interface when overloading assignment with polymorphic array
@ 2015-06-03 20:06 cmacmackin at gmail dot com
  2015-09-13 15:14 ` [Bug fortran/66409] " dominiq at lps dot ens.fr
                   ` (11 more replies)
  0 siblings, 12 replies; 13+ messages in thread
From: cmacmackin at gmail dot com @ 2015-06-03 20:06 UTC (permalink / raw)
  To: gcc-bugs

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

            Bug ID: 66409
           Summary: Reporting ambiguous interface when overloading
                    assignment with polymorphic array
           Product: gcc
           Version: 4.9.2
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
          Assignee: unassigned at gcc dot gnu.org
          Reporter: cmacmackin at gmail dot com
  Target Milestone: ---

I have come across what I believe to be a bug (or possibly a misunderstanding
of the standard on one of our counts) in gfortran. I'm trying to overload the
assignment operator with two custom procedures:

    module container_mod

        interface assignment(=)
            module procedure assign_to_variable
            module procedure assign_to_variable_1d
        end interface

    contains

        subroutine assign_to_variable (retval,input)
            class(*), intent(inout)         ::  retval
            real, intent(in)    ::  input

            return
        end subroutine assign_to_variable

        subroutine assign_to_variable_1d (retval_1d,input)
            class(*), dimension(:), intent(inout)   ::  retval_1d
            real, intent(in)            ::  input

            return
        end subroutine assign_to_variable_1d

    end module container_mod

(In the real program where I do this, the input variable is a derived type.)
However, I am getting the compile-time error 

    gfortran -Wall -c "dbg.f90"
    dbg.f90:5.46:
            module procedure assign_to_variable_1d
                                                  1
    Error: Ambiguous interfaces 'assign_to_variable_1d' and
'assign_to_variable' in intrinsic assignment operator at (1)

I've found that ifort 12.1.7.367 and pgfortran 8.0-6 both compile this just
fine. I've also found that, if I change the interface from assignment to just a
normal generic interface, it compiles properly. Finally, if I change the
unlimited polymorphic variables to anything else (a built-in variable type, a
derived type, or a non-unlimited polymorphic variable) it compiled without
problems.

It's also worth noting that, if I try to compile this with only the scalar
interface, gfortran complains when I try to use that to assign to an array. So
obviously the interface is not ambiguous when it comes to actually performing
the assignment.

I hope all of that's clear. I'll be happy to answer any questions or
clarifications.


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

* [Bug fortran/66409] Reporting ambiguous interface when overloading assignment with polymorphic array
  2015-06-03 20:06 [Bug fortran/66409] New: Reporting ambiguous interface when overloading assignment with polymorphic array cmacmackin at gmail dot com
@ 2015-09-13 15:14 ` dominiq at lps dot ens.fr
  2022-10-07 13:55 ` jeff.science at gmail dot com
                   ` (10 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: dominiq at lps dot ens.fr @ 2015-09-13 15:14 UTC (permalink / raw)
  To: gcc-bugs

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

Dominique d'Humieres <dominiq at lps dot ens.fr> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |NEW
   Last reconfirmed|                            |2015-09-13
     Ever confirmed|0                           |1

--- Comment #1 from Dominique d'Humieres <dominiq at lps dot ens.fr> ---
Confirmed from 4.8 up to trunk (6.0).


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

* [Bug fortran/66409] Reporting ambiguous interface when overloading assignment with polymorphic array
  2015-06-03 20:06 [Bug fortran/66409] New: Reporting ambiguous interface when overloading assignment with polymorphic array cmacmackin at gmail dot com
  2015-09-13 15:14 ` [Bug fortran/66409] " dominiq at lps dot ens.fr
@ 2022-10-07 13:55 ` jeff.science at gmail dot com
  2022-10-07 18:30 ` kargl at gcc dot gnu.org
                   ` (9 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: jeff.science at gmail dot com @ 2022-10-07 13:55 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #2 from Jeff Hammond <jeff.science at gmail dot com> ---
Is this ever going to be fixed?  I observe that a similar MCVE (below) is
compiled without complaint by Intel, Cray and NAG Fortran, so it's almost
certainly a lack of support for the standard in GCC.

As best I can, it is impossible to overload an interface when one of the
specific interfaces involves type(*), dimension(..), which makes it impossible
for me to implement MPI-3 F08 support.

My MCVE:

module f
    implicit none

    interface test
        module procedure test_f08
        module procedure test_f08ts
    end interface test

    contains

        subroutine test_f08(buf)
            integer :: buf
        end subroutine test_f08

        subroutine test_f08ts(buffer)
            type(*), dimension(..), intent(inout) :: buffer
        end subroutine test_f08ts

end module f

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

* [Bug fortran/66409] Reporting ambiguous interface when overloading assignment with polymorphic array
  2015-06-03 20:06 [Bug fortran/66409] New: Reporting ambiguous interface when overloading assignment with polymorphic array cmacmackin at gmail dot com
  2015-09-13 15:14 ` [Bug fortran/66409] " dominiq at lps dot ens.fr
  2022-10-07 13:55 ` jeff.science at gmail dot com
@ 2022-10-07 18:30 ` kargl at gcc dot gnu.org
  2022-10-07 19:15 ` anlauf at gcc dot gnu.org
                   ` (8 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: kargl at gcc dot gnu.org @ 2022-10-07 18:30 UTC (permalink / raw)
  To: gcc-bugs

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

kargl at gcc dot gnu.org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |kargl at gcc dot gnu.org

--- Comment #3 from kargl at gcc dot gnu.org ---
(In reply to Jeff Hammond from comment #2)
> Is this ever going to be fixed?  I observe that a similar MCVE (below) is
> compiled without complaint by Intel, Cray and NAG Fortran, so it's almost
> certainly a lack of support for the standard in GCC.
> 
> As best I can, it is impossible to overload an interface when one of the
> specific interfaces involves type(*), dimension(..), which makes it
> impossible for me to implement MPI-3 F08 support.
> 
> My MCVE:
> 
> module f
>     implicit none
> 
>     interface test
>         module procedure test_f08
>         module procedure test_f08ts
>     end interface test
> 
>     contains
> 
>         subroutine test_f08(buf)
>             integer :: buf
>         end subroutine test_f08
> 
>         subroutine test_f08ts(buffer)
>             type(*), dimension(..), intent(inout) :: buffer
>         end subroutine test_f08ts
> 
> end module f

program foo
   use f
   integer i
   call test(i)
end program

which specific subroutine is called based on TKR?

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

* [Bug fortran/66409] Reporting ambiguous interface when overloading assignment with polymorphic array
  2015-06-03 20:06 [Bug fortran/66409] New: Reporting ambiguous interface when overloading assignment with polymorphic array cmacmackin at gmail dot com
                   ` (2 preceding siblings ...)
  2022-10-07 18:30 ` kargl at gcc dot gnu.org
@ 2022-10-07 19:15 ` anlauf at gcc dot gnu.org
  2022-10-07 19:54 ` sgk at troutmask dot apl.washington.edu
                   ` (7 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: anlauf at gcc dot gnu.org @ 2022-10-07 19:15 UTC (permalink / raw)
  To: gcc-bugs

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

anlauf at gcc dot gnu.org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|NEW                         |WAITING

--- Comment #4 from anlauf at gcc dot gnu.org ---
IIRC type(*), dimension(..) is beyond F2008, this is F2018.
At least the NAG compiler says so.  The Cray compiler 14.0 fails for me,
as well as Nvidia.

Tobias recently updated support for type(*), dimension(*) according to the
F2018 standard.

Assumed rank still has some unfixed issues, and I think we are happy for
all contributions to make progress here.

> Is this ever going to be fixed?

This is not a contribution to that end.

Note that the complaint from comment#2 has little to do with the original
PR, comment#0, which is accepted by current mainline.  Even with my 7.5.0
installation.

Should we rather close this PR as WORKSFORME and open a new one about
the F2018 stuff?  Once we clarifies that the complaint is valid?

@Steve: I thought there is something in the standard that says how the
resolution (specific then generic) works, but cannot find it now...

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

* [Bug fortran/66409] Reporting ambiguous interface when overloading assignment with polymorphic array
  2015-06-03 20:06 [Bug fortran/66409] New: Reporting ambiguous interface when overloading assignment with polymorphic array cmacmackin at gmail dot com
                   ` (3 preceding siblings ...)
  2022-10-07 19:15 ` anlauf at gcc dot gnu.org
@ 2022-10-07 19:54 ` sgk at troutmask dot apl.washington.edu
  2022-10-07 20:10 ` anlauf at gcc dot gnu.org
                   ` (6 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: sgk at troutmask dot apl.washington.edu @ 2022-10-07 19:54 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #5 from Steve Kargl <sgk at troutmask dot apl.washington.edu> ---
On Fri, Oct 07, 2022 at 07:15:59PM +0000, anlauf at gcc dot gnu.org wrote:
> 
> @Steve: I thought there is something in the standard that says how the
> resolution (specific then generic) works, but cannot find it now...
> 

type(*) = match any type and its type kind parameters
dimension(..) = match any rank, which includes rank 0.

function foo(i)
   integer i
end foo

function bar(i)
   type(*), dimension(..) :: i
end bar

Both match type "integer", kind "4", rank "0".

AFAIK, there is no other consideration than TKR to discern which function
to call.

Perhaps, someone, who cares about this bug, can point at the language in
the Fortran standard.

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

* [Bug fortran/66409] Reporting ambiguous interface when overloading assignment with polymorphic array
  2015-06-03 20:06 [Bug fortran/66409] New: Reporting ambiguous interface when overloading assignment with polymorphic array cmacmackin at gmail dot com
                   ` (4 preceding siblings ...)
  2022-10-07 19:54 ` sgk at troutmask dot apl.washington.edu
@ 2022-10-07 20:10 ` anlauf at gcc dot gnu.org
  2022-10-07 20:42 ` mikael at gcc dot gnu.org
                   ` (5 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: anlauf at gcc dot gnu.org @ 2022-10-07 20:10 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #6 from anlauf at gcc dot gnu.org ---
(In reply to Steve Kargl from comment #5)
> Both match type "integer", kind "4", rank "0".
> 
> AFAIK, there is no other consideration than TKR to discern which function
> to call.

Yes, assuming that there is no prioritization (as for non-elemental vs.
elemental).

> Perhaps, someone, who cares about this bug, can point at the language in
> the Fortran standard.

I looked again at F2018 and couldn't find anything.

BTW: Crayftn 13.0.1 says:

module f
       ^ 
ftn-855 crayftn: ERROR F, File = pr66409.f90, Line = 1, Column = 8 
  The compiler has detected errors in module "F".  No module information file
will be created for this module.

     module procedure test_f08ts
                      ^          
ftn-487 crayftn: ERROR F, File = pr66409.f90, Line = 6, Column = 23 
  The specific interfaces for "TEST_F08TS" and "TEST_F08" make the GENERIC
interface "TEST" ambiguous.

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

* [Bug fortran/66409] Reporting ambiguous interface when overloading assignment with polymorphic array
  2015-06-03 20:06 [Bug fortran/66409] New: Reporting ambiguous interface when overloading assignment with polymorphic array cmacmackin at gmail dot com
                   ` (5 preceding siblings ...)
  2022-10-07 20:10 ` anlauf at gcc dot gnu.org
@ 2022-10-07 20:42 ` mikael at gcc dot gnu.org
  2022-10-07 21:02 ` sgk at troutmask dot apl.washington.edu
                   ` (4 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: mikael at gcc dot gnu.org @ 2022-10-07 20:42 UTC (permalink / raw)
  To: gcc-bugs

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

Mikael Morin <mikael at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |mikael at gcc dot gnu.org

--- Comment #7 from Mikael Morin <mikael at gcc dot gnu.org> ---
(In reply to anlauf from comment #6)
> (In reply to Steve Kargl from comment #5)
> 
> > Perhaps, someone, who cares about this bug, can point at the language in
> > the Fortran standard.
> 
> I looked again at F2018 and couldn't find anything.
> 

I think it's in 15.4.3.4.5 Restrictions on generic declarations.
But it's too late for me to decipher what's written there.

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

* [Bug fortran/66409] Reporting ambiguous interface when overloading assignment with polymorphic array
  2015-06-03 20:06 [Bug fortran/66409] New: Reporting ambiguous interface when overloading assignment with polymorphic array cmacmackin at gmail dot com
                   ` (6 preceding siblings ...)
  2022-10-07 20:42 ` mikael at gcc dot gnu.org
@ 2022-10-07 21:02 ` sgk at troutmask dot apl.washington.edu
  2022-10-07 21:08 ` mikael at gcc dot gnu.org
                   ` (3 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: sgk at troutmask dot apl.washington.edu @ 2022-10-07 21:02 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #8 from Steve Kargl <sgk at troutmask dot apl.washington.edu> ---
On Fri, Oct 07, 2022 at 08:42:51PM +0000, mikael at gcc dot gnu.org wrote:
> https://gcc.gnu.org/bugzilla/show_bug.cgi?id=66409
> 
> Mikael Morin <mikael at gcc dot gnu.org> changed:
> 
>            What    |Removed                     |Added
> ----------------------------------------------------------------------------
>                  CC|                            |mikael at gcc dot gnu.org
> 
> --- Comment #7 from Mikael Morin <mikael at gcc dot gnu.org> ---
> (In reply to anlauf from comment #6)
> > (In reply to Steve Kargl from comment #5)
> > 
> > > Perhaps, someone, who cares about this bug, can point at the language in
> > > the Fortran standard.
> > 
> > I looked again at F2018 and couldn't find anything.
> > 
> 
> I think it's in 15.4.3.4.5 Restrictions on generic declarations.
> But it's too late for me to decipher what's written there.
> 

   Two dummy arguments are distinguishable if

   · one is a procedure and the other is a data object,
   · they are both data objects or known to be functions,
     and neither is TKR compatible with the other,
   · one has the ALLOCATABLE attribute and the other has
     the POINTER attribute and not the INTENT (IN) attribute, or
   · one is a function with nonzero rank and the other is not
     known to be a function.

Bullet 2 is the TKR restriction.  Admittedly, 21-007.pdf:C1514 is
somewhat difficult to parse with the non-passed-object dummy data
object vs passed-object dummy data object language.

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

* [Bug fortran/66409] Reporting ambiguous interface when overloading assignment with polymorphic array
  2015-06-03 20:06 [Bug fortran/66409] New: Reporting ambiguous interface when overloading assignment with polymorphic array cmacmackin at gmail dot com
                   ` (7 preceding siblings ...)
  2022-10-07 21:02 ` sgk at troutmask dot apl.washington.edu
@ 2022-10-07 21:08 ` mikael at gcc dot gnu.org
  2022-10-07 21:12 ` anlauf at gcc dot gnu.org
                   ` (2 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: mikael at gcc dot gnu.org @ 2022-10-07 21:08 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #9 from Mikael Morin <mikael at gcc dot gnu.org> ---
(In reply to Jeff Hammond from comment #2)
> 
> My MCVE:
> 
> module f
>     implicit none
> 
>     interface test
>         module procedure test_f08
>         module procedure test_f08ts
>     end interface test
> 
>     contains
> 
>         subroutine test_f08(buf)
>             integer :: buf
>         end subroutine test_f08
> 
>         subroutine test_f08ts(buffer)
>             type(*), dimension(..), intent(inout) :: buffer
>         end subroutine test_f08ts
> 
> end module f

The following variant is not pretty, and I don't know if it does the job.
But at least it is accepted by the compiler.


module f
    implicit none

    interface test
        module procedure test_f08ts
    end interface test

    contains

        subroutine test_f08(buf)
            integer :: buf
        end subroutine test_f08

        subroutine test_f08ts(buffer)
            class(*), dimension(..), intent(inout) :: buffer
            select rank(a => buffer)
              rank(0)
                select type(b => a)
                  type is(integer)
                    call test_f08(b)
                end select
            end select
        end subroutine test_f08ts

end module f

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

* [Bug fortran/66409] Reporting ambiguous interface when overloading assignment with polymorphic array
  2015-06-03 20:06 [Bug fortran/66409] New: Reporting ambiguous interface when overloading assignment with polymorphic array cmacmackin at gmail dot com
                   ` (8 preceding siblings ...)
  2022-10-07 21:08 ` mikael at gcc dot gnu.org
@ 2022-10-07 21:12 ` anlauf at gcc dot gnu.org
  2022-10-08  6:53 ` jeff.science at gmail dot com
  2022-10-08 16:02 ` kargl at gcc dot gnu.org
  11 siblings, 0 replies; 13+ messages in thread
From: anlauf at gcc dot gnu.org @ 2022-10-07 21:12 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #10 from anlauf at gcc dot gnu.org ---
(In reply to Mikael Morin from comment #7)
> I think it's in 15.4.3.4.5 Restrictions on generic declarations.
> But it's too late for me to decipher what's written there.

Tomorrow you'll discover:

C.10.6 Rules ensuring unambiguous generics (15.4.3.4.5)

There is talk about "limited type mismatch", and some examples about
polymorphic variables, but you need a clear head to understand it.

Unfortunately there is no mentioning of TYPE(*) in that context;
this is only explained in 7.3.3.2:

"An entity that is declared using the TYPE(*) type specifier is assumed-type
and is an unlimited polymorphic entity. It is not declared to have a type,
and is not considered to have the same declared type as any other entity,
including another unlimited polymorphic entity."

So what does it mean in the present context?

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

* [Bug fortran/66409] Reporting ambiguous interface when overloading assignment with polymorphic array
  2015-06-03 20:06 [Bug fortran/66409] New: Reporting ambiguous interface when overloading assignment with polymorphic array cmacmackin at gmail dot com
                   ` (9 preceding siblings ...)
  2022-10-07 21:12 ` anlauf at gcc dot gnu.org
@ 2022-10-08  6:53 ` jeff.science at gmail dot com
  2022-10-08 16:02 ` kargl at gcc dot gnu.org
  11 siblings, 0 replies; 13+ messages in thread
From: jeff.science at gmail dot com @ 2022-10-08  6:53 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #11 from Jeff Hammond <jeff.science at gmail dot com> ---
> program foo
>    use f
>    integer i
>    call test(i)
> end program
> 
> which specific subroutine is called based on TKR?

I understand there is an ambiguity here, but what if I never make this call? 
Is the module code incorrect?

Anyways, there was a lot of discussion of this on a few channels and it seems
to not be required to work, although it's ambiguous whether compilers need to
catch it, and it seems that at least some compilers defer detection of the
issue until the ambiguous overload is actually used.

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

* [Bug fortran/66409] Reporting ambiguous interface when overloading assignment with polymorphic array
  2015-06-03 20:06 [Bug fortran/66409] New: Reporting ambiguous interface when overloading assignment with polymorphic array cmacmackin at gmail dot com
                   ` (10 preceding siblings ...)
  2022-10-08  6:53 ` jeff.science at gmail dot com
@ 2022-10-08 16:02 ` kargl at gcc dot gnu.org
  11 siblings, 0 replies; 13+ messages in thread
From: kargl at gcc dot gnu.org @ 2022-10-08 16:02 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #12 from kargl at gcc dot gnu.org ---
(In reply to Jeff Hammond from comment #11)
> > program foo
> >    use f
> >    integer i
> >    call test(i)
> > end program
> > 
> > which specific subroutine is called based on TKR?
> 
> I understand there is an ambiguity here, but what if I never make this call?
> Is the module code incorrect?
> 

21-007.pdf:C1514 is sufficiently opaque that I cannot easily decide if
a compiler needs to catch this or not.  OTOH, the TKR information is
present during compilation, it would seem appropriate that a compiler
will complain about the issue.

BTW, the original code from Chris MacMackin compiles, so at least that
portion of the PR has been fixed.

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

end of thread, other threads:[~2022-10-08 16:02 UTC | newest]

Thread overview: 13+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2015-06-03 20:06 [Bug fortran/66409] New: Reporting ambiguous interface when overloading assignment with polymorphic array cmacmackin at gmail dot com
2015-09-13 15:14 ` [Bug fortran/66409] " dominiq at lps dot ens.fr
2022-10-07 13:55 ` jeff.science at gmail dot com
2022-10-07 18:30 ` kargl at gcc dot gnu.org
2022-10-07 19:15 ` anlauf at gcc dot gnu.org
2022-10-07 19:54 ` sgk at troutmask dot apl.washington.edu
2022-10-07 20:10 ` anlauf at gcc dot gnu.org
2022-10-07 20:42 ` mikael at gcc dot gnu.org
2022-10-07 21:02 ` sgk at troutmask dot apl.washington.edu
2022-10-07 21:08 ` mikael at gcc dot gnu.org
2022-10-07 21:12 ` anlauf at gcc dot gnu.org
2022-10-08  6:53 ` jeff.science at gmail dot com
2022-10-08 16:02 ` kargl at gcc dot gnu.org

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).