module Darcs.RepoPath (
AbsolutePath,
makeAbsolute,
ioAbsolute,
rootDirectory,
AbsolutePathOrStd,
makeAbsoluteOrStd,
ioAbsoluteOrStd,
useAbsoluteOrStd,
stdOut,
AbsoluteOrRemotePath,
ioAbsoluteOrRemote,
isRemote,
SubPath,
makeSubPathOf,
simpleSubPath,
sp2fn,
FilePathOrURL(..),
FilePathLike(toFilePath),
getCurrentDirectory,
setCurrentDirectory
) where
import Data.List ( isPrefixOf, isSuffixOf )
import Control.Exception ( bracket )
import Darcs.URL ( isAbsolute, isRelative, isSshNopath )
import qualified Workaround ( getCurrentDirectory )
import qualified System.Directory ( setCurrentDirectory )
import System.Directory ( doesDirectoryExist )
import qualified System.FilePath.Posix as FilePath ( normalise )
import qualified System.FilePath as NativeFilePath ( takeFileName, takeDirectory )
import qualified Darcs.Patch.FileName as PatchFileName ( FileName, fp2fn, fn2fp )
#include "impossible.h"
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 FilePathOrURL PatchFileName.FileName where
toPath = PatchFileName.fn2fp
instance FilePathLike PatchFileName.FileName where
toFilePath = PatchFileName.fn2fp
instance FilePathLike AbsolutePath where
toFilePath (AbsolutePath x) = x
instance FilePathLike SubPath where
toFilePath (SubPath x) = x
class CharLike c where
toChar :: c -> Char
fromChar :: Char -> c
instance CharLike Char where
toChar = id
fromChar = 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 = bug "simpleSubPath called with empty path"
| isRelative x = Just $ SubPath $ FilePath.normalise $ pathToPosix x
| otherwise = Nothing
ioAbsolute :: FilePath -> IO AbsolutePath
ioAbsolute dir =
do isdir <- doesDirectoryExist dir
here <- getCurrentDirectory
if isdir
then bracket (setCurrentDirectory dir)
(const $ setCurrentDirectory $ toFilePath here)
(const 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
rootDirectory :: AbsolutePath
rootDirectory = AbsolutePath "/"
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
sp2fn :: SubPath -> PatchFileName.FileName
sp2fn = PatchFileName.fp2fn . toFilePath