-------------------------------------------------------------------- -- | -- Module : Happy -- Description : Specification/template for the Happy 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 Happy where import Data.List import Bamse.Util.Dir import System.FilePath import Bamse.Package import Bamse.PackageUtils pkgName :: String pkgName = "happy" pkgVersion :: String pkgVersion = "1.18.3" pkgDoc :: String pkgDoc = "doc\\happy-"++pkgVersion++"\\index.html" defaultOutFile :: FilePath defaultOutFile = toMsiFileName pkgName pkg :: Package pkg = Package { name = pkgName , title = pkgName , productVersion = "1.18.3.0" , author = "Simon Marlow" , comment = unwords [pkgName, "Version", pkgVersion] } webSite :: String webSite = "http://haskell.org/happy" bannerBitmap :: InstallEnv -> Maybe FilePath bannerBitmap ienv = Just (lFile (toolDir ienv) "art/banner.bmp") bgroundBitmap :: InstallEnv -> Maybe FilePath bgroundBitmap _ienv = Nothing {- The installer needs to record the following in the Registry: * the location of the installation directory. -- used by the Cryptol interpreter to set up the Cryptol import path when invoking GHC. * Cryptol as a Hugs 'project' -- requires the addition of a (large) set of directories to the search path. -} registry :: [RegEntry] registry = [] features :: [Tree Feature] features = [ Leaf baseFeature ] baseFeatureName :: String baseFeatureName = pkgName baseFeature :: Feature baseFeature = (baseFeatureName, pkgName ++ '-':pkgVersion) startMenu :: InstallEnv -> (String, [Shortcut]) startMenu ienv = (pkgName, entries) where iconDir = lFile (toolDir ienv) "icons" entries :: [Shortcut] entries = [ Shortcut "Happy user manual" (lFile (srcDir ienv) pkgDoc) "" "Happy documentation" (Just (lFile iconDir "html.exe")) 1 "[TARGETDIR]" ] 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 == "CVS") distFileMap :: Maybe (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]"++pkgName++'\\':pkgName++'-':pkgVersion finalMessage :: Maybe String finalMessage = Nothing userInstall :: Bool userInstall = False services :: [Service] services = [] ghcPackageInfo :: Maybe GhcPackage ghcPackageInfo = Nothing cabalPackageInfo :: Maybe CabalPackage cabalPackageInfo = Nothing nestedInstalls :: [(FilePath, Maybe String)] nestedInstalls = [] assemblies :: [Assembly] assemblies = []