{-# LINE 1 "libraries/directory/System/Directory/Internal/Posix.hsc" #-}
module System.Directory.Internal.Posix where
{-# LINE 4 "libraries/directory/System/Directory/Internal/Posix.hsc" #-}
{-# LINE 5 "libraries/directory/System/Directory/Internal/Posix.hsc" #-}
{-# LINE 7 "libraries/directory/System/Directory/Internal/Posix.hsc" #-}
import Prelude ()
import System.Directory.Internal.Prelude
{-# LINE 10 "libraries/directory/System/Directory/Internal/Posix.hsc" #-}
import System.Directory.Internal.C_utimensat
{-# LINE 12 "libraries/directory/System/Directory/Internal/Posix.hsc" #-}
import System.Directory.Internal.Common
import System.Directory.Internal.Config (exeExtension)
import Data.Time (UTCTime)
import Data.Time.Clock.POSIX (POSIXTime)
import System.FilePath ((</>), isRelative, splitSearchPath)
import qualified Data.Time.Clock.POSIX as POSIXTime
import qualified GHC.Foreign as GHC
import qualified System.Posix as Posix
import qualified System.Posix.User as PU
createDirectoryInternal :: FilePath -> IO ()
createDirectoryInternal :: FilePath -> IO ()
createDirectoryInternal FilePath
path = FilePath -> FileMode -> IO ()
Posix.createDirectory FilePath
path FileMode
0o777
removePathInternal :: Bool -> FilePath -> IO ()
removePathInternal :: Bool -> FilePath -> IO ()
removePathInternal Bool
True  = FilePath -> IO ()
Posix.removeDirectory
removePathInternal Bool
False = FilePath -> IO ()
Posix.removeLink
renamePathInternal :: FilePath -> FilePath -> IO ()
renamePathInternal :: FilePath -> FilePath -> IO ()
renamePathInternal = FilePath -> FilePath -> IO ()
Posix.rename
simplify :: FilePath -> FilePath
simplify :: FilePath -> FilePath
simplify = FilePath -> FilePath
simplifyPosix
foreign import ccall unsafe "free" c_free :: Ptr a -> IO ()
c_PATH_MAX :: Maybe Int
{-# LINE 42 "libraries/directory/System/Directory/Internal/Posix.hsc" #-}
c_PATH_MAX | c_PATH_MAX' > toInteger maxValue = Nothing
           | otherwise                        = Just (fromInteger c_PATH_MAX')
  where c_PATH_MAX' = (4096)
{-# LINE 45 "libraries/directory/System/Directory/Internal/Posix.hsc" #-}
        maxValue = maxBound `asTypeInMaybe` c_PATH_MAX
        asTypeInMaybe :: a -> Maybe a -> a
        asTypeInMaybe = const
{-# LINE 51 "libraries/directory/System/Directory/Internal/Posix.hsc" #-}
{-# LINE 58 "libraries/directory/System/Directory/Internal/Posix.hsc" #-}
foreign import ccall "realpath" c_realpath :: CString -> CString -> IO CString
{-# LINE 62 "libraries/directory/System/Directory/Internal/Posix.hsc" #-}
withRealpath :: CString -> (CString -> IO a) -> IO a
withRealpath :: forall a. CString -> (CString -> IO a) -> IO a
withRealpath CString
path CString -> IO a
action = case Maybe Int
c_PATH_MAX of
  Maybe Int
Nothing ->
    
    
    IO CString -> (CString -> IO ()) -> (CString -> IO a) -> IO a
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (CString -> IO CString
realpath CString
forall a. Ptr a
nullPtr) CString -> IO ()
forall a. Ptr a -> IO ()
c_free CString -> IO a
action
  Just Int
pathMax ->
    
    Int -> (CString -> IO a) -> IO a
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes (Int
pathMax Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (CString -> IO CString
realpath (CString -> IO CString) -> (CString -> IO a) -> CString -> IO a
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> CString -> IO a
action)
  where realpath :: CString -> IO CString
realpath = FilePath -> IO CString -> IO CString
forall a. FilePath -> IO (Ptr a) -> IO (Ptr a)
throwErrnoIfNull FilePath
"" (IO CString -> IO CString)
-> (CString -> IO CString) -> CString -> IO CString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CString -> CString -> IO CString
c_realpath CString
path
canonicalizePathWith :: ((FilePath -> IO FilePath) -> FilePath -> IO FilePath)
                     -> FilePath
                     -> IO FilePath
canonicalizePathWith :: ((FilePath -> IO FilePath) -> FilePath -> IO FilePath)
-> FilePath -> IO FilePath
canonicalizePathWith (FilePath -> IO FilePath) -> FilePath -> IO FilePath
attemptRealpath FilePath
path = do
  TextEncoding
encoding <- IO TextEncoding
getFileSystemEncoding
  let realpath :: FilePath -> IO FilePath
realpath FilePath
path' =
        TextEncoding -> FilePath -> (CString -> IO FilePath) -> IO FilePath
forall a. TextEncoding -> FilePath -> (CString -> IO a) -> IO a
GHC.withCString TextEncoding
encoding FilePath
path' (CString -> (CString -> IO FilePath) -> IO FilePath
forall a. CString -> (CString -> IO a) -> IO a
`withRealpath` TextEncoding -> CString -> IO FilePath
GHC.peekCString TextEncoding
encoding)
  (FilePath -> IO FilePath) -> FilePath -> IO FilePath
attemptRealpath FilePath -> IO FilePath
realpath FilePath
path
canonicalizePathSimplify :: FilePath -> IO FilePath
canonicalizePathSimplify :: FilePath -> IO FilePath
canonicalizePathSimplify = FilePath -> IO FilePath
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
findExecutablesLazyInternal :: ([FilePath] -> String -> ListT IO FilePath)
                            -> String
                            -> ListT IO FilePath
findExecutablesLazyInternal :: ([FilePath] -> FilePath -> ListT IO FilePath)
-> FilePath -> ListT IO FilePath
findExecutablesLazyInternal [FilePath] -> FilePath -> ListT IO FilePath
findExecutablesInDirectoriesLazy FilePath
binary =
  IO (ListT IO FilePath) -> ListT IO FilePath
forall (m :: * -> *) a. Monad m => m (ListT m a) -> ListT m a
liftJoinListT (IO (ListT IO FilePath) -> ListT IO FilePath)
-> IO (ListT IO FilePath) -> ListT IO FilePath
forall a b. (a -> b) -> a -> b
$ do
    [FilePath]
path <- IO [FilePath]
getPath
    ListT IO FilePath -> IO (ListT IO FilePath)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([FilePath] -> FilePath -> ListT IO FilePath
findExecutablesInDirectoriesLazy [FilePath]
path FilePath
binary)
exeExtensionInternal :: String
exeExtensionInternal :: FilePath
exeExtensionInternal = FilePath
exeExtension
getDirectoryContentsInternal :: FilePath -> IO [FilePath]
getDirectoryContentsInternal :: FilePath -> IO [FilePath]
getDirectoryContentsInternal FilePath
path =
  IO DirStream
-> (DirStream -> IO ())
-> (DirStream -> IO [FilePath])
-> IO [FilePath]
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket
    (FilePath -> IO DirStream
Posix.openDirStream FilePath
path)
    DirStream -> IO ()
Posix.closeDirStream
    DirStream -> IO [FilePath]
start
  where
    start :: DirStream -> IO [FilePath]
start DirStream
dirp = ([FilePath] -> [FilePath]) -> IO [FilePath]
forall {c}. ([FilePath] -> c) -> IO c
loop [FilePath] -> [FilePath]
forall a. a -> a
id
      where
        loop :: ([FilePath] -> c) -> IO c
loop [FilePath] -> c
acc = do
          FilePath
e <- DirStream -> IO FilePath
Posix.readDirStream DirStream
dirp
          if FilePath -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
e
            then c -> IO c
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([FilePath] -> c
acc [])
            else ([FilePath] -> c) -> IO c
loop ([FilePath] -> c
acc ([FilePath] -> c) -> ([FilePath] -> [FilePath]) -> [FilePath] -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath
eFilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
:))
getCurrentDirectoryInternal :: IO FilePath
getCurrentDirectoryInternal :: IO FilePath
getCurrentDirectoryInternal = IO FilePath
Posix.getWorkingDirectory
prependCurrentDirectory :: FilePath -> IO FilePath
prependCurrentDirectory :: FilePath -> IO FilePath
prependCurrentDirectory FilePath
path
  | FilePath -> Bool
isRelative FilePath
path =
    ((IOError -> FilePath -> IOError
`ioeAddLocation` FilePath
"prependCurrentDirectory") (IOError -> IOError) -> (IOError -> IOError) -> IOError -> IOError
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
     (IOError -> FilePath -> IOError
`ioeSetFileName` FilePath
path)) (IOError -> IOError) -> IO FilePath -> IO FilePath
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
      (FilePath -> FilePath -> FilePath
</> FilePath
path) (FilePath -> FilePath) -> IO FilePath -> IO FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO FilePath
getCurrentDirectoryInternal
  | Bool
otherwise = FilePath -> IO FilePath
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure FilePath
path
setCurrentDirectoryInternal :: FilePath -> IO ()
setCurrentDirectoryInternal :: FilePath -> IO ()
setCurrentDirectoryInternal = FilePath -> IO ()
Posix.changeWorkingDirectory
linkToDirectoryIsDirectory :: Bool
linkToDirectoryIsDirectory :: Bool
linkToDirectoryIsDirectory = Bool
False
createSymbolicLink :: Bool -> FilePath -> FilePath -> IO ()
createSymbolicLink :: Bool -> FilePath -> FilePath -> IO ()
createSymbolicLink Bool
_ = FilePath -> FilePath -> IO ()
Posix.createSymbolicLink
readSymbolicLink :: FilePath -> IO FilePath
readSymbolicLink :: FilePath -> IO FilePath
readSymbolicLink = FilePath -> IO FilePath
Posix.readSymbolicLink
type Metadata = Posix.FileStatus
getSymbolicLinkMetadata :: FilePath -> IO Metadata
getSymbolicLinkMetadata :: FilePath -> IO Metadata
getSymbolicLinkMetadata = FilePath -> IO Metadata
Posix.getSymbolicLinkStatus
getFileMetadata :: FilePath -> IO Metadata
getFileMetadata :: FilePath -> IO Metadata
getFileMetadata = FilePath -> IO Metadata
Posix.getFileStatus
fileTypeFromMetadata :: Metadata -> FileType
fileTypeFromMetadata :: Metadata -> FileType
fileTypeFromMetadata Metadata
stat
  | Bool
isLink    = FileType
SymbolicLink
  | Bool
isDir     = FileType
Directory
  | Bool
otherwise = FileType
File
  where
    isLink :: Bool
isLink = Metadata -> Bool
Posix.isSymbolicLink Metadata
stat
    isDir :: Bool
isDir  = Metadata -> Bool
Posix.isDirectory Metadata
stat
fileSizeFromMetadata :: Metadata -> Integer
fileSizeFromMetadata :: Metadata -> Integer
fileSizeFromMetadata = FileOffset -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (FileOffset -> Integer)
-> (Metadata -> FileOffset) -> Metadata -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Metadata -> FileOffset
Posix.fileSize
accessTimeFromMetadata :: Metadata -> UTCTime
accessTimeFromMetadata :: Metadata -> UTCTime
accessTimeFromMetadata =
  POSIXTime -> UTCTime
POSIXTime.posixSecondsToUTCTime (POSIXTime -> UTCTime)
-> (Metadata -> POSIXTime) -> Metadata -> UTCTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Metadata -> POSIXTime
posix_accessTimeHiRes
modificationTimeFromMetadata :: Metadata -> UTCTime
modificationTimeFromMetadata :: Metadata -> UTCTime
modificationTimeFromMetadata =
  POSIXTime -> UTCTime
POSIXTime.posixSecondsToUTCTime (POSIXTime -> UTCTime)
-> (Metadata -> POSIXTime) -> Metadata -> UTCTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Metadata -> POSIXTime
posix_modificationTimeHiRes
posix_accessTimeHiRes, posix_modificationTimeHiRes
  :: Posix.FileStatus -> POSIXTime
{-# LINE 175 "libraries/directory/System/Directory/Internal/Posix.hsc" #-}
posix_accessTimeHiRes = Posix.accessTimeHiRes
posix_modificationTimeHiRes :: Metadata -> POSIXTime
posix_modificationTimeHiRes = Metadata -> POSIXTime
Posix.modificationTimeHiRes
{-# LINE 181 "libraries/directory/System/Directory/Internal/Posix.hsc" #-}
type Mode = Posix.FileMode
modeFromMetadata :: Metadata -> Mode
modeFromMetadata :: Metadata -> FileMode
modeFromMetadata = Metadata -> FileMode
Posix.fileMode
allWriteMode :: Posix.FileMode
allWriteMode :: FileMode
allWriteMode =
  FileMode
Posix.ownerWriteMode FileMode -> FileMode -> FileMode
forall a. Bits a => a -> a -> a
.|.
  FileMode
Posix.groupWriteMode FileMode -> FileMode -> FileMode
forall a. Bits a => a -> a -> a
.|.
  FileMode
Posix.otherWriteMode
hasWriteMode :: Mode -> Bool
hasWriteMode :: FileMode -> Bool
hasWriteMode FileMode
m = FileMode
m FileMode -> FileMode -> FileMode
forall a. Bits a => a -> a -> a
.&. FileMode
allWriteMode FileMode -> FileMode -> Bool
forall a. Eq a => a -> a -> Bool
/= FileMode
0
setWriteMode :: Bool -> Mode -> Mode
setWriteMode :: Bool -> FileMode -> FileMode
setWriteMode Bool
False FileMode
m = FileMode
m FileMode -> FileMode -> FileMode
forall a. Bits a => a -> a -> a
.&. FileMode -> FileMode
forall a. Bits a => a -> a
complement FileMode
allWriteMode
setWriteMode Bool
True  FileMode
m = FileMode
m FileMode -> FileMode -> FileMode
forall a. Bits a => a -> a -> a
.|. FileMode
allWriteMode
setFileMode :: FilePath -> Mode -> IO ()
setFileMode :: FilePath -> FileMode -> IO ()
setFileMode = FilePath -> FileMode -> IO ()
Posix.setFileMode
setFilePermissions :: FilePath -> Mode -> IO ()
setFilePermissions :: FilePath -> FileMode -> IO ()
setFilePermissions = FilePath -> FileMode -> IO ()
setFileMode
getAccessPermissions :: FilePath -> IO Permissions
getAccessPermissions :: FilePath -> IO Permissions
getAccessPermissions FilePath
path = do
  Metadata
m <- FilePath -> IO Metadata
getFileMetadata FilePath
path
  let isDir :: Bool
isDir = FileType -> Bool
fileTypeIsDirectory (Metadata -> FileType
fileTypeFromMetadata Metadata
m)
  Bool
r <- FilePath -> Bool -> Bool -> Bool -> IO Bool
Posix.fileAccess FilePath
path Bool
True  Bool
False Bool
False
  Bool
w <- FilePath -> Bool -> Bool -> Bool -> IO Bool
Posix.fileAccess FilePath
path Bool
False Bool
True  Bool
False
  Bool
x <- FilePath -> Bool -> Bool -> Bool -> IO Bool
Posix.fileAccess FilePath
path Bool
False Bool
False Bool
True
  Permissions -> IO Permissions
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Permissions
       { readable :: Bool
readable   = Bool
r
       , writable :: Bool
writable   = Bool
w
       , executable :: Bool
executable = Bool
x Bool -> Bool -> Bool
&& Bool -> Bool
not Bool
isDir
       , searchable :: Bool
searchable = Bool
x Bool -> Bool -> Bool
&& Bool
isDir
       }
setAccessPermissions :: FilePath -> Permissions -> IO ()
setAccessPermissions :: FilePath -> Permissions -> IO ()
setAccessPermissions FilePath
path (Permissions Bool
r Bool
w Bool
e Bool
s) = do
  Metadata
m <- FilePath -> IO Metadata
getFileMetadata FilePath
path
  FilePath -> FileMode -> IO ()
setFileMode FilePath
path (Bool -> FileMode -> FileMode -> FileMode
modifyBit (Bool
e Bool -> Bool -> Bool
|| Bool
s) FileMode
Posix.ownerExecuteMode (FileMode -> FileMode)
-> (Metadata -> FileMode) -> Metadata -> FileMode
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                    Bool -> FileMode -> FileMode -> FileMode
modifyBit Bool
w FileMode
Posix.ownerWriteMode (FileMode -> FileMode)
-> (Metadata -> FileMode) -> Metadata -> FileMode
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                    Bool -> FileMode -> FileMode -> FileMode
modifyBit Bool
r FileMode
Posix.ownerReadMode (FileMode -> FileMode)
-> (Metadata -> FileMode) -> Metadata -> FileMode
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                    Metadata -> FileMode
modeFromMetadata (Metadata -> FileMode) -> Metadata -> FileMode
forall a b. (a -> b) -> a -> b
$ Metadata
m)
  where
    modifyBit :: Bool -> Posix.FileMode -> Posix.FileMode -> Posix.FileMode
    modifyBit :: Bool -> FileMode -> FileMode -> FileMode
modifyBit Bool
False FileMode
b FileMode
m = FileMode
m FileMode -> FileMode -> FileMode
forall a. Bits a => a -> a -> a
.&. FileMode -> FileMode
forall a. Bits a => a -> a
complement FileMode
b
    modifyBit Bool
True  FileMode
b FileMode
m = FileMode
m FileMode -> FileMode -> FileMode
forall a. Bits a => a -> a -> a
.|. FileMode
b
copyOwnerFromStatus :: Posix.FileStatus -> FilePath -> IO ()
copyOwnerFromStatus :: Metadata -> FilePath -> IO ()
copyOwnerFromStatus Metadata
st FilePath
dst = do
  FilePath -> UserID -> GroupID -> IO ()
Posix.setOwnerAndGroup FilePath
dst (Metadata -> UserID
Posix.fileOwner Metadata
st) (-GroupID
1)
copyGroupFromStatus :: Posix.FileStatus -> FilePath -> IO ()
copyGroupFromStatus :: Metadata -> FilePath -> IO ()
copyGroupFromStatus Metadata
st FilePath
dst = do
  FilePath -> UserID -> GroupID -> IO ()
Posix.setOwnerAndGroup FilePath
dst (-UserID
1) (Metadata -> GroupID
Posix.fileGroup Metadata
st)
tryCopyOwnerAndGroupFromStatus :: Posix.FileStatus -> FilePath -> IO ()
tryCopyOwnerAndGroupFromStatus :: Metadata -> FilePath -> IO ()
tryCopyOwnerAndGroupFromStatus Metadata
st FilePath
dst = do
  IO () -> IO ()
ignoreIOExceptions (Metadata -> FilePath -> IO ()
copyOwnerFromStatus Metadata
st FilePath
dst)
  IO () -> IO ()
ignoreIOExceptions (Metadata -> FilePath -> IO ()
copyGroupFromStatus Metadata
st FilePath
dst)
copyFileWithMetadataInternal :: (Metadata -> FilePath -> IO ())
                             -> (Metadata -> FilePath -> IO ())
                             -> FilePath
                             -> FilePath
                             -> IO ()
copyFileWithMetadataInternal :: (Metadata -> FilePath -> IO ())
-> (Metadata -> FilePath -> IO ()) -> FilePath -> FilePath -> IO ()
copyFileWithMetadataInternal Metadata -> FilePath -> IO ()
copyPermissionsFromMetadata
                             Metadata -> FilePath -> IO ()
copyTimesFromMetadata
                             FilePath
src
                             FilePath
dst = do
  Metadata
st <- FilePath -> IO Metadata
Posix.getFileStatus FilePath
src
  FilePath -> FilePath -> IO ()
copyFileContents FilePath
src FilePath
dst
  Metadata -> FilePath -> IO ()
tryCopyOwnerAndGroupFromStatus Metadata
st FilePath
dst
  Metadata -> FilePath -> IO ()
copyPermissionsFromMetadata Metadata
st FilePath
dst
  Metadata -> FilePath -> IO ()
copyTimesFromMetadata Metadata
st FilePath
dst
setTimes :: FilePath -> (Maybe POSIXTime, Maybe POSIXTime) -> IO ()
setTimes :: FilePath -> (Maybe POSIXTime, Maybe POSIXTime) -> IO ()
{-# LINE 262 "libraries/directory/System/Directory/Internal/Posix.hsc" #-}
setTimes path' (atime', mtime') =
  withFilePath path' $ \ path'' ->
  withArray [ maybe utimeOmit toCTimeSpec atime'
            , maybe utimeOmit toCTimeSpec mtime' ] $ \ times ->
  throwErrnoPathIfMinus1_ "" path' $
    c_utimensat c_AT_FDCWD path'' times 0
{-# LINE 288 "libraries/directory/System/Directory/Internal/Posix.hsc" #-}
getPath :: IO [FilePath]
getPath :: IO [FilePath]
getPath = FilePath -> [FilePath]
splitSearchPath (FilePath -> [FilePath]) -> IO FilePath -> IO [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> IO FilePath
getEnv FilePath
"PATH"
getHomeDirectoryInternal :: IO FilePath
getHomeDirectoryInternal :: IO FilePath
getHomeDirectoryInternal = do
  Maybe FilePath
e <- FilePath -> IO (Maybe FilePath)
lookupEnv FilePath
"HOME"
  case Maybe FilePath
e of
       Just FilePath
fp -> FilePath -> IO FilePath
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure FilePath
fp
       Maybe FilePath
Nothing -> UserEntry -> FilePath
PU.homeDirectory (UserEntry -> FilePath) -> IO UserEntry -> IO FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (IO UserID
PU.getEffectiveUserID IO UserID -> (UserID -> IO UserEntry) -> IO UserEntry
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= UserID -> IO UserEntry
PU.getUserEntryForID)
getXdgDirectoryFallback :: IO FilePath -> XdgDirectory -> IO FilePath
getXdgDirectoryFallback :: IO FilePath -> XdgDirectory -> IO FilePath
getXdgDirectoryFallback IO FilePath
getHomeDirectory XdgDirectory
xdgDir = do
  ((FilePath -> FilePath) -> IO FilePath -> IO FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO FilePath
getHomeDirectory) ((FilePath -> FilePath) -> IO FilePath)
-> (FilePath -> FilePath) -> IO FilePath
forall a b. (a -> b) -> a -> b
$ (FilePath -> FilePath -> FilePath)
-> FilePath -> FilePath -> FilePath
forall a b c. (a -> b -> c) -> b -> a -> c
flip FilePath -> FilePath -> FilePath
(</>) (FilePath -> FilePath -> FilePath)
-> FilePath -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ case XdgDirectory
xdgDir of
    XdgDirectory
XdgData   -> FilePath
".local/share"
    XdgDirectory
XdgConfig -> FilePath
".config"
    XdgDirectory
XdgCache  -> FilePath
".cache"
    XdgDirectory
XdgState  -> FilePath
".local/state"
getXdgDirectoryListFallback :: XdgDirectoryList -> IO [FilePath]
getXdgDirectoryListFallback :: XdgDirectoryList -> IO [FilePath]
getXdgDirectoryListFallback XdgDirectoryList
xdgDirs =
  [FilePath] -> IO [FilePath]
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([FilePath] -> IO [FilePath]) -> [FilePath] -> IO [FilePath]
forall a b. (a -> b) -> a -> b
$ case XdgDirectoryList
xdgDirs of
    XdgDirectoryList
XdgDataDirs   -> [FilePath
"/usr/local/share/", FilePath
"/usr/share/"]
    XdgDirectoryList
XdgConfigDirs -> [FilePath
"/etc/xdg"]
getAppUserDataDirectoryInternal :: FilePath -> IO FilePath
getAppUserDataDirectoryInternal :: FilePath -> IO FilePath
getAppUserDataDirectoryInternal FilePath
appName =
  (\ FilePath
home -> FilePath
home FilePath -> FilePath -> FilePath
forall a. Semigroup a => a -> a -> a
<> (Char
'/' Char -> FilePath -> FilePath
forall a. a -> [a] -> [a]
: Char
'.' Char -> FilePath -> FilePath
forall a. a -> [a] -> [a]
: FilePath
appName)) (FilePath -> FilePath) -> IO FilePath -> IO FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO FilePath
getHomeDirectoryInternal
getUserDocumentsDirectoryInternal :: IO FilePath
getUserDocumentsDirectoryInternal :: IO FilePath
getUserDocumentsDirectoryInternal = IO FilePath
getHomeDirectoryInternal
getTemporaryDirectoryInternal :: IO FilePath
getTemporaryDirectoryInternal :: IO FilePath
getTemporaryDirectoryInternal = FilePath -> Maybe FilePath -> FilePath
forall a. a -> Maybe a -> a
fromMaybe FilePath
"/tmp" (Maybe FilePath -> FilePath) -> IO (Maybe FilePath) -> IO FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> IO (Maybe FilePath)
lookupEnv FilePath
"TMPDIR"
{-# LINE 327 "libraries/directory/System/Directory/Internal/Posix.hsc" #-}