module Lambdabot.File
( stateDir
, findLBFileForReading
, findLBFileForWriting
, findOrCreateLBFile
, findLBFile
, outputDir
) where
import Lambdabot.Config
import Lambdabot.Config.Core
import Lambdabot.Monad
import Lambdabot.Util
import Control.Applicative
import Control.Monad
import System.Directory
import System.FilePath
lambdabot :: FilePath
lambdabot :: FilePath
lambdabot = FilePath
".lambdabot"
stateDir :: LB FilePath
stateDir :: LB FilePath
stateDir = do
FilePath
output <- Config FilePath -> LB FilePath
forall (m :: * -> *) a. MonadConfig m => Config a -> m a
getConfig Config FilePath
outputDir
Bool
b <- IO Bool -> LB Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (IO Bool -> LB Bool) -> IO Bool -> LB Bool
forall a b. (a -> b) -> a -> b
$ FilePath -> IO Bool
doesDirectoryExist FilePath
output
if Bool
b then FilePath -> LB FilePath
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
output else LB FilePath
homeDir
homeDir :: LB FilePath
homeDir :: LB FilePath
homeDir = do
FilePath
output <- Config FilePath -> LB FilePath
forall (m :: * -> *) a. MonadConfig m => Config a -> m a
getConfig Config FilePath
outputDir
FilePath
home <- IO FilePath -> LB FilePath
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io IO FilePath
getHomeDirectory
FilePath -> LB FilePath
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath -> LB FilePath) -> FilePath -> LB FilePath
forall a b. (a -> b) -> a -> b
$ FilePath
home FilePath -> FilePath -> FilePath
</> FilePath
lambdabot FilePath -> FilePath -> FilePath
</> FilePath
output
findLBFileForReading :: FilePath -> LB (Maybe FilePath)
findLBFileForReading :: FilePath -> LB (Maybe FilePath)
findLBFileForReading FilePath
f = do
FilePath
state <- LB FilePath
stateDir
FilePath
home <- LB FilePath
homeDir
FilePath
output <- Config FilePath -> LB FilePath
forall (m :: * -> *) a. MonadConfig m => Config a -> m a
getConfig Config FilePath
outputDir
FilePath
rodir <- Config FilePath -> LB FilePath
forall (m :: * -> *) a. MonadConfig m => Config a -> m a
getConfig Config FilePath
dataDir
[FilePath] -> LB (Maybe FilePath)
findFirstFile [FilePath
state FilePath -> FilePath -> FilePath
</> FilePath
f, FilePath
home FilePath -> FilePath -> FilePath
</> FilePath
f, FilePath
rodir FilePath -> FilePath -> FilePath
</> FilePath
output FilePath -> FilePath -> FilePath
</> FilePath
f]
findLBFileForWriting :: FilePath -> LB FilePath
findLBFileForWriting :: FilePath -> LB FilePath
findLBFileForWriting FilePath
f = do
FilePath
state <- LB FilePath
stateDir
IO () -> LB ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (IO () -> LB ()) -> IO () -> LB ()
forall a b. (a -> b) -> a -> b
$ Bool -> FilePath -> IO ()
createDirectoryIfMissing Bool
True FilePath
state
Bool
success <- IO Bool -> LB Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (IO Bool -> LB Bool) -> IO Bool -> LB Bool
forall a b. (a -> b) -> a -> b
$ FilePath -> IO Bool
doesDirectoryExist FilePath
state
Bool -> LB () -> LB ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not Bool
success) (LB () -> LB ()) -> LB () -> LB ()
forall a b. (a -> b) -> a -> b
$ FilePath -> LB ()
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail (FilePath -> LB ()) -> FilePath -> LB ()
forall a b. (a -> b) -> a -> b
$ [FilePath] -> FilePath
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [FilePath
"Unable to create directory ", FilePath
state]
FilePath -> LB FilePath
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath -> LB FilePath) -> FilePath -> LB FilePath
forall a b. (a -> b) -> a -> b
$ FilePath
state FilePath -> FilePath -> FilePath
</> FilePath
f
findFirstFile :: [FilePath] -> LB (Maybe FilePath)
findFirstFile :: [FilePath] -> LB (Maybe FilePath)
findFirstFile [] = Maybe FilePath -> LB (Maybe FilePath)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FilePath
forall a. Maybe a
Nothing
findFirstFile (FilePath
path:[FilePath]
ps) = do
Bool
b <- IO Bool -> LB Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (IO Bool -> LB Bool) -> IO Bool -> LB Bool
forall a b. (a -> b) -> a -> b
$ FilePath -> IO Bool
doesFileExist FilePath
path
if Bool
b then Maybe FilePath -> LB (Maybe FilePath)
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just FilePath
path) else [FilePath] -> LB (Maybe FilePath)
findFirstFile [FilePath]
ps
{-# DEPRECATED findLBFile
"Use `findLBFileForReading` or `findLBFileForWriting` instead" #-}
findLBFile :: FilePath -> LB (Maybe String)
findLBFile :: FilePath -> LB (Maybe FilePath)
findLBFile FilePath
f = do
FilePath
state <- LB FilePath
stateDir
FilePath
home <- LB FilePath
homeDir
[FilePath] -> LB (Maybe FilePath)
findFirstFile [FilePath
state FilePath -> FilePath -> FilePath
</> FilePath
f, FilePath
home FilePath -> FilePath -> FilePath
</> FilePath
f]
findOrCreateLBFile :: FilePath -> LB String
findOrCreateLBFile :: FilePath -> LB FilePath
findOrCreateLBFile FilePath
f = do
FilePath
outFile <- FilePath -> LB FilePath
findLBFileForWriting FilePath
f
Bool
b <- IO Bool -> LB Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (IO Bool -> LB Bool) -> IO Bool -> LB Bool
forall a b. (a -> b) -> a -> b
$ FilePath -> IO Bool
doesFileExist FilePath
outFile
Bool -> LB () -> LB ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not Bool
b) (LB () -> LB ()) -> LB () -> LB ()
forall a b. (a -> b) -> a -> b
$ do
Maybe FilePath
b <- FilePath -> LB (Maybe FilePath)
findLBFileForReading FilePath
f
case Maybe FilePath
b of
Maybe FilePath
Nothing -> IO () -> LB ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (IO () -> LB ()) -> IO () -> LB ()
forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath -> IO ()
writeFile FilePath
outFile FilePath
""
Just FilePath
roFile -> IO () -> LB ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (IO () -> LB ()) -> IO () -> LB ()
forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath -> IO ()
copyFile FilePath
roFile FilePath
outFile
FilePath -> LB FilePath
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
outFile