-------------------------------------------------------------------- -- | -- Module : GHC -- Description : Specification/template for the GHC installer builder. -- Copyright : (c) Sigbjorn Finne, 2004-2009 -- License : BSD3 -- -- Maintainer : Sigbjorn Finne -- Stability : provisional -- Portability : portable -- -- Template file for (big) GHC installers. -- -- Assumes that you've already created a 'binary-dist' tree -- (and re-jigged it) before invoking the installer builder. -- -- ToDo: -- - make profiling a separate feature. -- - bundle up less-used packages into separate installers. -- -------------------------------------------------------------------- module GHC where import Bamse.Util.Dir import Bamse.Package import Bamse.PackageUtils import System.FilePath -- Start section of version-specific settings: versionNumber :: String versionNumber = "6.6.1" versionStringUser :: String versionStringUser = "version " ++ versionNumber buildNumber :: String buildNumber = "0" ghcVersion :: String ghcVersion = "ghc-" ++ versionNumber -- End section -- default name of output file; used if no -o option is provided. defaultOutFile :: FilePath defaultOutFile = toMsiFileName ghcVersion -- pkg :: Package pkg = Package { name = "GHC-"++versionStringUser , title = "Glasgow Haskell Compiler, " ++ versionStringUser , productVersion = versionNumber ++ '.':buildNumber , author = "Sigbjorn Finne" , comment = "GHC " ++ versionStringUser } webSite :: String webSite = "http://haskell.org/ghc" bannerBitmap :: InstallEnv -> Maybe FilePath bannerBitmap ienv = Just (lFile (toolDir ienv) "art/banner.bmp") bgroundBitmap :: InstallEnv -> Maybe FilePath bgroundBitmap ienv = Just (lFile (toolDir ienv) "art/ghc-background.bmp") registry :: [RegEntry] registry = haskellImpl "GHC" ghcVersion [ ("InstallDir", "[TARGETDIR]") ] features :: [Tree Feature] features = [ Leaf baseFeature ] baseFeatureName :: String baseFeatureName = "GHC" baseFeature :: (String, String) baseFeature = (baseFeatureName, "Glasgow Haskell Compiler") startMenu :: InstallEnv -> (String, [Shortcut]) startMenu ienv = ("GHC/" ++ versionNumber, entries) where entries :: [Shortcut] entries = [ Shortcut "GHCi" (lFile (srcDir ienv) "bin\\ghci.exe") "" "GHC interpreter" (Just (lFile iconDir "hsx2.exe")) 1 "[TARGETDIR]" , Shortcut "GHC Readme" (lFile (srcDir ienv) "README.txt") "" "GHC Readme" (Just (lFile iconDir "txt.exe")) 1 "[TARGETDIR]" , Shortcut "GHC documentation" (lFile (srcDir ienv) "doc\\html\\index.html") "" "GHC documentation" (Just (lFile iconDir "html.exe")) 1 "[TARGETDIR]" , Shortcut "GHC library documentation" (lFile (srcDir ienv) "doc\\html\\libraries\\index.html") "" "GHC lib doc" (Just (lFile iconDir "html.exe")) 1 "[TARGETDIR]" ] iconDir = toolDir ienv ++ "\\icons" desktopShortcuts :: InstallEnv -> [Shortcut] desktopShortcuts _ienv = [] extensions :: InstallEnv -> [ Extension ] extensions ienv = [ hsExt "hs" , hsExt "lhs" ] where hsExt = haskellExtension ghci (srcDir ienv) (toolDir ienv) ghci = lFile (srcDir ienv) "bin\\ghci.exe" verbs :: [ ( String -- extension , String -- verb , String -- label , String -- arguments ) ] verbs = [ ( "lhs" , "open" , "&Open with GHCi" , "\"%1\"" ) , ( "hs" , "open" , "&Open with GHCi" , "\"%1\"" ) ] dirTree :: InstallEnv -> IO DirTree dirTree ienv = findFiles ofInterest (srcDir ienv) where ofInterest file = not (not (null (tail file)) && last file == '~') && not (takeFileName file == "CVS") distFileMap :: Maybe (InstallEnv -> 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]ghc\\"++ghcVersion -- Example of how to use an environment variable: --defaultInstallFolder = Just $ "[%SYSTEMDRIVE]\\ghc\\"++ghcVersion finalMessage :: Maybe String finalMessage = Just "Please remember to add [TARGETDIR]bin to your PATH." 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 = []