{- Example of how to query for category members, demonstrating the modules, types and steps used to interact with the API: foo$ listCat "Functional programming" ... foo$ -} module Main(main) where import MediaWiki.API.Base import MediaWiki.API.Types ( PageTitle(..) ) import MediaWiki.API import MediaWiki.API.Query.CategoryMembers as CatMem import MediaWiki.API.Query.CategoryMembers.Import as CatMem import Util.GetOpts import System.IO import System.Environment import System.Exit import Control.Monad --import Data.Maybe ( fromMaybe ) import Data.List -- begin option handling data Options = Options { optWiki :: String , optUser :: Maybe String , optPass :: Maybe String , optCat :: Maybe String } nullOptions :: Options nullOptions = Options { optWiki = "http://en.wikipedia.org/w/" , optUser = Nothing , optPass = Nothing , optCat = Nothing } option_descr :: [OptDescr (Options -> Options)] option_descr = [ Option ['u'] ["user"] (ReqArg (\ x o -> o{optUser=Just x}) "USER") "Wiki user name to login as" , Option ['p'] ["pass"] (ReqArg (\ x o -> o{optPass=Just x}) "PASSWORD") "user's password credentials to supply if logging in" , Option ['w'] ["wiki"] (ReqArg (\ x o -> o{optWiki=x}) "WIKI") "the Wiki to access" , Option ['c'] ["cat"] (ReqArg (\ x o -> o{optCat=Just x}) "CAT") "the Wiki category to query for" ] parseOptions :: [String] -> (Options, [String], [String]) parseOptions argv = getOpt2 Permute option_descr argv nullOptions processOptions :: IO (Options, [String]) processOptions = do ls <- getArgs let (opts, ws, es) = parseOptions ls when (not $ null es) $ do hPutStrLn stderr (unlines es) hPutStrLn stderr ("(try '--help' for list of options supported.)") exitFailure return (opts, ws) -- end option handling queryCat :: URLString -> String -> IO [PageTitle] queryCat url catName = queryCat' url catName' req [] where catName' | "Category:" `isPrefixOf` catName = wikify catName | otherwise = "Category:"++wikify catName req = categoryMembersRequest{cmTitle=Just catName'} wikify "" = "" wikify (' ':xs) = '_':wikify xs wikify (x:xs) = x : wikify xs queryCat' :: URLString -> String -> CategoryMembersRequest -> [PageTitle] -> IO [PageTitle] queryCat' url catName cReq acc = do let req = emptyXmlRequest (mkQueryAction (queryPage catName) cReq) mb <- webGetXml CatMem.stringXml url req case mb of Nothing -> fail ("Failed to fetch pages for category " ++ catName ++ " from " ++ url) Just c -> do let acc' = (acc ++ cmPages c) case cmContinue c of Nothing -> return acc' Just x -> queryCat' url catName cReq{cmContinueFrom=Just x} acc' main :: IO () main = do (opts, fs) <- processOptions let url = optWiki opts -- not needed here, but left in to show how to login to a Wiki. case (optUser opts, optPass opts) of (Just u, Just p) -> do x <- loginWiki url u p case x of Nothing -> putStrLn ("Unable to login to: " ++ url) Just lg -> print (lgSuccess lg) _ -> return () case mbCons (optCat opts) fs of [] -> putStrLn "No categories specified!" xs -> mapM_ (showCat url) xs showCat :: URLString -> String -> IO () showCat url cat = do ps <- queryCat url cat putStrLn ("Members of category `" ++ cat ++ "'") mapM_ (putStrLn.toTitle) ps where toTitle pg = ' ':pgTitle pg {- NS prefix seems to be included in title.. case pgNS pg of "" -> pgTitle pg xs -> xs ++ ':':pgTitle pg -} mbCons :: Maybe a -> [a] -> [a] mbCons Nothing xs = xs mbCons (Just x) xs = x:xs