[GHC] #10736: threadWaitRead/registerFd unusable
GHC
ghc-devs at haskell.org
Tue Aug 4 22:30:05 UTC 2015
#10736: threadWaitRead/registerFd unusable
-------------------------------------+-------------------------------------
Reporter: mboes | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.2
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Revisions: |
-------------------------------------+-------------------------------------
The following program:
{{{
module Main where
import System.Posix.IO
import GHC.Event
main = do
Just mgr <- getSystemEventManager
fd <- openFd "/tmp/bleh" ReadOnly Nothing defaultFileFlags { nonBlock =
True }
key <- registerFd mgr (\_ _ -> putStrLn "hello") fd evtRead MultiShot
return ()
}}}
fails with:
{{{
*** Exception: modifyFdOnce: permission denied (Operation not permitted)
}}}
Since `threadWaitRead` and family are implemented in terms of
`registerFd`, they also fail with the same error.
Perhaps I am misunderstanding how to use this function, but in this case
the conditions that must hold true regarding file descriptors should be
documented somewhere.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10736>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list