4r/app/Cli.hs

59 lines
1.5 KiB
Haskell

{-# LANGUAGE Strict #-}
module Cli ( Options(..)
, Choice(..)
, optsParser
, choiceParser
, optsInfo
, getOpts
) where
import Relude
import Prelude (foldl1)
import Options.Applicative
-- TODO: add debug
data Options = Options
{ offline :: Bool
, noAnsi :: Bool
, columns :: Maybe Integer
, choice :: Choice
}
deriving stock (Show)
optsParser :: Parser Options
optsParser =
Options <$> switch (long "offline" <> short 'N' <> help "only access cache")
<*> switch (long "no-ansi" <> short 'A' <> help "disable ANSI codes")
<*> (Just <$> option auto (metavar "COLUMNS_NUMBER" <> long "columns" <> short 'c' <> help "number of columns")
<|> pure Nothing)
<*> choiceParser
data Choice = GetSections
| GetTopics
| GetTopic {topic_id :: Integer}
deriving stock (Show)
choiceParser :: Parser Choice
choiceParser = foldl1 (<|>)
[ subparser
(command "ss" (info
(pure GetSections)
(progDesc "Request list of sections")))
, subparser
(command "ts" (info
(pure GetTopics)
(progDesc "Request list of topics")))
, subparser
(command "t" (info
(GetTopic <$> argument auto (metavar "TOPIC_ID"))
(progDesc "Request a topic")))
]
optsInfo :: ParserInfo Options
optsInfo = info (optsParser <**> helper) mempty
getOpts :: IO Options
getOpts = execParser optsInfo