-------------------------------------------------------------------- -- | -- Module : ComPkg -- Description : Specification/template for the ComPkg installer builder. -- Copyright : (c) Sigbjorn Finne, 2004-2009 -- License : BSD3 -- -- Maintainer : Sigbjorn Finne -- Stability : provisional -- Portability : portable -- -- To create your own installer, you need to supply a Haskell module -- which exports functions and values that together define the -- functionality (and contents) of your package; -- see Base.hs just what those exports are. -- -------------------------------------------------------------------- module ComPkg where import Bamse.Util.Dir import System.FilePath import Bamse.Package import Bamse.PackageUtils import Debug.Trace versionNumber :: String versionNumber = "0.30" libVersion :: String libVersion = "comlib-" ++ versionNumber defaultOutFile :: FilePath defaultOutFile = toMsiFileName libVersion packageName :: String packageName="comLib" pkg :: Package pkg = Package { name = "comlib" , title = "COM support library for GHC-" ++ forGhcVersion , productVersion = "1.0.0.0" , author = "Sigbjorn Finne" , comment = "Version: " ++ versionNumber } webSite :: String webSite = "http://haskell.org/hdirect" bannerBitmap :: InstallEnv -> Maybe FilePath bannerBitmap ienv = Just (lFile (toolDir ienv) "art/banner.bmp") bgroundBitmap :: InstallEnv -> Maybe FilePath bgroundBitmap _ienv = Nothing registry :: [RegEntry] registry = [] features :: [Tree Feature] features = [ Leaf baseFeature ] baseFeatureName :: String baseFeatureName = "comlib" baseFeature :: Feature baseFeature = (baseFeatureName, "COM library for GHC") startMenu :: InstallEnv -> (String, [Shortcut]) startMenu ienv = ("GHC/packages/"++packageName, entries) where entries :: [Shortcut] entries = [ Shortcut "Documentation (HTML)" (lFile (srcDir ienv) "doc\\index.html") "" "Library documentation" (Just (lFile iconDir "html.exe")) 1 "[TARGETDIR]" ] iconDir = toolDir ienv ++ "\\icons" desktopShortcuts :: InstallEnv -> [Shortcut] desktopShortcuts _ienv = [] extensions :: InstallEnv -> [ Extension ] extensions _ienv = [ ] verbs :: [ ( String -- extension , String -- verb , String -- label , String -- arguments ) ] verbs = [] dirTree :: InstallEnv -> IO DirTree dirTree ienv = findFiles ofInterest' (srcDir ienv) where ofInterest' f = if ofInterest f then trace ("including:" ++ f) True else trace ("excluding:" ++ f ++ show (takeDirectory f)) False -- Note: 'path' is prefixed by 'topDir'. ofInterest path = path == srcDir ienv -- || ("System" `elem` splitPath path && not ("tmp" `elem` splitPath path)) || takeFileName path `elem` ["com.pkg", "HScom.o", "doc", "include", "cbits"] || takeFileName path == "doc" || takeFileName (takeDirectory path) == "doc" || takeFileName path == "build" || takeFileName (takeDirectory path) == "build" || takeExtension path `elem` [{-"",-} ".a", ".hi", ".h", ".hs"] || not (emacsCVSMeta path || takeExtension path `elem` [".raw-hs"]) -- By leaving out "", we won't recurse into subdirs. We specially -- check for the toplevel directory, as it needs to be present. -- (takeExtension file `elem` [""{-directory-}, ".dll", ".hs", ".lhs", ".idl", ".h", ".pkg"]) emacsCVSMeta f = case takeFileName f of '#':_ -> True '.':'#':_ -> True "CVS" -> True ".cvsignore" -> True _ -> not (null f) && last f == '~' distFileMap :: Maybe (InstallEnv -> FilePath -> Maybe FilePath) distFileMap = Nothing featureMap :: Maybe (FilePath -> FeatureName) featureMap = Nothing license :: InstallEnv -> Maybe FilePath license _ienv = Nothing userRegistration :: Bool userRegistration = False defaultInstallFolder :: Maybe String defaultInstallFolder = Just $ "[WindowsVolume]ghc\\packages\\ghc-"++forGhcVersion ++ "\\" ++ packageName ++ "\\" forGhcVersion :: String forGhcVersion = "6.6.1" finalMessage :: Maybe String finalMessage = Nothing userInstall :: Bool userInstall = False services :: [Service] services = [] ghcPackageInfo :: Maybe GhcPackage ghcPackageInfo = Just $ GhcPackage { ghc_packageName = "Com" -- ToDo: allow 'most-recent' compiler to be used. , ghc_forVersion = forGhcVersion , ghc_packageFile = Just "com.pkg" , ghc_pkgCmdLine = Just (unwords [ def "hd_lib" "" , def "hd_imp" "build" , def "hd_inc" "include" ]) } where tgt "" = "\"[TARGETDIR]build\"" tgt s = "\"[TARGETDIR]" ++ s ++ "\"" def s v = '-':'D':s ++ '=':tgt v nestedInstalls :: [(FilePath,Maybe String)] nestedInstalls = [] cabalPackageInfo :: Maybe CabalPackage cabalPackageInfo = Nothing assemblies :: [Assembly] assemblies = []