GHC uses O_NONBLOCK on regular files, which has no effect, and blocks the runtime
This is the outcome of https://mail.haskell.org/pipermail/ghc-devs/2018-May/015749.html
Reading through the code of readRawBufferPtr the first line jumped to my eye:
| isNonBlocking fd = unsafe_read -- unsafe is ok, it can't block
This looks suspicious.
On Linux, if fd
is a a descriptor to a regular file (on disk, a networked filesystem, or a block device), then O_NONBLOCK
will have no effect, yet unsafe_read
is used which will block the running OS thread.
You can read more about O_NONBLOCK
not working on regular files on Linux here:
- https://www.nginx.com/blog/thread-pools-boost-performance-9x/
- https://stackoverflow.com/questions/8057892/epoll-on-regular-files
- https://jvns.ca/blog/2017/06/03/async-io-on-linux--select--poll--and-epoll/
- https://groups.google.com/forum/#!topic/comp.os.linux.development.system/K-fC-G6P4EA
And indeed, the following program does NOT keep printing things in the printing thread, and instead blocks for 30 seconds:
module Main where
import Control.Concurrent
import Control.Monad
import qualified Data.ByteString as BS
import System.Environment
main :: IO ()
main = do
args <- getArgs
case args of
[file] -> do
forkIO $ forever $ do
putStrLn "still running"
threadDelay 100000 -- 0.1 s
bs <- BS.readFile file
putStrLn $ "Read " ++ show (BS.length bs) ++ " bytes"
_ -> error "Pass 1 argument (a file)"
when compiled with
~/.stack/programs/x86_64-linux/ghc-8.2.2/bin/ghc --make -O -threaded blocking-regular-file-read-test.hs
on my Ubuntu 16.04 and on a 2GB file like
./blocking-regular-file-read-test /mnt/images/ubuntu-18.04-desktop-amd64.iso
And strace -f -e open,read
on it shows:
open("/mnt/images/ubuntu-18.04-desktop-amd64.iso", O_RDONLY|O_NOCTTY|O_NONBLOCK) = 11
read(11, <unfinished ...>
So GHC is trying to use O_NONBLOCK
on regular files, which cannot work and will block when used through unsafe foreign calls like that.
Trac metadata
Trac field | Value |
---|---|
Version | 8.2.2 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Runtime System |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | lehins, nh2 |
Operating system | |
Architecture |