-------------------------------------------------------------------- -- | -- Module : Hugs98 -- Description : Specification/template for the Hugs98 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 Hugs98 where import Bamse.Package import Bamse.PackageUtils import Util.Dir import Util.Path hugsVersion = "Nov 2003" versionString = "Nov2003" defaultOutFile = toMsiFileName "hugs98-Nov2003" pkg :: Package pkg = Package { name = "Hugs98" , title = "Hugs98 " ++ versionString , productVersion = "1.0.0.0" , author = "Sigbjorn Finne" , comment = "Hugs98 " ++ versionString } webSite :: String webSite = "http://haskell.org/hugs" bannerBitmap :: InstallEnv -> Maybe FilePath bannerBitmap ienv = Just (lFile (toolDir ienv) "art/banner.bmp") bgroundBitmap :: InstallEnv -> Maybe FilePath bgroundBitmap _ienv = Nothing registry :: [RegEntry] registry = haskellImpl "Hugs" hugsVersion [ ("InstallDir", "[TARGETDIR]") ] features :: [Tree Feature] features = [ Leaf baseFeature ] baseFeatureName :: FeatureName baseFeatureName = "Hugs98" baseFeature :: Feature baseFeature = (baseFeatureName, "Hugs98 interpreter") startMenu :: InstallEnv -> (String, [Shortcut]) startMenu ienv = ("Hugs98/"++versionString, entries) where 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 "WinHugs (Haskell98 mode)" (lFile topDir "winhugs.exe") "+98" "WinHugs interpreter (Haskell98 mode)" (Just (lFile iconDir "hugs.exe")) 1 "[TARGETDIR]" , Shortcut "WinHugs (Hugs mode)" (lFile topDir "winhugs.exe") "-98" "Hugs98 interpreter (Hugs mode)" (Just (lFile iconDir "hugs.exe")) 1 "[TARGETDIR]" , Shortcut "Hugs98 Readme" (lFile topDir "Readme.txt") "" "Hugs98 Readme" (Just (lFile iconDir "txt.exe")) 1 "[TARGETDIR]" , Shortcut "Hugs98 documentation (HTML)" (lFile topDir "docs\\users_guide\\users-guide.html") "" "Hugs98 documentation (HTML)" (Just (lFile iconDir "html.exe")) 1 "[TARGETDIR]" , Shortcut "Hugs98 documentation (PDF)" (lFile topDir "docs\\users_guide\\users_guide.pdf") "" "Hugs98 documentation (PDF)" (Just (lFile iconDir "pdf.exe")) 1 "[TARGETDIR]" , Shortcut "Original Hugs98 user manual (PDF)" (lFile topDir "docs\\hugs.pdf") "" "Hugs98 documentation (PDF)" (Just (lFile iconDir "pdf.exe")) 1 "[TARGETDIR]" , Shortcut "Original Hugs98 user manual (HTML)" (lFile topDir "docs\\hugsman\\index.html") "" "Hugs98 documentation (HTML)" (Just (lFile iconDir "html.exe")) 1 "[TARGETDIR]" , Shortcut "Original Hugs98 user manual (HTMLHelp)" (lFile topDir "docs\\hugs98.chm") "" "Hugs98 documentation (HTMLHelp)" (Just (lFile iconDir "chm.exe")) 1 "[TARGETDIR]" , Shortcut "Original Hugs98 user manual (WinHelp)" (lFile topDir "docs\\hugs.hlp") "" "Hugs98 documentation (WinHelp)" (Just (lFile iconDir "hlp.exe")) 1 "[TARGETDIR]" ] topDir = srcDir ienv iconDir = lFile (toolDir ienv) "icons" desktopShortcuts :: InstallEnv -> [Shortcut] desktopShortcuts _ienv = [] extensions :: InstallEnv -> [ Extension ] extensions ienv = [ hsExt "hs" , hsExt "lhs" ] where hsExt = haskellExtension interp (srcDir ienv) (toolDir ienv) interp = lFile (srcDir ienv) "hugs.exe" verbs :: [ ( String -- extension , String -- verb , String -- label , String -- arguments ) ] verbs = [ ( "lhs" , "open" , "&Open" , "\"%1\"" ) , ( "lhs" , "open2" , "Open with (Hugs exts mode)" , "-98 \"%1\"" ) , ( "hs" , "open" , "&Open" , "\"%1\"" ) , ( "hs" , "open2" , "Open with (Hugs exts mode)" , "-98 \"%1\"" ) ] dirTree :: InstallEnv -> IO DirTree dirTree ienv = findFiles ofInterest (srcDir ienv) where topDir = srcDir ienv ofInterest file = not (ignoreDir file) && not (last file == '~') && not (baseName file == "CVS") ignoreDir file = file `elem` ignore_dirs ignore_dirs = map (\ x -> lFile topDir x) $ [ "src", "tests" , "bugs", "fptools" , "libs", "dotnet" , "tools", "lib" , "docs\\users_guide_src" ] distFileMap :: Maybe (FilePath -> Maybe FilePath) distFileMap = Nothing featureMap :: Maybe (FilePath -> FeatureName) featureMap = Nothing license :: InstallEnv -> Maybe FilePath license _ = Nothing userRegistration :: Bool userRegistration = False defaultInstallFolder :: Maybe String defaultInstallFolder = Nothing finalMessage :: Maybe String finalMessage = Just "Please remember to add [TARGETDIR] to your PATH." userInstall :: Bool userInstall = True services :: [Service] services = [] ghcPackageInfo :: Maybe GhcPackage ghcPackageInfo = Nothing nestedInstalls = []