module System.Directory.Internal.Common
( module System.Directory.Internal.Common
, OsPath
, OsString
) where
import Prelude ()
import System.Directory.Internal.Prelude
import GHC.IO.Encoding.Failure (CodingFailureMode(TransliterateCodingFailure))
import GHC.IO.Encoding.UTF16 (mkUTF16le)
import GHC.IO.Encoding.UTF8 (mkUTF8)
import System.IO (hSetBinaryMode)
import System.OsPath
( OsPath
, OsString
, addTrailingPathSeparator
, decodeUtf
, decodeWith
, encodeUtf
, hasTrailingPathSeparator
, isPathSeparator
, isRelative
, joinDrive
, joinPath
, normalise
, pack
, pathSeparator
, pathSeparators
, splitDirectories
, splitDrive
, toChar
, unpack
, unsafeFromChar
)
newtype ListT m a = ListT { forall (m :: * -> *) a. ListT m a -> m (Maybe (a, ListT m a))
unListT :: m (Maybe (a, ListT m a)) }
emptyListT :: Applicative m => ListT m a
emptyListT :: forall (m :: * -> *) a. Applicative m => ListT m a
emptyListT = forall (m :: * -> *) a. m (Maybe (a, ListT m a)) -> ListT m a
ListT (forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Maybe a
Nothing)
maybeToListT :: Applicative m => m (Maybe a) -> ListT m a
maybeToListT :: forall (m :: * -> *) a. Applicative m => m (Maybe a) -> ListT m a
maybeToListT m (Maybe a)
m = forall (m :: * -> *) a. m (Maybe (a, ListT m a)) -> ListT m a
ListT (((\ a
x -> (a
x, forall (m :: * -> *) a. Applicative m => ListT m a
emptyListT)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m (Maybe a)
m)
listToListT :: Applicative m => [a] -> ListT m a
listToListT :: forall (m :: * -> *) a. Applicative m => [a] -> ListT m a
listToListT [] = forall (m :: * -> *) a. Applicative m => ListT m a
emptyListT
listToListT (a
x : [a]
xs) = forall (m :: * -> *) a. m (Maybe (a, ListT m a)) -> ListT m a
ListT (forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. a -> Maybe a
Just (a
x, forall (m :: * -> *) a. Applicative m => [a] -> ListT m a
listToListT [a]
xs)))
liftJoinListT :: Monad m => m (ListT m a) -> ListT m a
liftJoinListT :: forall (m :: * -> *) a. Monad m => m (ListT m a) -> ListT m a
liftJoinListT m (ListT m a)
m = forall (m :: * -> *) a. m (Maybe (a, ListT m a)) -> ListT m a
ListT (m (ListT m a)
m forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *) a. ListT m a -> m (Maybe (a, ListT m a))
unListT)
listTHead :: Functor m => ListT m a -> m (Maybe a)
listTHead :: forall (m :: * -> *) a. Functor m => ListT m a -> m (Maybe a)
listTHead (ListT m (Maybe (a, ListT m a))
m) = (forall a b. (a, b) -> a
fst forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m (Maybe (a, ListT m a))
m
listTToList :: Monad m => ListT m a -> m [a]
listTToList :: forall (m :: * -> *) a. Monad m => ListT m a -> m [a]
listTToList (ListT m (Maybe (a, ListT m a))
m) = do
Maybe (a, ListT m a)
mx <- m (Maybe (a, ListT m a))
m
case Maybe (a, ListT m a)
mx of
Maybe (a, ListT m a)
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return []
Just (a
x, ListT m a
m') -> do
[a]
xs <- forall (m :: * -> *) a. Monad m => ListT m a -> m [a]
listTToList ListT m a
m'
forall (m :: * -> *) a. Monad m => a -> m a
return (a
x forall a. a -> [a] -> [a]
: [a]
xs)
andM :: Monad m => m Bool -> m Bool -> m Bool
andM :: forall (m :: * -> *). Monad m => m Bool -> m Bool -> m Bool
andM m Bool
mx m Bool
my = do
Bool
x <- m Bool
mx
if Bool
x
then m Bool
my
else forall (m :: * -> *) a. Monad m => a -> m a
return Bool
x
sequenceWithIOErrors_ :: [IO ()] -> IO ()
sequenceWithIOErrors_ :: [IO ()] -> IO ()
sequenceWithIOErrors_ [IO ()]
actions = Either IOError () -> [IO ()] -> IO ()
go (forall a b. b -> Either a b
Right ()) [IO ()]
actions
where
go :: Either IOError () -> [IO ()] -> IO ()
go :: Either IOError () -> [IO ()] -> IO ()
go (Left IOError
e) [] = forall a. IOError -> IO a
ioError IOError
e
go (Right ()) [] = forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
go Either IOError ()
s (IO ()
m : [IO ()]
ms) = Either IOError ()
s seq :: forall a b. a -> b -> b
`seq` do
Either IOError ()
r <- forall a. IO a -> IO (Either IOError a)
tryIOError IO ()
m
Either IOError () -> [IO ()] -> IO ()
go (Either IOError ()
s forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Either IOError ()
r) [IO ()]
ms
tryIOErrorType :: (IOError -> Bool) -> IO a -> IO (Either IOError a)
tryIOErrorType :: forall a. (IOError -> Bool) -> IO a -> IO (Either IOError a)
tryIOErrorType IOError -> Bool
check IO a
action = do
Either IOError a
result <- forall a. IO a -> IO (Either IOError a)
tryIOError IO a
action
case Either IOError a
result of
Left IOError
err -> if IOError -> Bool
check IOError
err then forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a b. a -> Either a b
Left IOError
err) else forall e a. Exception e => e -> IO a
throwIO IOError
err
Right a
val -> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a b. b -> Either a b
Right a
val)
ignoreIOExceptions :: IO () -> IO ()
ignoreIOExceptions :: IO () -> IO ()
ignoreIOExceptions IO ()
io = IO ()
io forall a. IO a -> (IOError -> IO a) -> IO a
`catchIOError` (\IOError
_ -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
specializeErrorString :: String -> (IOError -> Bool) -> IO a -> IO a
specializeErrorString :: forall a. String -> (IOError -> Bool) -> IO a -> IO a
specializeErrorString String
str IOError -> Bool
errType IO a
action = do
Either IOError a
mx <- forall a. (IOError -> Bool) -> IO a -> IO (Either IOError a)
tryIOErrorType IOError -> Bool
errType IO a
action
case Either IOError a
mx of
Left IOError
e -> forall e a. Exception e => e -> IO a
throwIO (IOError -> String -> IOError
ioeSetErrorString IOError
e String
str)
Right a
x -> forall (f :: * -> *) a. Applicative f => a -> f a
pure a
x
ioeAddLocation :: IOError -> String -> IOError
ioeAddLocation :: IOError -> String -> IOError
ioeAddLocation IOError
e String
loc = do
IOError -> String -> IOError
ioeSetLocation IOError
e String
newLoc
where
newLoc :: String
newLoc = String
loc forall a. Semigroup a => a -> a -> a
<> if forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
oldLoc then String
"" else String
":" forall a. Semigroup a => a -> a -> a
<> String
oldLoc
oldLoc :: String
oldLoc = IOError -> String
ioeGetLocation IOError
e
rightOrError :: Exception e => Either e a -> a
rightOrError :: forall e a. Exception e => Either e a -> a
rightOrError (Left e
e) = forall a. HasCallStack => String -> a
error (forall e. Exception e => e -> String
displayException e
e)
rightOrError (Right a
a) = a
a
os :: String -> OsString
os :: String -> OsPath
os = forall e a. Exception e => Either e a -> a
rightOrError forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *). MonadThrow m => String -> m OsPath
encodeUtf
so :: OsString -> String
so :: OsPath -> String
so = forall e a. Exception e => Either e a -> a
rightOrError forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *). MonadThrow m => OsPath -> m String
decodeUtf
ioeSetOsPath :: IOError -> OsPath -> IOError
ioeSetOsPath :: IOError -> OsPath -> IOError
ioeSetOsPath IOError
err =
IOError -> String -> IOError
ioeSetFileName IOError
err forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall e a. Exception e => Either e a -> a
rightOrError forall b c a. (b -> c) -> (a -> b) -> a -> c
.
TextEncoding
-> TextEncoding -> OsPath -> Either EncodingException String
decodeWith
(CodingFailureMode -> TextEncoding
mkUTF8 CodingFailureMode
TransliterateCodingFailure)
(CodingFailureMode -> TextEncoding
mkUTF16le CodingFailureMode
TransliterateCodingFailure)
expandDots :: [OsPath] -> [OsPath]
expandDots :: [OsPath] -> [OsPath]
expandDots = forall a. [a] -> [a]
reverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. [OsPath] -> [OsPath] -> [OsPath]
go []
where
go :: [OsPath] -> [OsPath] -> [OsPath]
go [OsPath]
ys' [OsPath]
xs' =
case [OsPath]
xs' of
[] -> [OsPath]
ys'
OsPath
x : [OsPath]
xs
| OsPath
x forall a. Eq a => a -> a -> Bool
== String -> OsPath
os String
"." -> [OsPath] -> [OsPath] -> [OsPath]
go [OsPath]
ys' [OsPath]
xs
| OsPath
x forall a. Eq a => a -> a -> Bool
== String -> OsPath
os String
".." ->
case [OsPath]
ys' of
[] -> [OsPath] -> [OsPath] -> [OsPath]
go (OsPath
x forall a. a -> [a] -> [a]
: [OsPath]
ys') [OsPath]
xs
OsPath
y : [OsPath]
ys
| OsPath
y forall a. Eq a => a -> a -> Bool
== String -> OsPath
os String
".." -> [OsPath] -> [OsPath] -> [OsPath]
go (OsPath
x forall a. a -> [a] -> [a]
: [OsPath]
ys') [OsPath]
xs
| Bool
otherwise -> [OsPath] -> [OsPath] -> [OsPath]
go [OsPath]
ys [OsPath]
xs
| Bool
otherwise -> [OsPath] -> [OsPath] -> [OsPath]
go (OsPath
x forall a. a -> [a] -> [a]
: [OsPath]
ys') [OsPath]
xs
normalisePathSeps :: OsPath -> OsPath
normalisePathSeps :: OsPath -> OsPath
normalisePathSeps OsPath
p = [OsChar] -> OsPath
pack (OsChar -> OsChar
normaliseChar forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> OsPath -> [OsChar]
unpack OsPath
p)
where normaliseChar :: OsChar -> OsChar
normaliseChar OsChar
c = if OsChar -> Bool
isPathSeparator OsChar
c then OsChar
pathSeparator else OsChar
c
normaliseTrailingSep :: OsPath -> OsPath
normaliseTrailingSep :: OsPath -> OsPath
normaliseTrailingSep OsPath
path = do
let path' :: [OsChar]
path' = forall a. [a] -> [a]
reverse (OsPath -> [OsChar]
unpack OsPath
path)
let ([OsChar]
sep, [OsChar]
path'') = forall a. (a -> Bool) -> [a] -> ([a], [a])
span OsChar -> Bool
isPathSeparator [OsChar]
path'
let addSep :: [OsChar] -> [OsChar]
addSep = if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [OsChar]
sep then forall a. a -> a
id else (OsChar
pathSeparator forall a. a -> [a] -> [a]
:)
[OsChar] -> OsPath
pack (forall a. [a] -> [a]
reverse ([OsChar] -> [OsChar]
addSep [OsChar]
path''))
emptyToCurDir :: OsPath -> OsPath
emptyToCurDir :: OsPath -> OsPath
emptyToCurDir OsPath
path
| OsPath
path forall a. Eq a => a -> a -> Bool
== forall a. Monoid a => a
mempty = String -> OsPath
os String
"."
| Bool
otherwise = OsPath
path
simplifyPosix :: OsPath -> OsPath
simplifyPosix :: OsPath -> OsPath
simplifyPosix OsPath
path
| OsPath
path forall a. Eq a => a -> a -> Bool
== forall a. Monoid a => a
mempty = forall a. Monoid a => a
mempty
| Bool
otherwise = OsPath -> OsPath
normalise OsPath
path
simplifyWindows :: OsPath -> OsPath
simplifyWindows :: OsPath -> OsPath
simplifyWindows OsPath
path
| OsPath
path forall a. Eq a => a -> a -> Bool
== forall a. Monoid a => a
mempty = forall a. Monoid a => a
mempty
| OsPath
drive' forall a. Eq a => a -> a -> Bool
== String -> OsPath
os String
"\\\\?\\" = OsPath
drive' forall a. Semigroup a => a -> a -> a
<> OsPath
subpath
| Bool
otherwise = OsPath
simplifiedPath
where
simplifiedPath :: OsPath
simplifiedPath = OsPath -> OsPath -> OsPath
joinDrive OsPath
drive' OsPath
subpath'
(OsPath
drive, OsPath
subpath) = OsPath -> (OsPath, OsPath)
splitDrive OsPath
path
drive' :: OsPath
drive' = OsPath -> OsPath
upperDrive (OsPath -> OsPath
normaliseTrailingSep (OsPath -> OsPath
normalisePathSeps OsPath
drive))
subpath' :: OsPath
subpath' = OsPath -> OsPath
appendSep forall b c a. (b -> c) -> (a -> b) -> a -> c
. OsPath -> OsPath
avoidEmpty forall b c a. (b -> c) -> (a -> b) -> a -> c
. OsPath -> OsPath
prependSep forall b c a. (b -> c) -> (a -> b) -> a -> c
. [OsPath] -> OsPath
joinPath forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[OsPath] -> [OsPath]
stripPardirs forall b c a. (b -> c) -> (a -> b) -> a -> c
. [OsPath] -> [OsPath]
expandDots forall b c a. (b -> c) -> (a -> b) -> a -> c
. [OsPath] -> [OsPath]
skipSeps forall b c a. (b -> c) -> (a -> b) -> a -> c
.
OsPath -> [OsPath]
splitDirectories forall a b. (a -> b) -> a -> b
$ OsPath
subpath
upperDrive :: OsPath -> OsPath
upperDrive OsPath
d = case OsPath -> [OsChar]
unpack OsPath
d of
OsChar
c : OsChar
k : [OsChar]
s
| Char -> Bool
isAlpha (OsChar -> Char
toChar OsChar
c), OsChar -> Char
toChar OsChar
k forall a. Eq a => a -> a -> Bool
== Char
':', forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all OsChar -> Bool
isPathSeparator [OsChar]
s ->
[OsChar] -> OsPath
pack (Char -> OsChar
unsafeFromChar (Char -> Char
toUpper (OsChar -> Char
toChar OsChar
c)) forall a. a -> [a] -> [a]
: Char -> OsChar
unsafeFromChar Char
':' forall a. a -> [a] -> [a]
: [OsChar]
s)
[OsChar]
_ -> OsPath
d
skipSeps :: [OsPath] -> [OsPath]
skipSeps =
([OsChar] -> OsPath
pack forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (forall (f :: * -> *) a. Applicative f => a -> f a
pure forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [OsChar]
pathSeparators))) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
(OsPath -> [OsChar]
unpack forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>)
stripPardirs :: [OsPath] -> [OsPath]
stripPardirs | Bool
pathIsAbsolute Bool -> Bool -> Bool
|| Bool
subpathIsAbsolute = forall a. (a -> Bool) -> [a] -> [a]
dropWhile (forall a. Eq a => a -> a -> Bool
== String -> OsPath
os String
"..")
| Bool
otherwise = forall a. a -> a
id
prependSep :: OsPath -> OsPath
prependSep | Bool
subpathIsAbsolute = ([OsChar] -> OsPath
pack [OsChar
pathSeparator] forall a. Semigroup a => a -> a -> a
<>)
| Bool
otherwise = forall a. a -> a
id
avoidEmpty :: OsPath -> OsPath
avoidEmpty | Bool -> Bool
not Bool
pathIsAbsolute
, OsPath
drive forall a. Eq a => a -> a -> Bool
== forall a. Monoid a => a
mempty Bool -> Bool -> Bool
|| Bool
hasTrailingPathSep
= OsPath -> OsPath
emptyToCurDir
| Bool
otherwise = forall a. a -> a
id
appendSep :: OsPath -> OsPath
appendSep OsPath
p | Bool
hasTrailingPathSep, Bool -> Bool
not (Bool
pathIsAbsolute Bool -> Bool -> Bool
&& OsPath
p forall a. Eq a => a -> a -> Bool
== forall a. Monoid a => a
mempty)
= OsPath -> OsPath
addTrailingPathSeparator OsPath
p
| Bool
otherwise = OsPath
p
pathIsAbsolute :: Bool
pathIsAbsolute = Bool -> Bool
not (OsPath -> Bool
isRelative OsPath
path)
subpathIsAbsolute :: Bool
subpathIsAbsolute = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any OsChar -> Bool
isPathSeparator (forall a. Int -> [a] -> [a]
take Int
1 (OsPath -> [OsChar]
unpack OsPath
subpath))
hasTrailingPathSep :: Bool
hasTrailingPathSep = OsPath -> Bool
hasTrailingPathSeparator OsPath
subpath
data FileType = File
| SymbolicLink
| Directory
| DirectoryLink
deriving (FileType
forall a. a -> a -> Bounded a
maxBound :: FileType
$cmaxBound :: FileType
minBound :: FileType
$cminBound :: FileType
Bounded, Int -> FileType
FileType -> Int
FileType -> [FileType]
FileType -> FileType
FileType -> FileType -> [FileType]
FileType -> FileType -> FileType -> [FileType]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: FileType -> FileType -> FileType -> [FileType]
$cenumFromThenTo :: FileType -> FileType -> FileType -> [FileType]
enumFromTo :: FileType -> FileType -> [FileType]
$cenumFromTo :: FileType -> FileType -> [FileType]
enumFromThen :: FileType -> FileType -> [FileType]
$cenumFromThen :: FileType -> FileType -> [FileType]
enumFrom :: FileType -> [FileType]
$cenumFrom :: FileType -> [FileType]
fromEnum :: FileType -> Int
$cfromEnum :: FileType -> Int
toEnum :: Int -> FileType
$ctoEnum :: Int -> FileType
pred :: FileType -> FileType
$cpred :: FileType -> FileType
succ :: FileType -> FileType
$csucc :: FileType -> FileType
Enum, FileType -> FileType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FileType -> FileType -> Bool
$c/= :: FileType -> FileType -> Bool
== :: FileType -> FileType -> Bool
$c== :: FileType -> FileType -> Bool
Eq, Eq FileType
FileType -> FileType -> Bool
FileType -> FileType -> Ordering
FileType -> FileType -> FileType
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
min :: FileType -> FileType -> FileType
$cmin :: FileType -> FileType -> FileType
max :: FileType -> FileType -> FileType
$cmax :: FileType -> FileType -> FileType
>= :: FileType -> FileType -> Bool
$c>= :: FileType -> FileType -> Bool
> :: FileType -> FileType -> Bool
$c> :: FileType -> FileType -> Bool
<= :: FileType -> FileType -> Bool
$c<= :: FileType -> FileType -> Bool
< :: FileType -> FileType -> Bool
$c< :: FileType -> FileType -> Bool
compare :: FileType -> FileType -> Ordering
$ccompare :: FileType -> FileType -> Ordering
Ord, ReadPrec [FileType]
ReadPrec FileType
Int -> ReadS FileType
ReadS [FileType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FileType]
$creadListPrec :: ReadPrec [FileType]
readPrec :: ReadPrec FileType
$creadPrec :: ReadPrec FileType
readList :: ReadS [FileType]
$creadList :: ReadS [FileType]
readsPrec :: Int -> ReadS FileType
$creadsPrec :: Int -> ReadS FileType
Read, Int -> FileType -> ShowS
[FileType] -> ShowS
FileType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FileType] -> ShowS
$cshowList :: [FileType] -> ShowS
show :: FileType -> String
$cshow :: FileType -> String
showsPrec :: Int -> FileType -> ShowS
$cshowsPrec :: Int -> FileType -> ShowS
Show)
fileTypeIsDirectory :: FileType -> Bool
fileTypeIsDirectory :: FileType -> Bool
fileTypeIsDirectory FileType
Directory = Bool
True
fileTypeIsDirectory FileType
DirectoryLink = Bool
True
fileTypeIsDirectory FileType
_ = Bool
False
fileTypeIsLink :: FileType -> Bool
fileTypeIsLink :: FileType -> Bool
fileTypeIsLink FileType
SymbolicLink = Bool
True
fileTypeIsLink FileType
DirectoryLink = Bool
True
fileTypeIsLink FileType
_ = Bool
False
data Permissions
= Permissions
{ Permissions -> Bool
readable :: Bool
, Permissions -> Bool
writable :: Bool
, Permissions -> Bool
executable :: Bool
, Permissions -> Bool
searchable :: Bool
} deriving (Permissions -> Permissions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Permissions -> Permissions -> Bool
$c/= :: Permissions -> Permissions -> Bool
== :: Permissions -> Permissions -> Bool
$c== :: Permissions -> Permissions -> Bool
Eq, Eq Permissions
Permissions -> Permissions -> Bool
Permissions -> Permissions -> Ordering
Permissions -> Permissions -> Permissions
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
min :: Permissions -> Permissions -> Permissions
$cmin :: Permissions -> Permissions -> Permissions
max :: Permissions -> Permissions -> Permissions
$cmax :: Permissions -> Permissions -> Permissions
>= :: Permissions -> Permissions -> Bool
$c>= :: Permissions -> Permissions -> Bool
> :: Permissions -> Permissions -> Bool
$c> :: Permissions -> Permissions -> Bool
<= :: Permissions -> Permissions -> Bool
$c<= :: Permissions -> Permissions -> Bool
< :: Permissions -> Permissions -> Bool
$c< :: Permissions -> Permissions -> Bool
compare :: Permissions -> Permissions -> Ordering
$ccompare :: Permissions -> Permissions -> Ordering
Ord, ReadPrec [Permissions]
ReadPrec Permissions
Int -> ReadS Permissions
ReadS [Permissions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Permissions]
$creadListPrec :: ReadPrec [Permissions]
readPrec :: ReadPrec Permissions
$creadPrec :: ReadPrec Permissions
readList :: ReadS [Permissions]
$creadList :: ReadS [Permissions]
readsPrec :: Int -> ReadS Permissions
$creadsPrec :: Int -> ReadS Permissions
Read, Int -> Permissions -> ShowS
[Permissions] -> ShowS
Permissions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Permissions] -> ShowS
$cshowList :: [Permissions] -> ShowS
show :: Permissions -> String
$cshow :: Permissions -> String
showsPrec :: Int -> Permissions -> ShowS
$cshowsPrec :: Int -> Permissions -> ShowS
Show)
withBinaryHandle :: IO Handle -> (Handle -> IO r) -> IO r
withBinaryHandle :: forall r. IO Handle -> (Handle -> IO r) -> IO r
withBinaryHandle IO Handle
open = forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket IO Handle
openBinary Handle -> IO ()
hClose
where
openBinary :: IO Handle
openBinary = do
Handle
h <- IO Handle
open
Handle -> Bool -> IO ()
hSetBinaryMode Handle
h Bool
True
forall (f :: * -> *) a. Applicative f => a -> f a
pure Handle
h
copyHandleData :: Handle
-> Handle
-> IO ()
copyHandleData :: Handle -> Handle -> IO ()
copyHandleData Handle
hFrom Handle
hTo =
(IOError -> String -> IOError
`ioeAddLocation` String
"copyData") forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
bufferSize forall {a}. Ptr a -> IO ()
go
where
bufferSize :: Int
bufferSize = Int
131072
go :: Ptr a -> IO ()
go Ptr a
buffer = do
Int
count <- forall a. Handle -> Ptr a -> Int -> IO Int
hGetBuf Handle
hFrom Ptr a
buffer Int
bufferSize
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
count forall a. Ord a => a -> a -> Bool
> Int
0) forall a b. (a -> b) -> a -> b
$ do
forall a. Handle -> Ptr a -> Int -> IO ()
hPutBuf Handle
hTo Ptr a
buffer Int
count
Ptr a -> IO ()
go Ptr a
buffer
data XdgDirectory
= XdgData
| XdgConfig
| XdgCache
| XdgState
deriving (XdgDirectory
forall a. a -> a -> Bounded a
maxBound :: XdgDirectory
$cmaxBound :: XdgDirectory
minBound :: XdgDirectory
$cminBound :: XdgDirectory
Bounded, Int -> XdgDirectory
XdgDirectory -> Int
XdgDirectory -> [XdgDirectory]
XdgDirectory -> XdgDirectory
XdgDirectory -> XdgDirectory -> [XdgDirectory]
XdgDirectory -> XdgDirectory -> XdgDirectory -> [XdgDirectory]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: XdgDirectory -> XdgDirectory -> XdgDirectory -> [XdgDirectory]
$cenumFromThenTo :: XdgDirectory -> XdgDirectory -> XdgDirectory -> [XdgDirectory]
enumFromTo :: XdgDirectory -> XdgDirectory -> [XdgDirectory]
$cenumFromTo :: XdgDirectory -> XdgDirectory -> [XdgDirectory]
enumFromThen :: XdgDirectory -> XdgDirectory -> [XdgDirectory]
$cenumFromThen :: XdgDirectory -> XdgDirectory -> [XdgDirectory]
enumFrom :: XdgDirectory -> [XdgDirectory]
$cenumFrom :: XdgDirectory -> [XdgDirectory]
fromEnum :: XdgDirectory -> Int
$cfromEnum :: XdgDirectory -> Int
toEnum :: Int -> XdgDirectory
$ctoEnum :: Int -> XdgDirectory
pred :: XdgDirectory -> XdgDirectory
$cpred :: XdgDirectory -> XdgDirectory
succ :: XdgDirectory -> XdgDirectory
$csucc :: XdgDirectory -> XdgDirectory
Enum, XdgDirectory -> XdgDirectory -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: XdgDirectory -> XdgDirectory -> Bool
$c/= :: XdgDirectory -> XdgDirectory -> Bool
== :: XdgDirectory -> XdgDirectory -> Bool
$c== :: XdgDirectory -> XdgDirectory -> Bool
Eq, Eq XdgDirectory
XdgDirectory -> XdgDirectory -> Bool
XdgDirectory -> XdgDirectory -> Ordering
XdgDirectory -> XdgDirectory -> XdgDirectory
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
min :: XdgDirectory -> XdgDirectory -> XdgDirectory
$cmin :: XdgDirectory -> XdgDirectory -> XdgDirectory
max :: XdgDirectory -> XdgDirectory -> XdgDirectory
$cmax :: XdgDirectory -> XdgDirectory -> XdgDirectory
>= :: XdgDirectory -> XdgDirectory -> Bool
$c>= :: XdgDirectory -> XdgDirectory -> Bool
> :: XdgDirectory -> XdgDirectory -> Bool
$c> :: XdgDirectory -> XdgDirectory -> Bool
<= :: XdgDirectory -> XdgDirectory -> Bool
$c<= :: XdgDirectory -> XdgDirectory -> Bool
< :: XdgDirectory -> XdgDirectory -> Bool
$c< :: XdgDirectory -> XdgDirectory -> Bool
compare :: XdgDirectory -> XdgDirectory -> Ordering
$ccompare :: XdgDirectory -> XdgDirectory -> Ordering
Ord, ReadPrec [XdgDirectory]
ReadPrec XdgDirectory
Int -> ReadS XdgDirectory
ReadS [XdgDirectory]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [XdgDirectory]
$creadListPrec :: ReadPrec [XdgDirectory]
readPrec :: ReadPrec XdgDirectory
$creadPrec :: ReadPrec XdgDirectory
readList :: ReadS [XdgDirectory]
$creadList :: ReadS [XdgDirectory]
readsPrec :: Int -> ReadS XdgDirectory
$creadsPrec :: Int -> ReadS XdgDirectory
Read, Int -> XdgDirectory -> ShowS
[XdgDirectory] -> ShowS
XdgDirectory -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [XdgDirectory] -> ShowS
$cshowList :: [XdgDirectory] -> ShowS
show :: XdgDirectory -> String
$cshow :: XdgDirectory -> String
showsPrec :: Int -> XdgDirectory -> ShowS
$cshowsPrec :: Int -> XdgDirectory -> ShowS
Show)
data XdgDirectoryList
= XdgDataDirs
| XdgConfigDirs
deriving (XdgDirectoryList
forall a. a -> a -> Bounded a
maxBound :: XdgDirectoryList
$cmaxBound :: XdgDirectoryList
minBound :: XdgDirectoryList
$cminBound :: XdgDirectoryList
Bounded, Int -> XdgDirectoryList
XdgDirectoryList -> Int
XdgDirectoryList -> [XdgDirectoryList]
XdgDirectoryList -> XdgDirectoryList
XdgDirectoryList -> XdgDirectoryList -> [XdgDirectoryList]
XdgDirectoryList
-> XdgDirectoryList -> XdgDirectoryList -> [XdgDirectoryList]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: XdgDirectoryList
-> XdgDirectoryList -> XdgDirectoryList -> [XdgDirectoryList]
$cenumFromThenTo :: XdgDirectoryList
-> XdgDirectoryList -> XdgDirectoryList -> [XdgDirectoryList]
enumFromTo :: XdgDirectoryList -> XdgDirectoryList -> [XdgDirectoryList]
$cenumFromTo :: XdgDirectoryList -> XdgDirectoryList -> [XdgDirectoryList]
enumFromThen :: XdgDirectoryList -> XdgDirectoryList -> [XdgDirectoryList]
$cenumFromThen :: XdgDirectoryList -> XdgDirectoryList -> [XdgDirectoryList]
enumFrom :: XdgDirectoryList -> [XdgDirectoryList]
$cenumFrom :: XdgDirectoryList -> [XdgDirectoryList]
fromEnum :: XdgDirectoryList -> Int
$cfromEnum :: XdgDirectoryList -> Int
toEnum :: Int -> XdgDirectoryList
$ctoEnum :: Int -> XdgDirectoryList
pred :: XdgDirectoryList -> XdgDirectoryList
$cpred :: XdgDirectoryList -> XdgDirectoryList
succ :: XdgDirectoryList -> XdgDirectoryList
$csucc :: XdgDirectoryList -> XdgDirectoryList
Enum, XdgDirectoryList -> XdgDirectoryList -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: XdgDirectoryList -> XdgDirectoryList -> Bool
$c/= :: XdgDirectoryList -> XdgDirectoryList -> Bool
== :: XdgDirectoryList -> XdgDirectoryList -> Bool
$c== :: XdgDirectoryList -> XdgDirectoryList -> Bool
Eq, Eq XdgDirectoryList
XdgDirectoryList -> XdgDirectoryList -> Bool
XdgDirectoryList -> XdgDirectoryList -> Ordering
XdgDirectoryList -> XdgDirectoryList -> XdgDirectoryList
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
min :: XdgDirectoryList -> XdgDirectoryList -> XdgDirectoryList
$cmin :: XdgDirectoryList -> XdgDirectoryList -> XdgDirectoryList
max :: XdgDirectoryList -> XdgDirectoryList -> XdgDirectoryList
$cmax :: XdgDirectoryList -> XdgDirectoryList -> XdgDirectoryList
>= :: XdgDirectoryList -> XdgDirectoryList -> Bool
$c>= :: XdgDirectoryList -> XdgDirectoryList -> Bool
> :: XdgDirectoryList -> XdgDirectoryList -> Bool
$c> :: XdgDirectoryList -> XdgDirectoryList -> Bool
<= :: XdgDirectoryList -> XdgDirectoryList -> Bool
$c<= :: XdgDirectoryList -> XdgDirectoryList -> Bool
< :: XdgDirectoryList -> XdgDirectoryList -> Bool
$c< :: XdgDirectoryList -> XdgDirectoryList -> Bool
compare :: XdgDirectoryList -> XdgDirectoryList -> Ordering
$ccompare :: XdgDirectoryList -> XdgDirectoryList -> Ordering
Ord, ReadPrec [XdgDirectoryList]
ReadPrec XdgDirectoryList
Int -> ReadS XdgDirectoryList
ReadS [XdgDirectoryList]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [XdgDirectoryList]
$creadListPrec :: ReadPrec [XdgDirectoryList]
readPrec :: ReadPrec XdgDirectoryList
$creadPrec :: ReadPrec XdgDirectoryList
readList :: ReadS [XdgDirectoryList]
$creadList :: ReadS [XdgDirectoryList]
readsPrec :: Int -> ReadS XdgDirectoryList
$creadsPrec :: Int -> ReadS XdgDirectoryList
Read, Int -> XdgDirectoryList -> ShowS
[XdgDirectoryList] -> ShowS
XdgDirectoryList -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [XdgDirectoryList] -> ShowS
$cshowList :: [XdgDirectoryList] -> ShowS
show :: XdgDirectoryList -> String
$cshow :: XdgDirectoryList -> String
showsPrec :: Int -> XdgDirectoryList -> ShowS
$cshowsPrec :: Int -> XdgDirectoryList -> ShowS
Show)