[Bug fortran/30407] New: Compilation errors on valid code

dominiq at lps dot ens dot fr gcc-bugzilla@gcc.gnu.org
Mon Jan 8 13:06:00 GMT 2007


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



More information about the Gcc-bugs mailing list