public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/47844] New: Pointer-valued function: Provide wrong result when dereferenced automatically after list-write
@ 2011-02-22  7:07 Kdx1999 at gmail dot com
  2011-02-22  8:37 ` [Bug fortran/47844] " burnus at gcc dot gnu.org
                   ` (11 more replies)
  0 siblings, 12 replies; 13+ messages in thread
From: Kdx1999 at gmail dot com @ 2011-02-22  7:07 UTC (permalink / raw)
  To: gcc-bugs

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

           Summary: Pointer-valued function: Provide wrong result when
                    dereferenced automatically after list-write
           Product: gcc
           Version: 4.6.0
            Status: UNCONFIRMED
          Severity: minor
          Priority: P3
         Component: fortran
        AssignedTo: unassigned@gcc.gnu.org
        ReportedBy: Kdx1999@gmail.com


Hello,I'm trying to compile Example 15.20 in Stephen J.Chapman's book Fortran
95/2003 for Scientists & Engineers. The purpose of the function is simple:
"Return a pointer to every fifth element in a input rank 1 array".
------------------------------------------------------------------------------
------------------------------------------------------------------------------
Code:

PROGRAM test_pointer_value
  !
  ! Purpose:
  ! Test pointer valued function
  !
  ! Record of revisions:
  ! Date          Programmer          Description of change
  ! 02/22/2011    KePu                Original code
  !
  IMPLICIT NONE

  ! Data dictionary
  INTEGER,DIMENSION(10),TARGET::array=[1,3,5,7,9,11,13,15,17,19]! Array to be
test
  INTEGER,dimension(2)::arrar_fifth
  INTEGER,POINTER,DIMENSION(:)::ptr_array=>NULL()        ! Pointer to array
  INTEGER,POINTER,DIMENSION(:)::ptr_array_fifth=>NULL()  ! Pointer return every
fifth element of array

  ptr_array=>array              ! Initialization

  ptr_array_fifth=>every_fifth(ptr_array)
  WRITE(*,*)ptr_array_fifth
  WRITE(*,*)every_fifth(ptr_array)
CONTAINS
  FUNCTION every_fifth(ptr_array) RESULT(ptr_fifth)
    !
    ! Purpose:
    ! To produce a pointer ot every fifth element in an
    ! input rand 1 array.
    !
    ! Record of revisions:
    ! Date          Programmer          Description of change
    ! 02/22/2011    KePu                Original code
    !
    IMPLICIT NONE

    INTEGER,POINTER,DIMENSION(:)::ptr_fifth
    INTEGER,POINTER,DIMENSION(:),INTENT(in)::ptr_array
    INTEGER::low
    INTEGER::high

    low=LBOUND(ptr_array,1)
    high=UBOUND(ptr_array,1)
    ptr_fifth=>ptr_array(low:high:5) 
  END FUNCTION every_fifth
END PROGRAM test_pointer_value 
------------------------------------------------------------------------------
------------------------------------------------------------------------------

The book says "The function can also be used in a location where an integer
array is expected. Inthat case, the pointer returned by the function will
automatically be dereferenced,and will print out the value by the pointer
returned from the function". But after ran the program, two result prompt on
the screen are different(The first line is right answer):
1   11
1    3

I'm not sure if it's a bug. Any help to my problem will be appreciated. Thank
you.


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

* [Bug fortran/47844] Pointer-valued function: Provide wrong result when dereferenced automatically after list-write
  2011-02-22  7:07 [Bug fortran/47844] New: Pointer-valued function: Provide wrong result when dereferenced automatically after list-write Kdx1999 at gmail dot com
@ 2011-02-22  8:37 ` burnus at gcc dot gnu.org
  2011-02-22 15:35 ` [Bug fortran/47844] I/O: data transfer statement: Array stride ignored for pointer-valued function results burnus at gcc dot gnu.org
                   ` (10 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: burnus at gcc dot gnu.org @ 2011-02-22  8:37 UTC (permalink / raw)
  To: gcc-bugs

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

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

           What    |Removed                     |Added
----------------------------------------------------------------------------
           Keywords|                            |wrong-code
                 CC|                            |burnus at gcc dot gnu.org
             Blocks|                            |32834
      Known to fail|                            |4.3.4, 4.4.0, 4.5.1, 4.6.0

--- Comment #1 from Tobias Burnus <burnus at gcc dot gnu.org> 2011-02-22 07:13:57 UTC ---
I have not yet checked the code, but ifort, open64, pathf95 and NAG it prints
twice "1 11", with gfortran (FE: 4.3 to 4.6; libgfortran was always 4.6) I get
"1 11" and "1 3".


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

* [Bug fortran/47844] I/O: data transfer statement: Array stride ignored for pointer-valued function results
  2011-02-22  7:07 [Bug fortran/47844] New: Pointer-valued function: Provide wrong result when dereferenced automatically after list-write Kdx1999 at gmail dot com
  2011-02-22  8:37 ` [Bug fortran/47844] " burnus at gcc dot gnu.org
@ 2011-02-22 15:35 ` burnus at gcc dot gnu.org
  2011-03-01 13:20 ` [Bug fortran/47844] " burnus at gcc dot gnu.org
                   ` (9 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: burnus at gcc dot gnu.org @ 2011-02-22 15:35 UTC (permalink / raw)
  To: gcc-bugs

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

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

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |pault at gcc dot gnu.org
            Summary|Pointer-valued function:    |I/O: data transfer
                   |Provide wrong result when   |statement: Array stride
                   |dereferenced automatically  |ignored for pointer-valued
                   |after list-write            |function results

--- Comment #2 from Tobias Burnus <burnus at gcc dot gnu.org> 2011-02-22 14:45:42 UTC ---
Paul, I added you as you are a tad more familiar with the scalarizer than I am.

 * * *

Slightly simplified test case:

  integer, target :: tgt(5) = [1,2,3,4,5]
  integer, pointer :: ptr(:)
  print *, f(tgt)
contains
  function f(x)
    integer, target :: x(:)
    integer, pointer :: f(:)
    f => x(::2)
  end function f
end

While "f" correctly sets the stride, it is ignored by the PRINT statement;
-fdump-tree-original shows:

      f (&atmp.8, D.1566);
[...]
              D.1579 = (*(integer(kind=4)[0:] * restrict) atmp.8.data)[S.9];
              _gfortran_transfer_integer_write (&dt_parm.5, &D.1579, 4);
            }
            S.9 = S.9 + 1;

The last line should be S.9 = S.9 + atmp.8.stride, which gets correctly set by
"f()".

Thus, one needs to teach the scalarizer that the stride does not have to be
always 1 for SS_FUNCTION, though the only case I currently can come up with are
array-valued pointer-returning functions. I think one should consider adding a
is_pointer_result:1 to gfc_ss, which could be set in gfc_walk_function_expr.

The scalarizers are set up via gfc_trans_transfer. The "1" setting seems to
happen in gfc_conv_ss_startstride:

        case GFC_SS_CONSTRUCTOR:
        case GFC_SS_FUNCTION:
          for (n = 0; n < ss->data.info.dimen; n++)
            {
              ss->data.info.start[n] = gfc_index_zero_node;
              ss->data.info.end[n] = gfc_index_zero_node;
              ss->data.info.stride[n] = gfc_index_one_node;
            }
          break;

At some point, it needs to be modified for array-pointer-returning functions; I
think that should happen in gfc_conv_loop_setup


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

* [Bug fortran/47844] Array stride ignored for pointer-valued function results
  2011-02-22  7:07 [Bug fortran/47844] New: Pointer-valued function: Provide wrong result when dereferenced automatically after list-write Kdx1999 at gmail dot com
  2011-02-22  8:37 ` [Bug fortran/47844] " burnus at gcc dot gnu.org
  2011-02-22 15:35 ` [Bug fortran/47844] I/O: data transfer statement: Array stride ignored for pointer-valued function results burnus at gcc dot gnu.org
@ 2011-03-01 13:20 ` burnus at gcc dot gnu.org
  2011-10-05 10:02 ` dominiq at lps dot ens.fr
                   ` (8 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: burnus at gcc dot gnu.org @ 2011-03-01 13:20 UTC (permalink / raw)
  To: gcc-bugs

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

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

           What    |Removed                     |Added
----------------------------------------------------------------------------
            Summary|I/O: data transfer          |Array stride ignored for
                   |statement: Array stride     |pointer-valued function
                   |ignored for pointer-valued  |results
                   |function results            |

--- Comment #3 from Tobias Burnus <burnus at gcc dot gnu.org> 2011-03-01 13:20:28 UTC ---
Does not only affect I/O but also assignment; cf. example below.

  integer, target :: tgt(5) = [1,2,3,4,5]
  integer :: var(3)
  var = f(tgt) ! should assign 1 3 5
  print *, ptr ! but    prints 1 2 3
contains
  function f(x)
    integer, target :: x(:)
    integer, pointer :: f(:)
    f => x(::2)
  end function f
end


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

* [Bug fortran/47844] Array stride ignored for pointer-valued function results
  2011-02-22  7:07 [Bug fortran/47844] New: Pointer-valued function: Provide wrong result when dereferenced automatically after list-write Kdx1999 at gmail dot com
                   ` (2 preceding siblings ...)
  2011-03-01 13:20 ` [Bug fortran/47844] " burnus at gcc dot gnu.org
@ 2011-10-05 10:02 ` dominiq at lps dot ens.fr
  2011-10-05 10:22 ` pault at gcc dot gnu.org
                   ` (7 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: dominiq at lps dot ens.fr @ 2011-10-05 10:02 UTC (permalink / raw)
  To: gcc-bugs

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

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

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |NEW
   Last reconfirmed|                            |2011-10-05
     Ever Confirmed|0                           |1

--- Comment #4 from Dominique d'Humieres <dominiq at lps dot ens.fr> 2011-10-05 10:02:21 UTC ---
Still there on trunk at revision 179525 (I see it with 4.4.6, 4.5.3, and
4.6.1). Note that for the test in comment #3, the line

  print *, ptr ! but    prints 1 2 3

should probably be replaced with

  print *, var ! but    prints 1 2 3


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

* [Bug fortran/47844] Array stride ignored for pointer-valued function results
  2011-02-22  7:07 [Bug fortran/47844] New: Pointer-valued function: Provide wrong result when dereferenced automatically after list-write Kdx1999 at gmail dot com
                   ` (3 preceding siblings ...)
  2011-10-05 10:02 ` dominiq at lps dot ens.fr
@ 2011-10-05 10:22 ` pault at gcc dot gnu.org
  2011-10-05 14:36 ` paul.richard.thomas at gmail dot com
                   ` (6 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: pault at gcc dot gnu.org @ 2011-10-05 10:22 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #5 from Paul Thomas <pault at gcc dot gnu.org> 2011-10-05 10:21:33 UTC ---
(In reply to comment #4)
> Still there on trunk at revision 179525 (I see it with 4.4.6, 4.5.3, and
> 4.6.1). Note that for the test in comment #3, the line
> 
>   print *, ptr ! but    prints 1 2 3
> 
> should probably be replaced with
> 
>   print *, var ! but    prints 1 2 3

Dear All,

I missed the CC during my lengthy "outage" during the first half of the year.

I'll take a look.

Cheers

Paul


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

* [Bug fortran/47844] Array stride ignored for pointer-valued function results
  2011-02-22  7:07 [Bug fortran/47844] New: Pointer-valued function: Provide wrong result when dereferenced automatically after list-write Kdx1999 at gmail dot com
                   ` (4 preceding siblings ...)
  2011-10-05 10:22 ` pault at gcc dot gnu.org
@ 2011-10-05 14:36 ` paul.richard.thomas at gmail dot com
  2011-10-05 15:04 ` burnus at gcc dot gnu.org
                   ` (5 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: paul.richard.thomas at gmail dot com @ 2011-10-05 14:36 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #6 from paul.richard.thomas at gmail dot com <paul.richard.thomas at gmail dot com> 2011-10-05 14:35:14 UTC ---
Dear Tobias and Dominique,

We could fix this in 4.7 by adding a sm field to array descriptors.
If we added the sm field after the dimension array, we would not
damage the exiting API.

On Tue, Mar 1, 2011 at 2:20 PM, burnus at gcc dot gnu.org
<gcc-bugzilla@gcc.gnu.org> wrote:
> http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47844
>
> Tobias Burnus <burnus at gcc dot gnu.org> changed:
>
>           What    |Removed                     |Added
> ----------------------------------------------------------------------------
>            Summary|I/O: data transfer          |Array stride ignored for
>                   |statement: Array stride     |pointer-valued function
>                   |ignored for pointer-valued  |results
>                   |function results            |
>
> --- Comment #3 from Tobias Burnus <burnus at gcc dot gnu.org> 2011-03-01 13:20:28 UTC ---
> Does not only affect I/O but also assignment; cf. example below.
>
>  integer, target :: tgt(5) = [1,2,3,4,5]
>  integer :: var(3)
>  var = f(tgt) ! should assign 1 3 5
>  print *, ptr ! but    prints 1 2 3
> contains
>  function f(x)
>    integer, target :: x(:)
>    integer, pointer :: f(:)
>    f => x(::2)
>  end function f
> end
>
> --
> Configure bugmail: http://gcc.gnu.org/bugzilla/userprefs.cgi?tab=email
> ------- You are receiving this mail because: -------
> You are on the CC list for the bug.
>


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

* [Bug fortran/47844] Array stride ignored for pointer-valued function results
  2011-02-22  7:07 [Bug fortran/47844] New: Pointer-valued function: Provide wrong result when dereferenced automatically after list-write Kdx1999 at gmail dot com
                   ` (5 preceding siblings ...)
  2011-10-05 14:36 ` paul.richard.thomas at gmail dot com
@ 2011-10-05 15:04 ` burnus at gcc dot gnu.org
  2011-10-05 21:40 ` dominiq at lps dot ens.fr
                   ` (4 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: burnus at gcc dot gnu.org @ 2011-10-05 15:04 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #7 from Tobias Burnus <burnus at gcc dot gnu.org> 2011-10-05 15:04:02 UTC ---
(In reply to comment #6)
> We could fix this in 4.7 by adding a sm field to array descriptors.
> If we added the sm field after the dimension array, we would not
> damage the exiting API.

I think that one can create cases, where it fails - for instance when combining
a GCC 4.7 compiled procedure with a GCC 4.6 compiled procedure. For instance
some combination of
  gcc_4_6_compiled()
    type(t), pointer :: A(:)
    call assign_in_gcc_4_7_compiled (A)
might fail, if one accesses "a.sm" in "assign_in_gcc_4_7_compiled". If we can
rule out that such issues occur for currently working code, we can do so.

You also have a small ABI issue with allocatable coarrays: In GCC 4.6 or 4.7,
using -fcoarray=single, one has for
  integer, allocatable :: A(:)[:]
  allocate (A(1)[3:*])
an extra dimension triplet for coarrays:
        a.dim[0].lbound = 1;
        a.dim[0].ubound = 1;
        a.dim[0].stride = 1;
        a.dim[1].lbound = 3;
Given that coarrays are not yet widely used and that coarrays in 4.6 had some
issues, it might be a smaller problem.


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

* [Bug fortran/47844] Array stride ignored for pointer-valued function results
  2011-02-22  7:07 [Bug fortran/47844] New: Pointer-valued function: Provide wrong result when dereferenced automatically after list-write Kdx1999 at gmail dot com
                   ` (6 preceding siblings ...)
  2011-10-05 15:04 ` burnus at gcc dot gnu.org
@ 2011-10-05 21:40 ` dominiq at lps dot ens.fr
  2011-10-05 22:20 ` pault at gcc dot gnu.org
                   ` (3 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: dominiq at lps dot ens.fr @ 2011-10-05 21:40 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #8 from Dominique d'Humieres <dominiq at lps dot ens.fr> 2011-10-05 21:39:31 UTC ---
> We could fix this in 4.7 by adding a sm field to array descriptors.

I don't see why. I have looked at the dump.original of the following code:

  integer, target :: tgt(9) = [1,2,3,4,5,6,7,8,9]
  integer, pointer :: p(:)
  integer :: var(3)
  p => tgt(ubound(tgt,1)-4:lbound(tgt,1):-2)
  var = p
  print *, var ! prints 5 3 1
  var = f(tgt) ! should assign 5 3 1
  print *, var ! but    prints 5 6 7
  if(any(var/=[5,3,1])) call abort()
contains
  function f(x) result(r)
    integer, target :: x(:)
    integer, pointer :: r(:)
    r => x(ubound(x,1)-4:lbound(x,1):-2)
    print *, r ! prints 5 3 1
  end function f
end

The first assignment (var = p) is

  p.dtype = 265;
  p.dim[0].lbound = 1;
  p.dim[0].ubound = 3;
  p.dim[0].stride = -2;
  p.data = (void *) &tgt[4];
  p.offset = 2;
  {
    integer(kind=8) D.1793;
    integer(kind=8) D.1792;
    integer(kind=8) D.1791;
    integer(kind=8) D.1790;
    integer(kind=4)[0:] * D.1789;

    D.1789 = (integer(kind=4)[0:] *) p.data;
    D.1790 = p.offset;
    D.1791 = p.dim[0].lbound;
    D.1792 = p.dim[0].ubound;
    D.1793 = D.1791 + -1;
    {
      integer(kind=8) D.1795;
      integer(kind=8) S.7;

      D.1795 = p.dim[0].stride;
      S.7 = 1;
      while (1)
        {
          if (S.7 > 3) goto L.1;
          var[S.7 + -1] = (*D.1789)[(S.7 + D.1793) * D.1795 + D.1790];
          S.7 = S.7 + 1;
        }
      L.1:;
    }
  }

while the second one (var = f(tgt)) is:

    f (&atmp.12, D.1804);
    {
      integer(kind=8) S.13;

      S.13 = 0;
      while (1)
        {
          if (S.13 > 2) goto L.2;
          var[S.13] = (*(integer(kind=4)[3] * restrict) atmp.12.data)[S.13];
          S.13 = S.13 + 1;
        }
      L.2:;
    }

As far I understand the dump, atmp.12 is set with the same values as p (through
an awfully complicated process), but atmp.12.dim[0].stride is not used in the
assignment.


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

* [Bug fortran/47844] Array stride ignored for pointer-valued function results
  2011-02-22  7:07 [Bug fortran/47844] New: Pointer-valued function: Provide wrong result when dereferenced automatically after list-write Kdx1999 at gmail dot com
                   ` (7 preceding siblings ...)
  2011-10-05 21:40 ` dominiq at lps dot ens.fr
@ 2011-10-05 22:20 ` pault at gcc dot gnu.org
  2011-10-08 10:19 ` pault at gcc dot gnu.org
                   ` (2 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: pault at gcc dot gnu.org @ 2011-10-05 22:20 UTC (permalink / raw)
  To: gcc-bugs

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

Paul Thomas <pault at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
         AssignedTo|unassigned at gcc dot       |pault at gcc dot gnu.org
                   |gnu.org                     |

--- Comment #9 from Paul Thomas <pault at gcc dot gnu.org> 2011-10-05 22:20:13 UTC ---
Created attachment 25425
  --> http://gcc.gnu.org/bugzilla/attachment.cgi?id=25425
a draft patch for the pr

This has been partially regtested and looks OK at 20k tests or so - I had to
head off to bed!

If all is well, I will look for a slightly cleaner place to use the returned
stride; this place might not exist of course!

I will submit tomorrow with the test case below.

Cheers

Paul

! (dg-do run }
! Test the fix for PR47844, in which the stride in the function result
! was ignored. Previously, the result was [1,3] at lines 15 and 16.
!
! Contributed by KePu  <Kdx1999@gmail.com>
!
PROGRAM test_pointer_value
  IMPLICIT NONE
  INTEGER, DIMENSION(10), TARGET :: array= [1,3,5,7,9,11,13,15,17,19]
  INTEGER, dimension(2) :: array_fifth
  INTEGER, POINTER, DIMENSION(:) :: ptr_array => NULL()
  INTEGER, POINTER, DIMENSION(:) :: ptr_array_fifth => NULL()
  ptr_array => array
  array_fifth = every_fifth (ptr_array)
  if (any (array_fifth .ne. [1,11])) call abort
  if (any (every_fifth(ptr_array) .ne. [1,11])) call abort
CONTAINS
  FUNCTION every_fifth (ptr_array) RESULT (ptr_fifth)
    IMPLICIT NONE
    INTEGER, POINTER, DIMENSION(:) :: ptr_fifth
    INTEGER, POINTER, DIMENSION(:), INTENT(in) :: ptr_array
    INTEGER :: low
    INTEGER :: high
    low = LBOUND (ptr_array, 1)
    high = UBOUND (ptr_array, 1)
    ptr_fifth => ptr_array (low: high: 5) 
  END FUNCTION every_fifth
END PROGRAM test_pointer_value


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

* [Bug fortran/47844] Array stride ignored for pointer-valued function results
  2011-02-22  7:07 [Bug fortran/47844] New: Pointer-valued function: Provide wrong result when dereferenced automatically after list-write Kdx1999 at gmail dot com
                   ` (8 preceding siblings ...)
  2011-10-05 22:20 ` pault at gcc dot gnu.org
@ 2011-10-08 10:19 ` pault at gcc dot gnu.org
  2012-02-19 20:23 ` tkoenig at gcc dot gnu.org
  2012-06-29 18:09 ` mikael at gcc dot gnu.org
  11 siblings, 0 replies; 13+ messages in thread
From: pault at gcc dot gnu.org @ 2011-10-08 10:19 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #10 from Paul Thomas <pault at gcc dot gnu.org> 2011-10-08 10:18:56 UTC ---
Author: pault
Date: Sat Oct  8 10:18:51 2011
New Revision: 179710

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=179710
Log:
2011-10-08  Paul Thomas  <pault@gcc.gnu.org>

    PR fortran/47844
    * trans-array.c (gfc_conv_array_index_offset): Use descriptor
    stride for pointer function results.

2011-10-08  Paul Thomas  <pault@gcc.gnu.org>

    PR fortran/47844
    * gfortran.dg/pointer_function_result_1.f90 : New test.

Added:
    trunk/gcc/testsuite/gfortran.dg/pointer_function_result_1.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/trans-array.c
    trunk/gcc/testsuite/ChangeLog


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

* [Bug fortran/47844] Array stride ignored for pointer-valued function results
  2011-02-22  7:07 [Bug fortran/47844] New: Pointer-valued function: Provide wrong result when dereferenced automatically after list-write Kdx1999 at gmail dot com
                   ` (9 preceding siblings ...)
  2011-10-08 10:19 ` pault at gcc dot gnu.org
@ 2012-02-19 20:23 ` tkoenig at gcc dot gnu.org
  2012-06-29 18:09 ` mikael at gcc dot gnu.org
  11 siblings, 0 replies; 13+ messages in thread
From: tkoenig at gcc dot gnu.org @ 2012-02-19 20:23 UTC (permalink / raw)
  To: gcc-bugs

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

Thomas Koenig <tkoenig at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|NEW                         |WAITING
                 CC|                            |tkoenig at gcc dot gnu.org

--- Comment #11 from Thomas Koenig <tkoenig at gcc dot gnu.org> 2012-02-19 20:02:31 UTC ---
Is this fixed now?

>From the comments, it seems that we can close this.


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

* [Bug fortran/47844] Array stride ignored for pointer-valued function results
  2011-02-22  7:07 [Bug fortran/47844] New: Pointer-valued function: Provide wrong result when dereferenced automatically after list-write Kdx1999 at gmail dot com
                   ` (10 preceding siblings ...)
  2012-02-19 20:23 ` tkoenig at gcc dot gnu.org
@ 2012-06-29 18:09 ` mikael at gcc dot gnu.org
  11 siblings, 0 replies; 13+ messages in thread
From: mikael at gcc dot gnu.org @ 2012-06-29 18:09 UTC (permalink / raw)
  To: gcc-bugs

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

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

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|WAITING                     |RESOLVED
                 CC|                            |mikael at gcc dot gnu.org
         Resolution|                            |FIXED

--- Comment #12 from Mikael Morin <mikael at gcc dot gnu.org> 2012-06-29 18:08:42 UTC ---
(In reply to comment #11)
> Is this fixed now?
> 
> From the comments, it seems that we can close this.

I assume we can. At least the original problem, comment #2 and #3 work fine
now.


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

end of thread, other threads:[~2012-06-29 18:09 UTC | newest]

Thread overview: 13+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2011-02-22  7:07 [Bug fortran/47844] New: Pointer-valued function: Provide wrong result when dereferenced automatically after list-write Kdx1999 at gmail dot com
2011-02-22  8:37 ` [Bug fortran/47844] " burnus at gcc dot gnu.org
2011-02-22 15:35 ` [Bug fortran/47844] I/O: data transfer statement: Array stride ignored for pointer-valued function results burnus at gcc dot gnu.org
2011-03-01 13:20 ` [Bug fortran/47844] " burnus at gcc dot gnu.org
2011-10-05 10:02 ` dominiq at lps dot ens.fr
2011-10-05 10:22 ` pault at gcc dot gnu.org
2011-10-05 14:36 ` paul.richard.thomas at gmail dot com
2011-10-05 15:04 ` burnus at gcc dot gnu.org
2011-10-05 21:40 ` dominiq at lps dot ens.fr
2011-10-05 22:20 ` pault at gcc dot gnu.org
2011-10-08 10:19 ` pault at gcc dot gnu.org
2012-02-19 20:23 ` tkoenig at gcc dot gnu.org
2012-06-29 18:09 ` mikael 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).