-------------------------------------------------------------------- -- | -- Module : SOE -- Description : Specification/template for the SOE 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. -- -- [Having Haskell as the only 'specification language' for packages -- is not a goal. ] -------------------------------------------------------------------- module SOE where import Bamse.Util.Dir import Bamse.Package import Bamse.PackageUtils defaultOutFile :: FilePath defaultOutFile = "SOE.msi" pkg :: Package pkg = Package { name = "SOE" , title = "School of Expression Software" , productVersion = "1.0.0.0" , author = "Paul Hudak" , comment = "Software accompanying textbook" } webSite :: String webSite = "http://haskell.org/soe" bannerBitmap :: InstallEnv -> Maybe FilePath bannerBitmap ienv = Just (lFile (toolDir ienv) "soe/banner.bmp") bgroundBitmap :: InstallEnv -> Maybe FilePath bgroundBitmap ienv = Just (lFile (toolDir ienv) "art/bground2.bmp") registry :: [RegEntry] registry = haskellProject "SOE" [ hugsPath "[TARGETDIR]src;[TARGETDIR]graphics\\lib\\win32;[TARGETDIR]haskore\\src" ] features :: [Tree Feature] features = [ Leaf baseFeature ] baseFeature :: Feature baseFeature = ("SOE", "School of Expression") startMenu :: InstallEnv -> (String, [Shortcut]) startMenu ienv = ("School of Expression", entries) where iconDir = lFile (toolDir ienv) "icons" entries :: [Shortcut] entries = [ Shortcut "Source code" (lFile (srcDir ienv) "src\\Code.html") "" "Example code" (Just (lFile iconDir "html.exe")) 1 "[TARGETDIR]src" ] 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 = do fs <- findFiles ofInterest (srcDir ienv ++ "\\soelib") return fs where ofInterest file = not (last file == '~') license :: InstallEnv -> Maybe FilePath license _ienv = Nothing -- Just "c:\\src\\soelib\\license.rtf" userRegistration :: Bool userRegistration = False defaultInstallFolder :: Maybe String defaultInstallFolder = Nothing distFileMap :: Maybe (InstallEnv -> 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 nestedInstalls :: [(FilePath,Maybe String)] nestedInstalls = [] cabalPackageInfo :: Maybe CabalPackage cabalPackageInfo = Nothing assemblies :: [Assembly] assemblies = []