module System.Directory.Internal.Common where
import Prelude ()
import System.Directory.Internal.Prelude
import System.FilePath
( addTrailingPathSeparator
, hasTrailingPathSeparator
, isPathSeparator
, isRelative
, joinDrive
, joinPath
, normalise
, pathSeparator
, pathSeparators
, splitDirectories
, splitDrive
)
newtype ListT m a = ListT { ListT m a -> m (Maybe (a, ListT m a))
unListT :: m (Maybe (a, ListT m a)) }
emptyListT :: Applicative m => ListT m a
emptyListT :: ListT m a
emptyListT = m (Maybe (a, ListT m a)) -> ListT m a
forall (m :: * -> *) a. m (Maybe (a, ListT m a)) -> ListT m a
ListT (Maybe (a, ListT m a) -> m (Maybe (a, ListT m a))
forall (f :: * -> *) a. Applicative f => a -> f a
Evidence bound by a type signature of the constraint type Applicative m
pure Maybe (a, ListT m a)
forall a. Maybe a
Nothing)
maybeToListT :: Applicative m => m (Maybe a) -> ListT m a
maybeToListT :: m (Maybe a) -> ListT m a
maybeToListT m (Maybe a)
m = m (Maybe (a, ListT m a)) -> ListT m a
forall (m :: * -> *) a. m (Maybe (a, ListT m a)) -> ListT m a
ListT (((\ a
x -> (a
x, ListT m a
forall (m :: * -> *) a. Applicative m => ListT m a
Evidence bound by a type signature of the constraint type Applicative m
emptyListT)) (a -> (a, ListT m a)) -> Maybe a -> Maybe (a, ListT m a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Maybe
<$>) (Maybe a -> Maybe (a, ListT m a))
-> m (Maybe a) -> m (Maybe (a, ListT m a))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a type signature of the constraint type Applicative m
<$> m (Maybe a)
m)
listToListT :: Applicative m => [a] -> ListT m a
listToListT :: [a] -> ListT m a
listToListT [] = ListT m a
forall (m :: * -> *) a. Applicative m => ListT m a
Evidence bound by a type signature of the constraint type Applicative m
emptyListT
listToListT (a
x : [a]
xs) = m (Maybe (a, ListT m a)) -> ListT m a
forall (m :: * -> *) a. m (Maybe (a, ListT m a)) -> ListT m a
ListT (Maybe (a, ListT m a) -> m (Maybe (a, ListT m a))
forall (f :: * -> *) a. Applicative f => a -> f a
Evidence bound by a type signature of the constraint type Applicative m
pure ((a, ListT m a) -> Maybe (a, ListT m a)
forall a. a -> Maybe a
Just (a
x, [a] -> ListT m a
forall (m :: * -> *) a. Applicative m => [a] -> ListT m a
Evidence bound by a type signature of the constraint type Applicative m
listToListT [a]
xs)))
liftJoinListT :: Monad m => m (ListT m a) -> ListT m a
liftJoinListT :: m (ListT m a) -> ListT m a
liftJoinListT m (ListT m a)
m = m (Maybe (a, ListT m a)) -> ListT m a
forall (m :: * -> *) a. m (Maybe (a, ListT m a)) -> ListT m a
ListT (m (ListT m a)
m m (ListT m a)
-> (ListT m a -> m (Maybe (a, ListT m a)))
-> m (Maybe (a, ListT m a))
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Evidence bound by a type signature of the constraint type Monad m
>>= ListT m a -> m (Maybe (a, ListT m a))
forall (m :: * -> *) a. ListT m a -> m (Maybe (a, ListT m a))
unListT)
listTHead :: Functor m => ListT m a -> m (Maybe a)
listTHead :: ListT m a -> m (Maybe a)
listTHead (ListT m (Maybe (a, ListT m a))
m) = ((a, ListT m a) -> a
forall a b. (a, b) -> a
fst ((a, ListT m a) -> a) -> Maybe (a, ListT m a) -> Maybe a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Maybe
<$>) (Maybe (a, ListT m a) -> Maybe a)
-> m (Maybe (a, ListT m a)) -> m (Maybe a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor m
<$> m (Maybe (a, ListT m a))
m
listTToList :: Monad m => ListT m a -> m [a]
listTToList :: 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 -> [a] -> m [a]
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a type signature of the constraint type Monad m
return []
Just (a
x, ListT m a
m') -> do
[a]
xs <- ListT m a -> m [a]
forall (m :: * -> *) a. Monad m => ListT m a -> m [a]
Evidence bound by a type signature of the constraint type Monad m
listTToList ListT m a
m'
[a] -> m [a]
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a type signature of the constraint type Monad m
return (a
x a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
xs)
andM :: Monad m => m Bool -> m Bool -> m Bool
andM :: 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 Bool -> m Bool
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a type signature of the constraint type Monad m
return Bool
x
sequenceWithIOErrors_ :: [IO ()] -> IO ()
sequenceWithIOErrors_ :: [IO ()] -> IO ()
sequenceWithIOErrors_ [IO ()]
actions = Either IOError () -> [IO ()] -> IO ()
go (() -> Either IOError ()
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) [] = IOError -> IO ()
forall a. IOError -> IO a
ioError IOError
e
go (Right ()) [] = () -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type Applicative IO
pure ()
go Either IOError ()
s (IO ()
m : [IO ()]
ms) = Either IOError ()
s Either IOError () -> IO () -> IO ()
`seq` do
Either IOError ()
r <- IO () -> IO (Either IOError ())
forall a. IO a -> IO (Either IOError a)
tryIOError IO ()
m
Either IOError () -> [IO ()] -> IO ()
go (Either IOError () -> Either IOError () -> Either IOError ()
forall b a. Either b a -> Either b a -> Either b a
thenEither Either IOError ()
s Either IOError ()
r) [IO ()]
ms
thenEither :: Either b a -> Either b a -> Either b a
thenEither :: Either b a -> Either b a -> Either b a
thenEither x :: Either b a
x@(Left b
_) Either b a
_ = Either b a
x
thenEither Either b a
_ Either b a
y = Either b a
y
tryIOErrorType :: (IOError -> Bool) -> IO a -> IO (Either IOError a)
tryIOErrorType :: (IOError -> Bool) -> IO a -> IO (Either IOError a)
tryIOErrorType IOError -> Bool
check IO a
action = do
Either IOError a
result <- IO a -> IO (Either IOError a)
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 Either IOError a -> IO (Either IOError a)
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type Applicative IO
pure (IOError -> Either IOError a
forall a b. a -> Either a b
Left IOError
err) else IOError -> IO (Either IOError a)
forall e a. Exception e => e -> IO a
External instance of the constraint type Exception IOError
throwIO IOError
err
Right a
val -> Either IOError a -> IO (Either IOError a)
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type Applicative IO
pure (a -> Either IOError a
forall a b. b -> Either a b
Right a
val)
ignoreIOExceptions :: IO () -> IO ()
ignoreIOExceptions :: IO () -> IO ()
ignoreIOExceptions IO ()
io = IO ()
io IO () -> (IOError -> IO ()) -> IO ()
forall a. IO a -> (IOError -> IO a) -> IO a
`catchIOError` (\IOError
_ -> () -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type Applicative IO
pure ())
specializeErrorString :: String -> (IOError -> Bool) -> IO a -> IO a
specializeErrorString :: [Char] -> (IOError -> Bool) -> IO a -> IO a
specializeErrorString [Char]
str IOError -> Bool
errType IO a
action = do
Either IOError a
mx <- (IOError -> Bool) -> IO a -> IO (Either IOError a)
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 -> IOError -> IO a
forall e a. Exception e => e -> IO a
External instance of the constraint type Exception IOError
throwIO (IOError -> [Char] -> IOError
ioeSetErrorString IOError
e [Char]
str)
Right a
x -> a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type Applicative IO
pure a
x
ioeAddLocation :: IOError -> String -> IOError
ioeAddLocation :: IOError -> [Char] -> IOError
ioeAddLocation IOError
e [Char]
loc = do
IOError -> [Char] -> IOError
ioeSetLocation IOError
e [Char]
newLoc
where
newLoc :: [Char]
newLoc = [Char]
loc [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
External instance of the constraint type forall a. Semigroup [a]
<> if [Char] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
External instance of the constraint type Foldable []
null [Char]
oldLoc then [Char]
"" else [Char]
":" [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
External instance of the constraint type forall a. Semigroup [a]
<> [Char]
oldLoc
oldLoc :: [Char]
oldLoc = IOError -> [Char]
ioeGetLocation IOError
e
expandDots :: [FilePath] -> [FilePath]
expandDots :: [[Char]] -> [[Char]]
expandDots = [[Char]] -> [[Char]]
forall a. [a] -> [a]
reverse ([[Char]] -> [[Char]])
-> ([[Char]] -> [[Char]]) -> [[Char]] -> [[Char]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Char]] -> [[Char]] -> [[Char]]
go []
where
go :: [[Char]] -> [[Char]] -> [[Char]]
go [[Char]]
ys' [[Char]]
xs' =
case [[Char]]
xs' of
[] -> [[Char]]
ys'
[Char]
x : [[Char]]
xs ->
case [Char]
x of
[Char]
"." -> [[Char]] -> [[Char]] -> [[Char]]
go [[Char]]
ys' [[Char]]
xs
[Char]
".." ->
case [[Char]]
ys' of
[] -> [[Char]] -> [[Char]] -> [[Char]]
go ([Char]
x [Char] -> [[Char]] -> [[Char]]
forall a. a -> [a] -> [a]
: [[Char]]
ys') [[Char]]
xs
[Char]
".." : [[Char]]
_ -> [[Char]] -> [[Char]] -> [[Char]]
go ([Char]
x [Char] -> [[Char]] -> [[Char]]
forall a. a -> [a] -> [a]
: [[Char]]
ys') [[Char]]
xs
[Char]
_ : [[Char]]
ys -> [[Char]] -> [[Char]] -> [[Char]]
go [[Char]]
ys [[Char]]
xs
[Char]
_ -> [[Char]] -> [[Char]] -> [[Char]]
go ([Char]
x [Char] -> [[Char]] -> [[Char]]
forall a. a -> [a] -> [a]
: [[Char]]
ys') [[Char]]
xs
normalisePathSeps :: FilePath -> FilePath
normalisePathSeps :: [Char] -> [Char]
normalisePathSeps [Char]
p = (\ Char
c -> if Char -> Bool
isPathSeparator Char
c then Char
pathSeparator else Char
c) (Char -> Char) -> [Char] -> [Char]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor []
<$> [Char]
p
normaliseTrailingSep :: FilePath -> FilePath
normaliseTrailingSep :: [Char] -> [Char]
normaliseTrailingSep [Char]
path = do
let path' :: [Char]
path' = [Char] -> [Char]
forall a. [a] -> [a]
reverse [Char]
path
let ([Char]
sep, [Char]
path'') = (Char -> Bool) -> [Char] -> ([Char], [Char])
forall a. (a -> Bool) -> [a] -> ([a], [a])
span Char -> Bool
isPathSeparator [Char]
path'
let addSep :: [Char] -> [Char]
addSep = if [Char] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
External instance of the constraint type Foldable []
null [Char]
sep then [Char] -> [Char]
forall a. a -> a
id else (Char
pathSeparator Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:)
[Char] -> [Char]
forall a. [a] -> [a]
reverse ([Char] -> [Char]
addSep [Char]
path'')
emptyToCurDir :: FilePath -> FilePath
emptyToCurDir :: [Char] -> [Char]
emptyToCurDir [Char]
"" = [Char]
"."
emptyToCurDir [Char]
path = [Char]
path
simplifyPosix :: FilePath -> FilePath
simplifyPosix :: [Char] -> [Char]
simplifyPosix [Char]
"" = [Char]
""
simplifyPosix [Char]
path = [Char] -> [Char]
normalise [Char]
path
simplifyWindows :: FilePath -> FilePath
simplifyWindows :: [Char] -> [Char]
simplifyWindows [Char]
"" = [Char]
""
simplifyWindows [Char]
path =
case [Char]
drive' of
[Char]
"\\\\?\\" -> [Char]
drive' [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
External instance of the constraint type forall a. Semigroup [a]
<> [Char]
subpath
[Char]
_ -> [Char]
simplifiedPath
where
simplifiedPath :: [Char]
simplifiedPath = [Char] -> [Char] -> [Char]
joinDrive [Char]
drive' [Char]
subpath'
([Char]
drive, [Char]
subpath) = [Char] -> ([Char], [Char])
splitDrive [Char]
path
drive' :: [Char]
drive' = [Char] -> [Char]
upperDrive ([Char] -> [Char]
normaliseTrailingSep ([Char] -> [Char]
normalisePathSeps [Char]
drive))
subpath' :: [Char]
subpath' = [Char] -> [Char]
appendSep ([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [Char]
avoidEmpty ([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [Char]
prependSep ([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Char]] -> [Char]
joinPath ([[Char]] -> [Char]) -> ([Char] -> [[Char]]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[[Char]] -> [[Char]]
stripPardirs ([[Char]] -> [[Char]])
-> ([Char] -> [[Char]]) -> [Char] -> [[Char]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Char]] -> [[Char]]
expandDots ([[Char]] -> [[Char]])
-> ([Char] -> [[Char]]) -> [Char] -> [[Char]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Char]] -> [[Char]]
skipSeps ([[Char]] -> [[Char]])
-> ([Char] -> [[Char]]) -> [Char] -> [[Char]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[Char] -> [[Char]]
splitDirectories ([Char] -> [Char]) -> [Char] -> [Char]
forall a b. (a -> b) -> a -> b
$ [Char]
subpath
upperDrive :: [Char] -> [Char]
upperDrive [Char]
d = case [Char]
d of
Char
c : Char
':' : [Char]
s | Char -> Bool
isAlpha Char
c Bool -> Bool -> Bool
&& (Char -> Bool) -> [Char] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
External instance of the constraint type Foldable []
all Char -> Bool
isPathSeparator [Char]
s -> Char -> Char
toUpper Char
c Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: Char
':' Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: [Char]
s
[Char]
_ -> [Char]
d
skipSeps :: [[Char]] -> [[Char]]
skipSeps = ([Char] -> Bool) -> [[Char]] -> [[Char]]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> ([Char] -> Bool) -> [Char] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Char] -> [[Char]] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
External instance of the constraint type Foldable []
`elem` (Char -> [Char]
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type Applicative []
pure (Char -> [Char]) -> [Char] -> [[Char]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor []
<$> [Char]
pathSeparators)))
stripPardirs :: [[Char]] -> [[Char]]
stripPardirs | Bool
pathIsAbsolute Bool -> Bool -> Bool
|| Bool
subpathIsAbsolute = ([Char] -> Bool) -> [[Char]] -> [[Char]]
forall a. (a -> Bool) -> [a] -> [a]
dropWhile ([Char] -> [Char] -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
== [Char]
"..")
| Bool
otherwise = [[Char]] -> [[Char]]
forall a. a -> a
id
prependSep :: [Char] -> [Char]
prependSep | Bool
subpathIsAbsolute = (Char
pathSeparator Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:)
| Bool
otherwise = [Char] -> [Char]
forall a. a -> a
id
avoidEmpty :: [Char] -> [Char]
avoidEmpty | Bool -> Bool
not Bool
pathIsAbsolute
Bool -> Bool -> Bool
&& ([Char] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
External instance of the constraint type Foldable []
null [Char]
drive Bool -> Bool -> Bool
|| Bool
hasTrailingPathSep)
= [Char] -> [Char]
emptyToCurDir
| Bool
otherwise = [Char] -> [Char]
forall a. a -> a
id
appendSep :: [Char] -> [Char]
appendSep [Char]
p | Bool
hasTrailingPathSep
Bool -> Bool -> Bool
&& Bool -> Bool
not (Bool
pathIsAbsolute Bool -> Bool -> Bool
&& [Char] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
External instance of the constraint type Foldable []
null [Char]
p)
= [Char] -> [Char]
addTrailingPathSeparator [Char]
p
| Bool
otherwise = [Char]
p
pathIsAbsolute :: Bool
pathIsAbsolute = Bool -> Bool
not ([Char] -> Bool
isRelative [Char]
path)
subpathIsAbsolute :: Bool
subpathIsAbsolute = (Char -> Bool) -> [Char] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
External instance of the constraint type Foldable []
any Char -> Bool
isPathSeparator (Int -> [Char] -> [Char]
forall a. Int -> [a] -> [a]
take Int
1 [Char]
subpath)
hasTrailingPathSep :: Bool
hasTrailingPathSep = [Char] -> Bool
hasTrailingPathSeparator [Char]
subpath
data FileType = File
| SymbolicLink
| Directory
| DirectoryLink
deriving (FileType
FileType -> FileType -> Bounded 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]
(FileType -> FileType)
-> (FileType -> FileType)
-> (Int -> FileType)
-> (FileType -> Int)
-> (FileType -> [FileType])
-> (FileType -> FileType -> [FileType])
-> (FileType -> FileType -> [FileType])
-> (FileType -> FileType -> FileType -> [FileType])
-> Enum 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
External instance of the constraint type Enum Int
External instance of the constraint type Show Int
External instance of the constraint type Show Int
External instance of the constraint type Ord Int
External instance of the constraint type Ord Int
External instance of the constraint type Num Int
External instance of the constraint type Eq Int
Enum, FileType -> FileType -> Bool
(FileType -> FileType -> Bool)
-> (FileType -> FileType -> Bool) -> Eq FileType
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
Eq FileType
-> (FileType -> FileType -> Ordering)
-> (FileType -> FileType -> Bool)
-> (FileType -> FileType -> Bool)
-> (FileType -> FileType -> Bool)
-> (FileType -> FileType -> Bool)
-> (FileType -> FileType -> FileType)
-> (FileType -> FileType -> FileType)
-> Ord 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
Instance of class: Eq of the constraint type Eq FileType
Instance of class: Ord of the constraint type Ord FileType
Instance of class: Eq of the constraint type Eq FileType
Ord, ReadPrec [FileType]
ReadPrec FileType
Int -> ReadS FileType
ReadS [FileType]
(Int -> ReadS FileType)
-> ReadS [FileType]
-> ReadPrec FileType
-> ReadPrec [FileType]
-> Read 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
External instance of the constraint type Monad ReadPrec
External instance of the constraint type Monad ReadPrec
Instance of class: Read of the constraint type Read FileType
Read, Int -> FileType -> [Char] -> [Char]
[FileType] -> [Char] -> [Char]
FileType -> [Char]
(Int -> FileType -> [Char] -> [Char])
-> (FileType -> [Char])
-> ([FileType] -> [Char] -> [Char])
-> Show FileType
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
showList :: [FileType] -> [Char] -> [Char]
$cshowList :: [FileType] -> [Char] -> [Char]
show :: FileType -> [Char]
$cshow :: FileType -> [Char]
showsPrec :: Int -> FileType -> [Char] -> [Char]
$cshowsPrec :: Int -> FileType -> [Char] -> [Char]
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
(Permissions -> Permissions -> Bool)
-> (Permissions -> Permissions -> Bool) -> Eq Permissions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Permissions -> Permissions -> Bool
$c/= :: Permissions -> Permissions -> Bool
== :: Permissions -> Permissions -> Bool
$c== :: Permissions -> Permissions -> Bool
External instance of the constraint type Eq Bool
External instance of the constraint type Eq Bool
Eq, Eq Permissions
Eq Permissions
-> (Permissions -> Permissions -> Ordering)
-> (Permissions -> Permissions -> Bool)
-> (Permissions -> Permissions -> Bool)
-> (Permissions -> Permissions -> Bool)
-> (Permissions -> Permissions -> Bool)
-> (Permissions -> Permissions -> Permissions)
-> (Permissions -> Permissions -> Permissions)
-> Ord 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
External instance of the constraint type Ord Bool
External instance of the constraint type Ord Bool
External instance of the constraint type Ord Bool
Instance of class: Eq of the constraint type Eq Permissions
Instance of class: Ord of the constraint type Ord Permissions
Instance of class: Eq of the constraint type Eq Permissions
Ord, ReadPrec [Permissions]
ReadPrec Permissions
Int -> ReadS Permissions
ReadS [Permissions]
(Int -> ReadS Permissions)
-> ReadS [Permissions]
-> ReadPrec Permissions
-> ReadPrec [Permissions]
-> Read 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
External instance of the constraint type Read Bool
External instance of the constraint type Read Bool
External instance of the constraint type Monad ReadPrec
External instance of the constraint type Monad ReadPrec
Instance of class: Read of the constraint type Read Permissions
Read, Int -> Permissions -> [Char] -> [Char]
[Permissions] -> [Char] -> [Char]
Permissions -> [Char]
(Int -> Permissions -> [Char] -> [Char])
-> (Permissions -> [Char])
-> ([Permissions] -> [Char] -> [Char])
-> Show Permissions
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
showList :: [Permissions] -> [Char] -> [Char]
$cshowList :: [Permissions] -> [Char] -> [Char]
show :: Permissions -> [Char]
$cshow :: Permissions -> [Char]
showsPrec :: Int -> Permissions -> [Char] -> [Char]
$cshowsPrec :: Int -> Permissions -> [Char] -> [Char]
External instance of the constraint type Show Bool
External instance of the constraint type Show Bool
External instance of the constraint type Ord Int
Show)
copyFileContents :: FilePath
-> FilePath
-> IO ()
copyFileContents :: [Char] -> [Char] -> IO ()
copyFileContents [Char]
fromFPath [Char]
toFPath =
(IOError -> [Char] -> IOError
`ioeAddLocation` [Char]
"copyFileContents") (IOError -> IOError) -> IO () -> IO ()
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
[Char] -> IOMode -> (Handle -> IO ()) -> IO ()
forall r. [Char] -> IOMode -> (Handle -> IO r) -> IO r
withBinaryFile [Char]
toFPath IOMode
WriteMode ((Handle -> IO ()) -> IO ()) -> (Handle -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ Handle
hTo ->
[Char] -> Handle -> IO ()
copyFileToHandle [Char]
fromFPath Handle
hTo
copyFileToHandle :: FilePath
-> Handle
-> IO ()
copyFileToHandle :: [Char] -> Handle -> IO ()
copyFileToHandle [Char]
fromFPath Handle
hTo =
(IOError -> [Char] -> IOError
`ioeAddLocation` [Char]
"copyFileToHandle") (IOError -> IOError) -> IO () -> IO ()
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
[Char] -> IOMode -> (Handle -> IO ()) -> IO ()
forall r. [Char] -> IOMode -> (Handle -> IO r) -> IO r
withBinaryFile [Char]
fromFPath IOMode
ReadMode ((Handle -> IO ()) -> IO ()) -> (Handle -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ Handle
hFrom ->
Handle -> Handle -> IO ()
copyHandleData Handle
hFrom Handle
hTo
copyHandleData :: Handle
-> Handle
-> IO ()
copyHandleData :: Handle -> Handle -> IO ()
copyHandleData Handle
hFrom Handle
hTo =
(IOError -> [Char] -> IOError
`ioeAddLocation` [Char]
"copyData") (IOError -> IOError) -> IO () -> IO ()
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
Int -> (Ptr Any -> IO ()) -> IO ()
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
bufferSize Ptr Any -> IO ()
forall {a}. Ptr a -> IO ()
go
where
bufferSize :: Int
bufferSize = Int
131072
go :: Ptr a -> IO ()
go Ptr a
buffer = do
Int
count <- Handle -> Ptr a -> Int -> IO Int
forall a. Handle -> Ptr a -> Int -> IO Int
hGetBuf Handle
hFrom Ptr a
buffer Int
bufferSize
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
External instance of the constraint type Applicative IO
when (Int
count Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
> Int
0) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
Handle -> Ptr a -> Int -> IO ()
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
deriving (XdgDirectory
XdgDirectory -> XdgDirectory -> Bounded 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]
(XdgDirectory -> XdgDirectory)
-> (XdgDirectory -> XdgDirectory)
-> (Int -> XdgDirectory)
-> (XdgDirectory -> Int)
-> (XdgDirectory -> [XdgDirectory])
-> (XdgDirectory -> XdgDirectory -> [XdgDirectory])
-> (XdgDirectory -> XdgDirectory -> [XdgDirectory])
-> (XdgDirectory -> XdgDirectory -> XdgDirectory -> [XdgDirectory])
-> Enum 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
External instance of the constraint type Show Int
External instance of the constraint type Ord Int
External instance of the constraint type Enum Int
External instance of the constraint type Show Int
External instance of the constraint type Ord Int
External instance of the constraint type Num Int
External instance of the constraint type Eq Int
Enum, XdgDirectory -> XdgDirectory -> Bool
(XdgDirectory -> XdgDirectory -> Bool)
-> (XdgDirectory -> XdgDirectory -> Bool) -> Eq XdgDirectory
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
Eq XdgDirectory
-> (XdgDirectory -> XdgDirectory -> Ordering)
-> (XdgDirectory -> XdgDirectory -> Bool)
-> (XdgDirectory -> XdgDirectory -> Bool)
-> (XdgDirectory -> XdgDirectory -> Bool)
-> (XdgDirectory -> XdgDirectory -> Bool)
-> (XdgDirectory -> XdgDirectory -> XdgDirectory)
-> (XdgDirectory -> XdgDirectory -> XdgDirectory)
-> Ord 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
Instance of class: Eq of the constraint type Eq XdgDirectory
Instance of class: Ord of the constraint type Ord XdgDirectory
Instance of class: Eq of the constraint type Eq XdgDirectory
Ord, ReadPrec [XdgDirectory]
ReadPrec XdgDirectory
Int -> ReadS XdgDirectory
ReadS [XdgDirectory]
(Int -> ReadS XdgDirectory)
-> ReadS [XdgDirectory]
-> ReadPrec XdgDirectory
-> ReadPrec [XdgDirectory]
-> Read 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
External instance of the constraint type Monad ReadPrec
External instance of the constraint type Monad ReadPrec
Instance of class: Read of the constraint type Read XdgDirectory
Read, Int -> XdgDirectory -> [Char] -> [Char]
[XdgDirectory] -> [Char] -> [Char]
XdgDirectory -> [Char]
(Int -> XdgDirectory -> [Char] -> [Char])
-> (XdgDirectory -> [Char])
-> ([XdgDirectory] -> [Char] -> [Char])
-> Show XdgDirectory
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
showList :: [XdgDirectory] -> [Char] -> [Char]
$cshowList :: [XdgDirectory] -> [Char] -> [Char]
show :: XdgDirectory -> [Char]
$cshow :: XdgDirectory -> [Char]
showsPrec :: Int -> XdgDirectory -> [Char] -> [Char]
$cshowsPrec :: Int -> XdgDirectory -> [Char] -> [Char]
Show)
data XdgDirectoryList
= XdgDataDirs
| XdgConfigDirs
deriving (XdgDirectoryList
XdgDirectoryList -> XdgDirectoryList -> Bounded 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]
(XdgDirectoryList -> XdgDirectoryList)
-> (XdgDirectoryList -> XdgDirectoryList)
-> (Int -> XdgDirectoryList)
-> (XdgDirectoryList -> Int)
-> (XdgDirectoryList -> [XdgDirectoryList])
-> (XdgDirectoryList -> XdgDirectoryList -> [XdgDirectoryList])
-> (XdgDirectoryList -> XdgDirectoryList -> [XdgDirectoryList])
-> (XdgDirectoryList
-> XdgDirectoryList -> XdgDirectoryList -> [XdgDirectoryList])
-> Enum 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
External instance of the constraint type Show Int
External instance of the constraint type Ord Int
External instance of the constraint type Enum Int
External instance of the constraint type Show Int
External instance of the constraint type Ord Int
External instance of the constraint type Num Int
External instance of the constraint type Eq Int
Enum, XdgDirectoryList -> XdgDirectoryList -> Bool
(XdgDirectoryList -> XdgDirectoryList -> Bool)
-> (XdgDirectoryList -> XdgDirectoryList -> Bool)
-> Eq XdgDirectoryList
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
Eq XdgDirectoryList
-> (XdgDirectoryList -> XdgDirectoryList -> Ordering)
-> (XdgDirectoryList -> XdgDirectoryList -> Bool)
-> (XdgDirectoryList -> XdgDirectoryList -> Bool)
-> (XdgDirectoryList -> XdgDirectoryList -> Bool)
-> (XdgDirectoryList -> XdgDirectoryList -> Bool)
-> (XdgDirectoryList -> XdgDirectoryList -> XdgDirectoryList)
-> (XdgDirectoryList -> XdgDirectoryList -> XdgDirectoryList)
-> Ord 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
Instance of class: Eq of the constraint type Eq XdgDirectoryList
Instance of class: Ord of the constraint type Ord XdgDirectoryList
Instance of class: Eq of the constraint type Eq XdgDirectoryList
Ord, ReadPrec [XdgDirectoryList]
ReadPrec XdgDirectoryList
Int -> ReadS XdgDirectoryList
ReadS [XdgDirectoryList]
(Int -> ReadS XdgDirectoryList)
-> ReadS [XdgDirectoryList]
-> ReadPrec XdgDirectoryList
-> ReadPrec [XdgDirectoryList]
-> Read 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
External instance of the constraint type Monad ReadPrec
External instance of the constraint type Monad ReadPrec
Instance of class: Read of the constraint type Read XdgDirectoryList
Read, Int -> XdgDirectoryList -> [Char] -> [Char]
[XdgDirectoryList] -> [Char] -> [Char]
XdgDirectoryList -> [Char]
(Int -> XdgDirectoryList -> [Char] -> [Char])
-> (XdgDirectoryList -> [Char])
-> ([XdgDirectoryList] -> [Char] -> [Char])
-> Show XdgDirectoryList
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
showList :: [XdgDirectoryList] -> [Char] -> [Char]
$cshowList :: [XdgDirectoryList] -> [Char] -> [Char]
show :: XdgDirectoryList -> [Char]
$cshow :: XdgDirectoryList -> [Char]
showsPrec :: Int -> XdgDirectoryList -> [Char] -> [Char]
$cshowsPrec :: Int -> XdgDirectoryList -> [Char] -> [Char]
Show)