-------------------------------------------------------------------- -- | -- Module : Cryptol -- Description : Specification/template for the Cryptol 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 Cryptol where import Bamse.Package import Bamse.PackageUtils import Bamse.Util.Dir ( DirTree, findFiles ) import Bamse.Util.List ( concatWith ) import System.FilePath pkgName, pkgVersion :: String pkgName = "Cryptol" pkgVersion = expandString "$" -- what to output the MSI as if no -o option is given. defaultOutFile :: FilePath defaultOutFile = toMsiFileName (pkgName ++ '-':pkgVersion) -- 'information summary stream' data bundled up together. pkg :: Package pkg = Package { name = pkgName , title = pkgName ++ ", version " ++ pkgVersion , productVersion = "1.0.0.0" , author = "Galois Connections, Inc." , comment = unwords [pkgName, "Version", pkgVersion] } webSite :: String webSite = "http://www.cryptol.net/" bannerBitmap :: InstallEnv -> Maybe FilePath bannerBitmap ienv = Just (lFile (toolDir ienv) "art/banner3.bmp") bgroundBitmap :: InstallEnv -> Maybe FilePath bgroundBitmap ienv = Just (lFile (toolDir ienv) "art/bground2.bmp") {- The installer needs to record the following in the Registry: * the location of the installation directory. -- used by the Cryptol interpreter to set up the Cryptol import path when invoking GHC. * Cryptol as a Hugs 'project' -- requires the addition of a (large) set of directories to the search path. -} registry :: [RegEntry] registry = cryptolSettings ++ haskellProject "Cryptol" [ ("hugsPath", (sepBy ';' [ tgt "src\\lib\\hugs" , tgt "src\\lib\\parsec" , tgt "src\\CSP\\lib" , tgt "src\\CSP\\lib\\hugs" , tgt "src\\lib\\misc" , tgt "src\\CSP\\Cryptol" ])) ] ++ -- ToDo: verify that this isn't required with Dec'01 of Hugs. -- (i.e., Hugs has had an upper limit on the length of 'hugsPath'.) haskellProject "CryptolExtras" [ ("hugsPath", (sepBy ';' [ tgt "src\\CSP\\Cryptol\\win32" , tgt "src\\lib\\misc\\win32" ])) ] where sepBy ch ls = concatWith ch ls tgt = ("[TARGETDIR]"++) cryptolSettings :: [RegEntry] cryptolSettings = -- ToDo: have the interpreter create these entries on-the-fly, if missing. -- => drop these entries. [ RegEntry "HKCU" "Software" (CreateKey False) , RegEntry "HKCU" "Software\\Cryptol" (CreateKey True) , RegEntry "HKCU" "Software\\Cryptol" (CreateName (Just "Options") "") ] baseFeatureName :: String baseFeatureName = pkgName baseFeature :: Feature baseFeature = (baseFeatureName, pkgName ++ '-':pkgVersion) features :: [Tree Feature] features = [ Leaf baseFeature ] {- , Leaf ("Test", "The test feature") , Node ("ParentTest", "A parent test feature") [ Leaf ("Child1", "A child feature") , Leaf ("Child2", "Another child feature") ] ] -} startMenu :: InstallEnv -> (String, [Shortcut]) startMenu ienv = (pkgName, shortcuts ienv) shortcuts :: InstallEnv -> [Shortcut] shortcuts ienv = [ Shortcut "Cryptol interpreter" (lFile (srcDir ienv) "cryptol.exe") "" "Cryptol interpreter" (Just (lFile iconDir "cry.exe")) 1 "[TARGETDIR]" {- Example of how to specify directory shortcuts, the second arg giving the top-directory-relative directory name + assigning it the standard folder icon. , Shortcut "Cryptol test directory" "tests" "" "Cryptol test directory" (Just (lFile iconDir "folder.exe")) 1 "[TARGETDIR]" -} ] where iconDir = lFile (toolDir ienv) "icons" desktopShortcuts :: InstallEnv -> [Shortcut] desktopShortcuts ienv = shortcuts ienv extensions :: InstallEnv -> [ Extension ] extensions ienv = [ cryptolExtension (srcDir ienv) (toolDir ienv) "cry" ] cryptolExtension :: FilePath -> FilePath -> String -> Extension cryptolExtension topDir tDir ext = ( "CryptolFile" , lFile topDir "cryptol.exe" , lFile iconDir "cry.exe" , ext ) where iconDir = lFile tDir "icons" verbs :: [ ( String -- extension , String -- verb , String -- label , String -- arguments ) ] verbs = [ ( "cry" , "open" , "&Open" , "\"%1\"" ) ] license :: InstallEnv -> Maybe FilePath license _ienv = Nothing userRegistration :: Bool userRegistration = False defaultInstallFolder :: Maybe String defaultInstallFolder = Nothing dirTree :: InstallEnv -> IO DirTree dirTree ienv = findFiles ofInterest (srcDir ienv) where ofInterest file = not (last file == '~') && not (takeFileName file == "CVS") && not (takeFileName file == "bin") {- Older experiment in specifying a dist tree which differed from the source tree. Keep around as it might prove useful later on. dirTree :: FilePath -> IO DirTree dirTree = do aes <- findFilesRel ofInterest (topDir ++ "\\build\\share\\galois\\AES") ex <- findFilesRel ofInterest (topDir ++ "\\build\\Examples") lib <- findFilesRel ofInterest (topDir ++ "\\build\\lib") csp <- findFilesRel ofInterest (topDir ++ "\\CSP") hs <- findFilesRel ofInterest (topDir ++ "\\Haskell") libr <- findFilesRel ofInterest (topDir ++ "\\lib") mk <- findFilesRel ofInterest (topDir ++ "\\mk") tst <- findFilesRel ofInterest (topDir ++ "\\CSP\\Cryptol\\tests") let dataTree = aes docTree = [ File (topDir ++ "\\CSP\\Documentation\\CheatSheet.doc") , File (topDir ++ "\\CryptolIntro.ps") , File (topDir ++ "\\CryptolIntro.tex") ] dslTree = [ File (topDir ++ "\\DSL\\Perms.hs") , File (topDir ++ "\\DSL\\Permute.hs") ] incTree = [ File "CryPrim.c" , File "CryPrim.o" , File "cryptol.h" ] srcTree = unwrap csp ++ [ Directory "Haskell*cryptol\\Haskell" (unwrap hs) , Directory "lib*cryptol\\lib" (unwrap libr) , Directory "mk*cryptol\\mk" (unwrap mk) , File (topDir ++ "\\Makefile") , File (topDir ++ "\\README") ] return $ Directory "cryptol" [ File (lFile topDir "CSP\\Cryptol\\cryptol.exe") , Directory "data*cryptol\\build\\data" [dataTree] , Directory "doc" docTree , Directory "DSL" dslTree , Directory "examples*cryptol\\build" [ex] , Directory "include*cryptol\\CSP\\Cryptol\\include" incTree , Directory "lib*cryptol\\build" [lib] , Directory "src*cryptol\\CSP" srcTree , Directory "tests*cryptol\\CSP\\Cryptol\\tests" (unwrap tst) ] where unwrap (Directory _ xs) = xs iSuffixes = [ "hs", "lhs", "c", "h", "doc", "mk", "tex"] topDir = srcDir ++ "\\cryptol" ofInterest file = let base = baseName file suf = fileSuffix file in not (last file `elem` "~#") && not (base == "CVS") && not ( ".#" `isPrefixOf` base) && not ( "." `isPrefixOf` base) && (null suf || suf `elem` iSuffixes) -} distFileMap :: Maybe (FilePath -> Maybe FilePath) distFileMap = Nothing -- if provided, a mapping from dist tree filename to the -- the feature it belongs to. If Nothing, all files are -- mapped to the base feature. featureMap :: Maybe (FilePath -> FeatureName) featureMap = Nothing finalMessage :: Maybe String finalMessage = Nothing userInstall :: Bool userInstall = True services :: [Service] services = [] ghcPackageInfo :: Maybe GhcPackage ghcPackageInfo = Nothing cabalPackageInfo :: Maybe CabalPackage cabalPackageInfo = Nothing nestedInstalls :: [(FilePath, Maybe String)] nestedInstalls = [] assemblies :: [Assembly] assemblies = []