-------------------------------------------------------------------- -- | -- Module : HsDotnet -- Description : Specification/template for the hs-dotnet package. -- Copyright : (c) Sigbjorn Finne, 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 HsDotnet where import Bamse.Package import Bamse.PackageUtils versionNumber :: String versionNumber = "0.40" libVersion :: String libVersion = "hs-dotnet-" ++ versionNumber defaultOutFile :: FilePath defaultOutFile = toMsiFileName libVersion packageName :: String packageName="hs-dotnet" pkg :: Package pkg = Package { name = "hs-dotnet" , title = "Haskell .NET interop framework" , productVersion = "1.0.4.0" , author = "Sigbjorn Finne" , comment = "Version: " ++ versionNumber } webSite :: String webSite = "http://haskell.forkio.com/hs-dotnet" bannerBitmap :: InstallEnv -> Maybe FilePath bannerBitmap ienv = Just (lFile (toolDir ienv) "art/banner.bmp") bgroundBitmap :: InstallEnv -> Maybe FilePath bgroundBitmap _ienv = Nothing registry :: [RegEntry] registry = [] features :: [Tree Feature] features = [ Leaf baseFeature ] baseFeatureName :: String baseFeatureName = "hsdotnet" baseFeature :: Feature baseFeature = (baseFeatureName, "hs-dotnet package for GHC") startMenu :: InstallEnv -> (String, [Shortcut]) startMenu ienv = ("Haskell/"++packageName, entries) where entries :: [Shortcut] entries = [ Shortcut "Documentation (HTML)" (lFile (srcDir ienv) "dist\\doc\\html\\hs-dotnet\\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 = do mf <- getManifest (userOpts ienv) findFiles (entryOfInterest ienv mf) topDir where topDir = srcDir ienv 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\\packages\\ghc-"++forGhcVersion ++ "\\" ++ packageName ++ "\\" forGhcVersion :: String forGhcVersion = "6.10.1" finalMessage :: Maybe String finalMessage = Nothing userInstall :: Bool userInstall = False services :: [Service] services = [] nestedInstalls :: [a] nestedInstalls = [] cabalPackageInfo :: Maybe CabalPackage cabalPackageInfo = Just $ CabalPackage { cabal_packageName = "hs-dotnet" -- ToDo: allow 'most-recent' compiler to be used. , cabal_forGhcVersion = forGhcVersion , cabal_packageFile = Just "hs-dotnet.cabal" , cabal_pkgCmdLine = Nothing , cabal_fromSource = True } assemblies :: [Assembly] assemblies = [ bridge_assembly ] -- don't like the duplication of information here (version magic number in installer, bridge and package..!) -- Ditto for the public key..absolutely mental. bridge_assembly :: Assembly bridge_assembly = emptyAssembly { assem_dll = "HsDotnetBridge.dll" , assem_name = "HsDotnetBridge" , assem_manifest = Just "HsDotnetBridge.dll" , assem_version = "0.4.0.0" , assem_publicKey = "31b6626774fafd8b" , assem_win32 = False -- the default, but still. } --- unused stuff until the end: {- OLD and incomplete support for GHC .pkgs: ghcPackageInfo :: Maybe GhcPackage ghcPackageInfo = Just $ GhcPackage { ghc_packageName = "hs-dotnet" -- ToDo: allow 'most-recent' compiler to be used. , ghc_forVersion = forGhcVersion , ghc_packageFile = Just "hs-dotnet.cabal" , ghc_pkgCmdLine = Just (unwords [ "Setup", "install" ]) } where tgt "" = "\"[TARGETDIR]build\"" tgt s = "\"[TARGETDIR]" ++ s ++ "\"" def s v = '-':'D':s ++ '=':tgt v -}