-- -- (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 GaloisPkg where import Util.Dir import Util.Path import Bamse.Package import Bamse.PackageUtils import Debug.Trace import Data.Maybe ( fromJust ) versionNumber = "0.10" libName="galois" libVersion = "galois-" ++ versionNumber defaultOutFile = toMsiFileName libVersion pkg :: Package pkg = Package { name = "GaloisPkg" , title = "Galois Haskell libraries (for GHC 6.2.2)" , productVersion = "1.0.0.0" , author = "Galois Connections, Inc" , comment = "Version: " ++ versionNumber } webSite :: String webSite = "http://galois.com/" bannerBitmap :: InstallEnv -> Maybe FilePath bannerBitmap ienv = Just (lFile (toolDir ienv) "art/banner.bmp") bgroundBitmap :: InstallEnv -> Maybe FilePath bgroundBitmap _ = Nothing registry :: [RegEntry] registry = [] features :: [Tree Feature] features = [ Leaf baseFeature ] baseFeatureName :: String baseFeatureName = "GaloisPkg" baseFeature :: Feature baseFeature = (baseFeatureName, "Galois Haskell library for GHC") startMenu :: InstallEnv -> (String, [Shortcut]) startMenu ienv = ("GHC/ghc-" ++ ghc_forVersion (fromJust ghcPackageInfo) ++ "/libraries/"++libName, entries) where entries :: [Shortcut] entries = [ Shortcut "Documentation (HTML)" (lFile (srcDir ienv) "doc\\index.html") "" "Library documentation" (Just (lFile iconDir "html.exe")) 1 "[TARGETDIR]" ] iconDir = toolDir ienv ++ "\\icons" 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: 'path' is prefixed by 'topDir'. ofInterest path = True {- = path == topDir || baseName path `elem` ["com.pkg", "HScom.o", "doc", "imports", "include"] || baseName path == "doc" || baseName (dirname path) == "doc" || fileSuffix path `elem` [{-"",-} "a", "hi", "h"] -- By leaving out "", we won't recurse into subdirs. We specially -- check for the toplevel directory, as it needs to be present. -- (fileSuffix file `elem` [""{-directory-}, "dll", "hs", "lhs", "idl", "h", "pkg"]) -} distFileMap :: Maybe (FilePath -> Maybe FilePath) distFileMap = Nothing -- Just ( \ f -> Just (toDist f)) where -- Note: 'fn' does not have 'topDir' prepended to it. toDist fn | isHiFile fn = lFile "imports" fn -- store interface files in the imports/ directory, | isDocFile fn = lFile "doc" fn -- doc/html files in doc/ directory, | isHeaderFile fn = lFile "include" fn -- header files in include/, | otherwise = baseName fn -- and everything else in the toplevel directory. 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 = Just $ GhcPackage { ghc_packageName = "galois" -- ToDo: allow 'most-recent' compiler to be used. , ghc_forVersion = "6.2.2" , ghc_packageFile = Just "galois.pkg" , ghc_pkgCmdLine = Just (unwords [ def "impdir" "imports" , def "libdir" "" ]) } where tgt "" = "\"[TARGETDIR]\\\"" tgt s = "\"[TARGETDIR]\\\\" ++ s ++ "\"" def s v = '-':'D':s ++ '=':tgt v nestedInstalls = []