-- -- (c) 2007, Galois, Inc. -- -- To create a package, you need to define a module -- which exports information and functions that together -- define the functionality (and contents) of your package. -- -- [Having Haskell as the only 'specification language' for packages -- is not a goal. ] -- -- Installer definition for the HaskellDirect Hugs libraries. -- module HDirectLib where import Util.Dir import Util.Path import Bamse.Package import Bamse.PackageUtils libVersion = "hdirect-lib-0.19-hugsDec2001" versionNumber = "0.19" defaultOutFile = toMsiFileName libVersion pkg :: Package pkg = Package { name = "HDirectLib" , title = "HDirect COM library for Hugs" , 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 = haskellProject "HDirect" [ hugsPath "[TARGETDIR]" ] features :: [Tree Feature] features = [ Leaf baseFeature ] baseFeatureName :: String baseFeatureName = "HDirect" baseFeature :: Feature baseFeature = (baseFeatureName, "HaskellDirect") startMenu :: InstallEnv -> (String, [Shortcut]) startMenu _ienv = ("HDirect", []) -- i.e., no menu entry 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 -- Note: the file is also the name of the directory ofInterest file = (fileSuffix file `elem` [""{-directory-}, "dll", "hs", "lhs", "idl", "h"]) 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 = Nothing -- Just "c:\\ghc\\ghc-5.04" finalMessage :: Maybe String finalMessage = Nothing userInstall :: Bool userInstall = False services :: [Service] services = [] ghcPackageInfo :: Maybe GhcPackage ghcPackageInfo = Nothing nestedInstalls = []