convert from readFileStrict
This removes that function, using file-io readFile' instead. Had to deal with newline conversion, which readFileStrict does on Windows. In a few cases, that was pretty ugly to deal with. Sponsored-by: Kevin Mueller
This commit is contained in:
parent
de1af273e0
commit
6e27b0d4d1
19 changed files with 94 additions and 71 deletions
|
@ -22,6 +22,7 @@ import Annex.LockPool
|
|||
import Utility.TimeStamp
|
||||
import Logs.File
|
||||
import qualified Utility.RawFilePath as R
|
||||
import qualified Utility.FileIO as F
|
||||
#ifndef mingw32_HOST_OS
|
||||
import Annex.Perms
|
||||
#endif
|
||||
|
@ -119,7 +120,7 @@ checkTransfer t = debugLocks $ do
|
|||
(Just oldlck, _) -> getLockStatus oldlck
|
||||
case v' of
|
||||
StatusLockedBy pid -> liftIO $ catchDefaultIO Nothing $
|
||||
readTransferInfoFile (Just pid) (fromRawFilePath tfile)
|
||||
readTransferInfoFile (Just pid) tfile
|
||||
_ -> do
|
||||
mode <- annexFileMode
|
||||
-- Ignore failure due to permissions, races, etc.
|
||||
|
@ -140,7 +141,7 @@ checkTransfer t = debugLocks $ do
|
|||
v <- liftIO $ lockShared lck
|
||||
liftIO $ case v of
|
||||
Nothing -> catchDefaultIO Nothing $
|
||||
readTransferInfoFile Nothing (fromRawFilePath tfile)
|
||||
readTransferInfoFile Nothing tfile
|
||||
Just lockhandle -> do
|
||||
dropLock lockhandle
|
||||
deletestale
|
||||
|
@ -181,7 +182,7 @@ getFailedTransfers u = catMaybes <$> (liftIO . getpairs =<< concat <$> findfiles
|
|||
where
|
||||
getpairs = mapM $ \f -> do
|
||||
let mt = parseTransferFile f
|
||||
mi <- readTransferInfoFile Nothing (fromRawFilePath f)
|
||||
mi <- readTransferInfoFile Nothing f
|
||||
return $ case (mt, mi) of
|
||||
(Just t, Just i) -> Just (t, i)
|
||||
_ -> Nothing
|
||||
|
@ -285,9 +286,9 @@ writeTransferInfo info = unlines
|
|||
in maybe "" fromRawFilePath afile
|
||||
]
|
||||
|
||||
readTransferInfoFile :: Maybe PID -> FilePath -> IO (Maybe TransferInfo)
|
||||
readTransferInfoFile :: Maybe PID -> RawFilePath -> IO (Maybe TransferInfo)
|
||||
readTransferInfoFile mpid tfile = catchDefaultIO Nothing $
|
||||
readTransferInfo mpid <$> readFileStrict tfile
|
||||
readTransferInfo mpid . decodeBS <$> F.readFile' (toOsPath tfile)
|
||||
|
||||
readTransferInfo :: Maybe PID -> String -> Maybe TransferInfo
|
||||
readTransferInfo mpid s = TransferInfo
|
||||
|
@ -304,8 +305,11 @@ readTransferInfo mpid s = TransferInfo
|
|||
<*> pure False
|
||||
where
|
||||
#ifdef mingw32_HOST_OS
|
||||
(firstline, otherlines) = separate (== '\n') s
|
||||
(secondline, rest) = separate (== '\n') otherlines
|
||||
(firstliner, otherlines) = separate (== '\n') s
|
||||
(secondliner, rest) = separate (== '\n') otherlines
|
||||
firstline = dropWhileEnd (== '\r') firstliner
|
||||
secondline = dropWhileEnd (== '\r') secondliner
|
||||
secondline =
|
||||
mpid' = readish secondline
|
||||
#else
|
||||
(firstline, rest) = separate (== '\n') s
|
||||
|
|
|
@ -32,6 +32,7 @@ import qualified Data.Map as M
|
|||
import qualified Data.Set as S
|
||||
import Data.Time.Clock.POSIX
|
||||
import Data.Time
|
||||
import qualified Utility.FileIO as F
|
||||
|
||||
import Annex.Common
|
||||
import qualified Annex
|
||||
|
@ -73,10 +74,10 @@ writeUnusedLog prefix l = do
|
|||
|
||||
readUnusedLog :: RawFilePath -> Annex UnusedLog
|
||||
readUnusedLog prefix = do
|
||||
f <- fromRawFilePath <$> fromRepo (gitAnnexUnusedLog prefix)
|
||||
ifM (liftIO $ doesFileExist f)
|
||||
( M.fromList . mapMaybe parse . lines
|
||||
<$> liftIO (readFileStrict f)
|
||||
f <- fromRepo (gitAnnexUnusedLog prefix)
|
||||
ifM (liftIO $ doesFileExist (fromRawFilePath f))
|
||||
( M.fromList . mapMaybe (parse . decodeBS) . fileLines'
|
||||
<$> liftIO (F.readFile' (toOsPath f))
|
||||
, return M.empty
|
||||
)
|
||||
where
|
||||
|
|
|
@ -19,6 +19,7 @@ import Annex.Common
|
|||
import Utility.TimeStamp
|
||||
import Logs.File
|
||||
import Types.RepoVersion
|
||||
import qualified Utility.FileIO as F
|
||||
|
||||
import Data.Time.Clock.POSIX
|
||||
|
||||
|
@ -31,10 +32,10 @@ writeUpgradeLog v t = do
|
|||
|
||||
readUpgradeLog :: Annex [(RepoVersion, POSIXTime)]
|
||||
readUpgradeLog = do
|
||||
logfile <- fromRawFilePath <$> fromRepo gitAnnexUpgradeLog
|
||||
ifM (liftIO $ doesFileExist logfile)
|
||||
( mapMaybe parse . lines
|
||||
<$> liftIO (readFileStrict logfile)
|
||||
logfile <- fromRepo gitAnnexUpgradeLog
|
||||
ifM (liftIO $ doesFileExist (fromRawFilePath logfile))
|
||||
( mapMaybe (parse . decodeBS) . fileLines'
|
||||
<$> liftIO (F.readFile' (toOsPath logfile))
|
||||
, return []
|
||||
)
|
||||
where
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue