public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/57094] New: [Fortran-Dev] ICE: in lhd_incomplete_type_error, at langhooks.c:203
@ 2013-04-27 21:55 dominiq at lps dot ens.fr
  2013-04-30 11:42 ` [Bug fortran/57094] " dominiq at lps dot ens.fr
                   ` (6 more replies)
  0 siblings, 7 replies; 8+ messages in thread
From: dominiq at lps dot ens.fr @ 2013-04-27 21:55 UTC (permalink / raw)
  To: gcc-bugs


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

             Bug #: 57094
           Summary: [Fortran-Dev] ICE: in lhd_incomplete_type_error, at
                    langhooks.c:203
    Classification: Unclassified
           Product: gcc
           Version: fortran-dev
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
        AssignedTo: unassigned@gcc.gnu.org
        ReportedBy: dominiq@lps.ens.fr
                CC: burnus@gcc.gnu.org
            Blocks: 56818


When compiled with the fortran-dev branch, the tests
gfortran.dg/auto_char_len_3.f90, proc_decl_23.f90, and transfer_intrinsic_3.f90
give the same ICE:

[macbook] f90/bug% gfcd
/opt/gcc/for_work/gcc/testsuite/gfortran.dg/auto_char_len_3.f90
/opt/gcc/for_work/gcc/testsuite/gfortran.dg/auto_char_len_3.f90: In function
'teststringtools':
/opt/gcc/for_work/gcc/testsuite/gfortran.dg/auto_char_len_3.f90:22:0: internal
compiler error: in lhd_incomplete_type_error, at langhooks.c:203
   txt = chararray2string(chararr)
[macbook] f90/bug% gfcd
/opt/gcc/for_work/gcc/testsuite/gfortran.dg/proc_decl_23.f90
/opt/gcc/for_work/gcc/testsuite/gfortran.dg/proc_decl_23.f90: In function
'MAIN__':
/opt/gcc/for_work/gcc/testsuite/gfortran.dg/proc_decl_23.f90:36:0: internal
compiler error: in lhd_incomplete_type_error, at langhooks.c:203
   print *, string_to_char (["a","b","c"])
[macbook] f90/bug% gfcd
/opt/gcc/for_work/gcc/testsuite/gfortran.dg/transfer_intrinsic_3.f90
/opt/gcc/for_work/gcc/testsuite/gfortran.dg/transfer_intrinsic_3.f90: In
function 'MAIN__':
/opt/gcc/for_work/gcc/testsuite/gfortran.dg/transfer_intrinsic_3.f90:34:0:
internal compiler error: in lhd_incomplete_type_error, at langhooks.c:203
     call has_key_ns(str_vs(qname(1:n-1)),"", n)


^ permalink raw reply	[flat|nested] 8+ messages in thread

* [Bug fortran/57094] [Fortran-Dev] ICE: in lhd_incomplete_type_error, at langhooks.c:203
  2013-04-27 21:55 [Bug fortran/57094] New: [Fortran-Dev] ICE: in lhd_incomplete_type_error, at langhooks.c:203 dominiq at lps dot ens.fr
@ 2013-04-30 11:42 ` dominiq at lps dot ens.fr
  2013-04-30 13:40 ` dominiq at lps dot ens.fr
                   ` (5 subsequent siblings)
  6 siblings, 0 replies; 8+ messages in thread
From: dominiq at lps dot ens.fr @ 2013-04-30 11:42 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #1 from Dominique d'Humieres <dominiq at lps dot ens.fr> 2013-04-30 11:42:49 UTC ---
Reduced test for gfortran.dg/transfer_intrinsic_3.f90

module m
  implicit none
contains
  pure function str_vs(vs) result(s)
    character, dimension(:), intent(in) :: vs
    character(len=size(vs)) :: s
    s = transfer(vs, s)
  end function str_vs
end module m

  use m
  implicit none
  character, dimension(:), pointer :: QName
  character :: tmp(6)
  integer :: n
  allocate(qname(6))
  qname = (/ 'a','b','c','d','e','f' /)

  tmp = str_vs(qname(1:n-1))
  print *, tmp
end

transfer_intrinsic_3_red.f90: In function 'MAIN__':
transfer_intrinsic_3_red.f90:19:0: internal compiler error: in
lhd_incomplete_type_error, at langhooks.c:203
   tmp = str_vs(qname(1:n-1))

Note that the test compiles, but generates a wrong code, without the module:

  implicit none
  character, dimension(:), pointer :: QName
  character :: tmp(6)
  integer :: n
  allocate(qname(6))
  qname = (/ 'a','b','c','d','e','f' /)

  tmp = str_vs(qname(1:n-1))
  print *, tmp
contains
  pure function str_vs(vs) result(s)
    character, dimension(:), intent(in) :: vs
    character(len=size(vs)) :: s
    s = transfer(vs, s)
  end function str_vs
end


^ permalink raw reply	[flat|nested] 8+ messages in thread

* [Bug fortran/57094] [Fortran-Dev] ICE: in lhd_incomplete_type_error, at langhooks.c:203
  2013-04-27 21:55 [Bug fortran/57094] New: [Fortran-Dev] ICE: in lhd_incomplete_type_error, at langhooks.c:203 dominiq at lps dot ens.fr
  2013-04-30 11:42 ` [Bug fortran/57094] " dominiq at lps dot ens.fr
@ 2013-04-30 13:40 ` dominiq at lps dot ens.fr
  2013-04-30 21:44 ` burnus at gcc dot gnu.org
                   ` (4 subsequent siblings)
  6 siblings, 0 replies; 8+ messages in thread
From: dominiq at lps dot ens.fr @ 2013-04-30 13:40 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #2 from Dominique d'Humieres <dominiq at lps dot ens.fr> 2013-04-30 13:40:27 UTC ---
Reduced test for gfortran.dg/proc_decl_23.f90

module m_string

  type t_string
    procedure(string_to_char), pointer, nopass :: char3 ! segfault
  end type t_string

contains

  function string_to_char (s) result(res)
    character, dimension(:), intent(in) :: s
    character(len=size(s)) :: res
    do i = 1, size(s)
      res(i:i) = s(i)
    end do
  end function string_to_char

end module m_string

  use m_string
  type(t_string) :: t
  print *, string_to_char (["a","b","c"])
end

If 'print *, string_to_char (["a","b","c"])' is commented in the original test,
it compiles and passes.

I also confirm that if the "contains ..." is moved from the module to the
program, the tests compile and run without error for
gfortran.dg/auto_char_len_3.f90 andproc_decl_23.f90.


^ permalink raw reply	[flat|nested] 8+ messages in thread

* [Bug fortran/57094] [Fortran-Dev] ICE: in lhd_incomplete_type_error, at langhooks.c:203
  2013-04-27 21:55 [Bug fortran/57094] New: [Fortran-Dev] ICE: in lhd_incomplete_type_error, at langhooks.c:203 dominiq at lps dot ens.fr
  2013-04-30 11:42 ` [Bug fortran/57094] " dominiq at lps dot ens.fr
  2013-04-30 13:40 ` dominiq at lps dot ens.fr
@ 2013-04-30 21:44 ` burnus at gcc dot gnu.org
  2013-05-07 17:04 ` burnus at gcc dot gnu.org
                   ` (3 subsequent siblings)
  6 siblings, 0 replies; 8+ messages in thread
From: burnus at gcc dot gnu.org @ 2013-04-30 21:44 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #3 from Tobias Burnus <burnus at gcc dot gnu.org> 2013-04-30 21:44:37 UTC ---
I thought the following would work. While it does so for the test cases, it
causes new failures. In principle, not elem_len but "dim[0].sm" is the correct
value - assuming, it is set.

--- a/gcc/fortran/trans-array.c
+++ b/gcc/fortran/trans-array.c
@@ -424,3 +424,2 @@ gfc_conv_descriptor_stride_get (tree desc, tree dim)
-  tmp = gfc_get_element_type (type);
-  size = size_in_bytes (tmp);
-  size = fold_convert (gfc_array_index_type, size);
+  size = fold_convert (gfc_array_index_type,
+                      gfc_conv_descriptor_elem_len_get (desc));
@@ -442,2 +441,2 @@ gfc_conv_descriptor_stride_set (stmtblock_t *block, tree
desc,
-  tmp = gfc_get_element_type (TREE_TYPE (desc));
-  tmp = size_in_bytes (tmp);
+  tmp = fold_convert (gfc_array_index_type,
+                     gfc_conv_descriptor_elem_len_get (desc));


^ permalink raw reply	[flat|nested] 8+ messages in thread

* [Bug fortran/57094] [Fortran-Dev] ICE: in lhd_incomplete_type_error, at langhooks.c:203
  2013-04-27 21:55 [Bug fortran/57094] New: [Fortran-Dev] ICE: in lhd_incomplete_type_error, at langhooks.c:203 dominiq at lps dot ens.fr
                   ` (2 preceding siblings ...)
  2013-04-30 21:44 ` burnus at gcc dot gnu.org
@ 2013-05-07 17:04 ` burnus at gcc dot gnu.org
  2013-05-08  6:07 ` dominiq at lps dot ens.fr
                   ` (2 subsequent siblings)
  6 siblings, 0 replies; 8+ messages in thread
From: burnus at gcc dot gnu.org @ 2013-05-07 17:04 UTC (permalink / raw)
  To: gcc-bugs


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

Tobias Burnus <burnus at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |RESOLVED
         Resolution|                            |FIXED

--- Comment #4 from Tobias Burnus <burnus at gcc dot gnu.org> 2013-05-07 17:04:13 UTC ---
That should now be fixed since the commit http://gcc.gnu.org/r198688 /
http://gcc.gnu.org/ml/fortran/2013-05/msg00031.html

(I think some other patches before also contributed to this fix.)


(In reply to comment #1)
> Note that the test compiles, but generates a wrong code, without the module:

I think it works - but I am too lazy to look through the test case to
understand whether it indeed works.


^ permalink raw reply	[flat|nested] 8+ messages in thread

* [Bug fortran/57094] [Fortran-Dev] ICE: in lhd_incomplete_type_error, at langhooks.c:203
  2013-04-27 21:55 [Bug fortran/57094] New: [Fortran-Dev] ICE: in lhd_incomplete_type_error, at langhooks.c:203 dominiq at lps dot ens.fr
                   ` (3 preceding siblings ...)
  2013-05-07 17:04 ` burnus at gcc dot gnu.org
@ 2013-05-08  6:07 ` dominiq at lps dot ens.fr
  2013-05-08  7:22 ` burnus at gcc dot gnu.org
  2013-05-08  7:53 ` dominiq at lps dot ens.fr
  6 siblings, 0 replies; 8+ messages in thread
From: dominiq at lps dot ens.fr @ 2013-05-08  6:07 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #5 from Dominique d'Humieres <dominiq at lps dot ens.fr> 2013-05-08 06:07:11 UTC ---
For the record, the first test in comment #1 is invalid as n is not
initialized. Now I see something I don't expect for both trunk and fortran-dev:
if I set n to 7, then printing tmp gives 'aaaaaa'. Is this expected?
If yes, why? If no, should I open a PR for it?


^ permalink raw reply	[flat|nested] 8+ messages in thread

* [Bug fortran/57094] [Fortran-Dev] ICE: in lhd_incomplete_type_error, at langhooks.c:203
  2013-04-27 21:55 [Bug fortran/57094] New: [Fortran-Dev] ICE: in lhd_incomplete_type_error, at langhooks.c:203 dominiq at lps dot ens.fr
                   ` (4 preceding siblings ...)
  2013-05-08  6:07 ` dominiq at lps dot ens.fr
@ 2013-05-08  7:22 ` burnus at gcc dot gnu.org
  2013-05-08  7:53 ` dominiq at lps dot ens.fr
  6 siblings, 0 replies; 8+ messages in thread
From: burnus at gcc dot gnu.org @ 2013-05-08  7:22 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #6 from Tobias Burnus <burnus at gcc dot gnu.org> 2013-05-08 07:22:05 UTC ---
(In reply to comment #5)
> For the record, the first test in comment #1 is invalid as n is not
> initialized. Now I see something I don't expect for both trunk and fortran-dev:
> if I set n to 7, then printing tmp gives 'aaaaaa'. Is this expected?

Yes, it is:
   str_vs(qname(1:n-1))
returns the string "abcdef" which is then assigned to the len=1 array "tmp":
  tmp = "abcdef"
as tmp is only len=1, only "a" is assigned - to all elements of the size=6
array:
  character :: tmp(6)

I assume you misread it as:
    character :: tmp*6
or as
    character(len=6) :: tmp


^ permalink raw reply	[flat|nested] 8+ messages in thread

* [Bug fortran/57094] [Fortran-Dev] ICE: in lhd_incomplete_type_error, at langhooks.c:203
  2013-04-27 21:55 [Bug fortran/57094] New: [Fortran-Dev] ICE: in lhd_incomplete_type_error, at langhooks.c:203 dominiq at lps dot ens.fr
                   ` (5 preceding siblings ...)
  2013-05-08  7:22 ` burnus at gcc dot gnu.org
@ 2013-05-08  7:53 ` dominiq at lps dot ens.fr
  6 siblings, 0 replies; 8+ messages in thread
From: dominiq at lps dot ens.fr @ 2013-05-08  7:53 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #7 from Dominique d'Humieres <dominiq at lps dot ens.fr> 2013-05-08 07:52:22 UTC ---
> as tmp is only len=1, only "a" is assigned

Thanks for the explanation. I missed the fact that len=1 for tmp(i).


^ permalink raw reply	[flat|nested] 8+ messages in thread

end of thread, other threads:[~2013-05-08  7:53 UTC | newest]

Thread overview: 8+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2013-04-27 21:55 [Bug fortran/57094] New: [Fortran-Dev] ICE: in lhd_incomplete_type_error, at langhooks.c:203 dominiq at lps dot ens.fr
2013-04-30 11:42 ` [Bug fortran/57094] " dominiq at lps dot ens.fr
2013-04-30 13:40 ` dominiq at lps dot ens.fr
2013-04-30 21:44 ` burnus at gcc dot gnu.org
2013-05-07 17:04 ` burnus at gcc dot gnu.org
2013-05-08  6:07 ` dominiq at lps dot ens.fr
2013-05-08  7:22 ` burnus at gcc dot gnu.org
2013-05-08  7:53 ` dominiq at lps dot ens.fr

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for read-only IMAP folder(s) and NNTP newsgroup(s).