git-annex/Utility/Path.hs

220 lines
6.7 KiB
Haskell
Raw Normal View History

{- path manipulation
-
2013-05-12 18:58:46 +00:00
- Copyright 2010-2013 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
{-# LANGUAGE PackageImports, CPP #-}
module Utility.Path where
import Data.String.Utils
import System.FilePath
import System.Directory
import Data.List
import Data.Maybe
import Control.Applicative
2011-10-16 04:31:25 +00:00
2013-05-14 17:24:15 +00:00
#ifdef __WINDOWS__
import Data.Char
2013-05-14 19:21:35 +00:00
import qualified System.FilePath.Posix as Posix
#else
import qualified "MissingH" System.Path as MissingH
2013-05-14 17:24:15 +00:00
#endif
2011-10-16 04:31:25 +00:00
import Utility.Monad
import Utility.UserInfo
{- Makes a path absolute if it's not already.
- The first parameter is a base directory (ie, the cwd) to use if the path
- is not already absolute.
-
- On Unix, collapses and normalizes ".." etc in the path. May return Nothing
- if the path cannot be normalized.
-
- MissingH's absNormPath does not work on Windows, so on Windows
- no normalization is done.
-}
absNormPath :: FilePath -> FilePath -> Maybe FilePath
#ifndef __WINDOWS__
absNormPath dir path = MissingH.absNormPath dir path
#else
absNormPath dir path = Just $ combine dir path
#endif
2013-05-12 18:58:46 +00:00
{- Returns the parent directory of a path.
-
- To allow this to be easily used in loops, which terminate upon reaching the
- top, the parent of / is "" -}
parentDir :: FilePath -> FilePath
2011-10-11 18:43:45 +00:00
parentDir dir
2013-05-12 18:58:46 +00:00
| null dirs = ""
| otherwise = joinDrive drive (join s $ init dirs)
2012-12-13 04:24:19 +00:00
where
2013-05-12 18:58:46 +00:00
-- on Unix, the drive will be "/" when the dir is absolute, otherwise ""
(drive, path) = splitDrive dir
dirs = filter (not . null) $ split s path
2012-12-13 04:24:19 +00:00
s = [pathSeparator]
prop_parentDir_basics :: FilePath -> Bool
prop_parentDir_basics dir
| null dir = True
| dir == "/" = parentDir dir == ""
| otherwise = p /= dir
2012-12-13 04:24:19 +00:00
where
p = parentDir dir
{- Checks if the first FilePath is, or could be said to contain the second.
- For example, "foo/" contains "foo/bar". Also, "foo", "./foo", "foo/" etc
- are all equivilant.
-}
dirContains :: FilePath -> FilePath -> Bool
2013-05-12 18:58:46 +00:00
dirContains a b = a == b || a' == b' || (a'++[pathSeparator]) `isPrefixOf` b'
2012-12-13 04:24:19 +00:00
where
norm p = fromMaybe "" $ absNormPath p "."
a' = norm a
b' = norm b
2012-01-23 20:57:45 +00:00
{- Converts a filename into a normalized, absolute path.
-
- Unlike Directory.canonicalizePath, this does not require the path
- already exists. -}
absPath :: FilePath -> IO FilePath
absPath file = do
cwd <- getCurrentDirectory
return $ absPathFrom cwd file
{- Converts a filename into a normalized, absolute path
- from the specified cwd. -}
absPathFrom :: FilePath -> FilePath -> FilePath
absPathFrom cwd file = fromMaybe bad $ absNormPath cwd file
2012-12-13 04:24:19 +00:00
where
bad = error $ "unable to normalize " ++ file
{- Constructs a relative path from the CWD to a file.
-
- For example, assuming CWD is /tmp/foo/bar:
- relPathCwdToFile "/tmp/foo" == ".."
- relPathCwdToFile "/tmp/foo/bar" == ""
-}
relPathCwdToFile :: FilePath -> IO FilePath
relPathCwdToFile f = relPathDirToFile <$> getCurrentDirectory <*> absPath f
{- Constructs a relative path from a directory to a file.
-
- Both must be absolute, and normalized (eg with absNormpath).
-}
relPathDirToFile :: FilePath -> FilePath -> FilePath
2011-10-11 18:43:45 +00:00
relPathDirToFile from to = join s $ dotdots ++ uncommon
2012-12-13 04:24:19 +00:00
where
s = [pathSeparator]
pfrom = split s from
pto = split s to
common = map fst $ takeWhile same $ zip pfrom pto
same (c,d) = c == d
uncommon = drop numcommon pto
dotdots = replicate (length pfrom - numcommon) ".."
numcommon = length common
prop_relPathDirToFile_basics :: FilePath -> FilePath -> Bool
prop_relPathDirToFile_basics from to
| from == to = null r
| otherwise = not (null r)
2012-12-13 04:24:19 +00:00
where
r = relPathDirToFile from to
2011-09-19 05:37:04 +00:00
prop_relPathDirToFile_regressionTest :: Bool
prop_relPathDirToFile_regressionTest = same_dir_shortcurcuits_at_difference
2012-12-13 04:24:19 +00:00
where
{- Two paths have the same directory component at the same
- location, but it's not really the same directory.
- Code used to get this wrong. -}
same_dir_shortcurcuits_at_difference =
2013-06-18 17:08:28 +00:00
relPathDirToFile (joinPath [pathSeparator : "tmp", "r", "lll", "xxx", "yyy", "18"])
(joinPath [pathSeparator : "tmp", "r", ".git", "annex", "objects", "18", "gk", "SHA256-foo", "SHA256-foo"])
== joinPath ["..", "..", "..", "..", ".git", "annex", "objects", "18", "gk", "SHA256-foo", "SHA256-foo"]
{- Given an original list of paths, and an expanded list derived from it,
- generates a list of lists, where each sublist corresponds to one of the
2013-05-12 18:58:46 +00:00
- original paths. When the original path is a directory, any items
- in the expanded list that are contained in that directory will appear in
- its segment.
2011-09-19 05:37:04 +00:00
-}
segmentPaths :: [FilePath] -> [FilePath] -> [[FilePath]]
segmentPaths [] new = [new]
segmentPaths [_] new = [new] -- optimisation
segmentPaths (l:ls) new = [found] ++ segmentPaths ls rest
2012-12-13 04:24:19 +00:00
where
(found, rest)=partition (l `dirContains`) new
2011-09-19 05:37:04 +00:00
{- This assumes that it's cheaper to call segmentPaths on the result,
- 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.
2011-09-19 05:37:04 +00:00
-}
runSegmentPaths :: ([FilePath] -> IO [FilePath]) -> [FilePath] -> IO [[FilePath]]
runSegmentPaths a paths = segmentPaths paths <$> a paths
2011-10-16 04:31:25 +00:00
2012-08-02 11:47:50 +00:00
{- Converts paths in the home directory to use ~/ -}
relHome :: FilePath -> IO String
relHome path = do
home <- myHomeDir
return $ if dirContains home path
then "~/" ++ relPathDirToFile home path
else path
{- Checks if a command is available in PATH.
-
- The command may be fully-qualified, in which case, this succeeds as
- long as it exists. -}
2011-10-16 04:31:25 +00:00
inPath :: String -> IO Bool
inPath command = isJust <$> searchPath command
{- Finds a command in PATH and returns the full path to it.
-
- The command may be fully qualified already, in which case it will
- be returned if it exists.
-}
searchPath :: String -> IO (Maybe FilePath)
searchPath command
| isAbsolute command = check command
| otherwise = getSearchPath >>= getM indir
2012-12-13 04:24:19 +00:00
where
indir d = check $ d </> command
check f = firstM doesFileExist
#ifdef __WINDOWS__
[f, f ++ ".exe"]
#else
[f]
#endif
{- Checks if a filename is a unix dotfile. All files inside dotdirs
- count as dotfiles. -}
dotfile :: FilePath -> Bool
dotfile file
| f == "." = False
| f == ".." = False
| f == "" = False
| otherwise = "." `isPrefixOf` f || dotfile (takeDirectory file)
2012-12-13 04:24:19 +00:00
where
f = takeFileName file
2013-05-14 17:24:15 +00:00
{- Converts a DOS style path to a Cygwin style path. Only on Windows.
- Any trailing '\' is preserved as a trailing '/' -}
toCygPath :: FilePath -> FilePath
#ifndef __WINDOWS__
toCygPath = id
#else
toCygPath p
| null drive = recombine parts
| otherwise = recombine $ "/cygdrive" : driveletter drive : parts
where
(drive, p') = splitDrive p
parts = splitDirectories p'
driveletter = map toLower . takeWhile (/= ':')
recombine = fixtrailing . Posix.joinPath
fixtrailing s
| hasTrailingPathSeparator p = Posix.addTrailingPathSeparator s
| otherwise = s
#endif