public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/56261] New: seg fault call procedure pointer on polymorphic array
@ 2013-02-08 23:12 abensonca at gmail dot com
  2013-02-08 23:19 ` [Bug fortran/56261] " abensonca at gmail dot com
                   ` (13 more replies)
  0 siblings, 14 replies; 15+ messages in thread
From: abensonca at gmail dot com @ 2013-02-08 23:12 UTC (permalink / raw)
  To: gcc-bugs


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

             Bug #: 56261
           Summary: seg fault call procedure pointer on polymorphic array
    Classification: Unclassified
           Product: gcc
           Version: 4.8.0
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
        AssignedTo: unassigned@gcc.gnu.org
        ReportedBy: abensonca@gmail.com


The following test case causes a seg fault at run time using gfortran 4.8.0 
(r195874):

module t

  type, public :: nc
     character(len=3) :: n
  end type nc

  type, public :: tn
     class(nc), allocatable, dimension(:) :: c
   contains
     procedure :: mapProcPtr  =>  doMapProcPtr
     procedure :: mapExternal =>  doMapExternal
  end type tn

contains

  subroutine doMapProcPtr(self,func)
    implicit none
    class    (tn), intent(inout) :: self       
    procedure(  ), pointer       :: func
    call func(self%c) !! This form causes segfault.                             
!    call ff(self%c)  !! This form works.                                       
    return
  end subroutine doMapProcPtr

  subroutine doMapExternal(self,func)
    implicit none
    class    (tn), intent(inout) :: self       
    external                     :: func
    call func(self%c)
    return
  end subroutine doMapExternal

  subroutine ff(self)
    implicit none
    class(nc), intent(in), dimension(:) :: self

    write (0,*) '  --> in "ff" size of self is ',size(self)
    write (0,*) '  --> content of self(1)%n) is ',self(1)%n
    return
  end subroutine ff

end module t

program p
  use t
  implicit none
  type     (tn)          :: a
  procedure(  ), pointer :: f => ff

  allocate(a%c(10))
  a%c(1)%n='abc'
  write (0,*) 'in "p" size of a%c is ',size(a%c)
  write (0,*) "directly call ff():"
  call ff(a%c)
  ! write (0,*) "call via a%mapExternal(f):" !! Using this version, which 
passes the function to call as an                          
  ! call a%mapExternal(f)                    !! EXTERNAL rather than as a 
procedure pointer also segfaults.                          
  write (0,*) "call via a%mapProcPtr(f):"
  call a%mapProcPtr(f)

end program p


$ gfortran -v
Using built-in specs.
COLLECT_GCC=gfortran
COLLECT_LTO_WRAPPER=/home/abenson/libexec/gcc/x86_64-unknown-linux-
gnu/4.8.0/lto-wrapper
Target: x86_64-unknown-linux-gnu
Configured with: ../gcc-trunk/configure --prefix=/home/abenson --enable-
languages=c,c++,fortran --disable-multilib --with-gmp=/home/abenson
Thread model: posix
gcc version 4.8.0 20130208 (experimental) (GCC) 
$ gfortran -o bug.exe bug.F90
$ bug.exe 
 in "p" size of a%c is           10
 directly call ff():
   --> in "ff" size of self is           10
   --> content of self(1)%n) is abc
 call via a%mapProcPtr(f):
   --> in "ff" size of self is       131154

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

Backtrace for this error:
#0  0x2AE75E9FC387
#1  0x2AE75E9FC99E
#2  0x3D470302CF
#3  0x400BA4 in __t_MOD_ff
#4  0x400DB1 in __t_MOD_domapprocptr
#5  0x401106 in MAIN__ at bug.F90:0
Segmentation fault

The same problem happens if I use an EXTERNAL instead of a procedure pointer, 
but not if I call the subroutine directly.

If "c" in the "tn" type is a instead scalar then this works successfully.

Running this through valgrind I get:

$ valgrind bug.exe
==4488== Memcheck, a memory error detector
==4488== Copyright (C) 2002-2011, and GNU GPL'd, by Julian Seward et al.
==4488== Using Valgrind-3.7.0 and LibVEX; rerun with -h for copyright info
==4488== Command: bug.exe
==4488== 
 in "p" size of a%c is           10
 directly call ff():
   --> in "ff" size of self is           10
   --> content of self(1)%n) is abc
 call via a%mapProcPtr(f):
==4488== Invalid read of size 8
==4488==    at 0x400ADA: __t_MOD_ff (in ./bug.exe)
==4488==    by 0x400DB1: __t_MOD_domapprocptr (in ./bug.exe)
==4488==    by 0x401106: MAIN__ (in ./bug.exe)
==4488==    by 0x401162: main (in ./bug.exe)
==4488==  Address 0x5396368 is 10 bytes after a block of size 30 alloc'd
==4488==    at 0x4A08328: malloc (vg_replace_malloc.c:263)
==4488==    by 0x400E4E: MAIN__ (in ./bug.exe)
==4488==    by 0x401162: main (in ./bug.exe)
==4488== 
==4488== Invalid read of size 8
==4488==    at 0x400ADE: __t_MOD_ff (in ./bug.exe)
==4488==    by 0x400DB1: __t_MOD_domapprocptr (in ./bug.exe)
==4488==    by 0x401106: MAIN__ (in ./bug.exe)
==4488==    by 0x401162: main (in ./bug.exe)
==4488==  Address 0x5396360 is 2 bytes after a block of size 30 alloc'd
==4488==    at 0x4A08328: malloc (vg_replace_malloc.c:263)
==4488==    by 0x400E4E: MAIN__ (in ./bug.exe)
==4488==    by 0x401162: main (in ./bug.exe)
==4488== 
   --> in "ff" size of self is            1
==4488== Invalid read of size 8
==4488==    at 0x400B92: __t_MOD_ff (in ./bug.exe)
==4488==    by 0x400DB1: __t_MOD_domapprocptr (in ./bug.exe)
==4488==    by 0x401106: MAIN__ (in ./bug.exe)
==4488==    by 0x401162: main (in ./bug.exe)
==4488==  Address 0x5396358 is 24 bytes inside a block of size 30 alloc'd
==4488==    at 0x4A08328: malloc (vg_replace_malloc.c:263)
==4488==    by 0x400E4E: MAIN__ (in ./bug.exe)
==4488==    by 0x401162: main (in ./bug.exe)
==4488== 
==4488== Invalid read of size 8
==4488==    at 0x400BA0: __t_MOD_ff (in ./bug.exe)
==4488==    by 0x400DB1: __t_MOD_domapprocptr (in ./bug.exe)
==4488==    by 0x401106: MAIN__ (in ./bug.exe)
==4488==    by 0x401162: main (in ./bug.exe)
==4488==  Address 0x5396370 is not stack'd, malloc'd or (recently) free'd
==4488== 
==4488== Invalid read of size 4
==4488==    at 0x400BA4: __t_MOD_ff (in ./bug.exe)
==4488==    by 0x400DB1: __t_MOD_domapprocptr (in ./bug.exe)
==4488==    by 0x401106: MAIN__ (in ./bug.exe)
==4488==    by 0x401162: main (in ./bug.exe)
==4488==  Address 0x4 is not stack'd, malloc'd or (recently) free'd
==4488== 

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

Backtrace for this error:
#0  0x4C27387
#1  0x4C2799E
#2  0x3D470302CF
#3  0x400BA4 in __t_MOD_ff
#4  0x400DB1 in __t_MOD_domapprocptr
#5  0x401106 in MAIN__ at bug.F90:0
==4488== 
==4488== HEAP SUMMARY:
==4488==     in use at exit: 3,727 bytes in 18 blocks
==4488==   total heap usage: 18 allocs, 0 frees, 3,727 bytes allocated
==4488== 
==4488== LEAK SUMMARY:
==4488==    definitely lost: 0 bytes in 0 blocks
==4488==    indirectly lost: 0 bytes in 0 blocks
==4488==      possibly lost: 0 bytes in 0 blocks
==4488==    still reachable: 3,727 bytes in 18 blocks
==4488==         suppressed: 0 bytes in 0 blocks
==4488== Rerun with --leak-check=full to see details of leaked memory
==4488== 
==4488== For counts of detected and suppressed errors, rerun with: -v
==4488== ERROR SUMMARY: 5 errors from 5 contexts (suppressed: 4 from 4)
Segmentation fault


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

* [Bug fortran/56261] seg fault call procedure pointer on polymorphic array
  2013-02-08 23:12 [Bug fortran/56261] New: seg fault call procedure pointer on polymorphic array abensonca at gmail dot com
@ 2013-02-08 23:19 ` abensonca at gmail dot com
  2013-02-09  9:53 ` [Bug fortran/56261] [OOP] " janus at gcc dot gnu.org
                   ` (12 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: abensonca at gmail dot com @ 2013-02-08 23:19 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #1 from Andrew Benson <abensonca at gmail dot com> 2013-02-08 23:19:11 UTC ---
Reduced test case:

module t

  type, public :: nc
     integer :: n
  end type nc

contains

  subroutine ff(self)
    implicit none
    class(nc), intent(in), dimension(:) :: self

    write (0,*) '  --> content of self(1)%n) is ',self(1)%n
    return
  end subroutine ff

end module t

program p
  use t
  implicit none
  class    (nc), allocatable, dimension(:) :: c
  procedure(  ), pointer                   :: f => ff

  allocate(c(10))
  call f(c)

end program p


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

* [Bug fortran/56261] [OOP] seg fault call procedure pointer on polymorphic array
  2013-02-08 23:12 [Bug fortran/56261] New: seg fault call procedure pointer on polymorphic array abensonca at gmail dot com
  2013-02-08 23:19 ` [Bug fortran/56261] " abensonca at gmail dot com
@ 2013-02-09  9:53 ` janus at gcc dot gnu.org
  2013-02-09 10:03 ` janus at gcc dot gnu.org
                   ` (11 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: janus at gcc dot gnu.org @ 2013-02-09  9:53 UTC (permalink / raw)
  To: gcc-bugs


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

janus at gcc dot gnu.org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
           Keywords|                            |wrong-code
                 CC|                            |janus at gcc dot gnu.org
            Summary|seg fault call procedure    |[OOP] seg fault call
                   |pointer on polymorphic      |procedure pointer on
                   |array                       |polymorphic array

--- Comment #2 from janus at gcc dot gnu.org 2013-02-09 09:52:54 UTC ---
(In reply to comment #1)
>   allocate(c(10))
>   call f(c)

Adding in here a call to "ff(c)", the dump reveals the difference between the
two calls:


  static struct __class_t_Nc_1_0a c = {};
  static void (*<T4f8>) () f = ff;

        [..]
        __builtin_memset (c._data.data, 0, 40);
        c._data.dtype = 297;
        c._data.dim[0].lbound = 1;
        c._data.dim[0].ubound = 10;
        c._data.dim[0].stride = 1;
        c._data.offset = -1;
        (struct __vtype_t_Nc *) c._vptr = &__vtab_t_Nc;

        {
          struct __class_t_Nc_1_0 class.2;

          class.2._data = VIEW_CONVERT_EXPR<struct array1_nc>(c._data);
          class.2._vptr = c._vptr;
          ff (&class.2);
        }

        f ((struct nc[0:] * restrict) c._data.data);


The first part simply sets up the array descriptor for c after the allocation.
Then comes the call to 'ff' (in curly brackets), which is done correctly
(although I'm not quite sure why the temporary 'class.2' is needed). In the
call to 'f', we wrongly pass c._data.data, while we should rather pass 'c' as a
whole (or with a temporary as in the 'ff' case?).


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

* [Bug fortran/56261] [OOP] seg fault call procedure pointer on polymorphic array
  2013-02-08 23:12 [Bug fortran/56261] New: seg fault call procedure pointer on polymorphic array abensonca at gmail dot com
  2013-02-08 23:19 ` [Bug fortran/56261] " abensonca at gmail dot com
  2013-02-09  9:53 ` [Bug fortran/56261] [OOP] " janus at gcc dot gnu.org
@ 2013-02-09 10:03 ` janus at gcc dot gnu.org
  2013-02-09 10:08 ` janus at gcc dot gnu.org
                   ` (10 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: janus at gcc dot gnu.org @ 2013-02-09 10:03 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #3 from janus at gcc dot gnu.org 2013-02-09 10:03:06 UTC ---
Fortunately there is a simple workaround: Declaring the procedure pointer as

  procedure(ff), pointer                   :: f => ff

makes the segfault go away. The call is then done in the same way as the direct
call to 'ff':

        {
          struct __class_t_Nc_1_0 class.2;

          class.2._data = VIEW_CONVERT_EXPR<struct array1_nc>(c._data);
          class.2._vptr = c._vptr;
          f (&class.2);
        }


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

* [Bug fortran/56261] [OOP] seg fault call procedure pointer on polymorphic array
  2013-02-08 23:12 [Bug fortran/56261] New: seg fault call procedure pointer on polymorphic array abensonca at gmail dot com
                   ` (2 preceding siblings ...)
  2013-02-09 10:03 ` janus at gcc dot gnu.org
@ 2013-02-09 10:08 ` janus at gcc dot gnu.org
  2013-02-09 10:17 ` janus at gcc dot gnu.org
                   ` (9 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: janus at gcc dot gnu.org @ 2013-02-09 10:08 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #4 from janus at gcc dot gnu.org 2013-02-09 10:08:23 UTC ---
Actually I wonder whether the test case is really valid. The problem is: When
declaring the procedure pointer without an interface, we don't know which kind
of argument it expects. Here is a slightly modified variant:

module t

  type :: nc
     integer :: n = 1
  end type nc

contains

  subroutine ff(self)
    implicit none
    class(nc), intent(in), dimension(:) :: self
    write (0,*) '  --> content of self(1)%n) is ',self(1)%n
  end subroutine

end module t

program p
  use t
  implicit none
  type    (nc), dimension(1:10) :: c
  procedure(), pointer                   :: f => ff

  call ff(c)
  call f(c)

end program p


As the dump shows, we set up a different array descriptor for both cases, since
we don't know that the procedure pointer expects a polymorphic argument:

  {
    struct array1_nc parm.2;
    struct __class_t_Nc_1_0 class.1;

    class.1._vptr = (struct __vtype_t_Nc * {ref-all}) &__vtab_t_Nc;
    parm.2.dtype = 297;
    parm.2.dim[0].lbound = 1;
    parm.2.dim[0].ubound = 10;
    parm.2.dim[0].stride = 1;
    parm.2.data = (void *) &c[0];
    parm.2.offset = -1;
    class.1._data = parm.2;
    ff (&class.1);
  }
  {
    struct array1_nc parm.3;

    parm.3.dtype = 297;
    parm.3.dim[0].lbound = 1;
    parm.3.dim[0].ubound = 10;
    parm.3.dim[0].stride = 1;
    parm.3.data = (void *) &c[0];
    parm.3.offset = -1;
    f ((struct nc[0:] *) parm.3.data);
  }


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

* [Bug fortran/56261] [OOP] seg fault call procedure pointer on polymorphic array
  2013-02-08 23:12 [Bug fortran/56261] New: seg fault call procedure pointer on polymorphic array abensonca at gmail dot com
                   ` (3 preceding siblings ...)
  2013-02-09 10:08 ` janus at gcc dot gnu.org
@ 2013-02-09 10:17 ` janus at gcc dot gnu.org
  2013-02-09 15:30 ` janus at gcc dot gnu.org
                   ` (8 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: janus at gcc dot gnu.org @ 2013-02-09 10:17 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #5 from janus at gcc dot gnu.org 2013-02-09 10:17:16 UTC ---
One can play the same game with scalars, where the situation is even more
severe:

module t

  type :: nc
     integer :: n = 1
  end type nc

contains

  subroutine ff(self)
    implicit none
    class(nc), intent(in) :: self
    write (0,*) '  --> content of self%n) is ',self%n
  end subroutine

end module t

program p
  use t
  implicit none
  type    (nc) :: c
  procedure(), pointer                   :: f => ff

  call ff(c)
  call f(c)

end program p


The dump shows:

  {
    struct __class_t_Nc class.1;

    class.1._vptr = (struct __vtype_t_Nc * {ref-all}) &__vtab_t_Nc;
    class.1._data = &c;
    ff (&class.1);
  }
  f (&c);

i.e. we set up a polymorphic temporary for the 'ff' call, which we don't do for
'f' since we don't know that it expects a CLASS argument.

Fixing this for the array case would be possible, if we just use the
'polymorphic' version of the array descriptor everywhere.

In the scalar case, we would have to set up a class container, for every call
to a procedure pointer without interface, which is passed a TYPE or CLASS
argument. This would then in turn mean we have to wrap the argument of the
original function 'ff' in a class container, even if it is TYPE. AFAICS, this
could even mean we need an class container (or array descriptor) for *every*
TYPE(t) variable, which would be a rather dramatic change in implementation
(and in principle also affects pure F95 code).

I sincerely hope that all the test cases in this PR are invalud. One should
check the standard!

Btw, do other compilers handle this stuff?


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

* [Bug fortran/56261] [OOP] seg fault call procedure pointer on polymorphic array
  2013-02-08 23:12 [Bug fortran/56261] New: seg fault call procedure pointer on polymorphic array abensonca at gmail dot com
                   ` (4 preceding siblings ...)
  2013-02-09 10:17 ` janus at gcc dot gnu.org
@ 2013-02-09 15:30 ` janus at gcc dot gnu.org
  2013-02-09 15:53 ` janus at gcc dot gnu.org
                   ` (7 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: janus at gcc dot gnu.org @ 2013-02-09 15:30 UTC (permalink / raw)
  To: gcc-bugs


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

janus at gcc dot gnu.org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |NEW
   Last reconfirmed|                            |2013-02-09
     Ever Confirmed|0                           |1

--- Comment #6 from janus at gcc dot gnu.org 2013-02-09 15:30:13 UTC ---
(In reply to comment #5)
> I sincerely hope that all the test cases in this PR are invalud. One should
> check the standard!

Whew, good luck:

F08, chapter 12.4.2.2:
A procedure other than a statement function shall have an explicit interface if
it is referenced and
(1) a reference to the procedure appears
    (a) with an argument keyword (12.5.2), or
    (b) in a context that requires it to be pure,
(2) the procedure has a dummy argument that
    (a) has the ALLOCATABLE, [...] attribute,
    (b) is an assumed-shape array,
    (c) is a coarray,
    (d) is of a parameterized derived type, or
    (e) is polymorphic,


It seems this is not something that the compiler is required to diagnose
(probably because that can be hard or impossible in certain cases), but the
programmer is responsible for checking this.

For comment 1, we should probably throw a warning (at least), but for comment 4
and 5 there is not much we can do, I guess.

In general I would advise against using procedure pointers without interface
(and EXTERNAL declarations), in particular in OOP code (but also in other
cases, because the compiler cannot do any type checking of the arguments, etc).


In summary: All test cases shown here are invalid, the compiler is not strictly
required to detect this, but we should at least throw a warning where possible
(e.g. comment 0 and 1).


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

* [Bug fortran/56261] [OOP] seg fault call procedure pointer on polymorphic array
  2013-02-08 23:12 [Bug fortran/56261] New: seg fault call procedure pointer on polymorphic array abensonca at gmail dot com
                   ` (5 preceding siblings ...)
  2013-02-09 15:30 ` janus at gcc dot gnu.org
@ 2013-02-09 15:53 ` janus at gcc dot gnu.org
  2013-02-09 16:51 ` abensonca at gmail dot com
                   ` (6 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: janus at gcc dot gnu.org @ 2013-02-09 15:53 UTC (permalink / raw)
  To: gcc-bugs


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

janus at gcc dot gnu.org changed:

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

--- Comment #7 from janus at gcc dot gnu.org 2013-02-09 15:52:55 UTC ---
Here is a patch which rejects comment 0 and 1:

Index: gcc/fortran/interface.c
===================================================================
--- gcc/fortran/interface.c    (revision 195915)
+++ gcc/fortran/interface.c    (working copy)
@@ -3202,6 +3202,13 @@ gfc_procedure_use (gfc_symbol *sym, gfc_actual_arg
              "at %L", &a->expr->where);
           return FAILURE;
         }
+
+      if (a->expr && a->expr->ts.type == BT_CLASS)
+        {
+          gfc_error ("Polymorphic argument requires an explicit interface "
+             "at %L", &a->expr->where);
+          return FAILURE;
+        }
     }

       return SUCCESS;


I think it's ok to throw an error (and not just a warning), because a
polymorphic actual arg can only be passed to a polymorphic formal arg, which is
invalid in connection with an implicit interface.


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

* [Bug fortran/56261] [OOP] seg fault call procedure pointer on polymorphic array
  2013-02-08 23:12 [Bug fortran/56261] New: seg fault call procedure pointer on polymorphic array abensonca at gmail dot com
                   ` (6 preceding siblings ...)
  2013-02-09 15:53 ` janus at gcc dot gnu.org
@ 2013-02-09 16:51 ` abensonca at gmail dot com
  2013-02-09 16:59 ` janus at gcc dot gnu.org
                   ` (5 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: abensonca at gmail dot com @ 2013-02-09 16:51 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #8 from Andrew Benson <abensonca at gmail dot com> 2013-02-09 16:50:54 UTC ---
On the test case in comment 2, ifort v11.1 reports:

> ifort -o bug.exe bug.F90 
bug.F90(23): error #6592: This symbol must be a defined parameter, an
enumerator, or an argument of an inquiry function that evaluates to a
compile-time constant.   [FF]
  procedure(  ), pointer                   :: f => ff
---------------------------------------------------^
bug.F90(23): error #6973: This is not a valid initialization expression.   [FF]
  procedure(  ), pointer                   :: f => ff
---------------------------------------------------^
compilation aborted for bug.F90 (code 1)

Same for the scalar case.

Interestingly, the workaround doesn't work under ifort - it seems not to like:

  procedure(ff), pointer :: f => ff

but instead needs:

  procedure(ff), pointer :: f
  f => ff

In fact, if I use:

  procedure(), pointer :: f
  f => ff

then it compiles without any warnings/errors but segfaults at runtime.

With:


  procedure(ff), pointer :: f
  f => ff

it compiles and runs as expected.


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

* [Bug fortran/56261] [OOP] seg fault call procedure pointer on polymorphic array
  2013-02-08 23:12 [Bug fortran/56261] New: seg fault call procedure pointer on polymorphic array abensonca at gmail dot com
                   ` (7 preceding siblings ...)
  2013-02-09 16:51 ` abensonca at gmail dot com
@ 2013-02-09 16:59 ` janus at gcc dot gnu.org
  2013-02-09 17:01 ` abensonca at gmail dot com
                   ` (4 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: janus at gcc dot gnu.org @ 2013-02-09 16:59 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #9 from janus at gcc dot gnu.org 2013-02-09 16:58:54 UTC ---
(In reply to comment #8)
> On the test case in comment 2,

comment 1?


> ifort v11.1 reports:
> 
> > ifort -o bug.exe bug.F90 
> bug.F90(23): error #6592: This symbol must be a defined parameter, an
> enumerator, or an argument of an inquiry function that evaluates to a
> compile-time constant.   [FF]
>   procedure(  ), pointer                   :: f => ff
> ---------------------------------------------------^
> bug.F90(23): error #6973: This is not a valid initialization expression.   [FF]
>   procedure(  ), pointer                   :: f => ff
> ---------------------------------------------------^
> compilation aborted for bug.F90 (code 1)
> 
> Same for the scalar case.

Thanks for checking. Probably ifort does not support pointer initialization yet
(which is a F08 feature).


> Interestingly, the workaround doesn't work under ifort - it seems not to like:
> 
>   procedure(ff), pointer :: f => ff
> 
> but instead needs:
> 
>   procedure(ff), pointer :: f
>   f => ff

Again, pointer initialization.


> In fact, if I use:
> 
>   procedure(), pointer :: f
>   f => ff
> 
> then it compiles without any warnings/errors but segfaults at runtime.
> 
> With:
> 
> 
>   procedure(ff), pointer :: f
>   f => ff
> 
> it compiles and runs as expected.

Good, that's compatible with gfortran's behavior (which is fine, since the test
case is invalid). Apparently ifort also lacks diagnostics for this.


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

* [Bug fortran/56261] [OOP] seg fault call procedure pointer on polymorphic array
  2013-02-08 23:12 [Bug fortran/56261] New: seg fault call procedure pointer on polymorphic array abensonca at gmail dot com
                   ` (8 preceding siblings ...)
  2013-02-09 16:59 ` janus at gcc dot gnu.org
@ 2013-02-09 17:01 ` abensonca at gmail dot com
  2013-02-09 17:06 ` abensonca at gmail dot com
                   ` (3 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: abensonca at gmail dot com @ 2013-02-09 17:01 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #10 from Andrew Benson <abensonca at gmail dot com> 2013-02-09 17:01:22 UTC ---
You're right - comment 1.


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

* [Bug fortran/56261] [OOP] seg fault call procedure pointer on polymorphic array
  2013-02-08 23:12 [Bug fortran/56261] New: seg fault call procedure pointer on polymorphic array abensonca at gmail dot com
                   ` (9 preceding siblings ...)
  2013-02-09 17:01 ` abensonca at gmail dot com
@ 2013-02-09 17:06 ` abensonca at gmail dot com
  2013-02-09 18:25 ` janus at gcc dot gnu.org
                   ` (2 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: abensonca at gmail dot com @ 2013-02-09 17:06 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #11 from Andrew Benson <abensonca at gmail dot com> 2013-02-09 17:06:18 UTC ---
Thanks for figuring out the problem here. When I specify an interface for the
procedure pointer in the original code that I derived the test case from,
everything works OK.


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

* [Bug fortran/56261] [OOP] seg fault call procedure pointer on polymorphic array
  2013-02-08 23:12 [Bug fortran/56261] New: seg fault call procedure pointer on polymorphic array abensonca at gmail dot com
                   ` (10 preceding siblings ...)
  2013-02-09 17:06 ` abensonca at gmail dot com
@ 2013-02-09 18:25 ` janus at gcc dot gnu.org
  2013-04-08  8:11 ` burnus at gcc dot gnu.org
  2013-04-12 14:32 ` janus at gcc dot gnu.org
  13 siblings, 0 replies; 15+ messages in thread
From: janus at gcc dot gnu.org @ 2013-02-09 18:25 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #12 from janus at gcc dot gnu.org 2013-02-09 18:25:33 UTC ---
I just noticed that there is already related diagnostics in resolve.c
(resolve_global_procedure):

        /* F2003, 12.3.1.1 (2d); F2008, 12.4.2.2 (2e)   */
        else if (arg->sym->ts.type == BT_CLASS)
          {
        gfc_error ("Procedure '%s' at %L with polymorphic dummy "
               "argument '%s' must have an explicit interface",
               sym->name, &sym->declared_at, arg->sym->name);
        break;
          }

As a consequnce, whole_file_20.f03 now fails (due to a double error message).

Further, abstract_type_6.f03 fails, which is fixed by this:

Index: abstract_type_6.f03
===================================================================
--- abstract_type_6.f03 (revision 195915)
+++ abstract_type_6.f03 (working copy)
@@ -46,7 +46,7 @@

 SUBROUTINE bottom_c(obj)
    CLASS(Bottom) :: obj
-   CALL top_c(obj)
+   CALL top_c(obj)   ! { dg-error "requires an explicit interface" }
    ! other stuff
 END SUBROUTINE bottom_c 
 end module


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

* [Bug fortran/56261] [OOP] seg fault call procedure pointer on polymorphic array
  2013-02-08 23:12 [Bug fortran/56261] New: seg fault call procedure pointer on polymorphic array abensonca at gmail dot com
                   ` (11 preceding siblings ...)
  2013-02-09 18:25 ` janus at gcc dot gnu.org
@ 2013-04-08  8:11 ` burnus at gcc dot gnu.org
  2013-04-12 14:32 ` janus at gcc dot gnu.org
  13 siblings, 0 replies; 15+ messages in thread
From: burnus at gcc dot gnu.org @ 2013-04-08  8:11 UTC (permalink / raw)
  To: gcc-bugs


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

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

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

--- Comment #13 from Tobias Burnus <burnus at gcc dot gnu.org> 2013-04-08 08:11:44 UTC ---
(See also thread ending with
http://gcc.gnu.org/ml/fortran/2013-04/msg00048.html)

Regarding comment 1, using

  procedure(  ), pointer :: f => ff

as well as something like

  external :: ggg
  procedure(ff), pointer :: f => ggg

is invalid as "ff" has a class dummy argument, which mandates an explicit
interface (F2008, 12.4.2.2, (2)(a); cf. comment 6) and Fortran 2008 demands:

"If the characteristics of the pointer object or the pointer target are such
that an explicit interface is required, both the pointer object and the pointer
target shall have an explicit interface." (para 4 of "7.2.2.4 Procedure pointer
assignment")


[Those aren't constraints, hence, the compiler is not required to diagnose it -
nor can it do so in general. However, if the explicit interface of "ff" is
available, as comment 1, it can. Thus, a diagnostic would be nice.]


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

* [Bug fortran/56261] [OOP] seg fault call procedure pointer on polymorphic array
  2013-02-08 23:12 [Bug fortran/56261] New: seg fault call procedure pointer on polymorphic array abensonca at gmail dot com
                   ` (12 preceding siblings ...)
  2013-04-08  8:11 ` burnus at gcc dot gnu.org
@ 2013-04-12 14:32 ` janus at gcc dot gnu.org
  13 siblings, 0 replies; 15+ messages in thread
From: janus at gcc dot gnu.org @ 2013-04-12 14:32 UTC (permalink / raw)
  To: gcc-bugs


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

janus at gcc dot gnu.org changed:

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

--- Comment #14 from janus at gcc dot gnu.org 2013-04-12 14:32:30 UTC ---
Fixed with r197922, which rejects the test cases in comment 0 and 1:

http://gcc.gnu.org/viewcvs/gcc?view=revision&revision=197922


Author:     janus
Date:     Fri Apr 12 14:21:39 2013 UTC
Changed paths:     23
Log Message:     

2013-04-12  Janus Weil  <janus@gcc.gnu.org>

    PR fortran/56261
    * gfortran.h (gfc_explicit_interface_required): New prototype.
    * expr.c (gfc_check_pointer_assign): Check if an explicit interface is
    required in a proc-ptr assignment.
    * interface.c (check_result_characteristics): Extra check.
    * resolve.c (gfc_explicit_interface_required): New function.
    (resolve_global_procedure): Use new function
    'gfc_explicit_interface_required'. Do a full interface check.


2013-04-12  Janus Weil  <janus@gcc.gnu.org>

    PR fortran/56261
    * gfortran.dg/auto_char_len_4.f90: Add -pedantic. Changed error.
    * gfortran.dg/assumed_rank_4.f90: Modified error wording.
    * gfortran.dg/block_11.f90: Fix invalid test case.
    * gfortran.dg/function_types_3.f90: Add new error message.
    * gfortran.dg/global_references_1.f90: Ditto.
    * gfortran.dg/import2.f90: Remove unneeded parts.
    * gfortran.dg/import6.f90: Fix invalid test case.
    * gfortran.dg/proc_decl_2.f90: Ditto.
    * gfortran.dg/proc_decl_9.f90: Ditto.
    * gfortran.dg/proc_decl_18.f90: Ditto.
    * gfortran.dg/proc_ptr_40.f90: New.
    * gfortran.dg/whole_file_7.f90: Modified error wording.
    * gfortran.dg/whole_file_16.f90: Ditto.
    * gfortran.dg/whole_file_17.f90: Add -pedantic.
    * gfortran.dg/whole_file_18.f90: Modified error wording.
    * gfortran.dg/whole_file_20.f03: Ditto.
    * gfortran.fortran-torture/execute/intrinsic_associated.f90: Fix
    invalid test case.


Closing as fixed. Thanks for the report.


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

end of thread, other threads:[~2013-04-12 14:32 UTC | newest]

Thread overview: 15+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2013-02-08 23:12 [Bug fortran/56261] New: seg fault call procedure pointer on polymorphic array abensonca at gmail dot com
2013-02-08 23:19 ` [Bug fortran/56261] " abensonca at gmail dot com
2013-02-09  9:53 ` [Bug fortran/56261] [OOP] " janus at gcc dot gnu.org
2013-02-09 10:03 ` janus at gcc dot gnu.org
2013-02-09 10:08 ` janus at gcc dot gnu.org
2013-02-09 10:17 ` janus at gcc dot gnu.org
2013-02-09 15:30 ` janus at gcc dot gnu.org
2013-02-09 15:53 ` janus at gcc dot gnu.org
2013-02-09 16:51 ` abensonca at gmail dot com
2013-02-09 16:59 ` janus at gcc dot gnu.org
2013-02-09 17:01 ` abensonca at gmail dot com
2013-02-09 17:06 ` abensonca at gmail dot com
2013-02-09 18:25 ` janus at gcc dot gnu.org
2013-04-08  8:11 ` burnus at gcc dot gnu.org
2013-04-12 14:32 ` janus 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).