{-# LANGUAGE CPP #-}
module System.EasyFile.FilePath (
FilePath,
pathSeparator, pathSeparators, isPathSeparator,
extSeparator, isExtSeparator,
splitExtension,
takeExtension, replaceExtension, dropExtension, addExtension, hasExtension, (<.>),
splitExtensions, dropExtensions, takeExtensions,
splitDrive, joinDrive,
takeDrive, hasDrive, dropDrive, isDrive,
splitFileName,
takeFileName, replaceFileName, dropFileName,
takeBaseName, replaceBaseName,
takeDirectory, replaceDirectory,
combine, (</>),
splitPath, joinPath, splitDirectories,
hasTrailingPathSeparator,
addTrailingPathSeparator,
dropTrailingPathSeparator,
normalise, equalFilePath,
makeRelative,
isRelative, isAbsolute,
#ifdef TESTING
, isRelativeDrive
#endif
)
where
import Data.Char(toLower, toUpper)
import Data.Maybe(isJust, fromJust)
infixr 7 <.>
infixr 5 </>
isPosix :: Bool
isPosix :: Bool
isPosix = Bool -> Bool
not Bool
isWindows
isWindows :: Bool
#if defined(mingw32_HOST_OS) || defined(__MINGW32__)
isWindows = True
#else
isWindows :: Bool
isWindows = Bool
False
#endif
pathSeparator :: Char
pathSeparator :: Char
pathSeparator = Char
'/'
pathSeparators :: [Char]
pathSeparators :: FilePath
pathSeparators = if Bool
isWindows then FilePath
"\\/" else FilePath
"/"
isPathSeparator :: Char -> Bool
isPathSeparator :: Char -> Bool
isPathSeparator = (forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` FilePath
pathSeparators)
extSeparator :: Char
extSeparator :: Char
extSeparator = Char
'.'
isExtSeparator :: Char -> Bool
isExtSeparator :: Char -> Bool
isExtSeparator = (forall a. Eq a => a -> a -> Bool
== Char
extSeparator)
splitExtension :: FilePath -> (String, String)
splitExtension :: FilePath -> (FilePath, FilePath)
splitExtension FilePath
x = case FilePath
d of
FilePath
"" -> (FilePath
x,FilePath
"")
(Char
y:FilePath
ys) -> (FilePath
a forall a. [a] -> [a] -> [a]
++ forall a. [a] -> [a]
reverse FilePath
ys, Char
y forall a. a -> [a] -> [a]
: forall a. [a] -> [a]
reverse FilePath
c)
where
(FilePath
a,FilePath
b) = FilePath -> (FilePath, FilePath)
splitFileName FilePath
x
(FilePath
c,FilePath
d) = forall a. (a -> Bool) -> [a] -> ([a], [a])
break Char -> Bool
isExtSeparator forall a b. (a -> b) -> a -> b
$ forall a. [a] -> [a]
reverse FilePath
b
takeExtension :: FilePath -> String
takeExtension :: FilePath -> FilePath
takeExtension = forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> (FilePath, FilePath)
splitExtension
replaceExtension :: FilePath -> String -> FilePath
replaceExtension :: FilePath -> FilePath -> FilePath
replaceExtension FilePath
x FilePath
y = FilePath -> FilePath
dropExtension FilePath
x FilePath -> FilePath -> FilePath
<.> FilePath
y
(<.>) :: FilePath -> String -> FilePath
<.> :: FilePath -> FilePath -> FilePath
(<.>) = FilePath -> FilePath -> FilePath
addExtension
dropExtension :: FilePath -> FilePath
dropExtension :: FilePath -> FilePath
dropExtension = forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> (FilePath, FilePath)
splitExtension
addExtension :: FilePath -> String -> FilePath
addExtension :: FilePath -> FilePath -> FilePath
addExtension FilePath
file FilePath
"" = FilePath
file
addExtension FilePath
file xs :: FilePath
xs@(Char
x:FilePath
_) = FilePath -> FilePath -> FilePath
joinDrive FilePath
a FilePath
res
where
res :: FilePath
res = if Char -> Bool
isExtSeparator Char
x then FilePath
b forall a. [a] -> [a] -> [a]
++ FilePath
xs
else FilePath
b forall a. [a] -> [a] -> [a]
++ [Char
extSeparator] forall a. [a] -> [a] -> [a]
++ FilePath
xs
(FilePath
a,FilePath
b) = FilePath -> (FilePath, FilePath)
splitDrive FilePath
file
hasExtension :: FilePath -> Bool
hasExtension :: FilePath -> Bool
hasExtension = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Char -> Bool
isExtSeparator forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath
takeFileName
splitExtensions :: FilePath -> (FilePath, String)
splitExtensions :: FilePath -> (FilePath, FilePath)
splitExtensions FilePath
x = (FilePath
a forall a. [a] -> [a] -> [a]
++ FilePath
c, FilePath
d)
where
(FilePath
a,FilePath
b) = FilePath -> (FilePath, FilePath)
splitFileName FilePath
x
(FilePath
c,FilePath
d) = forall a. (a -> Bool) -> [a] -> ([a], [a])
break Char -> Bool
isExtSeparator FilePath
b
dropExtensions :: FilePath -> FilePath
dropExtensions :: FilePath -> FilePath
dropExtensions = forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> (FilePath, FilePath)
splitExtensions
takeExtensions :: FilePath -> String
takeExtensions :: FilePath -> FilePath
takeExtensions = forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> (FilePath, FilePath)
splitExtensions
isLetter :: Char -> Bool
isLetter :: Char -> Bool
isLetter Char
x = (Char
x forall a. Ord a => a -> a -> Bool
>= Char
'a' Bool -> Bool -> Bool
&& Char
x forall a. Ord a => a -> a -> Bool
<= Char
'z') Bool -> Bool -> Bool
|| (Char
x forall a. Ord a => a -> a -> Bool
>= Char
'A' Bool -> Bool -> Bool
&& Char
x forall a. Ord a => a -> a -> Bool
<= Char
'Z')
splitDrive :: FilePath -> (FilePath, FilePath)
splitDrive :: FilePath -> (FilePath, FilePath)
splitDrive FilePath
x | Bool
isPosix = forall a. (a -> Bool) -> [a] -> ([a], [a])
span (forall a. Eq a => a -> a -> Bool
== Char
'/') FilePath
x
splitDrive FilePath
x | forall a. Maybe a -> Bool
isJust Maybe (FilePath, FilePath)
y = forall a. HasCallStack => Maybe a -> a
fromJust Maybe (FilePath, FilePath)
y
where y :: Maybe (FilePath, FilePath)
y = FilePath -> Maybe (FilePath, FilePath)
readDriveLetter FilePath
x
splitDrive FilePath
x | forall a. Maybe a -> Bool
isJust Maybe (FilePath, FilePath)
y = forall a. HasCallStack => Maybe a -> a
fromJust Maybe (FilePath, FilePath)
y
where y :: Maybe (FilePath, FilePath)
y = FilePath -> Maybe (FilePath, FilePath)
readDriveUNC FilePath
x
splitDrive FilePath
x | forall a. Maybe a -> Bool
isJust Maybe (FilePath, FilePath)
y = forall a. HasCallStack => Maybe a -> a
fromJust Maybe (FilePath, FilePath)
y
where y :: Maybe (FilePath, FilePath)
y = FilePath -> Maybe (FilePath, FilePath)
readDriveShare FilePath
x
splitDrive FilePath
x = (FilePath
"",FilePath
x)
addSlash :: FilePath -> FilePath -> (FilePath, FilePath)
addSlash :: FilePath -> FilePath -> (FilePath, FilePath)
addSlash FilePath
a FilePath
xs = (FilePath
aforall a. [a] -> [a] -> [a]
++FilePath
c,FilePath
d)
where (FilePath
c,FilePath
d) = forall a. (a -> Bool) -> [a] -> ([a], [a])
span Char -> Bool
isPathSeparator FilePath
xs
readDriveUNC :: FilePath -> Maybe (FilePath, FilePath)
readDriveUNC :: FilePath -> Maybe (FilePath, FilePath)
readDriveUNC (Char
s1:Char
s2:Char
'?':Char
s3:FilePath
xs) | forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Char -> Bool
isPathSeparator [Char
s1,Char
s2,Char
s3] =
case forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toUpper FilePath
xs of
(Char
'U':Char
'N':Char
'C':Char
s4:FilePath
_) | Char -> Bool
isPathSeparator Char
s4 ->
let (FilePath
a,FilePath
b) = FilePath -> (FilePath, FilePath)
readDriveShareName (forall a. Int -> [a] -> [a]
drop Int
4 FilePath
xs)
in forall a. a -> Maybe a
Just (Char
s1forall a. a -> [a] -> [a]
:Char
s2forall a. a -> [a] -> [a]
:Char
'?'forall a. a -> [a] -> [a]
:Char
s3forall a. a -> [a] -> [a]
:forall a. Int -> [a] -> [a]
take Int
4 FilePath
xs forall a. [a] -> [a] -> [a]
++ FilePath
a, FilePath
b)
FilePath
_ -> case FilePath -> Maybe (FilePath, FilePath)
readDriveLetter FilePath
xs of
Just (FilePath
a,FilePath
b) -> forall a. a -> Maybe a
Just (Char
s1forall a. a -> [a] -> [a]
:Char
s2forall a. a -> [a] -> [a]
:Char
'?'forall a. a -> [a] -> [a]
:Char
s3forall a. a -> [a] -> [a]
:FilePath
a,FilePath
b)
Maybe (FilePath, FilePath)
Nothing -> forall a. Maybe a
Nothing
readDriveUNC FilePath
_ = forall a. Maybe a
Nothing
readDriveLetter :: String -> Maybe (FilePath, FilePath)
readDriveLetter :: FilePath -> Maybe (FilePath, FilePath)
readDriveLetter (Char
x:Char
':':Char
y:FilePath
xs) | Char -> Bool
isLetter Char
x Bool -> Bool -> Bool
&& Char -> Bool
isPathSeparator Char
y = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath -> (FilePath, FilePath)
addSlash [Char
x,Char
':'] (Char
yforall a. a -> [a] -> [a]
:FilePath
xs)
readDriveLetter (Char
x:Char
':':FilePath
xs) | Char -> Bool
isLetter Char
x = forall a. a -> Maybe a
Just ([Char
x,Char
':'], FilePath
xs)
readDriveLetter FilePath
_ = forall a. Maybe a
Nothing
readDriveShare :: String -> Maybe (FilePath, FilePath)
readDriveShare :: FilePath -> Maybe (FilePath, FilePath)
readDriveShare (Char
s1:Char
s2:FilePath
xs) | Char -> Bool
isPathSeparator Char
s1 Bool -> Bool -> Bool
&& Char -> Bool
isPathSeparator Char
s2 =
forall a. a -> Maybe a
Just (Char
s1forall a. a -> [a] -> [a]
:Char
s2forall a. a -> [a] -> [a]
:FilePath
a,FilePath
b)
where (FilePath
a,FilePath
b) = FilePath -> (FilePath, FilePath)
readDriveShareName FilePath
xs
readDriveShare FilePath
_ = forall a. Maybe a
Nothing
readDriveShareName :: String -> (FilePath, FilePath)
readDriveShareName :: FilePath -> (FilePath, FilePath)
readDriveShareName FilePath
name = FilePath -> FilePath -> (FilePath, FilePath)
addSlash FilePath
a FilePath
b
where (FilePath
a,FilePath
b) = forall a. (a -> Bool) -> [a] -> ([a], [a])
break Char -> Bool
isPathSeparator FilePath
name
joinDrive :: FilePath -> FilePath -> FilePath
joinDrive :: FilePath -> FilePath -> FilePath
joinDrive FilePath
a FilePath
b | Bool
isPosix = FilePath
a forall a. [a] -> [a] -> [a]
++ FilePath
b
| forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
a = FilePath
b
| forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
b = FilePath
a
| Char -> Bool
isPathSeparator (forall a. [a] -> a
last FilePath
a) = FilePath
a forall a. [a] -> [a] -> [a]
++ FilePath
b
| Bool
otherwise = case FilePath
a of
[Char
a1,Char
':'] | Char -> Bool
isLetter Char
a1 -> FilePath
a forall a. [a] -> [a] -> [a]
++ FilePath
b
FilePath
_ -> FilePath
a forall a. [a] -> [a] -> [a]
++ [Char
pathSeparator] forall a. [a] -> [a] -> [a]
++ FilePath
b
takeDrive :: FilePath -> FilePath
takeDrive :: FilePath -> FilePath
takeDrive = forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> (FilePath, FilePath)
splitDrive
dropDrive :: FilePath -> FilePath
dropDrive :: FilePath -> FilePath
dropDrive = forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> (FilePath, FilePath)
splitDrive
hasDrive :: FilePath -> Bool
hasDrive :: FilePath -> Bool
hasDrive = Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> Bool
null forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath
takeDrive
isDrive :: FilePath -> Bool
isDrive :: FilePath -> Bool
isDrive = forall (t :: * -> *) a. Foldable t => t a -> Bool
null forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath
dropDrive
splitFileName :: FilePath -> (String, String)
splitFileName :: FilePath -> (FilePath, FilePath)
splitFileName FilePath
x = (FilePath
c forall a. [a] -> [a] -> [a]
++ forall a. [a] -> [a]
reverse FilePath
b, forall a. [a] -> [a]
reverse FilePath
a)
where
(FilePath
a,FilePath
b) = forall a. (a -> Bool) -> [a] -> ([a], [a])
break Char -> Bool
isPathSeparator forall a b. (a -> b) -> a -> b
$ forall a. [a] -> [a]
reverse FilePath
d
(FilePath
c,FilePath
d) = FilePath -> (FilePath, FilePath)
splitDrive FilePath
x
replaceFileName :: FilePath -> String -> FilePath
replaceFileName :: FilePath -> FilePath -> FilePath
replaceFileName FilePath
x FilePath
y = FilePath -> FilePath
dropFileName FilePath
x FilePath -> FilePath -> FilePath
</> FilePath
y
dropFileName :: FilePath -> FilePath
dropFileName :: FilePath -> FilePath
dropFileName = forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> (FilePath, FilePath)
splitFileName
takeFileName :: FilePath -> FilePath
takeFileName :: FilePath -> FilePath
takeFileName = forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> (FilePath, FilePath)
splitFileName
takeBaseName :: FilePath -> String
takeBaseName :: FilePath -> FilePath
takeBaseName = FilePath -> FilePath
dropExtension forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath
takeFileName
replaceBaseName :: FilePath -> String -> FilePath
replaceBaseName :: FilePath -> FilePath -> FilePath
replaceBaseName FilePath
pth FilePath
nam = FilePath -> FilePath -> FilePath
combineAlways FilePath
a (FilePath
nam FilePath -> FilePath -> FilePath
<.> FilePath
ext)
where
(FilePath
a,FilePath
b) = FilePath -> (FilePath, FilePath)
splitFileName FilePath
pth
ext :: FilePath
ext = FilePath -> FilePath
takeExtension FilePath
b
hasTrailingPathSeparator :: FilePath -> Bool
hasTrailingPathSeparator :: FilePath -> Bool
hasTrailingPathSeparator FilePath
"" = Bool
False
hasTrailingPathSeparator FilePath
x = Char -> Bool
isPathSeparator (forall a. [a] -> a
last FilePath
x)
addTrailingPathSeparator :: FilePath -> FilePath
addTrailingPathSeparator :: FilePath -> FilePath
addTrailingPathSeparator FilePath
x = if FilePath -> Bool
hasTrailingPathSeparator FilePath
x then FilePath
x else FilePath
x forall a. [a] -> [a] -> [a]
++ [Char
pathSeparator]
dropTrailingPathSeparator :: FilePath -> FilePath
dropTrailingPathSeparator :: FilePath -> FilePath
dropTrailingPathSeparator FilePath
x =
if FilePath -> Bool
hasTrailingPathSeparator FilePath
x Bool -> Bool -> Bool
&& Bool -> Bool
not (FilePath -> Bool
isDrive FilePath
x)
then let x' :: FilePath
x' = forall a. [a] -> [a]
reverse forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
dropWhile Char -> Bool
isPathSeparator forall a b. (a -> b) -> a -> b
$ forall a. [a] -> [a]
reverse FilePath
x
in if forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
x' then [Char
pathSeparator] else FilePath
x'
else FilePath
x
takeDirectory :: FilePath -> FilePath
takeDirectory :: FilePath -> FilePath
takeDirectory FilePath
x = if FilePath -> Bool
isDrive FilePath
file then FilePath
file
else if forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
res Bool -> Bool -> Bool
&& Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
file) then FilePath
file
else FilePath
res
where
res :: FilePath
res = forall a. [a] -> [a]
reverse forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
dropWhile Char -> Bool
isPathSeparator forall a b. (a -> b) -> a -> b
$ forall a. [a] -> [a]
reverse FilePath
file
file :: FilePath
file = FilePath -> FilePath
dropFileName FilePath
x
replaceDirectory :: FilePath -> String -> FilePath
replaceDirectory :: FilePath -> FilePath -> FilePath
replaceDirectory FilePath
x FilePath
dir = FilePath -> FilePath -> FilePath
combineAlways FilePath
dir (FilePath -> FilePath
takeFileName FilePath
x)
combine :: FilePath -> FilePath -> FilePath
combine :: FilePath -> FilePath -> FilePath
combine FilePath
a FilePath
b | FilePath -> Bool
hasDrive FilePath
b Bool -> Bool -> Bool
|| (Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
b) Bool -> Bool -> Bool
&& Char -> Bool
isPathSeparator (forall a. [a] -> a
head FilePath
b)) = FilePath
b
| Bool
otherwise = FilePath -> FilePath -> FilePath
combineAlways FilePath
a FilePath
b
combineAlways :: FilePath -> FilePath -> FilePath
combineAlways :: FilePath -> FilePath -> FilePath
combineAlways FilePath
a FilePath
b | forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
a = FilePath
b
| forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
b = FilePath
a
| Char -> Bool
isPathSeparator (forall a. [a] -> a
last FilePath
a) = FilePath
a forall a. [a] -> [a] -> [a]
++ FilePath
b
| FilePath -> Bool
isDrive FilePath
a = FilePath -> FilePath -> FilePath
joinDrive FilePath
a FilePath
b
| Bool
otherwise = FilePath
a forall a. [a] -> [a] -> [a]
++ [Char
pathSeparator] forall a. [a] -> [a] -> [a]
++ FilePath
b
(</>) :: FilePath -> FilePath -> FilePath
</> :: FilePath -> FilePath -> FilePath
(</>) = FilePath -> FilePath -> FilePath
combine
splitPath :: FilePath -> [FilePath]
splitPath :: FilePath -> [FilePath]
splitPath FilePath
x = [FilePath
drive | FilePath
drive forall a. Eq a => a -> a -> Bool
/= FilePath
""] forall a. [a] -> [a] -> [a]
++ FilePath -> [FilePath]
f FilePath
path
where
(FilePath
drive,FilePath
path) = FilePath -> (FilePath, FilePath)
splitDrive FilePath
x
f :: FilePath -> [FilePath]
f FilePath
"" = []
f FilePath
y = (FilePath
aforall a. [a] -> [a] -> [a]
++FilePath
c) forall a. a -> [a] -> [a]
: FilePath -> [FilePath]
f FilePath
d
where
(FilePath
a,FilePath
b) = forall a. (a -> Bool) -> [a] -> ([a], [a])
break Char -> Bool
isPathSeparator FilePath
y
(FilePath
c,FilePath
d) = forall a. (a -> Bool) -> [a] -> ([a], [a])
break (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
isPathSeparator) FilePath
b
splitDirectories :: FilePath -> [FilePath]
splitDirectories :: FilePath -> [FilePath]
splitDirectories FilePath
path =
if FilePath -> Bool
hasDrive FilePath
path then forall a. [a] -> a
head [FilePath]
pathComponents forall a. a -> [a] -> [a]
: [FilePath] -> [FilePath]
f (forall a. [a] -> [a]
tail [FilePath]
pathComponents)
else [FilePath] -> [FilePath]
f [FilePath]
pathComponents
where
pathComponents :: [FilePath]
pathComponents = FilePath -> [FilePath]
splitPath FilePath
path
f :: [FilePath] -> [FilePath]
f [FilePath]
xs = forall a b. (a -> b) -> [a] -> [b]
map FilePath -> FilePath
g [FilePath]
xs
g :: FilePath -> FilePath
g FilePath
x = if forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
res then FilePath
x else FilePath
res
where res :: FilePath
res = forall a. (a -> Bool) -> [a] -> [a]
takeWhile (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
isPathSeparator) FilePath
x
joinPath :: [FilePath] -> FilePath
joinPath :: [FilePath] -> FilePath
joinPath [FilePath]
x = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr FilePath -> FilePath -> FilePath
combine FilePath
"" [FilePath]
x
equalFilePath :: FilePath -> FilePath -> Bool
equalFilePath :: FilePath -> FilePath -> Bool
equalFilePath FilePath
a FilePath
b = FilePath -> FilePath
f FilePath
a forall a. Eq a => a -> a -> Bool
== FilePath -> FilePath
f FilePath
b
where
f :: FilePath -> FilePath
f FilePath
x | Bool
isWindows = FilePath -> FilePath
dropTrailSlash forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath
normalise FilePath
x
| Bool
otherwise = FilePath -> FilePath
dropTrailSlash forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath
normalise FilePath
x
dropTrailSlash :: FilePath -> FilePath
dropTrailSlash FilePath
x | forall (t :: * -> *) a. Foldable t => t a -> Int
length FilePath
x forall a. Ord a => a -> a -> Bool
>= Int
2 Bool -> Bool -> Bool
&& Char -> Bool
isPathSeparator (forall a. [a] -> a
last FilePath
x) = forall a. [a] -> [a]
init FilePath
x
| Bool
otherwise = FilePath
x
makeRelative :: FilePath -> FilePath -> FilePath
makeRelative :: FilePath -> FilePath -> FilePath
makeRelative FilePath
root FilePath
path
| FilePath -> FilePath -> Bool
equalFilePath FilePath
root FilePath
path = FilePath
"."
| FilePath -> FilePath
takeAbs FilePath
root forall a. Eq a => a -> a -> Bool
/= FilePath -> FilePath
takeAbs FilePath
path = FilePath
path
| Bool
otherwise = FilePath -> FilePath -> FilePath
f (FilePath -> FilePath
dropAbs FilePath
root) (FilePath -> FilePath
dropAbs FilePath
path)
where
f :: FilePath -> FilePath -> FilePath
f FilePath
"" FilePath
y = forall a. (a -> Bool) -> [a] -> [a]
dropWhile Char -> Bool
isPathSeparator FilePath
y
f FilePath
x FilePath
y = let (FilePath
x1,FilePath
x2) = FilePath -> (FilePath, FilePath)
g FilePath
x
(FilePath
y1,FilePath
y2) = FilePath -> (FilePath, FilePath)
g FilePath
y
in if FilePath -> FilePath -> Bool
equalFilePath FilePath
x1 FilePath
y1 then FilePath -> FilePath -> FilePath
f FilePath
x2 FilePath
y2 else FilePath
path
g :: FilePath -> (FilePath, FilePath)
g FilePath
x = (forall a. (a -> Bool) -> [a] -> [a]
dropWhile Char -> Bool
isPathSeparator FilePath
a, forall a. (a -> Bool) -> [a] -> [a]
dropWhile Char -> Bool
isPathSeparator FilePath
b)
where (FilePath
a,FilePath
b) = forall a. (a -> Bool) -> [a] -> ([a], [a])
break Char -> Bool
isPathSeparator forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
dropWhile Char -> Bool
isPathSeparator FilePath
x
dropAbs :: FilePath -> FilePath
dropAbs (Char
x:FilePath
xs) | Char -> Bool
isPathSeparator Char
x = FilePath
xs
dropAbs FilePath
x = FilePath -> FilePath
dropDrive FilePath
x
takeAbs :: FilePath -> FilePath
takeAbs (Char
x:FilePath
_) | Char -> Bool
isPathSeparator Char
x = [Char
pathSeparator]
takeAbs FilePath
x = forall a b. (a -> b) -> [a] -> [b]
map (\Char
y -> if Char -> Bool
isPathSeparator Char
y then Char
pathSeparator else Char -> Char
toLower Char
y) forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath
takeDrive FilePath
x
normalise :: FilePath -> FilePath
normalise :: FilePath -> FilePath
normalise FilePath
path = FilePath -> FilePath -> FilePath
joinDrive (FilePath -> FilePath
normaliseDrive FilePath
drv) (FilePath -> FilePath
f FilePath
pth)
forall a. [a] -> [a] -> [a]
++ [Char
pathSeparator | Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
pth) Bool -> Bool -> Bool
&& Char -> Bool
isPathSeparator (forall a. [a] -> a
last FilePath
pth)]
where
(FilePath
drv,FilePath
pth) = FilePath -> (FilePath, FilePath)
splitDrive FilePath
path
f :: FilePath -> FilePath
f = [FilePath] -> FilePath
joinPath forall b c a. (b -> c) -> (a -> b) -> a -> c
. [FilePath] -> [FilePath] -> [FilePath]
dropDots [] forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> [FilePath]
splitDirectories forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath
propSep
propSep :: FilePath -> FilePath
propSep (Char
a:Char
b:FilePath
xs)
| Char -> Bool
isPathSeparator Char
a Bool -> Bool -> Bool
&& Char -> Bool
isPathSeparator Char
b = FilePath -> FilePath
propSep (Char
aforall a. a -> [a] -> [a]
:FilePath
xs)
propSep (Char
a:FilePath
xs)
| Char -> Bool
isPathSeparator Char
a = Char
pathSeparator forall a. a -> [a] -> [a]
: FilePath -> FilePath
propSep FilePath
xs
propSep (Char
x:FilePath
xs) = Char
x forall a. a -> [a] -> [a]
: FilePath -> FilePath
propSep FilePath
xs
propSep [] = []
dropDots :: [FilePath] -> [FilePath] -> [FilePath]
dropDots [FilePath]
acc (FilePath
".":[FilePath]
xs) | Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t a -> Bool
null [FilePath]
xs = [FilePath] -> [FilePath] -> [FilePath]
dropDots [FilePath]
acc [FilePath]
xs
dropDots [FilePath]
acc (FilePath
x:[FilePath]
xs) = [FilePath] -> [FilePath] -> [FilePath]
dropDots (FilePath
xforall a. a -> [a] -> [a]
:[FilePath]
acc) [FilePath]
xs
dropDots [FilePath]
acc [] = forall a. [a] -> [a]
reverse [FilePath]
acc
normaliseDrive :: FilePath -> FilePath
normaliseDrive :: FilePath -> FilePath
normaliseDrive FilePath
drive | Bool
isPosix = FilePath
drive
normaliseDrive FilePath
drive = if forall a. Maybe a -> Bool
isJust forall a b. (a -> b) -> a -> b
$ FilePath -> Maybe (FilePath, FilePath)
readDriveLetter FilePath
x2
then forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toUpper FilePath
x2
else FilePath
drive
where
x2 :: FilePath
x2 = forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
repSlash FilePath
drive
repSlash :: Char -> Char
repSlash Char
x = if Char -> Bool
isPathSeparator Char
x then Char
pathSeparator else Char
x
isRelative :: FilePath -> Bool
isRelative :: FilePath -> Bool
isRelative = FilePath -> Bool
isRelativeDrive forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath
takeDrive
isRelativeDrive :: String -> Bool
isRelativeDrive :: FilePath -> Bool
isRelativeDrive FilePath
x = forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
x Bool -> Bool -> Bool
||
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
isPathSeparator forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> a
last forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst) (FilePath -> Maybe (FilePath, FilePath)
readDriveLetter FilePath
x)
isAbsolute :: FilePath -> Bool
isAbsolute :: FilePath -> Bool
isAbsolute = Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Bool
isRelative