module Main where import qualified Data.Map as M import Distribution.Hackage.DB import Distribution.Text (simpleParse) import Prelude import qualified Prelude as P (map) import System.Console.ANSI main = do db <- readHackage input <- getContents let ls = lines input mapM_ (highlightOutdated db) ls -- | Take an individual line of output and see if it looks like a -- package identifier (/i.e./ @foo-0.3.2@). If so, compare it to -- the latest version on Hackage, and highlight it if the version -- differs (in red if the version is older than the latest on -- Hackage, or cyan if newer), also printing the version of the -- latest Hackage release in blue. highlightOutdated :: Hackage -> String -> IO () highlightOutdated db s = -- try to parse this line as a package identifier (like foo-1.3.2) case simpleParse s of Nothing -> putStrLn s Just pkgId -> -- look up this package name in the Hackage DB case (M.lookup (getPkgName pkgId) db) of Nothing -> putStrLn s Just versions -> do -- get the latest version and compare it to the stated version let latest = maximum . P.map fst . M.assocs $ versions case compare (pkgVersion pkgId) latest of EQ -> putStrLn s LT -> doHighlight s latest Red -- show outdated versions in red GT -> doHighlight s latest Cyan -- show newer versions in cyan -- | Output a package name highlighted in a given color, along with -- another version in blue. doHighlight :: String -> Version -> Color -> IO () doHighlight s latest color = do setSGR [SetColor Foreground Vivid color] putStr s setSGR [] putStr " (" setSGR [SetColor Foreground Vivid Blue] putStr (showVersion latest) setSGR [] putStrLn ")" getPkgName :: PackageIdentifier -> String getPkgName pkgId = case pkgName pkgId of PackageName name -> name