public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/61261] New: [OOP] Segfault on source-allocating polymorphic variables
@ 2014-05-21  1:52 thatcadguy at gmail dot com
  2014-05-21  1:52 ` [Bug fortran/61261] " thatcadguy at gmail dot com
                   ` (7 more replies)
  0 siblings, 8 replies; 9+ messages in thread
From: thatcadguy at gmail dot com @ 2014-05-21  1:52 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=61261

            Bug ID: 61261
           Summary: [OOP] Segfault on source-allocating polymorphic
                    variables
           Product: gcc
           Version: 4.8.2
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
          Assignee: unassigned at gcc dot gnu.org
          Reporter: thatcadguy at gmail dot com

Created attachment 32835
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=32835&action=edit
Test source file

The attached code produces a segfault on Ubuntu 14.04 with gfortran 4.8.2. I
think this may be related to an existing bug, but not sure.

MODULE modu

IMPLICIT NONE

TYPE element
 CLASS(*), ALLOCATABLE :: e
END TYPE element

CONTAINS
 SUBROUTINE sub(el, p)
  TYPE(element), INTENT(INOUT)  :: el
  CLASS(*), POINTER, INTENT(IN) :: p
  ALLOCATE(el%e, SOURCE = p)
 END SUBROUTINE sub
END MODULE modu

PROGRAM x

USE modu
IMPLICIT NONE

CHARACTER(LEN=80), TARGET :: c80
CLASS(*), POINTER :: p
TYPE(element) :: el

c80 = 'the quick brown fox jumps over the lazy dog'
p => c80
CALL  sub(el, p)

END PROGRAM x


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

* [Bug fortran/61261] [OOP] Segfault on source-allocating polymorphic variables
  2014-05-21  1:52 [Bug fortran/61261] New: [OOP] Segfault on source-allocating polymorphic variables thatcadguy at gmail dot com
@ 2014-05-21  1:52 ` thatcadguy at gmail dot com
  2014-05-21  1:53 ` thatcadguy at gmail dot com
                   ` (6 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: thatcadguy at gmail dot com @ 2014-05-21  1:52 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=61261

--- Comment #1 from Jacob Abel <thatcadguy at gmail dot com> ---
Created attachment 32836
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=32836&action=edit
gdb output


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

* [Bug fortran/61261] [OOP] Segfault on source-allocating polymorphic variables
  2014-05-21  1:52 [Bug fortran/61261] New: [OOP] Segfault on source-allocating polymorphic variables thatcadguy at gmail dot com
  2014-05-21  1:52 ` [Bug fortran/61261] " thatcadguy at gmail dot com
@ 2014-05-21  1:53 ` thatcadguy at gmail dot com
  2014-05-21  1:55 ` thatcadguy at gmail dot com
                   ` (5 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: thatcadguy at gmail dot com @ 2014-05-21  1:53 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=61261

--- Comment #2 from Jacob Abel <thatcadguy at gmail dot com> ---
Created attachment 32837
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=32837&action=edit
valgrind output


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

* [Bug fortran/61261] [OOP] Segfault on source-allocating polymorphic variables
  2014-05-21  1:52 [Bug fortran/61261] New: [OOP] Segfault on source-allocating polymorphic variables thatcadguy at gmail dot com
  2014-05-21  1:52 ` [Bug fortran/61261] " thatcadguy at gmail dot com
  2014-05-21  1:53 ` thatcadguy at gmail dot com
@ 2014-05-21  1:55 ` thatcadguy at gmail dot com
  2014-05-21  8:50 ` dominiq at lps dot ens.fr
                   ` (4 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: thatcadguy at gmail dot com @ 2014-05-21  1:55 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=61261

--- Comment #3 from Jacob Abel <thatcadguy at gmail dot com> ---
Created attachment 32838
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=32838&action=edit
gfortran -v


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

* [Bug fortran/61261] [OOP] Segfault on source-allocating polymorphic variables
  2014-05-21  1:52 [Bug fortran/61261] New: [OOP] Segfault on source-allocating polymorphic variables thatcadguy at gmail dot com
                   ` (2 preceding siblings ...)
  2014-05-21  1:55 ` thatcadguy at gmail dot com
@ 2014-05-21  8:50 ` dominiq at lps dot ens.fr
  2014-05-21 15:01 ` thatcadguy at gmail dot com
                   ` (3 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: dominiq at lps dot ens.fr @ 2014-05-21  8:50 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=61261

Dominique d'Humieres <dominiq at lps dot ens.fr> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |NEW
   Last reconfirmed|                            |2014-05-21
                 CC|                            |janus at gcc dot gnu.org
     Ever confirmed|0                           |1

--- Comment #4 from Dominique d'Humieres <dominiq at lps dot ens.fr> ---
Slightly reduced test

MODULE modu

IMPLICIT NONE

TYPE element
 CLASS(*), ALLOCATABLE :: e
END TYPE element

END MODULE modu

PROGRAM x

USE modu
IMPLICIT NONE

CHARACTER(LEN=80), TARGET :: c80
CLASS(*), POINTER :: p
TYPE(element) :: el

c80 = 'the quick brown fox jumps over the lazy dog'
p => c80
  ALLOCATE(el%e, SOURCE = p)

END PROGRAM x

Could be related to pr51864(?).


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

* [Bug fortran/61261] [OOP] Segfault on source-allocating polymorphic variables
  2014-05-21  1:52 [Bug fortran/61261] New: [OOP] Segfault on source-allocating polymorphic variables thatcadguy at gmail dot com
                   ` (3 preceding siblings ...)
  2014-05-21  8:50 ` dominiq at lps dot ens.fr
@ 2014-05-21 15:01 ` thatcadguy at gmail dot com
  2014-05-21 21:18 ` jouko.orava at iki dot fi
                   ` (2 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: thatcadguy at gmail dot com @ 2014-05-21 15:01 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=61261

--- Comment #5 from Jacob Abel <thatcadguy at gmail dot com> ---
(In reply to Dominique d'Humieres from comment #4)
> Slightly reduced test
> 
> MODULE modu
> 
> IMPLICIT NONE
> 
> TYPE element
>  CLASS(*), ALLOCATABLE :: e
> END TYPE element
> 
> END MODULE modu
> 
> PROGRAM x
> 
> USE modu
> IMPLICIT NONE
> 
> CHARACTER(LEN=80), TARGET :: c80
> CLASS(*), POINTER :: p
> TYPE(element) :: el
> 
> c80 = 'the quick brown fox jumps over the lazy dog'
> p => c80
>   ALLOCATE(el%e, SOURCE = p)
> 
> END PROGRAM x
> 
> Could be related to pr51864(?).

Even further works too:

PROGRAM x

IMPLICIT NONE

CLASS(*), ALLOCATABLE :: e
CHARACTER(LEN=80), TARGET :: c80
CLASS(*), POINTER :: p

c80 = 'the quick brown fox jumps over the lazy dog'
p => c80
ALLOCATE(e, SOURCE = p)

END PROGRAM x


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

* [Bug fortran/61261] [OOP] Segfault on source-allocating polymorphic variables
  2014-05-21  1:52 [Bug fortran/61261] New: [OOP] Segfault on source-allocating polymorphic variables thatcadguy at gmail dot com
                   ` (4 preceding siblings ...)
  2014-05-21 15:01 ` thatcadguy at gmail dot com
@ 2014-05-21 21:18 ` jouko.orava at iki dot fi
  2014-12-15 11:41 ` pault at gcc dot gnu.org
  2015-08-07 20:16 ` mikael at gcc dot gnu.org
  7 siblings, 0 replies; 9+ messages in thread
From: jouko.orava at iki dot fi @ 2014-05-21 21:18 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=61261

Jouko Orava <jouko.orava at iki dot fi> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |jouko.orava at iki dot fi

--- Comment #6 from Jouko Orava <jouko.orava at iki dot fi> ---
Confirmed using gfortran 4.8.1 on both x86 (i386) and x86-64 (AMD64).

I suspect the bug is in gcc/fortran/resolve.c:resolve_allocate_expr().
Specifically, that it fails to correctly handle the case where the
allocated object is unlimited polymorphic, and there SOURCE= is
a pointer to a string.

In particular, replacing

    CHARACTER(LEN=80), TARGET :: c80
    c80 = 'the quick brown fox jumps over the lazy dog'
    p => c80

in the example with

    TYPE boxed
        CHARACTER(LEN=80) :: c
    END type boxed
    TYPE(boxed), TARGET :: c
    c%c = 'the quick brown fox jumps over the lazy dog'
    p => c

works. The problem seems to only occur when target is a pointer to
a string (a pointer to a CHARACTER type target).

Unfortunately, I am not familiar enough with the code to discover the
exact problem or fix it.
 _ _ _ _ _

Background and detailed observations:

The root cause of the bug is that the
    ALLOCATE(..., SOURCE=pointer-to-string-target)
expression, where pointer-to-string-target is a pointer to
a target of character type, generates a built-in call to memmove(),
where the length parameter is an uninitialized number taken from stack.

Note, however, that the length used for the allocation itself is correct;
the bug is in initialization, not allocation per se.

This is easy to verify using interpose.c:

    #define _POSIX_C_SOURCE 200112L
    #include <unistd.h>
    #include <stdlib.h>
    #include <stdio.h>
    #include <errno.h>

    static void wrerr(const char *str, const char *const end)
    {
        while (str < end) {
            ssize_t n = write(STDERR_FILENO, str, (size_t)(end - str));
            if (n > (ssize_t)0)
                str += n;
            else
            if (n != (ssize_t)-1 || errno != EINTR)
                return;
        }
    }

    void *malloc(size_t n)
    {
        const size_t size = (n < 16) ? 16 :
                            (n % 16) ? n + 16 - (n % 16) : n;
        void *retval = NULL;
        char msg[128];
        int len, err, saved_errno;

        saved_errno = errno;

        len = snprintf(msg, sizeof msg, "malloc(%lu) = ",
                                        (unsigned long)n);
        if (len > 0 && len < sizeof msg)
            wrerr(msg, msg + len);

        err = posix_memalign(&retval, 16, size);

        len = snprintf(msg, sizeof msg, "%p\n", retval);
        if (len > 0 && len < sizeof msg)
            wrerr(msg, msg + len);

        if (err) {
            errno = err;
            return NULL;
        }

        errno = saved_errno;
        return retval;
    }

    void *memset(void *dest, int c, size_t n)
    {
        unsigned char *const d = dest;
        char msg[128];
        int  len, saved_errno;

        saved_errno = errno;

        len = snprintf(msg, sizeof msg, "memset(%p, %d, %lu) = ",
                       dest, c, (unsigned long)n);
        if (len > 0 && len < sizeof msg)
            wrerr(msg, msg + len);

        while (n-->0)
            d[n] = c;

        len = snprintf(msg, sizeof msg, "%p\n", dest);
        if (len > 0 && len < sizeof msg)
            wrerr(msg, msg + len);

        errno = saved_errno;
        return dest;
    }       

    void *memmove(void *dest, const void *src, size_t n)
    {
        unsigned char *const d = dest;
        const unsigned char *const s = src;
        char msg[128];
        int  len, saved_errno;

        saved_errno = errno;

        if (n >= 3)
            len = snprintf(msg, sizeof msg,
                           "memmove(%p, %p = \"%c%c%c\"..., %lu) = ",
                           dest, src, s[0], s[1], s[2], (unsigned long)n);
        else
            len = snprintf(msg, sizeof msg, "memmove(%p, %p, 0x%lx) =",
                           dest, src, (unsigned long)n);
        if (len > 0 && len < sizeof msg)
            wrerr(msg, msg + len);

        if (dest < src) {
            size_t i;
            for (i = 0; i < n; i++)
                d[i] = s[i];
        } else
        if (dest > src) {
            size_t i = n;
            while (i-->0)
                d[i] = s[i];
        }

        len = snprintf(msg, sizeof msg, "%p\n", dest);
        if (len > 0 && len < sizeof msg)
            wrerr(msg, msg + len);

        errno = saved_errno;
        return dest;
    }

It interposes malloc(), memset(), and memmove() calls.
The function parameters are always printed first to stderr.
After using an inline version of the function (or calling
posix_memalign() for malloc()), the result is printed,
before returning to the caller. Raw unistd.h I/O is used,
to avoid any call loops or other interference.
(It should work with both Fortran and C code.)

Compiling interpose.c and bug-61261.f90 using
    gcc-4.8 -m32 -Wall interpose.c -c
    gfortran-4.8 -m32 -Wall bug-61261.f90 interpose.o -o bug-61261
and running it,
    ./bug-61261
shows that the program dies with SIGSEGV executing
    malloc(80) = 0x88e8dc0
    memset(0x88e8dc0, 0, 80) = 0x88e8dc0
    memmove(0x88e8dc0, 0xff812960 = "the"..., 1768698482) = 

The allocation is of correct size, and it is even cleared
using the correct size, but the memmove() call has an invalid size!

Using a function that fills stack with specific values, e.g.
    SUBROUTINE dummy(value)
        INTEGER, INTENT(IN) :: value
        INTEGER :: x(1000)
        x = value
        WRITE (*,*) "value = ", x(999)
    END SUBROUTINE
and use e.g.
    CALL dummy(51)
    CALL sub(e1, p)
and again compiling with -m32 the interposed output is
    malloc(80) = 0x87c1dc0
    memset(0x87c1dc0, 0, 80) = 0x87c1dc0
    memmove(0x87c1dc0, 0xfff53ef0 = "the"..., 51) = 0x87c1dc0
and the code does not crash anymore.

Changing the dymmy subroutine parameter changes the length in memmove(),
which IMHO proves that it is used from stack, uninitialized.

IMHO, the above shows that for some reason, the length for the SOURCE=
string is used uninitialized from the stack. The length seems to be
correct for the preceding malloc() call, though.

Finally, using a custom type wrapping the string, i.e.
    TYPE custom
        CHARACTER(LEN=80) :: c80
    END TYPE custom
    TYPE(custom), TARGET :: ct
    CLASS(*), POINTER :: p
    TYPE(element) :: el
    ct%c80 = 'the quick brown fox jumps over the lazy dog'
    p => c
    CALL  sub(el, p)
does not crash. However, instead of a memmove() call, a special
__copy_x_Custom function, defined in the vtab for the custom type,
is emitted and used in the binary. (It uses the correct length, too.)

Although I used 32-bit code for the above, the 64-bit results
are similar, except that the length parameter supplied to memmove()
is much more difficult to control; it tends to be equal to the target pointer
value (or in some cases a return address from some previous call).

In summary, ALLOCATE(unlimited-polymorphic-object, SOURCE=string)
allocates the correct size, but initializes the allocated object
using incorrect/undefined/uninitialized length.

Hopefully the above will help one of the gfortran developers
to pinpoint the exact bug, and fix it.

Apologies for the mailing list members for an overlong message.


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

* [Bug fortran/61261] [OOP] Segfault on source-allocating polymorphic variables
  2014-05-21  1:52 [Bug fortran/61261] New: [OOP] Segfault on source-allocating polymorphic variables thatcadguy at gmail dot com
                   ` (5 preceding siblings ...)
  2014-05-21 21:18 ` jouko.orava at iki dot fi
@ 2014-12-15 11:41 ` pault at gcc dot gnu.org
  2015-08-07 20:16 ` mikael at gcc dot gnu.org
  7 siblings, 0 replies; 9+ messages in thread
From: pault at gcc dot gnu.org @ 2014-12-15 11:41 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=61261

Paul Thomas <pault at gcc dot gnu.org> changed:

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

--- Comment #7 from Paul Thomas <pault at gcc dot gnu.org> ---
Dear All,

This is one and the same as the second part of PR55901 and of PR60255. In all
these cases, the unlimited polymorphic entity does not carry a string length
with it. Until this is fixed, there is no hope to have characters work properly
as targets/sources of unlimited polymorphic entities.

Cheers

Paul


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

* [Bug fortran/61261] [OOP] Segfault on source-allocating polymorphic variables
  2014-05-21  1:52 [Bug fortran/61261] New: [OOP] Segfault on source-allocating polymorphic variables thatcadguy at gmail dot com
                   ` (6 preceding siblings ...)
  2014-12-15 11:41 ` pault at gcc dot gnu.org
@ 2015-08-07 20:16 ` mikael at gcc dot gnu.org
  7 siblings, 0 replies; 9+ messages in thread
From: mikael at gcc dot gnu.org @ 2015-08-07 20:16 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=61261

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

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

--- Comment #8 from Mikael Morin <mikael at gcc dot gnu.org> ---
(In reply to Jacob Abel from comment #0)
> Created attachment 32835 [details]
> Test source file
> 
> The attached code produces a segfault on Ubuntu 14.04 with gfortran 4.8.2. I
> think this may be related to an existing bug, but not sure.

No segfault with current trunk.  FIXED?


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

end of thread, other threads:[~2015-08-07 20:16 UTC | newest]

Thread overview: 9+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2014-05-21  1:52 [Bug fortran/61261] New: [OOP] Segfault on source-allocating polymorphic variables thatcadguy at gmail dot com
2014-05-21  1:52 ` [Bug fortran/61261] " thatcadguy at gmail dot com
2014-05-21  1:53 ` thatcadguy at gmail dot com
2014-05-21  1:55 ` thatcadguy at gmail dot com
2014-05-21  8:50 ` dominiq at lps dot ens.fr
2014-05-21 15:01 ` thatcadguy at gmail dot com
2014-05-21 21:18 ` jouko.orava at iki dot fi
2014-12-15 11:41 ` pault at gcc dot gnu.org
2015-08-07 20:16 ` mikael 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).