Skip to content

Commit

Permalink
Clean up here and there
Browse files Browse the repository at this point in the history
Signed-off-by: Alexander Berntsen <alexander@plaimi.net>
  • Loading branch information
Alexander Berntsen committed May 29, 2014
1 parent 9f0d1c7 commit b1514ad
Show file tree
Hide file tree
Showing 4 changed files with 14 additions and 17 deletions.
13 changes: 5 additions & 8 deletions Distribution/Gentoo/GHC.hs
Expand Up @@ -119,7 +119,7 @@ readConf = ghcLibDir >>= confFiles >>= foldM addConf Map.empty
-- Add this .conf file to the Map
addConf :: ConfMap -> FilePath -> IO ConfMap
addConf cmp conf = do cnts <- BS.unpack `fmap` BS.readFile conf
case (reads cnts) of
case reads cnts of
[] -> return cmp
-- ebuilds that have CABAL_CORE_LIB_GHC_PV set
-- for this version of GHC will have a .conf
Expand Down Expand Up @@ -150,9 +150,7 @@ oldGhcPkgs v =
-- It would be nice to do this, but we can't assume
-- some crazy user hasn't deleted one of these dirs
-- libFronts' <- filterM doesDirectoryExist libFronts
pkgs <- liftM notGHC
$ checkLibDirs v thisGhc' libFronts
return pkgs
liftM notGHC $ checkLibDirs v thisGhc' libFronts

-- Find packages installed by other versions of GHC in this possible
-- library directory.
Expand All @@ -163,7 +161,7 @@ checkLibDirs v thisGhc libDirs =
where
wanted dir = isValid dir && (not . isInvalid) dir

isValid dir = any (\ldir -> isGhcLibDir ldir dir) libDirs
isValid dir = any (`isGhcLibDir` dir) libDirs

-- Invalid if it's this GHC
isInvalid fp = fp == thisGhc || BS.isPrefixOf (thisGhc `BS.snoc` pathSeparator) fp
Expand Down Expand Up @@ -222,6 +220,5 @@ getBroken = liftM (mapMaybe simpleParse . words)
allInstalledPackages :: IO [Package]
allInstalledPackages = do libDir <- ghcLibDir
let libDir' = BS.pack libDir
pkgs <- liftM notGHC
$ pkgsHaveContent $ hasDirMatching (==libDir')
return pkgs
liftM notGHC $ pkgsHaveContent
$ hasDirMatching (==libDir')
4 changes: 2 additions & 2 deletions Distribution/Gentoo/Packages.hs
Expand Up @@ -59,7 +59,7 @@ ghcPkg = Package "dev-lang" "ghc" Nothing

-- Return all packages that are not a version of GHC.
notGHC :: [Package] -> [Package]
notGHC = filter (\p -> isNot ghcPkg p)
notGHC = filter (isNot ghcPkg)
where
isNot p1 = not . samePackageAs p1

Expand Down Expand Up @@ -182,7 +182,7 @@ haveFiles :: [FilePath] -> IO [Package]
haveFiles fps = pkgsHaveContent p
where
fps' = S.fromList $ map BS.pack fps
p = hasObjMatching (\fp -> S.member fp fps')
p = hasObjMatching (`S.member` fps')

-- Find which packages have Content information that matches the
-- provided predicate; to be used with the searching predicates
Expand Down
4 changes: 2 additions & 2 deletions Distribution/Gentoo/PkgManager.hs
Expand Up @@ -43,7 +43,7 @@ data PkgManager = Portage
-- defined, if it is unknown then it won't be used.
defaultPM :: IO PkgManager
defaultPM = do eDPM <- lookup "PACKAGE_MANAGER" `fmap` getEnvironment
let dPM = maybe defaultPMName id eDPM
let dPM = fromMaybe defaultPMName eDPM
mPM = dPM `M.lookup` pmNameMap
return $ fromMaybe knownDef mPM
where
Expand Down Expand Up @@ -77,7 +77,7 @@ nameOfPM pm = pmNameMap' M.! pm
-- | Choose the appropriate PM from the textual representation; throws
-- an error if that PM isn't known.
choosePM :: String -> PkgManager
choosePM pm = maybe (InvalidPM pm) id $ pm' `M.lookup` pmNameMap
choosePM pm = fromMaybe (InvalidPM pm) $ pm' `M.lookup` pmNameMap
where
pm' = map toLower pm

Expand Down
10 changes: 5 additions & 5 deletions Main.hs
Expand Up @@ -23,7 +23,7 @@ import qualified Data.Set as Set
import qualified Paths_haskell_updater as Paths(version)
import System.Console.GetOpt
import System.Environment(getArgs, getProgName)
import System.Exit(ExitCode(..), exitWith)
import System.Exit(ExitCode(..), exitSuccess, exitWith)
import System.IO(hPutStrLn, stderr)
import Control.Monad(liftM, unless)
import System.Process(rawSystem)
Expand Down Expand Up @@ -62,7 +62,7 @@ combineAllActions = emptyElse defaultAction (foldl1' combineActions)
-- Note that it's safe (at the moment at least) to assume that when
-- the lower of one is a Build that they're both build.
combineActions :: Action -> Action -> Action
combineActions a1 a2 = case (a1 `min` a2) of
combineActions a1 a2 = case a1 `min` a2 of
Help -> Help
Version -> Version
Build{} -> Build $ targets a1 `Set.union` targets a2
Expand Down Expand Up @@ -143,7 +143,7 @@ data WithCmd = RunOnly
runCmd :: WithCmd -> String -> [String] -> IO a
runCmd mode cmd args = case mode of
RunOnly -> runCommand cmd args
PrintOnly -> putStrLn cmd_line >> exitWith (ExitSuccess)
PrintOnly -> putStrLn cmd_line >> exitSuccess
PrintAndRun -> putStrLn cmd_line >> runCommand cmd args
where cmd_line = unwords (cmd:args)

Expand Down Expand Up @@ -250,7 +250,7 @@ options =
"Print this help message."
]
where
pmList = unlines . map ((++) " * ") $ definedPMs
pmList = unlines . map (" * " ++) $ definedPMs
defPM = "The last valid value of PM specified is chosen.\n\
\The default package manager is: " ++ defaultPMName ++ ",\n\
\which can be overriden with the \"PACKAGE_MANAGER\"\n\
Expand Down Expand Up @@ -297,7 +297,7 @@ systemInfo v rm = do ver <- ghcVersion

success :: Verbosity -> String -> IO a
success v msg = do say v msg
exitWith ExitSuccess
exitSuccess

die :: String -> IO a
die msg = do putErrLn ("ERROR: " ++ msg)
Expand Down

0 comments on commit b1514ad

Please sign in to comment.