module System.Directory.Internal.Common where
import Prelude ()
import System.Directory.Internal.Prelude
import System.FilePath ((</>), isPathSeparator, isRelative,
pathSeparator, splitDrive, takeDrive)
#ifdef mingw32_HOST_OS
import qualified System.Win32 as Win32
#else
import qualified System.Posix as Posix
#endif
tryIOErrorType :: (IOError -> Bool) -> IO a -> IO (Either IOError a)
tryIOErrorType check action = do
result <- tryIOError action
case result of
Left err -> if check err then return (Left err) else ioError err
Right val -> return (Right val)
specializeErrorString :: String -> (IOError -> Bool) -> IO a -> IO a
specializeErrorString str errType action = do
mx <- tryIOErrorType errType action
case mx of
Left e -> ioError (ioeSetErrorString e str)
Right x -> return x
ioeAddLocation :: IOError -> String -> IOError
ioeAddLocation e loc = do
ioeSetLocation e newLoc
where
newLoc = loc <> if null oldLoc then "" else ":" <> oldLoc
oldLoc = ioeGetLocation e
data FileType = File
| SymbolicLink
| Directory
| DirectoryLink
deriving (Bounded, Enum, Eq, Ord, Read, Show)
fileTypeIsDirectory :: FileType -> Bool
fileTypeIsDirectory Directory = True
fileTypeIsDirectory DirectoryLink = True
fileTypeIsDirectory _ = False
data Permissions
= Permissions
{ readable :: Bool
, writable :: Bool
, executable :: Bool
, searchable :: Bool
} deriving (Eq, Ord, Read, Show)
getCurrentDirectory :: IO FilePath
getCurrentDirectory = (`ioeAddLocation` "getCurrentDirectory") `modifyIOError`
specializeErrorString
"Current working directory no longer exists"
isDoesNotExistError
#ifdef mingw32_HOST_OS
Win32.getCurrentDirectory
#else
Posix.getWorkingDirectory
#endif
prependCurrentDirectory :: FilePath -> IO FilePath
prependCurrentDirectory path =
modifyIOError ((`ioeAddLocation` "prependCurrentDirectory") .
(`ioeSetFileName` path)) $
if isRelative path
then do
cwd <- getCurrentDirectory
let curDrive = takeWhile (not . isPathSeparator) (takeDrive cwd)
let (drive, subpath) = splitDrive path
return . (</> subpath) $
case drive of
_ : _ | (toUpper <$> drive) /= (toUpper <$> curDrive) ->
drive <> [pathSeparator]
_ -> cwd
else return path