{-# LANGUAGE DeriveDataTypeable #-}
module Hledger.Data.RawOptions (
RawOpts,
setopt,
setboolopt,
inRawOpts,
boolopt,
choiceopt,
collectopts,
stringopt,
maybestringopt,
listofstringopt,
intopt,
maybeintopt,
maybecharopt
)
where
import Data.Maybe
import Data.Data
import Data.Default
import Safe
import Hledger.Utils
newtype RawOpts = RawOpts { unRawOpts :: [(String,String)] }
deriving (Show, Data, Typeable)
instance Default RawOpts where def = RawOpts []
overRawOpts f = RawOpts . f . unRawOpts
setopt :: String -> String -> RawOpts -> RawOpts
setopt name val = overRawOpts (++ [(name, val)])
setboolopt :: String -> RawOpts -> RawOpts
setboolopt name = overRawOpts (++ [(name,"")])
inRawOpts :: String -> RawOpts -> Bool
inRawOpts name = isJust . lookup name . unRawOpts
boolopt :: String -> RawOpts -> Bool
boolopt = inRawOpts
choiceopt :: (String -> Maybe a)
-> RawOpts
-> Maybe a
choiceopt f = lastMay . collectopts (f . fst)
collectopts :: ((String, String) -> Maybe a) -> RawOpts -> [a]
collectopts f = mapMaybe f . unRawOpts
maybestringopt :: String -> RawOpts -> Maybe String
maybestringopt name = lookup name . reverse . unRawOpts
stringopt :: String -> RawOpts -> String
stringopt name = fromMaybe "" . maybestringopt name
maybecharopt :: String -> RawOpts -> Maybe Char
maybecharopt name (RawOpts rawopts) = lookup name rawopts >>= headMay
listofstringopt :: String -> RawOpts -> [String]
listofstringopt name (RawOpts rawopts) = [v | (k,v) <- rawopts, k==name]
maybeintopt :: String -> RawOpts -> Maybe Int
maybeintopt name rawopts =
let ms = maybestringopt name rawopts in
case ms of Nothing -> Nothing
Just s -> Just $ readDef (usageError $ "could not parse "++name++" number: "++s) s
intopt :: String -> RawOpts -> Int
intopt name = fromMaybe 0 . maybeintopt name