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 = ".lambdabot"
stateDir :: LB FilePath
stateDir = do
output <- getConfig outputDir
b <- io $ doesDirectoryExist output
if b then return output else homeDir
homeDir :: LB FilePath
homeDir = do
output <- getConfig outputDir
home <- io getHomeDirectory
return $ home </> lambdabot </> output
findLBFileForReading :: FilePath -> LB (Maybe FilePath)
findLBFileForReading f = do
state <- stateDir
home <- homeDir
output <- getConfig outputDir
rodir <- getConfig dataDir
findFirstFile [state </> f, home </> f, rodir </> output </> f]
findLBFileForWriting :: FilePath -> LB FilePath
findLBFileForWriting f = do
state <- stateDir
io $ createDirectoryIfMissing True state
success <- io $ doesDirectoryExist state
when (not success) $ fail $ concat ["Unable to create directory ", state]
return $ state </> f
findFirstFile :: [FilePath] -> LB (Maybe FilePath)
findFirstFile [] = return Nothing
findFirstFile (path:ps) = do
b <- io $ doesFileExist path
if b then return (Just path) else findFirstFile ps
{-# DEPRECATED findLBFile
"Use `findLBFileForReading` or `findLBFileForWriting` instead" #-}
findLBFile :: FilePath -> LB (Maybe String)
findLBFile f = do
state <- stateDir
home <- homeDir
findFirstFile [state </> f, home </> f]
findOrCreateLBFile :: FilePath -> LB String
findOrCreateLBFile f = do
outFile <- findLBFileForWriting f
b <- io $ doesFileExist outFile
when (not b) $ do
b <- findLBFileForReading f
case b of
Nothing -> io $ writeFile outFile ""
Just roFile -> io $ copyFile roFile outFile
return outFile