Skip to content

GitLab

  • Projects
  • Groups
  • Snippets
  • Help
    • Loading...
  • Help
    • Help
    • Support
    • Community forum
    • Submit feedback
  • Sign in / Register
GHC
GHC
  • Project overview
    • Project overview
    • Details
    • Activity
    • Releases
  • Repository
    • Repository
    • Files
    • Commits
    • Branches
    • Tags
    • Contributors
    • Graph
    • Compare
    • Locked Files
  • Issues 4,262
    • Issues 4,262
    • List
    • Boards
    • Labels
    • Service Desk
    • Milestones
    • Iterations
  • Merge Requests 419
    • Merge Requests 419
  • Requirements
    • Requirements
    • List
  • CI / CD
    • CI / CD
    • Pipelines
    • Jobs
    • Schedules
  • Security & Compliance
    • Security & Compliance
    • Dependency List
    • License Compliance
  • Operations
    • Operations
    • Incidents
    • Environments
  • Analytics
    • Analytics
    • CI / CD
    • Code Review
    • Insights
    • Issue
    • Repository
    • Value Stream
  • Wiki
    • Wiki
  • Snippets
    • Snippets
  • Members
    • Members
  • Collapse sidebar
  • Activity
  • Graph
  • Create a new issue
  • Jobs
  • Commits
  • Issue Boards
  • Glasgow Haskell Compiler
  • GHCGHC
  • Issues
  • #6059

Closed
Open
Opened Apr 29, 2012 by guest@trac-guest

FFI: segfault when jumping to code buffer (under certain conditions)

I updated my developing machine from Ubuntu 10.04 LTS to Ubuntu 12.04 LTS (or ghc 6.12.1 to ghc 7.4.1) and I run into a very strange behavior at my currenct project.

After some hours, I reduced it to the following code:

{-# LANGUAGE ForeignFunctionInterface #-}
module Main where

import Data.Word
import Text.Printf
import Foreign

foreign import ccall "dynamic"
   code_void :: FunPtr (IO ()) -> (IO ())

main :: IO ()
main = do
  entryPtr <- (mallocBytes 2)
  poke entryPtr (0xc390 :: Word16) -- nop (0x90); ret(0xc3) (little endian order)

  _ <- printf "entry point: 0x%08x\n" ((fromIntegral $ ptrToIntPtr entryPtr) :: Int)
  _ <- getLine -- for debugging
  code_void $ castPtrToFunPtr entryPtr
  putStrLn "welcome back"

I'm trying to generate some code at run-time, jump to it, and come back again. Using a Makefile, everything is fine:

$ make 
ghc --make -Wall -O2 Main.hs -o stackoverflow_segv
[1 of 1] Compiling Main             ( Main.hs, Main.o )
Linking stackoverflow_segv ...
./stackoverflow_segv
entry point: 0x098d77e0

welcome back

However, if I call the binary directly from the shell:

$ ./stackoverflow_segv 
entry point: 0x092547e0

Segmentation fault (core dumped)

This behavior is reproducible (luckily?).

Using gdb, objdump and /proc I figured out:

$ gdb -q stackoverflow_segv
Reading symbols from /home/lewurm/stackoverflow/stackoverflow_segv...(no debugging symbols found)...done.
(gdb) run
Starting program: /home/lewurm/stackoverflow/stackoverflow_segv
[Thread debugging using libthread_db enabled]
Using host libthread_db library "/lib/i386-linux-gnu/libthread_db.so.1".
entry point: 0x080fc810

before pressing enter, I switch to a second terminal:

$ cat /proc/`pgrep stackoverflow`/maps
[...]
08048000-080ea000 r-xp 00000000 08:01 2492678    /home/lewurm/stackoverflow/stackoverflow_segv
080ea000-080eb000 r--p 000a2000 08:01 2492678    /home/lewurm/stackoverflow/stackoverflow_segv
080eb000-080f1000 rw-p 000a3000 08:01 2492678    /home/lewurm/stackoverflow/stackoverflow_segv
080f1000-08115000 rw-p 00000000 00:00 0          [heap]
[...]

and back again:

<enter>
Program received signal SIGSEGV, Segmentation fault.
0x0804ce3c in s2aV_info ()

Boo. Let's see what this code does:

$ objdump -D stackoverflow_segv | grep -C 3 804ce3c
 804ce31:       89 44 24 4c             mov    %eax,0x4c(%esp)
 804ce35:       83 ec 0c                sub    $0xc,%esp
 804ce38:       8b 44 24 4c             mov    0x4c(%esp),%eax
 804ce3c:       ff d0                   call   *%eax
 804ce3e:       83 c4 0c                add    $0xc,%esp
 804ce41:       83 ec 08                sub    $0x8,%esp
 804ce44:       8b 44 24 54             mov    0x54(%esp),%eax

uhm, jumping to *%eax. What was %eax again?

 (gdb) info reg eax
 eax            0x80fc810        135251984

Well, actually it's just the code buffer. Looking up /proc/*/maps tells us, that this page isn't executeable (rw-p, right?). But, it's the same situation when executing it within make.

What is wrong here?

The code is also available via a gist

First, I posted this issue to stackoverflow, since I wasn't sure what causes this issue and I don't thought it would be a problem with GHC. But (read the comments there please), as it turns out, with older releases of GHC (e.g. 7.2.2) it works for me.

Some Information about the used system:

$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 7.4.1
$ gcc --version
gcc (Ubuntu/Linaro 4.6.3-1ubuntu5) 4.6.3
Copyright (C) 2011 Free Software Foundation, Inc.
This is free software; see the source for copying conditions.  There is NO
warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.

$ make --version
GNU Make 3.81
Copyright (C) 2006  Free Software Foundation, Inc.
This is free software; see the source for copying conditions.
There is NO warranty; not even for MERCHANTABILITY or FITNESS FOR A
PARTICULAR PURPOSE.

This program built for i686-pc-linux-gnu
$ uname -a
Linux matevm-dev 3.2.0-23-generic #36-Ubuntu SMP Tue Apr 10 20:41:14 UTC 2012 i686 athlon i386 GNU/Linux
$ cat /etc/issue
Ubuntu 12.04 LTS \n \l
Trac metadata
Trac field Value
Version 7.4.1
Type Bug
TypeOfFailure OtherFailure
Priority normal
Resolution Unresolved
Component Compiler (FFI)
Test case
Differential revisions
BlockedBy
Related
Blocking
CC lewurm@gmail.com
Operating system
Architecture
Assignee
Assign to
7.6.1
Milestone
7.6.1
Assign milestone
Time tracking
None
Due date
None
Reference: ghc/ghc#6059