use file-io for readFile/writeFile/appendFile on ByteStrings
These are all straightforward, and easy small performance wins. Sponsored-by: Nicholas Golder-Manning
This commit is contained in:
parent
90cd3aad37
commit
9b79f0f43d
19 changed files with 63 additions and 52 deletions
|
@ -39,7 +39,7 @@ import qualified Data.ByteString as S
|
|||
|
||||
#ifdef WITH_TORRENTPARSER
|
||||
import Data.Torrent
|
||||
import qualified Data.ByteString.Lazy as B
|
||||
import qualified Utility.FileIO as F
|
||||
#endif
|
||||
|
||||
remote :: RemoteType
|
||||
|
@ -366,7 +366,7 @@ torrentFileSizes :: RawFilePath -> IO [(FilePath, Integer)]
|
|||
torrentFileSizes torrent = do
|
||||
#ifdef WITH_TORRENTPARSER
|
||||
let mkfile = joinPath . map (scrub . decodeBL)
|
||||
b <- B.readFile (fromRawFilePath torrent)
|
||||
b <- F.readFile (toOsPath torrent)
|
||||
return $ case readTorrent b of
|
||||
Left e -> giveup $ "failed to parse torrent: " ++ e
|
||||
Right t -> case tInfo t of
|
||||
|
|
|
@ -15,7 +15,6 @@ module Remote.Directory (
|
|||
removeDirGeneric,
|
||||
) where
|
||||
|
||||
import qualified Data.ByteString.Lazy as L
|
||||
import qualified Data.Map as M
|
||||
import qualified Data.List.NonEmpty as NE
|
||||
import qualified System.FilePath.ByteString as P
|
||||
|
@ -52,6 +51,7 @@ import Utility.InodeCache
|
|||
import Utility.FileMode
|
||||
import Utility.Directory.Create
|
||||
import qualified Utility.RawFilePath as R
|
||||
import qualified Utility.FileIO as F
|
||||
#ifndef mingw32_HOST_OS
|
||||
import Utility.OpenFd
|
||||
#endif
|
||||
|
@ -257,7 +257,7 @@ retrieveKeyFileM d NoChunks cow = fileRetriever' $ \dest k p iv -> do
|
|||
src <- liftIO $ fromRawFilePath <$> getLocation d k
|
||||
void $ liftIO $ fileCopier cow src (fromRawFilePath dest) p iv
|
||||
retrieveKeyFileM d _ _ = byteRetriever $ \k sink ->
|
||||
sink =<< liftIO (L.readFile . fromRawFilePath =<< getLocation d k)
|
||||
sink =<< liftIO (F.readFile . toOsPath =<< getLocation d k)
|
||||
|
||||
retrieveKeyFileCheapM :: RawFilePath -> ChunkConfig -> Maybe (Key -> AssociatedFile -> FilePath -> Annex ())
|
||||
-- no cheap retrieval possible for chunks
|
||||
|
|
|
@ -24,6 +24,7 @@ import Annex.Tmp
|
|||
import Utility.Metered
|
||||
import Utility.Directory.Create
|
||||
import qualified Utility.RawFilePath as R
|
||||
import qualified Utility.FileIO as F
|
||||
|
||||
withCheckedFiles :: (FilePath -> IO Bool) -> FilePath -> (FilePath -> Key -> [FilePath]) -> Key -> ([FilePath] -> IO Bool) -> IO Bool
|
||||
withCheckedFiles _ [] _locations _ _ = return False
|
||||
|
@ -101,13 +102,13 @@ retrieve :: (RawFilePath -> Key -> [RawFilePath]) -> RawFilePath -> Retriever
|
|||
retrieve locations d basek p _dest miv c = withOtherTmp $ \tmpdir -> do
|
||||
showLongNote "This remote uses the deprecated chunksize setting. So this will be quite slow."
|
||||
let tmp = tmpdir P.</> keyFile basek <> ".directorylegacy.tmp"
|
||||
let tmp' = fromRawFilePath tmp
|
||||
let tmp' = toOsPath tmp
|
||||
let go = \k sink -> do
|
||||
liftIO $ void $ withStoredFiles (fromRawFilePath d) (legacyLocations locations) k $ \fs -> do
|
||||
forM_ fs $
|
||||
S.appendFile tmp' <=< S.readFile
|
||||
F.appendFile' tmp' <=< S.readFile
|
||||
return True
|
||||
b <- liftIO $ L.readFile tmp'
|
||||
b <- liftIO $ F.readFile tmp'
|
||||
liftIO $ removeWhenExistsWith R.removeLink tmp
|
||||
sink b
|
||||
byteRetriever go basek p tmp miv c
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue