more OsPath conversion

Sponsored-by: Kevin Mueller
This commit is contained in:
Joey Hess 2025-01-29 16:24:51 -04:00
parent c309edb8fb
commit a9f3a31a52
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
6 changed files with 41 additions and 39 deletions

View file

@ -42,12 +42,11 @@ import qualified Utility.FileIO as F
import qualified Data.ByteString.Lazy.Char8 as L8 import qualified Data.ByteString.Lazy.Char8 as L8
import qualified Data.ByteString.Char8 as S8 import qualified Data.ByteString.Char8 as S8
import qualified Data.Map as M import qualified Data.Map as M
import qualified System.FilePath.ByteString as P
{- A CredPair can be stored in a file, or in the environment, or {- A CredPair can be stored in a file, or in the environment, or
- in a remote's configuration. -} - in a remote's configuration. -}
data CredPairStorage = CredPairStorage data CredPairStorage = CredPairStorage
{ credPairFile :: FilePath { credPairFile :: OsPath
, credPairEnvironment :: (String, String) , credPairEnvironment :: (String, String)
, credPairRemoteField :: RemoteConfigField , credPairRemoteField :: RemoteConfigField
} }
@ -196,21 +195,21 @@ existsCacheCredPair storage =
{- Stores the creds in a file inside gitAnnexCredsDir that only the user {- Stores the creds in a file inside gitAnnexCredsDir that only the user
- can read. -} - can read. -}
writeCreds :: Creds -> FilePath -> Annex () writeCreds :: Creds -> OsPath -> Annex ()
writeCreds creds file = do writeCreds creds file = do
d <- fromRepo gitAnnexCredsDir d <- fromRepo gitAnnexCredsDir
createAnnexDirectory d createAnnexDirectory d
liftIO $ writeFileProtected (d P.</> toRawFilePath file) creds liftIO $ writeFileProtected (d </> file) creds
readCreds :: FilePath -> Annex (Maybe Creds) readCreds :: OsPath -> Annex (Maybe Creds)
readCreds f = do readCreds f = do
f' <- toOsPath . toRawFilePath <$> credsFile f f' <- credsFile f
liftIO $ catchMaybeIO $ decodeBS . S8.unlines . fileLines' liftIO $ catchMaybeIO $ decodeBS . S8.unlines . fileLines'
<$> F.readFile' f' <$> F.readFile' f'
credsFile :: FilePath -> Annex FilePath credsFile :: OsPath -> Annex OsPath
credsFile basefile = do credsFile basefile = do
d <- fromRawFilePath <$> fromRepo gitAnnexCredsDir d <- fromRepo gitAnnexCredsDir
return $ d </> basefile return $ d </> basefile
encodeCredPair :: CredPair -> Creds encodeCredPair :: CredPair -> Creds
@ -221,10 +220,10 @@ decodeCredPair creds = case lines creds of
l:p:[] -> Just (l, p) l:p:[] -> Just (l, p)
_ -> Nothing _ -> Nothing
removeCreds :: FilePath -> Annex () removeCreds :: OsPath -> Annex ()
removeCreds file = do removeCreds file = do
d <- fromRepo gitAnnexCredsDir d <- fromRepo gitAnnexCredsDir
liftIO $ removeWhenExistsWith R.removeLink (d P.</> toRawFilePath file) liftIO $ removeWhenExistsWith R.removeLink (fromOsPath (d </> file))
includeCredsInfo :: ParsedRemoteConfig -> CredPairStorage -> [(String, String)] -> Annex [(String, String)] includeCredsInfo :: ParsedRemoteConfig -> CredPairStorage -> [(String, String)] -> Annex [(String, String)]
includeCredsInfo pc@(ParsedRemoteConfig cm _) storage info = do includeCredsInfo pc@(ParsedRemoteConfig cm _) storage info = do

View file

@ -26,13 +26,12 @@ import qualified Data.ByteString.Short as S (toShort)
import qualified Data.ByteString.Char8 as B8 import qualified Data.ByteString.Char8 as B8
import System.Random import System.Random
import Control.Concurrent import Control.Concurrent
import qualified System.FilePath.ByteString as P
#endif #endif
benchmarkDbs :: CriterionMode -> Integer -> Annex () benchmarkDbs :: CriterionMode -> Integer -> Annex ()
#ifdef WITH_BENCHMARK #ifdef WITH_BENCHMARK
benchmarkDbs mode n = withTmpDirIn "." (toOsPath "benchmark") $ \tmpdir -> do benchmarkDbs mode n = withTmpDirIn (literalOsPath ".") (literalOsPath "benchmark") $ \tmpdir -> do
db <- benchDb (toRawFilePath tmpdir) n db <- benchDb tmpdir n
liftIO $ runMode mode liftIO $ runMode mode
[ bgroup "keys database" [ bgroup "keys database"
[ getAssociatedFilesHitBench db [ getAssociatedFilesHitBench db
@ -93,7 +92,7 @@ keyN n = mkKey $ \k -> k
} }
fileN :: Integer -> TopFilePath fileN :: Integer -> TopFilePath
fileN n = asTopFilePath (toRawFilePath ("file" ++ show n)) fileN n = asTopFilePath (toOsPath ("file" ++ show n))
keyMiss :: Key keyMiss :: Key
keyMiss = keyN 0 -- 0 is never stored keyMiss = keyN 0 -- 0 is never stored
@ -103,7 +102,7 @@ fileMiss = fileN 0 -- 0 is never stored
data BenchDb = BenchDb H.DbQueue Integer (MVar Integer) data BenchDb = BenchDb H.DbQueue Integer (MVar Integer)
benchDb :: RawFilePath -> Integer -> Annex BenchDb benchDb :: OsPath -> Integer -> Annex BenchDb
benchDb tmpdir num = do benchDb tmpdir num = do
liftIO $ putStrLn $ "setting up database with " ++ show num ++ " items" liftIO $ putStrLn $ "setting up database with " ++ show num ++ " items"
initDb db SQL.createTables initDb db SQL.createTables
@ -115,6 +114,6 @@ benchDb tmpdir num = do
mv <- liftIO $ newMVar 1 mv <- liftIO $ newMVar 1
return (BenchDb h num mv) return (BenchDb h num mv)
where where
db = tmpdir P.</> toRawFilePath (show num </> "db") db = tmpdir </> toOsPath (show num) </> literalOsPath "db"
#endif /* WITH_BENCHMARK */ #endif /* WITH_BENCHMARK */

View file

@ -20,7 +20,6 @@ import Database.RawFilePath
import Database.Persist.Sqlite import Database.Persist.Sqlite
import Lens.Micro import Lens.Micro
import qualified Data.Text as T import qualified Data.Text as T
import qualified System.FilePath.ByteString as P
{- Ensures that the database is freshly initialized. Deletes any {- Ensures that the database is freshly initialized. Deletes any
- existing database. Pass the migration action for the database. - existing database. Pass the migration action for the database.
@ -30,26 +29,26 @@ import qualified System.FilePath.ByteString as P
- file causes Sqlite to always use the same permissions for additional - file causes Sqlite to always use the same permissions for additional
- files it writes later on - files it writes later on
-} -}
initDb :: P.RawFilePath -> SqlPersistM () -> Annex () initDb :: OsPath -> SqlPersistM () -> Annex ()
initDb db migration = do initDb db migration = do
let dbdir = P.takeDirectory db let dbdir = takeDirectory db
let tmpdbdir = dbdir <> ".tmp" let tmpdbdir = dbdir <> literalOsPath ".tmp"
let tmpdb = tmpdbdir P.</> "db" let tmpdb = tmpdbdir </> literalOsPath "db"
let tmpdb' = T.pack (fromRawFilePath tmpdb) let tmpdb' = fromOsPath tmpdb
createAnnexDirectory tmpdbdir createAnnexDirectory tmpdbdir
#if MIN_VERSION_persistent_sqlite(2,13,3) #if MIN_VERSION_persistent_sqlite(2,13,3)
liftIO $ runSqliteInfo' tmpdb (enableWAL tmpdb') migration liftIO $ runSqliteInfo' tmpdb' (enableWAL tmpdb') migration
#else #else
liftIO $ runSqliteInfo (enableWAL tmpdb') migration liftIO $ runSqliteInfo (enableWAL tmpdb') migration
#endif #endif
setAnnexDirPerm tmpdbdir setAnnexDirPerm tmpdbdir
-- Work around sqlite bug that prevents it from honoring -- Work around sqlite bug that prevents it from honoring
-- less restrictive umasks. -- less restrictive umasks.
liftIO $ R.setFileMode tmpdb =<< defaultFileMode liftIO $ R.setFileMode tmpdb' =<< defaultFileMode
setAnnexFilePerm tmpdb setAnnexFilePerm tmpdb
liftIO $ do liftIO $ do
void $ tryIO $ removeDirectoryRecursive (fromRawFilePath dbdir) void $ tryIO $ removeDirectoryRecursive dbdir
R.rename tmpdbdir dbdir R.rename (fromOsPath tmpdbdir) (fromOsPath dbdir)
{- Make sure that the database uses WAL mode, to prevent readers {- Make sure that the database uses WAL mode, to prevent readers
- from blocking writers, and prevent a writer from blocking readers. - from blocking writers, and prevent a writer from blocking readers.
@ -59,6 +58,6 @@ initDb db migration = do
- -
- Note that once WAL mode is enabled, it will persist whenever the - Note that once WAL mode is enabled, it will persist whenever the
- database is opened. -} - database is opened. -}
enableWAL :: T.Text -> SqliteConnectionInfo enableWAL :: RawFilePath -> SqliteConnectionInfo
enableWAL db = over walEnabled (const True) $ enableWAL db = over walEnabled (const True) $
mkSqliteConnectionInfo db mkSqliteConnectionInfo (T.pack (fromRawFilePath db))

View file

@ -5,6 +5,8 @@
- Licensed under the GNU AGPL version 3 or higher. - Licensed under the GNU AGPL version 3 or higher.
-} -}
{-# LANGUAGE OverloadedStrings #-}
module P2P.Address where module P2P.Address where
import qualified Annex import qualified Annex
@ -75,24 +77,24 @@ storeP2PAddress addr = do
addrs <- loadP2PAddresses addrs <- loadP2PAddresses
unless (addr `elem` addrs) $ do unless (addr `elem` addrs) $ do
let s = unlines $ map formatP2PAddress (addr:addrs) let s = unlines $ map formatP2PAddress (addr:addrs)
let tmpnam = p2pAddressCredsFile ++ ".new" let tmpnam = p2pAddressCredsFile <> literalOsPath ".new"
writeCreds s tmpnam writeCreds s tmpnam
tmpf <- credsFile tmpnam tmpf <- credsFile tmpnam
destf <- credsFile p2pAddressCredsFile destf <- credsFile p2pAddressCredsFile
-- This may be run by root, so make the creds file -- This may be run by root, so make the creds file
-- and directory have the same owner and group as -- and directory have the same owner and group as
-- the git repository directory has. -- the git repository directory has.
st <- liftIO . R.getFileStatus . toRawFilePath st <- liftIO . R.getFileStatus . fromOsPath
=<< Annex.fromRepo repoLocation =<< Annex.fromRepo repoPath
let fixowner f = R.setOwnerAndGroup (toRawFilePath f) (fileOwner st) (fileGroup st) let fixowner f = R.setOwnerAndGroup (fromOsPath f) (fileOwner st) (fileGroup st)
liftIO $ do liftIO $ do
fixowner tmpf fixowner tmpf
fixowner (takeDirectory tmpf) fixowner (takeDirectory tmpf)
fixowner (takeDirectory (takeDirectory tmpf)) fixowner (takeDirectory (takeDirectory tmpf))
renameFile tmpf destf renameFile tmpf destf
p2pAddressCredsFile :: FilePath p2pAddressCredsFile :: OsPath
p2pAddressCredsFile = "p2paddrs" p2pAddressCredsFile = literalOsPath "p2paddrs"
torAppName :: AppName torAppName :: AppName
torAppName = "tor-annex" torAppName = "tor-annex"

View file

@ -5,6 +5,8 @@
- Licensed under the GNU AGPL version 3 or higher. - Licensed under the GNU AGPL version 3 or higher.
-} -}
{-# LANGUAGE OverloadedStrings #-}
module P2P.Auth where module P2P.Auth where
import Annex.Common import Annex.Common
@ -35,8 +37,8 @@ storeP2PAuthToken t = do
let d = unlines $ map (T.unpack . fromAuthToken) (t:ts) let d = unlines $ map (T.unpack . fromAuthToken) (t:ts)
writeCreds d p2pAuthCredsFile writeCreds d p2pAuthCredsFile
p2pAuthCredsFile :: FilePath p2pAuthCredsFile :: OsPath
p2pAuthCredsFile = "p2pauth" p2pAuthCredsFile = literalOsPath "p2pauth"
-- | Loads the AuthToken to use when connecting with a given P2P address. -- | Loads the AuthToken to use when connecting with a given P2P address.
-- --
@ -59,8 +61,9 @@ storeP2PRemoteAuthToken addr t = writeCreds
(T.unpack $ fromAuthToken t) (T.unpack $ fromAuthToken t)
(addressCredsFile addr) (addressCredsFile addr)
addressCredsFile :: P2PAddress -> FilePath addressCredsFile :: P2PAddress -> OsPath
-- We can omit the port and just use the onion address for the creds file, -- We can omit the port and just use the onion address for the creds file,
-- because any given tor hidden service runs on a single port and has a -- because any given tor hidden service runs on a single port and has a
-- unique onion address. -- unique onion address.
addressCredsFile (TorAnnex (OnionAddress onionaddr) _port) = onionaddr addressCredsFile (TorAnnex (OnionAddress onionaddr) _port) =
toOsPath onionaddr

View file

@ -23,7 +23,7 @@ import Data.Text (Text)
creds :: UUID -> CredPairStorage creds :: UUID -> CredPairStorage
creds u = CredPairStorage creds u = CredPairStorage
{ credPairFile = fromUUID u { credPairFile = literalOsPath (fromUUID u)
, credPairEnvironment = ("AWS_ACCESS_KEY_ID", "AWS_SECRET_ACCESS_KEY") , credPairEnvironment = ("AWS_ACCESS_KEY_ID", "AWS_SECRET_ACCESS_KEY")
, credPairRemoteField = s3credsField , credPairRemoteField = s3credsField
} }