summaryrefslogtreecommitdiff
path: root/Git/FilePath.hs
diff options
context:
space:
mode:
Diffstat (limited to 'Git/FilePath.hs')
-rw-r--r--Git/FilePath.hs55
1 files changed, 33 insertions, 22 deletions
diff --git a/Git/FilePath.hs b/Git/FilePath.hs
index ffa3331..66a0159 100644
--- a/Git/FilePath.hs
+++ b/Git/FilePath.hs
@@ -5,12 +5,14 @@
- top of the repository even when run in a subdirectory. Adding some
- types helps keep that straight.
-
- - Copyright 2012-2013 Joey Hess <id@joeyh.name>
+ - Copyright 2012-2019 Joey Hess <id@joeyh.name>
-
- - Licensed under the GNU GPL version 3 or higher.
+ - Licensed under the GNU AGPL version 3 or higher.
-}
{-# LANGUAGE CPP #-}
+{-# LANGUAGE DeriveGeneric #-}
+{-# LANGUAGE OverloadedStrings #-}
module Git.FilePath (
TopFilePath,
@@ -29,30 +31,39 @@ module Git.FilePath (
import Common
import Git
-import qualified System.FilePath.Posix
+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 FilePath, relative to the top of the git repository. -}
-newtype TopFilePath = TopFilePath { getTopFilePath :: FilePath }
- deriving (Show, Eq, Ord)
+{- 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 :: BranchFilePath -> String
-descBranchFilePath (BranchFilePath b f) = fromRef b ++ ':' : getTopFilePath f
+descBranchFilePath :: BranchFilePath -> S.ByteString
+descBranchFilePath (BranchFilePath b f) =
+ encodeBS' (fromRef b) <> ":" <> getTopFilePath f
{- Path to a TopFilePath, within the provided git repo. -}
-fromTopFilePath :: TopFilePath -> Git.Repo -> FilePath
-fromTopFilePath p repo = combine (repoPath repo) (getTopFilePath p)
+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 :: FilePath -> Git.Repo -> IO TopFilePath
-toTopFilePath file repo = TopFilePath <$> relPathDirToFile (repoPath repo) file
+toTopFilePath :: RawFilePath -> Git.Repo -> IO TopFilePath
+toTopFilePath file repo = TopFilePath . toRawFilePath
+ <$> relPathDirToFile (fromRawFilePath (repoPath repo)) (fromRawFilePath file)
-{- The input FilePath must already be relative to the top of the git
+{- The input RawFilePath must already be relative to the top of the git
- repository -}
-asTopFilePath :: FilePath -> TopFilePath
+asTopFilePath :: RawFilePath -> TopFilePath
asTopFilePath file = TopFilePath file
{- Git may use a different representation of a path when storing
@@ -62,25 +73,25 @@ asTopFilePath file = TopFilePath file
- despite Windows using '\'.
-
-}
-type InternalGitPath = String
+type InternalGitPath = RawFilePath
-toInternalGitPath :: FilePath -> InternalGitPath
+toInternalGitPath :: RawFilePath -> InternalGitPath
#ifndef mingw32_HOST_OS
toInternalGitPath = id
#else
-toInternalGitPath = replace "\\" "/"
+toInternalGitPath = encodeBS . replace "\\" "/" . decodeBS
#endif
-fromInternalGitPath :: InternalGitPath -> FilePath
+fromInternalGitPath :: InternalGitPath -> RawFilePath
#ifndef mingw32_HOST_OS
fromInternalGitPath = id
#else
-fromInternalGitPath = replace "/" "\\"
+fromInternalGitPath = encodeBS . replace "/" "\\" . decodeBS
#endif
{- isAbsolute on Windows does not think "/foo" or "\foo" is absolute,
- so try posix paths.
-}
-absoluteGitPath :: FilePath -> Bool
-absoluteGitPath p = isAbsolute p ||
- System.FilePath.Posix.isAbsolute (toInternalGitPath p)
+absoluteGitPath :: RawFilePath -> Bool
+absoluteGitPath p = P.isAbsolute p ||
+ System.FilePath.Posix.ByteString.isAbsolute (toInternalGitPath p)