{- Demonstrates how to use the FriendFeed API by querying for the most recent public entries collected by FriendFeed. The API interaction happens in @showPublic@, with @presentEntries@ outputting the results. The rest is option handling stuff + startup and shutdown code in @main@. Example command-line invocation: foo$ showPublic -u -k \ -s twitter -l 2 showing the last 2 public tweets. where and is your FriendFeed auth setup. Your remote key can be located here: http://friendfeed.com/remotekey However, since this example presently uses public methods not needing authentication, any old username/key combo will work. [Top tip: try leaving them out..] The @-s@ option constrains the entries from a given FriendFeed-supported service. @-l@ limits the length to given size (default: 30.) -} module Main(main) where import FriendFeed.API import FriendFeed.Updates import Util.GetOpts import System.IO import System.Environment import System.Exit import Control.Monad import Control.Concurrent import Data.Maybe ( fromMaybe, isJust ) -- main functions for grabbing public entries + -- presenting them to the user: getUpdateStream :: Maybe String -> Maybe Int -> Bool -> RoomName -> UpdateToken -> FFm [Entry] getUpdateStream mbS mbL isList r tok = (fromMaybe id (fmap forService mbS)) $ (fromMaybe id (fmap withPageSize mbL)) $ (if isList then getUpdatesRoom else (if r == "home" then const getUpdatesHome else getUpdatesList)) r tok (Just 3) presentEntries :: [Entry] -> IO () presentEntries [] = putStrLn "No public entries found!" presentEntries xs = do putStrLn ("Most recent public entries: ") mapM_ presentEntry xs where presentEntry e = putStrLn $ unlines [ "---" , " Title: " ++ entryTitle e , " Link: " ++ entryLink e , " User: " ++ resourceName (entryUser e) ] -- start option handling data Options = Options { optUser :: Maybe String , optKey :: Maybe String , optSize :: Maybe Int , optService :: Maybe String , optRoom :: Maybe String , optList :: Maybe String } nullOptions :: Options nullOptions = Options { optUser = Just "" , optKey = Just "" , optSize = Nothing , optService = Nothing , optRoom = Nothing , optList = Nothing } option_descr :: [OptDescr (Options -> Options)] option_descr = [ Option ['u'] ["user"] (ReqArg (\ x o -> o{optUser=Just x}) "USER") "user name to authenticate as" , Option ['k','p'] ["key","remote-key"] (ReqArg (\ x o -> o{optKey=Just x}) "REMOTE KEY") "the user's FriendFeed remote key" , Option ['l'] ["length"] (ReqArg (\ x o -> o{optSize=Just (read x)}) "SIZE") "fetch SIZE entries" , Option ['s'] ["service"] (ReqArg (\ x o -> o{optService=Just x}) "SERVICE") "limit query to given service name" , Option ['r'] ["room"] (ReqArg (\ x o -> o{optRoom=Just x}) "ROOM") "get continual updates from the given room" , Option ['L'] ["list"] (ReqArg (\ x o -> o{optRoom=Just x}) "LIST") "get continual updates from the given list (personal,favorites,etc.)" ] parseOptions :: [String] -> (Options, [String], [String]) parseOptions argv = getOpt2 Permute option_descr argv nullOptions processOptions :: IO Options processOptions = do ls <- getArgs let (opts, ws, es) = parseOptions ls when (not $ null ws) $ do hPutStrLn stderr "Command-line warnings: " hPutStrLn stderr (unlines ws) when (not $ null es) $ do hPutStrLn stderr (unlines es) hPutStrLn stderr ("(try '--help' for list of options supported.)") exitFailure return opts -- end option handling main :: IO () main = do opts <- processOptions case (optUser opts, optKey opts) of (Just u,Just k) -> do t <- runFF u k (getUpdateInfo) let r = fromMaybe (if isL then ls else "haskell") (optRoom opts) ls = fromMaybe "home" (optRoom opts) isL = isJust (optList opts) loopIt = do putStrLn "sampling.." hFlush stdout xs <- runFF u k (getUpdateStream (optService opts) (optSize opts) isL r (updToken t)) presentEntries xs hFlush stdout threadDelay (fromIntegral (updInterval t * 1000 * 1000)) loopIt loopIt _ -> do putStrLn ("Both user and remote-key options are required.") return ()