more OsPath conversion

Sponsored-by: Nicholas Golder-Manning
This commit is contained in:
Joey Hess 2025-01-29 11:53:20 -04:00
parent 0376bc5ee0
commit 27305042f3
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
24 changed files with 180 additions and 153 deletions

View file

@ -5,6 +5,7 @@
- Licensed under the GNU AGPL version 3 or higher.
-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE CPP #-}
module Annex.View.ViewedFile (
@ -20,13 +21,14 @@ module Annex.View.ViewedFile (
import Annex.Common
import Utility.QuickCheck
import Backend.Utilities (maxExtensions)
import qualified Utility.OsString as OS
import qualified Data.ByteString as S
type FileName = String
type ViewedFile = FileName
type MkViewedFile = FilePath -> ViewedFile
type MkViewedFile = OsPath -> ViewedFile
{- Converts a filepath used in a reference branch to the
- filename that will be used in the view.
@ -44,23 +46,26 @@ viewedFileFromReference g = viewedFileFromReference'
viewedFileFromReference' :: Maybe Int -> Maybe Int -> MkViewedFile
viewedFileFromReference' maxextlen maxextensions f = concat $
[ escape (fromRawFilePath base')
, if null dirs then "" else "_%" ++ intercalate "%" (map escape dirs) ++ "%"
[ escape (fromOsPath base')
, if null dirs
then ""
else "_%" ++ intercalate "%" (map (escape . fromOsPath) dirs) ++ "%"
, escape $ fromRawFilePath $ S.concat extensions'
]
where
(path, basefile) = splitFileName f
dirs = filter (/= ".") $ map dropTrailingPathSeparator (splitPath path)
dirs = filter (/= literalOsPath ".") $
map dropTrailingPathSeparator (splitPath path)
(base, extensions) = case maxextlen of
Nothing -> splitShortExtensions (toRawFilePath basefile')
Just n -> splitShortExtensions' (n+1) (toRawFilePath basefile')
Nothing -> splitShortExtensions basefile'
Just n -> splitShortExtensions' (n+1) basefile'
{- Limit number of extensions. -}
maxextensions' = fromMaybe maxExtensions maxextensions
(base', extensions')
| length extensions <= maxextensions' = (base, extensions)
| otherwise =
let (es,more) = splitAt maxextensions' (reverse extensions)
in (base <> mconcat (reverse more), reverse es)
in (base <> toOsPath (mconcat (reverse more)), reverse es)
{- On Windows, if the filename looked like "dir/c:foo" then
- basefile would look like it contains a drive letter, which will
- not work. There cannot really be a filename like that, probably,
@ -85,12 +90,12 @@ escchar = '!'
{- For use when operating already within a view, so whatever filepath
- is present in the work tree is already a ViewedFile. -}
viewedFileReuse :: MkViewedFile
viewedFileReuse = takeFileName
viewedFileReuse = fromOsPath . takeFileName
{- Extracts from a ViewedFile the directory where the file is located on
- in the reference branch. -}
dirFromViewedFile :: ViewedFile -> FilePath
dirFromViewedFile = joinPath . drop 1 . sep [] ""
dirFromViewedFile = fromOsPath . joinPath . map toOsPath . drop 1 . sep [] ""
where
sep l _ [] = reverse l
sep l curr (c:cs)
@ -103,10 +108,10 @@ dirFromViewedFile = joinPath . drop 1 . sep [] ""
prop_viewedFile_roundtrips :: TestableFilePath -> Bool
prop_viewedFile_roundtrips tf
-- Relative filenames wanted, not directories.
| any (isPathSeparator) (end f ++ beginning f) = True
| isAbsolute f || isDrive f = True
| otherwise = dir == dirFromViewedFile
(viewedFileFromReference' Nothing Nothing f)
| OS.any isPathSeparator (toOsPath (end f ++ beginning f)) = True
| isAbsolute (toOsPath f) || isDrive (toOsPath f) = True
| otherwise = fromOsPath dir == dirFromViewedFile
(viewedFileFromReference' Nothing Nothing (toOsPath f))
where
f = fromTestableFilePath tf
dir = joinPath $ beginning $ splitDirectories f
dir = joinPath $ beginning $ splitDirectories (toOsPath f)