more OsPath conversion

This commit is contained in:
Joey Hess 2025-01-27 10:13:43 -04:00
parent c64731f16a
commit 8bafe05500
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
5 changed files with 38 additions and 24 deletions

View file

@ -465,7 +465,7 @@ withCurrentState a = do
- because the git repo paths are stored relative.
- Instead, use this.
-}
changeDirectory :: FilePath -> Annex ()
changeDirectory :: OsPath -> Annex ()
changeDirectory d = do
r <- liftIO . Git.adjustPath absPath =<< gitRepo
liftIO $ setCurrentDirectory d

View file

@ -23,7 +23,6 @@ import qualified Data.List.NonEmpty as NE
import qualified Data.ByteArray as BA
import qualified Data.ByteArray.Encoding as BA
import qualified Data.ByteString as S
import qualified System.FilePath.ByteString as P
import Common
import Key
@ -32,7 +31,7 @@ import Types.Difference
import Utility.Hash
import Utility.MD5
type Hasher = Key -> RawFilePath
type Hasher = Key -> OsPath
-- Number of hash levels to use. 2 is the default.
newtype HashLevels = HashLevels Int
@ -51,7 +50,7 @@ configHashLevels d config
| hasDifference d (annexDifferences config) = HashLevels 1
| otherwise = def
branchHashDir :: GitConfig -> Key -> S.ByteString
branchHashDir :: GitConfig -> Key -> OsPath
branchHashDir = hashDirLower . branchHashLevels
{- Two different directory hashes may be used. The mixed case hash
@ -64,9 +63,10 @@ branchHashDir = hashDirLower . branchHashLevels
dirHashes :: NE.NonEmpty (HashLevels -> Hasher)
dirHashes = hashDirLower NE.:| [hashDirMixed]
hashDirs :: HashLevels -> Int -> S.ByteString -> RawFilePath
hashDirs (HashLevels 1) sz s = P.addTrailingPathSeparator $ S.take sz s
hashDirs _ sz s = P.addTrailingPathSeparator $ h P.</> t
hashDirs :: HashLevels -> Int -> S.ByteString -> OsPath
hashDirs (HashLevels 1) sz s = addTrailingPathSeparator $
toOsPath (S.take sz s)
hashDirs _ sz s = addTrailingPathSeparator $ toOsPath h </> toOsPath t
where
(h, t) = S.splitAt sz s

View file

@ -151,13 +151,13 @@ import qualified Utility.RawFilePath as R
{- The directory git annex uses for local state, relative to the .git
- directory -}
annexDir :: RawFilePath
annexDir = P.addTrailingPathSeparator "annex"
annexDir :: OsPath
annexDir = addTrailingPathSeparator (literalOsPath "annex")
{- The directory git annex uses for locally available object content,
- relative to the .git directory -}
objectDir :: RawFilePath
objectDir = P.addTrailingPathSeparator $ annexDir P.</> "objects"
objectDir :: OsPath
objectDir = addTrailingPathSeparator $ annexDir </> literalOsPath "objects"
{- Annexed file's possible locations relative to the .git directory
- in a non-bare eepository.
@ -165,7 +165,7 @@ objectDir = P.addTrailingPathSeparator $ annexDir P.</> "objects"
- Normally it is hashDirMixed. However, it's always possible that a
- bare repository was converted to non-bare, or that the cripped
- filesystem setting changed, so still need to check both. -}
annexLocationsNonBare :: GitConfig -> Key -> [RawFilePath]
annexLocationsNonBare :: GitConfig -> Key -> [OsPath]
annexLocationsNonBare config key =
map (annexLocation config key) [hashDirMixed, hashDirLower]
@ -174,15 +174,15 @@ annexLocationsBare :: GitConfig -> Key -> [RawFilePath]
annexLocationsBare config key =
map (annexLocation config key) [hashDirLower, hashDirMixed]
annexLocation :: GitConfig -> Key -> (HashLevels -> Hasher) -> RawFilePath
annexLocation config key hasher = objectDir P.</> keyPath key (hasher $ objectHashLevels config)
annexLocation :: GitConfig -> Key -> (HashLevels -> Hasher) -> OsPath
annexLocation config key hasher = objectDir </> keyPath key (hasher $ objectHashLevels config)
{- For exportree remotes with annexobjects=true, objects are stored
- in this location as well as in the exported tree. -}
exportAnnexObjectLocation :: GitConfig -> Key -> ExportLocation
exportAnnexObjectLocation gc k =
mkExportLocation $
".git" P.</> annexLocation gc k hashDirLower
literalOsPath ".git" P.</> annexLocation gc k hashDirLower
{- Number of subdirectories from the gitAnnexObjectDir
- to the gitAnnexLocation. -}

View file

@ -22,6 +22,7 @@ import Database.Utility
import qualified Database.Queue as H
import Utility.InodeCache
import Git.FilePath
import Utility.OsPath
import Database.Persist.Sql hiding (Key)
import Database.Persist.TH
@ -84,7 +85,7 @@ addAssociatedFile k f = queueDb $
(Associated k af)
[AssociatedFile =. af, AssociatedKey =. k]
where
af = SByteString (getTopFilePath f)
af = SByteString (fromOsPath (getTopFilePath f))
-- Faster than addAssociatedFile, but only safe to use when the file
-- was not associated with a different key before, as it does not delete
@ -93,14 +94,14 @@ newAssociatedFile :: Key -> TopFilePath -> WriteHandle -> IO ()
newAssociatedFile k f = queueDb $
insert_ $ Associated k af
where
af = SByteString (getTopFilePath f)
af = SByteString (fromOsPath (getTopFilePath f))
{- Note that the files returned were once associated with the key, but
- some of them may not be any longer. -}
getAssociatedFiles :: Key -> ReadHandle -> IO [TopFilePath]
getAssociatedFiles k = readDb $ do
l <- selectList [AssociatedKey ==. k] []
return $ map (asTopFilePath . (\(SByteString f) -> f) . associatedFile . entityVal) l
return $ map (asTopFilePath . toOsPath . (\(SByteString f) -> f) . associatedFile . entityVal) l
{- Gets any keys that are on record as having a particular associated file.
- (Should be one or none.) -}
@ -109,13 +110,13 @@ getAssociatedKey f = readDb $ do
l <- selectList [AssociatedFile ==. af] []
return $ map (associatedKey . entityVal) l
where
af = SByteString (getTopFilePath f)
af = SByteString (fromOsPath (getTopFilePath f))
removeAssociatedFile :: Key -> TopFilePath -> WriteHandle -> IO ()
removeAssociatedFile k f = queueDb $
deleteWhere [AssociatedKey ==. k, AssociatedFile ==. af]
where
af = SByteString (getTopFilePath f)
af = SByteString (fromOsPath (getTopFilePath f))
addInodeCaches :: Key -> [InodeCache] -> WriteHandle -> IO ()
addInodeCaches k is = queueDb $

View file

@ -6,6 +6,7 @@
-}
{-# LANGUAGE DeriveGeneric, DeriveFunctor #-}
{-# LANGUAGE CPP #-}
module Types.Import where
@ -13,21 +14,27 @@ import qualified Data.ByteString as S
import Data.Char
import Control.DeepSeq
import GHC.Generics
#ifdef WITH_OSPATH
import qualified System.OsPath.Posix as Posix
import System.OsString.Internal.Types
#else
import qualified System.FilePath.Posix.ByteString as Posix
#endif
import Types.Export
import Utility.QuickCheck
import Utility.FileSystemEncoding
import Utility.OsPath
{- Location of content on a remote that can be imported.
- This is just an alias to ExportLocation, because both are referring to a
- location on the remote. -}
type ImportLocation = ExportLocation
mkImportLocation :: RawFilePath -> ImportLocation
mkImportLocation :: OsPath -> ImportLocation
mkImportLocation = mkExportLocation
fromImportLocation :: ImportLocation -> RawFilePath
fromImportLocation :: ImportLocation -> OsPath
fromImportLocation = fromExportLocation
{- An identifier for content stored on a remote that has been imported into
@ -95,11 +102,17 @@ data ImportableContentsChunk m info = ImportableContentsChunk
}
deriving (Functor)
newtype ImportChunkSubDir = ImportChunkSubDir { importChunkSubDir :: RawFilePath }
newtype ImportChunkSubDir = ImportChunkSubDir { importChunkSubDir :: OsPath }
importableContentsChunkFullLocation
:: ImportChunkSubDir
-> RawFilePath
-> OsPath
-> ImportLocation
importableContentsChunkFullLocation (ImportChunkSubDir root) loc =
#ifdef WITH_OSPATH
mkImportLocation $ toOsPath $ getPosixString $ Posix.combine
(PosixString $ fromOsPath root)
(PosixString $ fromOsPath loc)
#else
mkImportLocation $ Posix.combine root loc
#endif