OsPath conversion

Decent win in exportDirectories, since it operates on ShortByteString
end to end now without needing conversion. That made it worth
implementing an OsPath specific code path there.

And ExportLocation already being a ShortByteString is an good example of why
it's a good thing that OsPath uses that!

Sponsored-by: k0ld on Patreon
This commit is contained in:
Joey Hess 2025-01-25 11:53:47 -04:00
parent 0cfeea5baf
commit 5bca78b813
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38

View file

@ -1,11 +1,12 @@
{- git-annex export types {- git-annex export types
- -
- Copyright 2017-2021 Joey Hess <id@joeyh.name> - Copyright 2017-2025 Joey Hess <id@joeyh.name>
- -
- Licensed under the GNU AGPL version 3 or higher. - Licensed under the GNU AGPL version 3 or higher.
-} -}
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE CPP #-}
module Types.Export ( module Types.Export (
ExportLocation, ExportLocation,
@ -19,48 +20,63 @@ module Types.Export (
import Git.FilePath import Git.FilePath
import Utility.Split import Utility.Split
import Utility.FileSystemEncoding import Utility.OsPath
import qualified Data.ByteString.Short as S
import qualified System.FilePath.Posix as Posix
import GHC.Generics import GHC.Generics
import Control.DeepSeq import Control.DeepSeq
#ifdef WITH_OSPATH
import qualified System.OsPath.Posix as Posix
import System.OsString.Internal.Types
#else
import qualified System.FilePath.Posix as Posix
import Utility.FileSystemEncoding
#endif
-- A location such as a path on a remote, that a key can be exported to. -- A location such as a path on a remote, that a key can be exported to.
-- The path is relative to the top of the remote, and uses unix-style -- The path is relative to the top of the remote, and uses unix-style
-- path separators. -- path separators.
-- --
-- This uses a ShortByteString to avoid problems with ByteString getting -- This must be a ShortByteString (which OsPath is) in order to to avoid
-- PINNED in memory which caused memory fragmentation and excessive memory -- problems with ByteString getting PINNED in memory which caused memory
-- use. -- fragmentation and excessive memory use.
newtype ExportLocation = ExportLocation S.ShortByteString newtype ExportLocation = ExportLocation OsPath
deriving (Show, Eq, Generic, Ord) deriving (Show, Eq, Generic, Ord)
instance NFData ExportLocation instance NFData ExportLocation
mkExportLocation :: RawFilePath -> ExportLocation mkExportLocation :: OsPath -> ExportLocation
mkExportLocation = ExportLocation . S.toShort . toInternalGitPath mkExportLocation = ExportLocation . toInternalGitPath
fromExportLocation :: ExportLocation -> RawFilePath fromExportLocation :: ExportLocation -> OsPath
fromExportLocation (ExportLocation f) = S.fromShort f fromExportLocation (ExportLocation f) = f
newtype ExportDirectory = ExportDirectory RawFilePath newtype ExportDirectory = ExportDirectory OsPath
deriving (Show, Eq) deriving (Show, Eq)
mkExportDirectory :: RawFilePath -> ExportDirectory mkExportDirectory :: OsPath -> ExportDirectory
mkExportDirectory = ExportDirectory . toInternalGitPath mkExportDirectory = ExportDirectory . toInternalGitPath
fromExportDirectory :: ExportDirectory -> RawFilePath fromExportDirectory :: ExportDirectory -> OsPath
fromExportDirectory (ExportDirectory f) = f fromExportDirectory (ExportDirectory f) = f
-- | All subdirectories down to the ExportLocation, with the deepest ones -- | All subdirectories down to the ExportLocation, with the deepest ones
-- last. Does not include the top of the export. -- last. Does not include the top of the export.
exportDirectories :: ExportLocation -> [ExportDirectory] exportDirectories :: ExportLocation -> [ExportDirectory]
exportDirectories (ExportLocation f) = exportDirectories (ExportLocation f) =
map (ExportDirectory . encodeBS . Posix.joinPath . reverse) (subs [] dirs) map (ExportDirectory . fromposixpath . Posix.joinPath . reverse)
(subs [] dirs)
where where
subs _ [] = [] subs _ [] = []
subs ps (d:ds) = (d:ps) : subs (d:ps) ds subs ps (d:ds) = (d:ps) : subs (d:ps) ds
#ifdef WITH_OSPATH
dirs = map Posix.dropTrailingPathSeparator $ dirs = map Posix.dropTrailingPathSeparator $
dropFromEnd 1 $ Posix.splitPath $ decodeBS $ S.fromShort f dropFromEnd 1 $ Posix.splitPath $ PosixString $ fromOsPath f
fromposixpath = toOsPath . getPosixString
#else
dirs = map Posix.dropTrailingPathSeparator $
dropFromEnd 1 $ Posix.splitPath $ fromOsPath f
fromposixpath = encodeBS
#endif