public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/23373] New: Functions returning pointers with pointer argument
@ 2005-08-13  9:16 tkoenig at gcc dot gnu dot org
  2005-08-13  9:31 ` [Bug fortran/23373] " pault at gcc dot gnu dot org
                   ` (15 more replies)
  0 siblings, 16 replies; 17+ messages in thread
From: tkoenig at gcc dot gnu dot org @ 2005-08-13  9:16 UTC (permalink / raw)
  To: gcc-bugs

There is a bad case of aliasing here:

$ cat pointer_function.f90
program Realloc
  IMPLICIT NONE
  REAL, DIMENSION(:), POINTER :: x
  INTEGER :: i
  x => NULL()
  x => myallocate(x)
contains
  FUNCTION myallocate(p)
    REAL, DIMENSION(:), POINTER :: p, myallocate
    INTEGER :: nold,ierr
    if (associated(p)) then
       print *,"p is associated"
    else
       print *,"p is not associated"
    end if
    allocate(myallocate(20))
    if (associated(p)) then
       print *,"p is associated"
    else
       print *,"p is not associated"
    end if
  END FUNCTION myallocate
end program Realloc
$ gfortran -fdump-tree-original pointer_function.f90
$ ./a.out
 p is not associated
 p is associated
$ tail -10 pointer_function.f90.t02.original
{
  struct array1_real4 x;
  static void myallocate (struct array1_real4 &, struct array1_real4 &);

  x.data = 0B;
  x.data = 0B;
  myallocate (&x, &x);
}

The two arguments to myallocate are bogus - they alias each other,
and they shouldn't.  A tempoaray array descriptor is needed here.

-- 
           Summary: Functions returning pointers with pointer argument
           Product: gcc
           Version: 4.1.0
            Status: UNCONFIRMED
          Keywords: wrong-code
          Severity: normal
          Priority: P2
         Component: fortran
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: tkoenig at gcc dot gnu dot org
                CC: gcc-bugs at gcc dot gnu dot org


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=23373


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

* [Bug fortran/23373] Functions returning pointers with pointer argument
  2005-08-13  9:16 [Bug fortran/23373] New: Functions returning pointers with pointer argument tkoenig at gcc dot gnu dot org
@ 2005-08-13  9:31 ` pault at gcc dot gnu dot org
  2005-08-13 11:47 ` tkoenig at gcc dot gnu dot org
                   ` (14 subsequent siblings)
  15 siblings, 0 replies; 17+ messages in thread
From: pault at gcc dot gnu dot org @ 2005-08-13  9:31 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From pault at gcc dot gnu dot org  2005-08-13 09:31 -------
(In reply to comment #0)
Edmund,

>
> professional. Is there a workaround or is this a bug which must be fixed?
>
>

Thomas beat you to it!

In the mean time, the following  works:

       program Realloc
       USE nrtype; USE nrutil
       IMPLICIT NONE
       REAL(SP), DIMENSION(:), POINTER :: x, y
       INTEGER(I4B) :: i
       allocate(x(10))
       forall(i=1:ubound(x,1)) x(i)=i
       write(*,"(10F6.2)") x
       y => reallocate(x,20)                 ! Use y...
       x => y                                ! ...and then point x to y
       forall(i=1:ubound(x,1)) x(i)=2*i
       write(*,"(20F6.2)") x
       end program Realloc

For some reason, the compiler is not detecting the dependency and putting the
result of reallocate in a temporary.  What happens is that reallocate does all
the right things, up until the deallocate..... which it does to the lhs, being
the same as the result, ie to x!  An alternative fix is to comment out the
deallocate.

I'll take a look see over the next few days.  It's a bit of code that I need to
revisit for another reason.

Best regards

Paul T

>   FUNCTION myallocate(p)
>     REAL, DIMENSION(:), POINTER :: p, myallocate
>     INTEGER :: nold,ierr
>     if (associated(p)) then
>        print *,"p is associated"
>     else
>        print *,"p is not associated"
>     end if
>     allocate(myallocate(20))
>     if (associated(p)) then
>        print *,"p is associated"
>     else
>        print *,"p is not associated"
>     end if
>   END FUNCTION myallocate
> end program Realloc
> $ gfortran -fdump-tree-original pointer_function.f90
> $ ./a.out
>  p is not associated
>  p is associated
> $ tail -10 pointer_function.f90.t02.original
> {
>   struct array1_real4 x;
>   static void myallocate (struct array1_real4 &, struct array1_real4 &);
> 
>   x.data = 0B;
>   x.data = 0B;
>   myallocate (&x, &x);
> }
> 
> The two arguments to myallocate are bogus - they alias each other,
> and they shouldn't.  A tempoaray array descriptor is needed here.

-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=23373


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

* [Bug fortran/23373] Functions returning pointers with pointer argument
  2005-08-13  9:16 [Bug fortran/23373] New: Functions returning pointers with pointer argument tkoenig at gcc dot gnu dot org
  2005-08-13  9:31 ` [Bug fortran/23373] " pault at gcc dot gnu dot org
@ 2005-08-13 11:47 ` tkoenig at gcc dot gnu dot org
  2005-08-13 11:47 ` tkoenig at gcc dot gnu dot org
                   ` (13 subsequent siblings)
  15 siblings, 0 replies; 17+ messages in thread
From: tkoenig at gcc dot gnu dot org @ 2005-08-13 11:47 UTC (permalink / raw)
  To: gcc-bugs



-- 
           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |NEW
     Ever Confirmed|                            |1
   Last reconfirmed|0000-00-00 00:00:00         |2005-08-13 11:47:53
               date|                            |


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=23373


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

* [Bug fortran/23373] Functions returning pointers with pointer argument
  2005-08-13  9:16 [Bug fortran/23373] New: Functions returning pointers with pointer argument tkoenig at gcc dot gnu dot org
  2005-08-13  9:31 ` [Bug fortran/23373] " pault at gcc dot gnu dot org
  2005-08-13 11:47 ` tkoenig at gcc dot gnu dot org
@ 2005-08-13 11:47 ` tkoenig at gcc dot gnu dot org
  2005-08-13 18:43 ` tobi at gcc dot gnu dot org
                   ` (12 subsequent siblings)
  15 siblings, 0 replies; 17+ messages in thread
From: tkoenig at gcc dot gnu dot org @ 2005-08-13 11:47 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From tkoenig at gcc dot gnu dot org  2005-08-13 11:47 -------
*** Bug 23374 has been marked as a duplicate of this bug. ***

-- 
           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |edunlop at utvinternet dot
                   |                            |ie


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=23373


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

* [Bug fortran/23373] Functions returning pointers with pointer argument
  2005-08-13  9:16 [Bug fortran/23373] New: Functions returning pointers with pointer argument tkoenig at gcc dot gnu dot org
                   ` (2 preceding siblings ...)
  2005-08-13 11:47 ` tkoenig at gcc dot gnu dot org
@ 2005-08-13 18:43 ` tobi at gcc dot gnu dot org
  2005-08-13 18:51 ` tobi at gcc dot gnu dot org
                   ` (11 subsequent siblings)
  15 siblings, 0 replies; 17+ messages in thread
From: tobi at gcc dot gnu dot org @ 2005-08-13 18:43 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From tobi at gcc dot gnu dot org  2005-08-13 18:43 -------
Looks like dependency checking is not strict enough.

-- 
           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |tobi at gcc dot gnu dot org


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=23373


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

* [Bug fortran/23373] Functions returning pointers with pointer argument
  2005-08-13  9:16 [Bug fortran/23373] New: Functions returning pointers with pointer argument tkoenig at gcc dot gnu dot org
                   ` (3 preceding siblings ...)
  2005-08-13 18:43 ` tobi at gcc dot gnu dot org
@ 2005-08-13 18:51 ` tobi at gcc dot gnu dot org
  2005-08-14 15:53 ` tobi at gcc dot gnu dot org
                   ` (10 subsequent siblings)
  15 siblings, 0 replies; 17+ messages in thread
From: tobi at gcc dot gnu dot org @ 2005-08-13 18:51 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From tobi at gcc dot gnu dot org  2005-08-13 18:51 -------
Interestingly, for characters we do the correct copying:
schluter@pcl247d:~/src/tests> cat test2.f90
program ac
  character*10 a
  a = "abc"
  a = f(a)

contains

  function f(b) result(x)
        character*10 b, x
     x = "falsch"
     b = b//"richtig"

  end function
end program
schluter@pcl247d:~/src/tests> ../gcc/build/gcc/f951 test2.f90
-fdump-tree-original -quiet
schluter@pcl247d:~/src/tests> tail -15 test2.f90.t02.original
MAIN__ ()
{
  char a[1:10];
  static void f (char[1:10] &, int4, char[1:10] &, int4);

  _gfortran_copy_string (10, &a, 3, "abc");
  {
    char str.1[10];

    f ((char[1:10] *) &str.1, 10, &a, 10);
    _gfortran_copy_string (10, &a, 10, (char[1:10] *) &str.1);
  }
}


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=23373


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

* [Bug fortran/23373] Functions returning pointers with pointer argument
  2005-08-13  9:16 [Bug fortran/23373] New: Functions returning pointers with pointer argument tkoenig at gcc dot gnu dot org
                   ` (4 preceding siblings ...)
  2005-08-13 18:51 ` tobi at gcc dot gnu dot org
@ 2005-08-14 15:53 ` tobi at gcc dot gnu dot org
  2005-09-07 15:59 ` rsandifo at gcc dot gnu dot org
                   ` (9 subsequent siblings)
  15 siblings, 0 replies; 17+ messages in thread
From: tobi at gcc dot gnu dot org @ 2005-08-14 15:53 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From tobi at gcc dot gnu dot org  2005-08-14 15:53 -------
An alternative approach to setting up a temporary in the caller would be to have
pointer-valued functions use a fake result variable, which only immediately
before returning gets assigned to the real result.  This would allow the
optimizers to do a good job if nothing bad can happen.

-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=23373


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

* [Bug fortran/23373] Functions returning pointers with pointer argument
  2005-08-13  9:16 [Bug fortran/23373] New: Functions returning pointers with pointer argument tkoenig at gcc dot gnu dot org
                   ` (5 preceding siblings ...)
  2005-08-14 15:53 ` tobi at gcc dot gnu dot org
@ 2005-09-07 15:59 ` rsandifo at gcc dot gnu dot org
  2005-09-07 16:58 ` rsandifo at gcc dot gnu dot org
                   ` (8 subsequent siblings)
  15 siblings, 0 replies; 17+ messages in thread
From: rsandifo at gcc dot gnu dot org @ 2005-09-07 15:59 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From rsandifo at gcc dot gnu dot org  2005-09-07 15:59 -------
Testing a patch.

-- 
           What    |Removed                     |Added
----------------------------------------------------------------------------
         AssignedTo|unassigned at gcc dot gnu   |rsandifo at gcc dot gnu dot
                   |dot org                     |org
             Status|NEW                         |ASSIGNED
   Last reconfirmed|2005-08-13 11:47:53         |2005-09-07 15:59:09
               date|                            |


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=23373


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

* [Bug fortran/23373] Functions returning pointers with pointer argument
  2005-08-13  9:16 [Bug fortran/23373] New: Functions returning pointers with pointer argument tkoenig at gcc dot gnu dot org
                   ` (6 preceding siblings ...)
  2005-09-07 15:59 ` rsandifo at gcc dot gnu dot org
@ 2005-09-07 16:58 ` rsandifo at gcc dot gnu dot org
  2005-09-07 17:04 ` tobi at gcc dot gnu dot org
                   ` (7 subsequent siblings)
  15 siblings, 0 replies; 17+ messages in thread
From: rsandifo at gcc dot gnu dot org @ 2005-09-07 16:58 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From rsandifo at gcc dot gnu dot org  2005-09-07 16:58 -------
Hmm.  I supposed I'd better check.  Is the following code
also valid:

program main
  implicit none
  real, dimension (:), pointer :: x
  x => null()
  x => test ()
contains
  function test
    real, dimension (:), pointer :: test
    if (associated (x)) call abort
    allocate (test (10))
    if (associated (x)) call abort
  end function test
end program main

I've not read anything in the standard that forbids it, but I'd
appreciate it if more seasoned folks could comment.


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=23373


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

* [Bug fortran/23373] Functions returning pointers with pointer argument
  2005-08-13  9:16 [Bug fortran/23373] New: Functions returning pointers with pointer argument tkoenig at gcc dot gnu dot org
                   ` (7 preceding siblings ...)
  2005-09-07 16:58 ` rsandifo at gcc dot gnu dot org
@ 2005-09-07 17:04 ` tobi at gcc dot gnu dot org
  2005-09-07 17:07 ` richard at codesourcery dot com
                   ` (6 subsequent siblings)
  15 siblings, 0 replies; 17+ messages in thread
From: tobi at gcc dot gnu dot org @ 2005-09-07 17:04 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From tobi at gcc dot gnu dot org  2005-09-07 17:04 -------
I don't have the standard at hand, but both the Intel and the Portland Group
compiler accept this.

-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=23373


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

* [Bug fortran/23373] Functions returning pointers with pointer argument
  2005-08-13  9:16 [Bug fortran/23373] New: Functions returning pointers with pointer argument tkoenig at gcc dot gnu dot org
                   ` (8 preceding siblings ...)
  2005-09-07 17:04 ` tobi at gcc dot gnu dot org
@ 2005-09-07 17:07 ` richard at codesourcery dot com
  2005-09-08  9:20 ` cvs-commit at gcc dot gnu dot org
                   ` (5 subsequent siblings)
  15 siblings, 0 replies; 17+ messages in thread
From: richard at codesourcery dot com @ 2005-09-07 17:07 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From richard at codesourcery dot com  2005-09-07 17:07 -------
Subject: Re:  Functions returning pointers with pointer argument

"tobi at gcc dot gnu dot org" <gcc-bugzilla@gcc.gnu.org> writes:
> I don't have the standard at hand, but both the Intel and the Portland Group
> compiler accept this.

OK, thanks for checking!  I'll work on the basis that it's valid.


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=23373


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

* [Bug fortran/23373] Functions returning pointers with pointer argument
  2005-08-13  9:16 [Bug fortran/23373] New: Functions returning pointers with pointer argument tkoenig at gcc dot gnu dot org
                   ` (9 preceding siblings ...)
  2005-09-07 17:07 ` richard at codesourcery dot com
@ 2005-09-08  9:20 ` cvs-commit at gcc dot gnu dot org
  2005-09-08  9:21 ` rsandifo at gcc dot gnu dot org
                   ` (4 subsequent siblings)
  15 siblings, 0 replies; 17+ messages in thread
From: cvs-commit at gcc dot gnu dot org @ 2005-09-08  9:20 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From cvs-commit at gcc dot gnu dot org  2005-09-08 09:20 -------
Subject: Bug 23373

CVSROOT:	/cvs/gcc
Module name:	gcc
Changes by:	rsandifo@gcc.gnu.org	2005-09-08 09:20:08

Modified files:
	gcc/fortran    : ChangeLog trans-expr.c 
	gcc/testsuite  : ChangeLog 
Added files:
	gcc/testsuite/gfortran.fortran-torture/execute: pr23373-1.f90 
	                                                pr23373-2.f90 

Log message:
	PR fortran/23373
	* trans-expr.c (gfc_trans_pointer_assignment): Assign to a temporary
	descriptor if the rhs is not a null pointer or variable.

Patches:
http://gcc.gnu.org/cgi-bin/cvsweb.cgi/gcc/gcc/fortran/ChangeLog.diff?cvsroot=gcc&r1=1.538&r2=1.539
http://gcc.gnu.org/cgi-bin/cvsweb.cgi/gcc/gcc/fortran/trans-expr.c.diff?cvsroot=gcc&r1=1.57&r2=1.58
http://gcc.gnu.org/cgi-bin/cvsweb.cgi/gcc/gcc/testsuite/ChangeLog.diff?cvsroot=gcc&r1=1.6026&r2=1.6027
http://gcc.gnu.org/cgi-bin/cvsweb.cgi/gcc/gcc/testsuite/gfortran.fortran-torture/execute/pr23373-1.f90.diff?cvsroot=gcc&r1=NONE&r2=1.1
http://gcc.gnu.org/cgi-bin/cvsweb.cgi/gcc/gcc/testsuite/gfortran.fortran-torture/execute/pr23373-2.f90.diff?cvsroot=gcc&r1=NONE&r2=1.1



-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=23373


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

* [Bug fortran/23373] Functions returning pointers with pointer argument
  2005-08-13  9:16 [Bug fortran/23373] New: Functions returning pointers with pointer argument tkoenig at gcc dot gnu dot org
                   ` (10 preceding siblings ...)
  2005-09-08  9:20 ` cvs-commit at gcc dot gnu dot org
@ 2005-09-08  9:21 ` rsandifo at gcc dot gnu dot org
  2005-09-18 19:50 ` [Bug fortran/23373] [4.0 only] " tkoenig at gcc dot gnu dot org
                   ` (3 subsequent siblings)
  15 siblings, 0 replies; 17+ messages in thread
From: rsandifo at gcc dot gnu dot org @ 2005-09-08  9:21 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From rsandifo at gcc dot gnu dot org  2005-09-08 09:21 -------
Patch applied to trunk.

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


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=23373


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

* [Bug fortran/23373] [4.0 only] Functions returning pointers with pointer argument
  2005-08-13  9:16 [Bug fortran/23373] New: Functions returning pointers with pointer argument tkoenig at gcc dot gnu dot org
                   ` (11 preceding siblings ...)
  2005-09-08  9:21 ` rsandifo at gcc dot gnu dot org
@ 2005-09-18 19:50 ` tkoenig at gcc dot gnu dot org
  2005-09-18 20:02 ` pinskia at gcc dot gnu dot org
                   ` (2 subsequent siblings)
  15 siblings, 0 replies; 17+ messages in thread
From: tkoenig at gcc dot gnu dot org @ 2005-09-18 19:50 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From tkoenig at gcc dot gnu dot org  2005-09-18 19:50 -------
Not fixed in 4.0:

$ cat pointer_function.f90
program Realloc
  IMPLICIT NONE
  REAL, DIMENSION(:), POINTER :: x
  INTEGER :: i
  x => NULL()
  x => myallocate(x)
contains
  FUNCTION myallocate(p)
    REAL, DIMENSION(:), POINTER :: p, myallocate
    INTEGER :: nold,ierr
    if (associated(p)) then
       print *,"p is associated"
    else
       print *,"p is not associated"
    end if
    allocate(myallocate(20))
    if (associated(p)) then
       print *,"p is associated"
    else
       print *,"p is not associated"
    end if
  END FUNCTION myallocate
end program Realloc
$ gfortran pointer_function.f90
$ ./a.out
 p is not associated
 p is associated
$ gfortran -v
Using built-in specs.
Target: i686-pc-linux-gnu
Configured with: ../gcc-4.0/configure --prefix=/home/ig25
--enable-languages=c,fortran
Thread model: posix
gcc version 4.0.2 20050917 (prerelease)


-- 
           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|RESOLVED                    |REOPENED
      Known to fail|                            |4.0.2
      Known to work|                            |4.1.0
         Resolution|FIXED                       |
            Summary|Functions returning pointers|[4.0 only] Functions
                   |with pointer argument       |returning pointers with
                   |                            |pointer argument
   Target Milestone|---                         |4.0.2


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=23373


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

* [Bug fortran/23373] [4.0 only] Functions returning pointers with pointer argument
  2005-08-13  9:16 [Bug fortran/23373] New: Functions returning pointers with pointer argument tkoenig at gcc dot gnu dot org
                   ` (12 preceding siblings ...)
  2005-09-18 19:50 ` [Bug fortran/23373] [4.0 only] " tkoenig at gcc dot gnu dot org
@ 2005-09-18 20:02 ` pinskia at gcc dot gnu dot org
  2005-09-18 20:10 ` rsandifo at gcc dot gnu dot org
  2005-09-18 20:27 ` pinskia at gcc dot gnu dot org
  15 siblings, 0 replies; 17+ messages in thread
From: pinskia at gcc dot gnu dot org @ 2005-09-18 20:02 UTC (permalink / raw)
  To: gcc-bugs



-- 
           What    |Removed                     |Added
----------------------------------------------------------------------------
   Target Milestone|4.0.2                       |4.0.3


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=23373


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

* [Bug fortran/23373] [4.0 only] Functions returning pointers with pointer argument
  2005-08-13  9:16 [Bug fortran/23373] New: Functions returning pointers with pointer argument tkoenig at gcc dot gnu dot org
                   ` (13 preceding siblings ...)
  2005-09-18 20:02 ` pinskia at gcc dot gnu dot org
@ 2005-09-18 20:10 ` rsandifo at gcc dot gnu dot org
  2005-09-18 20:27 ` pinskia at gcc dot gnu dot org
  15 siblings, 0 replies; 17+ messages in thread
From: rsandifo at gcc dot gnu dot org @ 2005-09-18 20:10 UTC (permalink / raw)
  To: gcc-bugs



-- 
           What    |Removed                     |Added
----------------------------------------------------------------------------
         AssignedTo|rsandifo at gcc dot gnu dot |unassigned at gcc dot gnu
                   |org                         |dot org
             Status|REOPENED                    |NEW


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=23373


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

* [Bug fortran/23373] [4.0 only] Functions returning pointers with pointer argument
  2005-08-13  9:16 [Bug fortran/23373] New: Functions returning pointers with pointer argument tkoenig at gcc dot gnu dot org
                   ` (14 preceding siblings ...)
  2005-09-18 20:10 ` rsandifo at gcc dot gnu dot org
@ 2005-09-18 20:27 ` pinskia at gcc dot gnu dot org
  15 siblings, 0 replies; 17+ messages in thread
From: pinskia at gcc dot gnu dot org @ 2005-09-18 20:27 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From pinskia at gcc dot gnu dot org  2005-09-18 20:26 -------
All of these are fixed in 4.1.0. Since 4.0.2 is the last 4.0 release before a 4.1.0 release will be made, 
4.0.2 and 4.0.1 were special releases for gfrotran.  4.0.3 should be a normal release for GCC and 
gfortran in that regressions are the only changes.

-- 
           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|NEW                         |RESOLVED
         Resolution|                            |FIXED
   Target Milestone|4.0.3                       |4.1.0


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=23373


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

end of thread, other threads:[~2005-09-18 20:27 UTC | newest]

Thread overview: 17+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2005-08-13  9:16 [Bug fortran/23373] New: Functions returning pointers with pointer argument tkoenig at gcc dot gnu dot org
2005-08-13  9:31 ` [Bug fortran/23373] " pault at gcc dot gnu dot org
2005-08-13 11:47 ` tkoenig at gcc dot gnu dot org
2005-08-13 11:47 ` tkoenig at gcc dot gnu dot org
2005-08-13 18:43 ` tobi at gcc dot gnu dot org
2005-08-13 18:51 ` tobi at gcc dot gnu dot org
2005-08-14 15:53 ` tobi at gcc dot gnu dot org
2005-09-07 15:59 ` rsandifo at gcc dot gnu dot org
2005-09-07 16:58 ` rsandifo at gcc dot gnu dot org
2005-09-07 17:04 ` tobi at gcc dot gnu dot org
2005-09-07 17:07 ` richard at codesourcery dot com
2005-09-08  9:20 ` cvs-commit at gcc dot gnu dot org
2005-09-08  9:21 ` rsandifo at gcc dot gnu dot org
2005-09-18 19:50 ` [Bug fortran/23373] [4.0 only] " tkoenig at gcc dot gnu dot org
2005-09-18 20:02 ` pinskia at gcc dot gnu dot org
2005-09-18 20:10 ` rsandifo at gcc dot gnu dot org
2005-09-18 20:27 ` pinskia at gcc dot gnu dot 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).