{-# LANGUAGE PatternGuards #-}
module System.FilePath.Posix
    (
    
    FilePath,
    pathSeparator, pathSeparators, isPathSeparator,
    searchPathSeparator, isSearchPathSeparator,
    extSeparator, isExtSeparator,
    
    splitSearchPath, getSearchPath,
    
    splitExtension,
    takeExtension, replaceExtension, (-<.>), dropExtension, addExtension, hasExtension, (<.>),
    splitExtensions, dropExtensions, takeExtensions, replaceExtensions, isExtensionOf,
    stripExtension,
    
    splitFileName,
    takeFileName, replaceFileName, dropFileName,
    takeBaseName, replaceBaseName,
    takeDirectory, replaceDirectory,
    combine, (</>),
    splitPath, joinPath, splitDirectories,
    
    splitDrive, joinDrive,
    takeDrive, hasDrive, dropDrive, isDrive,
    
    hasTrailingPathSeparator,
    addTrailingPathSeparator,
    dropTrailingPathSeparator,
    
    normalise, equalFilePath,
    makeRelative,
    isRelative, isAbsolute,
    isValid, makeValid
    )
    where
import Data.Char(toLower, toUpper, isAsciiLower, isAsciiUpper)
import Data.Maybe(isJust)
import Data.List(stripPrefix, isSuffixOf)
import System.Environment(getEnv)
infixr 7  <.>, -<.>
infixr 5  </>
isPosix :: Bool
isPosix :: Bool
isPosix = Bool -> Bool
not Bool
isWindows
isWindows :: Bool
isWindows :: Bool
isWindows = Bool
False
pathSeparator :: Char
pathSeparator :: Char
pathSeparator = if Bool
isWindows then Char
'\\' else Char
'/'
pathSeparators :: [Char]
pathSeparators :: FilePath
pathSeparators = if Bool
isWindows then FilePath
"\\/" else FilePath
"/"
isPathSeparator :: Char -> Bool
isPathSeparator :: Char -> Bool
isPathSeparator Char
'/' = Bool
True
isPathSeparator Char
'\\' = Bool
isWindows
isPathSeparator Char
_ = Bool
False
searchPathSeparator :: Char
searchPathSeparator :: Char
searchPathSeparator = if Bool
isWindows then Char
';' else Char
':'
isSearchPathSeparator :: Char -> Bool
isSearchPathSeparator :: Char -> Bool
isSearchPathSeparator = (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
searchPathSeparator)
extSeparator :: Char
extSeparator :: Char
extSeparator = Char
'.'
isExtSeparator :: Char -> Bool
isExtSeparator :: Char -> Bool
isExtSeparator = (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
extSeparator)
splitSearchPath :: String -> [FilePath]
splitSearchPath :: FilePath -> [FilePath]
splitSearchPath = FilePath -> [FilePath]
f
    where
    f :: FilePath -> [FilePath]
f FilePath
xs = case (Char -> Bool) -> FilePath -> (FilePath, FilePath)
forall a. (a -> Bool) -> [a] -> ([a], [a])
break Char -> Bool
isSearchPathSeparator FilePath
xs of
           (FilePath
pre, []    ) -> FilePath -> [FilePath]
g FilePath
pre
           (FilePath
pre, Char
_:FilePath
post) -> FilePath -> [FilePath]
g FilePath
pre [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ FilePath -> [FilePath]
f FilePath
post
    g :: FilePath -> [FilePath]
g FilePath
"" = [FilePath
"." | Bool
isPosix]
    g (Char
'\"':x :: FilePath
x@(Char
_:FilePath
_)) | Bool
isWindows Bool -> Bool -> Bool
&& FilePath -> Char
forall a. HasCallStack => [a] -> a
last FilePath
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\"' = [FilePath -> FilePath
forall a. HasCallStack => [a] -> [a]
init FilePath
x]
    g FilePath
x = [FilePath
x]
getSearchPath :: IO [FilePath]
getSearchPath :: IO [FilePath]
getSearchPath = (FilePath -> [FilePath]) -> IO FilePath -> IO [FilePath]
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap FilePath -> [FilePath]
splitSearchPath (FilePath -> IO FilePath
getEnv FilePath
"PATH")
splitExtension :: FilePath -> (String, String)
splitExtension :: FilePath -> (FilePath, FilePath)
splitExtension FilePath
x = case FilePath
nameDot of
                       FilePath
"" -> (FilePath
x,FilePath
"")
                       FilePath
_ -> (FilePath
dir FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath -> FilePath
forall a. HasCallStack => [a] -> [a]
init FilePath
nameDot, Char
extSeparator Char -> FilePath -> FilePath
forall a. a -> [a] -> [a]
: FilePath
ext)
    where
        (FilePath
dir,FilePath
file) = FilePath -> (FilePath, FilePath)
splitFileName_ FilePath
x
        (FilePath
nameDot,FilePath
ext) = (Char -> Bool) -> FilePath -> (FilePath, FilePath)
forall a. (a -> Bool) -> [a] -> ([a], [a])
breakEnd Char -> Bool
isExtSeparator FilePath
file
takeExtension :: FilePath -> String
takeExtension :: FilePath -> FilePath
takeExtension = (FilePath, FilePath) -> FilePath
forall a b. (a, b) -> b
snd ((FilePath, FilePath) -> FilePath)
-> (FilePath -> (FilePath, FilePath)) -> FilePath -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> (FilePath, FilePath)
splitExtension
(-<.>) :: FilePath -> String -> FilePath
-<.> :: FilePath -> FilePath -> FilePath
(-<.>) = FilePath -> FilePath -> FilePath
replaceExtension
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 = (FilePath, FilePath) -> FilePath
forall a b. (a, b) -> a
fst ((FilePath, FilePath) -> FilePath)
-> (FilePath -> (FilePath, FilePath)) -> FilePath -> FilePath
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 FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
xs
              else FilePath
b FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ [Char
extSeparator] FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
xs
        (FilePath
a,FilePath
b) = FilePath -> (FilePath, FilePath)
splitDrive FilePath
file
hasExtension :: FilePath -> Bool
hasExtension :: FilePath -> Bool
hasExtension = (Char -> Bool) -> FilePath -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Char -> Bool
isExtSeparator (FilePath -> Bool) -> (FilePath -> FilePath) -> FilePath -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath
takeFileName
isExtensionOf :: String -> FilePath -> Bool
isExtensionOf :: FilePath -> FilePath -> Bool
isExtensionOf ext :: FilePath
ext@(Char
'.':FilePath
_) = FilePath -> FilePath -> Bool
forall a. Eq a => [a] -> [a] -> Bool
isSuffixOf FilePath
ext (FilePath -> Bool) -> (FilePath -> FilePath) -> FilePath -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath
takeExtensions
isExtensionOf FilePath
ext         = FilePath -> FilePath -> Bool
forall a. Eq a => [a] -> [a] -> Bool
isSuffixOf (Char
'.'Char -> FilePath -> FilePath
forall a. a -> [a] -> [a]
:FilePath
ext) (FilePath -> Bool) -> (FilePath -> FilePath) -> FilePath -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath
takeExtensions
stripExtension :: String -> FilePath -> Maybe FilePath
stripExtension :: FilePath -> FilePath -> Maybe FilePath
stripExtension []        FilePath
path = FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just FilePath
path
stripExtension ext :: FilePath
ext@(Char
x:FilePath
_) FilePath
path = FilePath -> FilePath -> Maybe FilePath
forall a. Eq a => [a] -> [a] -> Maybe [a]
stripSuffix FilePath
dotExt FilePath
path
    where dotExt :: FilePath
dotExt = if Char -> Bool
isExtSeparator Char
x then FilePath
ext else Char
'.'Char -> FilePath -> FilePath
forall a. a -> [a] -> [a]
:FilePath
ext
splitExtensions :: FilePath -> (FilePath, String)
splitExtensions :: FilePath -> (FilePath, FilePath)
splitExtensions FilePath
x = (FilePath
a FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
c, FilePath
d)
    where
        (FilePath
a,FilePath
b) = FilePath -> (FilePath, FilePath)
splitFileName_ FilePath
x
        (FilePath
c,FilePath
d) = (Char -> Bool) -> FilePath -> (FilePath, FilePath)
forall a. (a -> Bool) -> [a] -> ([a], [a])
break Char -> Bool
isExtSeparator FilePath
b
dropExtensions :: FilePath -> FilePath
dropExtensions :: FilePath -> FilePath
dropExtensions = (FilePath, FilePath) -> FilePath
forall a b. (a, b) -> a
fst ((FilePath, FilePath) -> FilePath)
-> (FilePath -> (FilePath, FilePath)) -> FilePath -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> (FilePath, FilePath)
splitExtensions
takeExtensions :: FilePath -> String
takeExtensions :: FilePath -> FilePath
takeExtensions = (FilePath, FilePath) -> FilePath
forall a b. (a, b) -> b
snd ((FilePath, FilePath) -> FilePath)
-> (FilePath -> (FilePath, FilePath)) -> FilePath -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> (FilePath, FilePath)
splitExtensions
replaceExtensions :: FilePath -> String -> FilePath
replaceExtensions :: FilePath -> FilePath -> FilePath
replaceExtensions FilePath
x FilePath
y = FilePath -> FilePath
dropExtensions FilePath
x FilePath -> FilePath -> FilePath
<.> FilePath
y
isLetter :: Char -> Bool
isLetter :: Char -> Bool
isLetter Char
x = Char -> Bool
isAsciiLower Char
x Bool -> Bool -> Bool
|| Char -> Bool
isAsciiUpper Char
x
splitDrive :: FilePath -> (FilePath, FilePath)
splitDrive :: FilePath -> (FilePath, FilePath)
splitDrive FilePath
x | Bool
isPosix = (Char -> Bool) -> FilePath -> (FilePath, FilePath)
forall a. (a -> Bool) -> [a] -> ([a], [a])
span (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'/') FilePath
x
splitDrive FilePath
x | Just (FilePath, FilePath)
y <- FilePath -> Maybe (FilePath, FilePath)
readDriveLetter FilePath
x = (FilePath, FilePath)
y
splitDrive FilePath
x | Just (FilePath, FilePath)
y <- FilePath -> Maybe (FilePath, FilePath)
readDriveUNC FilePath
x = (FilePath, FilePath)
y
splitDrive FilePath
x | Just (FilePath, FilePath)
y <- FilePath -> Maybe (FilePath, FilePath)
readDriveShare FilePath
x = (FilePath, FilePath)
y
splitDrive FilePath
x = (FilePath
"",FilePath
x)
addSlash :: FilePath -> FilePath -> (FilePath, FilePath)
addSlash :: FilePath -> FilePath -> (FilePath, FilePath)
addSlash FilePath
a FilePath
xs = (FilePath
aFilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++FilePath
c,FilePath
d)
    where (FilePath
c,FilePath
d) = (Char -> Bool) -> FilePath -> (FilePath, FilePath)
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) | (Char -> Bool) -> FilePath -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Char -> Bool
isPathSeparator [Char
s1,Char
s2,Char
s3] =
    case (Char -> Char) -> FilePath -> FilePath
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 (Int -> FilePath -> FilePath
forall a. Int -> [a] -> [a]
drop Int
4 FilePath
xs)
            in (FilePath, FilePath) -> Maybe (FilePath, FilePath)
forall a. a -> Maybe a
Just (Char
s1Char -> FilePath -> FilePath
forall a. a -> [a] -> [a]
:Char
s2Char -> FilePath -> FilePath
forall a. a -> [a] -> [a]
:Char
'?'Char -> FilePath -> FilePath
forall a. a -> [a] -> [a]
:Char
s3Char -> FilePath -> FilePath
forall a. a -> [a] -> [a]
:Int -> FilePath -> FilePath
forall a. Int -> [a] -> [a]
take Int
4 FilePath
xs FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
a, FilePath
b)
        FilePath
_ -> case FilePath -> Maybe (FilePath, FilePath)
readDriveLetter FilePath
xs of
                 
                 Just (FilePath
a,FilePath
b) -> (FilePath, FilePath) -> Maybe (FilePath, FilePath)
forall a. a -> Maybe a
Just (Char
s1Char -> FilePath -> FilePath
forall a. a -> [a] -> [a]
:Char
s2Char -> FilePath -> FilePath
forall a. a -> [a] -> [a]
:Char
'?'Char -> FilePath -> FilePath
forall a. a -> [a] -> [a]
:Char
s3Char -> FilePath -> FilePath
forall a. a -> [a] -> [a]
:FilePath
a,FilePath
b)
                 Maybe (FilePath, FilePath)
Nothing -> Maybe (FilePath, FilePath)
forall a. Maybe a
Nothing
readDriveUNC FilePath
_ = Maybe (FilePath, 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 = (FilePath, FilePath) -> Maybe (FilePath, FilePath)
forall a. a -> Maybe a
Just ((FilePath, FilePath) -> Maybe (FilePath, FilePath))
-> (FilePath, FilePath) -> Maybe (FilePath, FilePath)
forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath -> (FilePath, FilePath)
addSlash [Char
x,Char
':'] (Char
yChar -> FilePath -> FilePath
forall a. a -> [a] -> [a]
:FilePath
xs)
readDriveLetter (Char
x:Char
':':FilePath
xs) | Char -> Bool
isLetter Char
x = (FilePath, FilePath) -> Maybe (FilePath, FilePath)
forall a. a -> Maybe a
Just ([Char
x,Char
':'], FilePath
xs)
readDriveLetter FilePath
_ = Maybe (FilePath, 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 =
        (FilePath, FilePath) -> Maybe (FilePath, FilePath)
forall a. a -> Maybe a
Just (Char
s1Char -> FilePath -> FilePath
forall a. a -> [a] -> [a]
:Char
s2Char -> FilePath -> FilePath
forall a. a -> [a] -> [a]
:FilePath
a,FilePath
b)
    where (FilePath
a,FilePath
b) = FilePath -> (FilePath, FilePath)
readDriveShareName FilePath
xs
readDriveShare FilePath
_ = Maybe (FilePath, 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) = (Char -> Bool) -> FilePath -> (FilePath, FilePath)
forall a. (a -> Bool) -> [a] -> ([a], [a])
break Char -> Bool
isPathSeparator FilePath
name
joinDrive :: FilePath -> FilePath -> FilePath
joinDrive :: FilePath -> FilePath -> FilePath
joinDrive = FilePath -> FilePath -> FilePath
combineAlways
takeDrive :: FilePath -> FilePath
takeDrive :: FilePath -> FilePath
takeDrive = (FilePath, FilePath) -> FilePath
forall a b. (a, b) -> a
fst ((FilePath, FilePath) -> FilePath)
-> (FilePath -> (FilePath, FilePath)) -> FilePath -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> (FilePath, FilePath)
splitDrive
dropDrive :: FilePath -> FilePath
dropDrive :: FilePath -> FilePath
dropDrive = (FilePath, FilePath) -> FilePath
forall a b. (a, b) -> b
snd ((FilePath, FilePath) -> FilePath)
-> (FilePath -> (FilePath, FilePath)) -> FilePath -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> (FilePath, FilePath)
splitDrive
hasDrive :: FilePath -> Bool
hasDrive :: FilePath -> Bool
hasDrive = Bool -> Bool
not (Bool -> Bool) -> (FilePath -> Bool) -> FilePath -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (FilePath -> Bool) -> (FilePath -> FilePath) -> FilePath -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath
takeDrive
isDrive :: FilePath -> Bool
isDrive :: FilePath -> Bool
isDrive FilePath
x = Bool -> Bool
not (FilePath -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
x) Bool -> Bool -> Bool
&& FilePath -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (FilePath -> FilePath
dropDrive FilePath
x)
splitFileName :: FilePath -> (String, String)
splitFileName :: FilePath -> (FilePath, FilePath)
splitFileName FilePath
x = (if FilePath -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
dir then FilePath
"./" else FilePath
dir, FilePath
name)
    where
        (FilePath
dir, FilePath
name) = FilePath -> (FilePath, FilePath)
splitFileName_ FilePath
x
splitFileName_ :: FilePath -> (String, String)
splitFileName_ :: FilePath -> (FilePath, FilePath)
splitFileName_ FilePath
x = (FilePath
drv FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
dir, FilePath
file)
    where
        (FilePath
drv,FilePath
pth) = FilePath -> (FilePath, FilePath)
splitDrive FilePath
x
        (FilePath
dir,FilePath
file) = (Char -> Bool) -> FilePath -> (FilePath, FilePath)
forall a. (a -> Bool) -> [a] -> ([a], [a])
breakEnd Char -> Bool
isPathSeparator FilePath
pth
replaceFileName :: FilePath -> String -> FilePath
replaceFileName :: FilePath -> FilePath -> FilePath
replaceFileName FilePath
x FilePath
y = FilePath
a FilePath -> FilePath -> FilePath
</> FilePath
y where (FilePath
a,FilePath
_) = FilePath -> (FilePath, FilePath)
splitFileName_ FilePath
x
dropFileName :: FilePath -> FilePath
dropFileName :: FilePath -> FilePath
dropFileName = (FilePath, FilePath) -> FilePath
forall a b. (a, b) -> a
fst ((FilePath, FilePath) -> FilePath)
-> (FilePath -> (FilePath, FilePath)) -> FilePath -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> (FilePath, FilePath)
splitFileName
takeFileName :: FilePath -> FilePath
takeFileName :: FilePath -> FilePath
takeFileName = (FilePath, FilePath) -> FilePath
forall a b. (a, b) -> b
snd ((FilePath, FilePath) -> FilePath)
-> (FilePath -> (FilePath, FilePath)) -> FilePath -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> (FilePath, FilePath)
splitFileName
takeBaseName :: FilePath -> String
takeBaseName :: FilePath -> FilePath
takeBaseName = FilePath -> FilePath
dropExtension (FilePath -> FilePath)
-> (FilePath -> FilePath) -> FilePath -> FilePath
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 (FilePath -> Char
forall a. HasCallStack => [a] -> a
last FilePath
x)
hasLeadingPathSeparator :: FilePath -> Bool
hasLeadingPathSeparator :: FilePath -> Bool
hasLeadingPathSeparator FilePath
"" = Bool
False
hasLeadingPathSeparator FilePath
x = Char -> Bool
isPathSeparator (FilePath -> Char
forall a. HasCallStack => [a] -> a
head FilePath
x)
addTrailingPathSeparator :: FilePath -> FilePath
addTrailingPathSeparator :: FilePath -> FilePath
addTrailingPathSeparator FilePath
x = if FilePath -> Bool
hasTrailingPathSeparator FilePath
x then FilePath
x else FilePath
x FilePath -> FilePath -> FilePath
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' = (Char -> Bool) -> FilePath -> FilePath
forall a. (a -> Bool) -> [a] -> [a]
dropWhileEnd Char -> Bool
isPathSeparator FilePath
x
         in if FilePath -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
x' then [FilePath -> Char
forall a. HasCallStack => [a] -> a
last FilePath
x] else FilePath
x'
    else FilePath
x
takeDirectory :: FilePath -> FilePath
takeDirectory :: FilePath -> FilePath
takeDirectory = FilePath -> FilePath
dropTrailingPathSeparator (FilePath -> FilePath)
-> (FilePath -> FilePath) -> FilePath -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath
dropFileName
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
hasLeadingPathSeparator FilePath
b Bool -> Bool -> Bool
|| FilePath -> Bool
hasDrive 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 | FilePath -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
a = FilePath
b
                  | FilePath -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
b = FilePath
a
                  | FilePath -> Bool
hasTrailingPathSeparator FilePath
a = FilePath
a FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
b
                  | Bool
otherwise = case FilePath
a of
                      [Char
a1,Char
':'] | Bool
isWindows Bool -> Bool -> Bool
&& Char -> Bool
isLetter Char
a1 -> FilePath
a FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
b
                      FilePath
_ -> FilePath
a FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ [Char
pathSeparator] FilePath -> FilePath -> FilePath
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 FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
/= FilePath
""] [FilePath] -> [FilePath] -> [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
aFilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++FilePath
c) FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: FilePath -> [FilePath]
f FilePath
d
            where
                (FilePath
a,FilePath
b) = (Char -> Bool) -> FilePath -> (FilePath, FilePath)
forall a. (a -> Bool) -> [a] -> ([a], [a])
break Char -> Bool
isPathSeparator FilePath
y
                (FilePath
c,FilePath
d) = (Char -> Bool) -> FilePath -> (FilePath, FilePath)
forall a. (a -> Bool) -> [a] -> ([a], [a])
span  Char -> Bool
isPathSeparator FilePath
b
splitDirectories :: FilePath -> [FilePath]
splitDirectories :: FilePath -> [FilePath]
splitDirectories = (FilePath -> FilePath) -> [FilePath] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> FilePath
dropTrailingPathSeparator ([FilePath] -> [FilePath])
-> (FilePath -> [FilePath]) -> FilePath -> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> [FilePath]
splitPath
joinPath :: [FilePath] -> FilePath
joinPath :: [FilePath] -> FilePath
joinPath = (FilePath -> FilePath -> FilePath)
-> FilePath -> [FilePath] -> FilePath
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr FilePath -> FilePath -> FilePath
combine FilePath
""
equalFilePath :: FilePath -> FilePath -> Bool
equalFilePath :: FilePath -> FilePath -> Bool
equalFilePath FilePath
a FilePath
b = FilePath -> FilePath
f FilePath
a FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath -> FilePath
f FilePath
b
    where
        f :: FilePath -> FilePath
f FilePath
x | Bool
isWindows = FilePath -> FilePath
dropTrailingPathSeparator (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ (Char -> Char) -> FilePath -> FilePath
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath
normalise FilePath
x
            | Bool
otherwise = FilePath -> FilePath
dropTrailingPathSeparator (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath
normalise 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 FilePath -> FilePath -> Bool
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 = (Char -> Bool) -> FilePath -> FilePath
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 = ((Char -> Bool) -> FilePath -> FilePath
forall a. (a -> Bool) -> [a] -> [a]
dropWhile Char -> Bool
isPathSeparator FilePath
a, (Char -> Bool) -> FilePath -> FilePath
forall a. (a -> Bool) -> [a] -> [a]
dropWhile Char -> Bool
isPathSeparator FilePath
b)
            where (FilePath
a,FilePath
b) = (Char -> Bool) -> FilePath -> (FilePath, FilePath)
forall a. (a -> Bool) -> [a] -> ([a], [a])
break Char -> Bool
isPathSeparator (FilePath -> (FilePath, FilePath))
-> FilePath -> (FilePath, FilePath)
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> FilePath -> FilePath
forall a. (a -> Bool) -> [a] -> [a]
dropWhile Char -> Bool
isPathSeparator FilePath
x
        
        dropAbs :: FilePath -> FilePath
dropAbs FilePath
x | FilePath -> Bool
hasLeadingPathSeparator FilePath
x Bool -> Bool -> Bool
&& Bool -> Bool
not (FilePath -> Bool
hasDrive FilePath
x) = FilePath -> FilePath
forall a. HasCallStack => [a] -> [a]
tail FilePath
x
        dropAbs FilePath
x = FilePath -> FilePath
dropDrive FilePath
x
        takeAbs :: FilePath -> FilePath
takeAbs FilePath
x | FilePath -> Bool
hasLeadingPathSeparator FilePath
x Bool -> Bool -> Bool
&& Bool -> Bool
not (FilePath -> Bool
hasDrive FilePath
x) = [Char
pathSeparator]
        takeAbs FilePath
x = (Char -> Char) -> FilePath -> FilePath
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) (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath
takeDrive FilePath
x
normalise :: FilePath -> FilePath
normalise :: FilePath -> FilePath
normalise FilePath
path = FilePath
result FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ [Char
pathSeparator | Bool
addPathSeparator]
    where
        (FilePath
drv,FilePath
pth) = FilePath -> (FilePath, FilePath)
splitDrive FilePath
path
        result :: FilePath
result = FilePath -> FilePath -> FilePath
joinDrive' (FilePath -> FilePath
normaliseDrive FilePath
drv) (FilePath -> FilePath
f FilePath
pth)
        joinDrive' :: FilePath -> FilePath -> FilePath
joinDrive' FilePath
"" FilePath
"" = FilePath
"."
        joinDrive' FilePath
d FilePath
p = FilePath -> FilePath -> FilePath
joinDrive FilePath
d FilePath
p
        addPathSeparator :: Bool
addPathSeparator = FilePath -> Bool
isDirPath FilePath
pth
            Bool -> Bool -> Bool
&& Bool -> Bool
not (FilePath -> Bool
hasTrailingPathSeparator FilePath
result)
            Bool -> Bool -> Bool
&& Bool -> Bool
not (FilePath -> Bool
isRelativeDrive FilePath
drv)
        isDirPath :: FilePath -> Bool
isDirPath FilePath
xs = FilePath -> Bool
hasTrailingPathSeparator FilePath
xs
            Bool -> Bool -> Bool
|| Bool -> Bool
not (FilePath -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
xs) Bool -> Bool -> Bool
&& FilePath -> Char
forall a. HasCallStack => [a] -> a
last FilePath
xs Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'.' Bool -> Bool -> Bool
&& FilePath -> Bool
hasTrailingPathSeparator (FilePath -> FilePath
forall a. HasCallStack => [a] -> [a]
init FilePath
xs)
        f :: FilePath -> FilePath
f = [FilePath] -> FilePath
joinPath ([FilePath] -> FilePath)
-> (FilePath -> [FilePath]) -> FilePath -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [FilePath] -> [FilePath]
dropDots ([FilePath] -> [FilePath])
-> (FilePath -> [FilePath]) -> FilePath -> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [FilePath] -> [FilePath]
propSep ([FilePath] -> [FilePath])
-> (FilePath -> [FilePath]) -> FilePath -> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> [FilePath]
splitDirectories
        propSep :: [FilePath] -> [FilePath]
propSep (FilePath
x:[FilePath]
xs) | (Char -> Bool) -> FilePath -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Char -> Bool
isPathSeparator FilePath
x = [Char
pathSeparator] FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: [FilePath]
xs
                       | Bool
otherwise = FilePath
x FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: [FilePath]
xs
        propSep [] = []
        dropDots :: [FilePath] -> [FilePath]
dropDots = (FilePath -> Bool) -> [FilePath] -> [FilePath]
forall a. (a -> Bool) -> [a] -> [a]
filter (FilePath
"." FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
/=)
normaliseDrive :: FilePath -> FilePath
normaliseDrive :: FilePath -> FilePath
normaliseDrive FilePath
"" = FilePath
""
normaliseDrive FilePath
_ | Bool
isPosix = [Char
pathSeparator]
normaliseDrive FilePath
drive = if Maybe (FilePath, FilePath) -> Bool
forall a. Maybe a -> Bool
isJust (Maybe (FilePath, FilePath) -> Bool)
-> Maybe (FilePath, FilePath) -> Bool
forall a b. (a -> b) -> a -> b
$ FilePath -> Maybe (FilePath, FilePath)
readDriveLetter FilePath
x2
                       then (Char -> Char) -> FilePath -> FilePath
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toUpper FilePath
x2
                       else FilePath
x2
    where
        x2 :: FilePath
x2 = (Char -> Char) -> FilePath -> FilePath
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
isBadCharacter :: Char -> Bool
isBadCharacter :: Char -> Bool
isBadCharacter Char
x = Char
x Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'\0' Bool -> Bool -> Bool
&& Char
x Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'\31' Bool -> Bool -> Bool
|| Char
x Char -> FilePath -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` FilePath
":*?><|\""
badElements :: [FilePath]
badElements :: [FilePath]
badElements =
    [FilePath
"CON",FilePath
"PRN",FilePath
"AUX",FilePath
"NUL",FilePath
"CLOCK$"
    ,FilePath
"COM1",FilePath
"COM2",FilePath
"COM3",FilePath
"COM4",FilePath
"COM5",FilePath
"COM6",FilePath
"COM7",FilePath
"COM8",FilePath
"COM9"
    ,FilePath
"LPT1",FilePath
"LPT2",FilePath
"LPT3",FilePath
"LPT4",FilePath
"LPT5",FilePath
"LPT6",FilePath
"LPT7",FilePath
"LPT8",FilePath
"LPT9"]
isValid :: FilePath -> Bool
isValid :: FilePath -> Bool
isValid FilePath
"" = Bool
False
isValid FilePath
x | Char
'\0' Char -> FilePath -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` FilePath
x = Bool
False
isValid FilePath
_ | Bool
isPosix = Bool
True
isValid FilePath
path =
        Bool -> Bool
not ((Char -> Bool) -> FilePath -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Char -> Bool
isBadCharacter FilePath
x2) Bool -> Bool -> Bool
&&
        Bool -> Bool
not ((FilePath -> Bool) -> [FilePath] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any FilePath -> Bool
f ([FilePath] -> Bool) -> [FilePath] -> Bool
forall a b. (a -> b) -> a -> b
$ FilePath -> [FilePath]
splitDirectories FilePath
x2) Bool -> Bool -> Bool
&&
        Bool -> Bool
not (Maybe (FilePath, FilePath) -> Bool
forall a. Maybe a -> Bool
isJust (FilePath -> Maybe (FilePath, FilePath)
readDriveShare FilePath
x1) Bool -> Bool -> Bool
&& (Char -> Bool) -> FilePath -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Char -> Bool
isPathSeparator FilePath
x1) Bool -> Bool -> Bool
&&
        Bool -> Bool
not (Maybe (FilePath, FilePath) -> Bool
forall a. Maybe a -> Bool
isJust (FilePath -> Maybe (FilePath, FilePath)
readDriveUNC FilePath
x1) Bool -> Bool -> Bool
&& Bool -> Bool
not (FilePath -> Bool
hasTrailingPathSeparator FilePath
x1))
    where
        (FilePath
x1,FilePath
x2) = FilePath -> (FilePath, FilePath)
splitDrive FilePath
path
        f :: FilePath -> Bool
f FilePath
x = (Char -> Char) -> FilePath -> FilePath
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toUpper ((Char -> Bool) -> FilePath -> FilePath
forall a. (a -> Bool) -> [a] -> [a]
dropWhileEnd (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
' ') (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath
dropExtensions FilePath
x) FilePath -> [FilePath] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [FilePath]
badElements
makeValid :: FilePath -> FilePath
makeValid :: FilePath -> FilePath
makeValid FilePath
"" = FilePath
"_"
makeValid FilePath
path
        | Bool
isPosix = (Char -> Char) -> FilePath -> FilePath
forall a b. (a -> b) -> [a] -> [b]
map (\Char
x -> if Char
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\0' then Char
'_' else Char
x) FilePath
path
        | Maybe (FilePath, FilePath) -> Bool
forall a. Maybe a -> Bool
isJust (FilePath -> Maybe (FilePath, FilePath)
readDriveShare FilePath
drv) Bool -> Bool -> Bool
&& (Char -> Bool) -> FilePath -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Char -> Bool
isPathSeparator FilePath
drv = Int -> FilePath -> FilePath
forall a. Int -> [a] -> [a]
take Int
2 FilePath
drv FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"drive"
        | Maybe (FilePath, FilePath) -> Bool
forall a. Maybe a -> Bool
isJust (FilePath -> Maybe (FilePath, FilePath)
readDriveUNC FilePath
drv) Bool -> Bool -> Bool
&& Bool -> Bool
not (FilePath -> Bool
hasTrailingPathSeparator FilePath
drv) =
            FilePath -> FilePath
makeValid (FilePath
drv FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ [Char
pathSeparator] FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
pth)
        | Bool
otherwise = FilePath -> FilePath -> FilePath
joinDrive FilePath
drv (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath
validElements (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath
validChars FilePath
pth
    where
        (FilePath
drv,FilePath
pth) = FilePath -> (FilePath, FilePath)
splitDrive FilePath
path
        validChars :: FilePath -> FilePath
validChars = (Char -> Char) -> FilePath -> FilePath
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
f
        f :: Char -> Char
f Char
x = if Char -> Bool
isBadCharacter Char
x then Char
'_' else Char
x
        validElements :: FilePath -> FilePath
validElements FilePath
x = [FilePath] -> FilePath
joinPath ([FilePath] -> FilePath) -> [FilePath] -> FilePath
forall a b. (a -> b) -> a -> b
$ (FilePath -> FilePath) -> [FilePath] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> FilePath
g ([FilePath] -> [FilePath]) -> [FilePath] -> [FilePath]
forall a b. (a -> b) -> a -> b
$ FilePath -> [FilePath]
splitPath FilePath
x
        g :: FilePath -> FilePath
g FilePath
x = FilePath -> FilePath
h FilePath
a FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
b
            where (FilePath
a,FilePath
b) = (Char -> Bool) -> FilePath -> (FilePath, FilePath)
forall a. (a -> Bool) -> [a] -> ([a], [a])
break Char -> Bool
isPathSeparator FilePath
x
        h :: FilePath -> FilePath
h FilePath
x = if (Char -> Char) -> FilePath -> FilePath
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toUpper ((Char -> Bool) -> FilePath -> FilePath
forall a. (a -> Bool) -> [a] -> [a]
dropWhileEnd (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
' ') FilePath
a) FilePath -> [FilePath] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [FilePath]
badElements then FilePath
a FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"_" FilePath -> FilePath -> FilePath
<.> FilePath
b else FilePath
x
            where (FilePath
a,FilePath
b) = FilePath -> (FilePath, FilePath)
splitExtensions FilePath
x
isRelative :: FilePath -> Bool
isRelative :: FilePath -> Bool
isRelative FilePath
x = FilePath -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
drive Bool -> Bool -> Bool
|| FilePath -> Bool
isRelativeDrive FilePath
drive
    where drive :: FilePath
drive = FilePath -> FilePath
takeDrive FilePath
x
isRelativeDrive :: String -> Bool
isRelativeDrive :: FilePath -> Bool
isRelativeDrive FilePath
x =
    Bool
-> ((FilePath, FilePath) -> Bool)
-> Maybe (FilePath, FilePath)
-> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False (Bool -> Bool
not (Bool -> Bool)
-> ((FilePath, FilePath) -> Bool) -> (FilePath, FilePath) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Bool
hasTrailingPathSeparator (FilePath -> Bool)
-> ((FilePath, FilePath) -> FilePath)
-> (FilePath, FilePath)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath, FilePath) -> FilePath
forall a b. (a, b) -> a
fst) (FilePath -> Maybe (FilePath, FilePath)
readDriveLetter FilePath
x)
isAbsolute :: FilePath -> Bool
isAbsolute :: FilePath -> Bool
isAbsolute = Bool -> Bool
not (Bool -> Bool) -> (FilePath -> Bool) -> FilePath -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Bool
isRelative
dropWhileEnd :: (a -> Bool) -> [a] -> [a]
dropWhileEnd :: forall a. (a -> Bool) -> [a] -> [a]
dropWhileEnd a -> Bool
p = [a] -> [a]
forall a. [a] -> [a]
reverse ([a] -> [a]) -> ([a] -> [a]) -> [a] -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Bool) -> [a] -> [a]
forall a. (a -> Bool) -> [a] -> [a]
dropWhile a -> Bool
p ([a] -> [a]) -> ([a] -> [a]) -> [a] -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> [a]
forall a. [a] -> [a]
reverse
takeWhileEnd :: (a -> Bool) -> [a] -> [a]
takeWhileEnd :: forall a. (a -> Bool) -> [a] -> [a]
takeWhileEnd a -> Bool
p = [a] -> [a]
forall a. [a] -> [a]
reverse ([a] -> [a]) -> ([a] -> [a]) -> [a] -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Bool) -> [a] -> [a]
forall a. (a -> Bool) -> [a] -> [a]
takeWhile a -> Bool
p ([a] -> [a]) -> ([a] -> [a]) -> [a] -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> [a]
forall a. [a] -> [a]
reverse
spanEnd :: (a -> Bool) -> [a] -> ([a], [a])
spanEnd :: forall a. (a -> Bool) -> [a] -> ([a], [a])
spanEnd a -> Bool
p [a]
xs = ((a -> Bool) -> [a] -> [a]
forall a. (a -> Bool) -> [a] -> [a]
dropWhileEnd a -> Bool
p [a]
xs, (a -> Bool) -> [a] -> [a]
forall a. (a -> Bool) -> [a] -> [a]
takeWhileEnd a -> Bool
p [a]
xs)
breakEnd :: (a -> Bool) -> [a] -> ([a], [a])
breakEnd :: forall a. (a -> Bool) -> [a] -> ([a], [a])
breakEnd a -> Bool
p = (a -> Bool) -> [a] -> ([a], [a])
forall a. (a -> Bool) -> [a] -> ([a], [a])
spanEnd (Bool -> Bool
not (Bool -> Bool) -> (a -> Bool) -> a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Bool
p)
stripSuffix :: Eq a => [a] -> [a] -> Maybe [a]
stripSuffix :: forall a. Eq a => [a] -> [a] -> Maybe [a]
stripSuffix [a]
xs [a]
ys = ([a] -> [a]) -> Maybe [a] -> Maybe [a]
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [a] -> [a]
forall a. [a] -> [a]
reverse (Maybe [a] -> Maybe [a]) -> Maybe [a] -> Maybe [a]
forall a b. (a -> b) -> a -> b
$ [a] -> [a] -> Maybe [a]
forall a. Eq a => [a] -> [a] -> Maybe [a]
stripPrefix ([a] -> [a]
forall a. [a] -> [a]
reverse [a]
xs) ([a] -> [a]
forall a. [a] -> [a]
reverse [a]
ys)