[GHC] #8684: hWaitForInput cannot be interrupted by async exceptions on unix

#8684: hWaitForInput cannot be interrupted by async exceptions on unix ------------------------------------+------------------------------------- Reporter: nh2 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.6.3 Keywords: | Operating System: Unknown/Multiple Architecture: Unknown/Multiple | Type of failure: None/Unknown Difficulty: Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | ------------------------------------+------------------------------------- http://hackage.haskell.org/package/base-4.6.0.1/docs/System-Timeout.html claims that {{{timeout}}} can interrupt {{{hWaitForInput}}}, but in fact that's false (e.g. mentioned in https://ghc.haskell.org/trac/ghc/ticket/7353#comment:4). {{{ -- import Control.Concurrent import System.IO import System.Timeout main = timeout (1 * 1000000) $ hWaitForInput stdin (5 * 1000) }}} will not be killed after 1 second, but instead wait for the full 5 seconds timeout passed to {{{hWaitForInput}}}. The implementation is {{{ready}}} at http://www.haskell.org/ghc/docs/latest/html/libraries/base/src/GHC-IO- FD.html, where we have two foreign calls: {{{safe fdReady}}} and {{{unsafe unsafe_fdReady}}}. The actual C implementation is at https://github.com/haskell- suite/base/blob/master/cbits/inputReady.c#L16. It uses {{{select}}} on Unix, and does check for {{{EINTR}}}, so I believe that according to http://www.haskell.org/ghc/docs/7.6.3/html/users_guide/ffi.html#ffi- interruptible both foreign calls can be replaced by a single {{{interruptible}}} one. Is that true? If not, it's a documentation bug in {{{timeout}}} at least. Also, does {{{interruptible}}}, apart from allowing the function to be interrupted, behave more like {{{safe}}} or {{{unsafe}}}? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8684 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8684: hWaitForInput cannot be interrupted by async exceptions on unix -------------------------------------+------------------------------------ Reporter: nh2 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by ezyang): Replying to [ticket:8684 nh2]:
Is that true?
This would work fine for Unix. It would be good to test if it does the right thing with CancelSynchronousIO as well.
Also, does {{{interruptible}}}, apart from allowing the function to be interrupted, behave more like {{{safe}}} or {{{unsafe}}}?
Interruptible acts like {{{safe}}}, except for the extra signal throwing behavior. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8684#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8684: hWaitForInput cannot be interrupted by async exceptions on unix -------------------------------------+------------------------------------ Reporter: nh2 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by nh2): Replying to [comment:1 ezyang]:
This would work fine for Unix. It would be good to test if it does the right thing with CancelSynchronousIO as well.
Ah, great. I guess we should update the documentation until this is actually implemented. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8684#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8684: hWaitForInput cannot be interrupted by async exceptions on unix -------------------------------------+------------------------------------ Reporter: nh2 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by lnandor): I have tried to fix the bug by replacing select with pselect to ignore the SIGVTALRM signal sent by the runtime, but to properly terminate when SIGPIPE is received. [https://github.com/nandor/packages-base/compare/fix-8684?expand=1] {{{ diff --git a/GHC/IO/FD.hs b/GHC/IO/FD.hs index 2023526..0b0b1de 100644 --- a/GHC/IO/FD.hs +++ b/GHC/IO/FD.hs @@ -3,6 +3,7 @@ , NoImplicitPrelude , BangPatterns , DeriveDataTypeable + , InterruptibleFFI #-} {-# OPTIONS_GHC -fno-warn-identities #-} -- Whether there are identities depends on the platform @@ -395,7 +396,7 @@ setNonBlockingMode fd set = do ready :: FD -> Bool -> Int -> IO Bool ready fd write msecs = do - r <- throwErrnoIfMinus1Retry "GHC.IO.FD.ready" $ + r <- throwErrnoIfMinus1 "GHC.IO.FD.ready" $ fdReady (fdFD fd) (fromIntegral $ fromEnum $ write) (fromIntegral msecs) #if defined(mingw32_HOST_OS) @@ -405,7 +406,7 @@ ready fd write msecs = do #endif return (toEnum (fromIntegral r)) -foreign import ccall safe "fdReady" +foreign import ccall interruptible "fdReady" fdReady :: CInt -> CInt -> CInt -> CInt -> IO CInt -- --------------------------------------------------------------------------- @@ -502,7 +503,7 @@ indicates that there's no data, we call threadWaitRead. readRawBufferPtr :: String -> FD -> Ptr Word8 -> Int -> CSize -> IO Int readRawBufferPtr loc !fd buf off len | isNonBlocking fd = unsafe_read -- unsafe is ok, it can't block - | otherwise = do r <- throwErrnoIfMinus1 loc + | otherwise = do r <- throwErrnoIfMinus1Retry loc (unsafe_fdReady (fdFD fd) 0 0 0) if r /= 0 then read diff --git a/GHC/IO/Handle/Text.hs b/GHC/IO/Handle/Text.hs index f182e7f..31f2cac 100644 --- a/GHC/IO/Handle/Text.hs +++ b/GHC/IO/Handle/Text.hs @@ -106,7 +106,6 @@ hWaitForInput h msecs = do writeIORef haCharBuffer cbuf' if not (isEmptyBuffer cbuf') then return True else do - r <- IODevice.ready haDevice False{-read-} msecs if r then do -- Call hLookAhead' to throw an EOF -- exception if appropriate diff --git a/cbits/inputReady.c b/cbits/inputReady.c index 51f278f..9d51750 100644 --- a/cbits/inputReady.c +++ b/cbits/inputReady.c @@ -22,9 +22,10 @@ fdReady(int fd, int write, int msecs, int isSock) #else ( 1 ) { #endif - int maxfd, ready; + int maxfd; fd_set rfd, wfd; - struct timeval tv; + struct timespec tv; + sigset_t set; FD_ZERO(&rfd); FD_ZERO(&wfd); @@ -39,16 +40,14 @@ fdReady(int fd, int write, int msecs, int isSock) */ maxfd = fd + 1; tv.tv_sec = msecs / 1000; - tv.tv_usec = (msecs % 1000) * 1000; + tv.tv_nsec = (msecs % 1000) * 1000000; - while ((ready = select(maxfd, &rfd, &wfd, NULL, &tv)) < 0 ) { - if (errno != EINTR ) { - return -1; - } - } + /* Block SIGVTALRM */ + sigprocmask(SIG_BLOCK, NULL, &set); + sigaddset(&set, SIGVTALRM); /* 1 => Input ready, 0 => not ready, -1 => error */ - return (ready); + return pselect(maxfd, &rfd, &wfd, NULL, &tv, &set); } #if defined(_MSC_VER) || defined(__MINGW32__) || defined(_WIN32) else { }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8684#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8684: hWaitForInput cannot be interrupted by async exceptions on unix -------------------------------------+------------------------------------ Reporter: nh2 | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: libraries/base | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Changes (by nh2): * status: new => patch -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8684#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8684: hWaitForInput cannot be interrupted by async exceptions on unix -------------------------------------+------------------------------------- Reporter: nh2 | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: | Version: 7.6.3 libraries/base | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: | Blocking: | Differential Revisions: Phab:D42 | -------------------------------------+------------------------------------- Changes (by thoughtpolice): * cc: hvr, ekmett (added) * differential: => Phab:D42 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8684#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8684: hWaitForInput cannot be interrupted by async exceptions on unix -------------------------------------+------------------------------------- Reporter: nh2 | Owner: snoyberg Type: bug | Status: patch Priority: normal | Milestone: Component: Core Libraries | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D42 -------------------------------------+------------------------------------- Changes (by snoyberg): * cc: core-libraries-committee@… (added) * owner: => snoyberg -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8684#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8684: hWaitForInput cannot be interrupted by async exceptions on unix -------------------------------------+------------------------------------- Reporter: nh2 | Owner: snoyberg Type: bug | Status: patch Priority: normal | Milestone: Component: Core Libraries | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D42 Wiki Page: | -------------------------------------+------------------------------------- Comment (by nh2): Ai, it seems that ghc 8.0.2 changed some behaviour here: {{{ import System.IO import System.Timeout main = hWaitForInput stdin (5 * 1000) }}} On ghc 8.0.2, this crashes with `fdReady: msecs != 0, this shouldn't happen`. On ghc 8.0.1, this works as expected (doing nothing, terminating after 5 seconds). Probably this commit: https://github.com/ghc/ghc/commit/f46369b8a1bf90a3bdc30f2b566c3a7e03672518 #diff-f727d72230bd33b0e218d47df4738565R28 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8684#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8684: hWaitForInput cannot be interrupted by async exceptions on unix -------------------------------------+------------------------------------- Reporter: nh2 | Owner: snoyberg Type: bug | Status: patch Priority: normal | Milestone: Component: Core Libraries | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D42 Wiki Page: | -------------------------------------+------------------------------------- Description changed by nh2: Old description:
http://hackage.haskell.org/package/base-4.6.0.1/docs/System-Timeout.html
claims that {{{timeout}}} can interrupt {{{hWaitForInput}}}, but in fact that's false (e.g. mentioned in https://ghc.haskell.org/trac/ghc/ticket/7353#comment:4).
{{{ -- import Control.Concurrent import System.IO import System.Timeout
main = timeout (1 * 1000000) $ hWaitForInput stdin (5 * 1000) }}}
will not be killed after 1 second, but instead wait for the full 5 seconds timeout passed to {{{hWaitForInput}}}.
The implementation is {{{ready}}} at http://www.haskell.org/ghc/docs/latest/html/libraries/base/src/GHC-IO- FD.html, where we have two foreign calls: {{{safe fdReady}}} and {{{unsafe unsafe_fdReady}}}.
The actual C implementation is at https://github.com/haskell- suite/base/blob/master/cbits/inputReady.c#L16. It uses {{{select}}} on Unix, and does check for {{{EINTR}}}, so I believe that according to http://www.haskell.org/ghc/docs/7.6.3/html/users_guide/ffi.html#ffi- interruptible both foreign calls can be replaced by a single {{{interruptible}}} one.
Is that true?
If not, it's a documentation bug in {{{timeout}}} at least.
Also, does {{{interruptible}}}, apart from allowing the function to be interrupted, behave more like {{{safe}}} or {{{unsafe}}}?
New description: http://hackage.haskell.org/package/base-4.6.0.1/docs/System-Timeout.html claims that {{{timeout}}} can interrupt {{{hWaitForInput}}}, but in fact that's false (e.g. mentioned in https://ghc.haskell.org/trac/ghc/ticket/7353#comment:4). {{{ -- import Control.Concurrent import System.IO import System.Timeout main = timeout (1 * 1000000) $ hWaitForInput stdin (5 * 1000) }}} will not be killed after 1 second, but instead wait for the full 5 seconds timeout passed to {{{hWaitForInput}}}. The implementation is {{{ready}}} at https://downloads.haskell.org/~ghc/7.6.3/docs/html/libraries/base/src/GHC- IO-FD.html, where we have two foreign calls: {{{safe fdReady}}} and {{{unsafe unsafe_fdReady}}}. The actual C implementation is at https://github.com/ghc/packages- base/blob/52c0b09036c36f1ed928663abb2f295fd36a88bb/cbits/inputReady.c#L16. It uses {{{select}}} on Unix, and does check for {{{EINTR}}}, so I believe that according to http://www.haskell.org/ghc/docs/7.6.3/html/users_guide/ffi.html#ffi- interruptible both foreign calls can be replaced by a single {{{interruptible}}} one. Is that true? If not, it's a documentation bug in {{{timeout}}} at least. Also, does {{{interruptible}}}, apart from allowing the function to be interrupted, behave more like {{{safe}}} or {{{unsafe}}}? -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8684#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8684: hWaitForInput cannot be interrupted by async exceptions on unix
-------------------------------------+-------------------------------------
Reporter: nh2 | Owner: snoyberg
Type: bug | Status: patch
Priority: normal | Milestone:
Component: Core Libraries | Version: 7.6.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D42
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#8684: hWaitForInput cannot be interrupted by async exceptions on unix -------------------------------------+------------------------------------- Reporter: nh2 | Owner: snoyberg Type: bug | Status: patch Priority: normal | Milestone: Component: Core Libraries | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D42 Wiki Page: | -------------------------------------+------------------------------------- Comment (by nh2): Replying to [comment:8 nh2]:
On ghc 8.0.2, this crashes with `fdReady: msecs != 0, this shouldn't happen`.
This is fixed for GHC 8.2 per #13525 (https://phabricator.haskell.org/rGHCe5732d2a28dfb8a754ee73e124e3558222a543bb) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8684#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8684: hWaitForInput cannot be interrupted by async exceptions on unix -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D42 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => new * owner: snoyberg => (none) Comment: Sorry, it looks like I was mistaken; this is in fact not fixed. The `timeout` does not, in fact, interrupt the `hWaitForInput`. It looks like Phab:D42 was never actually finished. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8684#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8684: hWaitForInput cannot be interrupted by async exceptions on unix -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 13525 | Blocking: Related Tickets: #12912, #13525 | Differential Rev(s): Phab:D42 Wiki Page: | -------------------------------------+------------------------------------- Changes (by nh2): * blockedby: => 13525 * related: => #12912, #13525 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8684#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8684: hWaitForInput cannot be interrupted by async exceptions on unix -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 13497, 13525 | Blocking: Related Tickets: #12912, #13525 | Differential Rev(s): Phab:D42 Wiki Page: | -------------------------------------+------------------------------------- Changes (by nh2): * blockedby: 13525 => 13497, 13525 Comment: Marking this as blocked by #13497 because that one is about getting the timing of `fdReady()` right. I believe that should be completed before making sure `fdReady()` can be interrupted. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8684#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8684: hWaitForInput cannot be interrupted by async exceptions on unix -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 13497, 13525 | Blocking: Related Tickets: #12912, #13525 | Differential Rev(s): Phab:D42 Wiki Page: | -------------------------------------+------------------------------------- Comment (by nh2): I've implemented a work-in-progress fix for GHC 8.2 [https://github.com/nh2/ghc/commit/d75bb46b6a16b4976a239442d90e5592ec439495 in this commit]. It's partly based on my older commit [https://github.com/nh2/ghc/commit/b23420378f68af9bddcced1cee08968779c505d0 b23420378f6]. It makes my example from the issue description work on the `-threaded` runtime on Linux (other platforms yet to be tested), but for unknown reason it doesn't fix it for the nonthreaded runtime. Maybe somehow in the nonthreaded runtime `timeout` doesn't actually throw the other thread the kill? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8684#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8684: hWaitForInput cannot be interrupted by async exceptions on unix -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 13497, 13525 | Blocking: Related Tickets: #12912, #13525 | Differential Rev(s): Phab:D42 Wiki Page: | -------------------------------------+------------------------------------- Comment (by nh2): OK new info with the power of `-debug` and `+RTS -Ds`: In non`-threaded`, it does raise the exception, but _after_ the entire `hWaitForInput` is over. I can see it in `cap 0: raising exception in thread 2.`, and also the reason: `timeout`'s `throwTo ` also only happens **after** `hWaitForInput` is over (it prints `cap 0: throwTo: from thread 1 to thread 2` only at the very end). So that means it's not the exception handling that's not working, it's the throwing. My C code returns back into Haskell land, but there is no exception there at the time so it continues. ---- On my debug commit https://github.com/nh2/ghc/blob/49a5e9ce7062da7594bfd86ca7af92796b84b52a/lib... that looks like this (relevant output without `-debug` in [https://gist.github.com/nh2/f543030a9b68b1530b19087d0c655115 this gist]): {{{ cap 0: running thread 1 (ThreadRunGHC) cap 0: thread 1 stopped (suspended while making a foreign call) fdReady called with msecs = 20 fdReady res = -1 cap 0: running thread 1 (ThreadRunGHC) cap 0: thread 1 stopped (suspended while making a foreign call) fdReady called with msecs = 10 fdReady res = -1 cap 0: running thread 1 (ThreadRunGHC) cap 0: thread 1 stopped (suspended while making a foreign call) fdReady called with msecs = 0 fdReady res = 0 cap 0: running thread 1 (ThreadRunGHC) cap 0: throwTo: from thread 1 to thread 2 thread 2 @ 0x42001059d0 is blocked until 558048911098409 (TSO_DIRTY) cap 0: raising exception in thread 2. cap 0: thread 1 stopped (finished) bound thread (1) finished task exiting }}} Observe here how `cap 0: throwTo: from thread 1 to thread 2` is after the `fdReady called with msecs = 0` (`hWaitForInput` ran its entire 5 seconds). ---- So now we just need to find out why `timeout` doesn't result in a prompt `cap 0: throwTo: from thread 1 to thread 2` after 1 second. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8684#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8684: hWaitForInput cannot be interrupted by async exceptions on unix -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 13497, 13525 | Blocking: Related Tickets: #12912, #13525 | Differential Rev(s): Phab:D42 Wiki Page: | -------------------------------------+------------------------------------- Comment (by nh2): OK, looking at the definition of `timeout` [http://hackage.haskell.org/package/base-4.10.0.0/docs/src/System.Timeout.htm... here], and making an instrumented copy of it into my test case file, it seems that the `threadDelay n >> throwTo pid ex` is never executed. The `cap 0: throwTo: from thread 1 to thread 2` I observe at the very end is from `killThread`. Changing it into this {{{ handleJust (\e -> if e == ex then Just () else Nothing) (\_ -> return Nothing) (bracket (forkIOWithUnmask $ \unmask -> do putStrLn "before unmask" unmask $ putStrLn "before delay" >> threadDelay n >> putStrLn "delay over" >> throwTo pid ex) (\x -> putStrLn "before killThread" >> uninterruptibleMask_ (killThread x)) (\_ -> fmap Just f)) }}} yields the output at the very end: {{{ fdReady called with msecs = 0 fdReady res = 1 before killThread fdReady called with msecs = 0 fdReady res = 1 before unmask }}} and then the program terminates. This suggests that nothing inside `unmask` is ever executed in my non- threaded case, and that the thread started with `forkIOWithUnmask` doesn't actually run until `hWaitForInput` is over. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8684#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8684: hWaitForInput cannot be interrupted by async exceptions on unix -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 13497, 13525 | Blocking: Related Tickets: #12912, #13525 | Differential Rev(s): Phab:D42 Wiki Page: | -------------------------------------+------------------------------------- Comment (by nh2): Looking at this with `+RTS -Ds` again, we get: {{{ created capset 0 of type 2 created capset 1 of type 3 cap 0: initialised assigned cap 0 to capset 0 assigned cap 0 to capset 1 new task (taskCount: 1) cap 0: created thread 1 new bound thread (1) cap 0: schedule() cap 0: running thread 1 (ThreadRunGHC) fdReady called with msecs = 0 fdReady res = 1 setup cap 0: created thread 2 cap 0: thread 1 stopped (suspended while making a foreign call) fdReady called with msecs = 5000 fdReady res = -1 ... [lots of output running only thread 1] ... cap 0: running thread 1 (ThreadRunGHC) cap 0: thread 1 stopped (suspended while making a foreign call) fdReady called with msecs = 4690 fdReady res = -1 cap 0: running thread 1 (ThreadRunGHC) cap 0: thread 1 stopped (suspended while making a foreign call) fdReady called with msecs = 4680 fdReady res = 0 cap 0: running thread 1 (ThreadRunGHC) cap 0: throwTo: from thread 1 to thread 2 thread 2 @ 0x4200105aa0 is not blocked (TSO_DIRTY) cap 0: throwTo: blocking on thread 2 cap 0: thread 1 stopped (blocked on throwTo) thread 1 @ 0x4200105388 is blocked on a throwto message (TSO_DIRTY) cap 0: running thread 2 (ThreadRunGHC) cap 0: raising exception in thread 2. cap 0: waking up thread 1 on cap 0 cap 0: thread 2 stopped (yielding) cap 0: running thread 1 (ThreadRunGHC) }}} So the new question here is: Why is `thread 2` (the one that contains `unmask $ threadDelay n >> throwTo pid ex`) never run, and `thread 1` is run all the time? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8684#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8684: hWaitForInput cannot be interrupted by async exceptions on unix -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 13497, 13525 | Blocking: Related Tickets: #12912, #13525 | Differential Rev(s): Phab:D42 Wiki Page: | -------------------------------------+------------------------------------- Comment (by nh2): The above seems to be because in `rts/Schedule.c` only `resumeThread()` is called, and `schedule()` is not called. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8684#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8684: hWaitForInput cannot be interrupted by async exceptions on unix -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 13497, 13525 | Blocking: Related Tickets: #12912, #13525 | Differential Rev(s): Phab:D42 Wiki Page: | -------------------------------------+------------------------------------- Comment (by nh2): I think I've got it! Inserting a `yield` [https://github.com/nh2/ghc/blob/49a5e9ce7062da7594bfd86ca7af92796b84b52a/lib... here] after `fdReady()` returns back into Haskell makes `delay over` appear and my example code terminate after the 1 second `timeout`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8684#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8684: hWaitForInput cannot be interrupted by async exceptions on unix -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 13497, 13525 | Blocking: Related Tickets: #12912, #13525 | Differential Rev(s): Phab:D42 Wiki Page: | -------------------------------------+------------------------------------- Comment (by nh2): Hmm, `interruptible yield` would be a workaround, but I think it wouldn't fix the key problem. It would fix only `hWaitForInput`/`ready`. But it looks like other safe foreign calls that are called in a tight loop that does not allocate cannot be `timeout`ed. It seems a proper solution would be to insert a `yield` right after /any/ foreign call returns (at least in the non-threaded RTS). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8684#comment:21 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8684: hWaitForInput cannot be interrupted by async exceptions on unix -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 13497, 13525 | Blocking: Related Tickets: #12912, #13525 | Differential Rev(s): Phab:D42 Wiki Page: | -------------------------------------+------------------------------------- Comment (by nh2): In other words, I believe we have a scheduling unfairness problem in the non-threaded RTS: A thread that loops tightly around a foreign call will never give other threads the chance to run. I ''suspect'' this is because of the run-queue logic mentioned in [https://ghc.haskell.org/trac/ghc/wiki/Commentary/Rts/Scheduler#Therunqueue the Scheduler commentary]: ----
In more detail, threads are put **in front** (`pushOnRunQueue`) if: [...] * In the non-threaded runtime, when a thread waiting on IO unblocks.
-- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8684#comment:22 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8684: hWaitForInput cannot be interrupted by async exceptions on unix
-------------------------------------+-------------------------------------
Reporter: nh2 | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Core Libraries | Version: 7.6.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: 13497, 13525 | Blocking:
Related Tickets: #12912, #13525 | Differential Rev(s): Phab:D42
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#8684: hWaitForInput cannot be interrupted by async exceptions on unix
-------------------------------------+-------------------------------------
Reporter: nh2 | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Core Libraries | Version: 7.6.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: 13497, 13525 | Blocking:
Related Tickets: #12912, #13525 | Differential Rev(s): Phab:D42
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Tamar Christina

#8684: hWaitForInput cannot be interrupted by async exceptions on unix -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 13497, 13525 | Blocking: Related Tickets: #12912, #13525 | Differential Rev(s): Phab:D42 Wiki Page: | -------------------------------------+------------------------------------- Comment (by nh2): Some more trouble on Windows (also for `-threaded`): If the FD is a [https://github.com/ghc/ghc/blob/ghc-8.2.1-release/libraries/base/cbits/input... FILE_TYPE_CHAR], then the implementation of `ccall interruptible` ([https://downloads.haskell.org/~ghc/8.2.1/docs/html/users_guide/ffi- chap.html#interruptible-foreign-calls see here]) via `CancelSynchronousIo` doesn't seem to kill the [https://github.com/nh2/ghc/blob/bug-8684 -interruptible-hWaitForInput/libraries/base/cbits/inputReady.c#L306 WaitForSingleObject()] invocation. Unfortunately, the call to [https://github.com/ghc/ghc/blob/ghc-8.2.1-release/rts/win32/OSThreads.c#L569 CancelSynchronousIo(), here named pCSIO()], does not actually check the return value of [https://msdn.microsoft.com/en- us/library/windows/desktop/aa363794(v=vs.85).aspx the function], which returns a `BOOL success`.
If this function cannot find a request to cancel, the return value is 0 (zero), and `GetLastError` returns `ERROR_NOT_FOUND`.
In my case, when logging it, I see it returns error code 1168, which is `ERROR_NOT_FOUND`, so apparently nothing was cancelled. As a result, my example program from the issue description runs for 5 seconds instead of one. With a bit more instrumentation, I get this: {{{ fdReady called with msecs = 5000 calling WaitForSingleObject calling pCSIO pCSIO ret 0 pCSIO error: 1168 WaitForSingleObject rc 258 (WAIT_TIMEOUT) }}} After 1 second, as expected, it's `calling pCSIO`, but it doesn't cancel anything due to the error, so after 5 seconds `WaitForSingleObject rc 258 (WAIT_TIMEOUT)` happens. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8684#comment:25 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8684: hWaitForInput cannot be interrupted by async exceptions on unix -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 13497, 13525 | Blocking: Related Tickets: #12912, #13525 | Differential Rev(s): Phab:D42 Wiki Page: | -------------------------------------+------------------------------------- Comment (by nh2): I've augmented my debugging output by the Windows thread ID [https://github.com/ghc/ghc/blob/ghc-8.2.1-release/rts/win32/OSThreads.c#L558 here] and with `GetCurrentThreadId()`: {{{ fdReady called with msecs = 5000 calling WaitForSingleObject in windows thread id 0000000000000b14 calling pCSIO(thread id 0000000000000b14) pCSIO ret 0 pCSIO error: 1168 WaitForSingleObject rc 258 (WAIT_TIMEOUT) }}} Looks like the thread IDs are the same, so I currently have no idea why `pCSIO()` running wouldn't switftly terminate the `WaitForSingleObject()` on this `FILE_TYPE_CHAR` FD. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8684#comment:26 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8684: hWaitForInput cannot be interrupted by async exceptions on unix -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 13497, 13525 | Blocking: Related Tickets: #12912, #13525 | Differential Rev(s): Phab:D42 Wiki Page: | -------------------------------------+------------------------------------- Comment (by nh2): Hmm, in [https://books.google.ch/books?id=r5tCAwAAQBAJ&pg=PT636&lpg=PT636&dq=CancelSynchronousIo++ERROR_NOT_FOUND&source=bl&ots=PS_yalzoMX&sig =hM- 5HzjZGwu66hal48xjV50kYsU&hl=en&sa=X&ved=0ahUKEwj0uvaI1sHXAhXDHxoKHdsDB_YQ6AEIRDAF#v=onepage&q=CancelSynchronousIo%20%20ERROR_NOT_FOUND&f=false this book] **Windows via C/C++** it says
Note that the thread calling `CancelSynchronousIo` doesn't really know where the thread that called the synchronous operation is. The thread could have been pre-empted and it has yet to actually communicate with the device; it could be suspended, waiting for the device to respond; or the device could have just responded, and the thread is in the process of returning from its call. If `CancelSynchronousIo` is called when the specified thread is not actually suspended waiting for the device to respond, `CancelSynchronousIo` returns `FALSE` and `GetLastError` returns error not found.
-- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8684#comment:27 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8684: hWaitForInput cannot be interrupted by async exceptions on unix
-------------------------------------+-------------------------------------
Reporter: nh2 | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Core Libraries | Version: 7.6.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: 13497, 13525 | Blocking:
Related Tickets: #12912, #13525 | Differential Rev(s): Phab:D42
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by nh2):
I managed to make it work on Windows for `FILE_TYPE_CHAR`, by using
`WaitForMultipleObjects()` and passing it 2 objects: The `HANDLE` we're
interested in, an Event object that we signal when we want to interrupt
the thread.
After searching for a very long time, I ended up with the above solution.
Most important links:
* [https://social.msdn.microsoft.com/Forums/sqlserver/en-
US/dd7ce0e9-847d-4727-b0a6-efd68bd5626e/synchronous-readfile-on-stdin-
cannot-be-unblocked-by-cancelsynchronousio?forum=windowssdk Post by Ben
Golding in this thread] that proposes this solution
* [https://stackoverflow.com/questions/47336755/how-to-
cancelsynchronousio-on-waitforsingleobject-waiting-on-stdin My
StackOverflow question] (answers trickled in only after I had already
implemented a work-in-progress solution
Here's the backstory of me finding it out via the `#ghc` and `#winapi` IRC
channels:
In `#ghc`:
{{{

#8684: hWaitForInput cannot be interrupted by async exceptions on unix -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 13497, 13525 | Blocking: Related Tickets: #12912, #13525 | Differential Rev(s): Phab:D42 Wiki Page: | -------------------------------------+------------------------------------- Comment (by nh2): As part of the review of my patch in https://phabricator.haskell.org/D42, I have gathered some information of how the timer signal is implemented. Since that may be a useful by itself, I post it here. It is as of commit `a1950e6`, and, since not much of this has changed since the last release, also of GHC 8.2. # How the timer signal is implemented In general, the tick callbacks go like this to do context switching: {{{ handle_tick() contextSwitchAllCapabilities() for all capabilities: contextSwitchCapability() stopCapability() cap->r.rHpLim = NULL; // makes the heap check fail also sets `cap->interrupt = 1;` }}} Methods used on the various platforms: {{{ - POSIX (method selected in `posix/Itimer.c`) - Linux, threaded RTS -> timer_create() if it exists, otherwise setitimer() - Linux, non-threaded, >= 2.6.25 -> pthread with timerfd - Linux, non-threaded, < 2.6.25 -> pthread without timerfd - Darwin -> pthread without timerfd - iOS -> pthread without timerfd - Windows (`win32/Ticker.c`) - Windows -> CreateTimerQueueTimer() }}} Notably the Darwin and iOS implementations use a pthread even for the non- threaded RTS! Relevant trac issues about the above methods: * #1933 - [https://ghc.haskell.org/trac/ghc/ticket/1933 Zero times in profiling with GHC-6.8.1] -- This added autoconf-based detection of `timer_create()` on Linux. * #10840 - [https://ghc.haskell.org/trac/ghc/ticket/10840 Periodic alarm signals can cause a retry loop to get stuck] -- This added the pthread-based implementations. Method implementation locations: {{{ - pthread with timerfd -> `itimer/Pthread.c` - pthread without timerfd (sleep loop) -> `itimer/Pthread.c` - timer_create() -> `itimer/TimerCreate.c` - setitimer() -> `itimer/Setitimer.c` }}} How the implementations work: - pthread with timerfd - A pthread is started that runs a loop reading from the timerfd. No SIGVTALRM is used. When the timerfd ticks, that thread wakes up and calls handle_tick(). - pthread without timerfd - A pthread is started that runs a loop running `sleep(itimer_interval)`. No SIGVTALRM is used. When that thread finishes the sleep, it calls handle_tick(). - timer_create() - A SIGVTALRM signal handler is set up that `handle_tick()`. Then timer_create() is called to set up a SIGVTALRM signal occurring regularly, using the `ITIMER_REAL` real-time clock. The SIGVTALRM signal occurring will EINTR all system calls of all threads of the process. - `setitimer()` - A SIGVTALRM signal handler is set up that `handle_tick()`. Then `setitimer()` is called to set up a SIGVTALRM signal occurring regularly, using the `CLOCK_ID` clock, which is `CLOCK_MONOTONIC` if available and `CLOCK_REALTIME` otherwise. The SIGVTALRM signal occurring will EINTR all system calls of all threads of the process. - `CreateTimerQueueTimer()` - `CreateTimerQueueTimer()` is set up to call `tick_callback()` which calls `tick_proc = handle_tick()` regularly. The option `WT_EXECUTEINTIMERTHREAD` is passed which results in "callback function is invoked by the timer thread itself". There are a couple issues with it: 1. The period is set to `TimeToUS(tick_interval) / 1000` milliseconds, which becomes 0 if less than a millisecond is chosen. `CreateTimerQueueTimer()` does not document what happens if a 0-period is given. It might busy-poll, but it's not documented, so who knows? 2. A comment in the code remarks that this timer has a maximum accuracy of 15ms on Windows 7, and even worse on older platforms. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8684#comment:29 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8684: hWaitForInput cannot be interrupted by async exceptions on unix -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 13497, 13525 | Blocking: Related Tickets: #12912, #13525 | Differential Rev(s): Phab:D42 Wiki Page: | -------------------------------------+------------------------------------- Comment (by nh2): OK, due to the reasons at https://phabricator.haskell.org/D42#119714 I found that this bug is also present in non`-threaded` on Darwin and iOS: `ghc-bug-8684-test.hs` {{{ import Control.Concurrent import System.IO import System.Timeout main :: IO () main = do forkIO $ do threadDelay (5 * 1000000) -- The timeout should terminate before we ever make it here putStrLn "t=5 seconds: we shouldn't be here" timeout (1 * 1000000) $ do hWaitForInput stdin (10 * 1000) putStrLn "we shouldn't be here" return () }}} I just confirmed that this prints `t=5 seconds: we shouldn't be here` on OSX. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8684#comment:30 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8684: hWaitForInput cannot be interrupted by async exceptions on unix -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 13497, 13525 | Blocking: Related Tickets: #12912, #13525 | Differential Rev(s): Phab:D42 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonmar): I think the table above is a bit wrong. The relevant bit of code is {{{ #if defined(linux_HOST_OS) && defined(THREADED_RTS) && HAVE_SYS_TIMERFD_H #define USE_PTHREAD_FOR_ITIMER #endif }}} which means we should have (I re-ordered the lines a bit) {{{ - POSIX (method selected in `posix/Itimer.c`) - Linux, threaded, >= 2.6.25 -> pthread with timerfd - Linux, threaded, < 2.6.25 -> timer_create() if it exists, otherwise setitimer() - Linux, non-threaded RTS -> timer_create() if it exists, otherwise setitimer() - Darwin -> pthread without timerfd - iOS -> pthread without timerfd - Windows (`win32/Ticker.c`) - Windows -> CreateTimerQueueTimer() }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8684#comment:31 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8684: hWaitForInput cannot be interrupted by async exceptions on unix -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 13497, 13525 | Blocking: Related Tickets: #12912, #13525 | Differential Rev(s): Phab:D42 Wiki Page: | -------------------------------------+------------------------------------- Comment (by nh2): @simonmar Oops, you are right. I swapped `threaded` and `non-threaded` when typing down my table, thus writing we use pthreads in non-threaded, which is exactly the wrong way around. I'll edit to reflect that. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8684#comment:32 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8684: hWaitForInput cannot be interrupted by async exceptions on unix -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 13497, 13525 | Blocking: Related Tickets: #12912, #13525, | Differential Rev(s): Phab:D42 #7353 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by nh2): * related: #12912, #13525 => #12912, #13525, #7353 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8684#comment:33 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC