-------------------------------------------------------------------- -- | -- Module : Hugs98Net -- Description : Specification/template for the public Hugs98.NET 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 Hugs98Net where import Bamse.Package import Bamse.PackageUtils import Util.Dir import Util.Path versionNumber = "March2003" defaultOutFile = "hugs98-net-March2003.msi" packageDir = "hugs98-net" pkg :: Package pkg = Package { name = "Hugs98.NET" , title = "Hugs98 for .NET" , productVersion = "1.0.0.0" , author = "Sigbjorn Finne" , comment = "Hugs98 for .NET " ++ versionNumber } webSite :: String webSite = "http://galois.com/~sof/hugs98.net/" bannerBitmap :: InstallEnv -> Maybe FilePath bannerBitmap ienv = Just (lFile (toolDir ienv) "art/banner.bmp") bgroundBitmap :: InstallEnv -> Maybe FilePath bgroundBitmap _ienv = Nothing registry :: [RegEntry] registry = haskellImpl "Hugs98.Net" "March 2002" [ ("InstallDir", "[TARGETDIR]") ] features :: [Tree Feature] features = [ Leaf baseFeature ] baseFeatureName :: FeatureName baseFeatureName = "Hugs98.NET" baseFeature :: Feature baseFeature = (baseFeatureName, "Hugs98.NET") startMenu :: InstallEnv -> (String, [Shortcut]) startMenu ienv = ("Hugs98.NET", entries) where topDir = srcDir ienv iconDir = lFile (toolDir ienv) "icons" entries :: [Shortcut] entries = [ Shortcut "Hugs (Haskell98 mode)" (lFile topDir "hugs.exe") "+98" "Hugs98 interpreter (Haskell98 mode)" (Just (lFile iconDir "hsx.exe")) 1 "[TARGETDIR]" , Shortcut "Hugs (Hugs mode)" (lFile topDir "hugs.exe") "-98" "Hugs98 interpreter (Hugs mode)" (Just (lFile iconDir "hsx.exe")) 1 "[TARGETDIR]" , Shortcut "Hugs98 Readme" (lFile topDir "Readme.txt") "" "Hugs98 Readme" (Just (lFile iconDir "txt.exe")) 1 "[TARGETDIR]" , Shortcut "Hugs98.Net documentation" (lFile topDir "dotnet\\doc\\dotnet.html") "" "Hugs98.Net documentation" (Just (lFile iconDir "html.exe")) 1 "[TARGETDIR]" ] desktopShortcuts :: InstallEnv -> [Shortcut] desktopShortcuts _ienv = [] -- turn off registration of Hugs98.net specific extensions + verbs. extensions :: InstallEnv -> [ Extension ] extensions _ienv = [ ] verbs :: [ ( String -- extension , String -- verb , String -- label , String -- arguments ) ] verbs = [] dirTree :: InstallEnv -> IO DirTree dirTree ienv = findFiles ofInterest topDir where topDir = srcDir ienv ofInterest file = file /= topDir ++ "\\src" && file /= topDir ++ "\\tests" && file /= topDir ++ "\\demos" && file /= topDir ++ "\\tools" && 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 = Nothing finalMessage :: Maybe String finalMessage = Nothing userInstall :: Bool userInstall = False services :: [ Service ] services = [] ghcPackageInfo :: Maybe GhcPackage ghcPackageInfo = Nothing nestedInstalls = []