[GHC] #7718: ios patch no 8: adjustor pools

#7718: ios patch no 8: adjustor pools ------------------------------+--------------------------------------------- Reporter: StephenBlackheath | Owner: Type: feature request | Status: new Priority: normal | Component: Compiler Version: 7.7 | Keywords: Os: Other | Architecture: arm Failure: None/Unknown | Blockedby: Blocking: | Related: ------------------------------+--------------------------------------------- "Adjustor" is the term used for a C function pointer that allows C code to call back to Haskell. Normally these are generated at runtime. However, the iOS kernel doesn't allow self-modifying code. So, on iOS we use a pool of precompiled adjustors of a fixed size, and this patch is the implementation for that. It consists of three parts: 1. A POOLSIZE pragma, that is used like this: foreign import ccall safe "wrapper" {-# POOLSIZE 100 #-} mkDelegate :: IO () -> IO (FunPtr (IO ())) This patch makes this pragma work on all platforms, but it'll have no effect on platforms other than iOS. I am not sure what the procedure is for additions of pragmas. Do pragmas require {-# LANGUAGE xx #-} ? Anyway, please review whether the approach taken here is acceptable. 2. The Haskell code in the compiler to generate the stubs for the pooled adjustors. 3. The runtime system's implementation of pooled adjustors in C. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7718 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7718: ios patch no 8: adjustor pools ------------------------------+--------------------------------------------- Reporter: StephenBlackheath | Owner: Type: feature request | Status: patch Priority: normal | Component: Compiler Version: 7.7 | Keywords: Os: Other | Architecture: arm Failure: None/Unknown | Blockedby: Blocking: | Related: ------------------------------+--------------------------------------------- Changes (by StephenBlackheath): * status: new => patch -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7718#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7718: ios patch no 8: adjustor pools ------------------------------+--------------------------------------------- Reporter: StephenBlackheath | Owner: Type: feature request | Status: patch Priority: normal | Component: Compiler Version: 7.7 | Keywords: Os: Other | Architecture: arm Failure: None/Unknown | Blockedby: Blocking: 7724 | Related: ------------------------------+--------------------------------------------- Comment(by StephenBlackheath): I'd like to turn the two occurrences of 32 into a global constant called defaultAdjustorPoolCapacity. Where's a suitable place to put that? -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7718#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7718: ios patch no 8: adjustor pools ----------------------------------+----------------------------------------- Reporter: StephenBlackheath | Owner: Type: feature request | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 7.7 Keywords: | Os: Other Architecture: arm | Failure: None/Unknown Difficulty: Unknown | Testcase: Blockedby: | Blocking: 7724 Related: | ----------------------------------+----------------------------------------- Changes (by igloo): * difficulty: => Unknown Comment: If we have to do this, can't we share a single pool between all the wrappers? Then the number of them can be specified as a linker flag. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7718#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7718: ios patch no 8: adjustor pools --------------------------------+------------------------------------------- Reporter: StephenBlackheath | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Os: Other | Architecture: arm Failure: None/Unknown | Difficulty: Unknown Testcase: | Blockedby: Blocking: 7724 | Related: --------------------------------+------------------------------------------- Changes (by StephenBlackheath): * status: patch => new Comment: That would certainly be better and I had talked about it. With your comment I think it is best to do this now. So I'll get right onto developing it. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7718#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7718: ios patch no 8: adjustor pools --------------------------------+------------------------------------------- Reporter: StephenBlackheath | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Os: Other | Architecture: arm Failure: None/Unknown | Difficulty: Unknown Testcase: | Blockedby: Blocking: 7724 | Related: --------------------------------+------------------------------------------- Comment(by simonmar): Are you sure there's no way to do this on iOS? I googled "libffi ios" and there's a port on github that claims to have been merged into upstream libffi: https://github.com/landonf/libffi-ios I'd be surprised if there were no way to do it at all, because we only need the same functionality as dynamically-loaded libraries. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7718#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7718: ios patch no 8: adjustor pools --------------------------------+------------------------------------------- Reporter: StephenBlackheath | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Os: Other | Architecture: arm Failure: None/Unknown | Difficulty: Unknown Testcase: | Blockedby: Blocking: 7724 | Related: --------------------------------+------------------------------------------- Comment(by StephenBlackheath): Thanks, Simon. No I'm not sure. I'll investigate those changes and see if it'll do the trick. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7718#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7718: ios patch no 8: adjustor pools --------------------------------+------------------------------------------- Reporter: StephenBlackheath | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Os: Other | Architecture: arm Failure: None/Unknown | Difficulty: Unknown Testcase: | Blockedby: Blocking: 7724 | Related: --------------------------------+------------------------------------------- Comment(by StephenBlackheath): UPDATE: Those changes were done in Apr 12, 2011 so they're likely to have been integrated, but I haven't checked fully. What I did do was just switch LIBFFI on for iOS and see what it would do. It generated a function pointer pointing to garbage. So this is what I've got to do: 1. Find out why LIBFFI doesn't work. 2. If it really can't be fixed, then finish developing the global adjustor pool. This is the only outstanding work for the iOS cross compiler now. Watch this space. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7718#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7718: ios patch no 8: adjustor pools --------------------------------+------------------------------------------- Reporter: StephenBlackheath | Owner: Type: feature request | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Os: Other | Architecture: arm Failure: None/Unknown | Difficulty: Unknown Testcase: | Blockedby: Blocking: 7724 | Related: --------------------------------+------------------------------------------- Changes (by StephenBlackheath): * status: new => patch Comment: I have got libffi working on iOS now for adjustors, so we don't need the pools any more, which is great news. My work is done now (unless you need something fixed), and it's over to you guys. ----------------- How libffi gets around Apple's restrictions is interesting, and I never would have thought of it. Somehow or other it manages to allocate two adjacent memory pages, setting the second one to be executable and putting some pre-compiled data in it. The executable page then fetches the closure's data with a PC-relative reference of -4096 or so (the page size), so it picks the data out of the writable memory! Mind boggling. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7718#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7718: ios patch no 8: adjustor pools
--------------------------------+-------------------------------------------
Reporter: StephenBlackheath | Owner:
Type: feature request | Status: patch
Priority: normal | Milestone:
Component: Compiler | Version: 7.7
Resolution: | Keywords:
Os: Other | Architecture: arm
Failure: None/Unknown | Difficulty: Unknown
Testcase: | Blockedby:
Blocking: 7724 | Related:
--------------------------------+-------------------------------------------
Comment(by StephenBlackheath):
I forgot to mention that I re-tested this patch on Linux to make sure my
refactoring didn't break it:
{{{
{-# LANGUAGE ForeignFunctionInterface #-}
import Foreign
import Foreign.C
foreign import ccall "wrapper" wrap :: (CInt -> IO CInt) -> IO (FunPtr
(CInt -> IO CInt))
foreign import ccall safe "callme" callme :: (FunPtr (CInt -> IO CInt)) ->
IO ()
main = do
putStrLn "hi"
f <- wrap $ \i -> do
putStrLn $ "haskell got "++show i
return $ i + 1
callme f
freeHaskellFunPtr f
putStrLn "bye"
}}}
{{{
#include

#7718: ios patch no 8: adjustor pools --------------------------------+------------------------------------------- Reporter: StephenBlackheath | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: 7.7 Resolution: | Keywords: Os: Other | Architecture: arm Failure: None/Unknown | Difficulty: Unknown Testcase: | Blockedby: Blocking: 7724 | Related: --------------------------------+------------------------------------------- Changes (by igloo): * milestone: => 7.8.1 -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7718#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7718: ios patch no 8: adjustor pools --------------------------------+------------------------------------------- Reporter: StephenBlackheath | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: 7.7 Resolution: | Keywords: Os: Other | Architecture: arm Failure: None/Unknown | Difficulty: Unknown Testcase: | Blockedby: Blocking: 7724 | Related: --------------------------------+------------------------------------------- Description changed by igloo: Old description:
"Adjustor" is the term used for a C function pointer that allows C code to call back to Haskell. Normally these are generated at runtime.
However, the iOS kernel doesn't allow self-modifying code. So, on iOS we use a pool of precompiled adjustors of a fixed size, and this patch is the implementation for that.
It consists of three parts:
1. A POOLSIZE pragma, that is used like this:
foreign import ccall safe "wrapper" {-# POOLSIZE 100 #-} mkDelegate :: IO () -> IO (FunPtr (IO ()))
This patch makes this pragma work on all platforms, but it'll have no effect on platforms other than iOS.
I am not sure what the procedure is for additions of pragmas. Do pragmas require {-# LANGUAGE xx #-} ? Anyway, please review whether the approach taken here is acceptable.
2. The Haskell code in the compiler to generate the stubs for the pooled adjustors.
3. The runtime system's implementation of pooled adjustors in C.
New description: "Adjustor" is the term used for a C function pointer that allows C code to call back to Haskell. Normally these are generated at runtime. However, the iOS kernel doesn't allow self-modifying code. So, on iOS we use a pool of precompiled adjustors of a fixed size, and this patch is the implementation for that. It consists of three parts: 1. A POOLSIZE pragma, that is used like this: {{{ foreign import ccall safe "wrapper" {-# POOLSIZE 100 #-} mkDelegate :: IO () -> IO (FunPtr (IO ())) }}} This patch makes this pragma work on all platforms, but it'll have no effect on platforms other than iOS. I am not sure what the procedure is for additions of pragmas. Do pragmas require {-# LANGUAGE xx #-} ? Anyway, please review whether the approach taken here is acceptable. 2. The Haskell code in the compiler to generate the stubs for the pooled adjustors. 3. The runtime system's implementation of pooled adjustors in C. -- -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7718#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7718: ios patch no 8: adjustor pools --------------------------------+------------------------------------------- Reporter: StephenBlackheath | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: 7.7 Resolution: | Keywords: Os: Other | Architecture: arm Failure: None/Unknown | Difficulty: Unknown Testcase: | Blockedby: Blocking: 7724 | Related: --------------------------------+------------------------------------------- Comment(by igloo): I'm a little confused still. This change looks good: {{{ - r = ffi_prep_closure(cl, cif, (void*)wptr, hptr/*userdata*/); + r = ffi_prep_closure_loc(cl, cif, (void*)wptr, hptr/*userdata*/, code); }}} (the libffi info page says {{{ You may see old code referring to `ffi_prep_closure'. This function is deprecated, as it cannot handle the need for separate writable and executable addresses. }}} ) but why does the iOS code need to be different to the Linux code? -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7718#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7718: ios patch no 8: adjustor pools
--------------------------------+-------------------------------------------
Reporter: StephenBlackheath | Owner:
Type: feature request | Status: patch
Priority: normal | Milestone: 7.8.1
Component: Compiler | Version: 7.7
Resolution: | Keywords:
Os: Other | Architecture: arm
Failure: None/Unknown | Difficulty: Unknown
Testcase: | Blockedby:
Blocking: 7724 | Related:
--------------------------------+-------------------------------------------
Comment(by ian@…):
commit 310735e7adce0145c653386c21686b4a1b96aea9
{{{
Author: Ian Lynagh

#7718: ios patch no 8: adjustor pools --------------------------------+------------------------------------------- Reporter: StephenBlackheath | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: 7.7 Resolution: | Keywords: Os: Other | Architecture: arm Failure: None/Unknown | Difficulty: Unknown Testcase: | Blockedby: Blocking: 7724 | Related: --------------------------------+------------------------------------------- Comment(by StephenBlackheath): igloo: I think this is correct (this whole business is quite complicated): On most platforms (but not iOS) libffi gives executable and writable pointers that are the same. i386 and x86_64 on all OSes including Linux do their own adjustors (which assume exec & writable are the same). On iOS libffi requires exec & writable pointers to be different and so we need a hash table to associate them. Most platforms do not require this overhead, so I've left them untouched except for abstracting the difference between executable/writable pointers a little bit using an explicit execToWritable() which is a no-op on most platforms. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7718#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7718: ios patch no 8: adjustor pools --------------------------------+------------------------------------------- Reporter: StephenBlackheath | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: 7.7 Resolution: | Keywords: Os: Other | Architecture: arm Failure: None/Unknown | Difficulty: Unknown Testcase: | Blockedby: Blocking: 7724 | Related: --------------------------------+------------------------------------------- Comment(by igloo): Here's the Linux code: {{{ void *allocateExec (W_ bytes, void **exec_ret) { void **ret, **exec; ACQUIRE_SM_LOCK; ret = ffi_closure_alloc (sizeof(void *) + (size_t)bytes, (void**)&exec); RELEASE_SM_LOCK; if (ret == NULL) return ret; *ret = ret; // save the address of the writable mapping, for freeExec(). *exec_ret = exec + 1; return (ret + 1); } }}} Note that it puts the writable address at the start of the memory allocated, so `freeExec` can find it: {{{ void freeExec (void *addr) { void *writable; writable = *((void**)addr - 1); }}} Doesn't this do what you use the hash table for? -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7718#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7718: ios patch no 8: adjustor pools --------------------------------+------------------------------------------- Reporter: StephenBlackheath | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: 7.7 Resolution: | Keywords: Os: Other | Architecture: arm Failure: None/Unknown | Difficulty: Unknown Testcase: | Blockedby: Blocking: 7724 | Related: --------------------------------+------------------------------------------- Comment(by StephenBlackheath): Reminding myself of the reason... I believe I was slightly wrong with what I just said: the 'exec' and 'write' pointer being the same is not the issue. Here's a more accurate explanation: On iOS, ffi_prep_closure_loc must be used to construct the closure (because that is the only way to get around Apple restrictions). It requires the exec and writable pointers to be exactly the ones returned by ffi_closure_alloc. No such limitation exists on Linux because we are creating our own closures. createAdjustor returns only the exec pointer, so this is all that freeExec can receive initially. I can use the same trick as on Linux to go from writable -> exec. However, I can't use the same trick for exec -> writable, because it requires me to write into the memory, and the exec pointer is not writable! Therefore the hash table is the only way. Note that the Linux code writes into the writable pointer and reads from the exec pointer. Therefore they MUST be the same address, or it would not retrieve the same value. The whole business of writing into the pointer and advancing it by one may be totally unnecessary on Linux. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7718#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7718: ios patch no 8: adjustor pools --------------------------------+------------------------------------------- Reporter: StephenBlackheath | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: 7.7 Resolution: | Keywords: Os: Other | Architecture: arm Failure: None/Unknown | Difficulty: Unknown Testcase: | Blockedby: Blocking: 7724 | Related: --------------------------------+------------------------------------------- Comment(by simonmar): Stephen - we do have Linux platforms that return different addresses for exec and writable: SE Linux on Fedora, for example. The two addresses refer to the same memory, which is why you can write to one and read from the other. I haven't looked at your patch in detail, but I am also wondering why we need an extra hash table. When I wrote this code it was intended to support the write and exec addresses being different. We had a bug in this that was discovered recently, see #7629, and with the fix it is working fine. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7718#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7718: ios patch no 8: adjustor pools --------------------------------+------------------------------------------- Reporter: StephenBlackheath | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: 7.7 Resolution: | Keywords: Os: Other | Architecture: arm Failure: None/Unknown | Difficulty: Unknown Testcase: | Blockedby: Blocking: 7724 | Related: --------------------------------+------------------------------------------- Comment(by StephenBlackheath): OK - that explains what I couldn't understand. Take a look at a file called libffi/build/src/arm/ffi.c on line 486: ffi_closure_alloc(). This is inside #if FFI_EXEC_TRAMPOLINE_TABLE which is true on iOS. This is the very clever LIBFFI code to get around Apple's restrictions. On iOS therefore, ffi_closure_alloc() treats the returned void* is a structure of type ffi_closure, stuffing some values into it prior to returning it. In order to allocate memory for associating the writable/exec addresses, our Linux version advances the pointer before returning it. This means that on Linux, the value later passed to ffi_prep_closure_loc() (first argument) is not the same as the one returned by ffi_closure_alloc(). Look at ffi.c again on line 604: ffi_prep_closure_loc(). The passed pointer (first parameter) is assumed to be of type ffi_closure. In the FFI_EXEC_TRAMPOLINE_TABLE implementation ffi_prep_closure_loc() doesn't use the values stuffed in during ffi_closure_alloc(), but the closure code itself uses them. You can see that advancing the pointer before passing it to ffi_prep_closure_loc() (as we do in our Linux implementation) would then violate an important assumption that exists in the FFI_EXEC_TRAMPOLINE_TABLE implementation - that the address returned by ffi_closure_alloc() is the same as the one passed to ffi_prep_closure_loc(). And, indeed when we do this, it crashes. In this implementation, the exec and writable pointers don't refer to the same memory. You can see this on lines 473 and 521. So, this completely rules out the method we use on Linux as I explained previously. I told you it was complicated. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7718#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7718: ios patch no 8: adjustor pools --------------------------------+------------------------------------------- Reporter: StephenBlackheath | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: 7.7 Resolution: | Keywords: Os: Other | Architecture: arm Failure: None/Unknown | Difficulty: Unknown Testcase: | Blockedby: Blocking: 7724 | Related: --------------------------------+------------------------------------------- Comment(by StephenBlackheath): Sorry - that was slightly wrong: It's actually ffi_closure_free() on line 529 that uses trampoline_table and trampoline_table_entry fields stored by ffi_closure_alloc() (line 756), not the closure code. It seems that even though they assume they're using the same structure, ffi_closure_alloc/free() and ffi_prep_closure_loc() could possibly be indepdendent if you make several assumptions about the internal functioning of libffi and allocate two adjacent ffi_closure structures (though the existing Linux implementation would not work). The performance overhead of the hash table seems preferable to the risk of breakage caused by future changes to libffi. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7718#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7718: ios patch no 8: adjustor pools --------------------------------+------------------------------------------- Reporter: StephenBlackheath | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: 7.7 Resolution: | Keywords: Os: Other | Architecture: arm Failure: None/Unknown | Difficulty: Unknown Testcase: | Blockedby: Blocking: 7724 | Related: --------------------------------+------------------------------------------- Comment(by simonmar): Ok, so the ARM version has an assumption that `ffi_closure_alloc()` returns an `ffi_closure*`, which isn't necessarily the case on the other architectures, and in the RTS we're assuming that we can write the memory it returns. Another way to fix this seems to be to require `freeExec()` take the writable address, and make it the caller's responsibility to store the writable address somewhere. When we're using `libffi` we could store the writable address after the `ffi_closure`, for example. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7718#comment:21 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7718: ios patch no 8: adjustor pools --------------------------------+------------------------------------------- Reporter: StephenBlackheath | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: 7.7 Resolution: | Keywords: Os: Other | Architecture: arm Failure: None/Unknown | Difficulty: Unknown Testcase: | Blockedby: Blocking: 7724 | Related: --------------------------------+------------------------------------------- Comment(by StephenBlackheath): It's specifically the iOS version of libffi (not ARM) that has the assumption that ffi_closure_alloc() / ffi_prep_closure_loc() are dealing with a ffi_closure*, and currently the RTS assumes we can do whatever we like with this memory (these two assumptions being incompatible). As you say, if the RTS managed both addresses and was able to pass the write address back to freeExec, we wouldn't need the hash table I put into my ios-patch-8e. The executable pointer is the only one that gets passed to C code when you use a FunPtr through the FFI, though. Even though it would be unusual, it seems that it is possible to pass a FunPtr that originated with a 'foreign import ccall "wrapper"' into C code and back out, and then freeHaskellFunPtr it. If this is so, I can't see how the hash table can be completely avoided. I think it's a reasonable compromise to go with my ios-patch-8e and pay a small performance penalty on freeHaskellFunPtr on iOS only rather than complicating the RTS for the benefit of a single architecture. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7718#comment:22 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7718: ios patch no 8: adjustor pools
--------------------------------+-------------------------------------------
Reporter: StephenBlackheath | Owner:
Type: feature request | Status: patch
Priority: normal | Milestone: 7.8.1
Component: Compiler | Version: 7.7
Resolution: | Keywords:
Os: Other | Architecture: arm
Failure: None/Unknown | Difficulty: Unknown
Testcase: | Blockedby:
Blocking: 7724 | Related:
--------------------------------+-------------------------------------------
Comment(by ian@…):
commit 972c044d5da72cee3a43209ccb41e2229914211c
{{{
Author: Ian Lynagh

#7718: ios patch no 8: adjustor pools --------------------------------+------------------------------------------- Reporter: StephenBlackheath | Owner: Type: feature request | Status: closed Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: 7.7 Resolution: fixed | Keywords: Os: Other | Architecture: arm Failure: None/Unknown | Difficulty: Unknown Testcase: | Blockedby: Blocking: 7724 | Related: --------------------------------+------------------------------------------- Changes (by igloo): * status: patch => closed * resolution: => fixed Comment: OK, thanks Stephen. I've applied a slightly simplified version of the patch. I haven't been able to test on iOS, so please let me know if it doesn't work there. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7718#comment:24 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7718: ios patch no 8: adjustor pools --------------------------------+------------------------------------------- Reporter: StephenBlackheath | Owner: Type: feature request | Status: closed Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: 7.7 Resolution: fixed | Keywords: Os: Other | Architecture: arm Failure: None/Unknown | Difficulty: Unknown Testcase: | Blockedby: Blocking: 7724 | Related: --------------------------------+------------------------------------------- Comment(by StephenBlackheath): Much appreciated. Will re-test. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7718#comment:25 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (2)
-
GHC
-
GHC