#5387: ffi/should_run fptr02 fails on OS X amd64
-------------------------------+--------------------------------------------
    Reporter:  igloo           |        Owner:              
        Type:  bug             |       Status:  new         
    Priority:  normal          |    Milestone:              
   Component:  Compiler        |      Version:  7.3         
    Keywords:                  |     Testcase:              
   Blockedby:                  |   Difficulty:              
          Os:  MacOS X         |     Blocking:              
Architecture:  x86_64 (amd64)  |      Failure:  None/Unknown
-------------------------------+--------------------------------------------
 `ffi/should_run fptr02` fails for me on OS X amd64:

 {{{
 {-# LANGUAGE ForeignFunctionInterface #-}

 module Main where

 import Foreign
 import Control.Monad

 foreign import ccall "&free" pfree :: FunPtr (Ptr a -> IO ())

 main = replicateM_ 1000000 $ newForeignPtr pfree nullPtr
 }}}

 {{{
 $ '/Users/ian/ghc/git/val64/inplace/bin/ghc-stage2' -fforce-recomp -dcore-
 lint -dcmm-lint -dno-debug-output -no-user-package-conf -rtsopts  -o
 fptr02 fptr02.hs -debug
 [1 of 1] Compiling Main             ( fptr02.hs, fptr02.o )
 Linking fptr02 ...
 $ gdb fptr02
 GNU gdb 6.3.50-20050815 (Apple version gdb-1515) (Sat Jan 15 08:33:48 UTC
 2011)
 Copyright 2004 Free Software Foundation, Inc.
 GDB is free software, covered by the GNU General Public License, and you
 are
 welcome to change it and/or distribute copies of it under certain
 conditions.
 Type "show copying" to see the conditions.
 There is absolutely no warranty for GDB.  Type "show warranty" for
 details.
 This GDB was configured as "x86_64-apple-darwin"...Reading symbols for
 shared libraries ... done

 (gdb) r +RTS -DS
 Starting program:
 /Users/ian/ghc/git/val64/testsuite/tests/ffi/should_run/fptr02 +RTS -DS
 Reading symbols for shared libraries ++. done
 created capset 0 of type 2
 assigned cap 0 to capset 0

 Program received signal EXC_BAD_ACCESS, Could not access memory.
 Reason: KERN_PROTECTION_FAILURE at address: 0x0000000100b042c0
 0x0000000100b042c0 in ?? ()
 (gdb) bt
 #0  0x0000000100b042c0 in ?? ()
 #1  0x000000010031ba4b in scheduleFinalizers (cap=0x1003cd380,
 list=0x100bfe070) at rts/Weak.c:107
 #2  0x0000000100321926 in GarbageCollect (force_major_gc=rtsFalse,
 do_heap_census=rtsFalse, gc_type=0, cap=0x1003cd380) at rts/sm/GC.c:656
 #3  0x0000000100311a75 in scheduleDoGC (cap=0x1003cd380, task=0x1009003c0,
 force_major=rtsFalse) at rts/Schedule.c:1448
 #4  0x0000000100310c6a in schedule (initialCapability=0x1003cd380,
 task=0x1009003c0) at rts/Schedule.c:547
 #5  0x00000001003122bb in scheduleWaitThread (tso=0x100b05390, ret=0x0,
 cap=0x1003cd380) at rts/Schedule.c:1939
 #6  0x0000000100308d54 in rts_evalLazyIO (cap=0x1003cd380, p=0x100392a30,
 ret=0x0) at rts/RtsAPI.c:494
 #7  0x000000010030b3d0 in real_main () at rts/RtsMain.c:63
 #8  0x000000010030b4c3 in hs_main (argc=3, argv=0x7fff5fbff860,
 main_closure=0x100392a30) at rts/RtsMain.c:111
 #9  0x0000000100001480 in start ()
 (gdb) up
 #1  0x000000010031ba4b in scheduleFinalizers (cap=0x1003cd380,
 list=0x100bfe070) at rts/Weak.c:107
 107                 runCFinalizer((void *)farr->payload[0],
 (gdb) p farr
 $1 = (StgArrWords *) 0x100bd6ae0
 (gdb) p (void *)farr->payload[0]
 $2 = (void *) 0x100b042c0
 (gdb) p4 0x100b042c0
 0x100b042d8:    0xaaaaaaaaaaaaaaaa
 0x100b042d0:    0xaaaaaaaaaaaaaaaa
 0x100b042c8:    0xaaaaaaaaaaaaaaaa
 0x100b042c0:    0xaaaaaaaaaaaaaaaa
 (gdb) p4 0x100bd6ae0
 0x100bd6af8:    0x0
 0x100bd6af0:    0x100b042c0
 0x100bd6ae8:    0x20
 0x100bd6ae0:    0x100337018 <stg_ARR_WORDS_info>
 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5387>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler

_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to