{-# OPTIONS_GHC -fglasgow-exts #-} module Main where import Control.Monad import Data.List import Debian.Apt.Methods import Debian.Report import Debian.Repo.SourcesList import Extra.Exit import Extra.HaXml import System.Environment import Text.PrettyPrint.HughesPJ import System.IO -- * main main :: IO () main = do (sourcesAFP, sourcesBFP) <- parseArgs let arch = "i386" -- not actually used for anything right now, could be when binary package list is enabled cacheDir = "." -- FIXME: replace with tempdir later sourcesA <- liftM parseSourcesList $ readFile sourcesAFP sourcesB <- liftM parseSourcesList $ readFile sourcesBFP trumpMap <- trumped (fetch emptyFetchCallbacks []) cacheDir arch sourcesA sourcesB print (showXML "trump.xsl" (trumpedXML trumpMap)) -- * command-line helper functions helpText :: String -> Doc helpText progName = (text "Usage:" <+> text progName <+> text "" <+> text ""$+$ text [] $+$ (fsep $ map text $ words $ "Find all the packages referenced by the second sources.list which trump packages find in the first sources.list.") ) parseArgs :: IO (String, String) parseArgs = do args <- getArgs case args of [dista, distb] -> return (dista, distb) _ -> exitWithHelp helpText