module Development.Shake.FilePath(
module System.FilePath, module System.FilePath.Posix,
dropDirectory1, takeDirectory1, replaceDirectory1,
makeRelativeEx, normaliseEx,
toNative, toStandard,
exe
) where
import System.Directory (canonicalizePath)
import System.Info.Extra
import Data.List.Extra
import qualified System.FilePath as Native
import System.FilePath hiding
(splitExtension, takeExtension, replaceExtension, dropExtension, addExtension
,hasExtension, (<.>), splitExtensions, takeExtensions, dropExtensions
)
import System.FilePath.Posix
(splitExtension, takeExtension, replaceExtension, dropExtension, addExtension
,hasExtension, (<.>), splitExtensions, takeExtensions, dropExtensions
)
dropDirectory1 :: FilePath -> FilePath
dropDirectory1 = drop1 . dropWhile (not . isPathSeparator)
takeDirectory1 :: FilePath -> FilePath
takeDirectory1 = takeWhile (not . isPathSeparator)
replaceDirectory1 :: FilePath -> String -> FilePath
replaceDirectory1 x dir = dir </> dropDirectory1 x
makeRelativeEx :: FilePath -> FilePath -> IO (Maybe FilePath)
makeRelativeEx pathA pathB
| isRelative makeRelativePathAPathB =
pure (Just makeRelativePathAPathB)
| otherwise = do
a' <- canonicalizePath pathA
b' <- canonicalizePath pathB
if takeDrive a' /= takeDrive b'
then pure Nothing
else Just <$> makeRelativeEx' a' b'
where
makeRelativePathAPathB = makeRelative pathA pathB
makeRelativeEx' :: FilePath -> FilePath -> IO FilePath
makeRelativeEx' a b = do
let rel = makeRelative a b
parent = takeDirectory a
if isRelative rel
then pure rel
else if a /= parent
then do
parentToB <- makeRelativeEx' parent b
pure (".." </> parentToB)
else error $ "Error calculating relative path from \""
++ pathA ++ "\" to \"" ++ show pathB ++ "\""
normaliseEx :: FilePath -> FilePath
normaliseEx xs | a:b:xs <- xs, isWindows && sep a && sep b = '/' : f ('/':xs)
| otherwise = f xs
where
sep = Native.isPathSeparator
f o = toNative $ deslash o $ (++"/") $ concatMap ('/':) $ reverse $ g 0 $ reverse $ split o
deslash o x
| x == "/" = case (pre,pos) of
(True,True) -> "/"
(True,False) -> "/."
(False,True) -> "./"
(False,False) -> "."
| otherwise = (if pre then id else tail) $ (if pos then id else init) x
where pre = sep $ head $ o ++ " "
pos = sep $ last $ " " ++ o
g i [] = replicate i ".."
g i ("..":xs) = g (i+1) xs
g i (".":xs) = g i xs
g 0 (x:xs) = x : g 0 xs
g i (_:xs) = g (i-1) xs
split xs = if null ys then [] else a : split b
where (a,b) = break sep ys
ys = dropWhile sep xs
toNative :: FilePath -> FilePath
toNative = if isWindows then map (\x -> if x == '/' then '\\' else x) else id
toStandard :: FilePath -> FilePath
toStandard = if isWindows then map (\x -> if x == '\\' then '/' else x) else id
exe :: String
exe = if isWindows then "exe" else ""