{- System.Installer : Installer wrapper for Haskell applications Copyright (C) 2007 Matthew Sackman This library is free software; you can redistribute it and/or modify it under the terms of the GNU Lesser General Public License as published by the Free Software Foundation; either version 2.1 of the License, or (at your option) any later version. This library is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser General Public License for more details. You should have received a copy of the GNU Lesser General Public License along with this library; if not, write to the Free Software Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -} -- | This module allows you to include any file into a module during -- compilation. You can then write out the file at run time. -- -- Expected use is via the Template Haskell splicing syntax. E.g. -- -- @ -- $(installBinariesFunc \"installMyFiles\" -- [(\"FileOne\", \"\/foo\/bar\/fileOne.txt\"), -- (\"FileTwo\", \"\/foo\/bar\/fileTwo.txt\"), -- (\"Three\", \"\/foo\/baz\/thirdFile.qux\") -- ]) -- @ -- -- This will cause an enumeration ADT to be defined as: -- -- @ -- data Installer_installMyFiles = -- Installer_installMyFiles_FileOne -- | Installer_installMyFiles_FileTwo -- | Installer_installMyFiles_Three -- @ -- -- with instances for Enum, Eq, Ord and Show. The install for Show -- will return the @fst@ element of the tuple in the list passed to -- 'installBinariesFunc'. A function called @installMyFiles@ will -- also be defined of type -- @Installer_installMyFiles -> FilePath -> IO ()@. Calling this -- will cause the file content to be written out to the filepath. -- If the filepath provided is a directory, then the file will be -- created within that directory with the same name as the leaf of -- the path in the @snd@ elem of the tuples passed to -- 'installBinariesFunc'. -- -- Note that the files written out are not set executable so you -- must correct file permissions yourself. -- Note that the current implementation is now reasonably -- efficient. However, either use -fvia-C which will take care of all -- compilation for you (but will be slow) or use -fasm which will -- probably fail at the linking stage. Compile the generated .c files -- and manually link together to complete the installation. On any -- non-trivial sized file, you may need to increase GHC's stack with -- @+RTS -K32M -RTS@ to avoid stack overflows. module System.Installer (installBinariesFunc ) where import System.IO import qualified System.Installer.TH as TH import System.Installer.Foreign import Language.Haskell.TH.Syntax installBinariesFunc :: String -> [(String, FilePath)] -> Q [Dec] installBinariesFunc funcName binaries = do { binariesWithTmp <- runIO (convertFilesToCHeaders funcName binaries) ; importDecls <- mapM (TH.makeImportDecl funcName) binariesWithTmp ; func <- TH.makeInstallFunc funcName clauses ; dataDecls <- TH.makeDataDecls funcName binaries ; return $ (concat importDecls) ++ (func : dataDecls) } where clauses = map (TH.makeInstallFuncCase funcName) binaries convertFilesToCHeaders :: String -> [(String, FilePath)] -> IO [(String, FilePath, FilePath)] convertFilesToCHeaders _ [] = return [] convertFilesToCHeaders funcName ((clauseName, filePath):rest) = do { result <- convertFilesToCHeaders funcName rest ; tmpFileName <- convertFileToCHeader filePath clauseName' ; return $ (clauseName, filePath, tmpFileName):result } where clauseName' = "installer_" ++ funcName ++ "_" ++ clauseName