-- -- Specification/template for the Bamse tool itself. -- -- (c) 2007, Galois, Inc. -- module Bamse where import Bamse.Package import Bamse.PackageUtils import Util.Dir ( DirTree(..), findFiles ) import Util.Path ( baseName, dirname, fileSuffix ) import Debug.Trace pkgName = "bamse" pkgVersion = "1.0" -- what to output the MSI as if no -o option is given. defaultOutFile = toMsiFileName (pkgName ++ '-':pkgVersion) -- 'information summary stream' data bundled up together. pkg :: Package pkg = Package { name = pkgName , title = pkgName ++ ", version " ++ pkgVersion , productVersion = "1.0.0.0" , author = "Galois, Inc." , comment = unwords [pkgName, "Version", pkgVersion] } webSite :: String webSite = "http://www.galois.com/" bannerBitmap :: InstallEnv -> Maybe FilePath bannerBitmap ienv = Just (lFile (toolDir ienv) "art/banner3.bmp") bgroundBitmap :: InstallEnv -> Maybe FilePath bgroundBitmap ienv = Just (lFile (toolDir ienv) "art/bground2.bmp") registry :: [RegEntry] registry = [] baseFeatureName :: String baseFeatureName = pkgName baseFeature :: Feature baseFeature = (baseFeatureName, pkgName ++ '-':pkgVersion) features :: [Tree Feature] features = [ Leaf baseFeature ] startMenu :: InstallEnv -> (String, [Shortcut]) startMenu ienv = (pkgName, shortcuts ienv) shortcuts :: InstallEnv -> [Shortcut] shortcuts ienv = [ Shortcut "Bamse installer" (lFile (srcDir ienv) "doc/index.html") "" "Bamse installer" (Just (lFile iconDir "html.exe")) 1 "[TARGETDIR]" , Shortcut "Using Bamse" (lFile (srcDir ienv) "doc/using.html") "" "Using bamse" (Just (lFile iconDir "html.exe")) 1 "[TARGETDIR]" , Shortcut "Getting started" (lFile (srcDir ienv) "doc/howto.html") "" "Getting started" (Just (lFile iconDir "html.exe")) 1 "[TARGETDIR]" ] where iconDir = lFile (toolDir ienv) "icons" desktopShortcuts :: InstallEnv -> [Shortcut] desktopShortcuts ienv = [] extensions :: InstallEnv -> [ Extension ] extensions ienv = [] verbs :: [ ( String -- extension , String -- verb , String -- label , String -- arguments ) ] verbs = [] license :: InstallEnv -> Maybe FilePath license ienv = Just (lFile (toolDir ienv) "license.rtf") userRegistration :: Bool userRegistration = False defaultInstallFolder :: Maybe String defaultInstallFolder = Nothing 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 (dirname f)) False ofInterest file = {-trace ("considering: " ++ show (dirname fileRel, fileRel)) $ -} not $ emacsCVSMeta fileRel || fileRel `elem` [ ".cvsignore", "TODO" ] || fileRel `elem` ["out", "output", "packages", "libraries", "soe"] || (dirname fileRel == "." && fileSuffix fileRel == "log") || (dirname fileRel == "." && fileSuffix fileRel == "msi") || (dirname fileRel == "." && fileSuffix fileRel == "exe") || (dirname fileRel == "." && fileSuffix fileRel == "a") || fileSuffix fileRel `elem` ["o", "obj", "hi"] where fileRel = dropDirPrefix (srcDir ienv) file emacsCVSMeta f = case baseName f of '#':_ -> True '.':'#':_ -> True "CVS" -> True _ -> not (null f) && last f == '~' distFileMap :: Maybe (FilePath -> Maybe FilePath) distFileMap = Nothing -- if provided, a mapping from dist tree filename to the -- the feature it belongs to. If Nothing, all files are -- mapped to the base feature. featureMap :: Maybe (FilePath -> FeatureName) featureMap = Nothing finalMessage :: Maybe String finalMessage = Nothing userInstall :: Bool userInstall = True services :: [Service] services = [] ghcPackageInfo :: Maybe GhcPackage ghcPackageInfo = Nothing -- nested installations are supported via sub-storage only. -- i.e., after having built the Bamse installer, you need -- to do the following: -- -- foo$ msidb -d bamse.msi -r com.msi -- foo$ msidb -d bamse.msi -r galois.msi -- -- where 'msidb' is the tool that comes with the MS Platform SDK. -- nestedInstalls :: [(FilePath, Maybe String)] nestedInstalls = [] {- painful to work with, disable. [ ("com.msi", Nothing) , ("galois.msi", Nothing) ] -}