git-annex/Git/FilePath.hs
Joey Hess 2ba1559a8e
git style quoting for ActionItemOther
Added StringContainingQuotedPath, which is used for ActionItemOther.

In the process, checked every ActionItemOther for those containing
filenames, and made them use quoting.

Sponsored-by: Graham Spencer on Patreon
2023-04-08 16:30:01 -04:00

97 lines
2.8 KiB
Haskell

{- git FilePath library
-
- Different git commands use different types of FilePaths to refer to
- files in the repository. Some commands use paths relative to the
- top of the repository even when run in a subdirectory. Adding some
- types helps keep that straight.
-
- Copyright 2012-2023 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
module Git.FilePath (
TopFilePath,
BranchFilePath(..),
descBranchFilePath,
getTopFilePath,
fromTopFilePath,
toTopFilePath,
asTopFilePath,
InternalGitPath,
toInternalGitPath,
fromInternalGitPath,
absoluteGitPath
) where
import Common
import Git
import qualified Git.Filename as Filename
import qualified System.FilePath.ByteString as P
import qualified System.FilePath.Posix.ByteString
import GHC.Generics
import Control.DeepSeq
import qualified Data.ByteString as S
{- A RawFilePath, relative to the top of the git repository. -}
newtype TopFilePath = TopFilePath { getTopFilePath :: RawFilePath }
deriving (Show, Eq, Ord, Generic)
instance NFData TopFilePath
{- A file in a branch or other treeish. -}
data BranchFilePath = BranchFilePath Ref TopFilePath
deriving (Show, Eq, Ord)
{- Git uses the branch:file form to refer to a BranchFilePath -}
descBranchFilePath :: Filename.QuotePath -> BranchFilePath -> S.ByteString
descBranchFilePath qp (BranchFilePath b f) =
fromRef' b <> ":" <> Filename.quote qp (getTopFilePath f)
{- Path to a TopFilePath, within the provided git repo. -}
fromTopFilePath :: TopFilePath -> Git.Repo -> RawFilePath
fromTopFilePath p repo = P.combine (repoPath repo) (getTopFilePath p)
{- The input FilePath can be absolute, or relative to the CWD. -}
toTopFilePath :: RawFilePath -> Git.Repo -> IO TopFilePath
toTopFilePath file repo = TopFilePath <$> relPathDirToFile (repoPath repo) file
{- The input RawFilePath must already be relative to the top of the git
- repository -}
asTopFilePath :: RawFilePath -> TopFilePath
asTopFilePath file = TopFilePath file
{- Git may use a different representation of a path when storing
- it internally.
-
- On Windows, git uses '/' to separate paths stored in the repository,
- despite Windows using '\'.
-
-}
type InternalGitPath = RawFilePath
toInternalGitPath :: RawFilePath -> InternalGitPath
#ifndef mingw32_HOST_OS
toInternalGitPath = id
#else
toInternalGitPath = encodeBS . replace "\\" "/" . decodeBS
#endif
fromInternalGitPath :: InternalGitPath -> RawFilePath
#ifndef mingw32_HOST_OS
fromInternalGitPath = id
#else
fromInternalGitPath = encodeBS . replace "/" "\\" . decodeBS
#endif
{- isAbsolute on Windows does not think "/foo" or "\foo" is absolute,
- so try posix paths.
-}
absoluteGitPath :: RawFilePath -> Bool
absoluteGitPath p = P.isAbsolute p ||
System.FilePath.Posix.ByteString.isAbsolute (toInternalGitPath p)