more OsPath conversion

Sponsored-by: Brock Spratlen
This commit is contained in:
Joey Hess 2025-02-01 11:54:19 -04:00
parent c69e57aede
commit 474cf3bc8b
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
38 changed files with 342 additions and 330 deletions

View file

@ -52,7 +52,7 @@ instance APIVersion V0 where protocolVersion _ = P2P.ProtocolVersion 0
newtype B64Key = B64Key Key
deriving (Show)
newtype B64FilePath = B64FilePath RawFilePath
newtype B64FilePath = B64FilePath OsPath
deriving (Show)
associatedFileToB64FilePath :: AssociatedFile -> Maybe B64FilePath
@ -233,11 +233,11 @@ instance FromHttpApiData (B64UUID t) where
Left err -> Left err
instance ToHttpApiData B64FilePath where
toUrlPiece (B64FilePath f) = encodeB64Text f
toUrlPiece (B64FilePath f) = encodeB64Text (fromOsPath f)
instance FromHttpApiData B64FilePath where
parseUrlPiece t = case decodeB64Text t of
Right b -> Right (B64FilePath b)
Right b -> Right (B64FilePath (toOsPath b))
Left err -> Left err
instance ToHttpApiData Offset where

View file

@ -175,7 +175,7 @@ serveUnixSocket unixsocket serveconn = do
-- Connections have to authenticate to do anything,
-- so it's fine that other local users can connect to the
-- socket.
modifyFileMode (toRawFilePath unixsocket) $ addModes
modifyFileMode (toOsPath unixsocket) $ addModes
[groupReadMode, groupWriteMode, otherReadMode, otherWriteMode]
S.listen soc 2
forever $ do
@ -381,7 +381,7 @@ runRelayService conn runner service = case connRepo conn of
serviceproc repo = gitCreateProcess
[ Param cmd
, File (fromRawFilePath (repoPath repo))
, File (fromOsPath (repoPath repo))
] repo
serviceproc' repo = (serviceproc repo)
{ std_out = CreatePipe

View file

@ -10,6 +10,7 @@
{-# LANGUAGE DeriveFunctor, TemplateHaskell, FlexibleContexts #-}
{-# LANGUAGE TypeSynonymInstances, FlexibleInstances, RankNTypes #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module P2P.Protocol where
@ -25,8 +26,9 @@ import Utility.AuthToken
import Utility.Applicative
import Utility.PartialPrelude
import Utility.Metered
import Utility.FileSystemEncoding
import Utility.MonotonicClock
import Utility.OsPath
import qualified Utility.OsString as OS
import Git.FilePath
import Annex.ChangedRefs (ChangedRefs)
import Types.NumCopies
@ -37,8 +39,6 @@ import Control.Monad.Free.TH
import Control.Monad.Catch
import System.Exit (ExitCode(..))
import System.IO
import qualified System.FilePath.ByteString as P
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as L
import qualified Data.Set as S
import Data.Char
@ -224,17 +224,19 @@ instance Proto.Serializable Service where
instance Proto.Serializable ProtoAssociatedFile where
serialize (ProtoAssociatedFile (AssociatedFile Nothing)) = ""
serialize (ProtoAssociatedFile (AssociatedFile (Just af))) =
decodeBS $ toInternalGitPath $ encodeBS $ concatMap esc $ fromRawFilePath af
fromOsPath $ toInternalGitPath $
OS.concat $ map esc $ OS.unpack af
where
esc '%' = "%%"
esc c
| isSpace c = "%"
| otherwise = [c]
esc c = case OS.toChar c of
'%' -> literalOsPath "%%"
c' | isSpace c' -> literalOsPath "%"
_ -> OS.singleton c
deserialize s = case fromInternalGitPath $ toRawFilePath $ deesc [] s of
deserialize s = case fromInternalGitPath $ toOsPath $ deesc [] s of
f
| B.null f -> Just $ ProtoAssociatedFile $ AssociatedFile Nothing
| P.isRelative f -> Just $ ProtoAssociatedFile $
| OS.null f -> Just $ ProtoAssociatedFile $
AssociatedFile Nothing
| isRelative f -> Just $ ProtoAssociatedFile $
AssociatedFile $ Just f
| otherwise -> Nothing
where