-- Copyright: 2010 Dino Morelli -- License: BSD3 (see LICENSE) -- Author: Dino Morelli {-# LANGUAGE FlexibleContexts #-} module Cltw.Opts ( Options (..) , parseOpts, usageText ) where import Control.Monad.Error import Data.List import System.Console.GetOpt data Options = Options { optUser :: String , optPassword :: Maybe String , optVerbosity :: Int , optEchoReqUri :: Bool , optAddNoise :: Bool } deriving Show defaultOptions :: Options defaultOptions = Options { optUser = "" , optPassword = Nothing , optVerbosity = 1 , optEchoReqUri = False , optAddNoise = False } options :: [OptDescr (Options -> Options)] options = [ Option ['u'] ["user"] (ReqArg (\u opts -> opts { optUser = u }) "USER" ) "Username (always required)" , Option ['p'] ["password"] (ReqArg (\u opts -> opts { optPassword = Just u }) "PASSWORD" ) "Password for calls requiring authentication" , Option ['v'] ["verbosity"] (ReqArg (\v opts -> opts { optVerbosity = read v }) "NUM") "Verbosity: 0, 1 (default), 2. Higher is more verbose" , Option ['e'] ["echo-request-uri"] (NoArg (\opts -> opts { optEchoReqUri = True })) "Echo the request URI string sent to Twitter" , Option ['a'] ["add-noise"] (NoArg (\opts -> opts { optAddNoise = True })) "Add a 2-character randomly-generated base-36 'noise' string to end of update. Good for repeating yourself, but please exercise restraint" ] commands :: [String] commands = ["followers", "friends", "help", "update"] disambCommand :: (MonadError String m) => String -> m String disambCommand i = case (filtCmds i) commands of [c] -> return c [] -> throwError $ "Unknown command: " ++ i cs -> throwError $ "Ambiguous command, could be one of: " ++ (intercalate " " cs) where filtCmds = filter . isPrefixOf parseOpts :: [String] -> IO (Options, String, [String]) parseOpts argv = do result <- runErrorT $ do (opts, inputCmd, rest) <- case getOpt Permute options argv of (o, (i:r), [] ) -> return (foldl (flip id) defaultOptions o, i, r) (_, [] , [] ) -> throwError $ "No command specified\n\n" ++ usageText (_, _ , errs) -> throwError $ concat errs command <- disambCommand inputCmd when ((optUser opts == "") && (command /= "help")) $ throwError "MUST specify a Twitter account username" return (opts, command, rest) either error return result usageText :: String usageText = (usageInfo header options) ++ "\n" ++ footer where header = init $ unlines [ "Usage: cltw COMMAND [OPTIONS] [COMMAND-SPECIFIC DATA]" , "Twitter API command-line utility" , "" , "Commands:" , "" , " followers -u USER" , " Show people following you" , "" , " friends -u USER" , " Show people whom you are following" , " Verbosity applies to followers/friends output like this:" , " -v 0 -> " , " -v 1 -> " , "" , " update -u USER -p PASSWORD STATUS_TEXT" , " Post a status update" , "" , " help" , " This help text" , "" , "Options:" ] footer = init $ unlines [ "This is a tool for performing some Twitter API functions from the command line." , "" , "What kinds of things can you do?" , "" , "Keep a list of people you are following:" , " $ cltw fr -u stimpy | sort > some/file" , "" , "Check to see if somebody specific is following you:" , " $ cltw fo -u stimpy | grep somebodyontwitter" , "" , "Post an update from a script or cron job:" , " $ cltw update -u stimpy -p spumco \"My message to the world\"" , "" , "Don't get crazy with scripts though, Twitter frowns on spam and so do your followers!" , "" , "Version 1.1.4 Dino Morelli " ]