{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
module Filesystem.Path.Internal where
import Prelude hiding (FilePath)
import Control.DeepSeq (NFData, rnf)
import qualified Control.Exception as Exc
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as B8
import Data.Char (chr, ord)
import Data.Data (Data)
import Data.List (intersperse)
import Data.Ord (comparing)
import qualified Data.Text as T
import qualified Data.Text.Encoding as TE
import Data.Text.Encoding.Error (UnicodeException)
import Data.Typeable (Typeable)
type Chunk = String
type Directory = Chunk
type Basename = Chunk
type Extension = Chunk
data Root
= RootPosix
| RootWindowsVolume Char Bool
| RootWindowsCurrentVolume
| RootWindowsUnc String String Bool
| RootWindowsDoubleQMark
deriving (Root -> Root -> Bool
(Root -> Root -> Bool) -> (Root -> Root -> Bool) -> Eq Root
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Root -> Root -> Bool
== :: Root -> Root -> Bool
$c/= :: Root -> Root -> Bool
/= :: Root -> Root -> Bool
Eq, Eq Root
Eq Root =>
(Root -> Root -> Ordering)
-> (Root -> Root -> Bool)
-> (Root -> Root -> Bool)
-> (Root -> Root -> Bool)
-> (Root -> Root -> Bool)
-> (Root -> Root -> Root)
-> (Root -> Root -> Root)
-> Ord Root
Root -> Root -> Bool
Root -> Root -> Ordering
Root -> Root -> Root
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Root -> Root -> Ordering
compare :: Root -> Root -> Ordering
$c< :: Root -> Root -> Bool
< :: Root -> Root -> Bool
$c<= :: Root -> Root -> Bool
<= :: Root -> Root -> Bool
$c> :: Root -> Root -> Bool
> :: Root -> Root -> Bool
$c>= :: Root -> Root -> Bool
>= :: Root -> Root -> Bool
$cmax :: Root -> Root -> Root
max :: Root -> Root -> Root
$cmin :: Root -> Root -> Root
min :: Root -> Root -> Root
Ord, Typeable Root
Typeable Root =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Root -> c Root)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Root)
-> (Root -> Constr)
-> (Root -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Root))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Root))
-> ((forall b. Data b => b -> b) -> Root -> Root)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Root -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Root -> r)
-> (forall u. (forall d. Data d => d -> u) -> Root -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Root -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Root -> m Root)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Root -> m Root)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Root -> m Root)
-> Data Root
Root -> Constr
Root -> DataType
(forall b. Data b => b -> b) -> Root -> Root
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Root -> u
forall u. (forall d. Data d => d -> u) -> Root -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Root -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Root -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Root -> m Root
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Root -> m Root
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Root
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Root -> c Root
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Root)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Root)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Root -> c Root
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Root -> c Root
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Root
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Root
$ctoConstr :: Root -> Constr
toConstr :: Root -> Constr
$cdataTypeOf :: Root -> DataType
dataTypeOf :: Root -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Root)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Root)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Root)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Root)
$cgmapT :: (forall b. Data b => b -> b) -> Root -> Root
gmapT :: (forall b. Data b => b -> b) -> Root -> Root
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Root -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Root -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Root -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Root -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Root -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Root -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Root -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Root -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Root -> m Root
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Root -> m Root
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Root -> m Root
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Root -> m Root
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Root -> m Root
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Root -> m Root
Data, Typeable, Int -> Root -> ShowS
[Root] -> ShowS
Root -> String
(Int -> Root -> ShowS)
-> (Root -> String) -> ([Root] -> ShowS) -> Show Root
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Root -> ShowS
showsPrec :: Int -> Root -> ShowS
$cshow :: Root -> String
show :: Root -> String
$cshowList :: [Root] -> ShowS
showList :: [Root] -> ShowS
Show)
data FilePath = FilePath
{ FilePath -> Maybe Root
pathRoot :: Maybe Root
, FilePath -> [String]
pathDirectories :: [Directory]
, FilePath -> Maybe String
pathBasename :: Maybe Basename
, FilePath -> [String]
pathExtensions :: [Extension]
}
deriving (Typeable FilePath
Typeable FilePath =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FilePath -> c FilePath)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FilePath)
-> (FilePath -> Constr)
-> (FilePath -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FilePath))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FilePath))
-> ((forall b. Data b => b -> b) -> FilePath -> FilePath)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FilePath -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FilePath -> r)
-> (forall u. (forall d. Data d => d -> u) -> FilePath -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> FilePath -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FilePath -> m FilePath)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FilePath -> m FilePath)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FilePath -> m FilePath)
-> Data FilePath
FilePath -> Constr
FilePath -> DataType
(forall b. Data b => b -> b) -> FilePath -> FilePath
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> FilePath -> u
forall u. (forall d. Data d => d -> u) -> FilePath -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FilePath -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FilePath -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FilePath -> m FilePath
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FilePath -> m FilePath
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FilePath
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FilePath -> c FilePath
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FilePath)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FilePath)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FilePath -> c FilePath
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FilePath -> c FilePath
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FilePath
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FilePath
$ctoConstr :: FilePath -> Constr
toConstr :: FilePath -> Constr
$cdataTypeOf :: FilePath -> DataType
dataTypeOf :: FilePath -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FilePath)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FilePath)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FilePath)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FilePath)
$cgmapT :: (forall b. Data b => b -> b) -> FilePath -> FilePath
gmapT :: (forall b. Data b => b -> b) -> FilePath -> FilePath
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FilePath -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FilePath -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FilePath -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FilePath -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> FilePath -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> FilePath -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> FilePath -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> FilePath -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FilePath -> m FilePath
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FilePath -> m FilePath
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FilePath -> m FilePath
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FilePath -> m FilePath
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FilePath -> m FilePath
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FilePath -> m FilePath
Data, Typeable)
instance Eq FilePath where
FilePath
x == :: FilePath -> FilePath -> Bool
== FilePath
y = FilePath -> FilePath -> Ordering
forall a. Ord a => a -> a -> Ordering
compare FilePath
x FilePath
y Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Ordering
EQ
instance Ord FilePath where
compare :: FilePath -> FilePath -> Ordering
compare = (FilePath -> (Maybe Root, [Text], Maybe Text, [Text]))
-> FilePath -> FilePath -> Ordering
forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing (\FilePath
p ->
(FilePath -> Maybe Root
pathRoot FilePath
p
, (String -> Text) -> [String] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Text
unescape' (FilePath -> [String]
pathDirectories FilePath
p)
, (String -> Text) -> Maybe String -> Maybe Text
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Text
unescape' (FilePath -> Maybe String
pathBasename FilePath
p)
, (String -> Text) -> [String] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Text
unescape' (FilePath -> [String]
pathExtensions FilePath
p)
))
instance NFData Root where
rnf :: Root -> ()
rnf (RootWindowsVolume Char
c Bool
extended) = Char -> ()
forall a. NFData a => a -> ()
rnf Char
c () -> () -> ()
forall a b. a -> b -> b
`seq` Bool -> ()
forall a. NFData a => a -> ()
rnf Bool
extended
rnf (RootWindowsUnc String
host String
share Bool
extended) = String -> ()
forall a. NFData a => a -> ()
rnf String
host () -> () -> ()
forall a b. a -> b -> b
`seq` String -> ()
forall a. NFData a => a -> ()
rnf String
share () -> () -> ()
forall a b. a -> b -> b
`seq` Bool -> ()
forall a. NFData a => a -> ()
rnf Bool
extended
rnf Root
_ = ()
instance NFData FilePath where
rnf :: FilePath -> ()
rnf FilePath
p = Maybe Root -> ()
forall a. NFData a => a -> ()
rnf (FilePath -> Maybe Root
pathRoot FilePath
p) () -> () -> ()
forall a b. a -> b -> b
`seq` [String] -> ()
forall a. NFData a => a -> ()
rnf (FilePath -> [String]
pathDirectories FilePath
p) () -> () -> ()
forall a b. a -> b -> b
`seq` Maybe String -> ()
forall a. NFData a => a -> ()
rnf (FilePath -> Maybe String
pathBasename FilePath
p) () -> () -> ()
forall a b. a -> b -> b
`seq` [String] -> ()
forall a. NFData a => a -> ()
rnf (FilePath -> [String]
pathExtensions FilePath
p)
empty :: FilePath
empty :: FilePath
empty = Maybe Root -> [String] -> Maybe String -> [String] -> FilePath
FilePath Maybe Root
forall a. Maybe a
Nothing [] Maybe String
forall a. Maybe a
Nothing []
dot :: Chunk
dot :: String
dot = String
"."
dots :: Chunk
dots :: String
dots = String
".."
filenameChunk :: FilePath -> Chunk
filenameChunk :: FilePath -> String
filenameChunk FilePath
p = [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat (String
nameString -> [String] -> [String]
forall a. a -> [a] -> [a]
:[String]
exts) where
name :: String
name = String -> ShowS -> Maybe String -> String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe String
"" ShowS
forall a. a -> a
id (FilePath -> Maybe String
pathBasename FilePath
p)
exts :: [String]
exts = case FilePath -> [String]
pathExtensions FilePath
p of
[] -> []
[String]
exts' -> String -> [String] -> [String]
forall a. a -> [a] -> [a]
intersperse String
dot (String
""String -> [String] -> [String]
forall a. a -> [a] -> [a]
:[String]
exts')
rootChunk :: Maybe Root -> Chunk
rootChunk :: Maybe Root -> String
rootChunk Maybe Root
r = ((Root -> String) -> Maybe Root -> String)
-> Maybe Root -> (Root -> String) -> String
forall a b c. (a -> b -> c) -> b -> a -> c
flip (String -> (Root -> String) -> Maybe Root -> String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe String
"") Maybe Root
r ((Root -> String) -> String) -> (Root -> String) -> String
forall a b. (a -> b) -> a -> b
$ \Root
r' -> case Root
r' of
Root
RootPosix -> String
"/"
RootWindowsVolume Char
c Bool
False -> Char
c Char -> ShowS
forall a. a -> [a] -> [a]
: String
":\\"
RootWindowsVolume Char
c Bool
True -> String
"\\\\?\\" String -> ShowS
forall a. [a] -> [a] -> [a]
++ (Char
c Char -> ShowS
forall a. a -> [a] -> [a]
: String
":\\")
Root
RootWindowsCurrentVolume -> String
"\\"
RootWindowsUnc String
host String
share Bool
False -> String
"\\\\" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
host String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"\\" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
share
RootWindowsUnc String
host String
share Bool
True -> String
"\\\\?\\UNC\\" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
host String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"\\" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
share
Root
RootWindowsDoubleQMark -> String
"\\??\\"
rootText :: Maybe Root -> T.Text
rootText :: Maybe Root -> Text
rootText = String -> Text
T.pack (String -> Text) -> (Maybe Root -> String) -> Maybe Root -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe Root -> String
rootChunk
directoryChunks :: FilePath -> [Chunk]
directoryChunks :: FilePath -> [String]
directoryChunks FilePath
path = FilePath -> [String]
pathDirectories FilePath
path [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [FilePath -> String
filenameChunk FilePath
path]
data Rules platformFormat = Rules
{ forall platformFormat. Rules platformFormat -> Text
rulesName :: T.Text
, forall platformFormat. Rules platformFormat -> FilePath -> Bool
valid :: FilePath -> Bool
, forall platformFormat.
Rules platformFormat -> platformFormat -> [FilePath]
splitSearchPath :: platformFormat -> [FilePath]
, forall platformFormat. Rules platformFormat -> String -> [FilePath]
splitSearchPathString :: String -> [FilePath]
, forall platformFormat.
Rules platformFormat -> FilePath -> Either Text Text
toText :: FilePath -> Either T.Text T.Text
, forall platformFormat. Rules platformFormat -> Text -> FilePath
fromText :: T.Text -> FilePath
, forall platformFormat.
Rules platformFormat -> FilePath -> platformFormat
encode :: FilePath -> platformFormat
, forall platformFormat.
Rules platformFormat -> platformFormat -> FilePath
decode :: platformFormat -> FilePath
, forall platformFormat. Rules platformFormat -> FilePath -> String
encodeString :: FilePath -> String
, forall platformFormat. Rules platformFormat -> String -> FilePath
decodeString :: String -> FilePath
}
instance Show (Rules a) where
showsPrec :: Int -> Rules a -> ShowS
showsPrec Int
d Rules a
r = Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10)
(String -> ShowS
showString String
"Rules " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ShowS
forall a. Show a => a -> ShowS
shows (Rules a -> Text
forall platformFormat. Rules platformFormat -> Text
rulesName Rules a
r))
escape :: T.Text -> Chunk
escape :: Text -> String
escape Text
t = Text -> String
T.unpack Text
t
unescape :: Chunk -> (T.Text, Bool)
unescape :: String -> (Text, Bool)
unescape String
cs = if (Char -> Bool) -> String -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (\Char
c -> Char -> Int
ord Char
c Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0xDC80 Bool -> Bool -> Bool
&& Char -> Int
ord Char
c Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0xDCFF) String
cs
then (String -> Text
T.pack ((Char -> Char) -> ShowS
forall a b. (a -> b) -> [a] -> [b]
map (\Char
c -> if Char -> Int
ord Char
c Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0xDC80 Bool -> Bool -> Bool
&& Char -> Int
ord Char
c Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0xDCFF
then Int -> Char
chr (Char -> Int
ord Char
c Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
0xDC00)
else Char
c) String
cs), Bool
False)
else (String -> Text
T.pack String
cs, Bool
True)
unescape' :: Chunk -> T.Text
unescape' :: String -> Text
unescape' = (Text, Bool) -> Text
forall a b. (a, b) -> a
fst ((Text, Bool) -> Text)
-> (String -> (Text, Bool)) -> String -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> (Text, Bool)
unescape
unescapeBytes' :: Chunk -> B.ByteString
unescapeBytes' :: String -> ByteString
unescapeBytes' String
cs = if (Char -> Bool) -> String -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (\Char
c -> Char -> Int
ord Char
c Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0xDC80 Bool -> Bool -> Bool
&& Char -> Int
ord Char
c Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0xDCFF) String
cs
then [ByteString] -> ByteString
B8.concat ((Char -> ByteString) -> String -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
map (\Char
c -> if Char -> Int
ord Char
c Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0xDC80 Bool -> Bool -> Bool
&& Char -> Int
ord Char
c Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0xDCFF
then Char -> ByteString
B8.singleton (Int -> Char
chr (Char -> Int
ord Char
c Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
0xDC00))
else Text -> ByteString
TE.encodeUtf8 (Char -> Text
T.singleton Char
c)) String
cs)
else Text -> ByteString
TE.encodeUtf8 (String -> Text
T.pack String
cs)
splitBy :: (a -> Bool) -> [a] -> [[a]]
splitBy :: forall a. (a -> Bool) -> [a] -> [[a]]
splitBy a -> Bool
p = [a] -> [[a]]
loop where
loop :: [a] -> [[a]]
loop [a]
xs = let
([a]
chunk, [a]
rest) = (a -> Bool) -> [a] -> ([a], [a])
forall a. (a -> Bool) -> [a] -> ([a], [a])
break a -> Bool
p [a]
xs
cont :: [[a]]
cont = [a]
chunk [a] -> [[a]] -> [[a]]
forall a. a -> [a] -> [a]
: [a] -> [[a]]
loop ([a] -> [a]
forall a. HasCallStack => [a] -> [a]
tail [a]
rest)
in if [a] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [a]
rest then [[a]
chunk] else [[a]]
cont
textSplitBy :: (Char -> Bool) -> T.Text -> [T.Text]
#if MIN_VERSION_text(0,11,0)
textSplitBy :: (Char -> Bool) -> Text -> [Text]
textSplitBy = (Char -> Bool) -> Text -> [Text]
T.split
#else
textSplitBy = T.splitBy
#endif
parseFilename :: Chunk -> (Maybe Basename, [Extension])
parseFilename :: String -> (Maybe String, [String])
parseFilename String
filename = (Maybe String, [String])
parsed where
parsed :: (Maybe String, [String])
parsed = if String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
filename
then (Maybe String
forall a. Maybe a
Nothing, [])
else case (Char -> Bool) -> String -> (String, String)
forall a. (a -> Bool) -> [a] -> ([a], [a])
span (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'.') String
filename of
(String
leadingDots, String
baseAndExts) -> case (Char -> Bool) -> String -> [String]
forall a. (a -> Bool) -> [a] -> [[a]]
splitBy (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'.') String
baseAndExts of
[] -> (String -> String -> Maybe String
forall {a}. [a] -> [a] -> Maybe [a]
joinDots String
leadingDots String
"", [])
(String
name':[String]
exts') -> (String -> String -> Maybe String
forall {a}. [a] -> [a] -> Maybe [a]
joinDots String
leadingDots String
name', [String]
exts')
joinDots :: [a] -> [a] -> Maybe [a]
joinDots [a]
leadingDots [a]
base = case [a]
leadingDots [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++ [a]
base of
[] -> Maybe [a]
forall a. Maybe a
Nothing
[a]
joined -> [a] -> Maybe [a]
forall a. a -> Maybe a
Just [a]
joined
maybeDecodeUtf8 :: B.ByteString -> Maybe T.Text
maybeDecodeUtf8 :: ByteString -> Maybe Text
maybeDecodeUtf8 ByteString
bytes = case ByteString -> Either UnicodeException Text
TE.decodeUtf8' ByteString
bytes of
Left UnicodeException
_ -> Maybe Text
forall a. Maybe a
Nothing
Right Text
text -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
text