[Bug fortran/70601] New: [OOP] ICE on procedure pointer component call

2016-04-08 Thread zmi007 at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=70601

Bug ID: 70601
   Summary: [OOP] ICE on procedure pointer component call
   Product: gcc
   Version: 6.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: zmi007 at gmail dot com
  Target Milestone: ---

I am playing around with procedure pointer components and get ICE 

module_gfortran_bug.f90:62:0:

call concrete % run()

internal compiler error: in fold_convert_loc, at fold-const.c:2256

on the following code with gfortran-6 [trunk revision 234449]. Note that I am
not sure if the code is valid, but ifort 16 is able to compile it.


! code
module abstract_type_module
   implicit none
   private
   public :: abstract_type


   type, abstract :: abstract_type
  procedure (abstract_type_procedure1), pointer :: run => NULL()
   end type abstract_type

   abstract interface
  subroutine abstract_type_procedure1(this)
 import  :: abstract_type
 class(abstract_type), intent(inout) :: this
  end subroutine abstract_type_procedure1
   end interface

end module abstract_type_module


module concrete_type_module
   use abstract_type_module
   implicit none
   private
   public :: concrete_type

   type, extends(abstract_type) :: concrete_type
   contains
  procedure , pass :: init => init_concrete_type
   end type concrete_type

contains

   subroutine  run_concrete_type(this)
  implicit none
  class(abstract_type), intent(inout) :: this

select type (this)
type is (concrete_type)
write(*,*) "run_concrete_type"
class default
write(*,*) "?"
end select
   end subroutine run_concrete_type

   subroutine  init_concrete_type(this)
  implicit none
  class(concrete_type), intent(inout) :: this
  this % run => run_concrete_type
  write(*,*) "init_concrete_type"

   end subroutine init_concrete_type

end module concrete_type_module


programtest
   use concrete_type_module
   implicit none
type(concrete_type) :: concrete

   call concrete % init()
   call concrete % run()

end program test

[Bug fortran/70601] [OOP] ICE on procedure pointer component call

2016-04-08 Thread zmi007 at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=70601

--- Comment #2 from zmi  ---
and this one?

programtest
   use concrete_type_module
   implicit none
type(concrete_type), allocatable :: concrete
allocate(concrete)

   call concrete % init()
   call concrete % run()

end program test

[Bug fortran/70601] [OOP] ICE on procedure pointer component call

2016-04-08 Thread zmi007 at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=70601

--- Comment #4 from zmi  ---
ok, my fault)
ice on allocatable type only

[Bug fortran/70739] New: VALUE attribute interpretation in a non-interoperable procedure

2016-04-20 Thread zmi007 at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=70739

Bug ID: 70739
   Summary: VALUE attribute interpretation in a non-interoperable
procedure
   Product: gcc
   Version: 6.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: zmi007 at gmail dot com
  Target Milestone: ---

I see difference between ifort and gfortran interpretation of a
non-interoperable procedure (without BIND(C)) with VALUE attribute in dummy
argument. 

Actually gfortran gives (intuitively) expected result compared to ifort, but
this is something that is difficult to find out in standard to confirm. 
See details here 
https://software.intel.com/en-us/forums/intel-fortran-compiler-for-linux-and-mac-os-x/topic/610807

(example)

/* test.c */
#include 
#include 
#include 

int32_t test (char* key, size_t len)
{
  int32_t hash = 666;
  printf("c key %s\n", key);
  printf("c len %zu\n", len); // expected 2
  return hash;
}


! test_main.f90

!---
!Module interface_module
!---
module interface_module
   implicit none

   interface
  function test(key, length) result(hash) bind(c, name="test")
 use iso_c_binding
 character(kind=c_char),dimension(*) :: key
 integer(c_size_t), value :: length
 integer(c_int32_t) :: hash
  end function test
   end interface

   abstract interface
  function function_hash_template(key, length) ! <= missing  bind(c)
here !!!
 use iso_c_binding
 character(kind=c_char),dimension(*) :: key
 integer(c_size_t), value :: length
 integer(c_int32_t) :: function_hash_template
  end function function_hash_template
   end interface

contains

   !---
   !Function hash_wrap
   !---
   function  hash_wrap(text, fun) result(hash)
  use iso_c_binding
  implicit none
  character (len=*), target, intent(in) :: text
  procedure(function_hash_template), pointer :: fun
  integer(c_int32_t) :: hash
  character(kind=c_char), dimension(len_trim(text)+1) :: text_c
  integer(c_size_t) :: length

  text_c = f_to_c_string(text) ! convert to c string for compatibility

  length = len_trim(text) + 1
  write(*,*) "hash_wrap, length = ", length
  hash = fun(text_c,length)
   end function hash_wrap

   !---
   !Function f_to_c_string
   !---
   pure function f_to_c_string (f_string) result (c_string)
  use, intrinsic :: iso_c_binding, only: c_char, c_null_char
  implicit none
  character(len=*), intent(in) :: f_string
  character(len=1,kind=c_char), dimension(len_trim(f_string)+1) :: c_string
  integer :: n, i
  n = len_trim(f_string)
  do i = 1, n
 c_string(i) = f_string(i:i)
  end do
  c_string(n + 1) = c_null_char
   end function f_to_c_string

end module interface_module

!---
!Main program test_main
!---
programtest_main
   use interface_module
   implicit none

   write(*,*) test_wrap("1")

   contains

   !---
   !Function test_wrap
   !---
   function test_wrap(text) result(hash)
  use iso_fortran_env
  implicit none
  character(len=*),intent(in) :: text
  integer(int32) :: hash
  procedure(function_hash_template), pointer :: fun
  fun => test
  hash = int(hash_wrap(text, fun), int32)
   end function test_wrap

end program test_main



Results:

gfortran:
gcc version 5.3.1 20160301 [gcc-5-branch revision 233849] (SUSE Linux)
gcc version 6.0.0 20160324 (experimental) [trunk revision 234449] (SUSE Linux) 
 hash_wrap, length = 2
c key 1
c len 2
 666

ifort:
ifort version 16.0.2
 hash_wrap, length =  2
c key 1
c len 140730916351912
 666

Note the difference in len argument 

Steve Lionel's  comment to discuss here:
- [...]For a non-interoperable procedure, one without BIND(C), VALUE causes a
writable, temporary copy of the argument to be passed by reference. So in zmi's
case, the call through the procedure pointer, defined with an interface that
did not have BIND(C), caused the address of a copy of "length" to be passed.

[Bug fortran/70739] VALUE attribute interpretation in a non-interoperable procedure

2016-05-12 Thread zmi007 at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=70739

--- Comment #2 from zmi  ---
This was also my wish but I couldn't find it too and assume now as an Intel's
interpretation of standard. Would be interesting to see if such interpretation
confirmed by another vendors (I don't have access to actual compilers from
Cray, IBM etc.)

[Bug fortran/44672] [F08] ALLOCATE with SOURCE and no array-spec

2015-09-29 Thread zmi007 at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=44672

zmi  changed:

   What|Removed |Added

 CC||zmi007 at gmail dot com

--- Comment #13 from zmi  ---
(In reply to vehre from comment #12)
Does it fix also the same situation with mold= specifier? f.e. in this simple
program?


program test_mold
   integer, allocatable, dimension(:) :: a,b
   type ac
  integer :: a
   end type ac
   type(ac), allocatable, dimension(:) :: aa,bb

   allocate(a(10))
   allocate(aa(10))
   allocate (b, mold=a) !<---
   allocate (bb, mold=aa) !<---

end program test_mold


gfortran --version
GNU Fortran (SUSE Linux) 5.2.1 20150721 [gcc-5-branch revision 226027]
Copyright (C) 2015 Free Software Foundation, Inc.
gfortran test_mold.f90 -o test_mold.xtest_mold.f90:11:13:

allocate (b, mold=a)
 1
Error: Array specification required in ALLOCATE statement at (1)
test_mold.f90:13:13:

allocate (bb, mold=aa)
 1
Error: Array specification required in ALLOCATE statement at (1)


Interpretation of F2008 6.7.1.2 is a bit tedious but mold= should work similar
to source= specifier ?


[Bug fortran/50069] FORALL fails on a character array

2015-10-11 Thread zmi007 at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=50069

zmi  changed:

   What|Removed |Added

 CC||zmi007 at gmail dot com

--- Comment #6 from zmi  ---
A am not sure if its the same bug, but I get ICE for the function

!---
!Function
!---
function  reverse(string) ! bind(c, name='reverse')
implicit none
character(len=*), intent(in) :: string
character(len=:),allocatable :: reverse
reverse = string
forall (i=1:len(reverse)) reverse(i:i) =
reverse(len(reverse)-i+1:len(reverse)-i+1)
end function reverse



forall (i=1:len(reverse)) reverse(i:i) =
reverse(len(reverse)-i+1:len(reverse)-i+1)
 1
internal compiler error: in gfc_conv_variable, at fortran/trans-expr.c:2368


gfortran --version
GNU Fortran (SUSE Linux) 5.2.1 20150721 [gcc-5-branch revision 226027]


[Bug fortran/63469] Automatic reallocation of allocatable scalar length even when substring implicitly specified

2015-12-10 Thread zmi007 at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63469

zmi  changed:

   What|Removed |Added

 CC||zmi007 at gmail dot com

--- Comment #4 from zmi  ---
I found this simple snippet in comp.lang.fortran newsgroup thread "Problem with
automatic reallocation of allocatable scalar on assignment" and it fails now
after some modification with the last version of gfortran I have

GNU Fortran (SUSE Linux) 5.3.1 20151207 [gcc-5-branch revision 231355]

program test
implicit none
 character(len=:), allocatable :: temp
 integer :: i
 do i = 1,1
 temp='abcdef'
 temp=temp(3:)
 write(*,'("|",A,"|")') temp
 deallocate(temp)
 enddo
end program test

./test.x
|cd  |

Note that if we remove dummy "do i= ... end do" we obtain expected substring
./test.x
|cdef|

[Bug fortran/72709] New: Incorrect assignment of allocatable character array used as component of derived type

2016-07-27 Thread zmi007 at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=72709

Bug ID: 72709
   Summary: Incorrect assignment of allocatable character array
used as component of derived type
   Product: gcc
   Version: unknown
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: zmi007 at gmail dot com
  Target Milestone: ---

In the following program the assignment to character array element doesn't work

programread_exp_data
   implicit none

   type experimental_data_t
  integer :: nh = 0
  character(len=:), dimension(:), allocatable :: header

   end type experimental_data_t

   type(experimental_data_t) :: ex
   integer :: nh_len
   integer :: i


   nh_len = 255
   ex % nh = 3
   allocate(character(len=nh_len) :: ex % header(ex % nh))

   ex % header(1) = "#Generated by X"
   ex % header(2) = "#from file 'Y'"
   ex % header(3) = "# Experimental 4 mg/g"

   do i = 1, ex % nh
  write(*,*) "header(",i,") = ", ex % header(i) 
   enddo

end program read_exp_data

I get all 3 header elements = "# Experimental 4 mg/g"

gfortran --version
GNU Fortran (SUSE Linux) 6.1.1 20160707 [gcc-6-branch revision 238088]

---
bug disappears if one replaces appropriate strings with

character(len=255), dimension(:), allocatable :: header

and

allocate(ex % header(ex % nh))