public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/38536]  New: ICE with C_LOC in resolve.c due to not properly going through expr->ref
@ 2008-12-15 20:34 burnus at gcc dot gnu dot org
  2008-12-26 22:55 ` [Bug fortran/38536] " mikael at gcc dot gnu dot org
                   ` (10 more replies)
  0 siblings, 11 replies; 12+ messages in thread
From: burnus at gcc dot gnu dot org @ 2008-12-15 20:34 UTC (permalink / raw)
  To: gcc-bugs

There are two C_LOC issues related to not going through all expr->ref. The
second one was found by Scot Breitenfeld (in PR 36771 comment 4), the first one
I found while trying to reduce it.

 * * *

use iso_c_binding
character(len=2),target :: str(2)
print *, c_loc(str(1))
end

Result:
  Gives no error
Expected:
  Error: CHARACTER argument 'str' to 'c_loc' at (1) must have a length of 1

Using C_LOC(str) an error is printed. Seemingly, is_scalar_expr_ptr either does
not work or it is the wrong function for the check in resolve.c's
gfc_iso_c_func_interface.

 * * *

The following program gives:

Internal Error at (1):
Unexpected expression reference type in gfc_iso_c_func_interface

The problem also occurs in resolve.c's gfc_iso_c_func_interface, though at a
different line.


  USE ISO_C_BINDING
  TYPE test
     CHARACTER(LEN=2), DIMENSION(1:2) :: c
     INTEGER(C_INT) :: i
  END TYPE test
  TYPE(test), TARGET :: chrScalar
  TYPE(C_PTR) :: f_ptr

  f_ptr = c_loc(chrScalar%c(1)(1:1))
  end


-- 
           Summary: ICE with C_LOC in resolve.c due to not properly going
                    through expr->ref
           Product: gcc
           Version: 4.4.0
            Status: UNCONFIRMED
          Keywords: ice-on-valid-code
          Severity: normal
          Priority: P3
         Component: fortran
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: burnus at gcc dot gnu dot org


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


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

* [Bug fortran/38536] ICE with C_LOC in resolve.c due to not properly going through expr->ref
  2008-12-15 20:34 [Bug fortran/38536] New: ICE with C_LOC in resolve.c due to not properly going through expr->ref burnus at gcc dot gnu dot org
@ 2008-12-26 22:55 ` mikael at gcc dot gnu dot org
  2008-12-26 23:06 ` mikael at gcc dot gnu dot org
                   ` (9 subsequent siblings)
  10 siblings, 0 replies; 12+ messages in thread
From: mikael at gcc dot gnu dot org @ 2008-12-26 22:55 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #1 from mikael at gcc dot gnu dot org  2008-12-26 22:54 -------
About the second error:

See http://gcc.gnu.org/bugzilla/show_bug.cgi?id=33497#c3

in resolve.c: 
 2095   else if (parent_ref != NULL && parent_ref->type != REF_COMPONENT)
 2096     gfc_internal_error ("Unexpected expression reference type in "
 2097                         "gfc_iso_c_func_interface");

we expect either a terminating component ref, or a component ref followed by a
terminating array or substring ref. 


-- 


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


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

* [Bug fortran/38536] ICE with C_LOC in resolve.c due to not properly going through expr->ref
  2008-12-15 20:34 [Bug fortran/38536] New: ICE with C_LOC in resolve.c due to not properly going through expr->ref burnus at gcc dot gnu dot org
  2008-12-26 22:55 ` [Bug fortran/38536] " mikael at gcc dot gnu dot org
@ 2008-12-26 23:06 ` mikael at gcc dot gnu dot org
  2008-12-27 11:41 ` dominiq at lps dot ens dot fr
                   ` (8 subsequent siblings)
  10 siblings, 0 replies; 12+ messages in thread
From: mikael at gcc dot gnu dot org @ 2008-12-26 23:06 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #2 from mikael at gcc dot gnu dot org  2008-12-26 23:04 -------
Created an attachment (id=16989)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=16989&action=view)
patch, not regression-tested

This patch fixes the ICE and accepts the following (valid, I think) program
(rejected by trunk)

  USE ISO_C_BINDING

  IMPLICIT NONE
  TYPE test3
          INTEGER, DIMENSION(5) :: b
  END TYPE test3

  TYPE test2
          TYPE(test3), DIMENSION(:), POINTER :: a
  END TYPE test2

  TYPE test
          TYPE(test2), DIMENSION(2) :: c
  END TYPE test

  TYPE(test) :: chrScalar
  TYPE(C_PTR) :: f_ptr
  TYPE(test3), TARGET :: d(3)


  chrScalar%c(1)%a => d
  f_ptr = c_loc(chrScalar%c(1)%a(1)%b(1))
  end


-- 

mikael at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
         AssignedTo|unassigned at gcc dot gnu   |mikael at gcc dot gnu dot
                   |dot org                     |org
             Status|UNCONFIRMED                 |ASSIGNED


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


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

* [Bug fortran/38536] ICE with C_LOC in resolve.c due to not properly going through expr->ref
  2008-12-15 20:34 [Bug fortran/38536] New: ICE with C_LOC in resolve.c due to not properly going through expr->ref burnus at gcc dot gnu dot org
  2008-12-26 22:55 ` [Bug fortran/38536] " mikael at gcc dot gnu dot org
  2008-12-26 23:06 ` mikael at gcc dot gnu dot org
@ 2008-12-27 11:41 ` dominiq at lps dot ens dot fr
  2008-12-27 13:02 ` dominiq at lps dot ens dot fr
                   ` (7 subsequent siblings)
  10 siblings, 0 replies; 12+ messages in thread
From: dominiq at lps dot ens dot fr @ 2008-12-27 11:41 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #3 from dominiq at lps dot ens dot fr  2008-12-27 11:40 -------
With the patch in comment#2, I see two regressions:

[ibook-dhum] f90/bug% gfc
/opt/gcc/_gcc_clean/gcc/testsuite/gfortran.dg/pr32601.f03
/opt/gcc/_gcc_clean/gcc/testsuite/gfortran.dg/pr32601.f03:10: internal compiler
error: in gfc_iso_c_func_interface, at fortran/resolve.c:2064
...
[ibook-dhum] f90/bug% gfc
/opt/gcc/_gcc_clean/gcc/testsuite/gfortran.dg/repack_arrays_1.f90
f951: internal compiler error: in gfc_iso_c_func_interface, at
fortran/resolve.c:2064

They are due to the new line:

  gcc_assert (args->expr->expr_type == EXPR_VARIABLE);


-- 


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


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

* [Bug fortran/38536] ICE with C_LOC in resolve.c due to not properly going through expr->ref
  2008-12-15 20:34 [Bug fortran/38536] New: ICE with C_LOC in resolve.c due to not properly going through expr->ref burnus at gcc dot gnu dot org
                   ` (2 preceding siblings ...)
  2008-12-27 11:41 ` dominiq at lps dot ens dot fr
@ 2008-12-27 13:02 ` dominiq at lps dot ens dot fr
  2008-12-27 23:24 ` mikael at gcc dot gnu dot org
                   ` (6 subsequent siblings)
  10 siblings, 0 replies; 12+ messages in thread
From: dominiq at lps dot ens dot fr @ 2008-12-27 13:02 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #4 from dominiq at lps dot ens dot fr  2008-12-27 13:00 -------
If I remove the assert gfortran.dg/repack_arrays_1.f90 passes, while
gfortran.dg/pr32601.f03 gives:

print *, c_loc(get_ptr()) ! { dg-error "has PRIVATE components" }
               1
Error: Parameter 'get_ptr' to 'c_loc' at (1) must be either a TARGET or an
associated pointer

instead of

/opt/gcc/_gcc_clean/gcc/testsuite/gfortran.dg/pr32601.f03:22.19:

print *, c_null_ptr, t  ! { dg-error "has PRIVATE components" }
                  1
Error: Derived type 'c_ptr' at (1) has PRIVATE components
/opt/gcc/_gcc_clean/gcc/testsuite/gfortran.dg/pr32601.f03:22.24:

print *, c_null_ptr, t  ! { dg-error "has PRIVATE components" }
                       1
Error: Derived type 'c_ptr' at (1) has PRIVATE components
/opt/gcc/_gcc_clean/gcc/testsuite/gfortran.dg/pr32601.f03:23.11:

print *, t ! { dg-error "has PRIVATE components" }
          1
Error: Derived type 'c_ptr' at (1) has PRIVATE components
/opt/gcc/_gcc_clean/gcc/testsuite/gfortran.dg/pr32601.f03:25.25:

print *, c_loc(get_ptr()) ! { dg-error "has PRIVATE components" }
                        1
Error: Derived type 'c_ptr' at (1) has PRIVATE components

Note that I do not understand a single word of this private business: what can
be the use of a PUBLIC derived type with PRIVATE components?


-- 


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


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

* [Bug fortran/38536] ICE with C_LOC in resolve.c due to not properly going through expr->ref
  2008-12-15 20:34 [Bug fortran/38536] New: ICE with C_LOC in resolve.c due to not properly going through expr->ref burnus at gcc dot gnu dot org
                   ` (3 preceding siblings ...)
  2008-12-27 13:02 ` dominiq at lps dot ens dot fr
@ 2008-12-27 23:24 ` mikael at gcc dot gnu dot org
  2008-12-30 22:48 ` mikael at gcc dot gnu dot org
                   ` (5 subsequent siblings)
  10 siblings, 0 replies; 12+ messages in thread
From: mikael at gcc dot gnu dot org @ 2008-12-27 23:24 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #5 from mikael at gcc dot gnu dot org  2008-12-27 23:23 -------
Created an attachment (id=16994)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=16994&action=view)
another attempt, regression-tested

Regression-tested, but with regressions :-(.
They are probably unrelated anyway:
FAIL fmt_g0_1.f08
It is about i/o, and there is a recent patch from Jerry about it. Note: it
fails with trunk as well.

FAIL is_iostat_end_eor_1.f90:
this one doesn't fail with trunk. The error is:
collect2: ld terminated with signal 11 [Segmentation fault]
This is unrelated, don't ask, because I don't want to investigate. 
I suspect it is a new feature of the glibc-2.9 :-/


What this patch changes:
remove the gcc_assert, and add handling for pointer-returning functions.


-- 

mikael at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
  Attachment #16989|0                           |1
        is obsolete|                            |


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


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

* [Bug fortran/38536] ICE with C_LOC in resolve.c due to not properly going through expr->ref
  2008-12-15 20:34 [Bug fortran/38536] New: ICE with C_LOC in resolve.c due to not properly going through expr->ref burnus at gcc dot gnu dot org
                   ` (4 preceding siblings ...)
  2008-12-27 23:24 ` mikael at gcc dot gnu dot org
@ 2008-12-30 22:48 ` mikael at gcc dot gnu dot org
  2008-12-31 15:38 ` brtnfld at hdfgroup dot org
                   ` (4 subsequent siblings)
  10 siblings, 0 replies; 12+ messages in thread
From: mikael at gcc dot gnu dot org @ 2008-12-30 22:48 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #6 from mikael at gcc dot gnu dot org  2008-12-30 22:47 -------
An other failure:

  use iso_c_binding
  type t1
          integer :: i(5)
  end type t1
  type t2
          type(t1) :: t(5)
  end type t2

  character(len=2),target :: str(2)
  type(t2), target :: tt
  type(C_PTR) :: p
  p = c_loc(tt%t%i(1))
  end


-- 


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


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

* [Bug fortran/38536] ICE with C_LOC in resolve.c due to not properly going through expr->ref
  2008-12-15 20:34 [Bug fortran/38536] New: ICE with C_LOC in resolve.c due to not properly going through expr->ref burnus at gcc dot gnu dot org
                   ` (5 preceding siblings ...)
  2008-12-30 22:48 ` mikael at gcc dot gnu dot org
@ 2008-12-31 15:38 ` brtnfld at hdfgroup dot org
  2009-01-04 12:27 ` dominiq at lps dot ens dot fr
                   ` (3 subsequent siblings)
  10 siblings, 0 replies; 12+ messages in thread
From: brtnfld at hdfgroup dot org @ 2008-12-31 15:38 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #7 from brtnfld at hdfgroup dot org  2008-12-31 15:36 -------
Additional failure:

SUBROUTINE test(buf, buf2)
  USE, INTRINSIC :: ISO_C_BINDING
  IMPLICIT NONE
  CHARACTER(LEN=*), INTENT(INOUT), TARGET :: buf
  CHARACTER(LEN=*), INTENT(INOUT), DIMENSION(1:2), TARGET :: buf2
  TYPE(C_PTR) :: f_ptr

  f_ptr = C_LOC(buf(1:1))      ! FAILS:
                               ! Error: CHARACTER argument 'buf' to 'c_loc'
                               ! at (1) must have a length of 1
  f_ptr = C_LOC(buf2(1)(1:1))  ! PASSES

END SUBROUTINE test


-- 


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


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

* [Bug fortran/38536] ICE with C_LOC in resolve.c due to not properly going through expr->ref
  2008-12-15 20:34 [Bug fortran/38536] New: ICE with C_LOC in resolve.c due to not properly going through expr->ref burnus at gcc dot gnu dot org
                   ` (6 preceding siblings ...)
  2008-12-31 15:38 ` brtnfld at hdfgroup dot org
@ 2009-01-04 12:27 ` dominiq at lps dot ens dot fr
  2009-01-04 13:01 ` mikael at gcc dot gnu dot org
                   ` (2 subsequent siblings)
  10 siblings, 0 replies; 12+ messages in thread
From: dominiq at lps dot ens dot fr @ 2009-01-04 12:27 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #8 from dominiq at lps dot ens dot fr  2009-01-04 12:27 -------
Withe the patch in comment #5 the problems reported in comment #4 disappear,
the test in comment #6 gives a bus error at compile time:

pr38536_3.f90: In function 'MAIN__':
pr38536_3.f90:1: internal compiler error: Bus error

and the test in comment #7 gives the reported error.


-- 


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


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

* [Bug fortran/38536] ICE with C_LOC in resolve.c due to not properly going through expr->ref
  2008-12-15 20:34 [Bug fortran/38536] New: ICE with C_LOC in resolve.c due to not properly going through expr->ref burnus at gcc dot gnu dot org
                   ` (7 preceding siblings ...)
  2009-01-04 12:27 ` dominiq at lps dot ens dot fr
@ 2009-01-04 13:01 ` mikael at gcc dot gnu dot org
  2010-05-02 15:09 ` dfranke at gcc dot gnu dot org
  2010-05-03 14:50 ` brtnfld at hdfgroup dot org
  10 siblings, 0 replies; 12+ messages in thread
From: mikael at gcc dot gnu dot org @ 2009-01-04 13:01 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #9 from mikael at gcc dot gnu dot org  2009-01-04 13:01 -------
Subject: Bug 38536

Author: mikael
Date: Sun Jan  4 13:01:12 2009
New Revision: 143050

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=143050
Log:
2009-01-04  Mikael Morin  <mikael.morin@tele2.fr>

        PR fortran/38536
        * gfortran.h (gfc_is_data_pointer): Added prototype
        * resolve.c (gfc_iso_c_func_interface):
        Use gfc_is_data_pointer to test for pointer attribute.
        * dependency.c (gfc_is_data_pointer):
        Support pointer-returning functions.

2009-01-04  Mikael Morin  <mikael.morin@tele2.fr>

        PR fortran/38536
        * gfortran.dg/c_loc_tests_13.f90: New test.
        * gfortran.dg/c_loc_tests_14.f90: New test.


Added:
    trunk/gcc/testsuite/gfortran.dg/c_loc_tests_13.f90
    trunk/gcc/testsuite/gfortran.dg/c_loc_tests_14.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/dependency.c
    trunk/gcc/fortran/gfortran.h
    trunk/gcc/fortran/resolve.c
    trunk/gcc/testsuite/ChangeLog


-- 


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


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

* [Bug fortran/38536] ICE with C_LOC in resolve.c due to not properly going through expr->ref
  2008-12-15 20:34 [Bug fortran/38536] New: ICE with C_LOC in resolve.c due to not properly going through expr->ref burnus at gcc dot gnu dot org
                   ` (8 preceding siblings ...)
  2009-01-04 13:01 ` mikael at gcc dot gnu dot org
@ 2010-05-02 15:09 ` dfranke at gcc dot gnu dot org
  2010-05-03 14:50 ` brtnfld at hdfgroup dot org
  10 siblings, 0 replies; 12+ messages in thread
From: dfranke at gcc dot gnu dot org @ 2010-05-02 15:09 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #10 from dfranke at gcc dot gnu dot org  2010-05-02 15:09 -------
Can this be closed? Is there something left to do here?


-- 

dfranke at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
OtherBugsDependingO|                            |32630
              nThis|                            |


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


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

* [Bug fortran/38536] ICE with C_LOC in resolve.c due to not properly going through expr->ref
  2008-12-15 20:34 [Bug fortran/38536] New: ICE with C_LOC in resolve.c due to not properly going through expr->ref burnus at gcc dot gnu dot org
                   ` (9 preceding siblings ...)
  2010-05-02 15:09 ` dfranke at gcc dot gnu dot org
@ 2010-05-03 14:50 ` brtnfld at hdfgroup dot org
  10 siblings, 0 replies; 12+ messages in thread
From: brtnfld at hdfgroup dot org @ 2010-05-03 14:50 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #11 from brtnfld at hdfgroup dot org  2010-05-03 14:50 -------
(In reply to comment #10)
> Can this be closed? Is there something left to do here?
> 
As of gfortran 4.4.4 (and 4.5.1) the program in comment #7 does not compile but
gives the same error:

Error: CHARACTER argument 'buf' to 'c_loc' at (1) must have a length of 1


-- 


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


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

end of thread, other threads:[~2010-05-03 14:50 UTC | newest]

Thread overview: 12+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2008-12-15 20:34 [Bug fortran/38536] New: ICE with C_LOC in resolve.c due to not properly going through expr->ref burnus at gcc dot gnu dot org
2008-12-26 22:55 ` [Bug fortran/38536] " mikael at gcc dot gnu dot org
2008-12-26 23:06 ` mikael at gcc dot gnu dot org
2008-12-27 11:41 ` dominiq at lps dot ens dot fr
2008-12-27 13:02 ` dominiq at lps dot ens dot fr
2008-12-27 23:24 ` mikael at gcc dot gnu dot org
2008-12-30 22:48 ` mikael at gcc dot gnu dot org
2008-12-31 15:38 ` brtnfld at hdfgroup dot org
2009-01-04 12:27 ` dominiq at lps dot ens dot fr
2009-01-04 13:01 ` mikael at gcc dot gnu dot org
2010-05-02 15:09 ` dfranke at gcc dot gnu dot org
2010-05-03 14:50 ` brtnfld at hdfgroup dot org

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).