module Turtle.Internal where
import Control.Applicative ((<|>))
import Control.Exception (handle, throwIO)
import Data.Text (Text)
import Foreign.C.Error (Errno(..), ePIPE)
import GHC.IO.Exception (IOErrorType(..), IOException(..))
import System.FilePath ((</>))
import qualified Data.List as List
import qualified Data.Text as Text
import qualified Data.Text.IO as Text.IO
import qualified System.FilePath as FilePath
ignoreSIGPIPE :: IO () -> IO ()
ignoreSIGPIPE :: IO () -> IO ()
ignoreSIGPIPE = forall e a. Exception e => (e -> IO a) -> IO a -> IO a
handle (\IOException
e -> case IOException
e of
IOError
{ ioe_type :: IOException -> IOErrorType
ioe_type = IOErrorType
ResourceVanished
, ioe_errno :: IOException -> Maybe CInt
ioe_errno = Just CInt
ioe }
| CInt -> Errno
Errno CInt
ioe forall a. Eq a => a -> a -> Bool
== Errno
ePIPE -> forall (m :: * -> *) a. Monad m => a -> m a
return ()
IOException
_ -> forall e a. Exception e => e -> IO a
throwIO IOException
e
)
toText :: FilePath -> Either Text Text
toText :: FilePath -> Either Text Text
toText = forall a b. b -> Either a b
Right forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Text
Text.pack
{-# DEPRECATED toText "Use Data.Text.pack instead" #-}
fromText :: Text -> FilePath
fromText :: Text -> FilePath
fromText = Text -> FilePath
Text.unpack
{-# DEPRECATED fromText "Use Data.Text.unpack instead" #-}
decodeString :: String -> FilePath
decodeString :: FilePath -> FilePath
decodeString = forall a. a -> a
id
{-# DEPRECATED decodeString "Use id instead" #-}
encodeString :: FilePath -> String
encodeString :: FilePath -> FilePath
encodeString = forall a. a -> a
id
{-# DEPRECATED encodeString "Use id instead" #-}
commonPrefix :: [FilePath] -> FilePath
commonPrefix :: [FilePath] -> FilePath
commonPrefix [ ] = forall a. Monoid a => a
mempty
commonPrefix (FilePath
path : [FilePath]
paths) = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr FilePath -> FilePath -> FilePath
longestPathPrefix FilePath
path [FilePath]
paths
where
longestPathPrefix :: FilePath -> FilePath -> FilePath
longestPathPrefix FilePath
left FilePath
right
| [FilePath]
leftComponents forall a. Eq a => a -> a -> Bool
== [FilePath]
rightComponents =
[FilePath] -> FilePath
FilePath.joinPath [FilePath]
leftComponents
forall a. [a] -> [a] -> [a]
++ forall a. Monoid a => [a] -> a
mconcat (forall a. Eq a => [a] -> [a] -> [a]
longestPrefix [FilePath]
leftExtensions [FilePath]
rightExtensions)
| Bool
otherwise =
[FilePath] -> FilePath
FilePath.joinPath (forall a. Eq a => [a] -> [a] -> [a]
longestPrefix [FilePath]
leftComponents [FilePath]
rightComponents)
where
([FilePath]
leftComponents, [FilePath]
leftExtensions) = [FilePath] -> ([FilePath], [FilePath])
splitExt (FilePath -> [FilePath]
splitDirectories FilePath
left)
([FilePath]
rightComponents, [FilePath]
rightExtensions) = [FilePath] -> ([FilePath], [FilePath])
splitExt (FilePath -> [FilePath]
splitDirectories FilePath
right)
longestPrefix :: Eq a => [a] -> [a] -> [a]
longestPrefix :: forall a. Eq a => [a] -> [a] -> [a]
longestPrefix (a
l : [a]
ls) (a
r : [a]
rs)
| a
l forall a. Eq a => a -> a -> Bool
== a
r = a
l forall a. a -> [a] -> [a]
: forall a. Eq a => [a] -> [a] -> [a]
longestPrefix [a]
ls [a]
rs
longestPrefix [a]
_ [a]
_ = [ ]
stripPrefix :: FilePath -> FilePath -> Maybe FilePath
stripPrefix :: FilePath -> FilePath -> Maybe FilePath
stripPrefix FilePath
prefix FilePath
path = do
[FilePath]
componentSuffix <- forall a. Eq a => [a] -> [a] -> Maybe [a]
List.stripPrefix [FilePath]
prefixComponents [FilePath]
pathComponents
if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [FilePath]
componentSuffix
then do
[FilePath]
prefixSuffix <- forall a. Eq a => [a] -> [a] -> Maybe [a]
List.stripPrefix [FilePath]
prefixExtensions [FilePath]
pathExtensions
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. Monoid a => [a] -> a
mconcat [FilePath]
prefixSuffix)
else do
forall (m :: * -> *) a. Monad m => a -> m a
return ([FilePath] -> FilePath
FilePath.joinPath [FilePath]
componentSuffix forall a. [a] -> [a] -> [a]
++ forall a. Monoid a => [a] -> a
mconcat [FilePath]
pathExtensions)
where
([FilePath]
prefixComponents, [FilePath]
prefixExtensions) = [FilePath] -> ([FilePath], [FilePath])
splitExt (FilePath -> [FilePath]
splitDirectories FilePath
prefix)
([FilePath]
pathComponents, [FilePath]
pathExtensions) = [FilePath] -> ([FilePath], [FilePath])
splitExt (FilePath -> [FilePath]
splitDirectories FilePath
path)
splitExt :: [FilePath] -> ([FilePath], [String])
splitExt :: [FilePath] -> ([FilePath], [FilePath])
splitExt [ FilePath
component ] = ([ FilePath
base ], forall a b. (a -> b) -> [a] -> [b]
map (FilePath
"." forall a. [a] -> [a] -> [a]
++) [FilePath]
exts)
where
(FilePath
base, [FilePath]
exts) = FilePath -> (FilePath, [FilePath])
splitExtensions FilePath
component
splitExt [ ] =
([ ], [ ])
splitExt (FilePath
component : [FilePath]
components) = (FilePath
component forall a. a -> [a] -> [a]
: [FilePath]
base, [FilePath]
exts)
where
([FilePath]
base, [FilePath]
exts) = [FilePath] -> ([FilePath], [FilePath])
splitExt [FilePath]
components
collapse :: FilePath -> FilePath
collapse :: FilePath -> FilePath
collapse = FilePath -> FilePath
FilePath.normalise
{-# DEPRECATED collapse "Use System.FilePath.normalise instead" #-}
readTextFile :: FilePath -> IO Text
readTextFile :: FilePath -> IO Text
readTextFile = FilePath -> IO Text
Text.IO.readFile
{-# DEPRECATED readTextFile "Use Data.Text.IO.readFile instead" #-}
writeTextFile :: FilePath -> Text -> IO ()
writeTextFile :: FilePath -> Text -> IO ()
writeTextFile = FilePath -> Text -> IO ()
Text.IO.writeFile
{-# DEPRECATED writeTextFile "Use Data.Text.IO.writeFile instead" #-}
root :: FilePath -> FilePath
root :: FilePath -> FilePath
root = forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> (FilePath, FilePath)
FilePath.splitDrive
parent :: FilePath -> FilePath
parent :: FilePath -> FilePath
parent FilePath
path = FilePath
prefix FilePath -> FilePath -> FilePath
</> FilePath
suffix
where
(FilePath
drive, FilePath
rest) = FilePath -> (FilePath, FilePath)
FilePath.splitDrive FilePath
path
components :: [FilePath]
components = forall {a}. [a] -> [a]
loop (FilePath -> [FilePath]
splitDirectories FilePath
rest)
prefix :: FilePath
prefix =
case [FilePath]
components of
FilePath
"./" : [FilePath]
_ -> FilePath
drive
FilePath
"../" : [FilePath]
_ -> FilePath
drive
[FilePath]
_ | forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
drive -> FilePath
"./"
| Bool
otherwise -> FilePath
drive
suffix :: FilePath
suffix = [FilePath] -> FilePath
FilePath.joinPath [FilePath]
components
loop :: [a] -> [a]
loop [ a
_ ] = [ ]
loop [ ] = [ ]
loop (a
c : [a]
cs) = a
c forall a. a -> [a] -> [a]
: [a] -> [a]
loop [a]
cs
directory :: FilePath -> FilePath
directory :: FilePath -> FilePath
directory FilePath
path
| FilePath
prefix forall a. Eq a => a -> a -> Bool
== FilePath
"" Bool -> Bool -> Bool
&& FilePath
suffix forall a. Eq a => a -> a -> Bool
== FilePath
".." =
FilePath
"../"
| Bool
otherwise =
FilePath -> FilePath
trailingSlash (FilePath -> FilePath
FilePath.takeDirectory FilePath
prefix) forall a. [a] -> [a] -> [a]
++ FilePath
suffix
where
(FilePath
prefix, FilePath
suffix) = FilePath -> (FilePath, FilePath)
trailingParent FilePath
path
where
trailingParent :: FilePath -> (FilePath, FilePath)
trailingParent FilePath
".." = (FilePath
"" , FilePath
"..")
trailingParent [ Char
a, Char
b ] = ([ Char
a, Char
b ], FilePath
"" )
trailingParent [ Char
a ] = ([ Char
a ] , FilePath
"" )
trailingParent [ ] = ([ ] , FilePath
"" )
trailingParent (Char
c : FilePath
cs) = (Char
c forall a. a -> [a] -> [a]
: FilePath
p, FilePath
s)
where
~(FilePath
p, FilePath
s) = FilePath -> (FilePath, FilePath)
trailingParent FilePath
cs
trailingSlash :: FilePath -> FilePath
trailingSlash FilePath
"" = FilePath
"/"
trailingSlash FilePath
"/" = FilePath
"/"
trailingSlash (Char
c : FilePath
cs) = Char
c forall a. a -> [a] -> [a]
: FilePath -> FilePath
trailingSlash FilePath
cs
filename :: FilePath -> FilePath
filename :: FilePath -> FilePath
filename FilePath
path
| FilePath
result forall a. Eq a => a -> a -> Bool
== FilePath
"." Bool -> Bool -> Bool
|| FilePath
result forall a. Eq a => a -> a -> Bool
== FilePath
".." = FilePath
""
| Bool
otherwise = FilePath
result
where
result :: FilePath
result = FilePath -> FilePath
FilePath.takeFileName FilePath
path
dirname :: FilePath -> FilePath
dirname :: FilePath -> FilePath
dirname FilePath
path = [FilePath] -> FilePath
loop (FilePath -> [FilePath]
splitDirectories FilePath
path)
where
loop :: [FilePath] -> FilePath
loop [ FilePath
x, FilePath
y ] =
case FilePath -> Maybe FilePath
deslash FilePath
y forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> FilePath -> Maybe FilePath
deslash FilePath
x of
Just FilePath
name -> FilePath
name
Maybe FilePath
Nothing -> FilePath
""
loop [ FilePath
x ] =
case FilePath -> Maybe FilePath
deslash FilePath
x of
Just FilePath
name -> FilePath
name
Maybe FilePath
Nothing -> FilePath
""
loop [ ] =
FilePath
""
loop (FilePath
_ : [FilePath]
xs) =
[FilePath] -> FilePath
loop [FilePath]
xs
deslash :: FilePath -> Maybe FilePath
deslash FilePath
"" = forall a. Maybe a
Nothing
deslash FilePath
"/" = forall a. a -> Maybe a
Just FilePath
""
deslash (Char
c : FilePath
cs) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Char
c forall a. a -> [a] -> [a]
:) (FilePath -> Maybe FilePath
deslash FilePath
cs)
basename :: FilePath -> String
basename :: FilePath -> FilePath
basename FilePath
path =
case FilePath
name of
Char
'.' : FilePath
_ -> FilePath
name
FilePath
_ ->
case FilePath -> (FilePath, [FilePath])
splitExtensions FilePath
name of
(FilePath
base, [FilePath]
_) -> FilePath
base
where
name :: FilePath
name = FilePath -> FilePath
filename FilePath
path
absolute :: FilePath -> Bool
absolute :: FilePath -> Bool
absolute = FilePath -> Bool
FilePath.isAbsolute
{-# DEPRECATED absolute "Use System.FilePath.isAbsolute instead" #-}
relative :: FilePath -> Bool
relative :: FilePath -> Bool
relative = FilePath -> Bool
FilePath.isRelative
{-# DEPRECATED relative "Use System.FilePath.isRelative instead" #-}
splitDirectories :: FilePath -> [FilePath]
splitDirectories :: FilePath -> [FilePath]
splitDirectories FilePath
path = [FilePath] -> [FilePath]
loop (FilePath -> [FilePath]
FilePath.splitPath FilePath
path)
where
loop :: [FilePath] -> [FilePath]
loop [ ] = [ ]
loop [ FilePath
".." ] = [ FilePath
"../" ]
loop [ FilePath
"." ] = [ FilePath
"./" ]
loop (FilePath
c : [FilePath]
cs) = FilePath
c forall a. a -> [a] -> [a]
: [FilePath] -> [FilePath]
loop [FilePath]
cs
extension :: FilePath -> Maybe String
extension :: FilePath -> Maybe FilePath
extension FilePath
path =
case FilePath
suffix of
Char
'.' : FilePath
ext -> forall a. a -> Maybe a
Just FilePath
ext
FilePath
_ -> forall a. Maybe a
Nothing
where
suffix :: FilePath
suffix = FilePath -> FilePath
FilePath.takeExtension FilePath
path
splitExtension :: FilePath -> (String, Maybe String)
splitExtension :: FilePath -> (FilePath, Maybe FilePath)
splitExtension FilePath
path =
case FilePath
suffix of
Char
'.' : FilePath
ext -> (FilePath
prefix, forall a. a -> Maybe a
Just FilePath
ext)
FilePath
_ -> (FilePath
prefix, forall a. Maybe a
Nothing)
where
(FilePath
prefix, FilePath
suffix) = FilePath -> (FilePath, FilePath)
FilePath.splitExtension FilePath
path
splitExtensions :: FilePath -> (String, [String])
splitExtensions :: FilePath -> (FilePath, [FilePath])
splitExtensions FilePath
path0 = (FilePath
prefix0, forall {a}. [a] -> [a]
reverse [FilePath]
exts0)
where
(FilePath
prefix0, [FilePath]
exts0) = FilePath -> (FilePath, [FilePath])
loop FilePath
path0
loop :: FilePath -> (FilePath, [FilePath])
loop FilePath
path = case FilePath -> (FilePath, Maybe FilePath)
splitExtension FilePath
path of
(FilePath
prefix, Just FilePath
ext) ->
(FilePath
base, FilePath
ext forall a. a -> [a] -> [a]
: [FilePath]
exts)
where
(FilePath
base, [FilePath]
exts) = FilePath -> (FilePath, [FilePath])
loop FilePath
prefix
(FilePath
base, Maybe FilePath
Nothing) ->
(FilePath
base, [])