[Bug fortran/38914] New: ICE with array inquiry functions above contains in parameter expression

2009-01-19 Thread dick dot hendrickson at gmail dot com
The following program causes an ICE.  If the contains and subroutine statements
are uncommented, then the program compiles.

Dick Hendrickson

  MODULE U_above_TESTS

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

!  contains
!  subroutine U_below

  INTEGER, PARAMETER, DIMENSION(0:20,4) :: IP_ARRAY2_4_S = 0

  INTEGER, PARAMETER, DIMENSION(12) ::  IP_ARRAY1_32_S =
 $(/  LBOUND(IP_ARRAY2_4_S), LBOUND(IP_ARRAY2_4_S(5:10,2:3)),
 $UBOUND(IP_ARRAY2_4_S), UBOUND(IP_ARRAY2_4_S(5:10,2:3)),
 $SIZE(IP_ARRAY2_4_S), SIZE(IP_ARRAY2_4_S(5:10,2:3)),
 $SHAPE(IP_ARRAY2_4_S(5:10,2:3))  /)

!  end subroutine u_below

  END MODULE U_above_TESTS


C:\gfortrangfortran u_above.f
f951.exe: internal compiler error: in gfc_conv_array_initializer, at
fortran/tra
ns-array.c:4009
Please submit a full bug report,
with preprocessed source if appropriate.
See http://gcc.gnu.org/bugs.html for instructions.


-- 
   Summary: ICE with array inquiry functions above contains in
parameter expression
   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=38914



[Bug fortran/38915] New: wrong results for structure assignment of character components when left and right sides overlap

2009-01-19 Thread dick dot hendrickson at gmail dot com
The following program gives the wrong results for the character assignments to
a structure component.  The problem appears to occur when there is an overlap
between the left and right hand sides of the assignment.  It is as if the
character length of the right hand side is treated as 1, rather than 9, and
then the left is blank padded to 9.  While experimenting with this, I tried
some simple things like L(1:2)%c = R(2:3)%c and they all worked.

Dick Hendrickson

   program cg0033_41

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

   type t
 sequence
 integer i
 character(len=9) c
   end type t

   type (t)  L(3),R(3), LL(4), RR(4)
   EQUIVALENCE (L,LL)

   integer nfv1(3), nfv2(3)

   R(1)%c = '123456789'
   R(2)%c = 'abcdefghi'
   R(3)%c = '!...@#$%^*('

   L%c = R%c
   print *, 'simple assignment'
   print *,  R%c
   print *,  L%c

   LL(1:3)%c = R%c
   LL(4)%c = 'QWERTYUIO'
   RR%c = LL%c

   L%c = LL(2:4)%c

   print *
   print *, 'overlapping assignment'
   print *,  RR(2:4)%c
   print *,  L%c

   nfv1 = (/1,2,3/)
   nfv2 = nfv1
   L%c = R%c
   L(nfv1)%c = L(nfv2)%c
   print *
   print *, ' vvs assignment'
   print *,  R%c
   print *,  L%c

   end


C:\gfortrangfortran try_cg0033_41.f

C:\gfortrana
 simple assignment
 123456789abcdefg...@#$%^*(
 123456789abcdefg...@#$%^*(

 overlapping assignment
 abcdefg...@#$%^*(QWERTYUIO
 a!Q

  vvs assignment
 123456789abcdefg...@#$%^*(
 1a!


-- 
   Summary: wrong results for structure assignment of character
components when left and right sides overlap
   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=38915



[Bug fortran/38917] New: Can't use DATA to initialize pointer to array to NULL()

2009-01-19 Thread dick dot hendrickson at gmail dot com
The following program gives error messages for using DATA to iniialize pointers
to arrays to NULL()

Dick Hendrickson

  SUBROUTINE PF0005

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

  REAL, SAVE, POINTER :: PTR1
  INTEGER, POINTER   :: PTR2(:,:,:)
  CHARACTER(LEN=1), SAVE, POINTER :: PTR3(:)

  DATA  PTR1 / NULL() /
  DATA  PTR2 / NULL() /
  DATA  PTR3 / NULL() /

  end subroutine pf0005


C:\documents and settings\s and h\my documents\g_experiments\gfortrangfortran
t
ry_pf0005.f
try_pf0005.f:12.10:

  DATA  PTR3 / NULL() /
  1
Error: Nonconstant array section at (1) in DATA statement
try_pf0005.f:11.10:

  DATA  PTR2 / NULL() /
  1
Error: Nonconstant array section at (1) in DATA statement


-- 
   Summary: Can't use DATA to initialize pointer to array to NULL()
   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=38917



[Bug fortran/38918] New: compile time error for DATA of NULL() to pointer structure component

2009-01-19 Thread dick dot hendrickson at gmail dot com
The following program gives a compile time error for a DATA assignment of
NULL() to a structure component.  Probably related to 38917

Dick Hendrickson

  SUBROUTINE PF0009

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

  TYPE  :: HAS_POINTER
INTEGER, POINTER:: PTR_S
  END TYPE HAS_POINTER
  TYPE (HAS_POINTER)  ::  PTR_ARRAY(5)

  DATA PTR_ARRAY(1)%PTR_S  /NULL()/

  end subroutine pf0009


C:\gfortrangfortran try_pf0009.f
try_pf0009.f:11.38:

  DATA PTR_ARRAY(1)%PTR_S  /NULL()/
  1
Error: NULL appears on right-hand side in assignment at (1)


-- 
   Summary: compile time error for DATA of NULL() to pointer
structure component
   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=38918



[Bug fortran/38863] WHERE with multiple elemental defined assignments gives wrong answer

2009-01-19 Thread dick dot hendrickson at gmail dot com


--- 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-bugzi...@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



[Bug fortran/38907] New: ICE when contained function has same name as module function and used in expression

2009-01-18 Thread dick dot hendrickson at gmail dot com
The following program gives an internal compiler error.  If the line
RDA = -1 is commented out, there is a different ICE.  If the unary +
before the function reference in the assignment to RDA(1,2) is removed
the ICE goes away.

Dick Hendrickson


  module sa0054_stuff

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

  contains

  PURE FUNCTION S_REAL_SUM_I (A,B)
  REAL  ::  S_REAL_SUM_I
  REAL, INTENT(IN), OPTIONAL  ::  A,B
  X = 0
  S_REAL_SUM_I = X

  END FUNCTION S_REAL_SUM_I

  SUBROUTINE SA0054(RDA, NF10,nf1,nf2,nf3,nf4)
  REAL RDA(NF10,NF10)

  RDA= -1  !changes ICE if commented out

  RDA(1,2) = + S_REAL_SUM_I(1.0,2.0)

! RDA(1,2) =   S_REAL_SUM_I(1.0,2.0) !This one works

  CONTAINS

  PURE FUNCTION S_REAL_SUM_I (A,B)
  REAL  ::  S_REAL_SUM_I
  REAL, INTENT(IN), OPTIONAL  ::  A,B
  S_REAL_SUM_I = 0
  END FUNCTION S_REAL_SUM_I

  END SUBROUTINE

  end module sa0054_stuff


With RDA = -1
C:\gfortrangfortran try_sa0054.f
f951.exe: internal compiler error: Segmentation fault
Please submit a full bug report,
with preprocessed source if appropriate.
See http://gcc.gnu.org/bugs.html for instructions.


With RDA = -1 commented out
C:\gfortrangfortran try_sa0054.f
f951.exe: internal compiler error: in check_host_association, at
fortran/resolve
.c:4369
Please submit a full bug report,
with preprocessed source if appropriate.
See http://gcc.gnu.org/bugs.html for instructions.


-- 
   Summary: ICE when contained function has same name as module
function and used in expression
   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=38907



[Bug fortran/38863] WHERE with multiple elemental defined assignments gives wrong answer

2009-01-18 Thread dick dot hendrickson at gmail dot com


--- 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-bugzi...@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|-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



[Bug fortran/38883] New: Internal Compiler Error for MVBITS with derived type argument that has run-time subscripts

2009-01-16 Thread dick dot hendrickson at gmail dot com
The following program causes an internal compiler error.  If the single
reference to NF3 in the MVBITS argument list is changed to 3 the program
compiles and executes.

Dick Hendrickson

  module yg0009_stuff

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

  type unseq
 integer I
  end type

  contains

  SUBROUTINE YG0009(TDA2L,NF4,NF3,NF1,MF1,MF4,MF3)
  TYPE(UNSEQ) TDA2L(4,3)

  CALL MVBITS (TDA2L(4:1:-1,1:3)%I,2,
 $   4, TDA2L(4:1:-1,1:NF3)%I, 3)

!  these also ICE, but seem needlessly complex
!  TYPE(UNSEQ) TDA2L(NF4,NF3)
!
!  CALL MVBITS (TDA2L(NF4:NF1:MF1,NF1:NF3)%I,2,
! $   4, TDA2L(-MF4:-MF1:-NF1,-MF1:-MF3)%I, 3)
!  but, you might as well try them in your spare time ;)

  END SUBROUTINE

  end module yg0009_stuff

  program try_yg0009
  use yg0009_stuff
  type(unseq)  tda2l(4,3)

  call yg0009(tda2l,4,3,1,-1,-4,-3)

  end


C:\gfortrangfortran try_yg0009.f
try_yg0009.f: In function 'yg0009':
try_yg0009.f:12: internal compiler error: in gfc_trans_allocate_array_storage,
a
t fortran/trans-array.c:558
Please submit a full bug report,
with preprocessed source if appropriate.
See http://gcc.gnu.org/bugs.html for instructions.


-- 
   Summary: Internal Compiler Error for MVBITS with derived type
argument that has run-time subscripts
   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=38883



[Bug fortran/38887] New: run-time abort for MVBITS with run-time zero sized array arguments

2009-01-16 Thread dick dot hendrickson at gmail dot com
The following program gives a run-time abort.  If either of the array arguments
to MVBITS has an explicit (ie (5,1) or (6,1) ) zero size, the program does not
abort.

It aborts differently on Windows, depending on how it is run.

Dick Hendrickson

  program try_ya0013

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

  integer ida(9)
  call ya0013(ida,1,5,6)
  end
  SUBROUTINE YA0013(IDA,nf1,nf5,nf6)
  INTEGER IDA(9)
  IDA = 1
  CALL MVBITS(IDA(NF5:NF1), 0, 1, IDA(NF6:NF1),2)
  END SUBROUTINE


C:gfortrangfortran try_ya0013.f

C:gfortrana

When run as a simple stand-alone test, an alert box appears.  The first part
is:
a.exe has encountered a problem and needs to close.  We are sorry for the
inconvenience.

The box then offers to send a report to Microsoft!


When the subroutine is run as part of a larger program this text message
appears:
This application has requested the Runtime to terminate it in an unusual way.
Please contact the application's support team for more information.
and the program terminates.


-- 
   Summary: run-time abort for MVBITS with run-time zero sized array
arguments
   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=38887



[Bug fortran/38859] New: ubound and lbound treat structure component references as whole arrays

2009-01-15 Thread dick dot hendrickson at gmail dot com
The UBOUND and LBOUND intrinsics treat a reference to an array structure
component as if they were inquires on a whole array.  

Dick Hendrickson


   program try_jg_15_18

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

   type x
 integer I
   end type x
   type (x) A(0:5, 2:8)
   integer ida(2)

   ida = lbound(a)
   if (any(ida /= (/0,2/))) print *, 'base array', ida

!note that a%i is neither a whole array nor an array structure component

   ida = lbound(a%i)
   if (any(ida /= (/1,1/))) print *, 'lbound', ida

   ida = ubound(a)
   if (any(ida /= (/6,7/))) print *, 'ubound', ida

   end


C:\gfortrangfortran try_jg_15_18.f

C:\gfortrana
 lbound   0   2
 ubound   5   8


-- 
   Summary: ubound and lbound treat structure component references
as whole arrays
   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=38859



[Bug fortran/38863] New: WHERE with multiple elemental defined assignments gives wrong answer

2009-01-15 Thread dick dot hendrickson at gmail dot com
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:gfortrangfortran try_rg0045.f
C:\gfortrana
   3  -18192  -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:gfortrangfortran try_rg0045.f

C:\gfortrana
   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:gfortrangfortran try_rg0045.f

C:\gfortrana
   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:\gfortrangfortran try_rg0045.f

C:\gfortrana
   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



[Bug fortran/38852] New: UBOUND fails for negative stride triplets

2009-01-14 Thread dick dot hendrickson at gmail dot com
The UBOUND function returns zero for subscript triplets that have a negative
stride, such as 5:4:-1.  Fails with both compile-time expressions and run-time
expressions.  LBOUND and SHAPE work correctly on the same triplets.

This might be related to 35685 since I think this started soon after 35685 was
closed.

Dick Hendrickson


  program try_je0031

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

  integer ida(4)
  real dda(5,5,5,5,5)
  call JE0031(IDA,DDA,2,5,-2)

  end 

  SUBROUTINE JE0031(IDA,DDA,nf2,nf5,mf2)
  INTEGER IDA(4)
  REAL DLA(:,:,:,:)
  REAL DDA(5,5,5,5,5)
  POINTER DLA
  TARGET DDA

  DLA = DDA(2:3, 1:3:2, 5:4:-1, NF2, NF5:NF2:MF2)
  IDA = UBOUND(DLA)
  if (any(ida /= 2)) print *, 'run-time ubound', ida

  DLA = DDA(2:3, 1:3:2, 5:4:-1, 2, 5:2:-2)
  IDA = UBOUND(DLA)
  if (any(ida /= 2)) print *, 'compile-time ubound', ida

!these work
  DLA = DDA(2:3, 1:3:2, 5:4:-1, 2, 5:2:-2)
  IDA = shape(DLA)
  if (any(ida /= 2)) print *, ' compile-time shape', ida

  DLA = DDA(2:3, 1:3:2, 5:4:-1, 2, 5:2:-2)
  IDA = LBOUND(DLA)
  if (any(ida /= 1)) print *, 'compile-time lbound', ida

  END SUBROUTINE


C:\gfortrangfortran try_je0031.f

C:\gfortrana
 run-time ubound   2   2   0   0
 compile-time ubound   2   2   0   0


-- 
   Summary: UBOUND fails for negative stride triplets
   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=38852



[Bug fortran/35681] wrong result for vector subscripted array expression in MVBITS

2008-10-18 Thread dick dot hendrickson at gmail dot com


--- Comment #11 from dick dot hendrickson at gmail dot com  2008-10-18 
17:02 ---
Subject: Re:  wrong result for vector subscripted array expression in MVBITS

Also, MVBITS is a special case.  See the top of page 215 in the F95
standard.  The FROM
and TO arguments are allowed to be the same variable.  The other thing
about overlapping
variables is (2) on page 205, which is a long way from the section
header and is often
overlooked (at least I missed it once).

I'm off to help paint my granddaughter's bedroom, so I can't think
much about this.

Somewhere, along time ago, there was a smallish test program of the form
subroutine xxx(a,b)
b = b+1
print *, a,b
end
and then a ton of call statements of the forms

   a = 99
   call xxx ((a),a)
   or
   call xxx( 1*a,a)
   or
   call xxx(a+0, a)
...
which might be a good thing to invent as a way to check that you
aren't oversimplifing
actual expressions.

Dick Hendrickson


On Sat, Oct 18, 2008 at 6:36 AM, burnus at gcc dot gnu dot org
[EMAIL PROTECTED] wrote:


 --- Comment #10 from burnus at gcc dot gnu dot org  2008-10-18 11:36 
 ---
 Somehow reading the bug report first before replying helps ... Ignore the crap
 I just wrote.

 Dick's (comment 0)
  CALL MVBITS ((ILA1(NFV3)), 2, 4, ILA1, 3)   !fails
 is valid as the first and the fourth argument don't refer to the same variable
 - the first argument is an expression for which a temporary needs to be
 created.

 Ditto for FX's (comment 1)
  call mvbits ((ILA1((/9/))), 2, 4, ILA1, 3)

 However, comment 7's
  CALL copy (a((/ 2, 1 /)), a)
 is wrong as one passes twice the same variable - once as array section and 
 once
 as whole array. There an outer ( ... ) is missing which is needed to makes 
 this
 an expression.

 For a lengthy answer including where to find it in the standard, see:

 http://groups.google.com/group/comp.lang.fortran/browse_thread/thread/160867d13fd90927/


 Seemingly somewhere  (x)  is simplified to x (= EXPR_VARIABLE) and thus no
 temporary is created - or something like that. For non-elemental procedures
 this was fixed in gfortran 4.3; before foo((x),x) was optimized to foo((x),x).

 One can probably ignore all examples after comment 1 and start with looking 
 why
 no temporary is created for comment 1 - afterwards one needs to check comment
 0.


 --


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

 --- You are receiving this mail because: ---
 You reported the bug, or are watching the reporter.



-- 


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



[Bug fortran/37787] New: right-left hand side overlap not recognized with EQUIVALENCEd array assignment

2008-10-09 Thread dick dot hendrickson at gmail dot com
The following program fails to recognize that the equivalence between qla1 and
qla2 causes a dependency in the assignment.  Using qla1 on the right (ie
resolving the dependency by hand) makes the problem go away.  It occurs for
both explicit constant subscripts and variable subscripts.

Dick Hendrickson


! fails on Windows XP
! gcc version 4.4.0 20080603 (experimental) [trunk revision136333] (GCC)
!apparently, the EQUIVALENCE between QLA1 and QLA2 isn't recognized
!and the left-right overlap isn't recognized
  module stuff
  integer nf1, nf2
  integer, parameter :: r4_kv = 4
  contains

  SUBROUTINE CF0004
!  COPYRIGHT 1999   SPACKMAN  HENDRICKSON, INC.
! CALL CF0004
  REAL(R4_KV) QLA1(100)
  REAL(R4_KV) QLA2(100)
  REAL(R4_KV) QLA3(100)
  REAL(R4_KV) QCA(100)
  EQUIVALENCE (QLA1, QLA2)

  do I = 1,100
  qca(i) = i
  enddo

  QLA1 = QCA
  QLA3 = QCA

  QLA3(  2:100:3) = QCA (  1:65:2) + 1
  QLA1(  2:100:3) = QLA2(  1:65:2) + 1!fails
!  QLA1(NF2:100:3) = QLA2(NF1:65:2) + 1!fails
!  QLA1(NF2:100:3) = QLA1(NF1:65:2) + 1!works
!  QLA1(  2:100:3) = QLA1(  1:65:2) + 1!works

  DO J1 = 1,100
  if (qla1(j1) .ne. qla3(j1)) print *, j1, qla1(j1), qla3(j1)
  100 ENDDO;

  END SUBROUTINE
  end module
  program try_cf004
  use stuff
  nf1 = 1
  nf2 = 2
  call cf0004
  end

C:\g_experiments\gfortrangfortran cf0004_2.f

C:\g_experiments\gfortrana
   8   5.000   6.000
  17   9.000   12.00
  26  10.000   18.00
  35   17.00   24.00
  44   21.00   30.00
  53   18.00   36.00
  62   29.00   42.00
  71   33.00   48.00
  80   19.00   54.00
  89   41.00   60.00
  98   45.00   66.00


-- 
   Summary: right-left hand side overlap not recognized with
EQUIVALENCEd array assignment
   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=37787



[Bug fortran/37723] New: wrong result for left-right hand side array overlap and (possibly) negative strides

2008-10-02 Thread dick dot hendrickson at gmail dot com
   8   8  23  80
   8   9  13  90
   8  10   3 100
   9   6  42  61
   9   7  32  71
   9   8  22  81
   9   9  12  91
   9  10   2 101
 second test different arrays on left and right
 third test, same local array on left and right
   1   6  50  53
   1   7  40  63
   1   8  30  73
   1   9  20  83
   1  10  10  93
   2   6  49  54
   2   7  39  64
   2   8  29  74
   2   9  19  84
   2  10   9  94
   3   6  48  55
   3   7  38  65
   3   8  28  75
   3   9  18  85
   3  10   8  95
   4   6  47  56
   4   7  37  66
   4   8  27  76
   4   9  17  86
   4  10   7  96
   5   6  46  57
   5   7  36  67
   5   8  26  77
   5   9  16  87
   5  10   6  97
   6   6  45  58
   6   7  35  68
   6   8  25  78
   6   9  15  88
   6  10   5  98
   7   6  44  59
   7   7  34  69
   7   8  24  79
   7   9  14  89
   7  10   4  99
   8   6  43  60
   8   7  33  70
   8   8  23  80
   8   9  13  90
   8  10   3 100
   9   6  42  61
   9   7  32  71
   9   8  22  81
   9   9  12  91
   9  10   2 101


-- 
   Summary: wrong result for left-right hand side array overlap and
(possibly) negative strides
   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=37723



[Bug fortran/34805] defined assignment not allowed to vector subscripted array

2008-08-12 Thread dick dot hendrickson at gmail dot com


--- Comment #6 from dick dot hendrickson at gmail dot com  2008-08-12 18:27 
---
Subject: Re:  defined assignment not allowed to vector subscripted array

On Fri, Aug 8, 2008 at 3:39 PM, jv244 at cam dot ac dot uk
[EMAIL PROTECTED] wrote:


 --- Comment #5 from jv244 at cam dot ac dot uk  2008-08-08 20:39 ---
 has J3 judged the testcase ?

Almost.  It's interpretation request 111.  The status in June was
passed J3, it next needs to be accepted by WG5, although that is
likely to be a mere formality.  The J3 vote was unanimous and taken at
a joint WG5/J3 meeting.  It's unlikely to change.

Unfortunately, they got it wrong and are rejecting my claim that the
test is standard conforming.  So, you can mark this bug report as
closed with no action or user error or whatever you use to
(politely) tell someone to go away.

Dick Hendrickson


 --


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

 --- You are receiving this mail because: ---
 You reported the bug, or are watching the reporter.



-- 


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



[Bug fortran/35988] New: run-time abort for MATMUL of run-time zero sized array

2008-04-20 Thread dick dot hendrickson at gmail dot com
Two of the following three subroutines abort at run time.
They have run time zero sized arrays that have different
zero sizes as arguments to matmul.  If the zeroness is visible
at compile time or if the zeroness has the same size, the
similar subroutines do not abort

Dick Hendrickson



   program try_gf1003

! fails on Windows XP
! gcc version 4.4.0 20080312 (experimental) [trunk revision 133139]

  call   gf1003a(  9,  8,  6)   
  call   gf1003b(  9,  8,  6)   
  call   gf1003c(  9,  8,  6)   !fails
  call   gf1003d(  9,  8,  6)   !fails
  end program


  SUBROUTINE GF1003a(nf9,nf8,nf6)
  REAL RDA(3,2)
  REAL RDA1(3,5)
  REAL RDA2(5,2)
  print *, 'gf1003a started'
  RDA = MATMUL(RDA1(:, 9:8),RDA2( 8:6,:))
  print *, 'gf1003a finished'
  END SUBROUTINE

  SUBROUTINE GF1003b(nf9,nf8,nf6)
  REAL RDA(3,2)
  REAL RDA1(3,0)
  REAL RDA2(0,2)
  print *, 'gf1003b started'
  RDA = MATMUL(RDA1(:,NF9:NF8),RDA2(NF9:NF8,:))
  print *, 'gf1003b finished'
  END SUBROUTINE

  SUBROUTINE GF1003c(nf9,nf8,nf6)
  REAL RDA(3,2)
  REAL RDA1(3,0)
  REAL RDA2(0,2)
  print *, 'gf1003c started'
  RDA = MATMUL(RDA1(:,NF9:NF8),RDA2(NF8:NF6,:))
  print *, 'gf1003c finished'
  END SUBROUTINE

  SUBROUTINE GF1003d(nf9,nf8,nf6)
  REAL RDA(3,2)
  REAL RDA1(3,5)
  REAL RDA2(5,2)
  print *, 'gf1003d started'
  RDA = MATMUL(RDA1(:,NF9:NF8),RDA2(NF8:NF6,:))
  print *, 'gf1003d finished'
  END SUBROUTINE

C:\gfortran:gfortran gf1003.f

C:\gfortran:a
 gf1003a started
 gf1003a finished
 gf1003b started
 gf1003b finished
 gf1003c started
Fortran runtime error: dimension of array B incorrect in MATMUL intrinsic


-- 
   Summary: run-time abort for MATMUL of run-time zero sized array
   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=35988



[Bug fortran/35990] New: run-time abort for MATMUL of run-time zero sized array

2008-04-20 Thread dick dot hendrickson at gmail dot com
Two of the following 4 subroutines abort at run time.  They
have a zero sized array argument to PACK.  If the left and
right hand zero sizes are the same, it works.  Also works if
the zero size is a compile time thing.

Dick Hendrickson

  program try_gf1048

! fails on Windows XP
! gcc version 4.4.0 20080312 (experimental) [trunk revision 133139]

  call   gf1048a(  10,  8,  7,  1,  0,  .true.)
  call   gf1048b(  10,  8,  7,  1,  0,  .true.)
  call   gf1048c(  10,  8,  7,  1,  0,  .true.)!fails
  call   gf1048d(  10,  8,  7,  1,  0,  .true.)!fails
  end program

  SUBROUTINE GF1048a(nf10,nf8,nf7,nf1,nf0,nf_true)
  logical nf_true
  CHARACTER(9) BDA(10)
  CHARACTER(9) BDA1(10)
  print *, 'gf1048a started'
  BDA(  8:7) = PACK(BDA1( 10:  1), NF_TRUE)
  print *, 'gf1048a finished'
  END SUBROUTINE

  SUBROUTINE GF1048b(nf10,nf8,nf7,nf1,nf0,nf_true)
  logical nf_true
  CHARACTER(9) BDA(10)
  CHARACTER(9) BDA1(nf10)
  print *, 'gf1048b started'
  BDA(NF8:NF7) = PACK(BDA1(NF8:NF7), NF_TRUE)
  print *, 'gf1048b finished'
  END SUBROUTINE

  SUBROUTINE GF1048c(nf10,nf8,nf7,nf1,nf0,nf_true)
!  on windows XP, natters to itself a while and then goes
!  back to command line prompt with no obvious message
  logical nf_true
  CHARACTER(9) BDA(10)
  CHARACTER(9) BDA1(10)
  print *, 'gf1048c started'
  BDA(NF8:NF7) = PACK(BDA1(NF10:NF1), NF_TRUE)
  print *, 'gf1048c finished'
  END SUBROUTINE

  SUBROUTINE GF1048d(nf10,nf8,nf7,nf1,nf0,nf_true)
!  on windows XP, natters to itself a while and then opens
!  a run time error box and offers to send report to MS
  logical nf_true
  CHARACTER(9) BDA(10)
  CHARACTER(9) BDA1(nf10)
  print *, 'gf1048d started'
  BDA(NF8:NF7) = PACK(BDA1(NF10:NF1), NF_TRUE)
  print *, 'gf1048d finished'
  END SUBROUTINE

C:\gfortran:gfortran gf1048.f

C:\gfortran:a
 gf1048a started
 gf1048a finished
 gf1048b started
 gf1048b finished
 gf1048c started

C:\gfortran:gfortran gf1048.f

!  call gf1048c commented out
C:\gfortran:a
 gf1048a started
 gf1048a finished
 gf1048b started
 gf1048b finished
 gf1048d started

C:\gfortran:


-- 
   Summary: run-time abort for MATMUL of run-time zero sized array
   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=35990



[Bug fortran/35991] New: run-time abort for CSHIFT of zero sized array

2008-04-20 Thread dick dot hendrickson at gmail dot com
The following program aborts at run-time.  On windows XP it
opens an error box saying a.exe has encountered a problem
and offers to send a problem report to MS.

Dick Hendrickson

  program try_gf0045

! fails on Windows XP
! gcc version 4.4.0 20080312 (experimental) [trunk revision 133139]

  call   gf0045(  9,  8)
  end

  subroutine GF0045(nf9,nf8)
  REAL RDA(10)
  REAL RDA1(0)

  RDA(NF9:NF8) = CSHIFT ( RDA1 ,1)

  END SUBROUTINE


-- 
   Summary: run-time abort for CSHIFT of zero sized array
   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=35991



[Bug fortran/35993] New: wrong answer for PRODUCT with scalar mask

2008-04-20 Thread dick dot hendrickson at gmail dot com
The PRODUCT intrinsic gives the wrong answer when the mask argument is
a scalar expression which evaluates to FALSE.  It's OK with
an array expression that evaluates to all FALSE.

Dick Hendrickson 

  program try ga3019

! fails on Windows XP
! gcc version 4.4.0 20080312 (experimental) [trunk revision 133139]

  call   ga3019(  1,  2,  3,  4)
  end program

  SUBROUTINE GA3019(nf1,nf2,nf3,nf4)
  INTEGER IDA(NF2,NF3)
  INTEGER IDA1(NF2,NF4,NF3)

  ida1 = 3

  ida = -3
  IDA(NF1:NF2,NF1:NF3) = PRODUCT(IDA1,NF2, NF1 .LT. 0)  !fails
  print '(6I3)', ida

  ida = -3
  IDA(NF1:NF2,NF1:NF3) = PRODUCT(IDA1,NF2, .false. )!fails
  print '(6I3)', ida

  ida = -3
  IDA(NF1:NF2,NF1:NF3) = PRODUCT(IDA1,NF2, ida1 .eq. 137 )!works
  print '(6I3)', ida

  END SUBROUTINE

C:\gfortran:gfortran ga3019.f

C:\gfortran:a
  1  1  1 -3 -3 -3
  1  1  1 -3 -3 -3
  1  1  1  1  1  1


-- 
   Summary: wrong answer for PRODUCT with scalar mask
   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=35993



[Bug fortran/35994] New: MAXLOC and MINLOC off by one with mask

2008-04-20 Thread dick dot hendrickson at gmail dot com
The MAXLOC and MINLOC functions give an off by one wrong
answer when there is a mask argument.

Dick Hendrickson

  program GA4076

! fails on Windows XP
! gcc version 4.4.0 20080312 (experimental) [trunk revision 133139]

  REAL DDA(100)
  dda = (/(J1,J1=1,100)/)

  IDS = MAXLOC(DDA,1)
  print *, 1, ids, ids.eq.100 !expect 100

  IDS = MAXLOC(DDA,1, (/(J1,J1=1,100)/)  50)
  print *, 2, ids, ids.eq.100 !expect 100

  IDS = minLOC(DDA,1)
  print *, 3, ids, ids.eq.1   !expect 1

  IDS = MinLOC(DDA,1, (/(J1,J1=1,100)/)  50)
  print *, 4, ids, ids.eq.51  !expect 51

  END 

C:\gfortran:gfortran ga4076.f

C:\gfortran:a
   1 100 T
   2 101 F
   3   1 T
   4  52 F


-- 
   Summary: MAXLOC and MINLOC off by one with mask
   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=35994



[Bug fortran/35995] New: ANY, ALL, and COUNT errors for zero sized sections

2008-04-20 Thread dick dot hendrickson at gmail dot com
The ANY, ALL, and COUNT intrinsics do not return the correct
answer when the MASK array is a zero sized section of an
array.  The whole array reduction versions give the correct
answer for the zero sized whole array argument.  It appears
as if nothing is being stored on the left hand side.

Dick Hendrickson

  program try_gf0026_etc

! fails on Windows XP
! gcc version 4.4.0 20080312 (experimental) [trunk revision 133139]

  call   gf0026(  0,  1)
  end program

  SUBROUTINE GF0026(nf0,nf1)
  LOGICAL LDA(9)
  INTEGER IDA(NF0,9), iii(9)

  lda = (/ (i/2*2 .eq. I, i=1,9) /)
  LDA = ALL ( IDA .NE. -1000,  1)
  print *, lda  !expect TRUE
  print *, all(ida .ne. -1000)   !expect TRUE

  lda = (/ (i/2*2 .eq. I, i=1,9) /)
  LDA = any ( IDA .NE. -1000,  1)
  print *, lda  !expect FALSE
  print *, any(ida .ne. -1000)   !expect FALSE

  iii = 137
  iii = count ( IDA .NE. -1000,  1)
  print '(9i4)', iii !expect 0
  print *, count(ida .ne. -1000)   !expect COUNT

  END SUBROUTINE

C:\gfortran:gfortran gf0026.f

C:\gfortran:a
 F T F T F T F T F
 T
 F T F T F T F T F
 F
 137 137 137 137 137 137 137 137 137
   0


-- 
   Summary: ANY, ALL, and COUNT errors for zero sized sections
   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=35995



[Bug fortran/35960] New: run time abort with assignment of RESHAPEd zero sized array

2008-04-16 Thread dick dot hendrickson at gmail dot com
Each line of the following subroutine causes a run-time
abort. Except for the one labeled gf1069.  It works if
literal constants are used in place of the nf* variables.

Dick Hendrickson

  program try_gf1065


! fails on Windows XP
! gcc version 4.4.0 20080312 (experimental) [trunk revision 133139]


  call   gf1065(1,  2,  3,  4,  7,  8,  9)
  end

  SUBROUTINE GF1065(nf1,nf2,nf3,nf4,nf7,nf8,nf9)
!also 1066 thru 1070, 1069 works

  REAL RDA(10,9)
  REAL RCA1(90)
  integer ila(2)
!gf1065
  RDA(NF9:NF8, NF7:NF3) = RESHAPE(RCA1,(/0,0/), (/1.0/),(/2,1/))
  print *, 'gf1065'

!gf1066
  rDA(NF9:NF8, NF7:NF3) = RESHAPE(rCA1,(/0,0/),ORDER=(/2,1/))
  print *, 'gf1066'

  ILA(1) = 5
  ILA(2) = 0
!gf1067
  rDA(NF4:NF8, NF7:NF3) = RESHAPE(rcA1,ILA)
  print *, 'gf1067'

!gf1068
  RdA(NF4:NF8, NF7:NF3) = RESHAPE(RcA1,ILA,PAD=(/-1.0/))
  print *, 'gf1068'

  ILA(1) = 0
  ILA(2) = 5
!gf1069this one works
  RdA(NF9:NF8,NF4:NF8)=RESHAPE(RcA1,ILA,(/-1.0/),(/NF2,NF1/))
  print *, 'gf1069'

  ILA(1) = 5
  ILA(2) = 0
!gf1070
  RdA(NF4:NF8, NF7:NF3) = RESHAPE(RcA1,ILA,ORDER=(/NF1,NF2/))
  print *, 'gf1070'


  END SUBROUTINE


C:\gfortran:gfortran gf1065.f

C:\gfortran:a
Fortran runtime error: shape and target do not conform


-- 
   Summary: run time abort with assignment of RESHAPEd zero sized
array
   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=35960



[Bug fortran/35944] New: wrong result for MOD with kind=10 for some array argument values

2008-04-15 Thread dick dot hendrickson at gmail dot com
The following program gives the wrong answers when the 
MOD arguments have kind = 10 and one is an array.  It
works when the kind is 4 or 8.

  program FA2083

! fails on Windows XP
! gcc version 4.4.0 20080312 (experimental) [trunk revision 133139]

  implicit none
  integer j1,k
  parameter (k=10)  !fails
!  parameter (k=8)  !works
!  parameter (k=4)  !works
  REAL(k) QDA1(10)
  REAL(k) QDA(10), qval

  print *, 'kind = ',k

  qda = (/ 1,2,3,4,5,6,7,8,9,10 /)

  QDA1 = MOD ( 1.1_k*( QDA(1) -5.0_k), P=( QDA -2.5_k))

  DO J1 = 1,10
  QVAL = MOD(1.1_k*(QDA(1)-5.0_k),P=(QDA(J1)-2.5_k))
  print '(i3, 3f10.2)', j1, qda1(j1), qval, qval-qda1(j1)
  ENDDO

  END

c:\gfortran:gfortran fa2083.f

c:\gfortran:a
 kind =   10
  1 -1.40 -1.40  0.00
  2 -0.40 -0.40  0.00
  3 -0.40 -0.40  0.00
  4 -0.40 -1.40 -1.00
  5 -0.40 -1.90 -1.50
  6 -0.40 -0.90 -0.50
  7 -0.40 -4.40 -4.00
  8 -0.40 -4.40 -4.00
  9 -0.40 -4.40 -4.00
 10 -0.40 -4.40 -4.00

c:\gfortran:gfortran fa2083.f

c:\gfortran:a
 kind =8
  1 -1.40 -1.40  0.00
  2 -0.40 -0.40  0.00
  3 -0.40 -0.40  0.00
  4 -1.40 -1.40  0.00
  5 -1.90 -1.90  0.00
  6 -0.90 -0.90  0.00
  7 -4.40 -4.40  0.00
  8 -4.40 -4.40  0.00
  9 -4.40 -4.40  0.00
 10 -4.40 -4.40  0.00

c:\gfortran:gfortran fa2083.f

c:\gfortran:a
 kind =4
  1 -1.40 -1.40  0.00
  2 -0.40 -0.40  0.00
  3 -0.40 -0.40  0.00
  4 -1.40 -1.40  0.00
  5 -1.90 -1.90  0.00
  6 -0.90 -0.90  0.00
  7 -4.40 -4.40  0.00
  8 -4.40 -4.40  0.00
  9 -4.40 -4.40  0.00
 10 -4.40 -4.40  0.00


-- 
   Summary: wrong result for MOD with kind=10 for some array
argument values
   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=35944



[Bug fortran/35946] New: wrong result with array constructor as argument to ATAN2

2008-04-15 Thread dick dot hendrickson at gmail dot com
The following program gives the wrong answers when an array
constructor with a complicated implied do is used as an
argument to REAL which is then used as an argument to
ATAN2.

Dick Hendrickson 

  program try_fa6013

! fails on Windows XP
! gcc version 4.4.0 20080312 (experimental) [trunk revision 133139]

  call fa6013(10,1,-1)
  end program


  subroutine  FA6013 (nf10,nf1,mf1)

  integer, parameter :: kv=4!fails
! integer, parameter :: kv=8!fails

  REAL(KV) DDA1(10)
  REAL(KV) DDA2(10)
  REAL(KV) DDA(10), dval

  dda = (/ 1,2,3,4,5,6,7,8,9,10/)

  print '(10f5.1)',   REAL((/(J1,J1=nf10,nf1,mf1)/),KV) !works 


   DDA1 = ATAN2 (  (/(REAL(J1,KV),J1=1,10)/) ,
 $ REAL((/(J1,J1=nf10,nf1,mf1)/),KV))   !fails

!$ REAL((/(J1,J1=  10,  1, -1)/),KV))   !works

   DDA2 = ATAN2 ( DDA, DDA(10:1:-1) )

  DVAL = .09967_kv !atan2(1.0,10.0)
  print '(i3,3f10.5)', 1, dda1(1),dval, dval-dda1(1)

  DO J1 = 2,10
  DVAL = DDA2(J1)
  print '(i3,3f10.5)', j1, dda1(j1),dval, dval-dda1(j1)
  100 ENDDO

  END

c:\gfortran:gfortran fa6013.f

c:\gfortran:a
 10.0  9.0  8.0  7.0  6.0  5.0  4.0  3.0  2.0  1.0
  1   0.11066   0.09967  -0.01099
  2   0.24498   0.21867  -0.02631
  3   0.40489   0.35877  -0.04612
  4   0.58800   0.51915  -0.06886
  5   0.78540   0.69474  -0.09066
  6   0.98279   0.87606  -0.10674
  7   1.16590   1.05165  -0.11425
  8   1.32582   1.21203  -0.11379
  9   1.46014   1.35213  -0.10801
 10   0.0   1.47113   1.47113


-- 
   Summary: wrong result with array constructor as argument to ATAN2
   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=35946



[Bug fortran/35947] New: wrong answers with array constructor argument to IEOR

2008-04-15 Thread dick dot hendrickson at gmail dot com
The following program gives wrong answers when an array
is used in an array constructor as an argument to IEOR.

Dick Hendrickson

  program try_fa6077

! fails on Windows XP
! gcc version 4.4.0 20080312 (experimental) [trunk revision 133139]

  call   fa6077 (  10,  1, -1, (/1,2,3,4,5,6,7,8,9,10/))
  end

  subroutine FA6077 (nf10,nf1,mf1, ida)
  INTEGER IDA1(10)
  INTEGER IDA2(10), ida(10)


  IDA1 = IEOR((/1,2,3,4,5,6,7,8,9,10/),
 $(/(IDA(J1),J1=10,1,-1)/) )

  IDA2 = IEOR ((/1,2,3,4,5,6,7,8,9,10/), (/10,9,8,7,6,5,4,3,2,1/) )

  print '(10i3)', (/1,2,3,4,5,6,7,8,9,10/), 
 $(/10,9,8,7,6,5,4,3,2,1/),ida1,ida2
  END SUBROUTINE
c:\gfortran:gfortran fa6077.f

c:\gfortran:a
  1  2  3  4  5  6  7  8  9 10
 10  9  8  7  6  5  4  3  2  1
  8 10  4  2  0  2  4 10  8 10
 11 11 11  3  3  3  3 11 11 11


-- 
   Summary: wrong answers with array constructor argument to IEOR
   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=35947



[Bug fortran/35932] New: internal compiler error: CHAR with array arg and also a KIND arg

2008-04-14 Thread dick dot hendrickson at gmail dot com
The following program generates an ICE.

  program FA0005
! fails on Windows XP
! gcc version 4.4.0 20080312 (experimental) [trunk revision 133139]

  CHARACTER(1) CDA1(10)
  INTEGER IDA(10)

  CDA1 = CHAR (  IDA, KIND(A )) !fails
  CDA1 = CHAR (  IDA  )   !works

  END 


C:\gfortrangfortran fa0005.f
fa0005.f: In function 'fa0005':
fa0005.f:1: internal compiler error: in gfc_trans_assignment_1, at
fortran/trans
-expr.c:4330


-- 
   Summary: internal compiler error: CHAR with array arg and also a
KIND arg
   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=35932



[Bug fortran/35940] New: Array BACK ignored in INDEX intrinsic when other args scalar

2008-04-14 Thread dick dot hendrickson at gmail dot com
The following gives the wrong answers.  It may have to do
with broadcasting things to arrays.  The all scalar case works
and an array first argument works.

  program FA1031

! fails on Windows XP
! gcc version 4.4.0 20080312 (experimental) [trunk revision 133139]

  INTEGER IDA1(10)
  LOGICAL GDA1(10)

  IDA1   = 0
  gda1 = (/ (i/2*2 .ne. I, i=1,10) /)
  print '(10L2)', gda1

  IDA1 = INDEX ( 'DEFDEF' , 'DEF', GDA1 )!fails
  print '(10I2)', ida1

  IDA1 = INDEX ( (/ ('DEFDEF',i=1,10) /) , 'DEF', GDA1 )!works
  print '(10I2)', ida1

  IDA = INDEX ( 'DEFDEF' , 'DEF', .true. )   !works
  print '(I2)', ida

  END


-- 
   Summary: Array BACK ignored in INDEX intrinsic when other args
scalar
   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=35940



[Bug fortran/35940] Array BACK ignored in INDEX intrinsic when other args scalar

2008-04-14 Thread dick dot hendrickson at gmail dot com


--- Comment #1 from dick dot hendrickson at gmail dot com  2008-04-14 21:49 
---
I forgot to include the output

C:\gfortrangfortran fa1031.f

C:\gfortrana
 T F T F T F T F T F
 1 1 1 1 1 1 1 1 1 1
 4 1 4 1 4 1 4 1 4 1
 4


-- 

dick dot hendrickson at gmail dot com changed:

   What|Removed |Added

 CC||dick dot hendrickson at
   ||gmail dot com


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



[Bug fortran/35819] New: internal compiler error with forall

2008-04-03 Thread dick dot hendrickson at gmail dot com



-- 
   Summary: internal compiler error with forall
   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=35819



[Bug fortran/35820] New: internal compiler error with forall

2008-04-03 Thread dick dot hendrickson at gmail dot com
) = YCA
  BDA(1:10,1:9,1:5) = BCA
  IDA(1:10) = ICA
  J1 = 6
  J2 = 7
  J3 = 8
!  T E S T  S T A T E M E N T S
  FORALL (J1 = NF1:NF10)
RDA(J1) = RDA(J1) + 1.0_R1_KV
IDA(J1) = IDA(J1) + 1
FORALL (J2 = NF1:NF9)
  FORALL (J3 = NF1:NF5) BDA(J1,J2,J3) = X//BDA(J1,J2,J3)
  YDA(J1,J2) = YDA(J1,J2) + 1
END FORALL
IDA(J1) = IDA(J1) + 1
  ENDFORALL
  END SUBROUTINE
  END MODULE TESTS


gfortran%gfortran sa0136.f
f951.exe: internal compiler error: Segmentation fault
Please submit a full bug report,
with preprocessed source if appropriate.
See http://gcc.gnu.org/bugs.html for instructions.


-- 
   Summary: internal compiler error with forall
   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=35820



[Bug fortran/35819] internal compiler error with forall

2008-04-03 Thread dick dot hendrickson at gmail dot com


--- Comment #1 from dick dot hendrickson at gmail dot com  2008-04-03 18:37 
---
Obviously, ignore this one.  I must have hit enter
by mistake


-- 


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



[Bug fortran/35820] internal compiler error with forall

2008-04-03 Thread dick dot hendrickson at gmail dot com


--- Comment #2 from dick dot hendrickson at gmail dot com  2008-04-03 22:12 
---
Subject: Re:  internal compiler error with forall

On Thu, Apr 3, 2008 at 3:30 PM, dominiq at lps dot ens dot fr
[EMAIL PROTECTED] wrote:


  --- Comment #1 from dominiq at lps dot ens dot fr  2008-04-03 20:30 
 ---
  The code compiles fine on (powerpc|i686)-apple-darwin9. Would it be possible 
 to
  check how the executable works?

Not easily, from my point of view.  This is an isolated part of a
large test suite.  I
spent a couple of half days getting it down to this level.  The
problem is that the
ICE moves around if I do anything.  I've deleted about 160 of the original set
of tests for this isolation.  If I leave the 160 in and delete only 2 of the 3
subroutines I sent in the results are

With SA0136 not removed

gfortran%try_gfortranr s_sa0
working\s_sa0_mods.f
working\s_sa0_tests.f
working\s_sa0_exts.f
1 file(s) copied.
rem.f: In function 'sa0160':
rem.f:5327: internal compiler error: Segmentation fault
[snip]

With SA0137 not removed

gfortran%try_gfortranr s_sa0
working\s_sa0_mods.f
working\s_sa0_tests.f
working\s_sa0_exts.f
1 file(s) copied.
rem.f: In function 'sa0131':
rem.f:4412: internal compiler error: Segmentation fault
[snip]

With SA0138 not removed

gfortran%try_gfortranr s_sa0
working\s_sa0_mods.f
working\s_sa0_tests.f
working\s_sa0_exts.f
1 file(s) copied.
rem.f: In function 'sa0128':
rem.f:4325: internal compiler error: Segmentation fault
[snip]


That is, the ICE appears in 3 different places, depending on which bad
subroutine I leave in the test set.  If I delete the 3 bad routines,
the other 160
all work correctly.

I'm reluctant to send in the whole set for two reasons.  It's large, the 160
subroutines are 19 characters or so and they need a substantial
amount of structure code to work.  Also, the suite is my bread-and-butter
product and I'm reluctant to put part of it in the public domain.

If no one can reproduce the problem on a Windows machine, I can try to
make an executable that fails.

Dick Hendrickson


  --


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

  --- You are receiving this mail because: ---
  You reported the bug, or are watching the reporter.



-- 


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



[Bug fortran/35779] New: error pointer wrong in PARAMETER

2008-03-31 Thread dick dot hendrickson at gmail dot com
The error message thingo points to the wrong place in the
bad line and/or gives a misleading diagnostic.  This isn't
all that important.  I only found it because I'm trying to
find the source of an internal compiler error and if I mess
around with things, this one crops up and hides the other.

Dick Hendrickson

   module bad_message
! fails on Windows XP
! gcc version 4.4.0 20080312 (experimental) [trunk revision 133139]



  integer,PARAMETER :: I3(10) = (/(J1,  J1=10,1,-1)/)

  integer,PARAMETER :: I2(10) = (/(J1,  J1=its_bad,1,-1)/)

  end module

gfortran%gfortran module_bad_message.f
module_bad_message.f:9.38:

  integer,PARAMETER :: I2(10) = (/(J1,  J1=its_bad,1,-1)/)
 1
Error: Invalid character in name at (1)


-- 
   Summary: error pointer wrong in PARAMETER
   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=35779



[Bug fortran/35780] New: internal compiler error for complicated PARAMETER expressions

2008-03-31 Thread dick dot hendrickson at gmail dot com
The following little module causes an ICE.  I believe the bigger module
following it causes different ICE's, or perhaps more instances of the
same one.  But, things move around for me when I try to isolate
statements and I can't be sure.  My advice would be to fix this one 
and hope some magic happens to the other module.

Dick Hendrickson

  MODULE MODS

! fails on Windows XP
! gcc version 4.4.0 20080312 (experimental) [trunk revision 133139]


  INTEGER, PARAMETER, DIMENSION(10) ::  IP_ARRAY1_1_M =3

  INTEGER, PARAMETER, DIMENSION(10) ::  IP_ARRAY1_2_M =3

  INTEGER, PARAMETER, DIMENSION(10)  ::
 $   IP_ARRAY1_25_M = ISHFTC(3, IP_ARRAY1_2_M, 5)   !ICE

! $   IP_ARRAY1_25_M = ISHFTC(IP_ARRAY1_1_M, 3, 5)   !  OK

  END MODULE MODS

gfortran%gfortran u_mods_ice.f
f951.exe: internal compiler error: in gfc_conv_array_initializer, at
fortran/tra
ns-array.c:3880
Please submit a full bug report,
with preprocessed source if appropriate.
See http://gcc.gnu.org/bugs.html for instructions.

--
  MODULE MODS_big

! try this after you've fixed the two related problems.
! this is the full version of the parameters that spawned
! the smaller reports.  The ICE moved around and came and
! went as I tried to isolate things.  

! I believe there are two more ICEs in this set, but they're
! hard to isolate when things move around.

  INTEGER, PRIVATE, PARAMETER  ::
 $ np1 = 1, np2 = 2, NP6=6, NP7=7, NP8=8, NP9=9, NP10=10,
 $ MP6=-6, MP7=-7, MP8=-8, MP9=-9, MP10=-10, np5 = 5,
 $ mp1 = -1

  INTEGER, PARAMETER, DIMENSION(10) ::  IP_ARRAY1_1_M =
 $   (/1,2,3,4,5,6,7,8,9,10/)
  INTEGER, PARAMETER, DIMENSION(10) ::  IP_ARRAY1_2_M =
 $   (/(J1,J1=IP_ARRAY1_1_M(IP_ARRAY1_1_M(NP10)),NP1,MP1)/)

  INTEGER, DIMENSION(SIZE(IP_ARRAY1_1_M)/2) ::
 $ IP_ARRAY1_5_M = IP_ARRAY1_2_M(1:9:2)
  INTEGER, PARAMETER, DIMENSION(SIZE(IP_ARRAY1_1_M)/2) ::
 $ IP_ARRAY1_6_M = IP_ARRAY1_2_M(NP1:NP10:NP2)
  INTEGER, PARAMETER, DIMENSION(10)  ::
 $   IP_ARRAY1_10_M = MAX(IP_ARRAY1_1_M,IP_ARRAY1_2_M),
 $   IP_ARRAY1_11_M = MIN(IP_ARRAY1_1_M,IP_ARRAY1_2_M),
 $   IP_ARRAY1_12_M = ABS(IP_ARRAY1_1_M-IP_ARRAY1_2_M),
 $   IP_ARRAY1_15_M = DIM(((IP_ARRAY1_1_M)),IP_ARRAY1_2_M),
 $   IP_ARRAY1_17_M = IAND(IP_ARRAY1_1_M,IP_ARRAY1_2_M),
 $   IP_ARRAY1_18_M = IBCLR(IP_ARRAY1_1_M,IP_ARRAY1_2_M),
 $   IP_ARRAY1_19_M = IBITS(IP_ARRAY1_1_M,IP_ARRAY1_2_M,
 $MAX(3,IP_ARRAY1_2_M(10:1:-1))),
 $   IP_ARRAY1_20_M(-MP10) = IBSET(IP_ARRAY1_1_M,IP_ARRAY1_2_M),
 $   IP_ARRAY1_21_M(NP2*NP5) = IEOR(IP_ARRAY1_1_M,IP_ARRAY1_2_M),
 $   IP_ARRAY1_22_M(NP10) = IOR(IP_ARRAY1_1_M,IP_ARRAY1_2_M),
 $   IP_ARRAY1_23_M(10) = INT(IP_ARRAY1_1_M),
 $   IP_ARRAY1_24_M = ISHFT(IP_ARRAY1_1_M,IP_ARRAY1_2_M),
 $   IP_ARRAY1_25_M = ISHFTC(IP_ARRAY1_1_M,IP_ARRAY1_2_M,
 $ MAX(5,IP_ARRAY1_2_M))


  END MODULE MODS_big


-- 
   Summary: internal compiler error for complicated PARAMETER
expressions
   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=35780



[Bug fortran/35769] New: inappropriate FORALL error

2008-03-30 Thread dick dot hendrickson at gmail dot com
The following (silly) program gives an incorrect error message.
There is only one assignment to each diagonal element of
the array.  I don't feel strongly about this because FORALL
is sort of a junk feature and this is an unlikely programming
style.  But, to be correct you should downgrade from ERROR
to WARNING for the message severity.

Dick Hendrickson

  program forall_warn
  integer  lda(10,10)

  FORALL(J1=1:10, J2=1:10,  J1 .EQ. J2) LDA(J1,J1) = 1

  end


gfortran:gfortran forall_warn.f
forall_warn.f:4.47:

  FORALL(J1=1:10, J2=1:10,  J1 .EQ. J2) LDA(J1,J1) = 1
  1
Error: The FORALL with index 'j2' cause more than one assignment to this object
at (1)


-- 
   Summary: inappropriate FORALL error
   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=35769



[Bug fortran/35770] New: implicit character(s) hides type of internal function

2008-03-30 Thread dick dot hendrickson at gmail dot com
The program gives an error message when the internal
function has an apparent character type due to the implicit
statement.  Commenting out the implicit fixes it.  This
looks similar to 34784 to me.

  program SA0021

! fails on Windows XP
! gcc version 4.4.0 20080312 (experimental) [trunk revision 133139]
!maybe also see 34784?


  implicit character (s)  ! removing this fixes the problem
  REAL RDA(10)
  RDA = 0

  RDA(J1) = S_REAL_SQRT_I(RDA(J1))

  CONTAINS

  ELEMENTAL FUNCTION S_REAL_SQRT_I(X) RESULT (R)
  REAL, INTENT(IN)  ::  X
  REAL  ::  R
R = 0.0
  END FUNCTION S_REAL_SQRT_I !internal procedure

  END

gfortran:gfortran sa0021.f
sa0021.f:11.16:

  RDA(J1) = S_REAL_SQRT_I(RDA(J1))
   1
Error: Can't convert CHARACTER(1) to REAL(4) at (1)


-- 
   Summary: implicit character(s) hides type of internal function
   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=35770



[Bug fortran/35756] New: incorrect WHERE for functions in ELSEWHERE and overlaps

2008-03-29 Thread dick dot hendrickson at gmail dot com
The following program computes the wrong values for the even
(elsewhere branch) of the left hand array.  It looks like the
function R_MY_MIN_I is evaluated before the store in the WHERE
branch happens.

The same thing happens if the R_M* functions are external 
rather than contained.

Dick Hendrickson

  program RA1028

! fails on Windows XP
! gcc version 4.4.0 20080312 (experimental) [trunk revision 133139]

  INTEGER  ILA(10)
  LOGICAL  LDA(10)

  ILA = (/ (I, i=1,10) /)
  LDA = (/ (i/2*2 .ne. I, i=1,10) /)

  WHERE(LDA)
ILA = R_MY_MAX_I(ILA)
  ELSEWHERE
ILA = R_MY_MIN_I(ILA)
  ENDWHERE

  print *, 10,2,10,2, '  etc'!expected
  print *, ila

  CONTAINS

  INTEGER FUNCTION R_MY_MAX_I(A)
  INTEGER  ::  A(:)
  R_MY_MAX_I = MAXVAL(A)
  END FUNCTION R_MY_MAX_I !internal procedure

  INTEGER FUNCTION R_MY_MIN_I(A)
  INTEGER  ::  A(:)
  R_MY_MIN_I = MINVAL(A)
  END FUNCTION R_MY_MIN_I !internal procedure

  END



C:\g_experiments\gfortrangfortran ra1028.f

C:\g_experiments\gfortrana
  10   2  10   2   etc
  10   1  10   1  10   1
  10   1  10   1


-- 
   Summary: incorrect WHERE for functions in ELSEWHERE and overlaps
   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=35756



[Bug fortran/35759] New: WHERE with overlap with ELSEWHERE error

2008-03-29 Thread dick dot hendrickson at gmail dot com
The following program computes the wrong result for a WHERE where
different sections of the same array are in both the WHERE and
ELSEWHERE section.  It's as if the ELSEWHERE block were
ignored.

Dick Hendrickson

  program RG0023
! fails on Windows XP
! gcc version 4.4.0 20080312 (experimental) [trunk revision 133139]


  integer UDA1L(6)
  integer ::  UDA1R(6), expected(6) = (/2,0,5,0,3,0/)
  LOGICAL LDA(5)

  UDA1L(1:6) = 0
  uda1r = (/1,2,3,4,5,6/)
  lda = (/ (i/2*2 .ne. I, i=1,5) /)

  WHERE (LDA)!  expected
UDA1L(1:5) = UDA1R(2:6)  !  uda1l = 2,0,4,0,6,0
  ELSEWHERE
UDA1L(2:6) = UDA1R(6:2:-1) !uda1l = 2,0,5,0,3,0
  ENDWHERE

  print *, 'expected = ',expected
  print *, 'computed = ', uda1l

  END

gfortran:gfortran rg0023.f

gfortran:a
 expected =2   0   5   0   3  
0
 computed =2   0   4   0   6  
0


-- 
   Summary: WHERE with overlap with ELSEWHERE error
   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=35759



[Bug fortran/35681] wrong result for vector subscripted array expression in MVBITS

2008-03-28 Thread dick dot hendrickson at gmail dot com


--- Comment #3 from dick dot hendrickson at gmail dot com  2008-03-28 15:48 
---
Subject: Re:  wrong result for vector subscripted array expression in MVBITS

Right, in case you haven't found it yet, the first paragraph of
12.7.3, page 214, says effectively
that all of the arguments must be conformable with the TO argument.  I
was mildly amused
that a significant restriction on MVBITS came in the paragraph before
the one that
explicitly discusses MVBITS.

Dick Hendrickson

On 28 Mar 2008 15:29:05 -, dominiq at lps dot ens dot fr
[EMAIL PROTECTED] wrote:


  --- Comment #2 from dominiq at lps dot ens dot fr  2008-03-28 15:29 
 ---
  For the second test in comment #1, ifort gives:

  fortcom: Error: pr35681_2.f90, line 2: The shapes of the arguments do not
  conform.   [MVBITS]

   call mvbits ((ILA1((/9/))), 2, 4, ILA1, 3)
  ^


  --




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

  --- You are receiving this mail because: ---
  You reported the bug, or are watching the reporter.



-- 


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



[Bug fortran/35743] New: allocate negative memory for zero-sized WHERE construct

2008-03-28 Thread dick dot hendrickson at gmail dot com
The following program fails when rg0025 attempts to allocate a negative
amount of memory under windows XP.  It doesn't abort when the array
subscripts are explicit constants instead of variables.

Dick Hendrickson
  program try_rg0025
! fails on Windows XP
! gcc version 4.4.0 20080312 (experimental) [trunk revision 133139]


  logical lda(5)
  lda = (/ (i/2*2 .ne. I, i=1,5) /)

  call   xx0025(lda,  1,  2,  3,  5,  6, -1, -2)   !works
  call   rg0025(lda,  1,  2,  3,  5,  6, -1, -2)   !fails

  end program

  SUBROUTINE XX0025(LDA,nf1,nf2,nf3,nf5,nf6,mf1,mf2)
  type unseq
real  r
  end type unseq
  TYPE(UNSEQ) TDA1L(6)
  LOGICAL LDA(NF5)

  TDA1L(1:6)%r = 1.0

  WHERE (LDA(6:3))
TDA1L(-1:5:-1) = TDA1L(6:2)
  ENDWHERE

  print *, 'end of xx0025'
  END SUBROUTINE

  SUBROUTINE RG0025(LDA,nf1,nf2,nf3,nf5,nf6,mf1,mf2)
  type unseq
real  r
  end type unseq
  TYPE(UNSEQ) TDA1L(6)
  LOGICAL LDA(NF5)

  TDA1L(1:6)%r = 1.0

  WHERE (LDA(NF6:NF3))
TDA1L(MF1:NF5:MF1) = TDA1L(NF6:NF2)
  ENDWHERE

  END SUBROUTINE

C:\g_experiments\gfortrangfortran rg0025.f

C:g_experiments\gfortrana
 end of xx0025
Fortran runtime error: Attempt to allocate a negative amount of memory.


-- 
   Summary: allocate negative memory for zero-sized WHERE construct
   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=35743



[Bug fortran/35745] New: Divide incorrectly extracted from WHERE block?; run time abort

2008-03-28 Thread dick dot hendrickson at gmail dot com
The following program aborts at run-time opening a 
box that says
a.exe has encountered a problem and needs to close.  
We are sorry for the inconvenience.

And then offers to send an error report to Microsoft.
I believe the problem is the extraction of the 1/NF0
from within the WHERE block.

  program RZ0048
  INTEGER IDA(10)
  REAL RDA(10)

  RDA= 1.0

  nf0 = 3
  WHERE (RDA  -15.0)
IDA = 1/NF0 + 2
  ENDWHERE
  print *, 'first where completed'

  nf0 = 0

  WHERE (RDA  -15.0)
IDA = 1/NF0 + 2
  ENDWHERE

  END


-- 
   Summary: Divide incorrectly extracted from WHERE block?; run time
abort
   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=35745



[Bug fortran/35718] New: deallocating non-allocated pointer target does not fail

2008-03-27 Thread dick dot hendrickson at gmail dot com
The following program fails to raise an error condition in the deallocate
statement.  The pointer target was not created by an allocate.

Dick Hendrickson

  program MF0069
! fails on Windows XP
! gcc version 4.4.0 20080312 (experimental) [trunk revision 133139]
! F95 page 83, line 34 says deallocating a pointer whose target
!wasn't created by an ALLOCATE causes error condition


  REAL, pointer  :: RLA(:)
  REAL, TARGET   :: RLA1(6)
  RLA1 = 0
  RLA = RLA1
  DEALLOCATE (RLA, STAT = ISTAT)
  IF (ISTAT .LE. 0) print *, 'deallocate did not fail!', istat
  END


-- 
   Summary: deallocating non-allocated pointer target does not fail
   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=35718



[Bug fortran/35719] New: pointer to zero sized array not associated

2008-03-27 Thread dick dot hendrickson at gmail dot com
The ASSOCIATED function returns FALSE when its argument is a
pointer to a zero-sized array.

Dick Hendrickson

  program try_mf1053

! fails on Windows XP
! gcc version 4.4.0 20080312 (experimental) [trunk revision 133139]

  call   mf1053 (  1,   2,   3,   4)
  end

  SUBROUTINE MF1053 (nf1, nf2, nf3, nf4)
  INTEGER, pointer :: ILA(:,:)
  INTEGER, target  :: ILA1(NF2,NF4:NF3)

  ILA = ILA1

  if (ASSOCIATED (ILA, ILA1(NF1:NF2,NF4:NF3) ) ) print *, 1 bad
  if ( .not. ASSOCIATED(ILA) )  print *, 2 bad

  END SUBROUTINE

C:\g_experiments\gfortrangfortran mf1053.f

C:\g_experiments\gfortrana
 2 bad


-- 
   Summary: pointer to zero sized array not associated
   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=35719



[Bug fortran/35721] New: ASSOCIATED returns false when strides confusing

2008-03-27 Thread dick dot hendrickson at gmail dot com
The ASSOCIATED functions returns false for the 4th test below.  It
should return true.  there have been a ton of interps and rewording
of the associated function.  It's probably clearer to read
case (v) in the F2003 standard.

  program try_mg0028
! fails on Windows XP
! gcc version 4.4.0 20080312 (experimental) [trunk revision 133139]

  real  tda2r(2,3)

  call   mg0028(tda2r,  1,  2,  3)

  end


  SUBROUTINE MG0028(TDA2R,nf1,nf2,nf3)
  real, pointer  ::  TLA2L(:,:),TLA2L1(:,:)
  real, target   ::  TDA2R(NF2,NF3)
  logical LL(4)
  TLA2L = TDA2R(NF2:NF1:-NF2,NF3:NF1:-NF2)
  TLA2L1 = TLA2L
  LL(1) = ASSOCIATED(TLA2L)
  LL(2) = ASSOCIATED(TLA2L,TLA2L1)
  LL(3) = ASSOCIATED(TLA2L,TDA2R)
  LL(4) = ASSOCIATED(TLA2L1,TDA2R(2:2,3:1:-2))  !should be true

  if (any(LL .neqv. (/ .true., .true., .false., .true./))) then
print *, LL
print *, shape(TLA2L1)
print *, shape(TDA2R(2:2,3:1:-2))
  endif

  END SUBROUTINE


C:\g_experiments\gfortrangfortran m
g0028.f

C:\g_experiments\gfortrana
 T T F F
   1   2
   1   2


-- 
   Summary: ASSOCIATED returns false when strides confusing
   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=35721



[Bug fortran/35723] New: Can't use run-time array element in character declaration

2008-03-27 Thread dick dot hendrickson at gmail dot com
The following program gives an error message for valid use of
an array element in an expression for an automatic character
array.  

The error message is repeated twice.

Changing from a run-time subscript in the parameter array to a
constant fixes the problem.

Dick Hendrickson

  program try_vf0016
! fails on Windows XP
! gcc version 4.4.0 20080312 (experimental) [trunk revision 133139]
! syntax error for valid syntax

  call   vf0016(  1,  2,  3)

  end
  SUBROUTINE VF0016(nf1,nf2,nf3)
  CHARACTER(LEN=9,KIND=1),DIMENSION(3), PARAMETER
 $ ::  TEST_STRINGS =
 $  (/'   HI','ABC  ','  CDEFG  '/)
  CHARACTER :: TEST_ARRAY
 $(LEN_TRIM(ADJUSTL(TEST_STRINGS(nf1))),  ! changing nf1 to 1 fixes it
 $ SUM(LEN_TRIM(ADJUSTL(TEST_STRINGS))),
 $ LEN_TRIM(ADJUSTL(ADJUSTR(TEST_STRINGS(3,
 $ SUM(LEN_TRIM(ADJUSTL(ADJUSTR(TEST_STRINGS(NF1:NF3:NF2)   )

   print *, 2, 10, 5, 7
   print *, shape (test_array)
 end



C:\g_experiments\gfortrangfortran vf0016.f
vf0016.f:14.24:

 $(LEN_TRIM(ADJUSTL(TEST_STRINGS(nf1))),  ! changing nf1 to 1 fixes
   1
Error: Variable 'test_strings' cannot appear in the expression at (1)
vf0016.f:14.24:

 $(LEN_TRIM(ADJUSTL(TEST_STRINGS(nf1))),  ! changing nf1 to 1 fixes
   1
Error: Variable 'test_strings' cannot appear in the expression at (1)


-- 
   Summary: Can't use run-time array element in character
declaration
   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=35723



[Bug fortran/35724] New: Compile time segmentation fault for CSHIFT with negative third arg

2008-03-27 Thread dick dot hendrickson at gmail dot com
The following program gives a compile time segmentation fault.
Changing the third argument to CSHIFT to either MF1 or -1 fixes 
the problem.

I didn't experiment with a unary minus expression for the 
second argument.

Dick Hendrickson

  SUBROUTINE RA0072(DDA,LDA,nf10,nf1,mf1,nf2)
! fails on Windows XP
! gcc version 4.4.0 20080312 (experimental) [trunk revision 133139]
!compile time seq fault

  REAL DDA(10,10)
  LOGICAL LDA(10,10)

  WHERE (LDA) DDA = CSHIFT(DDA,1,-MF1)  ! MF1 works, -1 works

  END SUBROUTINE



C:\g_experiments\gfortrangfortran ra0072.f
f951.exe: internal compiler error: Segmentation fault
Please submit a full bug report,
with preprocessed source if appropriate.
See http://gcc.gnu.org/bugs.html for instructions.


-- 
   Summary: Compile time segmentation fault for CSHIFT with negative
third arg
   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=35724



[Bug fortran/35721] ASSOCIATED returns false when strides confusing

2008-03-27 Thread dick dot hendrickson at gmail dot com


--- Comment #2 from dick dot hendrickson at gmail dot com  2008-03-28 00:57 
---
Subject: Re:  ASSOCIATED returns false when strides confusing

On 27 Mar 2008 18:27:44 -, burnus at gcc dot gnu dot org
[EMAIL PROTECTED] wrote:


  --- Comment #1 from burnus at gcc dot gnu dot org  2008-03-27 18:27 
 ---
  Confirm. Note NAG f95 complains the program is invalid and I think it is 
 right:

  Error: Explicit interface required for MG0028 from TRY_MG0028 - argument 
 TDA2R
  (no. 1) is a TARGET

Yes, you (and NAG) are correct.  Originally, the subroutine was in a big module
and when I cut it out I did the quick and dirty thing of merely
calling it without
thinking.  For what it's worth, the other g compiler I tried this on
also got the wrong
answer and didn't complain about the interface.

Dick Hendrickson

  But this does not solve the gfortran problem ;-)

  From the standard: (v) applies here, but (vii) is analog - except that TARGET
  is a pointer instead of a target.

  Case (v): If TARGET is present and is an array target, the result is true if
  the target associated with POINTER and TARGET have the same shape, are 
 neither
  of size zero nor arrays whose elements are zero-sized storage sequences, and
  occupy the same storage units in array element order. Otherwise, the result 
 is
  false. If POINTER is disassociated, the result is false.

  gfortran is failing since in dimension 1 they have different strides:
  Pointer:  2:1:-2  (namely: element 2)
  Target:   2:2:1   (namely: element 2)

  However, libgfortran/intrinsics/associated.c only checks whether the stride 
 is
  the same. Proposed patch:

  Index: libgfortran/intrinsics/associated.c
  ===
  --- libgfortran/intrinsics/associated.c (Revision 133633)
  +++ libgfortran/intrinsics/associated.c (Arbeitskopie)
  @@ -48,10 +48,12 @@ associated (const gfc_array_void *pointe
rank = GFC_DESCRIPTOR_RANK (pointer);
for (n = 0; n  rank; n++)
  {
  -  if (pointer-dim[n].stride != target-dim[n].stride)
  +  long extent;
  +  extent = pointer-dim[n].ubound - pointer-dim[n].lbound;
  +
  +  if (extent != (target-dim[n].ubound - target-dim[n].lbound))
  return 0;
  -  if ((pointer-dim[n].ubound - pointer-dim[n].lbound)
  -  != (target-dim[n].ubound - target-dim[n].lbound))
  +  if (pointer-dim[n].stride != target-dim[n].stride  extent != 0)
  return 0;
if (pointer-dim[n].ubound  pointer-dim[n].lbound)
 return 0;


  --

  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
Last reconfirmed|-00-00 00:00:00 |2008-03-27 18:27:43
date||


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

  --- You are receiving this mail because: ---
  You reported the bug, or are watching the reporter.



-- 


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



[Bug fortran/35698] New: lbound and ubound wrong for allocated run-time zero size array

2008-03-25 Thread dick dot hendrickson at gmail dot com
The following program gives wrong results for some positions
in LBOUND and UBOUND.  The allocated array has a run-time
computed zero-sized subscript range in the 4th subscript.
LBOUND and UBOUND give incorrect results for the 5th, 6th,
and 7th subscript.  They propagate the zero size (1,0) pair.
the results in subscripts 1, 2, and 3 are correct. 

The results are correct if the 4th subscript is replaced with
10:1 instead of the run-time expression.

Dick Hendrickson


 first test loop
   5  expected lbound =  -2 computed =1
   6  expected lbound =  -3 computed =1
   7  expected lbound =  -4 computed =1
 second test loop
   5  expected ubound =   7 computed =0
   6  expected ubound =   8 computed =0
   7  expected ubound =   9 computed =0



  program try_lf0030
! fails on Windows XP
! gcc version 4.4.0 20080312 (experimental) [trunk revision 133139]

  call LF0030(10)
  end

  SUBROUTINE LF0030(nf10)
  INTEGER ILA1(7)
  INTEGER ILA2(7)
  LOGICAL LLA(:,:,:,:,:,:,:)
  INTEGER ICA(7)
  ALLOCATABLE LLA


  ALLOCATE (LLA(2:3, 4, 0:5,
 $  NF10:1, -2:7, -3:8,
 $  -4:9))

  ILA1 = LBOUND(LLA)
  ILA2 = UBOUND(LLA)
C CORRECT FOR THE ZERO DIMENSIONED TERM TO ALLOW AN EASIER VERIFY
  ILA1(4) = ILA1(4) - 2!   1 - 2 = -1
  ILA2(4) = ILA2(4) + 6!   0 + 6 = 6 

  print *, 'first test loop'
  DO J1 = 1,7
  IVAL = 3-J1
  IF (ILA1(J1) .NE. IVAL) print *, J1,  expected lbound =, 
 $ ival, computed = , ila1(j1)
  100 ENDDO

  print *, 'second test loop'
  DO J1 = 1,7
  IVAL = 2+J1
  IF (ILA2(J1) .NE. IVAL) print *, J1,  expected ubound =, 
 $ ival, computed = , ila2(j1)
  101 ENDDO

  END SUBROUTINE


-- 
   Summary: lbound and ubound wrong for allocated run-time zero size
array
   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=35698



[Bug fortran/35699] New: run-time abort writing zero sized section to direct access file

2008-03-25 Thread dick dot hendrickson at gmail dot com
On Windows XP, with SP2, the following program beeps at me
and opens an alert box saying
a.exe has encountered a problem and needs to close.  
We are sorry for the inconvenience.

and offers to send Microsoft an error report (I declined).

Based on the print statements, it's the write statement that 
is causing the problem.

Changing the zero sized section subscripts from nf4:nf3 to
4:3 does not cure the problem 

  program try_qi0010
! fails on Windows XP
! gcc version 4.4.0 20080312 (experimental) [trunk revision 133139]



  call   QI0010 (  10,   1,   2,   3,   4,  9,   2)
  end

  SUBROUTINE QI0010 (nf10, nf1, nf2, nf3, nf4,nf9, np2)
  CHARACTER(9) BDA(nf10)
  CHARACTER(9) BDA1(nf10), bval

  INTEGER  J_LEN
  bda1(1) = 'x'
  do I = 2,10
  bda1(i) = 'x'//bda1(i-1)
  enddo
  bda = 'unread'

  print *, 'begin inquire'
  INQUIRE(IOLENGTH = J_LEN) BDA1(NF1:NF10:NF2), BDA1(NF4:NF3),
 $   BDA1(NF2:NF10:NF2)

  print *, 'begin open '
  OPEN (UNIT=48,
 $  STATUS='SCRATCH',
 $  ACCESS='DIRECT',
 $  RECL = j_len,
 $  IOSTAT = ISTAT,
 $  FORM='UNFORMATTED',
 $  ACTION='READWRITE')

  print *, 'begin write '
  WRITE (48,IOSTAT = ISTAT, REC = 3) BDA1(NF1:NF10:NF2),
 $BDA1(NF4:NF3), BDA1(NF2:NF10:NF2)
  IF ( ISTAT .NE. 0) then
print *, istat, ' WRITE FAILED '
stop
  ENDIF
  ISTAT = -314

  print *, 'begin read '

  READ (48,IOSTAT = ISTAT, REC = NP2+1) BDA(NF1:NF9:NF2),
 $   BDA(NF4:NF3), BDA(NF2:NF10:NF2)
  IF ( ISTAT .NE. 0) THEN
print *, istat, ' read FAILED '
stop
  ENDIF

  print *, 'begin check '
  DO J1 = 1,10
  BVAL = BDA1(J1)
  IF (BDA(J1) .NE. BVAL)
 $ print *, j1 ,BDA(J1),BVAL
  100 ENDDO;
  END SUBROUTINE


-- 
   Summary: run-time abort writing zero sized section to direct
access file
   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=35699



[Bug fortran/35699] run-time abort writing zero sized section to direct access file

2008-03-25 Thread dick dot hendrickson at gmail dot com


--- Comment #1 from dick dot hendrickson at gmail dot com  2008-03-25 21:49 
---
I have another essentially identical subroutine that uses double complex
instead of character and appears to fail in the same way.  I also have three
other subroutines that write/read zero sized arrays and return a non-zero
iostat value or incorrectly read a single value into the zero sized array. 
These are simpler write/reads and only have a single array, as opposed to
three, in the i/o lists.  For me, it's a mechanical pain in the rear to extract
the additional cases.  I'm looking for advice, is it easier A) for you to send
me a link to an experimental windows compiler once you think you have a fix, B)
me to wait until the next release and then retry the other cases, C)  slowly
over the next few days extract the others and make a working version of them? 
Or, do you guys have another suggestion?

Dick Hendrickson

Dick Hendrickson


-- 

dick dot hendrickson at gmail dot com changed:

   What|Removed |Added

 CC||dick dot hendrickson at
   ||gmail dot com


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



[Bug fortran/35702] New: internal compiler error: structure character element with subscripts

2008-03-25 Thread dick dot hendrickson at gmail dot com
The following program produces an internal compiler error.
Changing the structure element to real or replacing the
structure subscripts with constants fixes the problem.

  MODULE TESTS
! fails on Windows XP
! gcc version 4.4.0 20080312 (experimental) [trunk revision 133139]
! cg0028.f:15: internal compiler error: in gfc_add_modify, at
fortran/trans.c:167


  TYPE UNSEQ


CHARACTER(1)::  C
!real   ::  C !works

  END TYPE UNSEQ   
  CONTAINS
  SUBROUTINE CG0028(TDA1L,TDA1R,nf0,nf1,nf2,nf3)
  TYPE(UNSEQ) TDA1L(NF3)
  TYPE(UNSEQ) TDA1R(NF3)

  TDA1L(NF1:NF2:NF1)%C = TDA1L(NF0+2:NF3:NF2/2)%C

!  TDA1L(1:2:1)%C = TDA1L(0+2:3:2/2)%C   !works

  END SUBROUTINE
  END MODULE TESTS


-- 
   Summary: internal compiler error: structure character element
with subscripts
   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=35702



[Bug fortran/35681] New: wrong result for vector subscripted array expression in MVBITS

2008-03-24 Thread dick dot hendrickson at gmail dot com
The following program prints out the wrong results when an
array with vector valued subscript is used in an expression
as the FROM argument and also used as the TO argument.
The array case gives different results from a similar
scalar DO loop.

If a different array is used in the FROM argument, the array
results are the same as the scalar results.

I'd guess that you aren't recognizing
(ILA1(NFV3))
as an expression and copying it to a temp before invoking
MVBITS.

Dick Hendrickson


  program YA0017

! gcc version 4.4.0 20080312 (experimental) [trunk revision 133139] (GCC)

  INTEGER ILA1(10)
  INTEGER ILA2(10)
  INTEGER ICA3(10), nfv3(10)
  ILA1 = (/1,2,3,4,5,6,7,8,9,10/)
  ILA2 = (/1,2,3,4,5,6,7,8,9,10/)
  ica3 = (/1,2,3,4,5,6,7,8,9,10/)
  nfv3 = (/9,9,6,2,4,9,2,9,6,10/)

  DO J1 = 1,10
CALL MVBITS(Ila1(NFV3(J1)),2,4,ILA2(J1), 3)
  ENDDO

  CALL MVBITS ((ILA1(NFV3)), 2, 4, ILA1, 3)   !fails

  print *, 'first test'
  DO J1 = 1,10
  IF (ILA1(J1) .NE. ILA2(J1))
 $ print *, 'j1 = ', j1, '  vvs = ', nfv3(j1),
 $ '  scalar =', ila2(j1), '  vector = ', ila1(j1)
  ENDDO


  ILA1 = (/1,2,3,4,5,6,7,8,9,10/)
  ILA2 = (/1,2,3,4,5,6,7,8,9,10/)
  ica3 = (/1,2,3,4,5,6,7,8,9,10/)
  nfv3 = (/9,9,6,2,4,9,2,9,6,10/)

  DO J1 = 1,10
CALL MVBITS(Ica3(NFV3(J1)),2,4,ILA2(J1), 3)
  ENDDO

  CALL MVBITS ((Ica3(NFV3)), 2, 4, ILA1, 3)  !works

  print *, 'second test'
  DO J1 = 1,10
  IF (ILA1(J1) .NE. ILA2(J1))
 $ print *, 'j1 = ', j1, '  vvs = ', nfv3(j1),
 $ '  scalar =', ila2(j1), '  vector = ', ila1(j1)
  ENDDO
  END 


---
results
C:\g_experiments\gfortrangfortran ya0017.f
C:\g_experiments\gfortrana
 first test
 j1 =4   vvs =2   scalar =   4   vector =
36
 j1 =5   vvs =4   scalar =  13   vector =
77
 j1 =7   vvs =2   scalar =   7   vector =
39
 j1 =9   vvs =6   scalar =   9   vector =
41
 second test


-- 
   Summary: wrong result for vector subscripted array expression in
MVBITS
   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=35681



[Bug fortran/35682] New: assignment to run-time zero-sized complex section stores a value

2008-03-24 Thread dick dot hendrickson at gmail dot com
When I try the following test program, a value is stored into
the first element of the complex array, even though the array
section is zero sized.  It fails with variables for the 
section subscripts and works if I use explicit constants
for the subscripts.

Dick Hendrickson
--
C:\g_experiments\gfortrangfortran ha0020.f

C:\g_experiments\gfortrana
 first test
   1 (-1.,  0.000)
 second test

--


  program  try_ha0020
  call ha0020(1,10,-1,2,-3)
  end program

  SUBROUTINE HA0020(nf1,nf10,mf1,nf2,mf3)
  COMPLEX XCA(20), xda(20)

  do I = 1,20
xca(i) = i
xda(i) = -i
  enddo

   XCA(NF1:NF10:MF1) = XDA(NF1:NF2:MF3)!fails

  print *, 'first test'

  DO J1 = 1,20
if (xca(j1) .ne. j1) print *, j1, xca(j1)
  enddo
  do I = 1,20
xca(i) = i
xda(i) = -i
  enddo

   xca(  1:  10: -1) = xda(  1:  2: -3)!works

  print *, 'second test'

  DO J1 = 1,20
if (xca(j1) .ne. j1) print *, j1, xca(j1)
  enddo

  END SUBROUTINE


-- 
   Summary: assignment to run-time zero-sized complex section stores
a value
   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=35682



[Bug fortran/35682] assignment to run-time zero-sized complex section stores a value

2008-03-24 Thread dick dot hendrickson at gmail dot com


--- Comment #1 from dick dot hendrickson at gmail dot com  2008-03-24 20:35 
---
Some similar assignment statements that work correctly
  ZCA(NF1:NF10:MF1) = ZDA(NF1:NF10:MF1)
  XCA(NF10:NF5:NF2) = XDA(NF4:NF9:MF2)

where the NF* variables have the value * and the 
MF* variables have the value -*.  NF3 = 3, MF2 = -2 

Dick Hendrickson


-- 

dick dot hendrickson at gmail dot com changed:

   What|Removed |Added

 CC||dick dot hendrickson at
   ||gmail dot com


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



[Bug fortran/35685] New: UBOUND incorrect for run-time zero-sized section

2008-03-24 Thread dick dot hendrickson at gmail dot com
The following program gives the wrong value for the UBOUND
function on a zero sized array.  It looks correct for constant
section subscripts, but incorrect for run-time expressions.
The related functions, LBOUND, SHAPE, and SIZE are correct.

Dick Hendrickson

C:\g_experiments\gfortrangfortran ja0045.f

C:\g_experiments\gfortrana
 UBOUND ZDA1=   0  -5  -1

---
  program try_ja0045
  call ja0045(3,-3,7,1,6)
  end program

  SUBROUTINE JA0045(nf3,mf3,nf7,nf1,nf6)
  INTEGER IDA(3)
  real ZDA1(3:10,4:10,5:10)

  IDA = UBOUND(ZDA1(3:2, NF3:MF3, NF7+NF1:NF6))
  if ( any(ida .ne. (/0,0,0/)) ) print *, 'UBOUND ZDA1=',ida

  IDA = LBOUND(ZDA1(3:2, NF3:MF3, NF7+NF1:NF6))
  if ( any(ida .ne. (/1,1,1/)) ) print *, 'LBOUND =',ida

  IDA = SHAPE(ZDA1(3:2, NF3:MF3, NF7+NF1:NF6))
  if ( any(ida .ne. (/0,0,0/)) ) print *, 'SHAPE =',ida

  J = SIZE(ZDA1(3:2, NF3:MF3, NF7+NF1:NF6))
  if ( j .ne. 0 ) print *, 'SIZE =',j


  END SUBROUTINE


-- 
   Summary: UBOUND incorrect for run-time zero-sized section
   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=35685



[Bug fortran/34945] New: LBOUND fails for array with KIND(complex) used in zero-sized dimension

2008-01-23 Thread dick dot hendrickson at gmail dot com
With compiler
gcc version 4.3.0 20080109 (experimental) [trunk revision 131426] (GCC)

I get the following error message


gfortran vf0009.f
vf0009.f: In function 'vf0009':
vf0009.f:11: error: size of variable 'test_array' is too large

If I replace the second line in the declaration of test_array with
any of
 $   KIND(IDA1):5,
 $   KIND(YDA):9,
 $   8:5,
the program compiles without an error message.
The LBOUND function is needed to trigger the error message

Dick Hendrickson

  SUBROUTINE VF0009(IDA1,IDA2,YDA,HDA)
  INTEGER(4) IDA1(4)
  INTEGER(4) IDA2(4)
  COMPLEX(8) YDA(2)
  INTEGER(4) HDA(3)
!  I N I T I A L I Z A T I O N  S E C T I O N
  COMPLEX(KIND=4) :: TEST_ARRAY
 $(  4:5,
 $   KIND(YDA):5,
 $   4:5,
 $   4:5  )
!  T E S T  S T A T E M E N T S
   IDA1(1:4) = LBOUND(TEST_ARRAY)
  END SUBROUTINE


-- 
   Summary: LBOUND fails for array with KIND(complex) used in zero-
sized dimension
   Product: gcc
   Version: 4.3.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=34945



[Bug fortran/34784] [4.2/4.3 Regression] implicit character(s) hides type of selected_int_kind intrinsic

2008-01-23 Thread dick dot hendrickson at gmail dot com


--- Comment #8 from dick dot hendrickson at gmail dot com  2008-01-23 18:31 
---
Subject: Re:  [4.2/4.3 Regression] implicit character(s) hides type of
selected_int_kind intrinsic

I have another example of what might be the same problem, although the
symptoms are
a little different.  the error message is

C:gfortran v_ice.f
v_ice.f:21.72:

  END MODULE TESTS
   1
Internal Error at (1):
gfc_convert_constant(): Unexpected type

If I use either
  IMPLICIT CHARACTER (D)
  IMPLICIT CHARACTER (E)
things compile, although I'd have expected a problem with either
DIGITS or EPSILON.

A procedure question.  Is this the One True Way to add additional
comments or tests
about a bug report?  Or is there a better way?

Dick Hendrickson


  MODULE TESTS
  IMPLICIT CHARACTER (M)
  CONTAINS
  SUBROUTINE VF0010(IDA1,IDA2,RDA,QDA)
  INTEGER(4) IDA1(5)
  INTEGER(4) IDA2(5)
  REAL(4) RLA(5)
  REAL(4) RDA(5)
  REAL(8) QDA(5)
  REAL(8) DCA(5)
!  I N I T I A L I Z A T I O N  S E C T I O N
  INTEGER(KIND=4) :: TEST_ARRAY
 $(SUM((/DIGITS(1),DIGITS(RLA(2)),DIGITS(DCA),DIGITS(QDA)/))/10,
 $  MIN(6_4,
 $   INT((EPSILON(RLA)+EPSILON(ABS(QDA))+EPSILON(DCA))*1.E6)),
 $  INT(MIN(RDA(1),HUGE(RLA)/10)+MIN(QDA(1),HUGE(QDA)/10)
 $  +MIN(1,HUGE(IDA2))),
 $  MIN(6,MAXEXPONENT(1.0_8)+MAXEXPONENT(RLA)+
 $  MAXEXPONENT(QDA)))
  END SUBROUTINE
  END MODULE TESTS


On 20 Jan 2008 16:59:09 -, pault at gcc dot gnu dot org
[EMAIL PROTECTED] wrote:


 --- Comment #7 from pault at gcc dot gnu dot org  2008-01-20 16:59 ---
 Subject: Bug 34784

 Author: pault
 Date: Sun Jan 20 16:58:15 2008
 New Revision: 131679

 URL: http://gcc.gnu.org/viewcvs?root=gccview=revrev=131679
 Log:
 2008-01-20  Paul Thomas  [EMAIL PROTECTED]

 PR fortran/34861
 * resolve.c (resolve_entries): Do not do an array bounds check
 if the result symbols are the same.

 PR fortran/34854
 * module.c (read_module) : Hide the symtree of the previous
 version of the symbol if this symbol is renamed.

 2008-01-20  Paul Thomas  [EMAIL PROTECTED]

 PR fortran/34784
 * gfortran.dg/mapping_2.f90: Correct ubound expression for h4.

 PR fortran/34861
 * gfortran.dg/entry_array_specs_3.f90: New test.

 PR fortran/34854
 * gfortran.dg/use_rename_1.f90: New test.

 Added:
 trunk/gcc/testsuite/gfortran.dg/entry_array_specs_3.f90
 trunk/gcc/testsuite/gfortran.dg/use_rename_1.f90
 Modified:
 trunk/gcc/fortran/ChangeLog
 trunk/gcc/fortran/module.c
 trunk/gcc/fortran/resolve.c
 trunk/gcc/testsuite/ChangeLog
 trunk/gcc/testsuite/gfortran.dg/mapping_2.f90


 --



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

 --- You are receiving this mail because: ---
 You reported the bug, or are watching the reporter.



-- 


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



[Bug fortran/34875] New: read into vector-valued section doesn't transfer any values

2008-01-19 Thread dick dot hendrickson at gmail dot com
With compiler
4.3.0 20080109 (experimental) [trunk revision 131426] (GCC)

vector valued reads into an array don't appear to read in values.
The test program prints out
 kind of qda =4
 vector valued read failed
   1 -100.00  1.
   2 -100.00   2.000
   3 -100.00   3.000
   4 -100.00   4.000
   5 -100.00   5.000
   6 -100.00   6.000
   7 -100.00   7.000
   8 -100.00   8.000
   9 -100.00   9.000
  10 -100.00  10.000
 subscript range read succeeded

Dick Hendrickson

  Program QH0008

  REAL(4) QDA(10)
  REAL(4) QDA1(10)
  integer, dimension(10) ::  nfv1 = (/1,2,3,4,5,6,7,8,9,10/)

  qda1 = nfv1
  qda = -100

  print *, 'kind of qda = ', kind(qda)
  OPEN (UNIT=47,
 $  STATUS='SCRATCH',
 $  FORM='UNFORMATTED',
 $ ACTION='READWRITE')
  ISTAT = -314
  REWIND (47, IOSTAT = ISTAT)
  IF ( ISTAT .NE. 0) THEN
stop ' FIRST REWIND FAILED '
  ENDIF

  ISTAT = -314
  WRITE (47,IOSTAT = ISTAT) QDA1
  IF ( ISTAT .NE. 0) THEN
stop ' WRITE FAILED '
  ENDIF

  ISTAT = -314
  REWIND (47, IOSTAT = ISTAT)
  IF ( ISTAT .NE. 0) THEN
stop ' SECOND REWIND FAILED '
  ENDIF
  READ (47,IOSTAT = ISTAT) QDA(NFV1)
  IF ( ISTAT .NE. 0) THEN
stop ' READ FAILED '
  ENDIF

  IF ( ANY (QDA .ne. QDA1) ) then
 print *, 'vector valued read failed'
 DO I = 1,10
   print *, I, qda(i), qda1(i)
 enddo
  else
print *, 'vector valued read succeeded'
  endif


  ISTAT = -314
  REWIND (47, IOSTAT = ISTAT)
  IF ( ISTAT .NE. 0) THEN
stop ' THIRD REWIND FAILED '
  ENDIF
  qda = -200

  READ (47,IOSTAT = ISTAT) QDA(1:10)
  IF ( ISTAT .NE. 0) THEN
stop ' READ FAILED '
  ENDIF

  IF ( ANY (QDA .ne. QDA1) ) then
 print *, 'vector valued read failed'
 DO I = 1,10
   print *, I, qda(i), qda1(i)
 enddo
  else
print *, 'subscript range read succeeded'
  endif


  END


-- 
   Summary: read into vector-valued section doesn't transfer any
values
   Product: gcc
   Version: 4.3.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=34875



[Bug fortran/34876] New: can't read zero length array sections

2008-01-19 Thread dick dot hendrickson at gmail dot com
The following program prints READ FAILED.  A similar program
with an unformatted, rather than direct access, file also fails.

Dick Hendrickson

  Program qi0011
  CHARACTER(9) BDA(10)
  CHARACTER(9) BDA1(10)
  INTEGER  J_LEN
  ISTAT = -314

  INQUIRE(IOLENGTH = J_LEN) BDA1

  ISTAT = -314
  OPEN (UNIT=48,
 $  STATUS='SCRATCH',
 $  ACCESS='DIRECT',
 $  RECL = j_len,
 $  IOSTAT = ISTAT,
 $  FORM='UNFORMATTED',
 $  ACTION='READWRITE')


  IF (ISTAT /= 0) stop

  BDA = 'x'
  WRITE (48,IOSTAT = ISTAT, REC = 10) BDA1(4:3)
  IF ( ISTAT .NE. 0) THEN
stop ' WRITE FAILED '
  ENDIF

  ISTAT = -314
  READ (48,IOSTAT = ISTAT, REC=10) BDA(4:3)
  IF ( ISTAT .NE. 0) THEN
stop ' READ FAILED '
  ENDIF
  end


-- 
   Summary: can't read zero length array sections
   Product: gcc
   Version: 4.3.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=34876



[Bug fortran/34861] ICE in function with entry (and result?)

2008-01-19 Thread dick dot hendrickson at gmail dot com


--- Comment #4 from dick dot hendrickson at gmail dot com  2008-01-20 01:21 
---
Subject: Re:  ICE in function with entry (and result?)

Sorry, basically a typo on my part.  This is part of a large test suite and I
cut it down to a small case.  The variable NF3 has the value 3 and the
value is set in a way that the compiler shouldn't be able to use the
value in any optimizations.  You can either replace the NF3 by 3, add
NF3 to the argument list, or put the function in a module and declare
NF3 above the contains.

I try to run these small examples through another compiler as a check on
my typing skills.  This one clearly slipped by without the check.  I hope it
didn't cause too much trouble.

Dick Hendrickson

On 19 Jan 2008 18:42:13 -, dominiq at lps dot ens dot fr
[EMAIL PROTECTED] wrote:


 --- Comment #3 from dominiq at lps dot ens dot fr  2008-01-19 18:42 
 ---
 Is really SIZE(IDA2,NF3) done on purpose? or is this a typo for
 SIZE(IDA2,3)? It does not change the ICE AFAICT.



 --


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

 --- You are receiving this mail because: ---
 You reported the bug, or are watching the reporter.



-- 


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



[Bug fortran/34861] New: ICE in function with entry (and result?)

2008-01-18 Thread dick dot hendrickson at gmail dot com
The following generates:
i_1_mods_bug.f:10.72:

  END FUNCTION
   1
Internal Error at (1):
gfc_compare_array_spec(): Array spec clobbered

 4.3.0 20080109 (experimental) [trunk revision 131426] (GCC)

It works fine if I delete all 3 ENTRY statements.  I don't know if the
RESULT clause is necessary or not.

Dick Hendrickson



  FUNCTION I_IMFUD0 ( IDA2 , NDS4, NDS3) RESULT(I_IMFUDP)
  INTEGER  ::   NDS4, NDS3
  INTEGER  ::   IDA2(5,NDS4,NDS3,2)
  INTEGER  ::   I_IMFUDP(SIZE(IDA2,1), SIZE(IDA2,2),
 $  SIZE(IDA2,NF3), SIZE(IDA2,4))
  ENTRY I_IMFUDX (NDS4, NDS3, IDA2) RESULT(I_IMFUDP)
  ENTRY I_IMFUDY (NDS3, NDS4, IDA2) RESULT(I_IMFUDP)
  ENTRY I_IMFUDZ (NDS3, IDA2, NDS4) RESULT(I_IMFUDP)
  I_IMFUDP = 1-IDA2(:,:,:,::NDS4-NDS3)
  END FUNCTION


-- 
   Summary: ICE in function with entry (and result?)
   Product: gcc
   Version: 4.3.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=34861



[Bug fortran/34805] defined assignment not allowed to vector subscripted array

2008-01-16 Thread dick dot hendrickson at gmail dot com


--- Comment #3 from dick dot hendrickson at gmail dot com  2008-01-16 20:07 
---
Subject: Re:  defined assignment not allowed to vector subscripted array

Why not put this one on hold for a while.  I'll check some more.
There never was a
formal interpretation request.  It's kind of odd, both NAG and DEC
have (had for DEC)
the SHAPE95 and neither has complained in the last 10 or so years
about this test.

My reading is that you nheed to read 7.5.1.6 to see how defined assignment is
interpreted.  After you've read lines 27 to 30, then you go to
chapter 12 to see
how subroutines are called on an element-by-element basis.  Malcolm Cohen's
argument long ago was that we had dueling sections.  If you start at chapter 12
you'll come to the conclusion that the example is disallowed.

I'll see if I can get J3 to come to a consensus.

Dick

On 16 Jan 2008 16:34:47 -, burnus at gcc dot gnu dot org
[EMAIL PROTECTED] wrote:


 --- Comment #2 from burnus at gcc dot gnu dot org  2008-01-16 16:34 
 ---
 Found the relevant part in the Fortran standard:

 Fortran 2003: 12.4.1.2 Actual arguments associated with dummy data objects

 If the actual argument is an array section having a vector subscript, the
 dummy argument is not definable and shall not have the INTENT (OUT), INTENT
 (INOUT), VOLATILE, or ASYNCHRONOUS attributes.

 gfortran has this check - but it is not triggered for assignment(=) - or it
 happens later than the mismatch.

 It would helpful, if you could find the interpretation or re-check the test
 case.


 (There is a to-be corrected typo:
 @@ -2001,7 +2025,7 @@ compare_actual_formal (gfc_actual_arglis
 {
   if (where)
 gfc_error (Array-section actual argument with vector subscripts 
 -  at %L is incompatible with INTENT(IN), INTENT(INOUT) 
 +  at %L is incompatible with INTENT(OUT), INTENT(INOUT) 
 
or VOLATILE attribute of the dummy argument '%s',
a-expr-where, f-sym-name);
   return 0;

 )


 --


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

 --- You are receiving this mail because: ---
 You reported the bug, or are watching the reporter.



-- 


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



[Bug fortran/34784] implicit character(s) hides type of selected_int_kind intrinsic

2008-01-15 Thread dick dot hendrickson at gmail dot com


--- Comment #1 from dick dot hendrickson at gmail dot com  2008-01-15 20:49 
---
Another example in executable code

  MODULE s_TESTS
  IMPLICIT CHARACTER (P)
  CONTAINS
  subroutine simple (u,j1)
  optional ::  j1
  if (present (j1)) stop
  end subroutine
  END MODULE s_TESTS


-- 


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



[Bug fortran/34805] New: defined assignment not allowed to vector subscripted array

2008-01-15 Thread dick dot hendrickson at gmail dot com
The test program gives the message:
c_tests_cg0018.f:28.20:

  TLA1L(NFV1) = UDA1R
   1
Error: Can't convert TYPE(seq) to TYPE(unseq) at (1)

Where NFV1 is an integer scalar array.

I believe the error is incorrect.  This is from the SHAPE95 test suite.
This test was contentious during the suite development and at least
one vendor almost submitted an interpretation request.  I believe
that lines 27 to 30 of page 110 say that elemental defined assignments
are processed element-by-element, in any order, so that it's as if 
things were written
  TLA1L(3) = UDA1R(3)
  TLA1L(7) = UDA1R(7)
  
and those assignments are perfectly well defined (and gfortran accepts
similar ones).  Additionally, assignments like
  real_array(NFV1) = some_other_array
are well defined (with a restriction on NFV1's values).  That's the gist
of the argument as I remember it from 10 years ago.  

The sample program is

  MODULE c_TESTS

  integer, save :: nfv1(10)

  TYPE UNSEQ
REAL  R
  END TYPE UNSEQ   

  TYPE SEQ
sequence
REAL  R
  END TYPE SEQ   

  INTERFACE ASSIGNMENT(=)
MODULE PROCEDURE C_U_TO_T
  END INTERFACE ASSIGNMENT(=)

  CONTAINS

  ELEMENTAL PURE SUBROUTINE C_U_TO_T(T,U)
  TYPE(SEQ),INTENT(IN)  ::  U
  TYPE(UNSEQ), INTENT(OUT)  ::  T
  T%R = U%R
  END SUBROUTINE C_U_TO_T

  SUBROUTINE CG1018(UDA1R)
  TYPE(UNSEQ) TLA1L(10)
  TYPE(SEQ) UDA1R(10)
  TLA1L(NFV1) = UDA1R
  END SUBROUTINE
  END MODULE c_TESTS


-- 
   Summary: defined assignment not allowed to vector subscripted
array
   Product: gcc
   Version: 4.3.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=34805



[Bug fortran/34784] New: implicit character(s) hides type of selected_int_kind intrinsic

2008-01-14 Thread dick dot hendrickson at gmail dot com
When I have an IMPLICIT CHARACTER(S) statement above a declaration,
the SELECTED_INT_KIND( ) function is diagnosed as a character function
with the message


u_dimension.f:3.50:

  INTEGER, DIMENSION(0:20) ::  IP_ARRAY1_3_S =
 1
Error: Can't convert CHARACTER(1) to INTEGER(4) at (1)

  MODULE U_TESTS
  implicit character(s)
  INTEGER, DIMENSION(0:20) ::  IP_ARRAY1_3_S =
 $ (/ (SELECTED_INT_KIND(J1),J1=0,20) /)
  END MODULE U_TESTS


Note, I've gotten the same error message in other contexts.  This might
be a broader problem that just the selected_int_kind function in a
unusual use.  If it isn't obvious to you that there is a more general
problem than this isolated example, I'll try to track down some more
examples.

Dick Hendrickson


-- 
   Summary: implicit character(s) hides type of selected_int_kind
intrinsic
   Product: gcc
   Version: 4.3.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=34784



[Bug fortran/34785] New: internal compiler error for array constructor for sequence type

2008-01-14 Thread dick dot hendrickson at gmail dot com
I get the message

og0015.f: In function 'og0015':
og0015.f:81: internal compiler error: in gfc_trans_array_constructor, at
fortran
/trans-array.c:1672

I think things work if I replace the use o_type_defs with the actual
contents of the module.  (Technically, this one was hard to isolate, so
I might misremember this).

Dick Hendrickson

  MODULE o_TYPE_DEFS

  TYPE SEQ

  SEQUENCE

REAL(4)  R, RA(9,10)
REAL(8)  ::  D, DA(1:10)
REAL(10)  Q
REAL(KIND=10), DIMENSION(10)  ::  QA

COMPLEX(4)   ::  Z, ZA(0:8,1-1:9)
COMPLEX(KIND=8), DIMENSION (20)  ::  YA(10)
COMPLEX(8)   ::  Y
COMPLEX(10)   ::  X, XA(-4:5)

CHARACTER(9,1)   ::  B, BA(-4:5)
INTEGER(4)   ::  I, IA(9,10)
INTEGER(KIND=4)  ::  H
CHARACTER(1,KIND=1)::  C, CA(9,10)
INTEGER(4), DIMENSION(10)::  HA(-4:5)

CHARACTER(LEN=9,KIND=1)  ::  E, EA(9,10)
LOGICAL(4)   ::  L, LA(9,10)
CHARACTER(KIND=1)F, FA(10)
LOGICAL(4)   ::  G, GA(10)

  END TYPE SEQ

! TEMPORARIES FOR USE WITH 'SEQ' AND 'UNSEQ' TYPES
REAL(4)  ::  RS_T, RA_T(9,10)
REAL(8)  ::  DS_T, DA_T(1:10)
REAL(KIND=10) ::  QS_T, QA_T(10)

COMPLEX(4)   ::  ZS_T, ZA_T(0:8,0:9)
COMPLEX(KIND=8)  ::  YS_T, YA_T(10)
COMPLEX(10)   ::  XS_T, XA_T(-4:5)

INTEGER(4)   ::  IS_T, IA_T(9,10)
INTEGER(4)   ::  HS_T, HA_T(-4:5)

LOGICAL(4)   ::  LS_T, LA_T(9,10)
LOGICAL(4)   ::  GS_T, GA_T(10)

CHARACTER(9,1)   ::  BS_T, BA_T(-4:5)
CHARACTER(1,KIND=1)::  CS_T, CA_T(9,10)
CHARACTER(LEN=9,KIND=1)  ::  ES_T, EA_T(9,10)
CHARACTER(KIND=1, LEN=5-4)   ::  FS_T, FA_T(10)

  END MODULE o_TYPE_DEFS


  MODULE TESTS
!  COPYRIGHT 1999   SPACKMAN  HENDRICKSON, INC.

  use o_type_defs

!  INTEGER, PRIVATE :: J1,J2,J3,J4,J5,J6,J7,JJJ
  CONTAINS
  SUBROUTINE OG0015(UDS0L)
!  COPYRIGHT 1999   SPACKMAN  HENDRICKSON, INC.
  TYPE(SEQ)  UDS0L

  UDS0L = SEQ(INT(RS_T),INT(RESHAPE((/((RA_T(J1,J2), J1 = 1,9),
 $ J2=1,10)/), (/9,10/))),
 $INT(DS_T),INT((/ (DA_T(J1),J1=1,10,1) /)),
 $INT(QS_T),INT((/ (QA_T(J1), J1=10,1,-1) /)),
 $ZS_T,RESHAPE( (/ ((ZA_T(J1,J2), J1 =0,8),
 $ J2=0,9)/),(/9,10/)),
 $(/ (YA_T(J1),J1=1,2*5,2-1)/),YS_T,
 $XS_T,(/ (XA_T(J1),J1=-4, 5) /),
 $BS_T,(/ (BA_T(J1),J1=-4, 5) /),
 $INT(IS_T),INT(RESHAPE( (/ ((IA_T(J1,J2), J1 =1*1,3*3)
 $,J2= 1, 10)/), (/3*3,2*5/))), INT(HS_T),
 $CS_T,RESHAPE ( (/ ((CA_T(J1,J2), J1 =1, 9,1),
 $   J2=1, 2*5)/),(/8+1, 10/)),
 $INT((/ (HA_T(J1), J1=-4,5) /)),
 $ES_T,EA_T(1:9,1:10),
 $LS_T,RESHAPE( (/ ((LA_T(J1,J2),J1 = 2-1,10-1),
 $   J2=2-1,9+1)/), (/9, 10/) ),
 $FS_T,(/ (FA_T(J1), J1=1,2*5) /),
 $GS_T,(/ (GA_T(J1), J1= 1*1,2*5) /))

  END SUBROUTINE
  END MODULE TESTS


-- 
   Summary: internal compiler error for array constructor for
sequence type
   Product: gcc
   Version: 4.3.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=34785



[Bug fortran/34759] New: Assumed size array reference not allowed in SHAPE intrinsic, even though last subscript specified

2008-01-12 Thread dick dot hendrickson at gmail dot com
With gfortran 4.3.0 20080109 I get an incorrect error message
Error: 'source' argument of 'shape' intrinsic at (1) must not
be an assumed size array with the following little test case

   subroutine j_assumed_size(A,N)
   dimension A(10,11,12,*)
   k = shape(A(:,:,:,N))
   l = shape(A(:,:,:,3))
   end

I believe assumed size arrays are allowed provided the last subscript
is specified.

Dick Hendrickson


-- 
   Summary: Assumed size array reference not allowed in SHAPE
intrinsic, even though last subscript specified
   Product: gcc
   Version: 4.3.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=34759



[Bug fortran/34760] New: PRIVATE variable not allowed as STAT variable in ALLOCATE

2008-01-12 Thread dick dot hendrickson at gmail dot com
With gfortran 4.3.0 20080109 I get the error message

 ALLOCATE (RLA1(NF10), STAT = ISTAT)
  1
Error: STAT expression at (1) must be a variable

With the following program.

 MODULE TESTS
 INTEGER, PRIVATE :: ISTAT   !this one FAILS
!  INTEGER :: ISTAT   !this one works
!  PRIVATE :: ISTAT   !this one FAILS
 CONTAINS
 SUBROUTINE AD0001
 REAL RLA1(:)
 ALLOCATABLE RLA1
 ISTAT = -314
 ALLOCATE (RLA1(NF10), STAT = ISTAT)
 END SUBROUTINE
 END MODULE

In the real module there are several subroutines that do similar
allocates and they do not generate the error.  It looks like it is
only the first use of ISTAT in an allocate that triggers the message.

Dick Hendrickson


-- 
   Summary: PRIVATE variable not allowed as STAT variable in
ALLOCATE
   Product: gcc
   Version: 4.3.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=34760



[Bug fortran/34763] New: bare END not allowed in an interface block in a module procedure

2008-01-12 Thread dick dot hendrickson at gmail dot com
With gfortran 4.3.0 20080109 I get the error message

n_interface.f:7.12:

END
   1
Error: END SUBROUTINE statement expected at (1)

with the following program
  module n
  contains
  subroutine n_interface
  INTERFACE
SUBROUTINE NGSXDY(TLS1,TLS2)
REAL  ::  TLS1,TLS2
END 
  END INTERFACE
  end
  end module

If the n_interface is an external procedure it works fine.  A bare
END statement is allowed in interface blocks.  I'd guess you
are misapplying the constraint after R1224 to things inside of
interface blocks.  But NGSXDY isn't a module subroutine.  You'll
probably need a similar fix for functions in interface blocks,
although I haven't tried that.

Dick Hendrickson


-- 
   Summary: bare END not allowed in an interface block in a module
procedure
   Product: gcc
   Version: 4.3.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=34763