[Bug fortran/28873] New: Cannot resolve subroutine calls when modules are used in different scopes

2006-08-28 Thread drewmccormack at mac dot com
gfortran reports the following error:


call create()
1
Error: Generic subroutine 'create' at (1) is not an intrinsic subroutine


when trying to compile the following code:


module A
  private 
  interface create
module procedure create1 
  end interface
  public :: create
contains
  subroutine create1 
  end subroutine
end module

module B
  private 
  interface create
module procedure create1 
  end interface
  public :: create
contains
  subroutine create1(a)
integer a
  end subroutine
end module

module C
  use A
  private 
contains
  subroutine useCreate
use B   
call create()
  end subroutine
end module


The call to the overloaded routine 'create' should be resolved to create1 in
module A, but an error results. This error only occurs when module B is used in
the subroutine, and module A is used at the top level of module C. If you move
the 'use B' statement to the top level of module C, it resolves fine.


-- 
   Summary: Cannot resolve subroutine calls when modules are used in
different scopes
   Product: gcc
   Version: 4.2.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: drewmccormack at mac dot com
 GCC build triplet: gcc version 4.2.0 20060805 (experimental)
GCC target triplet: powerpc-apple-darwin8.7.0


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



[Bug fortran/28874] New: gfortran confuses 'cycle' keyword for subroutine call in subroutine called 'cycle'

2006-08-28 Thread drewmccormack at mac dot com
The following code:


subroutine cycle
  implicit none
  integer :: nsos, isym, nsym = 10
  integer :: norb(10)
  isym_: do isym = 1, nsym 
 nsos = norb(isym)
 if (nsos==0) cycle isym_
  enddo isym_
end subroutine


causes this compile time error:

 if (nsos==0) cycle isym_
  1
Error: Expected VARIABLE at (1)


The confusion seems to arise because the subroutine is called 'cycle'. Other
compilers do handle this correctly.


-- 
   Summary: gfortran confuses 'cycle' keyword for subroutine call in
subroutine called 'cycle'
   Product: gcc
   Version: 4.2.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: drewmccormack at mac dot com
 GCC build triplet: gcc version 4.2.0 20060805 (experimental)
GCC target triplet: powerpc-apple-darwin8.7.0


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



[Bug fortran/28885] New: ICE passing components of array of derived type

2006-08-29 Thread drewmccormack at mac dot com
This ICE arises:


bug2.f90: In function ‘MAIN__’:
bug2.f90:30: internal compiler error: in gimplify_var_or_parm_decl, at
gimplify.c:1665


when compiling the following code:


module modA
  implicit none
  private 
  public :: sub
  interface sub
module procedure subA
module procedure subB
  end interface
contains
  subroutine subA(key,a)
integer, intent(out):: a(:) 
character(*),intent(in) :: key
a = 1   
  end subroutine
  subroutine subB(key,a)
real, intent(out) :: a(:) 
character(*),intent(in) :: key
a = 1.0 
  end subroutine
end module

program test
  use modA
  type t  
integer :: i
real :: energy
  end type
  type (t) :: a(5) 
  call sub('blah',a%energy)
  call sub('blah',a%i)
end program 


The ICE only occurs if you call the overloaded subroutine multiple times in the
same scope, for different components of the derived type. If you make one call
for one component, compilation succeeds.


-- 
   Summary: ICE passing components of array of derived type
   Product: gcc
   Version: 4.2.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
AssignedTo: unassigned at gcc dot gnu dot org
ReportedBy: drewmccormack at mac dot com
 GCC build triplet: gcc version 4.2.0 20060805 (experimental)
GCC target triplet: powerpc-apple-darwin8.7.0


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



[Bug fortran/28873] Cannot resolve subroutine calls when modules are used in different scopes

2006-08-30 Thread drewmccormack at mac dot com


--- Comment #8 from drewmccormack at mac dot com  2006-08-30 07:01 ---
Thanks Paul!
I am just using binaries, so I can't test this, but I trust you ;-)

Drew


-- 


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



[Bug fortran/31390] New: ICE due to transfer function

2007-03-29 Thread drewmccormack at mac dot com
I receive the following ICE:
transferbug.f90: In function ‘bucketindexofkey’:
transferbug.f90:14: internal compiler error: in gfc_get_element_type, at
fortran/trans-types.c:741

when compiling this test code:

module InternalCompilerError

   type Byte
  private
  character(len=1)  :: singleByte
   end type

contains

   function BucketIndexOfKey(key) result (hash)
  type(Byte), intent(in):: key(:)
  integer   :: hash
  integer, parameter:: intPrototype(1) = 0
  integer   :: intKey(
size(transfer(key, intPrototype)) )
  intKey = transfer(key, intPrototype)   ! This line causes the ICE
  hash = 0
   end function

end module

program main
   use InternalCompilerError
end program


The ICE seems to disappear when removing the following line, which makes me
think that it is the direct cause:

  intKey = transfer(key, intPrototype)   ! This line causes the ICE


Regards,
Drew McCormack


-- 
   Summary: ICE due to transfer function
   Product: gcc
   Version: 4.3.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
AssignedTo: unassigned at gcc dot gnu dot org
ReportedBy: drewmccormack at mac dot com
 GCC build triplet: 4.3.0 20070316 (experimental)
GCC target triplet: powerpc-apple-darwin8.9.0


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



[Bug fortran/31424] New: ICE involving transfer function, and passing function return to subroutine

2007-04-02 Thread drewmccormack at mac dot com
I get the following ICE:

test.f90: In function ‘MAIN__’:
test.f90:29: internal compiler error: in gfc_get_symbol_decl, at
fortran/trans-decl.c:877
Please submit a full bug report,


when compiling this code:


module InternalCompilerError

   type Byte
  private 
  character(len=1) :: singleByte
   end type

   type (Byte) :: BytesPrototype(1)

   type UserType
  real :: r
   end type

contains

   function UserTypeToBytes(user) result (bytes) 
  type(UserType) :: user 
  type(Byte) :: bytes(size(transfer(user, BytesPrototype)))
  bytes = transfer(user, BytesPrototype) 
   end function

   subroutine DoSomethingWithBytes(bytes)
  type(Byte), intent(in) :: bytes(:)
   end subroutine

end module


program main
   use InternalCompilerError
   type (UserType) :: user 

   ! The following line causes the ICE 
   call DoSomethingWithBytes( UserTypeToBytes(user) )

end program 


As indicated in the comments, the ICE is caused by the line passing a function
result to a subroutine.

Kind regards,
Drew


-- 
   Summary: ICE involving transfer function, and passing function
return to subroutine
   Product: gcc
   Version: 4.3.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
AssignedTo: unassigned at gcc dot gnu dot org
ReportedBy: drewmccormack at mac dot com
 GCC build triplet: gcc version 4.3.0 20070325 (experimental)
GCC target triplet: powerpc-apple-darwin8


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



[Bug fortran/33037] New: TRANSFER intrinsic is context sensitive

2007-08-09 Thread drewmccormack at mac dot com
When using the transfer intrinsic to convert a character string to an array of
integers, and the string does not fit exactly into the integer array data
block, the resultant integer array is scope dependent, with the same code
giving a different resultant integer array in different subroutines/program
units. Basically, the transfer function is not deterministic in the case where
the source data is smaller than the destination data.

There is a small program below to demonstrate the issue. The integer array is
printed twice, and (on my machine) is different each time. The code producing
the two sets of output is exactly the same, but in the first case the code is
embedded in the main program, and in the other case in a subroutine.

I do not have a copy of the standard, but I cannot imagine that this behavior
is correct. The problem arises even if the destination array is initialized to
zero (as shown in the example).


module DataMod
   type Byte
  character(len=1) :: singleByte
   end type
end module

subroutine sub()
   use DataMod
   integer :: i(1), intarray(4), j
   character(len=15) :: str1
   type (Byte) :: bytes(15)
   type (Byte) :: byteProt(1)

   bytes = transfer('123456789012345', byteProt)
   print *, bytes(:)%singleByte
   intarray = 0
   intarray = transfer(bytes, i)
   print *, intarray

end subroutine

program test
   use DataMod
   integer :: i(1), intarray(4), j
   character(len=15) :: str1
   type (Byte) :: bytes(15)
   type (Byte) :: byteProt(1)

   bytes = transfer('123456789012345', byteProt)
   print *, bytes(:)%singleByte
   intarray = 0
   intarray = transfer(bytes, i)
   print *, intarray

   call sub()

end program


-- 
   Summary: TRANSFER intrinsic is context sensitive
   Product: gcc
   Version: 4.3.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
AssignedTo: unassigned at gcc dot gnu dot org
ReportedBy: drewmccormack at mac dot com
 GCC build triplet: gcc version 4.3.0 20070511 (experimental)
  GCC host triplet: powerpc-apple-darwin8.9.0
GCC target triplet: powerpc-apple-darwin8.9.0


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



[Bug fortran/34080] New: Transfer was working, now broken

2007-11-13 Thread drewmccormack at mac dot com
I have code that was previously working with gfortran and now is broken. The
problem has to do with the 'transfer' intrinsic. If I transfer a character
string into an array of a different type, and then transfer the array back to a
string, the result is not the original string, but apparently random bytes.

I have prepared sample code to demonstrate:


module TransferBug

   type ByteType
  private
  character(len=1)  :: singleByte
   end type

   type (ByteType), save:: BytesPrototype(1)

contains

   function StringToBytes(v) result (bytes)
  character(len=*), intent(in)  :: v
  type (ByteType)   ::
bytes(size(transfer(v, BytesPrototype)))
  bytes = transfer(v, BytesPrototype)
   end function

   subroutine BytesToString(bytes, string)
  type (ByteType), intent(in)   :: bytes(:)
  character(len=*), intent(out) :: string
  character(len=1)  :: singleChar(1)
  integer   :: numChars
  numChars = size(transfer(bytes,singleChar))
  string = ''
  string = transfer(bytes, string)
  string(numChars+1:) = ''
   end subroutine

end module


program main
   use TransferBug
   character(len=100) :: str
   call BytesToString( StringToBytes('Hi'), str )
   print *, trim(str)   ! This should print 'Hi'
end program


-- 
   Summary: Transfer was working, now broken
   Product: gcc
   Version: 4.3.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
AssignedTo: unassigned at gcc dot gnu dot org
ReportedBy: drewmccormack at mac dot com
 GCC build triplet: 4.3.0 20071026 (experimental)
GCC target triplet: powerpc-apple-darwin9.0.0


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



[Bug fortran/34080] [4.3 regression] Transfer was working, now broken

2007-11-13 Thread drewmccormack at mac dot com


--- Comment #6 from drewmccormack at mac dot com  2007-11-13 20:27 ---
Subject: Re:  [4.3 regression] Transfer was working, now broken

Thanks for fixing it so quick, Paul.

Drew


On 13/11/2007, at 9:19 PM, pault at gcc dot gnu dot org wrote:

>
>
> --- Comment #5 from pault at gcc dot gnu dot org  2007-11-13  
> 20:19 ---
> Drew,
>
> By the way - thanks!
>
> The regression test is just coming to an end, so it'll be fixed very  
> soon.
>
> Paul
>
>
> -- 
>
>
> http://gcc.gnu.org/bugzilla/show_bug.cgi?id=34080
>
> --- You are receiving this mail because: ---
> You reported the bug, or are watching the reporter.


-- 


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



[Bug fortran/35997] New: Used function interface bug

2008-04-21 Thread drewmccormack at mac dot com
Code that has a function interface used from two modules can fail if one of the
modules renames the function interface. The example below fails to compile with
this message:

gfortran testfuncinterface.f90 
testfuncinterface.f90:21.7:

  if ( valid() ) then
  1
Error: IF clause at (1) requires a scalar LOGICAL expression


Source Code:

module funcinterfacemod

  interface
logical function valid()
end function
  end interface

end module

module secondmod
  use funcinterfacemod, valid2 => valid
end module

logical function valid()
  valid = .true.
end function

program main
  use secondmod
  use funcinterfacemod
  if ( valid() ) then
print *,'Is Valid'
  endif
end program


This example does compile is the order of the use statements is reversed. This
also compiles on earlier versions of gfortran (eg 4.3.0 20071114 (experimental)
(GCC))


-- 
   Summary: Used function interface bug
   Product: gcc
   Version: 4.3.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
AssignedTo: unassigned at gcc dot gnu dot org
    ReportedBy: drewmccormack at mac dot com
 GCC build triplet: 4.3.0 20080125 (experimental) (GCC)
  GCC host triplet: i386-apple-darwin8.11.1
GCC target triplet: i386-apple-darwin8.11.1


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



[Bug fortran/28885] ICE passing components of array of derived type

2006-10-31 Thread drewmccormack at mac dot com


--- Comment #8 from drewmccormack at mac dot com  2006-10-31 08:51 ---
Unfortunately, though the fix did work for the example code, it doesn't seem to
be general enough. In particular, if you change the example code to include
just one extra subroutine call, the same compiler error arises. So, a fix is
need that can handle any number of subroutine calls, not just one or two.

Here is new code demonstrating the error. It is simply the original code with
one extra subroutine call:

program test
  type t  
integer :: i
integer :: j
  end type
  type (t) :: a(5) 
  call sub('one',a%j)
  call sub('two',a%i)
  call sub('two',a%i)
contains
  subroutine sub(key,a)
integer, intent(out):: a(:) 
character(*),intent(in) :: key
a = 1   
  end subroutine
end program 


-- 

drewmccormack at mac dot com changed:

   What|Removed |Added

     CC|                    |drewmccormack at mac dot com
 Status|RESOLVED|REOPENED
  GCC build triplet|gcc version 4.2.0 20060805  |gcc version 4.2.0 20061007
   |(experimental)  |(experimental)
 GCC target triplet|powerpc-apple-darwin8.7.0   |powerpc-apple-darwin8.8.0
 Resolution|FIXED   |


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



[Bug fortran/30435] New: Slash at end of input not recognized according to standard

2007-01-11 Thread drewmccormack at mac dot com
The Fortran standard states that when you have list directed input, and a
forward slash (/) appears at the end of a line of input, that any variables in
the read statement that have not been initialized should simply be skipped over
(ignored). 

When gfortran encounters a slash at the beginning of a line, it does not
exhibit the correct behavior. For example, this data:

6.34 1.34 4345.34534
/

with this read statement

read(50, *)r1,r2,r3,r4

should set r1 to 6.34, r2 to 1.34, r3 to 4345.34534, and leave r4 unchanged.
But gfortran code issues the following run time error:

Fortran runtime error: Bad real number in item 4 of list input

All other fortran compilers that I use (xlf, ifort, etc) handle this case
correctly.


-- 
   Summary: Slash at end of input not recognized according to
standard
   Product: gcc
   Version: 4.3.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
AssignedTo: unassigned at gcc dot gnu dot org
ReportedBy: drewmccormack at mac dot com
 GCC build triplet: Configured with: ../gcc-4.3-20061223/configure --enable-
language
  GCC host triplet: gcc version 4.3.0 20061223 (experimental)
GCC target triplet: Target: powerpc-apple-darwin8.8.0


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