public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/30407]  New: Compilation errors on valid code
@ 2007-01-08 13:06 dominiq at lps dot ens dot fr
  2007-01-08 13:23 ` [Bug fortran/30407] " burnus at gcc dot gnu dot org
                   ` (7 more replies)
  0 siblings, 8 replies; 9+ messages in thread
From: dominiq at lps dot ens dot fr @ 2007-01-08 13:06 UTC (permalink / raw)
  To: gcc-bugs

When compiled with gfortran (latest 4.3 snapshot), the following code

!==============================================================================

MODULE kind_mod

   IMPLICIT NONE

   PRIVATE

   INTEGER, PUBLIC, PARAMETER :: I4=SELECTED_INT_KIND(9)
   INTEGER, PUBLIC, PARAMETER :: TF=KIND(.TRUE._I4)

END MODULE kind_mod

!==============================================================================

MODULE pointer_mod

   USE kind_mod, ONLY : I4

   IMPLICIT NONE

   PRIVATE

   TYPE, PUBLIC :: pointer_vector_I4
      INTEGER(I4), POINTER, DIMENSION(:) :: vect
   END TYPE pointer_vector_I4

   INTERFACE ASSIGNMENT(=)
      MODULE PROCEDURE p_vect_I4_equals_p_vect_I4_sub
   END INTERFACE

   PUBLIC :: ASSIGNMENT(=)

CONTAINS

   !---------------------------------------------------------------------------

   PURE ELEMENTAL SUBROUTINE p_vect_I4_equals_p_vect_I4_sub(a1, a2)
      !  Redefines the default assignment of pointer_vector_I4 types,
      !     a1%vect=>a2%vect
      !  so that instead
      !     a1%vect=a2%vect
      IMPLICIT NONE
      TYPE(pointer_vector_I4), INTENT(OUT) :: a1
      TYPE(pointer_vector_I4), INTENT(IN) :: a2
      a1%vect = a2%vect
   END SUBROUTINE p_vect_I4_equals_p_vect_I4_sub

   !---------------------------------------------------------------------------

END MODULE pointer_mod

!==============================================================================

PROGRAM test_prog

   USE pointer_mod, ONLY : pointer_vector_I4, ASSIGNMENT(=)

   USE kind_mod, ONLY : I4, TF

   IMPLICIT NONE

   INTEGER(I4), DIMENSION(12_I4), TARGET :: integer_array
   LOGICAL(TF), DIMENSION(2_I4,3_I4) :: logical_array
   TYPE(pointer_vector_I4), DIMENSION(6_I4) :: p_vect
   INTEGER(I4) :: i

   ! Initialisation...
   logical_array(:,1_I4:3_I4:2_I4)=.TRUE._TF
   logical_array(:,2_I4)=.FALSE._TF

   DO i=1_I4,6_I4
      p_vect(i)%vect => integer_array((2_I4*i-1_I4):(2_I4*i))
   END DO

   integer_array=0_I4

   PRINT *,''
   PRINT *,'DO-WHERE:      pointer version'
   DO i=1_I4,3_I4
      WHERE(logical_array((/1_I4,2_I4/),i))
         p_vect((2_I4*i-1_I4):(2_I4*i))=&
            & elemental_pointer_fun((/(2_I4*i-1_I4),(2_I4*i)/))
      ELSEWHERE
         p_vect((2_I4*i-1_I4):(2_I4*i))=&
            & elemental_pointer_fun((/0_I4,0_I4/))
      END WHERE
   END DO

   PRINT '(A,6L6)', 'logical_array: ',logical_array
   PRINT '(A,12I3)', 'integer_array: ',integer_array

CONTAINS

   PURE TYPE(pointer_vector_I4) ELEMENTAL FUNCTION &
      & elemental_pointer_fun(index) RESULT(ans)

      USE kind_mod, ONLY :  I4
      USE pointer_mod, ONLY : pointer_vector_I4, ASSIGNMENT(=)

      IMPLICIT NONE

      INTEGER(I4), INTENT(IN) :: index

      ALLOCATE(ans%vect(2_I4))
      ans%vect=(/index,-index/)

   END FUNCTION elemental_pointer_fun

END PROGRAM test_prog

gives:

forall_where_red_2.f90:83.63:

            & elemental_pointer_fun((/(2_I4*i-1_I4),(2_I4*i)/))
                                                              1
Error: Unsupported statement inside WHERE at (1)
forall_where_red_2.f90:86.50:

            & elemental_pointer_fun((/0_I4,0_I4/))
                                                 1
Error: Unsupported statement inside WHERE at (1)

If I remove the = assignement, gfortran accept it (though the 
result changes).


-- 
           Summary: Compilation errors on valid code
           Product: gcc
           Version: 4.3.0
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: dominiq at lps dot ens dot fr
GCC target triplet: powerpc-apple-darwin7


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


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

* [Bug fortran/30407] Compilation errors on valid code
  2007-01-08 13:06 [Bug fortran/30407] New: Compilation errors on valid code dominiq at lps dot ens dot fr
@ 2007-01-08 13:23 ` burnus at gcc dot gnu dot org
  2007-01-09 20:36 ` [Bug fortran/30407] Elemental functions in WHERE assignments wrongly rejected pault at gcc dot gnu dot org
                   ` (6 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: burnus at gcc dot gnu dot org @ 2007-01-08 13:23 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #1 from burnus at gcc dot gnu dot org  2007-01-08 13:23 -------
A look into resolve.c's resolve_where, shows that only EXEC_ASSIGN and not
EXEC_ASSIGN_CALL exists in "switch (cnext->op)".

Expected: As elemental procedures are also allowed, a "case EXEC_ASSIGN_CALL:"
has to be added.

"7.4.3.1 General form of the masked array assignment"
"C729 (R747) A where-assignment-stmt that is a defined assignment shall be
elemental."


-- 

burnus at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |burnus at gcc dot gnu dot
                   |                            |org
             Status|UNCONFIRMED                 |NEW
     Ever Confirmed|0                           |1
 GCC target triplet|powerpc-apple-darwin7       |
           Keywords|                            |rejects-valid
   Last reconfirmed|0000-00-00 00:00:00         |2007-01-08 13:23:07
               date|                            |


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


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

* [Bug fortran/30407] Elemental functions in WHERE assignments wrongly rejected
  2007-01-08 13:06 [Bug fortran/30407] New: Compilation errors on valid code dominiq at lps dot ens dot fr
  2007-01-08 13:23 ` [Bug fortran/30407] " burnus at gcc dot gnu dot org
@ 2007-01-09 20:36 ` pault at gcc dot gnu dot org
  2007-01-17 14:11 ` pault at gcc dot gnu dot org
                   ` (5 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-01-09 20:36 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #2 from pault at gcc dot gnu dot org  2007-01-09 20:36 -------
(In reply to comment #1)
> A look into resolve.c's resolve_where, shows that only EXEC_ASSIGN and not
> EXEC_ASSIGN_CALL exists in "switch (cnext->op)".
> 
> Expected: As elemental procedures are also allowed, a "case EXEC_ASSIGN_CALL:"
> has to be added.
Tobias,

Indeed! Are you going to take it on? I'll look after the reviewing for you.

Paul


-- 


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


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

* [Bug fortran/30407] Elemental functions in WHERE assignments wrongly rejected
  2007-01-08 13:06 [Bug fortran/30407] New: Compilation errors on valid code dominiq at lps dot ens dot fr
  2007-01-08 13:23 ` [Bug fortran/30407] " burnus at gcc dot gnu dot org
  2007-01-09 20:36 ` [Bug fortran/30407] Elemental functions in WHERE assignments wrongly rejected pault at gcc dot gnu dot org
@ 2007-01-17 14:11 ` pault at gcc dot gnu dot org
  2007-01-21 22:00 ` patchapp at dberlin dot org
                   ` (4 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-01-17 14:11 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #3 from pault at gcc dot gnu dot org  2007-01-17 14:11 -------

> > Expected: As elemental procedures are also allowed, a "case EXEC_ASSIGN_CALL:"
> > has to be added.
This is the easy bit... You then get:

$ /irun/bin/gfortran pr30407.f90
pr30407.f90: In function 'MAIN__':
pr30407.f90:79: internal compiler error: in gfc_trans_where_2, at
fortran/trans-
stmt.c:3260

because none of the equipment is in place to do the subroutine call.  This was
easy for FORALL because the masking is done externally to the assignment.  The
WHERE construct is a totally different kettle of fish and it will take a while
to deal with it.

Paul


-- 


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


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

* [Bug fortran/30407] Elemental functions in WHERE assignments wrongly rejected
  2007-01-08 13:06 [Bug fortran/30407] New: Compilation errors on valid code dominiq at lps dot ens dot fr
                   ` (2 preceding siblings ...)
  2007-01-17 14:11 ` pault at gcc dot gnu dot org
@ 2007-01-21 22:00 ` patchapp at dberlin dot org
  2007-01-22  5:17 ` pault at gcc dot gnu dot org
                   ` (3 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: patchapp at dberlin dot org @ 2007-01-21 22:00 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #4 from patchapp at dberlin dot org  2007-01-21 22:00 -------
Subject: Bug number PR30407

A patch for this bug has been added to the patch tracker.
The mailing list url for the patch is
http://gcc.gnu.org/ml/gcc-patches/2007-01/msg01744.html


-- 


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


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

* [Bug fortran/30407] Elemental functions in WHERE assignments wrongly rejected
  2007-01-08 13:06 [Bug fortran/30407] New: Compilation errors on valid code dominiq at lps dot ens dot fr
                   ` (3 preceding siblings ...)
  2007-01-21 22:00 ` patchapp at dberlin dot org
@ 2007-01-22  5:17 ` pault at gcc dot gnu dot org
  2007-01-27 18:23 ` pault at gcc dot gnu dot org
                   ` (2 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-01-22  5:17 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #5 from pault at gcc dot gnu dot org  2007-01-22 05:17 -------
Dang it! In spite of New Year's resolutions, I had better take it.

Paul


-- 

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|2007-01-08 13:23:07         |2007-01-22 05:17:18
               date|                            |


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


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

* [Bug fortran/30407] Elemental functions in WHERE assignments wrongly rejected
  2007-01-08 13:06 [Bug fortran/30407] New: Compilation errors on valid code dominiq at lps dot ens dot fr
                   ` (4 preceding siblings ...)
  2007-01-22  5:17 ` pault at gcc dot gnu dot org
@ 2007-01-27 18:23 ` pault at gcc dot gnu dot org
  2007-02-12  7:35 ` [Bug fortran/30407] [4.2 and 4.1 only] " pault at gcc dot gnu dot org
  2007-02-12  7:37 ` [Bug fortran/30407] [4.1 " pault at gcc dot gnu dot org
  7 siblings, 0 replies; 9+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-01-27 18:23 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #6 from pault at gcc dot gnu dot org  2007-01-27 18:23 -------
Subject: Bug 30407

Author: pault
Date: Sat Jan 27 18:23:14 2007
New Revision: 121235

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=121235
Log:
2007-01-27  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/30407
        * trans-expr.c (gfc_conv_operator_assign): New function.
        * trans.h : Add prototype for gfc_conv_operator_assign.
        * trans-stmt.c (gfc_trans_where_assign): Add a gfc_symbol for
        a potential operator assignment subroutine.  If it is non-NULL
        call gfc_conv_operator_assign instead of the first assignment.
        ( gfc_trans_where_2): In the case of an operator assignment,
        extract the argument expressions from the code for the
        subroutine call and pass the symbol to gfc_trans_where_assign.
        resolve.c (resolve_where, gfc_resolve_where_code_in_forall,
        gfc_resolve_forall_body): Resolve the subroutine call for
        operator assignments.

2007-01-27  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/30407
        * gfortran.dg/where_operator_assign_1.f90: New test.
        * gfortran.dg/where_operator_assign_2.f90: New test.
        * gfortran.dg/where_operator_assign_3.f90: New test.

Added:
    trunk/gcc/testsuite/gfortran.dg/where_operator_assign_1.f90
    trunk/gcc/testsuite/gfortran.dg/where_operator_assign_2.f90
    trunk/gcc/testsuite/gfortran.dg/where_operator_assign_3.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/resolve.c
    trunk/gcc/fortran/trans-expr.c
    trunk/gcc/fortran/trans-stmt.c
    trunk/gcc/fortran/trans.h
    trunk/gcc/testsuite/ChangeLog


-- 


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


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

* [Bug fortran/30407] [4.2 and 4.1 only] Elemental functions in WHERE assignments wrongly rejected
  2007-01-08 13:06 [Bug fortran/30407] New: Compilation errors on valid code dominiq at lps dot ens dot fr
                   ` (5 preceding siblings ...)
  2007-01-27 18:23 ` pault at gcc dot gnu dot org
@ 2007-02-12  7:35 ` pault at gcc dot gnu dot org
  2007-02-12  7:37 ` [Bug fortran/30407] [4.1 " pault at gcc dot gnu dot org
  7 siblings, 0 replies; 9+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-02-12  7:35 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #7 from pault at gcc dot gnu dot org  2007-02-12 07:35 -------
Subject: Bug 30407

Author: pault
Date: Mon Feb 12 07:34:51 2007
New Revision: 121841

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=121841
Log:
2007-02-12  Paul Thomas  <pault@gcc.gnu.org>

        BACKPORTS FROM TRUNK

        PR fortran/30284
        PR fortran/30626
        * trans-expr.c (gfc_conv_aliased_arg): Remove static attribute
        from function and make sure that substring lengths are
        translated.
        (is_aliased_array): Remove static attribute.
        * trans.c : Add prototypes for gfc_conv_aliased_arg and
        is_aliased_array.
        * trans-io.c (set_internal_unit): Add the post block to the
        arguments of the function.  Use is_aliased_array to check if
        temporary is needed; if so call gfc_conv_aliased_arg.
        (build_dt): Pass the post block to set_internal_unit and
        add to the block after all io activiy is done.

        PR fortran/30407
        * trans-expr.c (gfc_conv_operator_assign): New function.
        * trans.h : Add prototype for gfc_conv_operator_assign.
        * trans-stmt.c (gfc_trans_where_assign): Add a gfc_symbol for
        a potential operator assignment subroutine.  If it is non-NULL
        call gfc_conv_operator_assign instead of the first assignment.
        ( gfc_trans_where_2): In the case of an operator assignment,
        extract the argument expressions from the code for the
        subroutine call and pass the symbol to gfc_trans_where_assign.
        resolve.c (resolve_where, gfc_resolve_where_code_in_forall,
        gfc_resolve_forall_body): Resolve the subroutine call for
        operator assignments.

        PR fortran/30514
        * array.c (match_array_element_spec): If the length of an array is
        negative, adjust the upper limit to make it zero length.

2007-02-12  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/30284
        * gfortran.dg/arrayio_11.f90: New test.

        PR fortran/30626
        * gfortran.dg/arrayio_12.f90: New test.

        PR fortran/30407
        * gfortran.dg/where_operator_assign_1.f90: New test.
        * gfortran.dg/where_operator_assign_2.f90: New test.
        * gfortran.dg/where_operator_assign_3.f90: New test.

        PR fortran/30514
        * gfortran.dg/zero_sized_2.f90: New test.

2007-02-12  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/30284
        PR fortran/30626
        * io/transfer.c (init_loop_spec, next_array_record): Change to
        lbound rather than unity base.

Added:
    branches/gcc-4_2-branch/gcc/testsuite/gfortran.dg/arrayio_11.f90
    branches/gcc-4_2-branch/gcc/testsuite/gfortran.dg/arrayio_12.f90
   
branches/gcc-4_2-branch/gcc/testsuite/gfortran.dg/where_operator_assign_1.f90
   
branches/gcc-4_2-branch/gcc/testsuite/gfortran.dg/where_operator_assign_2.f90
   
branches/gcc-4_2-branch/gcc/testsuite/gfortran.dg/where_operator_assign_3.f90
    branches/gcc-4_2-branch/gcc/testsuite/gfortran.dg/zero_sized_2.f90
Modified:
    branches/gcc-4_2-branch/gcc/fortran/ChangeLog
    branches/gcc-4_2-branch/gcc/fortran/array.c
    branches/gcc-4_2-branch/gcc/fortran/resolve.c
    branches/gcc-4_2-branch/gcc/fortran/trans-expr.c
    branches/gcc-4_2-branch/gcc/fortran/trans-io.c
    branches/gcc-4_2-branch/gcc/fortran/trans-stmt.c
    branches/gcc-4_2-branch/gcc/fortran/trans.h
    branches/gcc-4_2-branch/gcc/testsuite/ChangeLog
    branches/gcc-4_2-branch/libgfortran/ChangeLog
    branches/gcc-4_2-branch/libgfortran/io/transfer.c


-- 


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


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

* [Bug fortran/30407] [4.1 only] Elemental functions in WHERE assignments wrongly rejected
  2007-01-08 13:06 [Bug fortran/30407] New: Compilation errors on valid code dominiq at lps dot ens dot fr
                   ` (6 preceding siblings ...)
  2007-02-12  7:35 ` [Bug fortran/30407] [4.2 and 4.1 only] " pault at gcc dot gnu dot org
@ 2007-02-12  7:37 ` pault at gcc dot gnu dot org
  7 siblings, 0 replies; 9+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-02-12  7:37 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #8 from pault at gcc dot gnu dot org  2007-02-12 07:37 -------
Fixed on trunk and 4.2.

Paul


-- 

pault at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|ASSIGNED                    |RESOLVED
         Resolution|                            |FIXED
            Summary|[4.2 and 4.1 only] Elemental|[4.1 only] Elemental
                   |functions in WHERE          |functions in WHERE
                   |assignments wrongly rejected|assignments wrongly rejected


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


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

end of thread, other threads:[~2007-02-12  7:37 UTC | newest]

Thread overview: 9+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2007-01-08 13:06 [Bug fortran/30407] New: Compilation errors on valid code dominiq at lps dot ens dot fr
2007-01-08 13:23 ` [Bug fortran/30407] " burnus at gcc dot gnu dot org
2007-01-09 20:36 ` [Bug fortran/30407] Elemental functions in WHERE assignments wrongly rejected pault at gcc dot gnu dot org
2007-01-17 14:11 ` pault at gcc dot gnu dot org
2007-01-21 22:00 ` patchapp at dberlin dot org
2007-01-22  5:17 ` pault at gcc dot gnu dot org
2007-01-27 18:23 ` pault at gcc dot gnu dot org
2007-02-12  7:35 ` [Bug fortran/30407] [4.2 and 4.1 only] " pault at gcc dot gnu dot org
2007-02-12  7:37 ` [Bug fortran/30407] [4.1 " 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).