public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/63797] New: Bogus ambiguous reference to 'sqrt'
@ 2014-11-09 17:13 burnus at gcc dot gnu.org
  2014-11-09 17:15 ` [Bug fortran/63797] " burnus at gcc dot gnu.org
                   ` (12 more replies)
  0 siblings, 13 replies; 14+ messages in thread
From: burnus at gcc dot gnu.org @ 2014-11-09 17:13 UTC (permalink / raw)
  To: gcc-bugs

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

            Bug ID: 63797
           Summary: Bogus ambiguous reference to 'sqrt'
           Product: gcc
           Version: 5.0
            Status: UNCONFIRMED
          Keywords: rejects-valid
          Severity: normal
          Priority: P3
         Component: fortran
          Assignee: unassigned at gcc dot gnu.org
          Reporter: burnus at gcc dot gnu.org

Reported by David Smith on COMP-FORTRAN-90,
https://www.jiscmail.ac.uk/cgi-bin/webadmin?A2=comp-fortran-90;75486336.1411

The following code is rejected with:

      y = sqrt(x)
              1
Error: Name 'sqrt' at (1) is an ambiguous reference to 'sqrt' from module
'(intrinsic)'


Malcolm Cohen writes:
------------------------<cut>--------------------------------
I don't see anything wrong with this.  Neither does the NAG compiler."

> module mod1
> !    double precision :: max_allowed = 1.0d+75
>    double precision :: max_allowed = sqrt(sqrt(huge(max_allowed)))

This will result in the intrinsic SQRT being exported from MOD1.  This is not a
problem in the standard, which indeed allows this, but I guess this is the
source of the problem..."

>   interface sqrt
>      module procedure sqrt_pair

Here is the second SQRT, this is a user-defined generic name."

>      y = sqrt(x)

Here is the line that gfortran complains about.  At this point there are indeed
two SQRT's visible.  But the Fortran standard explicitly allows this:

(I'm quoting the draft F2015 here, but similar text exists in every standard
since Fortran 90.)

 "Two or more accessible entities, other than generic interfaces or defined
operators, may have the same local identifier only if the identifier is not
used. Generic interfaces and defined operators are handled as described in
12.4.3.4."

Both the intrinsic SQRT and the user-defined SQRT are generic, so the first
sentence does not apply, and the second sentence does.

In other words, you are allowed to import the same generic name from different
modules, as long as that generic follows the rules in 12.4.3.4 (which lay out
requirements on non-ambiguity, both being subroutines or both being functions,
etc.).  12.4.3.4 goes on for pages in excruciating detail which I will not
reproduce here!

So this looks like a simple gfortran bug to me.  Doubtless you could work
around it by putting a PRIVATE SQRT statement in mod1 (since you probably did
not intend to export the intrinsic SQRT from there anyway).
------------------------</cut>--------------------------------


And here's the code:
------------------------<cut>--------------------------------
module mod1
!    double precision :: max_allowed = 1.0d+75
   double precision :: max_allowed = sqrt(sqrt(huge(max_allowed)))
   integer :: kw = 6
end module mod1
module mod2
   type pair
      double precision :: a_pair(2) = (/ 0, 0 /)
   end type
  interface sqrt
     module procedure sqrt_pair
  end interface
contains
  function sqrt_pair(a)
     use mod1
     implicit none
     type (pair) :: a, sqrt_pair
     intent (in) :: a
     sqrt_pair%a_pair(1) = min( sqrt(a%a_pair(1)), max_allowed )
     sqrt_pair%a_pair(2) = min( sqrt(a%a_pair(2)), max_allowed )
  end function sqrt_pair
end module mod2

program test
use mod1
use mod2
type (pair) x, y
x%a_pair(1) = 1.23d+100
x%a_pair(2) = 1.23d+200
y = sqrt(x)
write (kw,*) ' y = ', y%a_pair(1), y%a_pair(2)
end program test


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

* [Bug fortran/63797] Bogus ambiguous reference to 'sqrt'
  2014-11-09 17:13 [Bug fortran/63797] New: Bogus ambiguous reference to 'sqrt' burnus at gcc dot gnu.org
@ 2014-11-09 17:15 ` burnus at gcc dot gnu.org
  2021-04-10  0:29 ` chrisonian at gmail dot com
                   ` (11 subsequent siblings)
  12 siblings, 0 replies; 14+ messages in thread
From: burnus at gcc dot gnu.org @ 2014-11-09 17:15 UTC (permalink / raw)
  To: gcc-bugs

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

Tobias Burnus <burnus at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |NEW
   Last reconfirmed|                            |2014-11-09
                 CC|                            |pault at gcc dot gnu.org
     Ever confirmed|0                           |1
      Known to fail|                            |4.4.5, 4.8.3, 5.0


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

* [Bug fortran/63797] Bogus ambiguous reference to 'sqrt'
  2014-11-09 17:13 [Bug fortran/63797] New: Bogus ambiguous reference to 'sqrt' burnus at gcc dot gnu.org
  2014-11-09 17:15 ` [Bug fortran/63797] " burnus at gcc dot gnu.org
@ 2021-04-10  0:29 ` chrisonian at gmail dot com
  2021-04-12 21:48 ` kargl at gcc dot gnu.org
                   ` (10 subsequent siblings)
  12 siblings, 0 replies; 14+ messages in thread
From: chrisonian at gmail dot com @ 2021-04-10  0:29 UTC (permalink / raw)
  To: gcc-bugs

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

chrisonian at gmail dot com changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |chrisonian at gmail dot com

--- Comment #1 from chrisonian at gmail dot com ---
This bug is still present in versions 8.3.0, 9.3.0, 10.1.0 


Testing on Cori (NERSC):

module load gcc/8.3.0
or
module load gcc/9.3.0
or
module load gcc/10.1.0

The result is the same:

gfortran test.f90 
test.f90:30:8:

 y = sqrt(x)
        1
Error: Name 'sqrt' at (1) is an ambiguous reference to 'sqrt' from module
'(intrinsic)'

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

* [Bug fortran/63797] Bogus ambiguous reference to 'sqrt'
  2014-11-09 17:13 [Bug fortran/63797] New: Bogus ambiguous reference to 'sqrt' burnus at gcc dot gnu.org
  2014-11-09 17:15 ` [Bug fortran/63797] " burnus at gcc dot gnu.org
  2021-04-10  0:29 ` chrisonian at gmail dot com
@ 2021-04-12 21:48 ` kargl at gcc dot gnu.org
  2021-04-13 20:06 ` anlauf at gcc dot gnu.org
                   ` (9 subsequent siblings)
  12 siblings, 0 replies; 14+ messages in thread
From: kargl at gcc dot gnu.org @ 2021-04-12 21:48 UTC (permalink / raw)
  To: gcc-bugs

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

kargl at gcc dot gnu.org changed:

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

--- Comment #2 from kargl at gcc dot gnu.org ---
(In reply to chrisonian from comment #1)
> This bug is still present in versions 8.3.0, 9.3.0, 10.1.0 
> 
>

The bug likely does not effect anyone that contributes code
to GCC.  Someday someone might look at this bug.  Fortunately,
there is a trivial work around, e.g., change the generic-name
from 'sqrt' to 'root'.  If one does this and then looks at the
contents of mod2.mod, one see the only difference shown here.
Perhaps, module.c needs to be fixed to record the generic
interface.



 diff -u zxc1 zxc2
--- zxc1        2021-04-12 14:29:48.345332000 -0700
+++ zxc2        2021-04-12 14:30:04.774051000 -0700
@@ -4,7 +4,7 @@

 ()

-(('pair' 'mod2' 2) ('root' 'mod2' 3 4))
+(('pair' 'mod2' 2) ('sqrt' '(intrinsic)' 3 4))

 ()

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

* [Bug fortran/63797] Bogus ambiguous reference to 'sqrt'
  2014-11-09 17:13 [Bug fortran/63797] New: Bogus ambiguous reference to 'sqrt' burnus at gcc dot gnu.org
                   ` (2 preceding siblings ...)
  2021-04-12 21:48 ` kargl at gcc dot gnu.org
@ 2021-04-13 20:06 ` anlauf at gcc dot gnu.org
  2021-04-13 20:49 ` anlauf at gcc dot gnu.org
                   ` (8 subsequent siblings)
  12 siblings, 0 replies; 14+ messages in thread
From: anlauf at gcc dot gnu.org @ 2021-04-13 20:06 UTC (permalink / raw)
  To: gcc-bugs

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

anlauf at gcc dot gnu.org changed:

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

--- Comment #3 from anlauf at gcc dot gnu.org ---
(In reply to kargl from comment #2)
> The bug likely does not effect anyone that contributes code
> to GCC.

It does not affect me, but that is due my coding style (using public/private).


> Fortunately,
> there is a trivial work around, e.g., change the generic-name
> from 'sqrt' to 'root'.

Please don't do that.  I already have my own generic root()...

However, why in the world does an intrinsic need to show up in the module
file in the first place?  Consider:

module mod1
  implicit none
  real, parameter :: z = sqrt (0.0)
end module mod1

Is there a reason why the intrinsic should not be prevented from occurring
in the module file?

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

* [Bug fortran/63797] Bogus ambiguous reference to 'sqrt'
  2014-11-09 17:13 [Bug fortran/63797] New: Bogus ambiguous reference to 'sqrt' burnus at gcc dot gnu.org
                   ` (3 preceding siblings ...)
  2021-04-13 20:06 ` anlauf at gcc dot gnu.org
@ 2021-04-13 20:49 ` anlauf at gcc dot gnu.org
  2021-04-14  1:25 ` sgk at troutmask dot apl.washington.edu
                   ` (7 subsequent siblings)
  12 siblings, 0 replies; 14+ messages in thread
From: anlauf at gcc dot gnu.org @ 2021-04-13 20:49 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #4 from anlauf at gcc dot gnu.org ---
The following patch regtests ok and fixes the testcase:

diff --git a/gcc/fortran/module.c b/gcc/fortran/module.c
index 4db0a3ac76d..b4b7b437f86 100644
--- a/gcc/fortran/module.c
+++ b/gcc/fortran/module.c
@@ -6218,6 +6218,9 @@ write_symtree (gfc_symtree *st)
   if (check_unique_name (st->name))
     return;

+  if (strcmp (sym->module, "(intrinsic)") == 0)
+    return;
+
   p = find_pointer (sym);
   if (p == NULL)
     gfc_internal_error ("write_symtree(): Symbol not written");


It even fixes the slightly reduced & refined testcase:

module mod1
  implicit none
  real, parameter :: z = sqrt (0.0)
end module mod1

module mod2
  implicit none
  type t
     real :: a = 0.
  end type
  interface sqrt
     module procedure sqrt
  end interface
contains
  function sqrt (a)
    type(t), intent(in) :: a
    type(t)             :: sqrt
    sqrt% a = a% a
  end function sqrt
end module mod2

program test
  use mod1
  use mod2
  implicit none
  type(t) :: x, y
  y = sqrt (x)
end program test

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

* [Bug fortran/63797] Bogus ambiguous reference to 'sqrt'
  2014-11-09 17:13 [Bug fortran/63797] New: Bogus ambiguous reference to 'sqrt' burnus at gcc dot gnu.org
                   ` (4 preceding siblings ...)
  2021-04-13 20:49 ` anlauf at gcc dot gnu.org
@ 2021-04-14  1:25 ` sgk at troutmask dot apl.washington.edu
  2021-04-14 20:43 ` anlauf at gcc dot gnu.org
                   ` (6 subsequent siblings)
  12 siblings, 0 replies; 14+ messages in thread
From: sgk at troutmask dot apl.washington.edu @ 2021-04-14  1:25 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #5 from Steve Kargl <sgk at troutmask dot apl.washington.edu> ---
On Tue, Apr 13, 2021 at 08:49:35PM +0000, anlauf at gcc dot gnu.org wrote:
> https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63797
> 
> --- Comment #4 from anlauf at gcc dot gnu.org ---
> The following patch regtests ok and fixes the testcase:
> 
> diff --git a/gcc/fortran/module.c b/gcc/fortran/module.c
> index 4db0a3ac76d..b4b7b437f86 100644
> --- a/gcc/fortran/module.c
> +++ b/gcc/fortran/module.c
> @@ -6218,6 +6218,9 @@ write_symtree (gfc_symtree *st)
>    if (check_unique_name (st->name))
>      return;
> 
> +  if (strcmp (sym->module, "(intrinsic)") == 0)
> +    return;
> +
>    p = find_pointer (sym);
>    if (p == NULL)
>      gfc_internal_error ("write_symtree(): Symbol not written");
> 
> 
> It even fixes the slightly reduced & refined testcase:
> 

Harald, if this survives regression testing, it might be
appropriate to commit.  The only issue I can think of 
is procedure pointers.  I don't use them, but if one can
point at sqrt (or dsqrt, i.e.,  with specific vs generic
name), then is [d]sqrt needed to be written into the module?

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

* [Bug fortran/63797] Bogus ambiguous reference to 'sqrt'
  2014-11-09 17:13 [Bug fortran/63797] New: Bogus ambiguous reference to 'sqrt' burnus at gcc dot gnu.org
                   ` (5 preceding siblings ...)
  2021-04-14  1:25 ` sgk at troutmask dot apl.washington.edu
@ 2021-04-14 20:43 ` anlauf at gcc dot gnu.org
  2021-04-14 21:37 ` sgk at troutmask dot apl.washington.edu
                   ` (5 subsequent siblings)
  12 siblings, 0 replies; 14+ messages in thread
From: anlauf at gcc dot gnu.org @ 2021-04-14 20:43 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #6 from anlauf at gcc dot gnu.org ---
Steve, can you give an example for the procedure pointer case you mentioned?
I played a bit, but the only valid code that I can think of did not produce
a reference to sqrt in such a way that it needs to show up in the mod.

Extended testcase that compiles and also uses a procedure pointer to sqrt():

! { dg-do compile }
! PR63797 - Bogus ambiguous reference to 'sqrt'

module mod1
  implicit none
  real, parameter :: z = sqrt (0.0)
  real            :: w = sqrt (1.0)
  interface
     pure real function sqrt_ifc (x)
       real, intent(in) :: x
     end function sqrt_ifc
  end interface
contains
  pure function myroot () result (f)
    procedure(sqrt_ifc), pointer :: f
    intrinsic :: sqrt
    f => sqrt
  end function myroot
end module mod1

module mod2
  implicit none
  type t
     real :: a = 0.
  end type
  interface sqrt
     module procedure sqrt
  end interface
contains
  function sqrt (a)
    type(t), intent(in) :: a
    type(t)             :: sqrt
    sqrt% a = a% a
  end function sqrt
end module mod2

program test
  use mod1
  use mod2
  implicit none
  type(t) :: x, y
  procedure(sqrt_ifc), pointer :: root
  root => myroot ()
  y    = sqrt (x)
  y% a = sqrt (x% a) + z - w + root (x% a)
end program test

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

* [Bug fortran/63797] Bogus ambiguous reference to 'sqrt'
  2014-11-09 17:13 [Bug fortran/63797] New: Bogus ambiguous reference to 'sqrt' burnus at gcc dot gnu.org
                   ` (6 preceding siblings ...)
  2021-04-14 20:43 ` anlauf at gcc dot gnu.org
@ 2021-04-14 21:37 ` sgk at troutmask dot apl.washington.edu
  2021-04-15 20:40 ` anlauf at gcc dot gnu.org
                   ` (4 subsequent siblings)
  12 siblings, 0 replies; 14+ messages in thread
From: sgk at troutmask dot apl.washington.edu @ 2021-04-14 21:37 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #7 from Steve Kargl <sgk at troutmask dot apl.washington.edu> ---
On Wed, Apr 14, 2021 at 08:43:50PM +0000, anlauf at gcc dot gnu.org wrote:
> https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63797
> 
> --- Comment #6 from anlauf at gcc dot gnu.org ---
> Steve, can you give an example for the procedure pointer case you mentioned?
> I played a bit, but the only valid code that I can think of did not produce
> a reference to sqrt in such a way that it needs to show up in the mod.
> 
> Extended testcase that compiles and also uses a procedure pointer to sqrt():
> 

Your testcase is what I first thought about, but didn't try to
write.  The only other instance that I might be concerned about
is 

module aaa

   abstract interface
      function real_func (x)
         real :: real_func
         real, intent (in) :: x
      end function real_func
   end interface

   procedure(real_func), pointer :: bah => sqrt

end module aaa

which looks like a default initialization.  Does sqrt need to be
recorded into the module?  If not, then your patch is probably ok.

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

* [Bug fortran/63797] Bogus ambiguous reference to 'sqrt'
  2014-11-09 17:13 [Bug fortran/63797] New: Bogus ambiguous reference to 'sqrt' burnus at gcc dot gnu.org
                   ` (7 preceding siblings ...)
  2021-04-14 21:37 ` sgk at troutmask dot apl.washington.edu
@ 2021-04-15 20:40 ` anlauf at gcc dot gnu.org
  2021-04-15 20:52 ` anlauf at gcc dot gnu.org
                   ` (3 subsequent siblings)
  12 siblings, 0 replies; 14+ messages in thread
From: anlauf at gcc dot gnu.org @ 2021-04-15 20:40 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #8 from anlauf at gcc dot gnu.org ---
(In reply to Steve Kargl from comment #7)
> which looks like a default initialization.  Does sqrt need to be
> recorded into the module?  If not, then your patch is probably ok.

My patch actually does not have any affect on the module file generated
for your testcase.  I'll add it to my testcase and submit.

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

* [Bug fortran/63797] Bogus ambiguous reference to 'sqrt'
  2014-11-09 17:13 [Bug fortran/63797] New: Bogus ambiguous reference to 'sqrt' burnus at gcc dot gnu.org
                   ` (8 preceding siblings ...)
  2021-04-15 20:40 ` anlauf at gcc dot gnu.org
@ 2021-04-15 20:52 ` anlauf at gcc dot gnu.org
  2021-04-16 14:24 ` cvs-commit at gcc dot gnu.org
                   ` (2 subsequent siblings)
  12 siblings, 0 replies; 14+ messages in thread
From: anlauf at gcc dot gnu.org @ 2021-04-15 20:52 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #9 from anlauf at gcc dot gnu.org ---
Patch: https://gcc.gnu.org/pipermail/fortran/2021-April/055935.html

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

* [Bug fortran/63797] Bogus ambiguous reference to 'sqrt'
  2014-11-09 17:13 [Bug fortran/63797] New: Bogus ambiguous reference to 'sqrt' burnus at gcc dot gnu.org
                   ` (9 preceding siblings ...)
  2021-04-15 20:52 ` anlauf at gcc dot gnu.org
@ 2021-04-16 14:24 ` cvs-commit at gcc dot gnu.org
  2021-04-18 19:48 ` cvs-commit at gcc dot gnu.org
  2021-04-18 19:50 ` anlauf at gcc dot gnu.org
  12 siblings, 0 replies; 14+ messages in thread
From: cvs-commit at gcc dot gnu.org @ 2021-04-16 14:24 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #10 from CVS Commits <cvs-commit at gcc dot gnu.org> ---
The master branch has been updated by Harald Anlauf <anlauf@gcc.gnu.org>:

https://gcc.gnu.org/g:d264194c1069fbcd129222f86455137f29a5c6fd

commit r11-8218-gd264194c1069fbcd129222f86455137f29a5c6fd
Author: Harald Anlauf <anlauf@gmx.de>
Date:   Fri Apr 16 16:24:31 2021 +0200

    PR fortran/63797 - Bogus ambiguous reference to 'sqrt'

    The interface of an intrinsic procedure is automatically explicit.
    Do not write it to the module file to prevent wrong ambiguities on USE.

    gcc/fortran/ChangeLog:

            PR fortran/63797
            * module.c (write_symtree): Do not write interface of intrinsic
            procedure to module file for F2003 and newer.

    gcc/testsuite/ChangeLog:

            PR fortran/63797
            * gfortran.dg/pr63797.f90: New test.

    Co-authored-by: Paul Thomas <pault@gcc.gnu.org>

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

* [Bug fortran/63797] Bogus ambiguous reference to 'sqrt'
  2014-11-09 17:13 [Bug fortran/63797] New: Bogus ambiguous reference to 'sqrt' burnus at gcc dot gnu.org
                   ` (10 preceding siblings ...)
  2021-04-16 14:24 ` cvs-commit at gcc dot gnu.org
@ 2021-04-18 19:48 ` cvs-commit at gcc dot gnu.org
  2021-04-18 19:50 ` anlauf at gcc dot gnu.org
  12 siblings, 0 replies; 14+ messages in thread
From: cvs-commit at gcc dot gnu.org @ 2021-04-18 19:48 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #11 from CVS Commits <cvs-commit at gcc dot gnu.org> ---
The releases/gcc-10 branch has been updated by Harald Anlauf
<anlauf@gcc.gnu.org>:

https://gcc.gnu.org/g:aff57bcebe534b1d92f78bdfb89a4001a6d12af2

commit r10-9712-gaff57bcebe534b1d92f78bdfb89a4001a6d12af2
Author: Harald Anlauf <anlauf@gmx.de>
Date:   Fri Apr 16 16:24:31 2021 +0200

    PR fortran/63797 - Bogus ambiguous reference to 'sqrt'

    The interface of an intrinsic procedure is automatically explicit.
    Do not write it to the module file to prevent wrong ambiguities on USE.

    gcc/fortran/ChangeLog:

            PR fortran/63797
            * module.c (write_symtree): Do not write interface of intrinsic
            procedure to module file for F2003 and newer.

    gcc/testsuite/ChangeLog:

            PR fortran/63797
            * gfortran.dg/pr63797.f90: New test.

    Co-authored-by: Paul Thomas <pault@gcc.gnu.org>
    (cherry picked from commit d264194c1069fbcd129222f86455137f29a5c6fd)

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

* [Bug fortran/63797] Bogus ambiguous reference to 'sqrt'
  2014-11-09 17:13 [Bug fortran/63797] New: Bogus ambiguous reference to 'sqrt' burnus at gcc dot gnu.org
                   ` (11 preceding siblings ...)
  2021-04-18 19:48 ` cvs-commit at gcc dot gnu.org
@ 2021-04-18 19:50 ` anlauf at gcc dot gnu.org
  12 siblings, 0 replies; 14+ messages in thread
From: anlauf at gcc dot gnu.org @ 2021-04-18 19:50 UTC (permalink / raw)
  To: gcc-bugs

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

anlauf at gcc dot gnu.org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|NEW                         |RESOLVED
         Resolution|---                         |FIXED

--- Comment #12 from anlauf at gcc dot gnu.org ---
Fixed on mainline for gcc-11, and backported to 10-branch as suggested by Paul.
Closing.

Thanks for the report!

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

end of thread, other threads:[~2021-04-18 19:50 UTC | newest]

Thread overview: 14+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2014-11-09 17:13 [Bug fortran/63797] New: Bogus ambiguous reference to 'sqrt' burnus at gcc dot gnu.org
2014-11-09 17:15 ` [Bug fortran/63797] " burnus at gcc dot gnu.org
2021-04-10  0:29 ` chrisonian at gmail dot com
2021-04-12 21:48 ` kargl at gcc dot gnu.org
2021-04-13 20:06 ` anlauf at gcc dot gnu.org
2021-04-13 20:49 ` anlauf at gcc dot gnu.org
2021-04-14  1:25 ` sgk at troutmask dot apl.washington.edu
2021-04-14 20:43 ` anlauf at gcc dot gnu.org
2021-04-14 21:37 ` sgk at troutmask dot apl.washington.edu
2021-04-15 20:40 ` anlauf at gcc dot gnu.org
2021-04-15 20:52 ` anlauf at gcc dot gnu.org
2021-04-16 14:24 ` cvs-commit at gcc dot gnu.org
2021-04-18 19:48 ` cvs-commit at gcc dot gnu.org
2021-04-18 19:50 ` anlauf 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).