module Options where import System.Console.GetOpt import Data.Maybe(fromMaybe) data LimitType = NumLimit Integer -- limit feed size to given number | NoLimit -- don't limit | KeepLimit -- limit feed size to current size (during add-item) deriving Show data DescType = DescFile FilePath -- means -Dfoo | DescCLI String -- means -dFoo | DescSTDIN -- means --pipe-mode deriving Show data Options = Options { optVerbose :: Bool , optShowVersion :: Bool , optPreDesc :: Bool , optOutput :: Maybe FilePath , optInput :: Maybe FilePath , optTmpDir :: FilePath , optDescription :: DescType , optLimit :: LimitType , optTitle :: String , optLink :: Maybe String } deriving Show defaultOptions :: Options defaultOptions = Options { optVerbose = False , optShowVersion = False , optPreDesc = False , optOutput = Nothing , optTmpDir = "/tmp" , optInput = Nothing , optLimit = NoLimit , optTitle = "" , optDescription = DescCLI "" , optLink = Nothing } options :: [OptDescr (Options -> Options)] options = [ Option ['v'] ["verbose"] (NoArg (\ opts -> opts { optVerbose = True })) "chatty output on stderr" , Option ['V','?'] ["version"] (NoArg (\ opts -> opts { optShowVersion = True })) "show version number" , Option ['p'] ["pre"] (NoArg (\ opts -> opts { optPreDesc = True })) "add
 tag to description for html readers"

 , Option [] ["pipe-mode"]
     (NoArg (\ opts -> opts { optDescription = DescSTDIN }))
     "description pipe mode, suitable for piping commands into, or -d or -D"

 , Option ['D']     ["description-file"]
     (ReqArg ((\ f opts -> opts { optDescription = DescFile f })) "FILE")
     "read the description from given file. or -d or --pipe-mode"

 , Option ['d']     ["description"]
         (ReqArg (\ t opts -> opts { optDescription = DescCLI t }) "description")
         "feed item description from command line. or -D or --pipe-mode"

 , Option ['o']     ["output"]
     (ReqArg ((\ f opts -> opts { optOutput = Just f })) "FILE")
     "output to this file, or -u"

 , Option []     ["tmp"]
     (ReqArg ((\ f opts -> opts { optTmpDir = f })) "FILE")
     "directory for temporary files; defaults to /tmp"

 , Option ['u']     ["update-file"]
    (ReqArg ((\ f opts -> opts { optInput = Just f
                               , optOutput = Just f })) "FILE")
    "update-file FILE"
 , Option []     ["limit"]
    (OptArg ((\ m opts -> opts { optLimit = 
                                   case m of
                                     Nothing -> KeepLimit
                                     Just l  -> NumLimit (fromMaybe (error ("--limit= expecting number, got " ++ show l)) (readInteger l))
                               }))
            "NUM")
    "limit=NUM"
 , Option ['i']     ["input"]
     (ReqArg ((\ f opts -> opts { optInput = Just f })) "FILE")
     "input FILE"
 , Option ['l']     ["link"]
     (ReqArg ((\ f opts -> opts { optLink = Just f })) "URL")
     "link http://foo.com"
 , Option ['t']     ["title"]
         (ReqArg (\ t opts -> opts { optTitle = t }) "title")
         "feed item title"

 ]

readInteger :: String -> Maybe Integer
readInteger s =
  case reads s of
    [(n, "")] -> Just n
    _         -> Nothing

parseOpts :: [String] -> IO (Options, [String])
parseOpts argv =
   case getOpt Permute options argv of
      (o,n,[]  ) -> return (foldl (flip id) defaultOptions o, n)
      (_,_,errs) -> ioError (userError (concat errs ++ usageInfo header options))
  where header = "Usage: ic [OPTION...] files..."