module System.Sifflet.Paths (findDataFile, copyLibFile, readLibFile) where import Control.Monad (unless) import System.Directory (doesFileExist, copyFile) import System.FilePath (replaceDirectory) -- Cabal-generated paths module tells where a datafile -- _should_ be, but not necessarily where it is, -- if the installed files have been relocated. import Paths_sifflet_lib (getDataFileName) import Graphics.UI.Sifflet.Types (VPUI(..)) import Graphics.UI.Sifflet.GtkUtil (showErrorMessage) -- | Try to find the original of a datafile that is part of the -- sifflet library. -- These are usually files like sifflet.scm or sifflet.py that provide -- Sifflet support for the target language when exporting. -- First try the directory where Cabal would have installed data files. -- This may fail if Sifflet has been installed (or portably installed) -- on Windows into a non-standard location; in that case, also try -- the directory from which sifflet.exe was launched. findDataFile :: VPUI -> FilePath -> IO (Maybe FilePath) findDataFile vpui fileBaseName = do -- path1 is where it should be; -- path2 is where it might be on Windows. path1 <- getDataFileName fileBaseName let path2 = replaceDirectory fileBaseName (vpuiInitialDir vpui) -- There's surely a name for this type of search, -- which simply returns the first item in the list -- for which a predicate `returns` True (m True): search [] = return Nothing search (path:paths) = do fileExists <- doesFileExist path if fileExists then return $ Just path else search paths search [path1, path2] -- | Try to copy a library file (such as sifflet.py or Sifflet.java) -- to the same directory where an export file is being written, -- if it doesn't already exist there. -- Show a warning message if the library file cannot be found. 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 -- | Get the contents of a library file (such as sifflet.scm) -- so you can insert it into the file being exported. -- If the file cannot be found, display an error message and -- return the empty string. 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