public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/38863]  New: WHERE with multiple elemental defined assignments gives wrong answer
@ 2009-01-15 21:36 dick dot hendrickson at gmail dot com
  2009-01-18 20:40 ` [Bug fortran/38863] " mikael at gcc dot gnu dot org
                   ` (18 more replies)
  0 siblings, 19 replies; 20+ messages in thread
From: dick dot hendrickson at gmail dot com @ 2009-01-15 21:36 UTC (permalink / raw)
  To: gcc-bugs

The following program gives the wrong answers from the WHERE block.  The
expected answers are in the tda2l array.  The problem seems to be an
interaction between the dimension statements, the defined logical assignment
and the defined integer assignment statement in the WHERE block.  

The defined assignment to the logical component of TLA2L is correct (it's
effectively a do nothing assignment, since the left and right hand sides are
the same elements).  The defined assignment to the integer component is wrong. 
Changing the dimension of TDA2L from (3,2) to (nf3,nf2) gives a different
incorrect answer.  (TDA2L is not used in any of the computations, it's just a
handy way to keep track of the expected answer).  Changing the dimension of
TLA2L from (nf3,nf2) to (3,2) fixes the problem.  Commenting out the assignment
to TLA2L%L in the WHERE gives the correct answer.

Dick Hendrickson


      module rg0045_stuff

! fails on Windows XP
! gcc version 4.4.0 20081219 (experimental) [trunk revision 142842] (GCC)


      TYPE UNSEQ

        INTEGER                       ::  I
        LOGICAL                       ::  L

      END TYPE UNSEQ       

      INTERFACE ASSIGNMENT(=)
        MODULE PROCEDURE L_TO_T,   I_TO_T
      END INTERFACE ASSIGNMENT(=)

      contains

        PURE ELEMENTAL SUBROUTINE Z_TO_T(OUT,ZIN)
        COMPLEX,INTENT(IN)  ::  ZIN
        INTEGER,INTENT(IN)  ::  IIN
        LOGICAL,INTENT(IN)  ::  LIN
        TYPE (UNSEQ), INTENT(INOUT) ::  OUT

        OUT%i = -99
        RETURN

        ENTRY I_TO_T(OUT,IIN)
        OUT%I = IIN
        RETURN

        ENTRY L_TO_T(OUT,LIN)
        OUT%L = LIN
        RETURN

        END SUBROUTINE


      SUBROUTINE RG0045(nf1,nf2,nf3)

      TYPE(UNSEQ) TLA2L(nf3,nf2)   !changing dimension to (3,2) fixes problem
      TYPE(UNSEQ) TDA2L(3,2)       !changing dimension to (nf3,nf2) changes
output
      logical  lda(nf3,nf2)

!expected results
      tda2l(1:3,1)%l = (/.true.,.false.,.true./)
      tda2l(1:3,2)%l = (/.false.,.true.,.false./)
      tda2l(1:3,1)%i = (/1,-1,3/)
      tda2l(1:3,2)%i = (/-1,5,-1/)


      lda = tda2l%l

      tLa2l%l = lda
      tLa2l(1:3,1)%i = (/1,2,3/)
      tLa2l(1:3,2)%i = (/4,5,6/)


      WHERE(LDA)
        TLA2L = TLA2L(1:3,1:2)%L     !removing this line fixes problem
        TLA2L = TLA2L(1:3,1:2)%I
      ELSEWHERE
        TLA2L = -1
      ENDWHERE

      print *, tla2l%i
      print *, tda2l%i

      print *, tla2l%l
      print *, tda2l%l

      END SUBROUTINE
      end module rg0045_stuff

      program try_rg0045
      use rg0045_stuff

      call rg0045(1,2,3)

      end

from the above program
C:gfortran>gfortran try_rg0045.f
C:\gfortran>a
           3          -1        8192          -1           0          -1
           1          -1           3          -1           5          -1
 T F T F T F
 T F T F T F

with the tda2l array dimensioned (nf3,nf2)
C:gfortran>gfortran try_rg0045.f

C:\gfortran>a
           0          -1     4063608          -1          -1          -1
           1          -1           3          -1           5          -1
 T F T F T F
 T F T F T F

With the logical assignment commented out
C:gfortran>gfortran try_rg0045.f

C:\gfortran>a
           1          -1           3          -1           5          -1
           1          -1           3          -1           5          -1
 T F T F T F
 T F T F T F


with constant (3,2) array dimensions and the logical assignment left in
C:\gfortran>gfortran try_rg0045.f

C:\gfortran>a
           1          -1           3          -1           5          -1
           1          -1           3          -1           5          -1
 T F T F T F
 T F T F T F


-- 
           Summary: WHERE with multiple elemental defined assignments gives
                    wrong answer
           Product: gcc
           Version: 4.4.0
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: dick dot hendrickson at gmail dot com


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


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

* [Bug fortran/38863] WHERE with multiple elemental defined assignments gives wrong answer
  2009-01-15 21:36 [Bug fortran/38863] New: WHERE with multiple elemental defined assignments gives wrong answer dick dot hendrickson at gmail dot com
@ 2009-01-18 20:40 ` mikael at gcc dot gnu dot org
  2009-01-18 21:37 ` dick dot hendrickson at gmail dot com
                   ` (17 subsequent siblings)
  18 siblings, 0 replies; 20+ messages in thread
From: mikael at gcc dot gnu dot org @ 2009-01-18 20:40 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #1 from mikael at gcc dot gnu dot org  2009-01-18 20:40 -------
I suspect the following  is invalid as the arguments to the defined assignment
alias. 

      WHERE(LDA)
        TLA2L = TLA2L(1:3,1:2)%L     !removing this line fixes problem
        TLA2L = TLA2L(1:3,1:2)%I
      ELSEWHERE
        TLA2L = -1
      ENDWHERE

However, the following is valid (I think):

     module m

     type t
        integer :: i,j
     end type t

     interface assignment (=)
             procedure i_to_t
     end interface

     contains 

     elemental subroutine i_to_t (p, q)

     type(t), intent(out) :: p
     integer, intent(in)  :: q

     p%i = q

     end subroutine

     end module

     use m

     type(t), target :: a(3)
     type(t), target  :: b(3)

     type(t), dimension(:), pointer :: p
     logical :: l(3)

     a%i = 1
     a%j = 2
     b%i = 3
     b%j = 4

     p => b
     l = .true.


     where (l)
          a = p%i
     end where

     print *, a%j

     end

The output I get is:
       32758       32758           0
instead of:
           2           2           2


The problem is that we create a temporary for the defined assignment, but we
don't copy the values of the lhs (before calling the function) to it as they
will be overwritten by the rhs's ones. However, if the assignment function
doesn't set all the members of the derived type, the unset members keep the
values of the temporary, and are copied to the lhs. 
Thus, confirmed


-- 

mikael at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |NEW
     Ever Confirmed|0                           |1
           Keywords|                            |wrong-code
   Last reconfirmed|0000-00-00 00:00:00         |2009-01-18 20:40:05
               date|                            |


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


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

* [Bug fortran/38863] WHERE with multiple elemental defined assignments gives wrong answer
  2009-01-15 21:36 [Bug fortran/38863] New: WHERE with multiple elemental defined assignments gives wrong answer dick dot hendrickson at gmail dot com
  2009-01-18 20:40 ` [Bug fortran/38863] " mikael at gcc dot gnu dot org
@ 2009-01-18 21:37 ` dick dot hendrickson at gmail dot com
  2009-01-19 22:18 ` mikael at gcc dot gnu dot org
                   ` (16 subsequent siblings)
  18 siblings, 0 replies; 20+ messages in thread
From: dick dot hendrickson at gmail dot com @ 2009-01-18 21:37 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #2 from dick dot hendrickson at gmail dot com  2009-01-18 21:37 -------
Subject: Re:  WHERE with multiple elemental defined assignments gives wrong
answer

On Sun, Jan 18, 2009 at 2:40 PM, mikael at gcc dot gnu dot org
<gcc-bugzilla@gcc.gnu.org> wrote:
>
>
> ------- Comment #1 from mikael at gcc dot gnu dot org  2009-01-18 20:40 -------
> I suspect the following  is invalid as the arguments to the defined assignment
> alias.
>

Why do you think it is invalid?  I cut this down from a larger program, but the
arguments look good to me.  For what it's worth, the test case compiles
successfully with a different compiler.  The larger program compiles with
several other compilers.

Dick Hendrickson

>      WHERE(LDA)
>        TLA2L = TLA2L(1:3,1:2)%L     !removing this line fixes problem
>        TLA2L = TLA2L(1:3,1:2)%I
>      ELSEWHERE
>        TLA2L = -1
>      ENDWHERE
>
> However, the following is valid (I think):
>
>     module m
>
>     type t
>        integer :: i,j
>     end type t
>
>     interface assignment (=)
>             procedure i_to_t
>     end interface
>
>     contains
>
>     elemental subroutine i_to_t (p, q)
>
>     type(t), intent(out) :: p
>     integer, intent(in)  :: q
>
>     p%i = q
>
>     end subroutine
>
>     end module
>
>     use m
>
>     type(t), target :: a(3)
>     type(t), target  :: b(3)
>
>     type(t), dimension(:), pointer :: p
>     logical :: l(3)
>
>     a%i = 1
>     a%j = 2
>     b%i = 3
>     b%j = 4
>
>     p => b
>     l = .true.
>
>
>     where (l)
>          a = p%i
>     end where
>
>     print *, a%j
>
>     end
>
> The output I get is:
>       32758       32758           0
> instead of:
>           2           2           2
>
>
> The problem is that we create a temporary for the defined assignment, but we
> don't copy the values of the lhs (before calling the function) to it as they
> will be overwritten by the rhs's ones. However, if the assignment function
> doesn't set all the members of the derived type, the unset members keep the
> values of the temporary, and are copied to the lhs.
> Thus, confirmed
>
>
> --
>
> mikael at gcc dot gnu dot org changed:
>
>           What    |Removed                     |Added
> ----------------------------------------------------------------------------
>             Status|UNCONFIRMED                 |NEW
>     Ever Confirmed|0                           |1
>           Keywords|                            |wrong-code
>   Last reconfirmed|0000-00-00 00:00:00         |2009-01-18 20:40:05
>               date|                            |
>
>
> http://gcc.gnu.org/bugzilla/show_bug.cgi?id=38863
>
> ------- You are receiving this mail because: -------
> You reported the bug, or are watching the reporter.
>


-- 


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


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

* [Bug fortran/38863] WHERE with multiple elemental defined assignments gives wrong answer
  2009-01-15 21:36 [Bug fortran/38863] New: WHERE with multiple elemental defined assignments gives wrong answer dick dot hendrickson at gmail dot com
  2009-01-18 20:40 ` [Bug fortran/38863] " mikael at gcc dot gnu dot org
  2009-01-18 21:37 ` dick dot hendrickson at gmail dot com
@ 2009-01-19 22:18 ` mikael at gcc dot gnu dot org
  2009-01-19 22:31 ` dick dot hendrickson at gmail dot com
                   ` (15 subsequent siblings)
  18 siblings, 0 replies; 20+ messages in thread
From: mikael at gcc dot gnu dot org @ 2009-01-19 22:18 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #3 from mikael at gcc dot gnu dot org  2009-01-19 22:18 -------
> > I suspect the following  is invalid as the arguments to the defined assignment
> > alias.
> >
> 
> Why do you think it is invalid?  
Because the arguments to the i_to_t (or l_to_t) alias. They point to the same
data. 
I may be wrong however (actually it wouldn't be the first time when arguing
about standard conformance). I'm sure it is wrong with basic subroutines, but
mixing that with where, elemental and defined assignment doesn't make it clear. 

> For what it's worth, the test case compiles
> successfully with a different compiler.  The larger program compiles with
> several other compilers.
And it compiles with gfortran too ;). 


-- 


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


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

* [Bug fortran/38863] WHERE with multiple elemental defined assignments gives wrong answer
  2009-01-15 21:36 [Bug fortran/38863] New: WHERE with multiple elemental defined assignments gives wrong answer dick dot hendrickson at gmail dot com
                   ` (2 preceding siblings ...)
  2009-01-19 22:18 ` mikael at gcc dot gnu dot org
@ 2009-01-19 22:31 ` dick dot hendrickson at gmail dot com
  2009-02-03  8:55 ` pault at gcc dot gnu dot org
                   ` (14 subsequent siblings)
  18 siblings, 0 replies; 20+ messages in thread
From: dick dot hendrickson at gmail dot com @ 2009-01-19 22:31 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #4 from dick dot hendrickson at gmail dot com  2009-01-19 22:31 -------
Subject: Re:  WHERE with multiple elemental defined assignments gives wrong
answer

On Mon, Jan 19, 2009 at 4:18 PM, mikael at gcc dot gnu dot org
<gcc-bugzilla@gcc.gnu.org> wrote:
>
>
> ------- Comment #3 from mikael at gcc dot gnu dot org  2009-01-19 22:18 -------
>> > I suspect the following  is invalid as the arguments to the defined assignment
>> > alias.
>> >
>>
>> Why do you think it is invalid?
> Because the arguments to the i_to_t (or l_to_t) alias. They point to the same
> data.
> I may be wrong however (actually it wouldn't be the first time when arguing
> about standard conformance). I'm sure it is wrong with basic subroutines, but
> mixing that with where, elemental and defined assignment doesn't make it clear.

Defined assignment is sort of a special case.  A statement like

      A = B

is equivalent to
    CALL DEFINED_ROUTINE ( A, (B) )

The "extra" parenthesis allow something like

      A = A

to work like

    CALL DEFINED_ROUTINE ( A, (A)  )

and it is legal for the first argument to be intent(out) since the first
and second arguments are different.   See 12.3.2.1.2 in F95

Dick Hendrickson


>
>> For what it's worth, the test case compiles
>> successfully with a different compiler.  The larger program compiles with
>> several other compilers.
> And it compiles with gfortran too ;).
>
>
> --
>
>
> http://gcc.gnu.org/bugzilla/show_bug.cgi?id=38863
>
> ------- You are receiving this mail because: -------
> You reported the bug, or are watching the reporter.
>


-- 


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


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

* [Bug fortran/38863] WHERE with multiple elemental defined assignments gives wrong answer
  2009-01-15 21:36 [Bug fortran/38863] New: WHERE with multiple elemental defined assignments gives wrong answer dick dot hendrickson at gmail dot com
                   ` (3 preceding siblings ...)
  2009-01-19 22:31 ` dick dot hendrickson at gmail dot com
@ 2009-02-03  8:55 ` pault at gcc dot gnu dot org
  2009-02-03 19:59 ` pault at gcc dot gnu dot org
                   ` (13 subsequent siblings)
  18 siblings, 0 replies; 20+ messages in thread
From: pault at gcc dot gnu dot org @ 2009-02-03  8:55 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #5 from pault at gcc dot gnu dot org  2009-02-03 08:55 -------
(In reply to comment #4)

I would have said that the value of the integer component after the first
assignment is, at best, ill-defined. If L_TO_T assigns a value to it, gfortran
gives the same result as any other compiler.

> >> For what it's worth, the test case compiles
> >> successfully with a different compiler.  The larger program compiles with
> >> several other compilers.
> > And it compiles with gfortran too ;).

Indeed, all this is so.  Regardless of the legality of the testcase, this
highlights that gfortran is being too conservative in its dependency analysis
and is using a temporary in the WHERE assignements unnecessarily.  There is an
error of logic in gfc_dep_resolver that I haven't quite caught yet.  It has all
the hooks needed to detect that implicit and explicit full arrays are the same
but it is not working (remove the rhs array reference from the first assignment
and gfortran gets the "right" result).

Cheers

Paul

PS I might as well take it!


-- 

pault at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
         AssignedTo|unassigned at gcc dot gnu   |pault at gcc dot gnu dot org
                   |dot org                     |
             Status|NEW                         |ASSIGNED
   Last reconfirmed|2009-01-18 20:40:05         |2009-02-03 08:55:19
               date|                            |


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


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

* [Bug fortran/38863] WHERE with multiple elemental defined assignments gives wrong answer
  2009-01-15 21:36 [Bug fortran/38863] New: WHERE with multiple elemental defined assignments gives wrong answer dick dot hendrickson at gmail dot com
                   ` (4 preceding siblings ...)
  2009-02-03  8:55 ` pault at gcc dot gnu dot org
@ 2009-02-03 19:59 ` pault at gcc dot gnu dot org
  2009-04-06 20:14 ` pault at gcc dot gnu dot org
                   ` (12 subsequent siblings)
  18 siblings, 0 replies; 20+ messages in thread
From: pault at gcc dot gnu dot org @ 2009-02-03 19:59 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #6 from pault at gcc dot gnu dot org  2009-02-03 19:59 -------
I have just realised that this is a case of complete overlap that we miss
completely in dependency analysis:

If one of the lhs or rhs is a full array, the stride is unity and one of lbound
== start or ubound == end, then the arrays overlap.

I feel a fix coming on....

Paul


-- 


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


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

* [Bug fortran/38863] WHERE with multiple elemental defined assignments gives wrong answer
  2009-01-15 21:36 [Bug fortran/38863] New: WHERE with multiple elemental defined assignments gives wrong answer dick dot hendrickson at gmail dot com
                   ` (5 preceding siblings ...)
  2009-02-03 19:59 ` pault at gcc dot gnu dot org
@ 2009-04-06 20:14 ` pault at gcc dot gnu dot org
  2009-04-06 20:17 ` pault at gcc dot gnu dot org
                   ` (11 subsequent siblings)
  18 siblings, 0 replies; 20+ messages in thread
From: pault at gcc dot gnu dot org @ 2009-04-06 20:14 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #7 from pault at gcc dot gnu dot org  2009-04-06 20:13 -------
Subject: Bug 38863

Author: pault
Date: Mon Apr  6 20:13:39 2009
New Revision: 145621

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=145621
Log:
2009-04-06  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/38863
        * dependency.c (ref_same_as_full_array): New function.
        (gfc_dep_resolver): Call it.

2009-04-06  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/38863
        * gfortran.dg/dependency_23.f90: New test.

Added:
    trunk/gcc/testsuite/gfortran.dg/dependency_23.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/dependency.c
    trunk/gcc/testsuite/ChangeLog


-- 


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


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

* [Bug fortran/38863] WHERE with multiple elemental defined assignments gives wrong answer
  2009-01-15 21:36 [Bug fortran/38863] New: WHERE with multiple elemental defined assignments gives wrong answer dick dot hendrickson at gmail dot com
                   ` (6 preceding siblings ...)
  2009-04-06 20:14 ` pault at gcc dot gnu dot org
@ 2009-04-06 20:17 ` pault at gcc dot gnu dot org
  2009-04-07 21:03 ` dominiq at lps dot ens dot fr
                   ` (10 subsequent siblings)
  18 siblings, 0 replies; 20+ messages in thread
From: pault at gcc dot gnu dot org @ 2009-04-06 20:17 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #8 from pault at gcc dot gnu dot org  2009-04-06 20:17 -------
Fixed on trunk.

Thanks for the report

Paul


-- 

pault at gcc dot gnu dot org changed:

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


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


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

* [Bug fortran/38863] WHERE with multiple elemental defined assignments gives wrong answer
  2009-01-15 21:36 [Bug fortran/38863] New: WHERE with multiple elemental defined assignments gives wrong answer dick dot hendrickson at gmail dot com
                   ` (7 preceding siblings ...)
  2009-04-06 20:17 ` pault at gcc dot gnu dot org
@ 2009-04-07 21:03 ` dominiq at lps dot ens dot fr
  2009-04-08  4:33 ` burnus at gcc dot gnu dot org
                   ` (9 subsequent siblings)
  18 siblings, 0 replies; 20+ messages in thread
From: dominiq at lps dot ens dot fr @ 2009-04-07 21:03 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #9 from dominiq at lps dot ens dot fr  2009-04-07 21:02 -------
The code in comment #1 still does not give the right result. I get
(intel-darwin):

[ibook-dhum] f90/bug% gfc pr38863_1.f90
[ibook-dhum] f90/bug% a.out
       12288 -1880941592 -1073751380
[ibook-dhum] f90/bug% gfc -O3 pr38863_1.f90
[ibook-dhum] f90/bug% a.out
           0           0           0
[ibook-dhum] f90/bug% gfc -m64 pr38863_1.f90
[ibook-dhum] f90/bug% a.out
           1           1           0
[ibook-dhum] f90/bug% gfc -m64 -O3 pr38863_1.f90
[ibook-dhum] f90/bug% a.out
       65280           0        -256

instead of

[ibook-dhum] f90/bug% bg95 pr38863_1.f90
[ibook-dhum] f90/bug% a.out 
 2 2 2


-- 


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


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

* [Bug fortran/38863] WHERE with multiple elemental defined assignments gives wrong answer
  2009-01-15 21:36 [Bug fortran/38863] New: WHERE with multiple elemental defined assignments gives wrong answer dick dot hendrickson at gmail dot com
                   ` (8 preceding siblings ...)
  2009-04-07 21:03 ` dominiq at lps dot ens dot fr
@ 2009-04-08  4:33 ` burnus at gcc dot gnu dot org
  2009-04-08  8:59 ` pault at gcc dot gnu dot org
                   ` (8 subsequent siblings)
  18 siblings, 0 replies; 20+ messages in thread
From: burnus at gcc dot gnu dot org @ 2009-04-08  4:33 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #10 from burnus at gcc dot gnu dot org  2009-04-08 04:32 -------
Reopen based on comment #9.


-- 

burnus at gcc dot gnu dot org changed:

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


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


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

* [Bug fortran/38863] WHERE with multiple elemental defined assignments gives wrong answer
  2009-01-15 21:36 [Bug fortran/38863] New: WHERE with multiple elemental defined assignments gives wrong answer dick dot hendrickson at gmail dot com
                   ` (9 preceding siblings ...)
  2009-04-08  4:33 ` burnus at gcc dot gnu dot org
@ 2009-04-08  8:59 ` pault at gcc dot gnu dot org
  2009-04-08 11:57 ` dominiq at lps dot ens dot fr
                   ` (7 subsequent siblings)
  18 siblings, 0 replies; 20+ messages in thread
From: pault at gcc dot gnu dot org @ 2009-04-08  8:59 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #11 from pault at gcc dot gnu dot org  2009-04-08 08:59 -------
Subject: Bug 38863

Author: pault
Date: Wed Apr  8 08:59:34 2009
New Revision: 145714

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

        PR fortran/38863
        * trans-array.c (gfc_trans_deferred_array): Return if this
        is a result variable.

2009-04-08  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/38863
        * gfortran.dg/alloc_comp_result_1.f90: New test.


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


-- 


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


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

* [Bug fortran/38863] WHERE with multiple elemental defined assignments gives wrong answer
  2009-01-15 21:36 [Bug fortran/38863] New: WHERE with multiple elemental defined assignments gives wrong answer dick dot hendrickson at gmail dot com
                   ` (10 preceding siblings ...)
  2009-04-08  8:59 ` pault at gcc dot gnu dot org
@ 2009-04-08 11:57 ` dominiq at lps dot ens dot fr
  2009-04-10 14:27 ` pault at gcc dot gnu dot org
                   ` (6 subsequent siblings)
  18 siblings, 0 replies; 20+ messages in thread
From: dominiq at lps dot ens dot fr @ 2009-04-08 11:57 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #12 from dominiq at lps dot ens dot fr  2009-04-08 11:57 -------
Comment #11 should probably go to PR38802.


-- 


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


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

* [Bug fortran/38863] WHERE with multiple elemental defined assignments gives wrong answer
  2009-01-15 21:36 [Bug fortran/38863] New: WHERE with multiple elemental defined assignments gives wrong answer dick dot hendrickson at gmail dot com
                   ` (11 preceding siblings ...)
  2009-04-08 11:57 ` dominiq at lps dot ens dot fr
@ 2009-04-10 14:27 ` pault at gcc dot gnu dot org
  2009-04-10 19:07 ` pault at gcc dot gnu dot org
                   ` (5 subsequent siblings)
  18 siblings, 0 replies; 20+ messages in thread
From: pault at gcc dot gnu dot org @ 2009-04-10 14:27 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #13 from pault at gcc dot gnu dot org  2009-04-10 14:27 -------
(In reply to comment #12)
> Comment #11 should probably go to PR38802.
> 
Indeed - sorry.

Paul


-- 


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


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

* [Bug fortran/38863] WHERE with multiple elemental defined assignments gives wrong answer
  2009-01-15 21:36 [Bug fortran/38863] New: WHERE with multiple elemental defined assignments gives wrong answer dick dot hendrickson at gmail dot com
                   ` (12 preceding siblings ...)
  2009-04-10 14:27 ` pault at gcc dot gnu dot org
@ 2009-04-10 19:07 ` pault at gcc dot gnu dot org
  2009-04-14 15:16 ` domob at gcc dot gnu dot org
                   ` (4 subsequent siblings)
  18 siblings, 0 replies; 20+ messages in thread
From: pault at gcc dot gnu dot org @ 2009-04-10 19:07 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #14 from pault at gcc dot gnu dot org  2009-04-10 19:06 -------

(In reply to comment #9)
> The code in comment #1 still does not give the right result. I get
> (intel-darwin):

No, it's not right.  We have seen this before with module assignments involving
derived types.

It should be noted that this is an entirely different bug to the original one. 
In the case of the first, the dependency was missed.  In this second, it is
detected OK but the components of the lhs that are not assigned to by the
module procedure are left indeterminate.

Daniel, I expect this looks familiar????

Cheers

Paul


-- 

pault at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |d at domob dot eu


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


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

* [Bug fortran/38863] WHERE with multiple elemental defined assignments gives wrong answer
  2009-01-15 21:36 [Bug fortran/38863] New: WHERE with multiple elemental defined assignments gives wrong answer dick dot hendrickson at gmail dot com
                   ` (13 preceding siblings ...)
  2009-04-10 19:07 ` pault at gcc dot gnu dot org
@ 2009-04-14 15:16 ` domob at gcc dot gnu dot org
  2009-04-30 17:03 ` pault at gcc dot gnu dot org
                   ` (3 subsequent siblings)
  18 siblings, 0 replies; 20+ messages in thread
From: domob at gcc dot gnu dot org @ 2009-04-14 15:16 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #15 from domob at gcc dot gnu dot org  2009-04-14 15:16 -------
(In reply to comment #14)
> In the case of the first, the dependency was missed.  In this second, it is
> detected OK but the components of the lhs that are not assigned to by the
> module procedure are left indeterminate.
> 
> Daniel, I expect this looks familiar????

Yes, it does... somewhat.  I'll try to find something out about this one,
though I've so far no idea (apart from that it looks similar :D).

Daniel


-- 


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


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

* [Bug fortran/38863] WHERE with multiple elemental defined assignments gives wrong answer
  2009-01-15 21:36 [Bug fortran/38863] New: WHERE with multiple elemental defined assignments gives wrong answer dick dot hendrickson at gmail dot com
                   ` (14 preceding siblings ...)
  2009-04-14 15:16 ` domob at gcc dot gnu dot org
@ 2009-04-30 17:03 ` pault at gcc dot gnu dot org
  2009-05-10  7:24 ` pault at gcc dot gnu dot org
                   ` (2 subsequent siblings)
  18 siblings, 0 replies; 20+ messages in thread
From: pault at gcc dot gnu dot org @ 2009-04-30 17:03 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #16 from pault at gcc dot gnu dot org  2009-04-30 17:03 -------
module m
  type t
    integer :: i,j
  end type t
  interface assignment (=)
    module procedure i_to_t
  end interface
contains 
  elemental subroutine i_to_t (p, q)
    type(t), intent(out) :: p
    integer, intent(in)  :: q
    p%i = q
  end subroutine
end module

  use m
  type(t), target :: a(3)
  type(t), target  :: b(3)
  type(t), dimension(:), pointer :: p

  a%i = 1
  a%j = 2
  b%i = 3
  b%j = 4

  p => b
  a = p%i
  print *, a%j
end

Also shows the fault, so it's not just restricted to WHERE assignments.  It's
interesting to note that in this case, the dependency is due to the possibility
of aliasing and is, in fact, not present.

I can see easily how to fix it for the case here but have not quite clocked how
to do comment#1 yet.

Paul


-- 


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


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

* [Bug fortran/38863] WHERE with multiple elemental defined assignments gives wrong answer
  2009-01-15 21:36 [Bug fortran/38863] New: WHERE with multiple elemental defined assignments gives wrong answer dick dot hendrickson at gmail dot com
                   ` (15 preceding siblings ...)
  2009-04-30 17:03 ` pault at gcc dot gnu dot org
@ 2009-05-10  7:24 ` pault at gcc dot gnu dot org
  2009-05-10  8:56 ` pault at gcc dot gnu dot org
  2009-05-10 15:35 ` pault at gcc dot gnu dot org
  18 siblings, 0 replies; 20+ messages in thread
From: pault at gcc dot gnu dot org @ 2009-05-10  7:24 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #17 from pault at gcc dot gnu dot org  2009-05-10 07:23 -------
Subject: Bug 38863

Author: pault
Date: Sun May 10 07:23:30 2009
New Revision: 147329

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

        PR fortran/38863
        * trans-expr.c (gfc_conv_operator_assign): Remove function.
        * trans.h : Remove prototype for gfc_conv_operator_assign.
        * trans-stmt.c (gfc_conv_elemental_dependencies): Initialize
        derivde types with intent(out).
        (gfc_trans_call): Add mask, count1 and invert arguments. Add
        code to use mask for WHERE assignments.
        (gfc_trans_forall_1): Use new arguments for gfc_trans_call.
        (gfc_trans_where_assign): The gfc_symbol argument is replaced
        by the corresponding code. If this has a resolved_sym, then
        gfc_trans_call is called. The call to gfc_conv_operator_assign
        is removed.
        (gfc_trans_where_2): Change the last argument in the call to
        gfc_trans_where_assign.
        * trans-stmt.h : Modify prototype for gfc_trans_call.
        * trans.c (gfc_trans_code): Use new args for gfc_trans_call.

2009-05-10  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/38863
        * gfortran.dg/dependency_24.f90: New test.
        * gfortran.dg/dependency_23.f90: Clean up module files.

Added:
    trunk/gcc/testsuite/gfortran.dg/dependency_23.f90.rej
    trunk/gcc/testsuite/gfortran.dg/dependency_24.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/trans-expr.c
    trunk/gcc/fortran/trans-stmt.c
    trunk/gcc/fortran/trans-stmt.h
    trunk/gcc/fortran/trans.c
    trunk/gcc/fortran/trans.h
    trunk/gcc/testsuite/ChangeLog
    trunk/gcc/testsuite/gfortran.dg/dependency_23.f90


-- 


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


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

* [Bug fortran/38863] WHERE with multiple elemental defined assignments gives wrong answer
  2009-01-15 21:36 [Bug fortran/38863] New: WHERE with multiple elemental defined assignments gives wrong answer dick dot hendrickson at gmail dot com
                   ` (16 preceding siblings ...)
  2009-05-10  7:24 ` pault at gcc dot gnu dot org
@ 2009-05-10  8:56 ` pault at gcc dot gnu dot org
  2009-05-10 15:35 ` pault at gcc dot gnu dot org
  18 siblings, 0 replies; 20+ messages in thread
From: pault at gcc dot gnu dot org @ 2009-05-10  8:56 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #18 from pault at gcc dot gnu dot org  2009-05-10 08:56 -------
Problem in comment #1 is fixed on trunk.

Cheers

Paul


-- 

pault at gcc dot gnu dot org changed:

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


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


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

* [Bug fortran/38863] WHERE with multiple elemental defined assignments gives wrong answer
  2009-01-15 21:36 [Bug fortran/38863] New: WHERE with multiple elemental defined assignments gives wrong answer dick dot hendrickson at gmail dot com
                   ` (17 preceding siblings ...)
  2009-05-10  8:56 ` pault at gcc dot gnu dot org
@ 2009-05-10 15:35 ` pault at gcc dot gnu dot org
  18 siblings, 0 replies; 20+ messages in thread
From: pault at gcc dot gnu dot org @ 2009-05-10 15:35 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #19 from pault at gcc dot gnu dot org  2009-05-10 15:35 -------
Subject: Bug 38863

Author: pault
Date: Sun May 10 15:34:55 2009
New Revision: 147345

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

        PR fortran/38863
        * trans-expr.c (gfc_conv_operator_assign): Remove function.
        * trans.h : Remove prototype for gfc_conv_operator_assign.
        * trans-stmt.c (gfc_conv_elemental_dependencies): Initialize
        derivde types with intent(out).
        (gfc_trans_call): Add mask, count1 and invert arguments. Add
        code to use mask for WHERE assignments.
        (gfc_trans_forall_1): Use new arguments for gfc_trans_call.
        (gfc_trans_where_assign): The gfc_symbol argument is replaced
        by the corresponding code. If this has a resolved_sym, then
        gfc_trans_call is called. The call to gfc_conv_operator_assign
        is removed.
        (gfc_trans_where_2): Change the last argument in the call to
        gfc_trans_where_assign.
        * trans-stmt.h : Modify prototype for gfc_trans_call.
        * trans.c (gfc_trans_code): Use new args for gfc_trans_call.

2009-05-10  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/38863
        * gfortran.dg/dependency_24.f90: New test.

Added:
    branches/gcc-4_4-branch/gcc/testsuite/gfortran.dg/dependency_24.f90
Modified:
    branches/gcc-4_4-branch/gcc/fortran/ChangeLog
    branches/gcc-4_4-branch/gcc/fortran/trans-expr.c
    branches/gcc-4_4-branch/gcc/fortran/trans-stmt.c
    branches/gcc-4_4-branch/gcc/fortran/trans-stmt.h
    branches/gcc-4_4-branch/gcc/fortran/trans.c
    branches/gcc-4_4-branch/gcc/fortran/trans.h
    branches/gcc-4_4-branch/gcc/testsuite/ChangeLog


-- 


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


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

end of thread, other threads:[~2009-05-10 15:35 UTC | newest]

Thread overview: 20+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2009-01-15 21:36 [Bug fortran/38863] New: WHERE with multiple elemental defined assignments gives wrong answer dick dot hendrickson at gmail dot com
2009-01-18 20:40 ` [Bug fortran/38863] " mikael at gcc dot gnu dot org
2009-01-18 21:37 ` dick dot hendrickson at gmail dot com
2009-01-19 22:18 ` mikael at gcc dot gnu dot org
2009-01-19 22:31 ` dick dot hendrickson at gmail dot com
2009-02-03  8:55 ` pault at gcc dot gnu dot org
2009-02-03 19:59 ` pault at gcc dot gnu dot org
2009-04-06 20:14 ` pault at gcc dot gnu dot org
2009-04-06 20:17 ` pault at gcc dot gnu dot org
2009-04-07 21:03 ` dominiq at lps dot ens dot fr
2009-04-08  4:33 ` burnus at gcc dot gnu dot org
2009-04-08  8:59 ` pault at gcc dot gnu dot org
2009-04-08 11:57 ` dominiq at lps dot ens dot fr
2009-04-10 14:27 ` pault at gcc dot gnu dot org
2009-04-10 19:07 ` pault at gcc dot gnu dot org
2009-04-14 15:16 ` domob at gcc dot gnu dot org
2009-04-30 17:03 ` pault at gcc dot gnu dot org
2009-05-10  7:24 ` pault at gcc dot gnu dot org
2009-05-10  8:56 ` pault at gcc dot gnu dot org
2009-05-10 15:35 ` pault 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).