more OsPath conversion (464/749)
Sponsored-by: unqueued
This commit is contained in:
parent
cf986bc7e2
commit
54f0710fd2
17 changed files with 164 additions and 165 deletions
|
@ -14,7 +14,6 @@ module Remote.Directory.LegacyChunked where
|
|||
|
||||
import qualified Data.ByteString.Lazy as L
|
||||
import qualified Data.ByteString as S
|
||||
import qualified System.FilePath.ByteString as P
|
||||
|
||||
import Annex.Common
|
||||
import Utility.FileMode
|
||||
|
@ -23,7 +22,6 @@ import qualified Remote.Helper.Chunked.Legacy as Legacy
|
|||
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
|
||||
|
@ -45,7 +43,7 @@ withCheckedFiles check d locations k a = go $ locations d k
|
|||
else a chunks
|
||||
)
|
||||
withStoredFiles :: FilePath -> (FilePath -> Key -> [FilePath]) -> Key -> ([FilePath] -> IO Bool) -> IO Bool
|
||||
withStoredFiles = withCheckedFiles doesFileExist
|
||||
withStoredFiles = withCheckedFiles (doesFileExist . toOsPath)
|
||||
|
||||
{- Splits a ByteString into chunks and writes to dests, obeying configured
|
||||
- chunk size (not to be confused with the L.ByteString chunk size). -}
|
||||
|
@ -77,20 +75,20 @@ storeLegacyChunked' meterupdate chunksize (d:dests) bs c = do
|
|||
feed bytes' (sz - s) ls h
|
||||
else return (l:ls)
|
||||
|
||||
storeHelper :: FilePath -> (RawFilePath -> RawFilePath -> IO ()) -> Key -> ([FilePath] -> IO [FilePath]) -> FilePath -> FilePath -> IO ()
|
||||
storeHelper :: FilePath -> (OsPath -> OsPath -> IO ()) -> Key -> ([FilePath] -> IO [FilePath]) -> FilePath -> FilePath -> IO ()
|
||||
storeHelper repotop finalizer key storer tmpdir destdir = do
|
||||
void $ liftIO $ tryIO $ createDirectoryUnder
|
||||
[toRawFilePath repotop]
|
||||
(toRawFilePath tmpdir)
|
||||
[toOsPath repotop]
|
||||
(toOsPath tmpdir)
|
||||
Legacy.storeChunks key tmpdir destdir storer recorder (legacyFinalizer finalizer)
|
||||
where
|
||||
recorder f s = do
|
||||
let f' = toRawFilePath f
|
||||
let f' = toOsPath f
|
||||
void $ tryIO $ allowWrite f'
|
||||
writeFile f s
|
||||
void $ tryIO $ preventWrite f'
|
||||
|
||||
store :: FilePath -> ChunkSize -> (RawFilePath -> RawFilePath -> IO ()) -> Key -> L.ByteString -> MeterUpdate -> FilePath -> FilePath -> IO ()
|
||||
store :: FilePath -> ChunkSize -> (OsPath -> OsPath -> IO ()) -> Key -> L.ByteString -> MeterUpdate -> FilePath -> FilePath -> IO ()
|
||||
store repotop chunksize finalizer k b p = storeHelper repotop finalizer k $ \dests ->
|
||||
storeLegacyChunked p chunksize dests b
|
||||
|
||||
|
@ -98,30 +96,29 @@ store repotop chunksize finalizer k b p = storeHelper repotop finalizer k $ \des
|
|||
- Done very innefficiently, by writing to a temp file.
|
||||
- :/ This is legacy code..
|
||||
-}
|
||||
retrieve :: (RawFilePath -> Key -> [RawFilePath]) -> RawFilePath -> Retriever
|
||||
retrieve :: (OsPath -> Key -> [OsPath]) -> OsPath -> 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' = toOsPath tmp
|
||||
let tmp = tmpdir </> keyFile basek <> literalOsPath ".directorylegacy.tmp"
|
||||
let go = \k sink -> do
|
||||
liftIO $ void $ withStoredFiles (fromRawFilePath d) (legacyLocations locations) k $ \fs -> do
|
||||
liftIO $ void $ withStoredFiles (fromOsPath d) (legacyLocations locations) k $ \fs -> do
|
||||
forM_ fs $
|
||||
F.appendFile' tmp' <=< S.readFile
|
||||
F.appendFile' tmp <=< S.readFile
|
||||
return True
|
||||
b <- liftIO $ F.readFile tmp'
|
||||
liftIO $ removeWhenExistsWith R.removeLink tmp
|
||||
b <- liftIO $ F.readFile tmp
|
||||
liftIO $ removeWhenExistsWith removeFile tmp
|
||||
sink b
|
||||
byteRetriever go basek p tmp miv c
|
||||
|
||||
checkKey :: RawFilePath -> (RawFilePath -> Key -> [RawFilePath]) -> Key -> Annex Bool
|
||||
checkKey :: OsPath -> (OsPath -> Key -> [OsPath]) -> Key -> Annex Bool
|
||||
checkKey d locations k = liftIO $
|
||||
withStoredFiles (fromRawFilePath d) (legacyLocations locations) k $
|
||||
withStoredFiles (fromOsPath d) (legacyLocations locations) k $
|
||||
-- withStoredFiles checked that it exists
|
||||
const $ return True
|
||||
|
||||
legacyFinalizer :: (RawFilePath -> RawFilePath -> IO ()) -> (FilePath -> FilePath -> IO ())
|
||||
legacyFinalizer f = \a b -> f (toRawFilePath a) (toRawFilePath b)
|
||||
legacyFinalizer :: (OsPath -> OsPath -> IO ()) -> (FilePath -> FilePath -> IO ())
|
||||
legacyFinalizer f = \a b -> f (toOsPath a) (toOsPath b)
|
||||
|
||||
legacyLocations :: (RawFilePath -> Key -> [RawFilePath]) -> (FilePath -> Key -> [FilePath])
|
||||
legacyLocations :: (OsPath -> Key -> [OsPath]) -> (FilePath -> Key -> [FilePath])
|
||||
legacyLocations locations = \f k ->
|
||||
map fromRawFilePath $ locations (toRawFilePath f) k
|
||||
map fromOsPath $ locations (toOsPath f) k
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue