diffing dir...
Thu Sep 23 20:10:56 EDT 2010 Andy Stewart <laz...@gm...>
* Update Gtk2HsSetup.hs in cairo
Ignore-this: deec4b151a66eb2c6499302f89dd3f02
{
hunk ./cairo/Gtk2HsSetup.hs 35
-module Gtk2HsSetup ( gtk2hsUserHooks, getPkgConfigPackages ) where
+module Gtk2HsSetup ( [_$_]
+ gtk2hsUserHooks, [_$_]
+ getPkgConfigPackages, [_$_]
+ checkGtk2hsBuildtools
+ ) where
hunk ./cairo/Gtk2HsSetup.hs 72
- rawSystemProgramConf, rawSystemProgramStdoutConf,
+ rawSystemProgramConf, rawSystemProgramStdoutConf, programName,
hunk ./cairo/Gtk2HsSetup.hs 90
-import System.Directory ( doesFileExist )
+import System.Exit (exitFailure)
+import System.Directory ( doesFileExist, getDirectoryContents, doesDirectoryExist )
hunk ./cairo/Gtk2HsSetup.hs 94
-import Control.Monad (when, unless, filterM)
+import Control.Monad (when, unless, filterM, liftM, forM, forM_)
hunk ./cairo/Gtk2HsSetup.hs 102
-import System.Directory (getDirectoryContents, doesDirectoryExist)
hunk ./cairo/Gtk2HsSetup.hs 110
- confHook simpleUserHooks pd cf >>= return . adjustLocalBuildInfo,
+ (fmap adjustLocalBuildInfo (confHook simpleUserHooks pd cf)),
hunk ./cairo/Gtk2HsSetup.hs 115
- (buildHook simpleUserHooks) pd lbi uh bf,
- copyHook = \pd lbi uh flags -> (copyHook simpleUserHooks) pd lbi uh flags >>
+ buildHook simpleUserHooks pd lbi uh bf,
+ copyHook = \pd lbi uh flags -> copyHook simpleUserHooks pd lbi uh flags >>
hunk ./cairo/Gtk2HsSetup.hs 305
- ++ [opt | opt@('-':c:_) <- (PD.cppOptions bi ++ PD.ccOptions bi), c `elem` "DIU"]
+ ++ [opt | opt@('-':c:_) <- PD.cppOptions bi ++ PD.ccOptions bi, c `elem` "DIU"]
hunk ./cairo/Gtk2HsSetup.hs 315
- mFiles <- mapM (findFileWithExtension' ["chi"] [buildDir lbi])
- (map toFilePath
+ mFiles <- mapM (findFileWithExtension' ["chi"] [buildDir lbi] . toFilePath)
hunk ./cairo/Gtk2HsSetup.hs 321
- )
+ [_$_]
hunk ./cairo/Gtk2HsSetup.hs 337
-typeGenProgram = (simpleProgram "gtk2hsTypeGen")
+typeGenProgram = simpleProgram "gtk2hsTypeGen"
hunk ./cairo/Gtk2HsSetup.hs 340
-signalGenProgram = (simpleProgram "gtk2hsHookGenerator")
+signalGenProgram = simpleProgram "gtk2hsHookGenerator"
hunk ./cairo/Gtk2HsSetup.hs 343
-c2hsLocal = (simpleProgram "gtk2hsC2hs")
+c2hsLocal = simpleProgram "gtk2hsC2hs"
hunk ./cairo/Gtk2HsSetup.hs 376
- (flip mapM_) (filter (\(tag,_) -> "x-types-" `isPrefixOf` tag && "file" `isSuffixOf` tag) xList) $
+ forM_ (filter (\(tag,_) -> "x-types-" `isPrefixOf` tag && "file" `isSuffixOf` tag) xList) $
hunk ./cairo/Gtk2HsSetup.hs 397
- Nothing -> die $ "parsing output of pkg-config --modversion failed"
+ Nothing -> die "parsing output of pkg-config --modversion failed"
hunk ./cairo/Gtk2HsSetup.hs 462
- let findImports acc (('{':'#':xs):xxs) = case (dropWhile ((==) ' ') xs) of
+ let findImports acc (('{':'#':xs):xxs) = case (dropWhile (' ' ==) xs) of
hunk ./cairo/Gtk2HsSetup.hs 464
- case simpleParse (takeWhile ((/=) '#') ys) of
+ case simpleParse (takeWhile ('#' /=) ys) of
hunk ./cairo/Gtk2HsSetup.hs 490
+
+-- Check user whether install gtk2hs-buildtools correctly.
+checkGtk2hsBuildtools :: [String] -> IO ()
+checkGtk2hsBuildtools programs = do
+ programInfos <- mapM (\ name -> do
+ location <- programFindLocation (simpleProgram name) normal
+ return (name, location)
+ ) programs
+ let printError name = do
+ putStrLn $ "Cannot find " ++ name ++ "\n" [_$_]
+ ++ "Please install `gtk2hs-buildtools` first and check that the install directory is in your PATH (e.g. HOME/.cabal/bin)."
+ exitFailure
+ forM_ programInfos $ \ (name, location) ->
+ when (isNothing location) (printError name) [_$_]
hunk ./cairo/Setup.hs 4
-import Gtk2HsSetup ( gtk2hsUserHooks )
+import Gtk2HsSetup ( gtk2hsUserHooks, checkGtk2hsBuildtools )
hunk ./cairo/Setup.hs 7
-main = defaultMainWithHooks gtk2hsUserHooks
+main = do
+ checkGtk2hsBuildtools ["gtk2hsC2hs"]
+ defaultMainWithHooks gtk2hsUserHooks
+ [_$_]
}
|