module System.Sifflet.Paths
(findDataFile, copyLibFile, readLibFile)
where
import Control.Monad (unless)
import System.Directory (doesFileExist, copyFile)
import System.FilePath (replaceDirectory)
import Paths_sifflet (getDataFileName)
import Graphics.UI.Sifflet.Types (VPUI(..))
import Graphics.UI.Sifflet.GtkUtil (showErrorMessage)
findDataFile :: VPUI -> FilePath -> IO (Maybe FilePath)
findDataFile vpui fileBaseName = do
path1 <- getDataFileName fileBaseName
let path2 = replaceDirectory fileBaseName (vpuiInitialDir vpui)
search [] = return Nothing
search (path:paths) = do
fileExists <- doesFileExist path
if fileExists
then return $ Just path
else search paths
search [path1, path2]
copyLibFile :: VPUI -> FilePath -> FilePath -> IO ()
copyLibFile vpui libFileName dest = do
mLibFilePath <- findDataFile vpui libFileName
destExists <- doesFileExist dest
unless destExists $ do
case mLibFilePath of
Nothing ->
showErrorMessage $ "Sifflet could not locate the file " ++
libFileName ++ "\n" ++
"Please copy it from the Sifflet installation directory to " ++
"the same directory into which you are saving the export file.\n"
Just libFileSource ->
copyFile libFileSource dest
readLibFile :: VPUI -> FilePath -> FilePath -> IO String
readLibFile vpui libFileName exportFile = do
mLibFilePath <- findDataFile vpui libFileName
case mLibFilePath of
Nothing -> do
showErrorMessage $ "Sifflet could not locate the file " ++
libFileName ++ "\n" ++
"Please find it in the Sifflet installation directory " ++
"and insert its contents into " ++ exportFile ++ "\n"
return ""
Just libFilePath ->
readFile libFilePath