-- -- (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. ] module Haddock where import Data.List import Util.Dir import Util.Path import Util.List import Bamse.Package import Bamse.PackageUtils pkgName = "haddock" pkgVersion = "0.7" pkgDoc = "doc\\haddock\\haddock.html" defaultOutFile = toMsiFileName pkgName pkg :: Package pkg = Package { name = pkgName , title = pkgName , productVersion = "0.7" , author = "Simon Marlow" , comment = unwords [pkgName, "Version", pkgVersion] } webSite :: String webSite = "http://haskell.org/haddock" 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 "Haddock user manual" (lFile (srcDir ienv) pkgDoc) "" "Haddock 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 (baseName 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 nestedInstalls = []