{-# LANGUAGE CPP #-}
module Darcs.Util.Path
( encodeWhite
, decodeWhite
, encodeWhiteName
, decodeWhiteName
, AbsolutePath
, makeAbsolute
, ioAbsolute
, AbsolutePathOrStd
, makeAbsoluteOrStd
, ioAbsoluteOrStd
, useAbsoluteOrStd
, stdOut
, AbsoluteOrRemotePath
, ioAbsoluteOrRemote
, isRemote
, SubPath
, makeSubPathOf
, simpleSubPath
, floatSubPath
, FilePathOrURL(..)
, FilePathLike(toFilePath)
, getCurrentDirectory
, setCurrentDirectory
, getUniquePathName
, doesPathExist
, isMaliciousSubPath
, filterPaths
, Name
, name2fp
, makeName
, rawMakeName
, eqAnycase
, AnchoredPath(..)
, anchoredRoot
, appendPath
, anchorPath
, isPrefix
, breakOnDir
, movedirfilename
, parent
, parents
, replaceParent
, catPaths
, flatten
, inDarcsdir
, displayPath
, realPath
, isRoot
, darcsdirName
, floatPath
) where
import Darcs.Prelude
import Data.List
( isPrefixOf
, isSuffixOf
, stripPrefix
, intersect
, inits
)
import Data.Char ( isSpace, chr, ord, toLower )
import Data.Typeable ( Typeable )
import Control.Exception ( tryJust, bracket_, throw, Exception )
import Control.Monad ( when )
import System.IO.Error ( isDoesNotExistError )
import qualified Darcs.Util.Workaround as Workaround ( getCurrentDirectory )
import qualified System.Directory ( setCurrentDirectory )
import System.Directory ( doesDirectoryExist, doesFileExist )
import qualified System.FilePath.Posix as FilePath ( (</>), normalise, isRelative )
import qualified System.FilePath as NativeFilePath ( takeFileName, takeDirectory )
import System.FilePath( splitDirectories, normalise, dropTrailingPathSeparator )
import System.Posix.Files ( isDirectory, getSymbolicLinkStatus )
import Darcs.Util.ByteString ( encodeLocale, decodeLocale )
import qualified Data.ByteString.Char8 as BC
import qualified Data.ByteString as B
import Data.Binary
import Darcs.Util.Global ( darcsdir )
import Darcs.Util.URL ( isAbsolute, isRelative, isSshNopath )
displayPath :: AnchoredPath -> FilePath
displayPath p
| isRoot p = "."
| otherwise = anchorPath "." p
realPath :: AnchoredPath -> FilePath
realPath = anchorPath ""
encodeWhite :: FilePath -> String
encodeWhite (c:cs) | isSpace c || c == '\\' =
'\\' : show (ord c) ++ "\\" ++ encodeWhite cs
encodeWhite (c:cs) = c : encodeWhite cs
encodeWhite [] = []
decodeWhite :: String -> FilePath
decodeWhite cs_ = go cs_ [] False
where go "" acc True = reverse acc
go "" _ False = cs_
go ('\\':cs) acc _ =
case break (=='\\') cs of
(theord, '\\':rest) ->
go rest (chr (read theord) :acc) True
_ -> error "malformed filename"
go (c:cs) acc modified = go cs (c:acc) modified
class FilePathOrURL a where
toPath :: a -> String
class FilePathOrURL a => FilePathLike a where
toFilePath :: a -> FilePath
newtype SubPath = SubPath FilePath deriving (Eq, Ord)
newtype AbsolutePath = AbsolutePath FilePath deriving (Eq, Ord)
data AbsolutePathOrStd = AP AbsolutePath | APStd deriving (Eq, Ord)
data AbsoluteOrRemotePath = AbsP AbsolutePath | RmtP String deriving (Eq, Ord)
instance FilePathOrURL AbsolutePath where
toPath (AbsolutePath x) = x
instance FilePathOrURL SubPath where
toPath (SubPath x) = x
instance CharLike c => FilePathOrURL [c] where
toPath = toFilePath
instance FilePathOrURL AbsoluteOrRemotePath where
toPath (AbsP a) = toPath a
toPath (RmtP r) = r
instance FilePathLike AbsolutePath where
toFilePath (AbsolutePath x) = x
instance FilePathLike SubPath where
toFilePath (SubPath x) = x
class CharLike c where
toChar :: c -> Char
instance CharLike Char where
toChar = id
instance CharLike c => FilePathLike [c] where
toFilePath = map toChar
makeSubPathOf :: AbsolutePath -> AbsolutePath -> Maybe SubPath
makeSubPathOf (AbsolutePath p1) (AbsolutePath p2) =
if p1 == p2 || (p1 ++ "/") `isPrefixOf` p2
then Just $ SubPath $ drop (length p1 + 1) p2
else Nothing
simpleSubPath :: FilePath -> Maybe SubPath
simpleSubPath x | null x = error "simpleSubPath called with empty path"
| isRelative x = Just $ SubPath $ FilePath.normalise $ pathToPosix x
| otherwise = Nothing
doesDirectoryReallyExist :: FilePath -> IO Bool
doesDirectoryReallyExist f = do
x <- tryJust (\x -> if isDoesNotExistError x then Just () else Nothing) $
isDirectory <$> getSymbolicLinkStatus f
return $ case x of
Left () -> False
Right y -> y
doesPathExist :: FilePath -> IO Bool
doesPathExist p = do
dir_exists <- doesDirectoryExist p
file_exists <- doesFileExist p
return $ dir_exists || file_exists
ioAbsolute :: FilePath -> IO AbsolutePath
ioAbsolute dir =
do isdir <- doesDirectoryReallyExist dir
here <- getCurrentDirectory
if isdir
then bracket_ (setCurrentDirectory dir)
(setCurrentDirectory $ toFilePath here)
getCurrentDirectory
else let super_dir = case NativeFilePath.takeDirectory dir of
"" -> "."
d -> d
file = NativeFilePath.takeFileName dir
in do abs_dir <- if dir == super_dir
then return $ AbsolutePath dir
else ioAbsolute super_dir
return $ makeAbsolute abs_dir file
makeAbsolute :: AbsolutePath -> FilePath -> AbsolutePath
makeAbsolute a dir = if not (null dir) && isAbsolute dir
then AbsolutePath (normSlashes dir')
else ma a dir'
where
dir' = FilePath.normalise $ pathToPosix dir
ma here ('.':'.':'/':r) = ma (takeDirectory here) r
ma here ".." = takeDirectory here
ma here "." = here
ma here "" = here
ma here r = here /- ('/':r)
(/-) :: AbsolutePath -> String -> AbsolutePath
x /- ('/':r) = x /- r
(AbsolutePath "/") /- r = AbsolutePath ('/':simpleClean r)
(AbsolutePath x) /- r = AbsolutePath (x++'/':simpleClean r)
simpleClean :: String -> String
simpleClean = normSlashes . reverse . dropWhile (=='/') . reverse . pathToPosix
makeAbsoluteOrStd :: AbsolutePath -> String -> AbsolutePathOrStd
makeAbsoluteOrStd _ "-" = APStd
makeAbsoluteOrStd a p = AP $ makeAbsolute a p
stdOut :: AbsolutePathOrStd
stdOut = APStd
ioAbsoluteOrStd :: String -> IO AbsolutePathOrStd
ioAbsoluteOrStd "-" = return APStd
ioAbsoluteOrStd p = AP `fmap` ioAbsolute p
useAbsoluteOrStd :: (AbsolutePath -> a) -> a -> AbsolutePathOrStd -> a
useAbsoluteOrStd _ f APStd = f
useAbsoluteOrStd f _ (AP x) = f x
ioAbsoluteOrRemote :: String -> IO AbsoluteOrRemotePath
ioAbsoluteOrRemote p = do
isdir <- doesDirectoryExist p
if not isdir
then return $ RmtP $
case () of _ | isSshNopath p -> p++"."
| "/" `isSuffixOf` p -> init p
| otherwise -> p
else AbsP `fmap` ioAbsolute p
isRemote :: AbsoluteOrRemotePath -> Bool
isRemote (RmtP _) = True
isRemote _ = False
takeDirectory :: AbsolutePath -> AbsolutePath
takeDirectory (AbsolutePath x) =
case reverse $ drop 1 $ dropWhile (/='/') $ reverse x of
"" -> AbsolutePath "/"
x' -> AbsolutePath x'
instance Show AbsolutePath where
show = show . toFilePath
instance Show SubPath where
show = show . toFilePath
instance Show AbsolutePathOrStd where
show (AP a) = show a
show APStd = "standard input/output"
instance Show AbsoluteOrRemotePath where
show (AbsP a) = show a
show (RmtP r) = show r
pathToPosix :: FilePath -> FilePath
pathToPosix = map convert where
#ifdef WIN32
convert '\\' = '/'
#endif
convert c = c
normSlashes :: FilePath -> FilePath
#ifndef WIN32
normSlashes ('/':p) = '/' : dropWhile (== '/') p
#endif
normSlashes p = p
getCurrentDirectory :: IO AbsolutePath
getCurrentDirectory = AbsolutePath `fmap` Workaround.getCurrentDirectory
setCurrentDirectory :: FilePathLike p => p -> IO ()
setCurrentDirectory = System.Directory.setCurrentDirectory . toFilePath
isMaliciousSubPath :: String -> Bool
isMaliciousSubPath fp =
not (FilePath.isRelative fp) || isGenerallyMalicious fp
isGenerallyMalicious :: String -> Bool
isGenerallyMalicious fp =
splitDirectories fp `contains_any` [ "..", darcsdir ]
where
contains_any a b = not . null $ intersect a b
getUniquePathName :: Bool -> (FilePath -> String) -> (Int -> FilePath) -> IO FilePath
getUniquePathName talkative buildMsg buildName = go (-1)
where
go :: Int -> IO FilePath
go i = do
exists <- doesPathExist thename
if not exists
then do when (i /= -1 && talkative) $ putStrLn $ buildMsg thename
return thename
else go $ i+1
where thename = buildName i
newtype Name = Name { unName :: B.ByteString } deriving (Binary, Eq, Show, Ord)
newtype AnchoredPath = AnchoredPath [Name] deriving (Binary, Eq, Show, Ord)
isPrefix :: AnchoredPath -> AnchoredPath -> Bool
(AnchoredPath a) `isPrefix` (AnchoredPath b) = a `isPrefixOf` b
appendPath :: AnchoredPath -> Name -> AnchoredPath
appendPath (AnchoredPath p) n = AnchoredPath $ p ++ [n]
catPaths :: AnchoredPath -> AnchoredPath -> AnchoredPath
catPaths (AnchoredPath p) (AnchoredPath n) = AnchoredPath (p ++ n)
parent :: AnchoredPath -> Maybe AnchoredPath
parent (AnchoredPath []) = Nothing
parent (AnchoredPath x) = Just (AnchoredPath (init x))
parents :: AnchoredPath -> [AnchoredPath]
parents (AnchoredPath []) = []
parents (AnchoredPath xs) = map AnchoredPath $ inits $ init xs
breakOnDir :: AnchoredPath -> Either Name (Name, AnchoredPath)
breakOnDir (AnchoredPath []) = error "breakOnDir called on root"
breakOnDir (AnchoredPath (n:[])) = Left n
breakOnDir (AnchoredPath (n:ns)) = Right (n, AnchoredPath ns)
anchorPath :: FilePath -> AnchoredPath -> FilePath
anchorPath dir p = dir FilePath.</> decodeLocale (flatten p)
{-# INLINE anchorPath #-}
name2fp :: Name -> FilePath
name2fp (Name ps) = decodeLocale ps
flatten :: AnchoredPath -> BC.ByteString
flatten (AnchoredPath []) = BC.singleton '.'
flatten (AnchoredPath p) = BC.intercalate (BC.singleton '/') [n | (Name n) <- p]
makeName :: String -> Either String Name
makeName = rawMakeName . encodeLocale
internalMakeName :: String -> Name
internalMakeName = either error id . rawMakeName . encodeLocale
floatPath :: FilePath -> AnchoredPath
floatPath =
AnchoredPath . map internalMakeName . filter sensible .
splitDirectories . normalise . dropTrailingPathSeparator
where
sensible s = s `notElem` ["", "."]
anchoredRoot :: AnchoredPath
anchoredRoot = AnchoredPath []
parentChild :: AnchoredPath -> Maybe (AnchoredPath, Name)
parentChild (AnchoredPath []) = Nothing
parentChild (AnchoredPath xs) = Just (AnchoredPath (init xs), last xs)
replaceParent :: AnchoredPath -> AnchoredPath -> Maybe AnchoredPath
replaceParent (AnchoredPath xs) p =
case parentChild p of
Nothing -> Nothing
Just (_,x) -> Just (AnchoredPath (xs ++ [x]))
rawMakeName :: B.ByteString -> Either String Name
rawMakeName s
| isBadName s =
Left $ "'"++decodeLocale s++"' is not a valid AnchoredPath component name"
| otherwise = Right (Name s)
isBadName :: B.ByteString -> Bool
isBadName n = hasPathSeparator n || n `elem` forbiddenNames
forbiddenNames :: [B.ByteString]
forbiddenNames = [BC.empty, BC.pack ".", BC.pack ".."]
hasPathSeparator :: B.ByteString -> Bool
hasPathSeparator = BC.elem '/'
eqAnycase :: Name -> Name -> Bool
eqAnycase (Name a) (Name b) = BC.map toLower a == BC.map toLower b
encodeWhiteName :: Name -> B.ByteString
encodeWhiteName = encodeLocale . encodeWhite . decodeLocale . unName
data CorruptPatch = CorruptPatch String deriving (Eq, Typeable)
instance Exception CorruptPatch
instance Show CorruptPatch where show (CorruptPatch s) = s
decodeWhiteName :: B.ByteString -> Name
decodeWhiteName =
either (throw . CorruptPatch) id .
rawMakeName . encodeLocale . decodeWhite . decodeLocale
movedirfilename :: AnchoredPath -> AnchoredPath -> AnchoredPath -> AnchoredPath
movedirfilename (AnchoredPath old) newp@(AnchoredPath new) orig@(AnchoredPath path) =
case stripPrefix old path of
Just [] -> newp
Just rest -> AnchoredPath (new ++ rest)
Nothing -> orig
filterPaths :: [AnchoredPath] -> AnchoredPath -> t -> Bool
filterPaths files p _ = any (\x -> x `isPrefix` p || p `isPrefix` x) files
floatSubPath :: SubPath -> AnchoredPath
floatSubPath = floatPath . toFilePath
inDarcsdir :: AnchoredPath -> Bool
inDarcsdir (AnchoredPath (x:_)) | x == darcsdirName = True
inDarcsdir _ = False
darcsdirName :: Name
darcsdirName = internalMakeName darcsdir
isRoot :: AnchoredPath -> Bool
isRoot (AnchoredPath xs) = null xs