module System.IO.B9Extras
( SystemPath (..),
overSystemPath,
resolve,
ensureSystemPath,
ensureDir,
getDirectoryFiles,
prettyPrintToFile,
consult,
ConsultException (..),
randomUUID,
UUID (),
removeIfExists,
)
where
import Control.Exception
import Control.Monad.Except
import Data.Data
import Data.Word
( Word16,
Word32,
)
import System.Directory
import System.FilePath
import System.IO.Error
import System.Random (randomIO)
import Text.Printf
import Text.Read (readEither)
import Text.Show.Pretty (ppShow)
data SystemPath
=
Path FilePath
|
InHomeDir FilePath
|
InB9UserDir FilePath
|
InTempDir FilePath
deriving (Eq, Read, Show, Typeable, Data)
overSystemPath :: (FilePath -> FilePath) -> SystemPath -> SystemPath
overSystemPath f sp =
case sp of
Path p -> Path (f p)
InHomeDir p -> InHomeDir (f p)
InB9UserDir p -> InB9UserDir (f p)
InTempDir p -> InTempDir (f p)
resolve :: MonadIO m => SystemPath -> m FilePath
resolve (Path p) = return p
resolve (InHomeDir p) = liftIO $ do
d <- getHomeDirectory
return $ d </> p
resolve (InB9UserDir p) = liftIO $ do
d <- getAppUserDataDirectory "b9"
return $ d </> p
resolve (InTempDir p) = liftIO $ do
d <- getTemporaryDirectory
return $ d </> p
getDirectoryFiles :: MonadIO m => FilePath -> m [FilePath]
getDirectoryFiles dir = do
entries <- liftIO (getDirectoryContents dir)
fileEntries <- mapM (liftIO . doesFileExist . (dir </>)) entries
return (snd <$> filter fst (fileEntries `zip` entries))
ensureSystemPath :: MonadIO m => SystemPath -> m ()
ensureSystemPath =
resolve >=> liftIO . createDirectoryIfMissing True
ensureDir :: MonadIO m => FilePath -> m ()
ensureDir p = liftIO (createDirectoryIfMissing True $ takeDirectory p)
prettyPrintToFile :: (MonadIO m, Show a) => FilePath -> a -> m ()
prettyPrintToFile f x = do
ensureDir f
liftIO (writeFile f (ppShow x))
consult :: (MonadIO m, Read a) => FilePath -> m a
consult f = liftIO $ do
c <- readFile f
case readEither c of
Left e -> throwIO $ ConsultException f e
Right a -> return a
data ConsultException = ConsultException FilePath String
deriving (Show, Typeable)
instance Exception ConsultException
newtype UUID = UUID (Word32, Word16, Word16, Word16, Word32, Word16)
deriving (Read, Show, Eq, Ord)
instance PrintfArg UUID where
formatArg (UUID (a, b, c, d, e, f)) fmt
| fmtChar (vFmt 'U' fmt) == 'U' =
let str = (printf "%08x-%04x-%04x-%04x-%08x%04x" a b c d e f :: String)
in formatString str (fmt {fmtChar = 's', fmtPrecision = Nothing})
| otherwise =
errorBadFormat $ fmtChar fmt
randomUUID :: MonadIO m => m UUID
randomUUID =
liftIO
( UUID
<$> ( (,,,,,)
<$> randomIO
<*> randomIO
<*> randomIO
<*> randomIO
<*> randomIO
<*> randomIO
)
)
removeIfExists :: FilePath -> IO ()
removeIfExists fileName = removeFile fileName `catch` handleExists
where
handleExists e
| isDoesNotExistError e = return ()
| otherwise = throwIO e