[Bug fortran/87151] New: allocating array of character

2018-08-30 Thread valeryweber at hotmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87151

Bug ID: 87151
   Summary: allocating array of character
   Product: gcc
   Version: 8.2.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: valeryweber at hotmail dot com
  Target Milestone: ---

dear all

gcc 8.2 seems to have a problem allocating the string below. the len() should
be 2, is that a bug?

many thanks

valery


cat alloc_char.f90
module bvec
type, public :: bvec_t
 private
 character(:), dimension(:), allocatable :: vc 
   contains
 PROCEDURE, PASS :: create
  end type bvec_t
contains
  subroutine create(this)
class(bvec_t), intent(inout) :: this
allocate(character(2)::this%vc(3))
write(*,*) len(this%vc),size(this%vc)
  end subroutine create
end module bvec

program test
  use bvec
  type(bvec_t) :: a
  call a%create()
end program test



gfortran-8.2.0 alloc_char.f90
./a.out 
   0   3

[Bug fortran/87045] New: pointer to array of character

2018-08-21 Thread valeryweber at hotmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87045

Bug ID: 87045
   Summary: pointer to array of character
   Product: gcc
   Version: 8.2.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: valeryweber at hotmail dot com
  Target Milestone: ---

hi all

i m getting a weird error with the following code.


many thanks

v

cat t2.f90
program test
  character(:), dimension(:), allocatable, target :: t
  character(:), pointer, dimension(:) :: p
  allocate( character(3) :: t(2) )
  t(1) = "abc"
  t(2) = "123"
  write(*,*) t
  p => t
  write(*,*) p(1)
  write(*,*) p(2)
end program test



gfortran-8.1.0 t2.f90 -g -fcheck=all
./a.out 
 abc123
At line 8 of file t2.f90
Fortran runtime error: Unequal character lengths (-3262553545697656832/3) in
pointer assignment

Error termination. Backtrace:
#0  0x402548 in test
at /home/vwe/work/axv/pkg/build/t2.f90:8
#1  0x402724 in main
at /home/vwe/work/axv/pkg/build/t2.f90:11

[Bug fortran/83088] New: ICE with -init-derived

2017-11-21 Thread valeryweber at hotmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=83088

Bug ID: 83088
   Summary: ICE with -init-derived
   Product: gcc
   Version: 8.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: valeryweber at hotmail dot com
  Target Milestone: ---

hi all
the following code is ICEing
v

gfortran-intel-trunk -free -c -finit-derived  hfx_libint_wrapper.F90   
 hfx_libint_wrapper.F90:101:0:

 END MODULE hfx_libint_wrapper

internal compiler error: Segmentation fault
0xc2f705 crash_signal
../../gcc-trunk-src/gcc/toplev.c:325
0x6ba206 contains_struct_check
../../gcc-trunk-src/gcc/tree.h:3203
0x6ba206 gfc_conv_structure(gfc_se*, gfc_expr*, int)
../../gcc-trunk-src/gcc/fortran/trans-expr.c:7751
0x674480 gfc_conv_array_initializer(tree_node*, gfc_expr*)
../../gcc-trunk-src/gcc/fortran/trans-array.c:5894
0x6b9dfa gfc_conv_initializer(gfc_expr*, gfc_typespec*, tree_node*, bool, bool,
bool)
../../gcc-trunk-src/gcc/fortran/trans-expr.c:6848
0x69c48f gfc_get_symbol_decl(gfc_symbol*)
../../gcc-trunk-src/gcc/fortran/trans-decl.c:1825
0x69e063 gfc_create_module_variable
../../gcc-trunk-src/gcc/fortran/trans-decl.c:4943
0x653930 do_traverse_symtree
../../gcc-trunk-src/gcc/fortran/symbol.c:4157
0x69d4d2 gfc_generate_module_vars(gfc_namespace*)
../../gcc-trunk-src/gcc/fortran/trans-decl.c:5415
0x66b2c8 gfc_generate_module_code(gfc_namespace*)
../../gcc-trunk-src/gcc/fortran/trans.c:2180
0x6212c2 translate_all_program_units
../../gcc-trunk-src/gcc/fortran/parse.c:6078
0x6212c2 gfc_parse_file()
../../gcc-trunk-src/gcc/fortran/parse.c:6294
0x66775f gfc_be_parse_file
../../gcc-trunk-src/gcc/fortran/f95-lang.c:204
Please submit a full bug report,
with preprocessed source if appropriate.
Please include the complete backtrace with any bug report.
See <https://gcc.gnu.org/bugs/> for instructions.





cat hfx_libint_wrapper.F90
MODULE hfx_libint_wrapper
   USE ISO_C_BINDING,   ONLY: C_DOUBLE,&
  C_F_POINTER,&
  C_F_PROCPOINTER,&
  C_INT,&
  C_LOC,&
  C_PTR,&
  c_funptr

   IMPLICIT NONE
   PRIVATE

   INTEGER, PARAMETER :: dp = SELECTED_REAL_KIND(14, 200)

   integer,parameter :: build_deriv1_eri_size=10,build_eri_size=2,
libderiv_max_am1=4, &
libint_max_am=4, libint_dvrr_classes_size=1, libint_vrr_classes_size=1,
prim_data_f_size=1
   integer, dimension(1):: nco

   TYPE, BIND(C) :: prim_data
  REAL(C_DOUBLE) :: F(prim_data_f_size)
  REAL(C_DOUBLE) :: U(3, 6)
  REAL(C_DOUBLE) :: twozeta_a
  REAL(C_DOUBLE) :: twozeta_b
  REAL(C_DOUBLE) :: twozeta_c
  REAL(C_DOUBLE) :: twozeta_d
  REAL(C_DOUBLE) :: oo2z
  REAL(C_DOUBLE) :: oo2n
  REAL(C_DOUBLE) :: oo2zn
  REAL(C_DOUBLE) :: poz
  REAL(C_DOUBLE) :: pon
  REAL(C_DOUBLE) :: oo2p
  REAL(C_DOUBLE) :: ss_r12_ss
   END TYPE prim_data


   TYPE, BIND(C) :: lib_int
  TYPE(C_PTR) :: int_stack
  TYPE(C_PTR) :: PrimQuartet
  REAL(C_DOUBLE)  :: AB(3)
  REAL(C_DOUBLE)  :: CD(3)
  TYPE(C_PTR) :: vrr_classes(libint_vrr_classes_size,
libint_vrr_classes_size)
  TYPE(C_PTR) :: vrr_stack
   END TYPE lib_int

   TYPE, BIND(C) :: lib_deriv
  TYPE(C_PTR) :: int_stack
  TYPE(C_PTR) :: PrimQuartet
  TYPE(C_PTR) :: zero_stack
  TYPE(C_PTR) :: ABCD(156)
  REAL(C_DOUBLE)  :: AB(3)
  REAL(C_DOUBLE)  :: CD(3)
  TYPE(C_PTR) :: deriv_classes(12, libint_dvrr_classes_size,
libint_dvrr_classes_size)
  TYPE(C_PTR) :: deriv2_classes(144, libint_dvrr_classes_size,
libint_dvrr_classes_size)
  TYPE(C_PTR) :: dvrr_classes(libint_dvrr_classes_size,
libint_dvrr_classes_size)
  TYPE(C_PTR) :: dvtt_stack
   END TYPE lib_deriv

   CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'hfx_libint_wrapper'


   TYPE(C_FUNPTR), DIMENSION(0:build_eri_size, 0:build_eri_size,
0:build_eri_size, 0:build_eri_size), BIND(C) :: build_eri
   TYPE(C_FUNPTR), DIMENSION(0:build_deriv1_eri_size, 0:build_deriv1_eri_size,
&
 0:build_deriv1_eri_size, 0:build_deriv1_eri_size),
BIND(C) :: build_deriv1_eri

   INTERFACE
  SUBROUTINE build_deriv1(deriv, np) BIND(C)
 IMPORT
 TYPE(lib_deriv):: deriv
 INTEGER(KIND=C_INT), VALUE  :: np
  END SUBROUTINE build_deriv1
   END INTERFACE

CONTAINS
   SUBROUTINE get_derivs(n_d, n_c, n_b, n_a, deriv, prim, work_forces,
a_mysize)
  INTEGER, INTENT(IN)  

[Bug fortran/82009] New: ICE with block construct

2017-08-28 Thread valeryweber at hotmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=82009

Bug ID: 82009
   Summary: ICE with block construct
   Product: gcc
   Version: 7.2.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: valeryweber at hotmail dot com
  Target Milestone: ---

hi all

the following code is ICEing with gcc 7.2.0

thanks

v

cat sparse_matrix_csx_benchmark_utils.F90
MODULE sparse_matrix_csx_benchmark_utils
  IMPLICIT NONE
CONTAINS  
  SUBROUTINE sparse_matrix_csr_benchmark ( )
WRITE(*,*) 'At*x: t'
block
  integer, dimension(1), parameter :: idxs=[1]
  integer :: i, idx
  do i = 1, size(idxs)
 idx = idxs(i)
  enddo
end block
  END SUBROUTINE sparse_matrix_csr_benchmark
  SUBROUTINE sparse_matrix_csc_benchmark ( )
WRITE(*,*) 'An*x: t'
block
  integer, dimension(1), parameter :: idxs=[1]
  integer :: i, idx
  do i = 1, size(idxs)
 idx = idxs(i)
  enddo
end block
  END SUBROUTINE sparse_matrix_csc_benchmark
END MODULE sparse_matrix_csx_benchmark_utils


gfortran-7.2.0 -c  sparse_matrix_csx_benchmark_utils.F90
sparse_matrix_csx_benchmark_utils.F90:6:0:

 block

internal compiler error: in gfc_process_block_locals, at
fortran/trans-decl.c:6626
0x6c3fd6 gfc_process_block_locals(gfc_namespace*)
../../gcc-7.2.0/gcc/fortran/trans-decl.c:6626
0x710d60 gfc_trans_block_construct(gfc_code*)
../../gcc-7.2.0/gcc/fortran/trans-stmt.c:1812
0x6a73a7 trans_code
../../gcc-7.2.0/gcc/fortran/trans.c:1913
0x6cc9ac gfc_generate_function_code(gfc_namespace*)
../../gcc-7.2.0/gcc/fortran/trans-decl.c:6332
0x6aae21 gfc_generate_module_code(gfc_namespace*)
../../gcc-7.2.0/gcc/fortran/trans.c:2195
0x6611bd translate_all_program_units
../../gcc-7.2.0/gcc/fortran/parse.c:6061
0x6611bd gfc_parse_file()
../../gcc-7.2.0/gcc/fortran/parse.c:6274
0x6a473f gfc_be_parse_file
../../gcc-7.2.0/gcc/fortran/f95-lang.c:204
Please submit a full bug report,
with preprocessed source if appropriate.
Please include the complete backtrace with any bug report.
See <https://gcc.gnu.org/bugs/> for instructions.

[Bug fortran/81251] New: check of logical pointers

2017-06-29 Thread valeryweber at hotmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=81251

Bug ID: 81251
   Summary: check of logical pointers
   Product: gcc
   Version: 8.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: valeryweber at hotmail dot com
  Target Milestone: ---

Hi All

Would it be possible to have a check of the validity of logical pointers (like
for integer)?

many thanks

v

program test
  logical, pointer :: l
  if(l) then
 write(*,*) '0t'
  else
 write(*,*) '0f'
  endif
end program test

gfortran-trunk test.f90 -fcheck=all -g
./a.out
 0t

[Bug fortran/80752] New: ICE with wrong type initialization

2017-05-15 Thread valeryweber at hotmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=80752

Bug ID: 80752
   Summary: ICE with wrong type initialization
   Product: gcc
   Version: 7.1.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: valeryweber at hotmail dot com
  Target Milestone: ---

Hi All
The following wrong code is ICEing.
v



 MODULE cp_mgga_exchange_utils
  IMPLICIT NONE
  INTEGER, PARAMETER, PUBLIC :: real_8 = SELECTED_REAL_KIND ( 14, 200 )
  TYPE, PRIVATE :: m05_m06_x_t
 LOGICAL :: add_vs98 = 0.0_real_8
  END TYPE m05_m06_x_t
  TYPE, PRIVATE :: cp_mgga_x_param_t
 TYPE(m05_m06_x_t)   :: M05_M06
  END TYPE cp_mgga_x_param_t
  TYPE(cp_mgga_x_param_t), PUBLIC, SAVE :: cp_mgga_x_param
END MODULE cp_mgga_exchange_utils


gfortran-intel-7.1.0 -c cp_mgga_exchange_utils.mod.F90
cp_mgga_exchange_utils.mod.F90:5:46:

  LOGICAL :: add_vs98 = 0.0_real_8
  1
internal compiler error: Can't convert ‘REAL(8)’ to ‘LOGICAL(4)’ at (1)
0x5a1ec8 gfc_internal_error(char const*, ...)
../../gcc-7.1.0/gcc/fortran/error.c:1348
0x5b592f gfc_convert_type_warn(gfc_expr*, gfc_typespec*, int, int)
../../gcc-7.1.0/gcc/fortran/intrinsic.c:5069
0x5a93fa gfc_generate_initializer(gfc_typespec*, bool)
../../gcc-7.1.0/gcc/fortran/expr.c:4398
0x59aab4 variable_decl
../../gcc-7.1.0/gcc/fortran/decl.c:2437
0x59aab4 gfc_match_data_decl()
../../gcc-7.1.0/gcc/fortran/decl.c:4888
0x5f9e29 match_word
../../gcc-7.1.0/gcc/fortran/parse.c:65
0x5fc871 decode_statement
../../gcc-7.1.0/gcc/fortran/parse.c:376
0x5fe0d4 next_free
../../gcc-7.1.0/gcc/fortran/parse.c:1223
0x5fe0d4 next_statement
../../gcc-7.1.0/gcc/fortran/parse.c:1455
0x5ffc35 parse_derived
../../gcc-7.1.0/gcc/fortran/parse.c:3250
0x5ffc35 parse_spec
../../gcc-7.1.0/gcc/fortran/parse.c:3790
0x602933 parse_module
../../gcc-7.1.0/gcc/fortran/parse.c:5883
0x602c2f gfc_parse_file()
../../gcc-7.1.0/gcc/fortran/parse.c:6196
0x64a90f gfc_be_parse_file
../../gcc-7.1.0/gcc/fortran/f95-lang.c:204
Please submit a full bug report,
with preprocessed source if appropriate.
Please include the complete backtrace with any bug report.
See <https://gcc.gnu.org/bugs/> for instructions.

[Bug fortran/80668] New: wrong error message with -finit-derived

2017-05-08 Thread valeryweber at hotmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=80668

Bug ID: 80668
   Summary: wrong error message with -finit-derived
   Product: gcc
   Version: 8.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: valeryweber at hotmail dot com
  Target Milestone: ---

Dear All

The following code is producing wrong error message with -finit-derived

thanks
v


MODULE pw_hfx
  IMPLICIT NONE
  TYPE :: dist_t
 INTEGER :: TYPE,nblks_loc,nblks
 INTEGER,DIMENSION(:),POINTER :: dist
  END TYPE dist_t

CONTAINS

  SUBROUTINE hfx_new()
TYPE(dist_t) :: dist
CALL release_dist(dist)
  END SUBROUTINE hfx_new

  SUBROUTINE release_dist(dist)
TYPE(dist_t) :: dist
  END SUBROUTINE release_dist
END MODULE pw_hfx


gfortran-trunk -c  -finit-derived -finit-integer=1234567890
-finit-logical=false -finit-real=snan  pw_hfx.mod.F90 
pw_hfx.mod.F90:5:41:

  INTEGER,DIMENSION(:),POINTER :: dist
 1
Error: The element in the structure constructor at (1), for pointer component
‘dist’ should be a POINTER or a TARGET
pw_hfx.mod.F90:5:41:

  INTEGER,DIMENSION(:),POINTER :: dist
 1
Error: Pointer initialization target at (1) must have the SAVE attribute

[Bug fortran/71880] pointer to allocatable character

2016-07-14 Thread valeryweber at hotmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=71880

--- Comment #1 from Valery Weber  ---
what about this one?

cat gcc-6.1b.f90
program t
character(:), dimension(:), allocatable, target :: c
character(:), dimension(:), pointer :: p
allocate(c(10),source='X')
p=>c(:)
write(*,*) 'p=<',p(1),'> c=<',c(1),'>',len(p(1))
end program t


gfortran-6.1.0 gcc-6.1b.f90 
./a.out 
p= c=   32674

[Bug fortran/71880] New: pointer to allocatable character

2016-07-14 Thread valeryweber at hotmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=71880

Bug ID: 71880
   Summary: pointer to allocatable character
   Product: gcc
   Version: 6.1.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: valeryweber at hotmail dot com
  Target Milestone: ---

Hi All
is that a compiler bug?
many thanks
v

cat gcc-6.1.f90 
program t
character(:), dimension(:), allocatable, target :: c
character(:), dimension(:), pointer :: p
allocate(c(10),source='X')
p=>c
write(*,*) 'p=<',p(1),'> c=<',c(1),'>',len(p(1))
end program t

gfortran-6.1.0 gcc-6.1.f90 
./a.out 
 p=<> c=   0

gfortran-trunk gcc-6.1.f90 
./a.out 
 p=<> c=   0

[Bug fortran/70575] New: write syntax check

2016-04-07 Thread valeryweber at hotmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=70575

Bug ID: 70575
   Summary: write syntax check
   Product: gcc
   Version: 6.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: valeryweber at hotmail dot com
  Target Milestone: ---

Hi All
Should gfortran complain about the syntax of the following code?
v

gcc version 6.0.0 20160330 (experimental) (GCC) 

cat t.f90 
subroutine foo()
write(*,*) , 1
end subroutine foo

[Bug fortran/70397] New: ice while allocating ultimate polymorphic

2016-03-24 Thread valeryweber at hotmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=70397

Bug ID: 70397
   Summary: ice while allocating ultimate polymorphic
   Product: gcc
   Version: 5.3.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: valeryweber at hotmail dot com
  Target Milestone: ---

Dear All
The following code is ICEing.
v

cat gcc-ice-polym.f90
module mod

  TYPE, PUBLIC :: base_type
  END TYPE base_type

  TYPE, PUBLIC :: dict_entry_type
 PRIVATE
 CLASS( * ), ALLOCATABLE :: key
 CLASS( * ), ALLOCATABLE :: val
  END TYPE dict_entry_type


contains

  SUBROUTINE dict_put ( this, key, val )
CLASS(dict_entry_type), INTENT(INOUT) :: this
CLASS(base_type), INTENT(IN) :: key, val
INTEGER  :: istat
ALLOCATE( this%key, SOURCE=key, STAT=istat )
  end SUBROUTINE dict_put
end module mod

gfortran-5.3.0  -c gcc-ice-polym.f90
gcc-ice-polym.f90:19:0:

 ALLOCATE( this%key, SOURCE=key, STAT=istat )
 1
internal compiler error: Segmentation fault
0xa3420f crash_signal
../../gcc-5.3.0/gcc/toplev.c:383
0x69c8b8 gfc_class_len_get(tree_node*)
../../gcc-5.3.0/gcc/fortran/trans-expr.c:170
0x69fcb7 gfc_copy_class_to_class(tree_node*, tree_node*, tree_node*, bool)
../../gcc-5.3.0/gcc/fortran/trans-expr.c:1052
0x6d6fec gfc_trans_allocate(gfc_code*)
../../gcc-5.3.0/gcc/fortran/trans-stmt.c:5630
0x678bd7 trans_code
../../gcc-5.3.0/gcc/fortran/trans.c:1820
0x6995c4 gfc_generate_function_code(gfc_namespace*)
../../gcc-5.3.0/gcc/fortran/trans-decl.c:5851
0x67a1b9 gfc_generate_module_code(gfc_namespace*)
../../gcc-5.3.0/gcc/fortran/trans.c:2036
0x635118 translate_all_program_units
../../gcc-5.3.0/gcc/fortran/parse.c:5330
0x635118 gfc_parse_file()
../../gcc-5.3.0/gcc/fortran/parse.c:5540
0x674dd5 gfc_be_parse_file
../../gcc-5.3.0/gcc/fortran/f95-lang.c:229
Please submit a full bug report,
with preprocessed source if appropriate.
Please include the complete backtrace with any bug report.
See <http://gcc.gnu.org/bugs.html> for instructions.

[Bug fortran/70368] New: storage_size and size_of in initialization expression

2016-03-23 Thread valeryweber at hotmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=70368

Bug ID: 70368
   Summary: storage_size and size_of in initialization expression
   Product: gcc
   Version: 4.8.5
Status: UNCONFIRMED
  Severity: minor
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: valeryweber at hotmail dot com
  Target Milestone: ---

Dear All
Would it be possible to have one of the storage_size() or size_of() working in
initialization expression with the 4.8 series?
many thanks
v

cat t.f90
module test
private
INTEGER, parameter, public ::  i = storage_size(0)
INTEGER, parameter, public ::  j = size_of(0)
end module test

gfortran-intel-4.8.5 -c t.f90
t.f90:3.49:

INTEGER, parameter, public ::  i = storage_size(0)
 1
Error: Invalid character in name at (1)
t.f90:4.34:

INTEGER, parameter, public ::  j = size_of(0)
  1
Error: Function 'size_of' in initialization expression at (1) must be an
intrinsic function

[Bug fortran/70350] New: ICE with -fcheck=all and array initialization

2016-03-22 Thread valeryweber at hotmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=70350

Bug ID: 70350
   Summary: ICE with -fcheck=all and array initialization
   Product: gcc
   Version: 5.3.1
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: valeryweber at hotmail dot com
  Target Milestone: ---

Hi All
The following code is producing an ICE with -fcheck=all.
v

gcc version 5.3.1 20160318 

cat tmp.f90 
MODULE system
  IMPLICIT NONE
  PRIVATE
  TYPE, PUBLIC :: paraw_t
 INTEGER, ALLOCATABLE, DIMENSION(:,:) :: nwa12
  END TYPE paraw_t
  TYPE(paraw_t), SAVE, PUBLIC :: paraw
END MODULE system

MODULE system_utils
  USE system,  ONLY: paraw_t
  IMPLICIT NONE
  PRIVATE
CONTAINS
  SUBROUTINE alloc_paraw( paraw, max_nproc )
TYPE(paraw_t), INTENT(INOUT) :: paraw
INTEGER, INTENT(IN)  :: max_nproc
INTEGER  :: ierr
ALLOCATE( paraw%nwa12(0:max_nproc,2), &
 &STAT=ierr )
paraw%nwa12 = HUGE(0)
  END SUBROUTINE alloc_paraw
END MODULE system_utils

gfortran -fcheck=all tmp.f90 
tmp.f90:21:0:

 paraw%nwa12 = HUGE(0)
 1
internal compiler error: in wide_int_to_tree, at tree.c:1464
0x10c03da7 wide_int_to_tree(tree_node*,
generic_wide_int<wide_int_ref_storage > const&)
../../src/gcc/tree.c:1464
0x10c036c3 build_int_cst(tree_node*, long)
../../src/gcc/tree.c:1272
0x1063d127 gfc_trans_assignment_1
../../src/gcc/fortran/trans-expr.c:9127
0x10621d37 trans_code
../../src/gcc/fortran/trans.c:1711
0x10621d37 gfc_trans_code(gfc_code*)
../../src/gcc/fortran/trans.c:2020
0x1062e1bb gfc_generate_function_code(gfc_namespace*)
../../src/gcc/fortran/trans-decl.c:5927
0x10e984cf gfc_generate_module_code(gfc_namespace*)
../../src/gcc/fortran/trans.c:2087
0x105da05b translate_all_program_units
../../src/gcc/fortran/parse.c:5393
0x105da05b gfc_parse_file()
../../src/gcc/fortran/parse.c:5603
0x10e92207 gfc_be_parse_file
../../src/gcc/fortran/f95-lang.c:229
Please submit a full bug report,
with preprocessed source if appropriate.
Please include the complete backtrace with any bug report.
See  for instructions.

[Bug fortran/68856] New: wrong compilation wtih character interoperability

2015-12-11 Thread valeryweber at hotmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=68856

Bug ID: 68856
   Summary: wrong compilation wtih character interoperability
   Product: gcc
   Version: 5.3.1
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: valeryweber at hotmail dot com
  Target Milestone: ---

Dear All

The following code compiles with 5.3.0. Would it be possible to have an error
check on character with len>1 that are binded to C?
thanks
valery


cat t.f90
module test
  use iso_c_binding
  TYPE, BIND(C), PUBLIC :: cudaDeviceProp_t
 character(kind=c_char,len=256) :: name
  end type cudaDeviceProp_t
end module test

gfortran-5.3.0 -c t.f90 -std=f2008ts -Wall

[Bug fortran/65173] New: ICE while compiling wrong code

2015-02-23 Thread valeryweber at hotmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=65173

Bug ID: 65173
   Summary: ICE while compiling wrong code
   Product: gcc
   Version: 4.9.2
Status: UNCONFIRMED
  Severity: minor
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: valeryweber at hotmail dot com

Dear All
the following junk code is producing an ICE with 4.9.2
v

program min_obj
  implicit none
  integer, parameter :: string_length = 128
  integer, parameter :: max_n_params = 256
  type :: param_t
 integer :: n= 0
 real*8, dimension(256), allocatable :: x
 real*8, dimension(2,256), allocatable :: bounds
 character(string_length), dimension(256), allocatable :: names
  end type param_t
contains
  subroutine extrace_params_from_section ( )
character(*), dimension(), parameter :: char_params =
['element','parametrization']
  end subroutine extrace_params_from_section
end program min_obj


gfortran-intel-4.9.2 test.f90 
test.f90:7.45:

 real*8, dimension(256), allocatable :: x
 1
Error: Allocatable component of structure at (1) must have a deferred shape
test.f90:8.52:

 real*8, dimension(2,256), allocatable :: bounds
1
Error: Allocatable component of structure at (1) must have a deferred shape
test.f90:9.67:

 character(string_length), dimension(256), allocatable :: names
   1
Error: Allocatable component of structure at (1) must have a deferred shape
test.f90:13.28:

character(*), dimension(), parameter :: char_params =
['element','parametrization']
1
Error: Expected expression in array specification at (1)
f951: internal compiler error: Segmentation fault
0x911b6f crash_signal
../../gcc-4.9.2/gcc/toplev.c:337
0x55d8b2 gfc_is_constant_expr(gfc_expr*)
../../gcc-4.9.2/gcc/fortran/expr.c:897
0x5bdc7f resolve_fl_derived0
../../gcc-4.9.2/gcc/fortran/resolve.c:12428
0x5bed77 resolve_fl_derived0
../../gcc-4.9.2/gcc/fortran/resolve.c:12019
0x5bed77 resolve_fl_derived
../../gcc-4.9.2/gcc/fortran/resolve.c:12629
0x5b9a9f resolve_symbol
../../gcc-4.9.2/gcc/fortran/resolve.c:12900
0x5d07db do_traverse_symtree
../../gcc-4.9.2/gcc/fortran/symbol.c:3630
0x5bcba4 resolve_types
../../gcc-4.9.2/gcc/fortran/resolve.c:14644
0x5b8920 gfc_resolve
../../gcc-4.9.2/gcc/fortran/resolve.c:14745
0x5a43fa resolve_all_program_units
../../gcc-4.9.2/gcc/fortran/parse.c:4886
0x5a43fa gfc_parse_file()
../../gcc-4.9.2/gcc/fortran/parse.c:5135
0x5e1695 gfc_be_parse_file
../../gcc-4.9.2/gcc/fortran/f95-lang.c:212
Please submit a full bug report,
with preprocessed source if appropriate.
Please include the complete backtrace with any bug report.
See http://gcc.gnu.org/bugs.html for instructions.


[Bug fortran/64381] New: ICE with initialization of procedure pointer in type

2014-12-23 Thread valeryweber at hotmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64381

Bug ID: 64381
   Summary: ICE with initialization of procedure pointer in type
   Product: gcc
   Version: 4.9.2
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: valeryweber at hotmail dot com

Dear All

the following code is producing an ICE with gcc 4.9.2.

v

cat gcc-4.9.2.f90 
MODULE distribution_types_
  IMPLICIT NONE
  ABSTRACT INTERFACE
 FUNCTION dist_map_proc_to_blk_raw_list_func ( ) RESULT( list )
   INTEGER, DIMENSION(:,:), ALLOCATABLE :: list
 END FUNCTION dist_map_proc_to_blk_raw_list_func
  END INTERFACE
  TYPE, PUBLIC :: sm_type
 INTEGER, DIMENSION( : ), ALLOCATABLE :: proc_grid
 PROCEDURE( dist_map_proc_to_blk_raw_list_func ), NOPASS, POINTER ::
map_proc_to_blk_raw_list = NULL( )
  END TYPE sm_type
CONTAINS
  SUBROUTINE sm_multiply ( )
TYPE(sm_type), ALLOCATABLE, DIMENSION(:) :: matrices_a
ALLOCATE( matrices_a( 3 ) )
  END SUBROUTINE sm_multiply
END MODULE distribution_types_

gfortran-4.9.2 -c gcc-4.9.2.f90 
gcc-4.9.2.f90: In function ‘sm_multiply’:
gcc-4.9.2.f90:15:0: internal compiler error: in gfc_conv_descriptor_data_set,
at fortran/trans-array.c:171
 ALLOCATE( matrices_a( 3 ) )
 ^
0x5ebd56 gfc_conv_descriptor_data_set
../../gcc-4.9.2/gcc/fortran/trans-array.c:171
0x5ebd56 gfc_conv_descriptor_data_set(stmtblock_t*, tree_node*, tree_node*)
../../gcc-4.9.2/gcc/fortran/trans-array.c:166
0x5f370d structure_alloc_comps
../../gcc-4.9.2/gcc/fortran/trans-array.c:7785
0x5f305f structure_alloc_comps
../../gcc-4.9.2/gcc/fortran/trans-array.c:7646
0x5f4546 gfc_array_allocate(gfc_se*, gfc_expr*, tree_node*, tree_node*,
tree_node*, tree_node*, tree_node*, tree_node**, gfc_expr*, gfc_typespec*)
../../gcc-4.9.2/gcc/fortran/trans-array.c:5322
0x63c159 gfc_trans_allocate(gfc_code*)
../../gcc-4.9.2/gcc/fortran/trans-stmt.c:4952
0x5e8907 trans_code
../../gcc-4.9.2/gcc/fortran/trans.c:1794
0x6081f2 gfc_generate_function_code(gfc_namespace*)
../../gcc-4.9.2/gcc/fortran/trans-decl.c:5653
0x5e9e41 gfc_generate_module_code(gfc_namespace*)
../../gcc-4.9.2/gcc/fortran/trans.c:1995
0x5a7b60 translate_all_program_units
../../gcc-4.9.2/gcc/fortran/parse.c:4940
0x5a7b60 gfc_parse_file()
../../gcc-4.9.2/gcc/fortran/parse.c:5150
0x5e4be5 gfc_be_parse_file
../../gcc-4.9.2/gcc/fortran/f95-lang.c:212
Please submit a full bug report,
with preprocessed source if appropriate.
Please include the complete backtrace with any bug report.
See http://gcc.gnu.org/bugs.html for instructions.

[Bug fortran/63932] New: posible problem with allocatable character(:)

2014-11-18 Thread valeryweber at hotmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63932

Bug ID: 63932
   Summary: posible problem with allocatable character(:)
   Product: gcc
   Version: 4.9.2
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: valeryweber at hotmail dot com

Dear All
the following code seems to produce the wrong result with 4.9.2.
thanks
v

cat test.f90
module mod
  type :: t
 character(:), allocatable :: c
 integer :: i
   contains
 procedure, pass :: get
  end type t
  type :: u
 character(:), allocatable :: c
  end type u
contains
  subroutine get(this, a)
class(t), intent(in) :: this
character(:), allocatable, intent(out), optional :: a
if(present(a)) a=this%c
  end subroutine get
end module mod

program test
  use mod
  type(t) :: a
  type(u) :: b
  a%c='soemthing'
  call a%get(a=b%c)
  write(*,*) b%c
end program test

gfortran-4.9.2  test.f90 
./a.out


[Bug fortran/63674] New: procedure pointer and non/pure procedure

2014-10-29 Thread valeryweber at hotmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63674

Bug ID: 63674
   Summary: procedure pointer and non/pure procedure
   Product: gcc
   Version: 4.9.1
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: valeryweber at hotmail dot com

Dear All

the following code is compiling fine with 4.9.1, but shouldnt gcc complain
about calling a nonpure procedure from a pure one?

v

cat gcc_pure.f90
module test
  interface
 function func_interface ( ) RESULT( reslt )
   INTEGER :: reslt
 end function func_interface
  end interface
  type :: t
 procedure(func_interface), nopass, pointer :: f = NULL()
  end type t
contains
  function func_1 ( ) RESULT( reslt )
integer :: reslt
reslt = 1
  end function func_1
  pure subroutine eval( a, reslt )
type(t), intent(in) :: a
integer, intent(out) :: reslt
reslt = a%f()
!reslt = func_1()
  end subroutine eval
end module test

program prog
  use test
  type(t) :: a
  integer :: reslt
  a%f=func_1
  call eval(a,reslt)
  write(*,*) reslt
end program prog

gfortran-4.9.1   gcc_pure.f90
./a.out 
   1


[Bug fortran/63667] New: ICE with DEFERRED procedure

2014-10-28 Thread valeryweber at hotmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63667

Bug ID: 63667
   Summary: ICE with DEFERRED procedure
   Product: gcc
   Version: 4.9.1
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: valeryweber at hotmail dot com

Hi All

the following (wrong) piece of code is producing an ICE with gcc 4.9.1

v

cat cuba_types.F90
MODULE cubature_types
  IMPLICIT NONE
  PRIVATE
  TYPE, ABSTRACT :: cu_user_function_type
   CONTAINS
 PROCEDURE( cu_user_function_interface ), DEFERRED :: evaluate
  END TYPE cu_user_function_type

  ABSTRACT INTERFACE
 FUNCTION cu_user_function_interface ( this, r ) RESULT( reslt )
   IMPORT :: cu_user_function_type
   CLASS( cu_user_function_type ), INTENT( INOUT ) :: this
   REAL, DIMENSION( : ), INTENT( IN ) :: r
   REAL :: reslt
 END FUNCTION cu_user_function_interface
  END INTERFACE

  TYPE, PUBLIC :: cu_type
 PRIVATE
 LOGICAL :: init = .FALSE.
 CLASS( cu_user_function_type ) :: user_func
   CONTAINS
 PROCEDURE, PASS :: integrate = cu_integrate
  END TYPE cu_type

CONTAINS

  SUBROUTINE cu_integrate ( this )
CLASS(cu_type), INTENT(INOUT):: this
REAL, DIMENSION(3) :: r
r = 1.0
write(*,*) this%user_func%evaluate ( r )
  END SUBROUTINE cu_integrate

END MODULE cubature_types

gfortran-4.9.1 cuba_types.F90
cuba_types.F90:21.48:

 CLASS( cu_user_function_type ) :: user_func
1
Error: Component 'user_func' with CLASS at (1) must be allocatable or pointer
f951: internal compiler error: in check_typebound_baseobject, at
fortran/resolve.c:5369
0x5bb9a8 check_typebound_baseobject
../../gcc-4.9.1/gcc/fortran/resolve.c:5369
0x5be5ce resolve_compcall
../../gcc-4.9.1/gcc/fortran/resolve.c:5656
0x5b4de2 resolve_typebound_function
../../gcc-4.9.1/gcc/fortran/resolve.c:5798
0x5b4de2 gfc_resolve_expr(gfc_expr*)
../../gcc-4.9.1/gcc/fortran/resolve.c:6107
0x5bf9ee gfc_resolve_code(gfc_code*, gfc_namespace*)
../../gcc-4.9.1/gcc/fortran/resolve.c:9804
0x5c124b gfc_resolve_blocks(gfc_code*, gfc_namespace*)
../../gcc-4.9.1/gcc/fortran/resolve.c:9021
0x5beac7 gfc_resolve_code(gfc_code*, gfc_namespace*)
../../gcc-4.9.1/gcc/fortran/resolve.c:9794
0x5c140e resolve_codes
../../gcc-4.9.1/gcc/fortran/resolve.c:14719
0x5c1317 resolve_codes
../../gcc-4.9.1/gcc/fortran/resolve.c:14705
0x5b2385 gfc_resolve
../../gcc-4.9.1/gcc/fortran/resolve.c:14747
0x5b2385 gfc_resolve(gfc_namespace*)
../../gcc-4.9.1/gcc/fortran/resolve.c:14733
0x5a76ea gfc_parse_file()
../../gcc-4.9.1/gcc/fortran/parse.c:5089
0x5e4ca5 gfc_be_parse_file
../../gcc-4.9.1/gcc/fortran/f95-lang.c:212
Please submit a full bug report,
with preprocessed source if appropriate.
Please include the complete backtrace with any bug report.
See http://gcc.gnu.org/bugs.html for instructions.

gfortran-4.9.1 --version
GNU Fortran (GCC) 4.9.1
Copyright (C) 2014 Free Software Foundation, Inc.


[Bug preprocessor/63413] New: cpp trying to expand vector word in commented line in fortran file on power8

2014-09-30 Thread valeryweber at hotmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63413

Bug ID: 63413
   Summary: cpp trying to expand vector word in commented line
in fortran file on power8
   Product: gcc
   Version: 4.9.1
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: preprocessor
  Assignee: unassigned at gcc dot gnu.org
  Reporter: valeryweber at hotmail dot com

Hi All

The following code produces a wrong error while cpp (4.9.1 power8 ppc64le).
This gets cpp correctly on different archs.

v


cat tmp.F90 
program test
  ! vector
end program test

cpp --version
cpp (Ubuntu 4.9.1-15ubuntu1) 4.9.1
Copyright (C) 2014 Free Software Foundation, Inc.
This is free software; see the source for copying conditions.  There is NO
warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.

cpp -traditional -P tmp.F90













tmp.F90:2:0: error: detected recursion whilst expanding macro vector
   ! vector
 ^
program test
  ! vector
end program test


[Bug fortran/63294] ICE allocattion of array of type of type

2014-09-19 Thread valeryweber at hotmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63294

--- Comment #2 from Valery Weber valeryweber at hotmail dot com ---
the problem is the same as 61952


[Bug fortran/63294] New: ICE allocattion of array of type of type

2014-09-18 Thread valeryweber at hotmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63294

Bug ID: 63294
   Summary: ICE allocattion of array of type of type
   Product: gcc
   Version: 4.9.1
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: valeryweber at hotmail dot com


[Bug fortran/61952] New: ICE allocattion of array of type of type

2014-07-29 Thread valeryweber at hotmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=61952

Bug ID: 61952
   Summary: ICE allocattion of array of type of type
   Product: gcc
   Version: 4.9.1
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: valeryweber at hotmail dot com

Dear All

the following code is ICEing with gfortran 4.9.1

v

gfortran-4.9.1 -c  bug.F90 
bug.F90: In function ‘sm_multiply_a’:
bug.F90:29:0: internal compiler error: in gfc_conv_descriptor_data_set, at
fortran/trans-array.c:171
 ALLOCATE( matrices_a( n_push_tot + 1 ), matrices_b( n_push_tot + 1 ),
STAT=istat )
 ^
0x5ebe16 gfc_conv_descriptor_data_set
../../gcc-4.9.1/gcc/fortran/trans-array.c:171
0x5ebe16 gfc_conv_descriptor_data_set(stmtblock_t*, tree_node*, tree_node*)
../../gcc-4.9.1/gcc/fortran/trans-array.c:166
0x5f37cd structure_alloc_comps
../../gcc-4.9.1/gcc/fortran/trans-array.c:7785
0x5f2e8b structure_alloc_comps
../../gcc-4.9.1/gcc/fortran/trans-array.c:7978
0x5f311f structure_alloc_comps
../../gcc-4.9.1/gcc/fortran/trans-array.c:7646
0x5f4606 gfc_array_allocate(gfc_se*, gfc_expr*, tree_node*, tree_node*,
tree_node*, tree_node*, tree_node*, tree_node**, gfc_expr*, gfc_typespec*)
../../gcc-4.9.1/gcc/fortran/trans-array.c:5322
0x63c0b9 gfc_trans_allocate(gfc_code*)
../../gcc-4.9.1/gcc/fortran/trans-stmt.c:4952
0x5e89c7 trans_code
../../gcc-4.9.1/gcc/fortran/trans.c:1794
0x6082e2 gfc_generate_function_code(gfc_namespace*)
../../gcc-4.9.1/gcc/fortran/trans-decl.c:5653
0x5e9f01 gfc_generate_module_code(gfc_namespace*)
../../gcc-4.9.1/gcc/fortran/trans.c:1995
0x5a7b48 translate_all_program_units
../../gcc-4.9.1/gcc/fortran/parse.c:4940
0x5a7b48 gfc_parse_file()
../../gcc-4.9.1/gcc/fortran/parse.c:5150
0x5e4ca5 gfc_be_parse_file
../../gcc-4.9.1/gcc/fortran/f95-lang.c:212
Please submit a full bug report,
with preprocessed source if appropriate.
Please include the complete backtrace with any bug report.
See http://gcc.gnu.org/bugs.html for instructions.

cat bug.F90
MODULE distribution_types
  ABSTRACT INTERFACE
 FUNCTION dist_map_blk_to_proc_func ( row, col, nrow_tot, ncol_tot,
proc_grid ) RESULT( reslt )
   INTEGER, INTENT( IN ) :: row, col, nrow_tot, ncol_tot
   INTEGER, DIMENSION( : ), INTENT( IN ) :: proc_grid
   INTEGER, DIMENSION( : ), ALLOCATABLE :: reslt
 END FUNCTION dist_map_blk_to_proc_func
  END INTERFACE
  TYPE, PUBLIC :: dist_type
 INTEGER, DIMENSION( : ), ALLOCATABLE :: task_coords
 PROCEDURE( dist_map_blk_to_proc_func ), NOPASS, POINTER :: map_blk_to_proc
= NULL( )
  END TYPE dist_type
END MODULE distribution_types

MODULE sparse_matrix_types
  USE distribution_types,  ONLY : dist_type
  TYPE, PUBLIC :: sm_type
 TYPE( dist_type ) :: dist
  END TYPE sm_type
END MODULE sparse_matrix_types

MODULE sparse_matrix_multiply_a
  USE sparse_matrix_types,  ONLY : sm_type
CONTAINS
  SUBROUTINE sm_multiply_a (  )
INTEGER :: n_push_tot, istat
TYPE( sm_type ), DIMENSION( : ), ALLOCATABLE :: matrices_a, matrices_b
n_push_tot =2
ALLOCATE( matrices_a( n_push_tot + 1 ), matrices_b( n_push_tot + 1 ),
STAT=istat )
  END SUBROUTINE sm_multiply_a
END MODULE sparse_matrix_multiply_a

[Bug target/60301] New: cross compiler for android: multiple definition of TARGET_POSIX_IO

2014-02-21 Thread valeryweber at hotmail dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=60301

Bug ID: 60301
   Summary: cross compiler for android: multiple definition of
TARGET_POSIX_IO
   Product: gcc
   Version: 4.9.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: target
  Assignee: unassigned at gcc dot gnu.org
  Reporter: valeryweber at hotmail dot com

Dear 

while building a cross gcc (trunk) for android (ndk-r9c toolchains). 
I get a multiple definition of TARGET_POSIX_IO (see bellow). 
Getting rid of it makes the thing compile fine.

Thanks

v


./build/tools/build-gcc.sh  --build-out=/home/vwe/libs/gcc/test/tmp2
--binutils-version=2.22.90 --mpfr-version=3.1.2 --mpc-version=1.0
--gmp-version=5.1.3 --gdb-version=7.7 --cloog-version=0.18.1 --ppl-version=1.1
--isl-version=0.12  --try-64 /home/vwe/libs/gcc/test/android-ndk-r9c/src
/home/vwe/libs/gcc/test/android-ndk-r9c arm-linux-androideabi-4.8

[...]

In file included from ../.././gcc/tm.h:24:0,
 from
/home/vwe/libs/gcc/test/android-ndk-r9c/src/build/../gcc/gcc-4.8/libgcc/fixed-bit.c:48:
/home/vwe/libs/gcc/test/android-ndk-r9c/src/build/../gcc/gcc-4.8/libgcc/../gcc/config/gnu-user.h:109:0:
warning: TARGET_POSIX_IO redefined
 #define TARGET_POSIX_IO


[Bug fortran/60302] New: ICE with c_f_pointer and android cross compiler

2014-02-21 Thread valeryweber at hotmail dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=60302

Bug ID: 60302
   Summary: ICE with c_f_pointer and android cross compiler
   Product: gcc
   Version: 4.9.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: valeryweber at hotmail dot com

Dear All

I get an ICE while cross (android, ndk-toolchains 4.9c) compiling (gcc-trunk)
the following code.
The problem seems to arises in c_f_pointer.

Please let me know if more info is needed.

Thanks

v



cat gcc_reshaper.f90 
module reshaper

  implicit none

contains

  subroutine reshape_inplace_c2_c2(tgt_x, new_shape, ptr_x)
use, intrinsic :: iso_c_binding
implicit none
complex(8), target, intent(in) :: tgt_x(1,*)
integer, intent(in) :: new_shape(:)
complex(8), pointer, intent(out) :: ptr_x(:,:)
type(c_ptr) :: loc_x
loc_x = c_loc(tgt_x)
call c_f_pointer(loc_x, ptr_x, new_shape)
  end subroutine reshape_inplace_c2_c2

end module reshaper

+


/home/vwe/libs/gcc/test/tmp2/prefix/bin/arm-linux-androideabi-gfortran -c
gcc_reshaper.f90 
*** glibc detected ***
/home/vwe/libs/gcc/test/tmp2/prefix/libexec/gcc/arm-linux-androideabi/4.9.0/f951:
double free or corruption (fasttop): 0x036c5b60 ***
=== Backtrace: =
/lib64/libc.so.6[0x308147cb3e]
/home/vwe/libs/gcc/test/tmp2/prefix/libexec/gcc/arm-linux-androideabi/4.9.0/f951(_Z21gfc_check_c_f_pointerP8gfc_exprS0_S0_+0x191)[0x577c61]
/home/vwe/libs/gcc/test/tmp2/prefix/libexec/gcc/arm-linux-androideabi/4.9.0/f951(_Z27gfc_intrinsic_sub_interfaceP8gfc_codei+0xee)[0x5b1dee]
/home/vwe/libs/gcc/test/tmp2/prefix/libexec/gcc/arm-linux-androideabi/4.9.0/f951[0x5eef29]
/home/vwe/libs/gcc/test/tmp2/prefix/libexec/gcc/arm-linux-androideabi/4.9.0/f951[0x5f3d7d]
/home/vwe/libs/gcc/test/tmp2/prefix/libexec/gcc/arm-linux-androideabi/4.9.0/f951[0x5f58df]
/home/vwe/libs/gcc/test/tmp2/prefix/libexec/gcc/arm-linux-androideabi/4.9.0/f951[0x5f57e8]
/home/vwe/libs/gcc/test/tmp2/prefix/libexec/gcc/arm-linux-androideabi/4.9.0/f951(_Z11gfc_resolveP13gfc_namespace+0x66)[0x5e66b6]
/home/vwe/libs/gcc/test/tmp2/prefix/libexec/gcc/arm-linux-androideabi/4.9.0/f951(_Z14gfc_parse_filev+0x29b)[0x5dbd9b]
/home/vwe/libs/gcc/test/tmp2/prefix/libexec/gcc/arm-linux-androideabi/4.9.0/f951[0x6199f6]
/home/vwe/libs/gcc/test/tmp2/prefix/libexec/gcc/arm-linux-androideabi/4.9.0/f951[0xa21cbc]
/home/vwe/libs/gcc/test/tmp2/prefix/libexec/gcc/arm-linux-androideabi/4.9.0/f951(_Z11toplev_mainiPPc+0xa18)[0xa23978]
/lib64/libc.so.6(__libc_start_main+0xf5)[0x3081421a05]
/home/vwe/libs/gcc/test/tmp2/prefix/libexec/gcc/arm-linux-androideabi/4.9.0/f951[0x56aa99]
=== Memory map: 
0040-01638000 r-xp  fd:03 7609006   
/home/vwe/libs/gcc/test/tmp2/prefix/libexec/gcc/arm-linux-androideabi/4.9.0/f951
01838000-0183e000 r--p 01238000 fd:03 7609006   
/home/vwe/libs/gcc/test/tmp2/prefix/libexec/gcc/arm-linux-androideabi/4.9.0/f951
0183e000-0184c000 rw-p 0123e000 fd:03 7609006   
/home/vwe/libs/gcc/test/tmp2/prefix/libexec/gcc/arm-linux-androideabi/4.9.0/f951
0184c000-0192d000 rw-p  00:00 0 
03646000-036e6000 rw-p  00:00 0  [heap]
3080c0-3080c2 r-xp  fd:02 1458068   
/usr/lib64/ld-2.16.so
3080e2-3080e21000 r--p 0002 fd:02 1458068   
/usr/lib64/ld-2.16.so
3080e21000-3080e22000 rw-p 00021000 fd:02 1458068   
/usr/lib64/ld-2.16.so
3080e22000-3080e23000 rw-p  00:00 0 
308140-30815ad000 r-xp  fd:02 1458069   
/usr/lib64/libc-2.16.so
30815ad000-30817ad000 ---p 001ad000 fd:02 1458069   
/usr/lib64/libc-2.16.so
30817ad000-30817b1000 r--p 001ad000 fd:02 1458069   
/usr/lib64/libc-2.16.so
30817b1000-30817b3000 rw-p 001b1000 fd:02 1458069   
/usr/lib64/libc-2.16.so
30817b3000-30817b8000 rw-p  00:00 0 
3081c0-3081c03000 r-xp  fd:02 1458072   
/usr/lib64/libdl-2.16.so
3081c03000-3081e02000 ---p 3000 fd:02 1458072   
/usr/lib64/libdl-2.16.so
3081e02000-3081e03000 r--p 2000 fd:02 1458072   
/usr/lib64/libdl-2.16.so
3081e03000-3081e04000 rw-p 3000 fd:02 1458072   
/usr/lib64/libdl-2.16.so
308200-308210 r-xp  fd:02 1458079   
/usr/lib64/libm-2.16.so
308210-30822ff000 ---p 0010 fd:02 1458079   
/usr/lib64/libm-2.16.so
30822ff000-308230 r--p 000ff000 fd:02 1458079   
/usr/lib64/libm-2.16.so
308230-3082301000 rw-p 0010 fd:02 1458079   
/usr/lib64/libm-2.16.so
3082c0-3082c15000 r-xp  fd:02 1458080   
/usr/lib64

[Bug libgomp/59546] New: wrong behavior with reduction

2013-12-18 Thread valeryweber at hotmail dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=59546

Bug ID: 59546
   Summary: wrong behavior with reduction
   Product: gcc
   Version: 4.9.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: libgomp
  Assignee: unassigned at gcc dot gnu.org
  Reporter: valeryweber at hotmail dot com
CC: jakub at gcc dot gnu.org

hi all

the following code is producing strange result (removing the writes works
fine). is it a bug?

v


gfortran-trunk --version
GNU Fortran (GCC) 4.9.0 20131119 (experimental)
Copyright (C) 2013 Free Software Foundation, Inc.

GNU Fortran comes with NO WARRANTY, to the extent permitted by law.
You may redistribute copies of GNU Fortran
under the terms of the GNU General Public License.
For more information about these matters, see the file named COPYING

[vwe@triest semd]$ cat gcc_reduction.f90 
program test
  use omp_lib
  implicit none
  integer :: i

  !$omp parallel reduction(+:i)
  i=1

  !$omp master
  write(*,*) 'first write'
  write(*,*) 'second write'
  !$omp end master

  !$omp end parallel

  if(i.ne.omp_get_max_threads()) then
 write(*,*) i
 stop 'err1'
  endif

end program test
[vwe@triest semd]$ export OMP_NUM_THREADS=1; gfortran-trunk -fopenmp
gcc_reduction.f90   ;  ./a.out 
 first write
 second write
  49
STOP err1


[Bug libgomp/59467] New: copyprivate in the fortran testsuite

2013-12-11 Thread valeryweber at hotmail dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=59467

Bug ID: 59467
   Summary: copyprivate in the fortran testsuite
   Product: gcc
   Version: 4.9.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: libgomp
  Assignee: unassigned at gcc dot gnu.org
  Reporter: valeryweber at hotmail dot com
CC: jakub at gcc dot gnu.org

Dear All

the file

libgomp/testsuite/libgomp.fortran/crayptr2.f90

contains at line 26

!$omp end single copyprivate (d, ip)

but the variable d isnt declared as private (or threadprivate)
in its parallel region.

Isnt that a bug?

Thanks
Valery


[Bug fortran/59228] New: ICE with assume type and ASYNCHRONOUS

2013-11-21 Thread valeryweber at hotmail dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=59228

Bug ID: 59228
   Summary: ICE with assume type and ASYNCHRONOUS
   Product: gcc
   Version: 4.9.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: valeryweber at hotmail dot com

Dear All

The following wrong code is producing an ICE with gcc version 4.9.0 20131119.
Should gcc report an error rank mismatch instead?
Valery


cat gcc_1.f90 
MODULE mp
  IMPLICIT NONE
  interface
 subroutine test(base)
   TYPE(*), ASYNCHRONOUS :: base
 end subroutine Test
  end interface
CONTAINS
  SUBROUTINE foo ( data )
REAL( kind=8 ), DIMENSION( : ), ASYNCHRONOUS :: data
CALL test ( data )
  END SUBROUTINE foo
END MODULE mp

gfortran-trunk -c gcc_1.f90 
f951: internal compiler error: Segmentation fault
0x9eabbf crash_signal
../../trunk-src/gcc/toplev.c:334
0x57148e compare_parameter
../../trunk-src/gcc/fortran/interface.c:2091
0x57148e compare_actual_formal
../../trunk-src/gcc/fortran/interface.c:2589
0x571d23 gfc_procedure_use(gfc_symbol*, gfc_actual_arglist**, locus*)
../../trunk-src/gcc/fortran/interface.c:3292
0x5bd966 resolve_specific_s0
../../trunk-src/gcc/fortran/resolve.c:3185
0x5bd966 resolve_specific_s
../../trunk-src/gcc/fortran/resolve.c:3204
0x5bd966 resolve_call
../../trunk-src/gcc/fortran/resolve.c:3360
0x5c2a47 resolve_code
../../trunk-src/gcc/fortran/resolve.c:9925
0x5c45ce resolve_codes
../../trunk-src/gcc/fortran/resolve.c:14546
0x5c44d7 resolve_codes
../../trunk-src/gcc/fortran/resolve.c:14532
0x5b53a5 gfc_resolve
../../trunk-src/gcc/fortran/resolve.c:14574
0x5b53a5 gfc_resolve(gfc_namespace*)
../../trunk-src/gcc/fortran/resolve.c:14560
0x5aabfa gfc_parse_file()
../../trunk-src/gcc/fortran/parse.c:4672
0x5e87c5 gfc_be_parse_file
../../trunk-src/gcc/fortran/f95-lang.c:188
Please submit a full bug report,
with preprocessed source if appropriate.
Please include the complete backtrace with any bug report.
See http://gcc.gnu.org/bugs.html for instructions.


[Bug fortran/58433] New: FINAL memory leaks

2013-09-16 Thread valeryweber at hotmail dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=58433

Bug ID: 58433
   Summary: FINAL memory leaks
   Product: gcc
   Version: 4.9.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: valeryweber at hotmail dot com

Dear All

I get memory leaks with the FINAL for the following code and
gcc version 4.9.0 20130916 (experimental) (GCC).
Is that a bug?
V


cat tmp.f90
module mod
  type t
 integer,allocatable,dimension(:)::i
   contains
 final :: t_final
  end type t
contains
  subroutine t_final(a)
type(t) :: a
deallocate(a%i)
  end subroutine t_final
end module mod
program main
  use mod
  type(t) :: a
  allocate(a%i(1))
end program main
gfortran-trunk -g tmp.f90
valgrind ./a.out 
==13378== Memcheck, a memory error detector
==13378== Copyright (C) 2002-2012, and GNU GPL'd, by Julian Seward et al.
==13378== Using Valgrind-3.8.1 and LibVEX; rerun with -h for copyright info
==13378== Command: ./a.out
==13378== 
==13378== 
==13378== HEAP SUMMARY:
==13378== in use at exit: 40,000 bytes in 1 blocks
==13378==   total heap usage: 18 allocs, 17 frees, 43,688 bytes allocated
==13378== 
==13378== LEAK SUMMARY:
==13378==definitely lost: 0 bytes in 0 blocks
==13378==indirectly lost: 0 bytes in 0 blocks
==13378==  possibly lost: 0 bytes in 0 blocks
==13378==still reachable: 40,000 bytes in 1 blocks
==13378== suppressed: 0 bytes in 0 blocks
==13378== Rerun with --leak-check=full to see details of leaked memory
==13378== 
==13378== For counts of detected and suppressed errors, rerun with: -v
==13378== ERROR SUMMARY: 0 errors from 0 contexts (suppressed: 2 from 2)


[Bug fortran/58434] New: no automatic deallocation with trunk

2013-09-16 Thread valeryweber at hotmail dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=58434

Bug ID: 58434
   Summary: no automatic deallocation with trunk
   Product: gcc
   Version: 4.9.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: valeryweber at hotmail dot com

Dear All
I noticed a changed of behavior between 4.8.1 and trunk.
While the following code produde no memory leaks with 4.8.1 it does with
the trunk. Is that a bug?
v


cat tmp.f90
module mod
  type t
 integer,allocatable,dimension(:)::i
  end type t
end module mod
program main
  use mod
  type(t) :: a
  allocate(a%i(1))
end program main
gfortran-trunk -g tmp.f90
valgrind ./a.out 
==13501== Memcheck, a memory error detector
==13501== Copyright (C) 2002-2012, and GNU GPL'd, by Julian Seward et al.
==13501== Using Valgrind-3.8.1 and LibVEX; rerun with -h for copyright info
==13501== Command: ./a.out
==13501== 
==13501== 
==13501== HEAP SUMMARY:
==13501== in use at exit: 40,000 bytes in 1 blocks
==13501==   total heap usage: 18 allocs, 17 frees, 43,688 bytes allocated
==13501== 
==13501== LEAK SUMMARY:
==13501==definitely lost: 0 bytes in 0 blocks
==13501==indirectly lost: 0 bytes in 0 blocks
==13501==  possibly lost: 0 bytes in 0 blocks
==13501==still reachable: 40,000 bytes in 1 blocks
==13501== suppressed: 0 bytes in 0 blocks
==13501== Rerun with --leak-check=full to see details of leaked memory
==13501== 
==13501== For counts of detected and suppressed errors, rerun with: -v
==13501== ERROR SUMMARY: 0 errors from 0 contexts (suppressed: 2 from 2)
gfortran-4.8.1 -g tmp.f90
valgrind ./a.out 
==13508== Memcheck, a memory error detector
==13508== Copyright (C) 2002-2012, and GNU GPL'd, by Julian Seward et al.
==13508== Using Valgrind-3.8.1 and LibVEX; rerun with -h for copyright info
==13508== Command: ./a.out
==13508== 
==13508== 
==13508== HEAP SUMMARY:
==13508== in use at exit: 0 bytes in 0 blocks
==13508==   total heap usage: 18 allocs, 18 frees, 43,664 bytes allocated
==13508== 
==13508== All heap blocks were freed -- no leaks are possible
==13508== 
==13508== For counts of detected and suppressed errors, rerun with: -v
==13508== ERROR SUMMARY: 0 errors from 0 contexts (suppressed: 2 from 2)


[Bug fortran/58433] FINAL memory leaks

2013-09-16 Thread valeryweber at hotmail dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=58433

--- Comment #2 from Valery Weber valeryweber at hotmail dot com ---
But the std says:



4.5.6.3 When finalization occurs
...
2 A nonpointer, nonallocatable object that is not a dummy argument or function
result is finalized immediately before it would become undefined due to
execution of a RETURN or END statement (16.6.6, item (3)).


and


1.3.66
END statement
end-block-data-stmt, end-function-stmt, end-module-stmt,
end-mp-subprogram-stmt, end-program-stmt, end-submodule-stmt, or
end-subroutine-stmt


so does the code fulfilling the finalization requirement (nonpointer/nonalloc
object + end-program-stmt)?

v

[Bug fortran/57596] select type bug with optional variables?

2013-06-13 Thread valeryweber at hotmail dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=57596

--- Comment #2 from Valery Weber valeryweber at hotmail dot com ---
But the selector is not optional. The problem even remains if I 
move the optional variables outside the SELECT TYPE (see bellow).
Those 2 codes run just fine with other compilers like ifort or xlf.
Thanks
Valery


MODULE base_types
  TYPE :: base_integer_type
 INTEGER :: i
  END TYPE base_integer_type
  TYPE :: base_character_type
 CHARACTER( 10 ) :: c
  END TYPE base_character_type
END MODULE base_types

PROGRAM main
  USE base_types
  IMPLICIT NONE
  INTEGER::i_val
  call get (  i_val=i_val )
  write(*,*) 'i_val',i_val
contains

  SUBROUTINE get (i_val, c_val)
INTEGER, INTENT( OUT ), OPTIONAL :: i_val
CHARACTER( : ), INTENT( OUT ), ALLOCATABLE, OPTIONAL :: c_val
CLASS( * ), POINTER :: p
TYPE( base_integer_type ),target :: i_base
INTEGER :: i_val_tmp
CHARACTER( 10 ) :: c_val_tmp
i_base%i=-12
p=i_base
SELECT TYPE( p )
TYPE IS( base_integer_type )
   i_val_tmp = p%i
TYPE IS( base_character_type )
   c_val_tmp = p%c
CLASS DEFAULT
   stop
END SELECT
IF(present(i_val)) i_val = i_val_tmp
if(present(c_val)) c_val = c_val_tmp
  END SUBROUTINE get
END PROGRAM main


[Bug fortran/57596] New: select type bug with optional variables?

2013-06-12 Thread valeryweber at hotmail dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=57596

Bug ID: 57596
   Summary: select type bug with optional variables?
   Product: gcc
   Version: 4.9.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: valeryweber at hotmail dot com

Dear All

The following code is producing a segfault with 
gcc version 4.9.0 20130612 (experimental) (GCC)
Is that a bug?
v



MODULE base_types
  TYPE :: base_integer_type
 INTEGER :: i
  END TYPE base_integer_type
  TYPE :: base_character_type
 CHARACTER( 10 ) :: c
  END TYPE base_character_type
END MODULE base_types

PROGRAM main
  USE base_types
  IMPLICIT NONE
  INTEGER::i_val
  call get (  i_val=i_val )
  write(*,*) 'i_val',i_val
contains

  SUBROUTINE get (i_val, c_val)
INTEGER, INTENT( OUT ), OPTIONAL :: i_val
CHARACTER( : ), INTENT( OUT ), ALLOCATABLE, OPTIONAL :: c_val
CLASS( * ), POINTER :: p
TYPE( base_integer_type ),target :: i_base
i_base%i=-12
p=i_base
SELECT TYPE( p )
TYPE IS( base_integer_type )
   IF(present(i_val)) i_val = p%i
TYPE IS( base_character_type )
   if(present(c_val)) c_val = p%c
CLASS DEFAULT
   stop
END SELECT
  END SUBROUTINE get
END PROGRAM main

./a.out 

Program received signal SIGSEGV: Segmentation fault - invalid memory reference.

Backtrace for this error:
#0  0x4120ED in _gfortrani_backtrace at backtrace.c:258
#1  0x401DD0 in _gfortrani_backtrace_handler at compile_options.c:129
#2  0x3FC8C35C1F
#3  0x401C08 in get.1883 at main.f90:?
#4  0x401B71 in MAIN__ at main.f90:?
Segmentation fault (core dumped)


[Bug fortran/57538] New: SAVE attribute needed for derived type with default initialization?

2013-06-06 Thread valeryweber at hotmail dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=57538

Bug ID: 57538
   Summary: SAVE attribute needed for derived type with default
initialization?
   Product: gcc
   Version: 4.8.1
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: valeryweber at hotmail dot com

Dear,
I would like to ask you if the following code is f2008ts valid.
So does the declaration of the table(...) need the SAVE?
Thanks
Valery

MODULE periodic_table
  IMPLICIT NONE
  TYPE, PUBLIC :: atom_type
 INTEGER   :: number = 0
  END TYPE atom_type
  INTEGER, PARAMETER, PRIVATE :: n_elements = 118
  TYPE( atom_type ), PUBLIC :: table( 0:n_elements )
END MODULE periodic_table


[Bug fortran/56305] New: passing array of character with len1 to c_loc

2013-02-13 Thread valeryweber at hotmail dot com


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



 Bug #: 56305

   Summary: passing array of character with len1 to c_loc

Classification: Unclassified

   Product: gcc

   Version: 4.8.0

Status: UNCONFIRMED

  Severity: minor

  Priority: P3

 Component: fortran

AssignedTo: unassig...@gcc.gnu.org

ReportedBy: valerywe...@hotmail.com





Dear All

The following code compiles, but shouldnt it be rejected? 

V



program aaa

  use, intrinsic :: iso_c_binding

  type(c_ptr) :: p

  character(len=2),dimension(1), target :: c

  p=c_loc(c(1))

end program aaa


[Bug fortran/55895] New: multiple type-bound procedures

2013-01-07 Thread valeryweber at hotmail dot com


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



 Bug #: 55895

   Summary: multiple type-bound procedures

Classification: Unclassified

   Product: gcc

   Version: 4.8.0

Status: UNCONFIRMED

  Severity: minor

  Priority: P3

 Component: fortran

AssignedTo: unassig...@gcc.gnu.org

ReportedBy: valerywe...@hotmail.com





Dear All

Should gfortran complain with the following code (so far it doesnt with the

trunk)?

Valery



module 

  type :: t

   contains

 procedure ::foo = afoo, bfoo

  end type t

contains

  subroutine afoo(this)

class(t) :: this

  end subroutine afoo

  subroutine bfoo(this)

class(t) :: this

  end subroutine bfoo

end module 


[Bug fortran/55574] New: c binding access to c_ptr type

2012-12-03 Thread valeryweber at hotmail dot com


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



 Bug #: 55574

   Summary: c binding access to c_ptr type

Classification: Unclassified

   Product: gcc

   Version: 4.8.0

Status: UNCONFIRMED

  Severity: minor

  Priority: P3

 Component: fortran

AssignedTo: unassig...@gcc.gnu.org

ReportedBy: valerywe...@hotmail.com





Hi All 

shouldnt gfortran (gcc version 4.8.0 20121126) complain with the following code

(something like c_ptr not defined)?

v



program 

  use iso_c_binding, only : c_loc

  integer, target :: i

  type(C_PTR) :: f_ptr

  f_ptr=c_loc(i)

end program 


[Bug fortran/55427] New: ICE class pointer

2012-11-21 Thread valeryweber at hotmail dot com

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

 Bug #: 55427
   Summary: ICE class pointer
Classification: Unclassified
   Product: gcc
   Version: 4.8.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
AssignedTo: unassig...@gcc.gnu.org
ReportedBy: valerywe...@hotmail.com


Dear All

Is that known?

gcc version 4.8.0 20121121 (experimental) (GCC) 

Valery

!
MODULE base_types
  IMPLICIT NONE
  TYPE :: base_type
  END TYPE base_type
  TYPE, extends( base_type ) :: integer_type
 integer :: i
  END TYPE integer_type
contains
  FUNCTION points_to ( this ) RESULT( reslt )
CLASS( base_type ), DIMENSION( : ), TARGET :: this
CLASS( base_type ), DIMENSION( : ), POINTER :: reslt
reslt = this
  END FUNCTION points_to
END MODULE base_types

program bug
  use base_types
  implicit none
  CLASS( base_type ), POINTER, DIMENSION( : ) :: reslt
  CLASS( base_type ), ALLOCATABLE, DIMENSION( : ) :: val
  type(integer_type) :: i
  i%i=12345
  ALLOCATE( val(10), source=i )
  reslt = points_to ( val )
  write(*,*) associated(reslt)
  select type( p= reslt )
  type is(integer_type)
 write(*,*) 'p=',p(2)%i
  class default
 stop 666
  end select
end program bug
!=
 gfortran-trunk bug4.f90 
bug4.f90: In function ‘bug’:
bug4.f90:24:0: internal compiler error: in fold_convert_loc, at
fold-const.c:1857
   reslt = points_to ( val )
 ^
0x83cb322 fold_convert_loc(unsigned int, tree_node*, tree_node*)
../../gcc-trunk/gcc/fold-const.c:1856
0x81eff63 gfc_trans_pointer_assignment(gfc_expr*, gfc_expr*)
../../gcc-trunk/gcc/fortran/trans-expr.c:6350
0x81f34a5 gfc_trans_class_assign(gfc_expr*, gfc_expr*, gfc_exec_op)
../../gcc-trunk/gcc/fortran/trans-expr.c:888
0x81b1dda trans_code
../../gcc-trunk/gcc/fortran/trans.c:1322
0x81dcf17 gfc_generate_function_code(gfc_namespace*)
../../gcc-trunk/gcc/fortran/trans-decl.c:5349
0x816f1c5 translate_all_program_units
../../gcc-trunk/gcc/fortran/parse.c:4467
0x816f1c5 gfc_parse_file()
../../gcc-trunk/gcc/fortran/parse.c:4681
0x81acbca gfc_be_parse_file
../../gcc-trunk/gcc/fortran/f95-lang.c:191
Please submit a full bug report,
with preprocessed source if appropriate.
Please include the complete backtrace with any bug report.
See http://gcc.gnu.org/bugs.html for instructions.

!


[Bug fortran/55282] [OOP] openmp directive and classes

2012-11-13 Thread valeryweber at hotmail dot com


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



--- Comment #6 from Valery Weber valeryweber at hotmail dot com 2012-11-13 
16:57:28 UTC ---

Dear All 

I posted a comment on the openmp forum about the f2003 features. Complaining

there may help, who knows?

Valery


[Bug fortran/55282] New: openmp directive and classes

2012-11-12 Thread valeryweber at hotmail dot com

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

 Bug #: 55282
   Summary: openmp directive and classes
Classification: Unclassified
   Product: gcc
   Version: 4.8.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
AssignedTo: unassig...@gcc.gnu.org
ReportedBy: valerywe...@hotmail.com


Dear All

The following code doesnt compile at all with the lattest gfortran. 
The problem seems to be in the class definition of the variable this 
(works fine while declared as type).

gcc version 4.8.0 20121112 (experimental) (GCC) 


module mod
  use omp_lib
  type :: my_t
 integer :: i
  end type my_t
contains
  subroutine init( this )
class( my_t ) :: this
!type( my_t ) :: this
write(*,*) 'init thread=',omp_get_thread_num()
this%i=2
  end subroutine init
end module mod
program prog
  use mod
  type( my_t ) :: a
!$omp parallel default( none )  
!$omp  private( a )  
!$omp  num_threads( 4 )
  call init(a)
!$omp end parallel
end program prog
--
gfortran-trunk prog.f90 -fopenmp
bug.f90: In function ‘prog’:
bug.f90:21:0: error: ‘__vtab_mod_My_t’ not specified in enclosing parallel
   call init(a)
 ^
bug.f90:20:0: error: enclosing parallel
 !$omp  num_threads( 4 )


Thanks
Valery


[Bug fortran/55282] [OOP] openmp directive and classes

2012-11-12 Thread valeryweber at hotmail dot com


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



--- Comment #3 from Valery Weber valeryweber at hotmail dot com 2012-11-12 
19:18:34 UTC ---

Thanks pointing that. Is there any reason for not allowing the classes in

openmp?

I noticed that other compilers (eg ifort, xlf) can accommodate with this

deviation from the standard, is gfortran going in the same direction?


[Bug fortran/55234] New: module procedure potential syntax error within interface block

2012-11-07 Thread valeryweber at hotmail dot com


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



 Bug #: 55234

   Summary: module procedure potential syntax error within

interface block

Classification: Unclassified

   Product: gcc

   Version: 4.8.0

Status: UNCONFIRMED

  Severity: minor

  Priority: P3

 Component: fortran

AssignedTo: unassig...@gcc.gnu.org

ReportedBy: valerywe...@hotmail.com





Dear All



I wonder if the :: is not a syntax error in the following interface block?

While gfortran goes through, other compilers like xlf or pgf90 complain about

it.



gcc version 4.8.0 20121107 (experimental) (GCC) 



module mod

  interface foo

 module procedure :: foo1

  end interface

contains

  subroutine foo1 ( )

  end subroutine foo1

end module mod



Valery


[Bug fortran/55134] New: associate construct and assumed size array

2012-10-30 Thread valeryweber at hotmail dot com


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



 Bug #: 55134

   Summary: associate construct and assumed size array

Classification: Unclassified

   Product: gcc

   Version: 4.8.0

Status: UNCONFIRMED

  Severity: normal

  Priority: P3

 Component: fortran

AssignedTo: unassig...@gcc.gnu.org

ReportedBy: valerywe...@hotmail.com





Dear All



I get a wrong result when associating an array via an associate construct and

passing it as assumed size array to a routine.



gcc version 4.8.0 20121018 (experimental) (GCC) 





program bug

  implicit none

  integer,dimension(1)::i

  i(:)=1

  associate(a =i)

call foo(a)

  end associate

  write(*,*) i

contains

  subroutine foo(v)

integer, dimension(*) :: v

v(1)=2

  end subroutine foo

end program bug





this gives me



./a.out 

   1



while I would expect 2



Valery