From c3c8870752758672d867da28bff4a796159befe5 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 23 Jan 2025 11:07:29 -0400 Subject: [PATCH] add System.FilePath to this conversion It seems to make sense to convert both System.Directory and System.FilePath uses to OsPath in one go. This will generally look like replacing RawFilePath with OsPath in type signatures, and will be driven by the now absolutely massive pile of compile errors. Got a few modules building in this new regime. Sponsored-by: Jack Hill --- Build/TestConfig.hs | 8 ++++--- Common.hs | 1 - Git/Construct.hs | 4 ++-- Utility/OsPath.hs | 11 ++++++++++ Utility/Path.hs | 53 ++++++++++++++++++++------------------------- Utility/Tmp/Dir.hs | 22 +++++++++---------- 6 files changed, 53 insertions(+), 46 deletions(-) diff --git a/Build/TestConfig.hs b/Build/TestConfig.hs index 89a8027fa8..f20972fa8f 100644 --- a/Build/TestConfig.hs +++ b/Build/TestConfig.hs @@ -11,7 +11,6 @@ import Utility.SystemDirectory import Utility.OsPath import System.IO -import System.FilePath type ConfigKey = String data ConfigValue = @@ -106,8 +105,11 @@ findCmdPath k command = do ) where find d = - let f = d command - in ifM (doesFileExist (toOsPath f)) ( return (Just f), return Nothing ) + let f = toOsPath d toOsPath command + in ifM (doesFileExist f) + ( return (Just (fromOsPath f)) + , return Nothing + ) quiet :: String -> String quiet s = s ++ " >/dev/null 2>&1" diff --git a/Common.hs b/Common.hs index 71681275f9..fe322fa1c4 100644 --- a/Common.hs +++ b/Common.hs @@ -10,7 +10,6 @@ import Data.List as X hiding (head, tail, init, last) import Data.Monoid as X import Data.Default as X -import System.FilePath as X import System.IO as X hiding (FilePath) import System.Exit as X import System.PosixCompat.Files as X (FileStatus) diff --git a/Git/Construct.hs b/Git/Construct.hs index 76261cabf2..ac3c536cc9 100644 --- a/Git/Construct.hs +++ b/Git/Construct.hs @@ -64,11 +64,11 @@ fromPath dir -- When dir == "foo/.git", git looks for "foo/.git/.git", -- and failing that, uses "foo" as the repository. | (P.pathSeparator `B.cons` ".git") `B.isSuffixOf` canondir = - ifM (doesDirectoryExist $ fromRawFilePath dir ".git") + ifM (doesDirectoryExist $ fromOsPath dir ".git") ( ret dir , ret (P.takeDirectory canondir) ) - | otherwise = ifM (doesDirectoryExist (fromRawFilePath dir)) + | otherwise = ifM (doesDirectoryExist (fromOsPath dir)) ( checkGitDirFile dir >>= maybe (ret dir) (pure . newFrom) -- git falls back to dir.git when dir doesn't -- exist, as long as dir didn't end with a diff --git a/Utility/OsPath.hs b/Utility/OsPath.hs index 0567b647ab..99dcdf2180 100644 --- a/Utility/OsPath.hs +++ b/Utility/OsPath.hs @@ -13,17 +13,24 @@ module Utility.OsPath ( OsPath, OsString, + RawFilePath, literalOsPath, toOsPath, fromOsPath, + module X, + getSearchPath, ) where import Utility.FileSystemEncoding #ifdef WITH_OSPATH +import System.OsPath as X hiding (OsPath, OsString) import System.OsPath import "os-string" System.OsString.Internal.Types import qualified Data.ByteString.Short as S +import qualified System.FilePath.ByteString as PB #else +import System.FilePath.ByteString as X hiding (RawFilePath, getSearchPath) +import System.FilePath.ByteString (getSearchPath) import qualified Data.ByteString as S #endif @@ -61,6 +68,10 @@ bytesFromOsPath = S.fromShort . getWindowsString . getOsString bytesFromOsPath = S.fromShort . getPosixString . getOsString #endif +{- For some reason not included in System.OsPath -} +getSearchPath :: IO [OsPath] +getSearchPath = map toOsPath <$> PB.getSearchPath + #else {- When not building with WITH_OSPATH, use RawFilePath. -} diff --git a/Utility/Path.hs b/Utility/Path.hs index 493efcad1c..2a80d756be 100644 --- a/Utility/Path.hs +++ b/Utility/Path.hs @@ -27,13 +27,8 @@ module Utility.Path ( searchPathContents, ) where -import System.FilePath.ByteString -#ifdef WITH_OSPATH -import qualified System.OsPath as P -#else -import qualified System.FilePath.ByteString as P -#endif import qualified Data.ByteString as B +import qualified System.FilePath.ByteString as PB import Data.List import Data.Maybe import Control.Monad @@ -58,15 +53,15 @@ copyright = author JoeyHess (1996+14) - and removing the trailing path separator. - - On Windows, preserves whichever style of path separator might be used in - - the input RawFilePaths. This is done because some programs in Windows + - the input paths. This is done because some programs in Windows - demand a particular path separator -- and which one actually varies! - - This does not guarantee that two paths that refer to the same location, - and are both relative to the same location (or both absolute) will - - yield the same result. Run both through normalise from System.RawFilePath + - yield the same result. Run both through normalise from System.OsPath - to ensure that. -} -simplifyPath :: RawFilePath -> RawFilePath +simplifyPath :: OsPath -> OsPath simplifyPath path = dropTrailingPathSeparator $ joinDrive drive $ joinPath $ norm [] $ splitPath path' where @@ -82,27 +77,27 @@ simplifyPath path = dropTrailingPathSeparator $ p' = dropTrailingPathSeparator p {- takeDirectory "foo/bar/" is "foo/bar". This instead yields "foo" -} -parentDir :: RawFilePath -> RawFilePath +parentDir :: OsPath -> OsPath parentDir = takeDirectory . dropTrailingPathSeparator {- Just the parent directory of a path, or Nothing if the path has no - parent (ie for "/" or "." or "foo") -} -upFrom :: RawFilePath -> Maybe RawFilePath +upFrom :: OsPath -> Maybe OsPath upFrom dir | length dirs < 2 = Nothing - | otherwise = Just $ joinDrive drive $ + | otherwise = Just $ joinDrive drive $ toOsPath $ B.intercalate (B.singleton pathSeparator) $ init dirs where -- on Unix, the drive will be "/" when the dir is absolute, -- otherwise "" (drive, path) = splitDrive dir - dirs = filter (not . B.null) $ B.splitWith isPathSeparator path + dirs = filter (not . B.null) $ B.splitWith PB.isPathSeparator $ fromOsPath path -{- Checks if the first RawFilePath is, or could be said to contain the second. +{- Checks if the first path is, or could be said to contain the second. - For example, "foo/" contains "foo/bar". Also, "foo", "./foo", "foo/" etc - are all equivalent. -} -dirContains :: RawFilePath -> RawFilePath -> Bool +dirContains :: OsPath -> OsPath -> Bool dirContains a b = a == b || a' == b' || (a'' `B.isPrefixOf` b' && avoiddotdotb) @@ -124,7 +119,7 @@ dirContains a b = a == b - a'' is a prefix of b', so all that needs to be done is drop - that prefix, and check if the next path component is ".." -} - avoiddotdotb = nodotdot $ B.drop (B.length a'') b' + avoiddotdotb = nodotdot $ B.drop (B.length a'') $ fromOsPath b' nodotdot p = all (not . isdotdot) (splitPath p) @@ -161,10 +156,10 @@ dirContains a b = a == b - we stop preserving ordering at that point. Presumably a user passing - that many paths in doesn't care too much about order of the later ones. -} -segmentPaths :: (a -> RawFilePath) -> [RawFilePath] -> [a] -> [[a]] +segmentPaths :: (a -> OsPath) -> [OsPath] -> [a] -> [[a]] segmentPaths = segmentPaths' (\_ r -> r) -segmentPaths' :: (Maybe RawFilePath -> a -> r) -> (a -> RawFilePath) -> [RawFilePath] -> [a] -> [[r]] +segmentPaths' :: (Maybe OsPath -> a -> r) -> (a -> OsPath) -> [OsPath] -> [a] -> [[r]] segmentPaths' f _ [] new = [map (f Nothing) new] segmentPaths' f _ [i] new = [map (f (Just i)) new] -- optimisation segmentPaths' f c (i:is) new = @@ -179,15 +174,15 @@ segmentPaths' f c (i:is) new = - than it would be to run the action separately with each path. In - the case of git file list commands, that assumption tends to hold. -} -runSegmentPaths :: (a -> RawFilePath) -> ([RawFilePath] -> IO [a]) -> [RawFilePath] -> IO [[a]] +runSegmentPaths :: (a -> OsPath) -> ([OsPath] -> IO [a]) -> [OsPath] -> IO [[a]] runSegmentPaths c a paths = segmentPaths c paths <$> a paths -runSegmentPaths' :: (Maybe RawFilePath -> a -> r) -> (a -> RawFilePath) -> ([RawFilePath] -> IO [a]) -> [RawFilePath] -> IO [[r]] +runSegmentPaths' :: (Maybe OsPath -> a -> r) -> (a -> OsPath) -> ([OsPath] -> IO [a]) -> [OsPath] -> IO [[r]] runSegmentPaths' si c a paths = segmentPaths' si c paths <$> a paths {- Checks if a filename is a unix dotfile. All files inside dotdirs - count as dotfiles. -} -dotfile :: RawFilePath -> Bool +dotfile :: OsPath -> Bool dotfile file | f == "." = False | f == ".." = False @@ -196,11 +191,11 @@ dotfile file where f = takeFileName file -{- Similar to splitExtensions, but knows that some things in RawFilePaths +{- Similar to splitExtensions, but knows that some things in paths - after a dot are too long to be extensions. -} -splitShortExtensions :: RawFilePath -> (RawFilePath, [B.ByteString]) +splitShortExtensions :: OsPath -> (OsPath, [B.ByteString]) splitShortExtensions = splitShortExtensions' 5 -- enough for ".jpeg" -splitShortExtensions' :: Int -> RawFilePath -> (RawFilePath, [B.ByteString]) +splitShortExtensions' :: Int -> OsPath -> (OsPath, [B.ByteString]) splitShortExtensions' maxextension = go [] where go c f @@ -217,7 +212,7 @@ splitShortExtensions' maxextension = go [] - a relative path is not possible and the path is simply - returned as-is. -} -relPathDirToFileAbs :: RawFilePath -> RawFilePath -> RawFilePath +relPathDirToFileAbs :: OsPath -> OsPath -> OsPath relPathDirToFileAbs from to #ifdef mingw32_HOST_OS | normdrive from /= normdrive to = to @@ -238,7 +233,7 @@ relPathDirToFileAbs from to -- path separator, which takeDrive leaves on the drive -- letter. . dropWhileEnd (isPathSeparator . fromIntegral . ord) - . fromRawFilePath + . fromOsPath . takeDrive #endif @@ -258,11 +253,11 @@ inSearchPath command = isJust <$> searchPath command -} searchPath :: String -> IO (Maybe OsPath) searchPath command - | P.isAbsolute command' = copyright $ check command' + | isAbsolute command' = copyright $ check command' | otherwise = getSearchPath >>= getM indir . map toOsPath where command' = toOsPath command - indir d = check (d P. command') + indir d = check (d command') check f = firstM doesFileExist #ifdef mingw32_HOST_OS [f, f <> ".exe"] @@ -281,5 +276,5 @@ searchPathContents p = filterM doesFileExist =<< (concat <$> (getSearchPath >>= mapM (go . toOsPath))) where - go d = map (d P.) . filter p + go d = map (d ) . filter p <$> catchDefaultIO [] (getDirectoryContents d) diff --git a/Utility/Tmp/Dir.hs b/Utility/Tmp/Dir.hs index c359b9d82d..fa61d30f5b 100644 --- a/Utility/Tmp/Dir.hs +++ b/Utility/Tmp/Dir.hs @@ -1,6 +1,6 @@ {- Temporary directories - - - Copyright 2010-2022 Joey Hess + - Copyright 2010-2025 Joey Hess - - License: BSD-2-clause -} @@ -14,8 +14,6 @@ module Utility.Tmp.Dir ( ) where import Control.Monad.IfElse -import System.FilePath -import System.Directory import Control.Monad.IO.Class #ifndef mingw32_HOST_OS import System.Posix.Temp (mkdtemp) @@ -24,18 +22,20 @@ import System.Posix.Temp (mkdtemp) import Utility.Exception import Utility.Tmp (Template) import Utility.OsPath -import Utility.FileSystemEncoding +import Utility.SystemDirectory {- Runs an action with a tmp directory located within the system's tmp - directory (or within "." if there is none), then removes the tmp - directory and all its contents. -} -withTmpDir :: (MonadMask m, MonadIO m) => Template -> (FilePath -> m a) -> m a +withTmpDir :: (MonadMask m, MonadIO m) => Template -> (OsPath -> m a) -> m a withTmpDir template a = do - topleveltmpdir <- liftIO $ catchDefaultIO "." getTemporaryDirectory + topleveltmpdir <- liftIO $ + catchDefaultIO (literalOsPath ".") getTemporaryDirectory + let p = fromOsPath $ topleveltmpdir template #ifndef mingw32_HOST_OS -- Use mkdtemp to create a temp directory securely in /tmp. bracket - (liftIO $ mkdtemp $ topleveltmpdir fromRawFilePath (fromOsPath template)) + (liftIO $ toOsPath <$> mkdtemp p) removeTmpDir a #else @@ -44,21 +44,21 @@ withTmpDir template a = do {- Runs an action with a tmp directory located within a specified directory, - then removes the tmp directory and all its contents. -} -withTmpDirIn :: (MonadMask m, MonadIO m) => FilePath -> Template -> (FilePath -> m a) -> m a +withTmpDirIn :: (MonadMask m, MonadIO m) => OsPath -> Template -> (OsPath -> m a) -> m a withTmpDirIn tmpdir template = bracketIO create removeTmpDir where create = do createDirectoryIfMissing True tmpdir - makenewdir (tmpdir fromRawFilePath (fromOsPath template)) (0 :: Int) + makenewdir (tmpdir template) (0 :: Int) makenewdir t n = do - let dir = t ++ "." ++ show n + let dir = t <> toOsPath ("." ++ show n) catchIOErrorType AlreadyExists (const $ makenewdir t $ n + 1) $ do createDirectory dir return dir {- Deletes the entire contents of the the temporary directory, if it - exists. -} -removeTmpDir :: MonadIO m => FilePath -> m () +removeTmpDir :: MonadIO m => OsPath -> m () removeTmpDir tmpdir = liftIO $ whenM (doesDirectoryExist tmpdir) $ do #if mingw32_HOST_OS -- Windows will often refuse to delete a file