[commit: packages/bytestring] master: Catch IOException from hFileSize in readFile (7223f8f)
git at git.haskell.org
git at git.haskell.org
Mon Apr 17 21:31:27 UTC 2017
Repository : ssh://git@git.haskell.org/bytestring
On branch : master
Link : http://git.haskell.org/packages/bytestring.git/commitdiff/7223f8f6d921e4c2fb118de95e65ab9f27307238
>---------------------------------------------------------------
commit 7223f8f6d921e4c2fb118de95e65ab9f27307238
Author: Ossi Herrala <oherrala at gmail.com>
Date: Thu Sep 1 17:16:34 2016 +0300
Catch IOException from hFileSize in readFile
hFileSize only works for regular files and fails for example with
/dev/null. However, hFileSize is only used as a hint for how much to
read. It should be safe to ignore the exception and try reading the
given file anyway.
Fixes #67
>---------------------------------------------------------------
7223f8f6d921e4c2fb118de95e65ab9f27307238
Data/ByteString.hs | 11 ++++++++---
1 file changed, 8 insertions(+), 3 deletions(-)
diff --git a/Data/ByteString.hs b/Data/ByteString.hs
index 99c7e38..0b74c64 100644
--- a/Data/ByteString.hs
+++ b/Data/ByteString.hs
@@ -217,7 +217,7 @@ import Prelude hiding (reverse,head,tail,last,init,null
,scanl,scanl1,scanr,scanr1
,readFile,writeFile,appendFile,replicate
,getContents,getLine,putStr,putStrLn,interact
- ,zip,zipWith,unzip,notElem)
+ ,zip,zipWith,unzip,notElem,catch)
#if MIN_VERSION_base(4,7,0)
import Data.Bits (finiteBitSize, shiftL, (.|.), (.&.))
@@ -233,7 +233,7 @@ import qualified Data.List as List
import Data.Word (Word8)
import Data.Maybe (isJust)
-import Control.Exception (finally, assert, throwIO)
+import Control.Exception (IOException, catch, finally, assert, throwIO)
import Control.Monad (when)
import Foreign.C.String (CString, CStringLen)
@@ -1817,13 +1817,18 @@ interact transformer = putStr . transformer =<< getContents
readFile :: FilePath -> IO ByteString
readFile f =
withBinaryFile f ReadMode $ \h -> do
- filesz <- hFileSize h
+ -- hFileSize fails if file is not regular file (like
+ -- /dev/null). Catch exception and try reading anyway.
+ filesz <- catch (hFileSize h) useZeroIfNotRegularFile
let readsz = (fromIntegral filesz `max` 0) + 1
hGetContentsSizeHint h readsz (readsz `max` 255)
-- Our initial size is one bigger than the file size so that in the
-- typical case we will read the whole file in one go and not have
-- to allocate any more chunks. We'll still do the right thing if the
-- file size is 0 or is changed before we do the read.
+ where
+ useZeroIfNotRegularFile :: IOException -> IO Integer
+ useZeroIfNotRegularFile _ = return 0
modifyFile :: IOMode -> FilePath -> ByteString -> IO ()
modifyFile mode f txt = withBinaryFile f mode (`hPut` txt)
More information about the ghc-commits
mailing list