{-
    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.
--
--    The module works by, at compile time, reading in the files
--    specified and converting them to C files with a header. These
--    files will be stored in a directory called @hinstaller-tmp@ under
--    the same leaf name as the original. Then, the module calls a C
--    compiler by invoking the process @cc@ which must exist. Finally,
--    the names of the files must be passed to the linker. With GHC, use
--    @-optl hinstaller-tmp\//file/.o@ where /file/ is the name of the
--    file you're including. Repeat for each file.
--
--    In order to clean up this @hinstaller-tmp@ directory, the module
--    exports a function 'cabalCleanHInstallerDir'. To use this, modify
--    your @Setup.hs@ along the lines of the following:
--
-- >  #!/usr/bin/env runghc
-- >
-- >  import Distribution.Simple
-- >  import System.Installer
-- >
-- >  main = defaultMainWithHooks myHooks
-- >
-- >  myHooks :: UserHooks
-- >  myHooks = defaultUserHooks { postBuild = cabalCleanHInstallerDir }
--
--    Then, once the build is complete, the directory will be cleaned up.
--    With Cabal, use the @ld-options@ field to pass in the names of
--    compiled C files: @ld-options: hinstaller-tmp\//file/.o@
module System.Installer 
    (installBinariesFunc,
     cabalCleanHInstallerDir
    )
    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
                              (convertFilesToC 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

convertFilesToC :: String -> [(String, FilePath)] ->
                          IO [(String, FilePath, FilePath)]
convertFilesToC _ [] = return []
convertFilesToC funcName ((clauseName, filePath):rest)
    = do { result <- convertFilesToC funcName rest
         ; tmpFileName <- convertFileToC filePath clauseName'
         ; return $ (clauseName, filePath, tmpFileName):result
         }
    where
      clauseName' = "installer_" ++ funcName ++ "_" ++ clauseName