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; 26+ 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] 26+ 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; 26+ 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] 26+ 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; 26+ 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] 26+ 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; 26+ 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] 26+ 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; 26+ 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] 26+ 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; 26+ 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] 26+ 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; 26+ 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] 26+ 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; 26+ 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] 26+ 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; 26+ 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] 26+ 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; 26+ 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] 26+ 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; 26+ 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] 26+ 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; 26+ 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] 26+ messages in thread

* [Bug fortran/38536] ICE with C_LOC in resolve.c due to not properly going through expr->ref
       [not found] <bug-38536-4@http.gcc.gnu.org/bugzilla/>
                   ` (12 preceding siblings ...)
  2013-03-25 15:54 ` burnus at gcc dot gnu.org
@ 2013-03-25 17:56 ` burnus at gcc dot gnu.org
  13 siblings, 0 replies; 26+ messages in thread
From: burnus at gcc dot gnu.org @ 2013-03-25 17:56 UTC (permalink / raw)
  To: gcc-bugs


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

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

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

--- Comment #25 from Tobias Burnus <burnus at gcc dot gnu.org> 2013-03-25 17:56:11 UTC ---
FIXED on the 4.9 trunk.

I think all remaining issues are now fixed. Regarding the string length: Only
character(len=1) is interoperable, using a substring doesn't make it valid.
However, for C_LOC even Fortran 2003 (since Technical Corrigendum 5) allows
character(kind=C_char) with len > 1.


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

* [Bug fortran/38536] ICE with C_LOC in resolve.c due to not properly going through expr->ref
       [not found] <bug-38536-4@http.gcc.gnu.org/bugzilla/>
                   ` (11 preceding siblings ...)
  2012-08-26  9:14 ` mikael at gcc dot gnu.org
@ 2013-03-25 15:54 ` burnus at gcc dot gnu.org
  2013-03-25 17:56 ` burnus at gcc dot gnu.org
  13 siblings, 0 replies; 26+ messages in thread
From: burnus at gcc dot gnu.org @ 2013-03-25 15:54 UTC (permalink / raw)
  To: gcc-bugs


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

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

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |burnus at gcc dot gnu.org

--- Comment #24 from Tobias Burnus <burnus at gcc dot gnu.org> 2013-03-25 15:54:01 UTC ---
Author: burnus
Date: Mon Mar 25 15:40:26 2013
New Revision: 197053

URL: http://gcc.gnu.org/viewcvs?rev=197053&root=gcc&view=rev
Log:
2013-03-25  Tobias Burnus  <burnus@net-b.de>

        PR fortran/38536
        PR fortran/38813
        PR fortran/38894
        PR fortran/39288
        PR fortran/40963
        PR fortran/45824
        PR fortran/47023
        PR fortran/47034
        PR fortran/49023
        PR fortran/50269
        PR fortran/50612
        PR fortran/52426
        PR fortran/54263
        PR fortran/55343
        PR fortran/55444
        PR fortran/55574
        PR fortran/56079
        PR fortran/56378
        * check.c (gfc_var_strlen): Properly handle 0-sized string.
        (gfc_check_c_sizeof): Use is_c_interoperable, add checks.
        (is_c_interoperable, gfc_check_c_associated, gfc_check_c_f_pointer,
        gfc_check_c_f_procpointer, gfc_check_c_funloc, gfc_check_c_loc): New
        functions.
        * expr.c (check_inquiry): Add c_sizeof, compiler_version and
        compiler_options.
        (gfc_check_pointer_assign): Refine function result check.
        gfortran.h (gfc_isym_id): Add GFC_ISYM_C_ASSOCIATED,
        GFC_ISYM_C_F_POINTER, GFC_ISYM_C_F_PROCPOINTER, GFC_ISYM_C_FUNLOC,
        GFC_ISYM_C_LOC.
        (iso_fortran_env_symbol, iso_c_binding_symbol): Handle
        NAMED_SUBROUTINE.
        (generate_isocbinding_symbol): Update prototype.
        (get_iso_c_sym): Remove.
        (gfc_isym_id_by_intmod, gfc_isym_id_by_intmod_sym): New prototypes.
        * intrinsic.c (gfc_intrinsic_subroutine_by_id): New function.
        (gfc_intrinsic_sub_interface): Use it.
        (add_functions, add_subroutines): Add missing C-binding intrinsics.
        (gfc_intrinsic_func_interface): Add special case for c_loc.
        gfc_isym_id_by_intmod, gfc_isym_id_by_intmod_sym): New functions.
        (gfc_intrinsic_func_interface, gfc_intrinsic_sub_interface): Use them.
        * intrinsic.h (gfc_check_c_associated, gfc_check_c_f_pointer,
        gfc_check_c_f_procpointer, gfc_check_c_funloc, gfc_check_c_loc,
        gfc_resolve_c_loc, gfc_resolve_c_funloc): New prototypes.
        * iresolve.c (gfc_resolve_c_loc, gfc_resolve_c_funloc): New
        functions.
        * iso-c-binding.def: Split PROCEDURE into NAMED_SUBROUTINE and
        NAMED_FUNCTION.
        * iso-fortran-env.def: Add NAMED_SUBROUTINE for completeness.
        * module.c (create_intrinsic_function): Support subroutines and
        derived-type results.
        (use_iso_fortran_env_module): Update calls.
        (import_iso_c_binding_module): Ditto; update calls to
        generate_isocbinding_symbol.
        * resolve.c (find_arglists): Skip for intrinsic symbols.
        (gfc_resolve_intrinsic): Find intrinsic subs via id.
        (is_scalar_expr_ptr, gfc_iso_c_func_interface,
        set_name_and_label, gfc_iso_c_sub_interface): Remove.
        (resolve_function, resolve_specific_s0): Remove calls to those.
        (resolve_structure_cons): Fix handling.
        * symbol.c (gen_special_c_interop_ptr): Update c_ptr/c_funptr
        generation.
        (gen_cptr_param, gen_fptr_param, gen_shape_param,
        build_formal_args, get_iso_c_sym): Remove.
        (std_for_isocbinding_symbol): Handle NAMED_SUBROUTINE.
        (generate_isocbinding_symbol): Support hidden symbols and
        using c_ptr/c_funptr symtrees for nullptr defs.
        * target-memory.c (gfc_target_encode_expr): Fix handling
        of c_ptr/c_funptr.
        * trans-expr.c (conv_isocbinding_procedure): Remove.
        (gfc_conv_procedure_call): Remove call to it.
        (gfc_trans_subcomponent_assign, gfc_conv_expr): Update handling
        of c_ptr/c_funptr.
        * trans-intrinsic.c (conv_isocbinding_function,
        conv_isocbinding_subroutine): New.
        (gfc_conv_intrinsic_function, gfc_conv_intrinsic_subroutine):
        Call them.
        * trans-io.c (transfer_expr): Fix handling of c_ptr/c_funptr.
        * trans-types.c (gfc_typenode_for_spec,
        gfc_get_derived_type): Ditto.
        (gfc_init_c_interop_kinds): Handle NAMED_SUBROUTINE.

2013-03-25  Tobias Burnus  <burnus@net-b.de>

        PR fortran/38536
        PR fortran/38813
        PR fortran/38894
        PR fortran/39288
        PR fortran/40963
        PR fortran/45824
        PR fortran/47023
        PR fortran/47034
        PR fortran/49023
        PR fortran/50269
        PR fortran/50612
        PR fortran/52426
        PR fortran/54263
        PR fortran/55343
        PR fortran/55444
        PR fortran/55574
        PR fortran/56079
        PR fortran/56378
        * gfortran.dg/c_assoc_2.f03: Update dg-error wording.
        * gfortran.dg/c_f_pointer_shape_test.f90: Ditto.
        * gfortran.dg/c_f_pointer_shape_tests_3.f03: Ditto.
        * gfortran.dg/c_f_pointer_tests_5.f90: Ditto.
        * gfortran.dg/c_funloc_tests_2.f03: Ditto.
        * gfortran.dg/c_funloc_tests_5.f03: Ditto.
        * gfortran.dg/c_funloc_tests_6.f90: Ditto.
        * gfortran.dg/c_loc_tests_10.f03: Add -std=f2008.
        * gfortran.dg/c_loc_tests_11.f03: Ditto, update dg-error.
        * gfortran.dg/c_loc_tests_16.f90: Ditto.
        * gfortran.dg/c_loc_tests_4.f03: Ditto.
        * gfortran.dg/c_loc_tests_15.f90: Update dg-error wording.
        * gfortran.dg/c_loc_tests_3.f03: Valid since F2003 TC5.
        * gfortran.dg/c_loc_tests_8.f03: Ditto.
        * gfortran.dg/c_ptr_tests_14.f90: Update scan-tree-dump-times.
        * gfortran.dg/c_ptr_tests_15.f90: Ditto.
        * gfortran.dg/c_sizeof_1.f90: Fix invalid code.
        * gfortran.dg/iso_c_binding_init_expr.f03: Update dg-error wording.
        * gfortran.dg/pr32601_1.f03: Ditto.
        * gfortran.dg/storage_size_2.f08: Remove dg-error.
        * gfortran.dg/blockdata_7.f90: New.
        * gfortran.dg/c_assoc_4.f90: New.
        * gfortran.dg/c_f_pointer_tests_6.f90: New.
        * gfortran.dg/c_f_pointer_tests_7.f90: New.
        * gfortran.dg/c_funloc_tests_8.f90: New.
        * gfortran.dg/c_loc_test_17.f90: New.
        * gfortran.dg/c_loc_test_18.f90: New.
        * gfortran.dg/c_loc_test_19.f90: New.
        * gfortran.dg/c_loc_test_20.f90: New.
        * gfortran.dg/c_sizeof_5.f90: New.
        * gfortran.dg/iso_c_binding_rename_3.f90: New.
        * gfortran.dg/transfer_resolve_2.f90: New.
        * gfortran.dg/transfer_resolve_3.f90: New.
        * gfortran.dg/transfer_resolve_4.f90: New.
        * gfortran.dg/pr32601.f03: Update dg-error.
        * gfortran.dg/c_ptr_tests_13.f03: Update dg-error.
        * gfortran.dg/c_ptr_tests_9.f03: Fix test case.


Added:
    trunk/gcc/testsuite/gfortran.dg/blockdata_7.f90
    trunk/gcc/testsuite/gfortran.dg/c_assoc_4.f90
    trunk/gcc/testsuite/gfortran.dg/c_f_pointer_tests_6.f90
    trunk/gcc/testsuite/gfortran.dg/c_f_pointer_tests_7.f90
    trunk/gcc/testsuite/gfortran.dg/c_funloc_tests_8.f90
    trunk/gcc/testsuite/gfortran.dg/c_loc_test_17.f90
    trunk/gcc/testsuite/gfortran.dg/c_loc_test_18.f90
    trunk/gcc/testsuite/gfortran.dg/c_loc_test_19.f90
    trunk/gcc/testsuite/gfortran.dg/c_loc_test_20.f90
    trunk/gcc/testsuite/gfortran.dg/c_loc_tests_17.f90
    trunk/gcc/testsuite/gfortran.dg/c_sizeof_5.f90
    trunk/gcc/testsuite/gfortran.dg/iso_c_binding_rename_3.f90
    trunk/gcc/testsuite/gfortran.dg/transfer_resolve_2.f90
    trunk/gcc/testsuite/gfortran.dg/transfer_resolve_3.f90
    trunk/gcc/testsuite/gfortran.dg/transfer_resolve_4.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/check.c
    trunk/gcc/fortran/expr.c
    trunk/gcc/fortran/gfortran.h
    trunk/gcc/fortran/intrinsic.c
    trunk/gcc/fortran/intrinsic.h
    trunk/gcc/fortran/iresolve.c
    trunk/gcc/fortran/iso-c-binding.def
    trunk/gcc/fortran/iso-fortran-env.def
    trunk/gcc/fortran/module.c
    trunk/gcc/fortran/resolve.c
    trunk/gcc/fortran/symbol.c
    trunk/gcc/fortran/target-memory.c
    trunk/gcc/fortran/trans-expr.c
    trunk/gcc/fortran/trans-intrinsic.c
    trunk/gcc/fortran/trans-io.c
    trunk/gcc/fortran/trans-types.c
    trunk/gcc/testsuite/ChangeLog
    trunk/gcc/testsuite/gfortran.dg/c_assoc_2.f03
    trunk/gcc/testsuite/gfortran.dg/c_f_pointer_shape_test.f90
    trunk/gcc/testsuite/gfortran.dg/c_f_pointer_shape_tests_3.f03
    trunk/gcc/testsuite/gfortran.dg/c_f_pointer_tests_5.f90
    trunk/gcc/testsuite/gfortran.dg/c_funloc_tests_2.f03
    trunk/gcc/testsuite/gfortran.dg/c_funloc_tests_5.f03
    trunk/gcc/testsuite/gfortran.dg/c_funloc_tests_6.f90
    trunk/gcc/testsuite/gfortran.dg/c_loc_tests_10.f03
    trunk/gcc/testsuite/gfortran.dg/c_loc_tests_11.f03
    trunk/gcc/testsuite/gfortran.dg/c_loc_tests_15.f90
    trunk/gcc/testsuite/gfortran.dg/c_loc_tests_16.f90
    trunk/gcc/testsuite/gfortran.dg/c_loc_tests_3.f03
    trunk/gcc/testsuite/gfortran.dg/c_loc_tests_4.f03
    trunk/gcc/testsuite/gfortran.dg/c_loc_tests_8.f03
    trunk/gcc/testsuite/gfortran.dg/c_ptr_tests_13.f03
    trunk/gcc/testsuite/gfortran.dg/c_ptr_tests_14.f90
    trunk/gcc/testsuite/gfortran.dg/c_ptr_tests_15.f90
    trunk/gcc/testsuite/gfortran.dg/c_ptr_tests_9.f03
    trunk/gcc/testsuite/gfortran.dg/c_sizeof_1.f90
    trunk/gcc/testsuite/gfortran.dg/iso_c_binding_init_expr.f03
    trunk/gcc/testsuite/gfortran.dg/pr32601.f03
    trunk/gcc/testsuite/gfortran.dg/pr32601_1.f03
    trunk/gcc/testsuite/gfortran.dg/storage_size_2.f08


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

* [Bug fortran/38536] ICE with C_LOC in resolve.c due to not properly going through expr->ref
       [not found] <bug-38536-4@http.gcc.gnu.org/bugzilla/>
                   ` (10 preceding siblings ...)
  2011-01-25 16:26 ` burnus at gcc dot gnu.org
@ 2012-08-26  9:14 ` mikael at gcc dot gnu.org
  2013-03-25 15:54 ` burnus at gcc dot gnu.org
  2013-03-25 17:56 ` burnus at gcc dot gnu.org
  13 siblings, 0 replies; 26+ messages in thread
From: mikael at gcc dot gnu.org @ 2012-08-26  9:14 UTC (permalink / raw)
  To: gcc-bugs

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

Mikael Morin <mikael at gcc dot gnu.org> changed:

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

--- Comment #23 from Mikael Morin <mikael at gcc dot gnu.org> 2012-08-26 09:14:16 UTC ---
Unassigning.


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

* [Bug fortran/38536] ICE with C_LOC in resolve.c due to not properly going through expr->ref
       [not found] <bug-38536-4@http.gcc.gnu.org/bugzilla/>
                   ` (9 preceding siblings ...)
  2011-01-22 19:23 ` tkoenig at gcc dot gnu.org
@ 2011-01-25 16:26 ` burnus at gcc dot gnu.org
  2012-08-26  9:14 ` mikael at gcc dot gnu.org
                   ` (2 subsequent siblings)
  13 siblings, 0 replies; 26+ messages in thread
From: burnus at gcc dot gnu.org @ 2011-01-25 16:26 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #22 from Tobias Burnus <burnus at gcc dot gnu.org> 2011-01-25 15:44:50 UTC ---
Created attachment 23121
  --> http://gcc.gnu.org/bugzilla/attachment.cgi?id=23121
draft patch, working but too many warnings (cf. test suite failures)

Currently
  c_loc(a(1:2))
produces the warning
  "Array section in '%s' call at %L"
which is correct but possibly misleading as F2008 (contrary to F2003) allows
it.

What F2008 only requires is that the argument is contiguous. At
  http://gcc.gnu.org/ml/fortran/2011-01/msg00180.html
was an early (and very buggy), attached a more advanced patch which gives the
warning:
  "Array might be not contiguous in '%s' call at %L"

However, the patch is also overzealous by warning for "a(1:2:5)" which is
contiguous (as equivalent to "a(1:1)"). But it also warns elsewhere too much.

I think it would be useful to only warn (or error out) if it is known to be
noncontiguous of if one cuts down the number of warnings.


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

* [Bug fortran/38536] ICE with C_LOC in resolve.c due to not properly going through expr->ref
       [not found] <bug-38536-4@http.gcc.gnu.org/bugzilla/>
                   ` (8 preceding siblings ...)
  2011-01-14 19:53 ` tkoenig at gcc dot gnu.org
@ 2011-01-22 19:23 ` tkoenig at gcc dot gnu.org
  2011-01-25 16:26 ` burnus at gcc dot gnu.org
                   ` (3 subsequent siblings)
  13 siblings, 0 replies; 26+ messages in thread
From: tkoenig at gcc dot gnu.org @ 2011-01-22 19:23 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #21 from Thomas Koenig <tkoenig at gcc dot gnu.org> 2011-01-22 17:30:27 UTC ---
Author: tkoenig
Date: Sat Jan 22 17:30:22 2011
New Revision: 169130

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=169130
Log:
2011-01-22  Thomas Koenig  <tkoenig@gcc.gnu.org>

    PR fortran/38536
    * resolve.c (gfc_iso_c_func_interface):  For C_LOC,
    check for array sections followed by component references
    which are illegal.  Also check for coindexed arguments.

2011-01-22  Thomas Koenig  <tkoenig@gcc.gnu.org>

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


Added:
    trunk/gcc/testsuite/gfortran.dg/c_loc_tests_16.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/resolve.c
    trunk/gcc/testsuite/ChangeLog


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

* [Bug fortran/38536] ICE with C_LOC in resolve.c due to not properly going through expr->ref
       [not found] <bug-38536-4@http.gcc.gnu.org/bugzilla/>
                   ` (7 preceding siblings ...)
  2011-01-14  9:59 ` burnus at gcc dot gnu.org
@ 2011-01-14 19:53 ` tkoenig at gcc dot gnu.org
  2011-01-22 19:23 ` tkoenig at gcc dot gnu.org
                   ` (4 subsequent siblings)
  13 siblings, 0 replies; 26+ messages in thread
From: tkoenig at gcc dot gnu.org @ 2011-01-14 19:53 UTC (permalink / raw)
  To: gcc-bugs

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

Thomas Koenig <tkoenig at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
           Keywords|ice-on-valid-code           |ice-on-invalid-code

--- Comment #20 from Thomas Koenig <tkoenig at gcc dot gnu.org> 2011-01-14 19:42:58 UTC ---
(In reply to comment #19)

> 
> Similarly, c_loc(comp(1:2)%elem) is valid as long as "elem" is the only item in
> the derived type *and* no padding is happening. (As padding often occurs, one
> could always reject it.)

I don't think so, at least not in F 2003.  comp(1:2) is an array slice,
which is never interoperable.  The language in F 2008 appears unchanged,
so I guess the same applies there.

> And comp(1:1)%elem is always contiguous - but that's also a strange way of
> writing it. (Actually, I think that comp(1:1)%elem _is_ simply contiguous -
> though I am not sure gfc_simply_contiguous does detect this.)

That would be fairly easy to change.  Can you open a PR for this?


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

* [Bug fortran/38536] ICE with C_LOC in resolve.c due to not properly going through expr->ref
       [not found] <bug-38536-4@http.gcc.gnu.org/bugzilla/>
                   ` (6 preceding siblings ...)
  2011-01-13 20:02 ` tkoenig at gcc dot gnu.org
@ 2011-01-14  9:59 ` burnus at gcc dot gnu.org
  2011-01-14 19:53 ` tkoenig at gcc dot gnu.org
                   ` (5 subsequent siblings)
  13 siblings, 0 replies; 26+ messages in thread
From: burnus at gcc dot gnu.org @ 2011-01-14  9:59 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #19 from Tobias Burnus <burnus at gcc dot gnu.org> 2011-01-14 09:00:20 UTC ---
(In reply to comment #18)
> (I asked on comp.lang.fortran)

Cf.
http://groups.google.com/group/comp.lang.fortran/browse_thread/thread/4b65b1cd206ce9fe

Or from the standard (F2008):

"15.2.3.6 C LOC (X)": "Argument. X [...] shall not be a coindexed object. [...]
If it is an array, it shall be contiguous and have nonzero size."


> We just have to check for array sections along the references, and error
> out if there are any.

I was about to suggest to use gfc_simply_contiguous() but I then realized that
-- for a simply contiguous array "array" -- also the following array section 
  array([1,2,3,4])
is contiguous - even though it is not simply contiguous and in the general case
the contiguity is not compile-time checkable. (vector-subscripts are
notoriously difficult to check at compile time)

Similarly, c_loc(comp(1:2)%elem) is valid as long as "elem" is the only item in
the derived type *and* no padding is happening. (As padding often occurs, one
could always reject it.)

And comp(1:1)%elem is always contiguous - but that's also a strange way of
writing it. (Actually, I think that comp(1:1)%elem _is_ simply contiguous -
though I am not sure gfc_simply_contiguous does detect this.)


Personally, I think one should give some diagnostic as soon as the argument is
not simply contiguous -- be it a warning or an error. At least I cannot imagine
any sensible program using non-simply contiguous arrays as argument for C_LOC.

(The term simply contiguous is defined in section 6.5.4.)

 * * *

When you add another check  for C_LOC, can you include one for the following?
You just need to add a "gfc_is_coindexed (expr)".

use iso_c_binding
type t
  integer :: A
end type t
type(t), target, allocatable :: x(:)[:]
type(c_ptr) :: cptr

allocate(x(1)[*])
cptr = c_loc(x(1)%a)    ! OK
cptr = c_loc(x(1)[1]%a) ! Invalid
end


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

* [Bug fortran/38536] ICE with C_LOC in resolve.c due to not properly going through expr->ref
       [not found] <bug-38536-4@http.gcc.gnu.org/bugzilla/>
                   ` (5 preceding siblings ...)
  2011-01-09 16:02 ` tkoenig at netcologne dot de
@ 2011-01-13 20:02 ` tkoenig at gcc dot gnu.org
  2011-01-14  9:59 ` burnus at gcc dot gnu.org
                   ` (6 subsequent siblings)
  13 siblings, 0 replies; 26+ messages in thread
From: tkoenig at gcc dot gnu.org @ 2011-01-13 20:02 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #18 from Thomas Koenig <tkoenig at gcc dot gnu.org> 2011-01-13 19:52:31 UTC ---
(In reply to comment #6)
> 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

This is ice-on-invalid (I asked on comp.lang.fortran) because tt%t is an array
section, which is not interoperable.

We just have to check for array sections along the references, and error out if
there are any.


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

* [Bug fortran/38536] ICE with C_LOC in resolve.c due to not properly going through expr->ref
       [not found] <bug-38536-4@http.gcc.gnu.org/bugzilla/>
                   ` (4 preceding siblings ...)
  2011-01-09 16:00 ` tkoenig at gcc dot gnu.org
@ 2011-01-09 16:02 ` tkoenig at netcologne dot de
  2011-01-13 20:02 ` tkoenig at gcc dot gnu.org
                   ` (7 subsequent siblings)
  13 siblings, 0 replies; 26+ messages in thread
From: tkoenig at netcologne dot de @ 2011-01-09 16:02 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #17 from tkoenig at netcologne dot de <tkoenig at netcologne dot de> 2011-01-09 16:00:14 UTC ---
Am 09.01.2011 16:33, schrieb burnus at gcc dot gnu.org:
> http://gcc.gnu.org/bugzilla/show_bug.cgi?id=38536
> 
> --- Comment #15 from Tobias Burnus <burnus at gcc dot gnu.org> 2011-01-09 15:33:02 UTC ---
> (In reply to comment #13)
>> The test case from comment 6 gives an ICE (segfault) in
>> gfc_conv_procedure_call's check for
>>             && fsym->as->type != AS_ASSUMED_SHAPE;
>> (guess: "fsym->as" is NULL)
> 
> Actually, it's in conv_isocbinding_procedure (which got inlined). The issue
> seems to be that the code assumes that arg->expr->rank != 0 implies that
> arg->expr->symtree->n.sym->as is set. However, the assumption fails for:
>   p = c_loc(tt%t%i(1))
> as "tt" is a scalar.
> 

I'm looking at this.


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

* [Bug fortran/38536] ICE with C_LOC in resolve.c due to not properly going through expr->ref
       [not found] <bug-38536-4@http.gcc.gnu.org/bugzilla/>
                   ` (2 preceding siblings ...)
  2011-01-09 15:38 ` dominiq at lps dot ens.fr
@ 2011-01-09 16:00 ` burnus at gcc dot gnu.org
  2011-01-09 16:00 ` tkoenig at gcc dot gnu.org
                   ` (9 subsequent siblings)
  13 siblings, 0 replies; 26+ messages in thread
From: burnus at gcc dot gnu.org @ 2011-01-09 16:00 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #15 from Tobias Burnus <burnus at gcc dot gnu.org> 2011-01-09 15:33:02 UTC ---
(In reply to comment #13)
> The test case from comment 6 gives an ICE (segfault) in
> gfc_conv_procedure_call's check for
>             && fsym->as->type != AS_ASSUMED_SHAPE;
> (guess: "fsym->as" is NULL)

Actually, it's in conv_isocbinding_procedure (which got inlined). The issue
seems to be that the code assumes that arg->expr->rank != 0 implies that
arg->expr->symtree->n.sym->as is set. However, the assumption fails for:
  p = c_loc(tt%t%i(1))
as "tt" is a scalar.


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

* [Bug fortran/38536] ICE with C_LOC in resolve.c due to not properly going through expr->ref
       [not found] <bug-38536-4@http.gcc.gnu.org/bugzilla/>
                   ` (3 preceding siblings ...)
  2011-01-09 16:00 ` burnus at gcc dot gnu.org
@ 2011-01-09 16:00 ` tkoenig at gcc dot gnu.org
  2011-01-09 16:02 ` tkoenig at netcologne dot de
                   ` (8 subsequent siblings)
  13 siblings, 0 replies; 26+ messages in thread
From: tkoenig at gcc dot gnu.org @ 2011-01-09 16:00 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #16 from Thomas Koenig <tkoenig at gcc dot gnu.org> 2011-01-09 15:37:50 UTC ---
Author: tkoenig
Date: Sun Jan  9 15:37:47 2011
New Revision: 168614

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=168614
Log:
2011-01-09  Thomas Koenig  <tkoenig@gcc.gnu.org>

    PR fortran/38536
    * resolve.c (is_scalar_expr_ptr):  For a substring reference,
    use gfc_dep_compare_expr to compare start and end expession.
    Add FIXME for using gfc_deb_compare_expr elsewhere.

2011-01-09  Thomas Koenig  <tkoenig@gcc.gnu.org>

    PR fortran/38536
    * gfortran.dg/iso_c_binding_c_loc_char_1.f03:  New test.


Added:
    trunk/gcc/testsuite/gfortran.dg/iso_c_binding_c_loc_char_1.f03
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/resolve.c
    trunk/gcc/testsuite/ChangeLog


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

* [Bug fortran/38536] ICE with C_LOC in resolve.c due to not properly going through expr->ref
       [not found] <bug-38536-4@http.gcc.gnu.org/bugzilla/>
  2011-01-09  0:47 ` tkoenig at gcc dot gnu.org
  2011-01-09 15:33 ` burnus at gcc dot gnu.org
@ 2011-01-09 15:38 ` dominiq at lps dot ens.fr
  2011-01-09 16:00 ` burnus at gcc dot gnu.org
                   ` (10 subsequent siblings)
  13 siblings, 0 replies; 26+ messages in thread
From: dominiq at lps dot ens.fr @ 2011-01-09 15:38 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #14 from Dominique d'Humieres <dominiq at lps dot ens.fr> 2011-01-09 15:31:09 UTC ---
> Thomas posted his patch at: http://gcc.gnu.org/ml/fortran/2011-01/msg00067.html

With this patch, the test in comment #6 still gives an ICE: Segmentation fault.
The backtrace is

Program received signal EXC_BAD_ACCESS, Could not access memory.
Reason: KERN_INVALID_ADDRESS at address: 0x0000000000000008
0x00000001000dd18d in gfc_conv_procedure_call (se=0x7fff5fbfd650,
sym=0x141a21640, args=0x141a23000, expr=0x141a24680, append_args=0x0) at
../../work/gcc/fortran/trans-expr.c:2682
2682            && fsym->as->type != AS_ASSUMED_SHAPE;
(gdb) bt
#0  0x00000001000dd18d in gfc_conv_procedure_call (se=0x7fff5fbfd650,
sym=0x141a21640, args=0x141a23000, expr=0x141a24680, append_args=0x0) at
../../work/gcc/fortran/trans-expr.c:2682
#1  0x00000001000de004 in gfc_conv_function_expr (se=0x7fff5fbfd650,
expr=<value temporarily unavailable, due to optimizations>) at
../../work/gcc/fortran/trans-expr.c:4036
Previous frame inner to this frame (gdb could not unwind past this frame)

No further testing yet.


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

* [Bug fortran/38536] ICE with C_LOC in resolve.c due to not properly going through expr->ref
       [not found] <bug-38536-4@http.gcc.gnu.org/bugzilla/>
  2011-01-09  0:47 ` tkoenig at gcc dot gnu.org
@ 2011-01-09 15:33 ` burnus at gcc dot gnu.org
  2011-01-09 15:38 ` dominiq at lps dot ens.fr
                   ` (11 subsequent siblings)
  13 siblings, 0 replies; 26+ messages in thread
From: burnus at gcc dot gnu.org @ 2011-01-09 15:33 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #13 from Tobias Burnus <burnus at gcc dot gnu.org> 2011-01-09 15:21:11 UTC ---
(In reply to comment #10)
> Can this be closed? Is there something left to do here?

The first test case of comment 0 seems to be still unfixed (accepts-invalid -
expected error not printed).


The test case from comment 6 gives an ICE (segfault) in
gfc_conv_procedure_call's check for
          f = (fsym != NULL)
            && !(fsym->attr.pointer || fsym->attr.allocatable)
            && fsym->as->type != AS_ASSUMED_SHAPE;
(guess: "fsym->as" is NULL)


Comment 7 fails - but that's seems to be fixed by the patch of comment 12 (cf.
also below).

 * * *

(In reply to comment #12)
> > Error: CHARACTER argument 'buf' to 'c_loc' at (1) must have a length of 1
> This might be sufficient to fix it.

Thomas posted his patch at: http://gcc.gnu.org/ml/fortran/2011-01/msg00067.html


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

* [Bug fortran/38536] ICE with C_LOC in resolve.c due to not properly going through expr->ref
       [not found] <bug-38536-4@http.gcc.gnu.org/bugzilla/>
@ 2011-01-09  0:47 ` tkoenig at gcc dot gnu.org
  2011-01-09 15:33 ` burnus at gcc dot gnu.org
                   ` (12 subsequent siblings)
  13 siblings, 0 replies; 26+ messages in thread
From: tkoenig at gcc dot gnu.org @ 2011-01-09  0:47 UTC (permalink / raw)
  To: gcc-bugs

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

Thomas Koenig <tkoenig at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |tkoenig at gcc dot gnu.org

--- Comment #12 from Thomas Koenig <tkoenig at gcc dot gnu.org> 2011-01-08 23:35:40 UTC ---
(In reply to comment #11)
> (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

This might be sufficient to fix it.

Index: resolve.c
===================================================================
--- resolve.c   (Revision 168596)
+++ resolve.c   (Arbeitskopie)
@@ -2547,9 +2547,7 @@ is_scalar_expr_ptr (gfc_expr *expr)
       switch (ref->type)
         {
         case REF_SUBSTRING:
-          if (ref->u.ss.length != NULL
-              && ref->u.ss.length->length != NULL
-              && ref->u.ss.start
+          if (ref->u.ss.start
               && ref->u.ss.start->expr_type == EXPR_CONSTANT
               && ref->u.ss.end
               && ref->u.ss.end->expr_type == EXPR_CONSTANT)


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

end of thread, other threads:[~2013-03-25 17:56 UTC | newest]

Thread overview: 26+ 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
     [not found] <bug-38536-4@http.gcc.gnu.org/bugzilla/>
2011-01-09  0:47 ` tkoenig at gcc dot gnu.org
2011-01-09 15:33 ` burnus at gcc dot gnu.org
2011-01-09 15:38 ` dominiq at lps dot ens.fr
2011-01-09 16:00 ` burnus at gcc dot gnu.org
2011-01-09 16:00 ` tkoenig at gcc dot gnu.org
2011-01-09 16:02 ` tkoenig at netcologne dot de
2011-01-13 20:02 ` tkoenig at gcc dot gnu.org
2011-01-14  9:59 ` burnus at gcc dot gnu.org
2011-01-14 19:53 ` tkoenig at gcc dot gnu.org
2011-01-22 19:23 ` tkoenig at gcc dot gnu.org
2011-01-25 16:26 ` burnus at gcc dot gnu.org
2012-08-26  9:14 ` mikael at gcc dot gnu.org
2013-03-25 15:54 ` burnus at gcc dot gnu.org
2013-03-25 17:56 ` burnus at gcc dot gnu.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).