{-# LANGUAGE CPP #-}

{-
  This module based on System.FilePath.Internal of file-path.
  The code was copied with the permission from the author
  of file-path, Neil Mitchell. Thanks!
  See the copyright at the end of file.
-}

module System.EasyFile.FilePath (
    -- * Separator predicates
    FilePath,
    pathSeparator, pathSeparators, isPathSeparator,
{- xxx
    searchPathSeparator, isSearchPathSeparator,
-}
    extSeparator, isExtSeparator,

{- xxx
    -- * Path methods (environment $PATH)
    splitSearchPath, getSearchPath,
-}

    -- * Extension methods
    splitExtension,
    takeExtension, replaceExtension, dropExtension, addExtension, hasExtension, (<.>),
    splitExtensions, dropExtensions, takeExtensions,

    -- * Drive methods
    splitDrive, joinDrive,
    takeDrive, hasDrive, dropDrive, isDrive,

    -- * Operations on a FilePath, as a list of directories
    splitFileName,
    takeFileName, replaceFileName, dropFileName,
    takeBaseName, replaceBaseName,
    takeDirectory, replaceDirectory,
    combine, (</>),
    splitPath, joinPath, splitDirectories,

    -- * Low level FilePath operators
    hasTrailingPathSeparator,
    addTrailingPathSeparator,
    dropTrailingPathSeparator,

    -- * File name manipulators
    normalise, equalFilePath,
    makeRelative,
    isRelative, isAbsolute,
{- xxx
    isValid, makeValid
-}

#ifdef TESTING
    , isRelativeDrive
#endif

    )
    where

import Data.Char(toLower, toUpper)
import Data.Maybe(isJust, fromJust)

-- import System.Environment(getEnv) -- xxx


infixr 7  <.>
infixr 5  </>





---------------------------------------------------------------------
-- Platform Abstraction Methods (private)

-- | Is the operating system Unix or Linux like
isPosix :: Bool
isPosix :: Bool
isPosix = Bool -> Bool
not Bool
isWindows

-- | Is the operating system Windows like
isWindows :: Bool
#if defined(mingw32_HOST_OS) || defined(__MINGW32__)
isWindows = True
#else
isWindows :: Bool
isWindows = Bool
False
#endif

---------------------------------------------------------------------
-- The basic functions

-- | The character that separates directories.
--
-- > pathSeparator ==  '/'
-- > isPathSeparator pathSeparator
pathSeparator :: Char
pathSeparator :: Char
pathSeparator = Char
'/'

-- | The list of all possible separators.
--
-- > Windows: pathSeparators == ['\\', '/']
-- > Posix:   pathSeparators == ['/']
-- > pathSeparator `elem` pathSeparators
pathSeparators :: [Char]
pathSeparators :: [Char]
pathSeparators = if Bool
isWindows then [Char]
"\\/" else [Char]
"/"

-- | Rather than using @(== 'pathSeparator')@, use this. Test if something
--   is a path separator.
--
-- > isPathSeparator a == (a `elem` pathSeparators)
isPathSeparator :: Char -> Bool
isPathSeparator :: Char -> Bool
isPathSeparator = (Char -> [Char] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Char]
pathSeparators)


{- xxx
-- | The character that is used to separate the entries in the $PATH environment variable.
--
-- > Windows: searchPathSeparator == ';'
-- > Posix:   searchPathSeparator == ':'
searchPathSeparator :: Char
searchPathSeparator = if isWindows then ';' else ':'

-- | Is the character a file separator?
--
-- > isSearchPathSeparator a == (a == searchPathSeparator)
isSearchPathSeparator :: Char -> Bool
isSearchPathSeparator = (== searchPathSeparator)
-}

-- | File extension character
--
-- > extSeparator == '.'
extSeparator :: Char
extSeparator :: Char
extSeparator = Char
'.'

-- | Is the character an extension character?
--
-- > isExtSeparator a == (a == extSeparator)
isExtSeparator :: Char -> Bool
isExtSeparator :: Char -> Bool
isExtSeparator = (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
extSeparator)




{- xxx
---------------------------------------------------------------------
-- Path methods (environment $PATH)

-- | Take a string, split it on the 'searchPathSeparator' character.
--
--   Follows the recommendations in
--   <http://www.opengroup.org/onlinepubs/009695399/basedefs/xbd_chap08.html>
--
-- > Posix:   splitSearchPath "File1:File2:File3"  == ["File1","File2","File3"]
-- > Posix:   splitSearchPath "File1::File2:File3" == ["File1",".","File2","File3"]
-- > Windows: splitSearchPath "File1;File2;File3"  == ["File1","File2","File3"]
-- > Windows: splitSearchPath "File1;;File2;File3" == ["File1","File2","File3"]
splitSearchPath :: String -> [FilePath]
splitSearchPath = f
    where
    f xs = case break isSearchPathSeparator xs of
           (pre, []    ) -> g pre
           (pre, _:post) -> g pre ++ f post

    g "" = ["." | isPosix]
    g x = [x]


-- | Get a list of filepaths in the $PATH.
getSearchPath :: IO [FilePath]
getSearchPath = fmap splitSearchPath (getEnv "PATH")
-}

---------------------------------------------------------------------
-- Extension methods

-- | Split on the extension. 'addExtension' is the inverse.
--
-- > uncurry (++) (splitExtension x) == x
-- > uncurry addExtension (splitExtension x) == x
-- > splitExtension "file.txt" == ("file",".txt")
-- > splitExtension "file" == ("file","")
-- > splitExtension "file/file.txt" == ("file/file",".txt")
-- > splitExtension "file.txt/boris" == ("file.txt/boris","")
-- > splitExtension "file.txt/boris.ext" == ("file.txt/boris",".ext")
-- > splitExtension "file/path.txt.bob.fred" == ("file/path.txt.bob",".fred")
-- > splitExtension "file/path.txt/" == ("file/path.txt/","")
splitExtension :: FilePath -> (String, String)
splitExtension :: [Char] -> ([Char], [Char])
splitExtension [Char]
x = case [Char]
d of
                       [Char]
"" -> ([Char]
x,[Char]
"")
                       (Char
y:[Char]
ys) -> ([Char]
a [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char] -> [Char]
forall a. [a] -> [a]
reverse [Char]
ys, Char
y Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: [Char] -> [Char]
forall a. [a] -> [a]
reverse [Char]
c)
    where
        ([Char]
a,[Char]
b) = [Char] -> ([Char], [Char])
splitFileName [Char]
x
        ([Char]
c,[Char]
d) = (Char -> Bool) -> [Char] -> ([Char], [Char])
forall a. (a -> Bool) -> [a] -> ([a], [a])
break Char -> Bool
isExtSeparator ([Char] -> ([Char], [Char])) -> [Char] -> ([Char], [Char])
forall a b. (a -> b) -> a -> b
$ [Char] -> [Char]
forall a. [a] -> [a]
reverse [Char]
b

-- | Get the extension of a file, returns @\"\"@ for no extension, @.ext@ otherwise.
--
-- > takeExtension x == snd (splitExtension x)
-- > Valid x => takeExtension (addExtension x "ext") == ".ext"
-- > Valid x => takeExtension (replaceExtension x "ext") == ".ext"
takeExtension :: FilePath -> String
takeExtension :: [Char] -> [Char]
takeExtension = ([Char], [Char]) -> [Char]
forall a b. (a, b) -> b
snd (([Char], [Char]) -> [Char])
-> ([Char] -> ([Char], [Char])) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> ([Char], [Char])
splitExtension

-- | Set the extension of a file, overwriting one if already present.
--
-- > replaceExtension "file.txt" ".bob" == "file.bob"
-- > replaceExtension "file.txt" "bob" == "file.bob"
-- > replaceExtension "file" ".bob" == "file.bob"
-- > replaceExtension "file.txt" "" == "file"
-- > replaceExtension "file.fred.bob" "txt" == "file.fred.txt"
replaceExtension :: FilePath -> String -> FilePath
replaceExtension :: [Char] -> [Char] -> [Char]
replaceExtension [Char]
x [Char]
y = [Char] -> [Char]
dropExtension [Char]
x [Char] -> [Char] -> [Char]
<.> [Char]
y

-- | Alias to 'addExtension', for people who like that sort of thing.
(<.>) :: FilePath -> String -> FilePath
<.> :: [Char] -> [Char] -> [Char]
(<.>) = [Char] -> [Char] -> [Char]
addExtension

-- | Remove last extension, and the \".\" preceding it.
--
-- > dropExtension x == fst (splitExtension x)
dropExtension :: FilePath -> FilePath
dropExtension :: [Char] -> [Char]
dropExtension = ([Char], [Char]) -> [Char]
forall a b. (a, b) -> a
fst (([Char], [Char]) -> [Char])
-> ([Char] -> ([Char], [Char])) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> ([Char], [Char])
splitExtension

-- | Add an extension, even if there is already one there.
--   E.g. @addExtension \"foo.txt\" \"bat\" -> \"foo.txt.bat\"@.
--
-- > addExtension "file.txt" "bib" == "file.txt.bib"
-- > addExtension "file." ".bib" == "file..bib"
-- > addExtension "file" ".bib" == "file.bib"
-- > addExtension "/" "x" == "/.x"
-- > Valid x => takeFileName (addExtension (addTrailingPathSeparator x) "ext") == ".ext"
-- > Windows: addExtension "\\\\share" ".txt" == "\\\\share\\.txt"
addExtension :: FilePath -> String -> FilePath
addExtension :: [Char] -> [Char] -> [Char]
addExtension [Char]
file [Char]
"" = [Char]
file
addExtension [Char]
file xs :: [Char]
xs@(Char
x:[Char]
_) = [Char] -> [Char] -> [Char]
joinDrive [Char]
a [Char]
res
    where
        res :: [Char]
res = if Char -> Bool
isExtSeparator Char
x then [Char]
b [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
xs
              else [Char]
b [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char
extSeparator] [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
xs

        ([Char]
a,[Char]
b) = [Char] -> ([Char], [Char])
splitDrive [Char]
file

-- | Does the given filename have an extension?
--
-- > null (takeExtension x) == not (hasExtension x)
hasExtension :: FilePath -> Bool
hasExtension :: [Char] -> Bool
hasExtension = (Char -> Bool) -> [Char] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Char -> Bool
isExtSeparator ([Char] -> Bool) -> ([Char] -> [Char]) -> [Char] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [Char]
takeFileName


-- | Split on all extensions
--
-- > splitExtensions "file.tar.gz" == ("file",".tar.gz")
splitExtensions :: FilePath -> (FilePath, String)
splitExtensions :: [Char] -> ([Char], [Char])
splitExtensions [Char]
x = ([Char]
a [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
c, [Char]
d)
    where
        ([Char]
a,[Char]
b) = [Char] -> ([Char], [Char])
splitFileName [Char]
x
        ([Char]
c,[Char]
d) = (Char -> Bool) -> [Char] -> ([Char], [Char])
forall a. (a -> Bool) -> [a] -> ([a], [a])
break Char -> Bool
isExtSeparator [Char]
b

-- | Drop all extensions
--
-- > not $ hasExtension (dropExtensions x)
dropExtensions :: FilePath -> FilePath
dropExtensions :: [Char] -> [Char]
dropExtensions = ([Char], [Char]) -> [Char]
forall a b. (a, b) -> a
fst (([Char], [Char]) -> [Char])
-> ([Char] -> ([Char], [Char])) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> ([Char], [Char])
splitExtensions

-- | Get all extensions
--
-- > takeExtensions "file.tar.gz" == ".tar.gz"
takeExtensions :: FilePath -> String
takeExtensions :: [Char] -> [Char]
takeExtensions = ([Char], [Char]) -> [Char]
forall a b. (a, b) -> b
snd (([Char], [Char]) -> [Char])
-> ([Char] -> ([Char], [Char])) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> ([Char], [Char])
splitExtensions



---------------------------------------------------------------------
-- Drive methods

-- | Is the given character a valid drive letter?
-- only a-z and A-Z are letters, not isAlpha which is more unicodey
isLetter :: Char -> Bool
isLetter :: Char -> Bool
isLetter Char
x = (Char
x Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'a' Bool -> Bool -> Bool
&& Char
x Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'z') Bool -> Bool -> Bool
|| (Char
x Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'A' Bool -> Bool -> Bool
&& Char
x Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'Z')


-- | Split a path into a drive and a path.
--   On Unix, \/ is a Drive.
--
-- > uncurry (++) (splitDrive x) == x
-- > Windows: splitDrive "file" == ("","file")
-- > Windows: splitDrive "c:/file" == ("c:/","file")
-- > Windows: splitDrive "\\\\shared\\test" == ("\\\\shared\\","test")
-- > Windows: splitDrive "\\\\shared" == ("\\\\shared","")
-- > Windows: splitDrive "\\\\?\\UNC\\shared\\file" == ("\\\\?\\UNC\\shared\\","file")
-- > Windows: splitDrive "\\\\?\\UNCshared\\file" == ("\\\\?\\","UNCshared\\file")
-- > Windows: splitDrive "\\\\?\\d:\\file" == ("\\\\?\\d:\\","file")
-- > Windows: splitDrive "/d" == ("","/d") -- xxx
-- > Posix:   splitDrive "/test" == ("/","test") -- xxx
-- > Posix:   splitDrive "//test" == ("//","test")
-- > Posix:   splitDrive "test/file" == ("","test/file")
-- > Posix:   splitDrive "file" == ("","file")
splitDrive :: FilePath -> (FilePath, FilePath)
splitDrive :: [Char] -> ([Char], [Char])
splitDrive [Char]
x | Bool
isPosix = (Char -> Bool) -> [Char] -> ([Char], [Char])
forall a. (a -> Bool) -> [a] -> ([a], [a])
span (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'/') [Char]
x

splitDrive [Char]
x | Maybe ([Char], [Char]) -> Bool
forall a. Maybe a -> Bool
isJust Maybe ([Char], [Char])
y = Maybe ([Char], [Char]) -> ([Char], [Char])
forall a. HasCallStack => Maybe a -> a
fromJust Maybe ([Char], [Char])
y
    where y :: Maybe ([Char], [Char])
y = [Char] -> Maybe ([Char], [Char])
readDriveLetter [Char]
x

splitDrive [Char]
x | Maybe ([Char], [Char]) -> Bool
forall a. Maybe a -> Bool
isJust Maybe ([Char], [Char])
y = Maybe ([Char], [Char]) -> ([Char], [Char])
forall a. HasCallStack => Maybe a -> a
fromJust Maybe ([Char], [Char])
y
    where y :: Maybe ([Char], [Char])
y = [Char] -> Maybe ([Char], [Char])
readDriveUNC [Char]
x

splitDrive [Char]
x | Maybe ([Char], [Char]) -> Bool
forall a. Maybe a -> Bool
isJust Maybe ([Char], [Char])
y = Maybe ([Char], [Char]) -> ([Char], [Char])
forall a. HasCallStack => Maybe a -> a
fromJust Maybe ([Char], [Char])
y
    where y :: Maybe ([Char], [Char])
y = [Char] -> Maybe ([Char], [Char])
readDriveShare [Char]
x

splitDrive [Char]
x = ([Char]
"",[Char]
x)

addSlash :: FilePath -> FilePath -> (FilePath, FilePath)
addSlash :: [Char] -> [Char] -> ([Char], [Char])
addSlash [Char]
a [Char]
xs = ([Char]
a[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++[Char]
c,[Char]
d)
    where ([Char]
c,[Char]
d) = (Char -> Bool) -> [Char] -> ([Char], [Char])
forall a. (a -> Bool) -> [a] -> ([a], [a])
span Char -> Bool
isPathSeparator [Char]
xs

-- http://msdn.microsoft.com/library/default.asp?url=/library/en-us/fileio/fs/naming_a_file.asp
-- "\\?\D:\<path>" or "\\?\UNC\<server>\<share>"
-- a is "\\?\"
readDriveUNC :: FilePath -> Maybe (FilePath, FilePath)
readDriveUNC :: [Char] -> Maybe ([Char], [Char])
readDriveUNC (Char
s1:Char
s2:Char
'?':Char
s3:[Char]
xs) | (Char -> Bool) -> [Char] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Char -> Bool
isPathSeparator [Char
s1,Char
s2,Char
s3] =
    case (Char -> Char) -> [Char] -> [Char]
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toUpper [Char]
xs of
        (Char
'U':Char
'N':Char
'C':Char
s4:[Char]
_) | Char -> Bool
isPathSeparator Char
s4 ->
            let ([Char]
a,[Char]
b) = [Char] -> ([Char], [Char])
readDriveShareName (Int -> [Char] -> [Char]
forall a. Int -> [a] -> [a]
drop Int
4 [Char]
xs)
            in ([Char], [Char]) -> Maybe ([Char], [Char])
forall a. a -> Maybe a
Just (Char
s1Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:Char
s2Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:Char
'?'Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:Char
s3Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:Int -> [Char] -> [Char]
forall a. Int -> [a] -> [a]
take Int
4 [Char]
xs [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
a, [Char]
b)
        [Char]
_ -> case [Char] -> Maybe ([Char], [Char])
readDriveLetter [Char]
xs of
                 Just ([Char]
a,[Char]
b) -> ([Char], [Char]) -> Maybe ([Char], [Char])
forall a. a -> Maybe a
Just (Char
s1Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:Char
s2Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:Char
'?'Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:Char
s3Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:[Char]
a,[Char]
b)
                 Maybe ([Char], [Char])
Nothing -> Maybe ([Char], [Char])
forall a. Maybe a
Nothing
readDriveUNC [Char]
_ = Maybe ([Char], [Char])
forall a. Maybe a
Nothing

{- c:\ -}
readDriveLetter :: String -> Maybe (FilePath, FilePath)
readDriveLetter :: [Char] -> Maybe ([Char], [Char])
readDriveLetter (Char
x:Char
':':Char
y:[Char]
xs) | Char -> Bool
isLetter Char
x Bool -> Bool -> Bool
&& Char -> Bool
isPathSeparator Char
y = ([Char], [Char]) -> Maybe ([Char], [Char])
forall a. a -> Maybe a
Just (([Char], [Char]) -> Maybe ([Char], [Char]))
-> ([Char], [Char]) -> Maybe ([Char], [Char])
forall a b. (a -> b) -> a -> b
$ [Char] -> [Char] -> ([Char], [Char])
addSlash [Char
x,Char
':'] (Char
yChar -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:[Char]
xs)
readDriveLetter (Char
x:Char
':':[Char]
xs) | Char -> Bool
isLetter Char
x = ([Char], [Char]) -> Maybe ([Char], [Char])
forall a. a -> Maybe a
Just ([Char
x,Char
':'], [Char]
xs)
readDriveLetter [Char]
_ = Maybe ([Char], [Char])
forall a. Maybe a
Nothing

{- \\sharename\ -}
readDriveShare :: String -> Maybe (FilePath, FilePath)
readDriveShare :: [Char] -> Maybe ([Char], [Char])
readDriveShare (Char
s1:Char
s2:[Char]
xs) | Char -> Bool
isPathSeparator Char
s1 Bool -> Bool -> Bool
&& Char -> Bool
isPathSeparator Char
s2 =
        ([Char], [Char]) -> Maybe ([Char], [Char])
forall a. a -> Maybe a
Just (Char
s1Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:Char
s2Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:[Char]
a,[Char]
b)
    where ([Char]
a,[Char]
b) = [Char] -> ([Char], [Char])
readDriveShareName [Char]
xs
readDriveShare [Char]
_ = Maybe ([Char], [Char])
forall a. Maybe a
Nothing

{- assume you have already seen \\ -}
{- share\bob -> "share","\","bob" -}
readDriveShareName :: String -> (FilePath, FilePath)
readDriveShareName :: [Char] -> ([Char], [Char])
readDriveShareName [Char]
name = [Char] -> [Char] -> ([Char], [Char])
addSlash [Char]
a [Char]
b
    where ([Char]
a,[Char]
b) = (Char -> Bool) -> [Char] -> ([Char], [Char])
forall a. (a -> Bool) -> [a] -> ([a], [a])
break Char -> Bool
isPathSeparator [Char]
name



-- | Join a drive and the rest of the path.
--
-- >          uncurry joinDrive (splitDrive x) == x
-- > Windows: joinDrive "C:" "foo" == "C:foo"
-- > Windows: joinDrive "C:/" "bar" == "C:/bar"
-- > Windows: joinDrive "\\\\share" "foo" == "\\\\share/foo" -- xxx
-- > Windows: joinDrive "/:" "foo" == "/:/foo" -- xxx
joinDrive :: FilePath -> FilePath -> FilePath
joinDrive :: [Char] -> [Char] -> [Char]
joinDrive [Char]
a [Char]
b | Bool
isPosix = [Char]
a [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
b
              | [Char] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Char]
a = [Char]
b
              | [Char] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Char]
b = [Char]
a
              | Char -> Bool
isPathSeparator ([Char] -> Char
forall a. [a] -> a
last [Char]
a) = [Char]
a [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
b
              | Bool
otherwise = case [Char]
a of
                                [Char
a1,Char
':'] | Char -> Bool
isLetter Char
a1 -> [Char]
a [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
b
                                [Char]
_ -> [Char]
a [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char
pathSeparator] [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
b

-- | Get the drive from a filepath.
--
-- > takeDrive x == fst (splitDrive x)
takeDrive :: FilePath -> FilePath
takeDrive :: [Char] -> [Char]
takeDrive = ([Char], [Char]) -> [Char]
forall a b. (a, b) -> a
fst (([Char], [Char]) -> [Char])
-> ([Char] -> ([Char], [Char])) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> ([Char], [Char])
splitDrive

-- | Delete the drive, if it exists.
--
-- > dropDrive x == snd (splitDrive x)
dropDrive :: FilePath -> FilePath
dropDrive :: [Char] -> [Char]
dropDrive = ([Char], [Char]) -> [Char]
forall a b. (a, b) -> b
snd (([Char], [Char]) -> [Char])
-> ([Char] -> ([Char], [Char])) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> ([Char], [Char])
splitDrive

-- | Does a path have a drive.
--
-- > not (hasDrive x) == null (takeDrive x)
hasDrive :: FilePath -> Bool
hasDrive :: [Char] -> Bool
hasDrive = Bool -> Bool
not (Bool -> Bool) -> ([Char] -> Bool) -> [Char] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([Char] -> Bool) -> ([Char] -> [Char]) -> [Char] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [Char]
takeDrive


-- | Is an element a drive
isDrive :: FilePath -> Bool
isDrive :: [Char] -> Bool
isDrive = [Char] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([Char] -> Bool) -> ([Char] -> [Char]) -> [Char] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [Char]
dropDrive


---------------------------------------------------------------------
-- Operations on a filepath, as a list of directories

-- | Split a filename into directory and file. 'combine' is the inverse.
--
-- > uncurry (++) (splitFileName x) == x
-- > Valid x => uncurry combine (splitFileName x) == x
-- > splitFileName "file/bob.txt" == ("file/", "bob.txt")
-- > splitFileName "file/" == ("file/", "")
-- > splitFileName "bob" == ("", "bob")
-- > Posix:   splitFileName "/" == ("/","")
-- > Windows: splitFileName "c:" == ("c:","")
splitFileName :: FilePath -> (String, String)
splitFileName :: [Char] -> ([Char], [Char])
splitFileName [Char]
x = ([Char]
c [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char] -> [Char]
forall a. [a] -> [a]
reverse [Char]
b, [Char] -> [Char]
forall a. [a] -> [a]
reverse [Char]
a)
    where
        ([Char]
a,[Char]
b) = (Char -> Bool) -> [Char] -> ([Char], [Char])
forall a. (a -> Bool) -> [a] -> ([a], [a])
break Char -> Bool
isPathSeparator ([Char] -> ([Char], [Char])) -> [Char] -> ([Char], [Char])
forall a b. (a -> b) -> a -> b
$ [Char] -> [Char]
forall a. [a] -> [a]
reverse [Char]
d
        ([Char]
c,[Char]
d) = [Char] -> ([Char], [Char])
splitDrive [Char]
x


-- | Set the filename.
--
-- > Valid x => replaceFileName x (takeFileName x) == x
replaceFileName :: FilePath -> String -> FilePath
replaceFileName :: [Char] -> [Char] -> [Char]
replaceFileName [Char]
x [Char]
y = [Char] -> [Char]
dropFileName [Char]
x [Char] -> [Char] -> [Char]
</> [Char]
y

-- | Drop the filename.
--
-- > dropFileName x == fst (splitFileName x)
dropFileName :: FilePath -> FilePath
dropFileName :: [Char] -> [Char]
dropFileName = ([Char], [Char]) -> [Char]
forall a b. (a, b) -> a
fst (([Char], [Char]) -> [Char])
-> ([Char] -> ([Char], [Char])) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> ([Char], [Char])
splitFileName


-- | Get the file name.
--
-- > takeFileName "test/" == ""
-- > takeFileName x `isSuffixOf` x
-- > takeFileName x == snd (splitFileName x)
-- > Valid x => takeFileName (replaceFileName x "fred") == "fred"
-- > Valid x => takeFileName (x </> "fred") == "fred"
-- > Valid x => isRelative (takeFileName x)
takeFileName :: FilePath -> FilePath
takeFileName :: [Char] -> [Char]
takeFileName = ([Char], [Char]) -> [Char]
forall a b. (a, b) -> b
snd (([Char], [Char]) -> [Char])
-> ([Char] -> ([Char], [Char])) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> ([Char], [Char])
splitFileName

-- | Get the base name, without an extension or path.
--
-- > takeBaseName "file/test.txt" == "test"
-- > takeBaseName "dave.ext" == "dave"
-- > takeBaseName "" == ""
-- > takeBaseName "test" == "test"
-- > takeBaseName (addTrailingPathSeparator x) == ""
-- > takeBaseName "file/file.tar.gz" == "file.tar"
takeBaseName :: FilePath -> String
takeBaseName :: [Char] -> [Char]
takeBaseName = [Char] -> [Char]
dropExtension ([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [Char]
takeFileName

-- | Set the base name.
--
-- > replaceBaseName "file/test.txt" "bob" == "file/bob.txt"
-- > replaceBaseName "fred" "bill" == "bill"
-- > replaceBaseName "/dave/fred/bob.gz.tar" "new" == "/dave/fred/new.tar"
-- > replaceBaseName x (takeBaseName x) == x
replaceBaseName :: FilePath -> String -> FilePath
replaceBaseName :: [Char] -> [Char] -> [Char]
replaceBaseName [Char]
pth [Char]
nam = [Char] -> [Char] -> [Char]
combineAlways [Char]
a ([Char]
nam [Char] -> [Char] -> [Char]
<.> [Char]
ext)
    where
        ([Char]
a,[Char]
b) = [Char] -> ([Char], [Char])
splitFileName [Char]
pth
        ext :: [Char]
ext = [Char] -> [Char]
takeExtension [Char]
b

-- | Is an item either a directory or the last character a path separator?
--
-- > hasTrailingPathSeparator "test" == False
-- > hasTrailingPathSeparator "test/" == True
hasTrailingPathSeparator :: FilePath -> Bool
hasTrailingPathSeparator :: [Char] -> Bool
hasTrailingPathSeparator [Char]
"" = Bool
False
hasTrailingPathSeparator [Char]
x = Char -> Bool
isPathSeparator ([Char] -> Char
forall a. [a] -> a
last [Char]
x)


-- | Add a trailing file path separator if one is not already present.
--
-- > hasTrailingPathSeparator (addTrailingPathSeparator x)
-- > hasTrailingPathSeparator x ==> addTrailingPathSeparator x == x
-- > addTrailingPathSeparator "test/rest" == "test/rest/"
addTrailingPathSeparator :: FilePath -> FilePath
addTrailingPathSeparator :: [Char] -> [Char]
addTrailingPathSeparator [Char]
x = if [Char] -> Bool
hasTrailingPathSeparator [Char]
x then [Char]
x else [Char]
x [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char
pathSeparator]


-- | Remove any trailing path separators
--
-- > dropTrailingPathSeparator "file/test/" == "file/test"
-- > not (hasTrailingPathSeparator (dropTrailingPathSeparator x)) || isDrive x
-- > dropTrailingPathSeparator "/" == "/"
dropTrailingPathSeparator :: FilePath -> FilePath
dropTrailingPathSeparator :: [Char] -> [Char]
dropTrailingPathSeparator [Char]
x =
    if [Char] -> Bool
hasTrailingPathSeparator [Char]
x Bool -> Bool -> Bool
&& Bool -> Bool
not ([Char] -> Bool
isDrive [Char]
x)
    then let x' :: [Char]
x' = [Char] -> [Char]
forall a. [a] -> [a]
reverse ([Char] -> [Char]) -> [Char] -> [Char]
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> [Char] -> [Char]
forall a. (a -> Bool) -> [a] -> [a]
dropWhile Char -> Bool
isPathSeparator ([Char] -> [Char]) -> [Char] -> [Char]
forall a b. (a -> b) -> a -> b
$ [Char] -> [Char]
forall a. [a] -> [a]
reverse [Char]
x
         in if [Char] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Char]
x' then [Char
pathSeparator] else [Char]
x'
    else [Char]
x


-- | Get the directory name, move up one level.
--
-- >           takeDirectory x `isPrefixOf` x
-- >           takeDirectory "foo" == ""
-- >           takeDirectory "/foo/bar/baz" == "/foo/bar"
-- >           takeDirectory "/foo/bar/baz/" == "/foo/bar/baz"
-- >           takeDirectory "foo/bar/baz" == "foo/bar"
-- > Windows:  takeDirectory "foo\\bar\\\\" == "foo\\bar" -- xxx
-- > Windows:  takeDirectory "C:/" == "C:/"
takeDirectory :: FilePath -> FilePath
takeDirectory :: [Char] -> [Char]
takeDirectory [Char]
x = if [Char] -> Bool
isDrive [Char]
file then [Char]
file
                  else if [Char] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Char]
res Bool -> Bool -> Bool
&& Bool -> Bool
not ([Char] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Char]
file) then [Char]
file
                  else [Char]
res
    where
        res :: [Char]
res = [Char] -> [Char]
forall a. [a] -> [a]
reverse ([Char] -> [Char]) -> [Char] -> [Char]
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> [Char] -> [Char]
forall a. (a -> Bool) -> [a] -> [a]
dropWhile Char -> Bool
isPathSeparator ([Char] -> [Char]) -> [Char] -> [Char]
forall a b. (a -> b) -> a -> b
$ [Char] -> [Char]
forall a. [a] -> [a]
reverse [Char]
file
        file :: [Char]
file = [Char] -> [Char]
dropFileName [Char]
x

-- | Set the directory, keeping the filename the same.
--
-- > replaceDirectory x (takeDirectory x) `equalFilePath` x
replaceDirectory :: FilePath -> String -> FilePath
replaceDirectory :: [Char] -> [Char] -> [Char]
replaceDirectory [Char]
x [Char]
dir = [Char] -> [Char] -> [Char]
combineAlways [Char]
dir ([Char] -> [Char]
takeFileName [Char]
x)


-- | Combine two paths, if the second path 'isAbsolute', then it returns the second.
--
-- > Valid x => combine (takeDirectory x) (takeFileName x) `equalFilePath` x
-- > combine "/" "test" == "/test"
-- > combine "home" "bob" == "home/bob"
combine :: FilePath -> FilePath -> FilePath
combine :: [Char] -> [Char] -> [Char]
combine [Char]
a [Char]
b | [Char] -> Bool
hasDrive [Char]
b Bool -> Bool -> Bool
|| (Bool -> Bool
not ([Char] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Char]
b) Bool -> Bool -> Bool
&& Char -> Bool
isPathSeparator ([Char] -> Char
forall a. [a] -> a
head [Char]
b)) = [Char]
b
            | Bool
otherwise = [Char] -> [Char] -> [Char]
combineAlways [Char]
a [Char]
b

-- | Combine two paths, assuming rhs is NOT absolute.
combineAlways :: FilePath -> FilePath -> FilePath
combineAlways :: [Char] -> [Char] -> [Char]
combineAlways [Char]
a [Char]
b | [Char] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Char]
a = [Char]
b
                  | [Char] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Char]
b = [Char]
a
                  | Char -> Bool
isPathSeparator ([Char] -> Char
forall a. [a] -> a
last [Char]
a) = [Char]
a [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
b
                  | [Char] -> Bool
isDrive [Char]
a = [Char] -> [Char] -> [Char]
joinDrive [Char]
a [Char]
b
                  | Bool
otherwise = [Char]
a [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char
pathSeparator] [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
b


-- | A nice alias for 'combine'.
(</>) :: FilePath -> FilePath -> FilePath
</> :: [Char] -> [Char] -> [Char]
(</>) = [Char] -> [Char] -> [Char]
combine


-- | Split a path by the directory separator.
--
-- > concat (splitPath x) == x
-- > splitPath "test//item/" == ["test//","item/"]
-- > splitPath "test/item/file" == ["test/","item/","file"]
-- > splitPath "" == []
-- > Windows: splitPath "c:/test/path" == ["c:/","test/","path"]
-- > Posix:   splitPath "/file/test" == ["/","file/","test"]
splitPath :: FilePath -> [FilePath]
splitPath :: [Char] -> [[Char]]
splitPath [Char]
x = [[Char]
drive | [Char]
drive [Char] -> [Char] -> Bool
forall a. Eq a => a -> a -> Bool
/= [Char]
""] [[Char]] -> [[Char]] -> [[Char]]
forall a. [a] -> [a] -> [a]
++ [Char] -> [[Char]]
f [Char]
path
    where
        ([Char]
drive,[Char]
path) = [Char] -> ([Char], [Char])
splitDrive [Char]
x

        f :: [Char] -> [[Char]]
f [Char]
"" = []
        f [Char]
y = ([Char]
a[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++[Char]
c) [Char] -> [[Char]] -> [[Char]]
forall a. a -> [a] -> [a]
: [Char] -> [[Char]]
f [Char]
d
            where
                ([Char]
a,[Char]
b) = (Char -> Bool) -> [Char] -> ([Char], [Char])
forall a. (a -> Bool) -> [a] -> ([a], [a])
break Char -> Bool
isPathSeparator [Char]
y
                ([Char]
c,[Char]
d) = (Char -> Bool) -> [Char] -> ([Char], [Char])
forall a. (a -> Bool) -> [a] -> ([a], [a])
break (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
isPathSeparator) [Char]
b

-- | Just as 'splitPath', but don't add the trailing slashes to each element.
--
-- > splitDirectories "test/file" == ["test","file"]
-- > splitDirectories "/test/file" == ["/","test","file"]
-- > Valid x => joinPath (splitDirectories x) `equalFilePath` x
-- > splitDirectories "" == []
splitDirectories :: FilePath -> [FilePath]
splitDirectories :: [Char] -> [[Char]]
splitDirectories [Char]
path =
        if [Char] -> Bool
hasDrive [Char]
path then [[Char]] -> [Char]
forall a. [a] -> a
head [[Char]]
pathComponents [Char] -> [[Char]] -> [[Char]]
forall a. a -> [a] -> [a]
: [[Char]] -> [[Char]]
f ([[Char]] -> [[Char]]
forall a. [a] -> [a]
tail [[Char]]
pathComponents)
        else [[Char]] -> [[Char]]
f [[Char]]
pathComponents
    where
        pathComponents :: [[Char]]
pathComponents = [Char] -> [[Char]]
splitPath [Char]
path

        f :: [[Char]] -> [[Char]]
f [[Char]]
xs = ([Char] -> [Char]) -> [[Char]] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map [Char] -> [Char]
g [[Char]]
xs
        g :: [Char] -> [Char]
g [Char]
x = if [Char] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Char]
res then [Char]
x else [Char]
res
            where res :: [Char]
res = (Char -> Bool) -> [Char] -> [Char]
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
isPathSeparator) [Char]
x


-- | Join path elements back together.
--
-- > Valid x => joinPath (splitPath x) == x
-- > joinPath [] == ""
-- > Posix: joinPath ["test","file","path"] == "test/file/path"

-- Note that this definition on c:\\c:\\, join then split will give c:\\.
joinPath :: [FilePath] -> FilePath
joinPath :: [[Char]] -> [Char]
joinPath [[Char]]
x = ([Char] -> [Char] -> [Char]) -> [Char] -> [[Char]] -> [Char]
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr [Char] -> [Char] -> [Char]
combine [Char]
"" [[Char]]
x






---------------------------------------------------------------------
-- File name manipulators

-- | Equality of two 'FilePath's.
--   If you call @System.Directory.canonicalizePath@
--   first this has a much better chance of working.
--   Note that this doesn't follow symlinks or DOSNAM~1s.
--
-- >          x == y ==> equalFilePath x y
-- >          normalise x == normalise y ==> equalFilePath x y
-- > Posix:   equalFilePath "foo" "foo/"
-- > Posix:   not (equalFilePath "foo" "/foo")
-- > Posix:   not (equalFilePath "foo" "FOO")
-- > Windows: equalFilePath "foo" "FOO"
equalFilePath :: FilePath -> FilePath -> Bool
equalFilePath :: [Char] -> [Char] -> Bool
equalFilePath [Char]
a [Char]
b = [Char] -> [Char]
f [Char]
a [Char] -> [Char] -> Bool
forall a. Eq a => a -> a -> Bool
== [Char] -> [Char]
f [Char]
b
    where
        f :: [Char] -> [Char]
f [Char]
x | Bool
isWindows = [Char] -> [Char]
dropTrailSlash ([Char] -> [Char]) -> [Char] -> [Char]
forall a b. (a -> b) -> a -> b
$ (Char -> Char) -> [Char] -> [Char]
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower ([Char] -> [Char]) -> [Char] -> [Char]
forall a b. (a -> b) -> a -> b
$ [Char] -> [Char]
normalise [Char]
x
            | Bool
otherwise = [Char] -> [Char]
dropTrailSlash ([Char] -> [Char]) -> [Char] -> [Char]
forall a b. (a -> b) -> a -> b
$ [Char] -> [Char]
normalise [Char]
x

        dropTrailSlash :: [Char] -> [Char]
dropTrailSlash [Char]
x | [Char] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Char]
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
2 Bool -> Bool -> Bool
&& Char -> Bool
isPathSeparator ([Char] -> Char
forall a. [a] -> a
last [Char]
x) = [Char] -> [Char]
forall a. [a] -> [a]
init [Char]
x
                         | Bool
otherwise = [Char]
x


-- | Contract a filename, based on a relative path.
--
--   There is no corresponding @makeAbsolute@ function, instead use
--   @System.Directory.canonicalizePath@ which has the same effect.
--
-- >          Valid y => equalFilePath x y || (isRelative x && makeRelative y x == x) || equalFilePath (y </> makeRelative y x) x
-- >          makeRelative x x == "."
-- >          null y || equalFilePath (makeRelative x (x </> y)) y || null (takeFileName x)
-- > Windows: makeRelative "C:/Home" "c:/home/bob" == "bob"
-- > Windows: makeRelative "C:/Home" "D:/Home/Bob" == "D:/Home/Bob"
-- > Windows: makeRelative "C:/Home" "C:Home/Bob" == "C:Home/Bob"
-- > Windows: makeRelative "/Home" "/home/bob" == "bob"
-- > Posix:   makeRelative "/Home" "/home/bob" == "/home/bob"
-- > Posix:   makeRelative "/home/" "/home/bob/foo/bar" == "bob/foo/bar"
-- > Posix:   makeRelative "/fred" "bob" == "bob"
-- > Posix:   makeRelative "/file/test" "/file/test/fred" == "fred"
-- > Posix:   makeRelative "/file/test" "/file/test/fred/" == "fred/"
-- > Posix:   makeRelative "some/path" "some/path/a/b/c" == "a/b/c"
makeRelative :: FilePath -> FilePath -> FilePath
makeRelative :: [Char] -> [Char] -> [Char]
makeRelative [Char]
root [Char]
path
 | [Char] -> [Char] -> Bool
equalFilePath [Char]
root [Char]
path = [Char]
"."
 | [Char] -> [Char]
takeAbs [Char]
root [Char] -> [Char] -> Bool
forall a. Eq a => a -> a -> Bool
/= [Char] -> [Char]
takeAbs [Char]
path = [Char]
path
 | Bool
otherwise = [Char] -> [Char] -> [Char]
f ([Char] -> [Char]
dropAbs [Char]
root) ([Char] -> [Char]
dropAbs [Char]
path)
    where
        f :: [Char] -> [Char] -> [Char]
f [Char]
"" [Char]
y = (Char -> Bool) -> [Char] -> [Char]
forall a. (a -> Bool) -> [a] -> [a]
dropWhile Char -> Bool
isPathSeparator [Char]
y
        f [Char]
x [Char]
y = let ([Char]
x1,[Char]
x2) = [Char] -> ([Char], [Char])
g [Char]
x
                    ([Char]
y1,[Char]
y2) = [Char] -> ([Char], [Char])
g [Char]
y
                in if [Char] -> [Char] -> Bool
equalFilePath [Char]
x1 [Char]
y1 then [Char] -> [Char] -> [Char]
f [Char]
x2 [Char]
y2 else [Char]
path

        g :: [Char] -> ([Char], [Char])
g [Char]
x = ((Char -> Bool) -> [Char] -> [Char]
forall a. (a -> Bool) -> [a] -> [a]
dropWhile Char -> Bool
isPathSeparator [Char]
a, (Char -> Bool) -> [Char] -> [Char]
forall a. (a -> Bool) -> [a] -> [a]
dropWhile Char -> Bool
isPathSeparator [Char]
b)
            where ([Char]
a,[Char]
b) = (Char -> Bool) -> [Char] -> ([Char], [Char])
forall a. (a -> Bool) -> [a] -> ([a], [a])
break Char -> Bool
isPathSeparator ([Char] -> ([Char], [Char])) -> [Char] -> ([Char], [Char])
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> [Char] -> [Char]
forall a. (a -> Bool) -> [a] -> [a]
dropWhile Char -> Bool
isPathSeparator [Char]
x

        -- on windows, need to drop '/' which is kind of absolute, but not a drive
        dropAbs :: [Char] -> [Char]
dropAbs (Char
x:[Char]
xs) | Char -> Bool
isPathSeparator Char
x = [Char]
xs
        dropAbs [Char]
x = [Char] -> [Char]
dropDrive [Char]
x

        takeAbs :: [Char] -> [Char]
takeAbs (Char
x:[Char]
_) | Char -> Bool
isPathSeparator Char
x = [Char
pathSeparator]
        takeAbs [Char]
x = (Char -> Char) -> [Char] -> [Char]
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) ([Char] -> [Char]) -> [Char] -> [Char]
forall a b. (a -> b) -> a -> b
$ [Char] -> [Char]
takeDrive [Char]
x

-- | Normalise a file
--
-- * \/\/ outside of the drive can be made blank
--
-- * \/ -> 'pathSeparator'
--
-- * .\/ -> \"\"
--
-- > Posix:   normalise "/file/\\test////" == "/file/\\test/"
-- > Posix:   normalise "/file/./test" == "/file/test"
-- > Posix:   normalise "/test/file/../bob/fred/" == "/test/file/../bob/fred/"
-- > Posix:   normalise "../bob/fred/" == "../bob/fred/"
-- > Posix:   normalise "./bob/fred/" == "bob/fred/"
-- > Windows: normalise "c:\\file/bob\\" == "C:/file/bob/"
-- > Windows: normalise "c:/" == "C:/"
-- > Windows: normalise "\\\\server\\test" == "\\\\server\\test" -- xxx
-- > Windows: normalise "." == "."
-- > Posix:   normalise "./" == "./"
normalise :: FilePath -> FilePath
normalise :: [Char] -> [Char]
normalise [Char]
path = [Char] -> [Char] -> [Char]
joinDrive ([Char] -> [Char]
normaliseDrive [Char]
drv) ([Char] -> [Char]
f [Char]
pth)
              [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char
pathSeparator | Bool -> Bool
not ([Char] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Char]
pth) Bool -> Bool -> Bool
&& Char -> Bool
isPathSeparator ([Char] -> Char
forall a. [a] -> a
last [Char]
pth)]
    where
        ([Char]
drv,[Char]
pth) = [Char] -> ([Char], [Char])
splitDrive [Char]
path

        f :: [Char] -> [Char]
f = [[Char]] -> [Char]
joinPath ([[Char]] -> [Char]) -> ([Char] -> [[Char]]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Char]] -> [[Char]] -> [[Char]]
dropDots [] ([[Char]] -> [[Char]])
-> ([Char] -> [[Char]]) -> [Char] -> [[Char]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [[Char]]
splitDirectories ([Char] -> [[Char]]) -> ([Char] -> [Char]) -> [Char] -> [[Char]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [Char]
propSep

        propSep :: [Char] -> [Char]
propSep (Char
a:Char
b:[Char]
xs)
         | Char -> Bool
isPathSeparator Char
a Bool -> Bool -> Bool
&& Char -> Bool
isPathSeparator Char
b = [Char] -> [Char]
propSep (Char
aChar -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:[Char]
xs)
        propSep (Char
a:[Char]
xs)
         | Char -> Bool
isPathSeparator Char
a = Char
pathSeparator Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: [Char] -> [Char]
propSep [Char]
xs
        propSep (Char
x:[Char]
xs) = Char
x Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: [Char] -> [Char]
propSep [Char]
xs
        propSep [] = []

        dropDots :: [[Char]] -> [[Char]] -> [[Char]]
dropDots [[Char]]
acc ([Char]
".":[[Char]]
xs) | Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [[Char]] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [[Char]]
xs = [[Char]] -> [[Char]] -> [[Char]]
dropDots [[Char]]
acc [[Char]]
xs
        dropDots [[Char]]
acc ([Char]
x:[[Char]]
xs) = [[Char]] -> [[Char]] -> [[Char]]
dropDots ([Char]
x[Char] -> [[Char]] -> [[Char]]
forall a. a -> [a] -> [a]
:[[Char]]
acc) [[Char]]
xs
        dropDots [[Char]]
acc [] = [[Char]] -> [[Char]]
forall a. [a] -> [a]
reverse [[Char]]
acc

normaliseDrive :: FilePath -> FilePath
normaliseDrive :: [Char] -> [Char]
normaliseDrive [Char]
drive | Bool
isPosix = [Char]
drive
normaliseDrive [Char]
drive = if Maybe ([Char], [Char]) -> Bool
forall a. Maybe a -> Bool
isJust (Maybe ([Char], [Char]) -> Bool) -> Maybe ([Char], [Char]) -> Bool
forall a b. (a -> b) -> a -> b
$ [Char] -> Maybe ([Char], [Char])
readDriveLetter [Char]
x2
                       then (Char -> Char) -> [Char] -> [Char]
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toUpper [Char]
x2
                       else [Char]
drive
    where
        x2 :: [Char]
x2 = (Char -> Char) -> [Char] -> [Char]
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
repSlash [Char]
drive

        repSlash :: Char -> Char
repSlash Char
x = if Char -> Bool
isPathSeparator Char
x then Char
pathSeparator else Char
x

{- xxx
-- information for validity functions on Windows
-- see http://msdn.microsoft.com/library/default.asp?url=/library/en-us/fileio/fs/naming_a_file.asp
badCharacters :: [Char]
badCharacters = ":*?><|\""
badElements :: [FilePath]
badElements = ["CON", "PRN", "AUX", "NUL", "COM1", "COM2", "COM3", "COM4", "COM5", "COM6", "COM7", "COM8", "COM9", "LPT1", "LPT2", "LPT3", "LPT4", "LPT5", "LPT6", "LPT7", "LPT8", "LPT9", "CLOCK$"]

-- | Is a FilePath valid, i.e. could you create a file like it?
--
-- >          isValid "" == False
-- > Posix:   isValid "/random_ path:*" == True
-- > Posix:   isValid x == not (null x)
-- > Windows: isValid "c:\\test" == True
-- > Windows: isValid "c:\\test:of_test" == False
-- > Windows: isValid "test*" == False
-- > Windows: isValid "c:\\test\\nul" == False
-- > Windows: isValid "c:\\test\\prn.txt" == False
-- > Windows: isValid "c:\\nul\\file" == False
-- > Windows: isValid "\\\\" == False
isValid :: FilePath -> Bool
isValid "" = False
isValid _ | isPosix = True
isValid path =
        not (any (`elem` badCharacters) x2) &&
        not (any f $ splitDirectories x2) &&
        not (length path >= 2 && all isPathSeparator path)
    where
        x2 = dropDrive path
        f x = map toUpper (dropExtensions x) `elem` badElements


-- | Take a FilePath and make it valid; does not change already valid FilePaths.
--
-- > isValid (makeValid x)
-- > isValid x ==> makeValid x == x
-- > makeValid "" == "_"
-- > Windows: makeValid "c:\\test:of_test" == "c:\\test_of_test"
-- > Windows: makeValid "test*" == "test_"
-- > Windows: makeValid "c:\\test\\nul" == "c:\\test\\nul_"
-- > Windows: makeValid "c:\\test\\prn.txt" == "c:\\test\\prn_.txt"
-- > Windows: makeValid "c:\\test/prn.txt" == "c:\\test/prn_.txt"
-- > Windows: makeValid "c:\\nul\\file" == "c:\\nul_\\file"
makeValid :: FilePath -> FilePath
makeValid "" = "_"
makeValid path | isPosix = path
makeValid x | length x >= 2 && all isPathSeparator x = take 2 x ++ "drive"
makeValid path = joinDrive drv $ validElements $ validChars pth
    where
        (drv,pth) = splitDrive path

        validChars x = map f x
        f x | x `elem` badCharacters = '_'
            | otherwise = x

        validElements x = joinPath $ map g $ splitPath x
        g x = h (reverse b) ++ reverse a
            where (a,b) = span isPathSeparator $ reverse x
        h x = if map toUpper a `elem` badElements then a ++ "_" <.> b else x
            where (a,b) = splitExtensions x
-}

-- | Is a path relative, or is it fixed to the root?
--
-- > Windows: isRelative "path\\test" == True
-- > Windows: isRelative "c:\\test" == False
-- > Windows: isRelative "c:test" == True
-- > Windows: isRelative "c:" == True
-- > Windows: isRelative "\\\\foo" == False
-- > Windows: isRelative "/foo" == True
-- > Posix:   isRelative "test/path" == True
-- > Posix:   isRelative "/test" == False
isRelative :: FilePath -> Bool
isRelative :: [Char] -> Bool
isRelative = [Char] -> Bool
isRelativeDrive ([Char] -> Bool) -> ([Char] -> [Char]) -> [Char] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [Char]
takeDrive


-- > isRelativeDrive "" == True
-- > Windows: isRelativeDrive "c:\\" == False
-- > Windows: isRelativeDrive "c:/" == False
-- > Windows: isRelativeDrive "c:" == True
-- > Windows: isRelativeDrive "\\\\foo" == False
-- > Posix:   isRelativeDrive "/" == False
isRelativeDrive :: String -> Bool
isRelativeDrive :: [Char] -> Bool
isRelativeDrive [Char]
x = [Char] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Char]
x Bool -> Bool -> Bool
||
    Bool
-> (([Char], [Char]) -> Bool) -> Maybe ([Char], [Char]) -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False (Bool -> Bool
not (Bool -> Bool)
-> (([Char], [Char]) -> Bool) -> ([Char], [Char]) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
isPathSeparator (Char -> Bool)
-> (([Char], [Char]) -> Char) -> ([Char], [Char]) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Char
forall a. [a] -> a
last ([Char] -> Char)
-> (([Char], [Char]) -> [Char]) -> ([Char], [Char]) -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Char], [Char]) -> [Char]
forall a b. (a, b) -> a
fst) ([Char] -> Maybe ([Char], [Char])
readDriveLetter [Char]
x)


-- | @not . 'isRelative'@
--
-- > isAbsolute x == not (isRelative x)
isAbsolute :: FilePath -> Bool
isAbsolute :: [Char] -> Bool
isAbsolute = Bool -> Bool
not (Bool -> Bool) -> ([Char] -> Bool) -> [Char] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Bool
isRelative

{-
Copyright Neil Mitchell 2005-2007.
All rights reserved.

Redistribution and use in source and binary forms, with or without
modification, are permitted provided that the following conditions are
met:

    * Redistributions of source code must retain the above copyright
      notice, this list of conditions and the following disclaimer.

    * Redistributions in binary form must reproduce the above
      copyright notice, this list of conditions and the following
      disclaimer in the documentation and/or other materials provided
      with the distribution.

    * Neither the name of Neil Mitchell nor the names of other
      contributors may be used to endorse or promote products derived
      from this software without specific prior written permission.

THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR
A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT
OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT
LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
-}