{-# LANGUAGE CPP #-}
module System.Directory.OsPath.FileType
( FileType(..)
, getFileType
) where
import System.OsPath.Types (OsPath)
#ifdef mingw32_HOST_OS
import System.Directory.OsPath (doesFileExist, doesDirectoryExist)
getFileType :: OsPath -> IO FileType
getFileType fp = do
isFile <- doesFileExist fp
if isFile
then pure File
else do
isDir <- doesDirectoryExist fp
pure $ if isDir then Directory else Other
#else
import Control.Exception (try, IOException)
import System.OsString.Internal.Types (getOsString)
import System.Posix.Files.PosixString qualified as PosixF
getFileType :: OsPath -> IO FileType
getFileType :: OsPath -> IO FileType
getFileType OsPath
fp = do
FileStatus
s <- PosixPath -> IO FileStatus
PosixF.getSymbolicLinkStatus forall a b. (a -> b) -> a -> b
$ OsPath -> PosixPath
getOsString OsPath
fp
case () of
()
_ | FileStatus -> Bool
PosixF.isRegularFile FileStatus
s -> forall (f :: * -> *) a. Applicative f => a -> f a
pure FileType
File
| FileStatus -> Bool
PosixF.isDirectory FileStatus
s -> forall (f :: * -> *) a. Applicative f => a -> f a
pure FileType
Directory
| FileStatus -> Bool
PosixF.isSymbolicLink FileStatus
s -> do
Either IOException FileStatus
es' <- forall e a. Exception e => IO a -> IO (Either e a)
try forall a b. (a -> b) -> a -> b
$ PosixPath -> IO FileStatus
PosixF.getFileStatus forall a b. (a -> b) -> a -> b
$ OsPath -> PosixPath
getOsString OsPath
fp
case Either IOException FileStatus
es' of
Left (IOException
_ :: IOException) -> forall (f :: * -> *) a. Applicative f => a -> f a
pure FileType
Other
Right FileStatus
s'
| FileStatus -> Bool
PosixF.isRegularFile FileStatus
s' -> forall (f :: * -> *) a. Applicative f => a -> f a
pure FileType
FileSym
| FileStatus -> Bool
PosixF.isDirectory FileStatus
s' -> forall (f :: * -> *) a. Applicative f => a -> f a
pure FileType
DirectorySym
| Bool
otherwise -> forall (f :: * -> *) a. Applicative f => a -> f a
pure FileType
Other
| Bool
otherwise -> forall (f :: * -> *) a. Applicative f => a -> f a
pure FileType
Other
#endif
data FileType
= File
| FileSym
| Directory
| DirectorySym
| Other
deriving (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, 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, 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)