-------------------------------------------------------------------- -- | -- Module : Greencard -- Description : Specification/template for the Greencard 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 Greencard where import Bamse.Util.Dir import Bamse.Package import Bamse.PackageUtils import System.FilePath gcVersion :: String gcVersion = "gc-"++versionNumber versionNumber :: String versionNumber = "2.05" defaultOutFile :: FilePath defaultOutFile = toMsiFileName gcVersion pkg :: Package pkg = Package { name = "GreenCard" , title = "GreenCard - Haskell FFI preprocessor" , productVersion = "1.0.0.0" , author = "Sigbjorn Finne" , comment = "Version: " ++ versionNumber } webSite :: String webSite = "http://haskell.org/greencard" bannerBitmap :: InstallEnv -> Maybe FilePath bannerBitmap ienv = Just (lFile (toolDir ienv) "art/banner.bmp") bgroundBitmap :: InstallEnv -> Maybe FilePath bgroundBitmap _ienv = Nothing registry :: [RegEntry] registry = haskellProject "GreenCard" [ hugsPath "[TARGETDIR]\\lib\\hugs" ] features :: [Tree Feature] features = [ Leaf baseFeature ] baseFeatureName :: String baseFeatureName = "GreenCard" baseFeature :: Feature baseFeature = (baseFeatureName, "GreenCard") startMenu :: InstallEnv -> (String, [Shortcut]) startMenu ienv = ("GreenCard", entries) where entries :: [Shortcut] entries = [ Shortcut "GreenCard Readme" (lFile (srcDir ienv) "README.txt") "" "GHC Readme" (Just (lFile iconDir "txt.exe")) 1 "[TARGETDIR]" , Shortcut "User guide" (lFile (srcDir ienv) "doc\\green-card\\greencard.html") "" "User guide" (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 file = not (last file == '~') && not (takeFileName file == gcVersion) && not (takeFileName file == "green-card.junk") && not (takeFileName file == "distrib") && not (takeFileName file == "CVS") && not (takeFileName file == "mk") && (not (takeExtension file == ".o") || (takeFileName file == "HSgreencard.o")) && (not (takeExtension file == ".hi") || (takeFileName file == "StdDIS.hi")) 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 = Nothing finalMessage :: Maybe String finalMessage = Just "Please remember to add [TARGETDIR] to your PATH." userInstall :: Bool userInstall = False services :: [Service] services = [] ghcPackageInfo :: Maybe GhcPackage ghcPackageInfo = Nothing nestedInstalls :: [(FilePath,Maybe String)] nestedInstalls = [] cabalPackageInfo :: Maybe CabalPackage cabalPackageInfo = Nothing assemblies :: [Assembly] assemblies = []