[GHC] #8281: The impossible happened: primRepToFFIType

#8281: The impossible happened: primRepToFFIType -----------------------------------+--------------------------------------- Reporter: tibbe | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time crash Unknown/Multiple | Test Case: Difficulty: Unknown | Blocking: Blocked By: | Related Tickets: | -----------------------------------+--------------------------------------- I ran into this error while trying to use GHCi on the hashable package: {{{ $ cabal repl Preprocessing library hashable-1.2.0.10... GHCi, version 7.6.2: 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 package array-0.4.0.1 ... linking ... done. Loading package deepseq-1.3.0.1 ... linking ... done. Loading package bytestring-0.10.0.2 ... linking ... done. Loading package text-0.11.3.1 ... linking ... done. Loading object (static) dist/build/cbits/fnv.o ... done Loading object (static) dist/build/cbits/getRandomBytes.o ... done final link ... done [1 of 4] Compiling Data.Hashable.RandomSource ( Data/Hashable/RandomSource.hs, interpreted ) [flags changed] [2 of 4] Compiling Data.Hashable.Class ( Data/Hashable/Class.hs, interpreted ) [flags changed] ghc: panic! (the 'impossible' happened) (GHC version 7.6.2 for x86_64-apple-darwin): primRepToFFIType Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8281 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8281: The impossible happened: primRepToFFIType ---------------------------------------+----------------------------------- Reporter: tibbe | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time crash | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: ---------------------------------------+----------------------------------- Comment (by monoidal): Confirmed in HEAD. To reproduce, save this file as Class.hs and run ghci Class (not merely ghc). {{{ {-# LANGUAGE ForeignFunctionInterface, MagicHash, UnliftedFFITypes #-} module Data.Hashable.Class () where import GHC.Prim (ThreadId#) import Foreign.C.Types (CInt(..)) foreign import ccall unsafe "rts_getThreadId" getThreadId :: ThreadId# -> CInt }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8281#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8281: The impossible happened: primRepToFFIType ---------------------------------------+----------------------------------- Reporter: tibbe | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time crash | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: ---------------------------------------+----------------------------------- Changes (by simonpj): * cc: simonmar (added) Comment: I see what is happening here, but need help from Simon M or anyone else. Here's what I learned: * `ThreadId#` is represented by a heap pointer; it's "rep" is `PtrRep`. But it is a primitive type; i.e. not implemented in Haskell. * The totally-undocumented flag `-XUnliftedFFITypes` seems to allow all of GHC's primitive types to be marshalled across the FFI. * These primitive types include `Array#`, `MutableArray#`, `ByteArray#` and `MutableByteArray#`, all of which also have `PtrRep`. * Marshalling these pointer types seems utterly wrong for a '''safe''' call, where GC might occur during the call, thereby moving the array. (Or maybe arrays never move? If so, this is un-documented.) * The actual crash comes in `LibFFI.hsc`, in `primRepToFFIType` which is used (via `prepForeignCall`) only by the bytecode generator, to prepare the foreign call arguments. `primRepToFFIType` barfs if it gets a `PtrRep`. * How does it work for `Array#` and friends? Because have a special shim in `ByteCodeGen.generateCCall`, which adds an offset to get past the array header, and then says `AddrRep`! Hence `primRepToFFIType` sees an `AddrRep`. * There is no such special treatment for `ThreadId#`, hence the crash. * The base-library module `GHC.Conc.Sync` has precisely the `rts_getThreadId` import as in the tiny test case above, but works(just) because it is compiled. My conclusion: * These `PtrRep` things should not be allowed in '''safe''' foreign calls. * In `primRepToFFIType` we should allow `PtrRep` However I'm not certain about the last of these because I don't understand how foreign calls work in the bytecode interpreter. Simon M: do you agree? Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8281#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8281: The impossible happened: primRepToFFIType ---------------------------------------+----------------------------------- Reporter: tibbe | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time crash | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: ---------------------------------------+----------------------------------- Comment (by simonmar): We used to use `UnliftedFFITypes` quite a lot in the IO library in the base package, but I just looked and we use it very little now (only for `ThreadId#`). It does have a brief entry in the flags reference in the user's guide, but no proper documentation. As far as I recall we didn't intend it to be an advertised feature, so I'm not sure why it appears in the docs at all. So what's going wrong here is that we have a foreign call that takes a `ThreadId#`. The foreign call is marked unsafe, because (as you note, Simon) it couldn't work if it was safe. But GHCi only knows how to compile safe foreign calls - it ignores `unsafe` - so there's no way GHCi can compile this code such that it works. What I would like to do is get rid of `UnliftedFFITypes` and use `foreign import prim` instead. The example above is a good use for `foreign import prim`, and indeed we should change `GHC.Conc.Sync` to do it that way (where the example above was copy/pasted from, incidentally). But there are some places where `UnliftedFFITypes` is really useful, e.g.: {{{ foreign import ccall unsafe "memcpy" memcpy_freeze :: MutableByteArray# s -> MutableByteArray# s -> CSize -> IO (Ptr a) }}} from the `array` package. To do this with `foreign import prim` would mean another function call. So I think we have little choice here. - disallow passing boxed-but-unlifted types to safe foreign calls, except for arrays. This error would also trigger in GHCi for an unsafe call, because GHCi compiles unsafe calls as safe calls. Hence the above code would be rejected by GHCi, but accepted by GHC. - document `UnliftedFFITypes`, and explain the pitfalls: not fully supported by GHCi, and be careful passing arrays to `safe` calls (they must be pinned). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8281#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8281: The impossible happened: primRepToFFIType ---------------------------------------+----------------------------------- Reporter: tibbe | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time crash | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: ---------------------------------------+----------------------------------- Comment (by errge): I met this today and came up with the following temporary workaround: {{{#!haskell {-# LANGUAGE MagicHash #-} {-# LANGUAGE UnliftedFFITypes #-} {-# LANGUAGE ForeignFunctionInterface #-} import Control.Concurrent import GHC.Conc.Sync import Foreign.C import GHC.Base foreign import ccall unsafe "rts_getThreadId" getThreadId# :: Addr# -> CInt getThreadId :: ThreadId -> CInt {-# INLINE getThreadId #-} getThreadId (ThreadId tid) = getThreadId# (unsafeCoerce# tid) threadId :: IO Int {-# INLINE threadId #-} threadId = do mtid <- myThreadId return $ fromIntegral $ getThreadId mtid main = do print =<< threadId forkIO $ print =<< threadId threadDelay 10000 }}} Seems to work with ghci and 32/64-bit compiled and 32/64-bit optimized code. Total noob in this area, please tell me if this is dangerous somehow. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8281#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

We used to use `UnliftedFFITypes` quite a lot in the IO library in the
#8281: The impossible happened: primRepToFFIType ---------------------------------------+----------------------------------- Reporter: tibbe | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time crash | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: ---------------------------------------+----------------------------------- Comment (by simonpj): Summary: I think we have a plan but there are niggly details. Help needed from Simon M. Replying to [comment:3 simonmar]: base package, but I just looked and we use it very little now (only for `ThreadId#`). It does have a brief entry in the flags reference in the user's guide, but no proper documentation. As far as I recall we didn't intend it to be an advertised feature, so I'm not sure why it appears in the docs at all. I don't mind it being advertised as dangerous, but whoever ''is'' using it needs to know what the spec it. If the spec isn't in the user manual it should be on the wiki. But in the user manual is better (more findable, more robust), surrounded with caveats perhaps. Ditto `foreign import prim`. This does have a [http://www.haskell.org/ghc/docs/latest/html/users_guide/ffi.html#ffi-prim user manual entry (8.1.3)], but it refers to an unspecified place in the wiki. I believe that the intended documentation is [http://ghc.haskell.org/trac/ghc/wiki/Commentary/PrimOps here], but again I'd prefer the docs to be in the user manual; then it stays with that particular version of the compiler.
What I would like to do is get rid of `UnliftedFFITypes` and use `foreign import prim` instead. The example above is a good use for `foreign import prim`, and indeed we should change `GHC.Conc.Sync` to do it that way (where the example above was copy/pasted from, incidentally).
Why is `foreign import prim` better? The documentation (such as it is) says nothing about how things are marshaled, or what types are legal. Perhaps all types are legal and are passed without any sort of conversion or marshaling. (Eg a `MutableByteArray#` would be passed as a pointer to the array object, not a pointer to the data payload of the object, as happens with `foreign import unsafe`. Is `foreign import prim` by-construction unsafe? That is, it does not generate any save/restore for STG registers etc, and the Cmm code should never block or cause GC. It's just a "fat machine instruction". Is that right? What if you say `foreign import prim safe`? Presumably to make `GHC.Conc.Sync` use `foreign import prim` we'd need to call a function (with a different name) defined in some `.cmm` file, not `rts_getThreadId` defined in `Threads.c`?
But there are some places where `UnliftedFFITypes` is really useful,
e.g.:
{{{ foreign import ccall unsafe "memcpy" memcpy_freeze :: MutableByteArray# s -> MutableByteArray# s -> CSize -> IO (Ptr a) }}}
from the `array` package. To do this with `foreign import prim` would
mean another function call. Not only that, but presumably it is also sometimes convenient to pass an `Int#` because that is what is in your hand, rather than box it up only for the FFI to unbox it? And it's fine to use `Int#` as an argument to a safe foreign call. But this is plain wrong: {{{ foreign import ccall safe f :: ByteArray# -> IO Int }}} It should only work for unsafe. Or are you suggesting that it should be accepted, but may fail badly at runtime if the `ByteArray#` is not pinned, which is not statically checkable? You propose:
- disallow passing boxed-but-unlifted types to safe foreign calls, except for arrays. This error would also trigger in GHCi for an unsafe call, because GHCi compiles unsafe calls as safe calls. Hence the above code would be rejected by GHCi, but accepted by GHC.
Alternatives: * Disallow passing boxed-but-unlifted types to safe foreign calls altogether. If you want to do that, use `foreign import prim` (which is by-construction unsafe). * Disallow passing boxed-but-unlifted types to safe foreign calls, except for arrays (on the grounds that arrays may be pinned). You suggest the latter, but I'd prefer the former, because it's more clear-cut. Moreover the above only covers safe foreign calls. I think the rules for `unsafe` foreign calls should be the same as `foreign import prim`. Do you agree?
- document `UnliftedFFITypes`, and explain the pitfalls: not fully supported by GHCi, and be careful passing arrays to `safe` calls (they must be pinned).
Yes. And document `foreign import prim` better. Plus - Use `foreign import prim` for `rts_getThreadId` in `GHC.Conc.Sync` I'd really like to get this squared away. Simon M: it might be quicker for you to just do this than to explain to me how to do it. Or perhaps you can answer all my stupid questions and someone else can do it. Thanks Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8281#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8281: The impossible happened: primRepToFFIType -------------------------------------+------------------------------------- Reporter: tibbe | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.1 Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: | Architecture: Unknown/Multiple Unknown/Multiple | Difficulty: Unknown Type of failure: Compile- | Blocked By: time crash | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by thomie): * milestone: => 7.10.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8281#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8281: The impossible happened: primRepToFFIType -------------------------------------+------------------------------------- Reporter: tibbe | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by phadej): This happens with 8.0.1-rc1 still. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8281#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8281: The impossible happened: primRepToFFIType -------------------------------------+------------------------------------- Reporter: tibbe | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * priority: normal => high -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8281#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8281: The impossible happened: primRepToFFIType -------------------------------------+------------------------------------- Reporter: tibbe | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): It would be great if someone picked this up. There is helpful diagnosis above, but it does need someone to take a careful look and propose something concrete. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8281#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8281: The impossible happened: primRepToFFIType -------------------------------------+------------------------------------- Reporter: tibbe | Owner: Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.0.1 => 8.2.1 Comment: Not happening for 8.0.1. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8281#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8281: The impossible happened: primRepToFFIType -------------------------------------+------------------------------------- Reporter: tibbe | Owner: Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.2.1 => 8.4.1 Comment: Nor will this happen for 8.2. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8281#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8281: The impossible happened: primRepToFFIType -------------------------------------+------------------------------------- Reporter: tibbe | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by winter): I'd really like to see some documents on how `UnliftedFFITypes` interact with GC and an `unsafe` FFI call. According to my understanding, passing `ByteArray#` is safe here because GC can't happen during an `unsafe` call. Am i right on this? Or perhaps RTS do some thing else to prevent GC move the `ByteArray#` during FFI when `UnliftedFFITypes` enable? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8281#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8281: The impossible happened: primRepToFFIType -------------------------------------+------------------------------------- Reporter: tibbe | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonmar): @winter it's always wrong to pass an unpinned `ByteArray#` to a foreign call, regardless of whether the call is annotated as `safe` or `unsafe`, because GHC is free to implement an `unsafe` call as a `safe` call. Indeed we do this in GHCi. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8281#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8281: The impossible happened: primRepToFFIType -------------------------------------+------------------------------------- Reporter: tibbe | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): Wow, that's news to me! Does that apply to `foreign import prim` as well? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8281#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8281: The impossible happened: primRepToFFIType -------------------------------------+------------------------------------- Reporter: tibbe | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonmar): No, it doesn't apply to `foreign import prim`. Think of `foreign import prim` as declaring a primop: in principle we could implement all our primops using `foreign import prim` (except that we want to optimise by generating code directly for some of them). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8281#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8281: The impossible happened: primRepToFFIType -------------------------------------+------------------------------------- Reporter: tibbe | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by winter): Replying to [comment:15 simonmar]:
@winter it's always wrong to pass an unpinned `ByteArray#` to a foreign call, regardless of whether the call is annotated as `safe` or `unsafe`, because GHC is free to implement an `unsafe` call as a `safe` call. Indeed we do this in GHCi.
But lots of packages(text, for example) seems to be relying on this assumption, as you pointed out, text implemented its copy with FFI memcpy rather than a `copyByteArray#`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8281#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8281: The impossible happened: primRepToFFIType -------------------------------------+------------------------------------- Reporter: tibbe | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): `text` is used nearly everywhere at this point; the fact that it gets this wrong is a rather scary revelation; we really need to make this expectation better known. However, I am a bit worried that the inability to pass `ByteArray#`s to foreign calls may put us in a bit of a pickle performance-wise. For instance, currently `text` uses a C helper, `hs_text_decode_utf8`, to implement equality on `Text` (see `Data.Text.Array.equal`). Not only would it be harder to write the equivalent C-- implementation, but you would also be limited to the optimisation capabilities of the GHC backend, which might hurt for a tight loop such as this. What is the rationale for allowing GHC to implement `unsafe` calls as a `safe` call? It seems like this puts library authors is a tough spot. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8281#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8281: The impossible happened: primRepToFFIType -------------------------------------+------------------------------------- Reporter: tibbe | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonmar): @bgamari I understand the concerns and I agree. To answer your question about the rationale, the idea is that "safe" is the default and "unsafe" relaxes the compiler's obligations only. It doesn't add new obligations (such as the requirement not to interrupt the call with a GC). Implementing that obligation in GHCi might be possible, but we haven't done it. One way around this would be to add a new annotation to foreign calls that requires the call not to be interrupted by GC, e.g. `foreign import unsafenogc ...` or something. This would not be implemented by GHCi (yet?) so compilation would fail if you tried to load text into GHCi. Incidentally it's a bad idea to make one of these calls that might run for an arbitrarily long time, because if a GC strikes everything is blocked until the call returns. This has been a rich source of performance bugs in our system at Facebook. I don't think we've encountered problems with text, but we've had to fix other libraries (e.g. regex-pcre) to turn unsafe calls into safe calls. It's possible that the unsafe calls in Text would cause problems when working with very long strings. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8281#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8281: The impossible happened: primRepToFFIType -------------------------------------+------------------------------------- Reporter: tibbe | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I see that the docmentation on `foreign import unsafe` is thin in the extreme. The [http://downloads.haskell.org/~ghc/master/users-guide/ffi- chap.html user manual section] does not mention `unsafe`; while the [https://www.haskell.org/onlinereport/haskell2010/haskellch8.html#x15-1490008 relevant section of the Haskell 2010 report] has only a single cryptic sentence about "call backs into the Haskell system". It would be good to document it better, perhaps in the user manual. A good example is this thread: can you pass an unpinned bytearry to a foreign call? I don't think we have a shred of documentation about this. At one point we thought of unsafe foreign calls as a "fat machine instruction". GHC's obligations are simpler because GC cannot be invoked by the call, or thread-switching. Nor, I think, should it block (because then GC might happen while it was blocked). So it could be used for things like `cosine` that might be implemented out of line, but morally are like a machine instruction. I think Simon's `unsafenogc` gets closer to the "fat machine instruction" idea. It really must be used only for short-running calls. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8281#comment:21 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8281: The impossible happened: primRepToFFIType -------------------------------------+------------------------------------- Reporter: tibbe | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by winter): This is a very important technique to write high performance array code(we can't put everything related to ByteArray into ghc-prim after all). I'd like to get it fixed in GHCi and document it(include caveats) . what is stopping GHCi supporting unsafe FFI calls? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8281#comment:22 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8281: The impossible happened: primRepToFFIType -------------------------------------+------------------------------------- Reporter: tibbe | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by winter): This is a very important technique to write high performance array code(we can't put everything related to ByteArray into ghc-prim after all). I'd like to get it fixed in GHCi and document it(include caveats) . what is stopping GHCi supporting unsafe FFI calls? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8281#comment:23 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8281: The impossible happened: primRepToFFIType -------------------------------------+------------------------------------- Reporter: tibbe | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari):
what is stopping GHCi supporting unsafe FFI calls?
If I understand Simon correctly, the answer is probably "nothing". However, it's more a question of whether we want to change the semantics of "unsafe" foreign calls (something which would require the involvement of the Haskell Prime committee, if to be done properly). I can see the argument for `unsafe` not placing any new obligations on the compiler and think there's little reason to push for such a change. I do think, however, that it is important that we have a `unsafenogc` call type for the reason you describe. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8281#comment:24 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

what is stopping GHCi supporting unsafe FFI calls?
If I understand Simon correctly, the answer is probably "nothing". However, it's more a question of whether we want to change the semantics of "unsafe" foreign calls (something which would require the involvement of the Haskell Prime committee, if to be done properly). I can see the argument for `unsafe` not placing any new obligations on the compiler and
#8281: The impossible happened: primRepToFFIType -------------------------------------+------------------------------------- Reporter: tibbe | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by winter): Replying to [comment:24 bgamari]: think there's little reason to push for such a change.
I do think, however, that it is important that we have a `unsafenogc`
call type for the reason you describe. That's a reasonable solution. But as simon pointed out, we're too vague on `unsafe` FFI calls before, it's not a big deal to give a more clear semantics, is it? After all we have been relying that semantics for years, it's more costly to add new FFI keyword and change all the libraries. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8281#comment:25 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8281: The impossible happened: primRepToFFIType -------------------------------------+------------------------------------- Reporter: tibbe | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari):
But as simon pointed out, we're too vague on unsafe FFI calls before, it's not a big deal to give a more clear semantics, is it?
I absolutely agree that the documentation should be improved either way. It's possible that #13730 is also being bit by this same confusion. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8281#comment:26 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8281: The impossible happened: primRepToFFIType -------------------------------------+------------------------------------- Reporter: tibbe | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonmar): I suggested to @bgamari today that it might be possible to support `unsafe` foreign calls in GHCi with the same behaviour as compiled code (i.e. no GC during the call guaranteed) by avoiding the `suspendThread()` / `resumeThread()` calls that the interpreter makes in the bci_CCALL byte code implementation. We'd need to include a flag with the byte code to indicate that the call is unsafe, but there's already a flag being passed for interruptible so there's room for another flag in the same word. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8281#comment:27 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8281: The impossible happened: primRepToFFIType -------------------------------------+------------------------------------- Reporter: tibbe | Owner: (none) Type: bug | Status: patch Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3619 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch * differential: => Phab:D3619 Comment: There is a currently-untested patch for this in Phab:D3619. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8281#comment:28 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8281: The impossible happened: primRepToFFIType
-------------------------------------+-------------------------------------
Reporter: tibbe | Owner: (none)
Type: bug | Status: patch
Priority: high | Milestone: 8.4.1
Component: Compiler | Version: 7.6.2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D3619
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#8281: The impossible happened: primRepToFFIType -------------------------------------+------------------------------------- Reporter: tibbe | Owner: (none) Type: bug | Status: patch Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3619 Wiki Page: | -------------------------------------+------------------------------------- Comment (by winter): Thank you! I suggest to add some document in manual as well. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8281#comment:30 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8281: The impossible happened: primRepToFFIType -------------------------------------+------------------------------------- Reporter: tibbe | Owner: (none) Type: bug | Status: patch Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3619 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): How does Phab:D3682 look? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8281#comment:31 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8281: The impossible happened: primRepToFFIType
-------------------------------------+-------------------------------------
Reporter: tibbe | Owner: (none)
Type: bug | Status: patch
Priority: high | Milestone: 8.4.1
Component: Compiler | Version: 7.6.2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D3619
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#8281: The impossible happened: primRepToFFIType -------------------------------------+------------------------------------- Reporter: tibbe | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3619 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => new Comment: The GHCi FFI safety issue has been resolved (for 8.4) with comment:29, but I believe the original issue remains unsolved. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8281#comment:33 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8281: The impossible happened: primRepToFFIType -------------------------------------+------------------------------------- Reporter: tibbe | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3619 Wiki Page: | -------------------------------------+------------------------------------- Comment (by winter):
How does Phab:D3682 look?
It's good, thank you Ben! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8281#comment:34 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8281: The impossible happened: primRepToFFIType -------------------------------------+------------------------------------- Reporter: tibbe | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3619 Wiki Page: | -------------------------------------+------------------------------------- Changes (by angerman): * cc: angerman (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8281#comment:35 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8281: The impossible happened: primRepToFFIType -------------------------------------+------------------------------------- Reporter: tibbe | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.6.1 Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3619 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.4.1 => 8.6.1 Comment: Bumping to 8.6. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8281#comment:36 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8281: The impossible happened: primRepToFFIType -------------------------------------+------------------------------------- Reporter: tibbe | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3619 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * priority: high => normal * milestone: 8.6.1 => Comment: Bumping down in priority and removing milestone as this has been open for several years with no progress. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8281#comment:37 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8281: The impossible happened: primRepToFFIType -------------------------------------+------------------------------------- Reporter: tibbe | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3619 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): The plan: * Work out if and how the issue can now be reproduced * Document `UnliftedFFITypes` -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8281#comment:38 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8281: The impossible happened: primRepToFFIType -------------------------------------+------------------------------------- Reporter: tibbe | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3619 Wiki Page: | -------------------------------------+------------------------------------- Comment (by hvr): Fwiw, re documenting `UnliftedFFITypes` for unpinned `ByteArray#s` I (re)stumbled over this old authoritative sounding email (https://mail.haskell.org/pipermail/haskell-cafe/2014-June/114761.html) from Johan Tibell which stated
There is a way to pass an unpinned `ByteArray#` (or `MutableByteArray#`, but the former seems right in your case) to a foreign call, using the `UnliftedFFITypes` language extension. The `ByteArray#` is **guaranteed to not to be moved for the duration of the call**. The code should treat the `ByteArray#` argument as if it was a pointer to bytes. You will need to do any address offset computations on the C side (i.e. pass any offsets you need as extra argument to your C function).
...which might explain why there's a lot of code out there (including my own) which relies on that guarantee to be upheld (including for `safe` FFI calls). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8281#comment:39 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC