more OsPath conversion
Sponsored-by: Luke T. Shumaker
This commit is contained in:
parent
7da6f83582
commit
0376bc5ee0
7 changed files with 130 additions and 134 deletions
8
Remote/External/Types.hs
vendored
8
Remote/External/Types.hs
vendored
|
@ -480,12 +480,12 @@ instance Proto.Serializable URI where
|
|||
deserialize = parseURIPortable
|
||||
|
||||
instance Proto.Serializable ExportLocation where
|
||||
serialize = fromRawFilePath . fromExportLocation
|
||||
deserialize = Just . mkExportLocation . toRawFilePath
|
||||
serialize = fromOsPath . fromExportLocation
|
||||
deserialize = Just . mkExportLocation . toOsPath
|
||||
|
||||
instance Proto.Serializable ExportDirectory where
|
||||
serialize = fromRawFilePath . fromExportDirectory
|
||||
deserialize = Just . mkExportDirectory . toRawFilePath
|
||||
serialize = fromOsPath . fromExportDirectory
|
||||
deserialize = Just . mkExportDirectory . toOsPath
|
||||
|
||||
instance Proto.Serializable ExtensionList where
|
||||
serialize (ExtensionList l) = unwords l
|
||||
|
|
|
@ -10,7 +10,7 @@ module Remote.Helper.Path where
|
|||
import Annex.Common
|
||||
import Types.Availability
|
||||
|
||||
checkPathAvailability :: Bool -> FilePath -> Annex Availability
|
||||
checkPathAvailability :: Bool -> OsPath -> Annex Availability
|
||||
checkPathAvailability islocal d
|
||||
| not islocal = return GloballyAvailable
|
||||
| otherwise = ifM (liftIO $ doesDirectoryExist d)
|
||||
|
|
|
@ -14,9 +14,7 @@ import Types.Remote
|
|||
import Types.Import
|
||||
import Crypto (isEncKey)
|
||||
import Utility.Metered
|
||||
|
||||
import qualified System.FilePath.ByteString as P
|
||||
import qualified Data.ByteString as S
|
||||
import qualified Utility.OsString as OS
|
||||
|
||||
-- When a remote is thirdPartyPopulated, the files we want are probably
|
||||
-- in the .git directory. But, git does not really support .git in paths
|
||||
|
@ -24,22 +22,22 @@ import qualified Data.ByteString as S
|
|||
-- And so anything in .git is prevented from being imported.
|
||||
-- To work around that, this renames that directory when generating an
|
||||
-- ImportLocation.
|
||||
mkThirdPartyImportLocation :: RawFilePath -> ImportLocation
|
||||
mkThirdPartyImportLocation :: OsPath -> ImportLocation
|
||||
mkThirdPartyImportLocation =
|
||||
mkImportLocation . P.joinPath . map esc . P.splitDirectories
|
||||
mkImportLocation . joinPath . map esc . splitDirectories
|
||||
where
|
||||
esc ".git" = "dotgit"
|
||||
esc x
|
||||
| "dotgit" `S.isSuffixOf` x = "dot" <> x
|
||||
| x == literalOsPath ".git" = literalOsPath "dotgit"
|
||||
| literalOsPath "dotgit" `OS.isSuffixOf` x = literalOsPath "dot" <> x
|
||||
| otherwise = x
|
||||
|
||||
fromThirdPartyImportLocation :: ImportLocation -> RawFilePath
|
||||
fromThirdPartyImportLocation :: ImportLocation -> OsPath
|
||||
fromThirdPartyImportLocation =
|
||||
P.joinPath . map unesc . P.splitDirectories . fromImportLocation
|
||||
joinPath . map unesc . splitDirectories . fromImportLocation
|
||||
where
|
||||
unesc "dotgit" = ".git"
|
||||
unesc x
|
||||
| "dotgit" `S.isSuffixOf` x = S.drop 3 x
|
||||
| x == literalOsPath "dotgit" = literalOsPath ".git"
|
||||
| literalOsPath "dotgit" `OS.isSuffixOf` x = OS.drop 3 x
|
||||
| otherwise = x
|
||||
|
||||
-- When a remote is thirdPartyPopulated, and contains a backup of a
|
||||
|
@ -49,7 +47,7 @@ fromThirdPartyImportLocation =
|
|||
importKey :: ImportLocation -> ContentIdentifier -> ByteSize -> MeterUpdate -> Annex (Maybe Key)
|
||||
importKey loc _cid sz _ = return $ importKey' (fromImportLocation loc) (Just sz)
|
||||
|
||||
importKey' :: RawFilePath -> Maybe ByteSize -> Maybe Key
|
||||
importKey' :: OsPath -> Maybe ByteSize -> Maybe Key
|
||||
importKey' p msz = case fileKey f of
|
||||
Just k
|
||||
-- Annex objects always are in a subdirectory with the same
|
||||
|
@ -62,7 +60,7 @@ importKey' p msz = case fileKey f of
|
|||
-- part of special remotes that don't use that layout. The most
|
||||
-- likely special remote to be in a backup, the directory
|
||||
-- special remote, does use that layout at least.)
|
||||
| lastMaybe (P.splitDirectories (P.dropFileName p)) /= Just f -> Nothing
|
||||
| lastMaybe (splitDirectories (dropFileName p)) /= Just f -> Nothing
|
||||
-- Chunked or encrypted keys used in special remotes are not
|
||||
-- supported.
|
||||
| isChunkKey k || isEncKey k -> Nothing
|
||||
|
@ -82,4 +80,4 @@ importKey' p msz = case fileKey f of
|
|||
_ -> Just k
|
||||
Nothing -> Nothing
|
||||
where
|
||||
f = P.takeFileName p
|
||||
f = takeFileName p
|
||||
|
|
|
@ -14,14 +14,14 @@ import Annex.Locations
|
|||
import Utility.Rsync
|
||||
import Utility.SafeCommand
|
||||
import Utility.ShellEscape
|
||||
import Utility.FileSystemEncoding
|
||||
import Utility.OsPath
|
||||
import Annex.DirHashes
|
||||
#ifdef mingw32_HOST_OS
|
||||
import Utility.Split
|
||||
#endif
|
||||
|
||||
import Data.Default
|
||||
import System.FilePath.Posix
|
||||
import qualified System.FilePath.Posix as Posix
|
||||
import qualified Data.List.NonEmpty as NE
|
||||
|
||||
type RsyncUrl = String
|
||||
|
@ -40,15 +40,15 @@ rsyncEscape o u
|
|||
| otherwise = u
|
||||
|
||||
mkRsyncUrl :: RsyncOpts -> FilePath -> RsyncUrl
|
||||
mkRsyncUrl o f = rsyncUrl o </> rsyncEscape o f
|
||||
mkRsyncUrl o f = rsyncUrl o Posix.</> rsyncEscape o f
|
||||
|
||||
rsyncUrls :: RsyncOpts -> Key -> [RsyncUrl]
|
||||
rsyncUrls o k = map use (NE.toList dirHashes)
|
||||
where
|
||||
use h = rsyncUrl o </> hash h </> rsyncEscape o (f </> f)
|
||||
f = fromRawFilePath (keyFile k)
|
||||
use h = rsyncUrl o Posix.</> hash h Posix.</> rsyncEscape o (f Posix.</> f)
|
||||
f = fromOsPath (keyFile k)
|
||||
#ifndef mingw32_HOST_OS
|
||||
hash h = fromRawFilePath $ h def k
|
||||
hash h = fromOsPath $ h def k
|
||||
#else
|
||||
hash h = replace "\\" "/" $ fromRawFilePath $ h def k
|
||||
hash h = replace "\\" "/" $ fromOsPath $ h def k
|
||||
#endif
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue