[GHC] #9278: GHCi crash:
GHC
ghc-devs at haskell.org
Mon Jul 7 11:36:21 UTC 2014
#9278: GHCi crash:
------------------------------------------+-------------------------------
Reporter: mietek | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: GHCi | Version: 7.6.3
Keywords: crash, dynamic linking | Operating System: MacOS X
Architecture: x86_64 (amd64) | Type of failure: GHCi crash
Difficulty: Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: #9277 |
------------------------------------------+-------------------------------
Given an Objective-C object file referencing a symbol available in a
system framework, interactive GHCi 7.6.3 crashes in an odd fashion.
Start with an Objective-C source file, defining a function to be used via
the FFI:
{{{
$ cat >foo.m <<EOF
#import <Foundation/Foundation.h>
BOOL is_main_thread()
{
return [NSThread isMainThread];
}
EOF
}}}
{{{
$ cat >Main.hs <<EOF
module Main where
foreign import ccall "is_main_thread" isMainThread :: IO Bool
main :: IO ()
main = do
mt <- isMainThread
print mt
EOF
}}}
Non-interactive GHC 7.6.3 works as expected:
{{{
$ clang -c -o foo.o foo.m
}}}
{{{
$ ghc -framework Foundation -o foo foo.o Main.hs
[1 of 1] Compiling Main ( Main.hs, Main.o )
Linking foo ...
}}}
{{{
$ ./foo
True
}}}
Interactive GHCi 7.6.3 crashes:
{{{
$ ghci -framework Foundation foo.o Main.hs
GHCi, version 7.6.3: http://www.haskell.org/ghc/ :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Loading object (static) foo.o ... done
Loading object (framework) Foundation ... done
final link ... done
Ok, modules loaded: Main.
> main
2014-07-07 12:28:21.811 ghc[37395:1103] *** NSForwarding: warning:
selector (0x10ddef328) for message 'isMainThread' does not match selector
known to Objective C runtime (0x7fff8ea15881)-- abort
2014-07-07 12:28:21.813 ghc[37395:1103] +[NSThread isMainThread]:
unrecognized selector sent to class 0x7fff75535280
2014-07-07 12:28:21.814 ghc[37395:1103] *** Terminating app due to
uncaught exception 'NSInvalidArgumentException', reason: '+[NSThread
isMainThread]: unrecognized selector sent to class 0x7fff75535280'
*** First throw call stack:
(
0 CoreFoundation 0x00007fff8bb4825c
__exceptionPreprocess + 172
1 libobjc.A.dylib 0x00007fff85029e75
objc_exception_throw + 43
2 CoreFoundation 0x00007fff8bb4b02d
+[NSObject(NSObject) doesNotRecognizeSelector:] + 205
3 CoreFoundation 0x00007fff8baa6322
___forwarding___ + 1010
4 CoreFoundation 0x00007fff8baa5ea8
_CF_forwarding_prep_0 + 120
5 ??? 0x000000010ddef31a 0x0 +
4527682330
6 ??? 0x000000010ddf02f5 0x0 +
4527686389
)
libc++abi.dylib: terminating with uncaught exception of type NSException
Abort trap: 6
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9278>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list