Skip to content

Instantly share code, notes, and snippets.

@LeifW
Created July 6, 2015 07:13
Show Gist options
  • Select an option

  • Save LeifW/632e119d09ea0ee574f5 to your computer and use it in GitHub Desktop.

Select an option

Save LeifW/632e119d09ea0ee574f5 to your computer and use it in GitHub Desktop.
Compare version in Stackage-nightly and habs
module Compare where
import PkgDB (readDb, pkgName, pkgVersion)
import Distribution.Version (versionBranch)
import qualified Data.Map.Strict as Map
import Data.Map.Strict (Map)
import Data.List.Split (splitOn)
import Data.Bifunctor (bimap)
import Control.Arrow ((&&&))
splitNameVer :: String -> (String, String)
splitNameVer line = bimap init (drop 2) $ span (/= '=') line
markTable :: (String, ([Int], [Int])) -> String
markTable (a, (b, c)) = "| " ++ a ++ " | " ++ stringVersion b ++ " | " ++ stringVersion c ++ " |"
stringVersion :: [Int] -> String
stringVersion = init . foldr (\i b -> show i ++ '.':b) ""
stackage :: IO (Map String [Int])
stackage = do
f <- readFile "cabal.config"
let stringMap = fmap init $ Map.filter (not . null) $ Map.fromList $ fmap splitNameVer $ lines f
return $ fmap (map read . splitOn ".") stringMap
habs :: IO (Map String [Int])
habs = do
db <- readDb "cblrepo.db"
return $ Map.fromList $ map (pkgName &&& versionBranch . pkgVersion) db
main :: IO ()
main = do
stack <- stackage
h <- habs
print $ length $ Map.difference stack h
print $ length $ Map.difference h stack
let both = Map.intersectionWith (,) stack h
let differences = Map.filter (\(a, b) -> a /= b) both
let (stackageWins, habsWins) = Map.partition (\(a, b) -> a > b) differences
putStrLn "| package | stackage version | habs version |"
putStrLn "| ------- | ---------------- | ------------ |"
mapM_ (putStrLn . markTable) $ Map.toList $ stackageWins
putStrLn "| package | stackage version | habs version |"
putStrLn "| ------- | ---------------- | ------------ |"
mapM_ (putStrLn . markTable) $ Map.toList $ habsWins
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment