hledger-lib-1.17.1: Core data types, parsers and functionality for the hledger accounting tools

Safe HaskellNone
LanguageHaskell2010

Hledger.Data.RawOptions

Description

hledger's cmdargs modes parse command-line arguments to an intermediate format, RawOpts (an association list), rather than a fixed ADT like CliOpts. This allows the modes and flags to be reused more easily by hledger commands/scripts in this and other packages.

Synopsis

Documentation

data RawOpts Source #

The result of running cmdargs: an association list of option names to string values.

Instances
Data RawOpts Source # 
Instance details

Defined in Hledger.Data.RawOptions

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RawOpts -> c RawOpts #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RawOpts #

toConstr :: RawOpts -> Constr #

dataTypeOf :: RawOpts -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RawOpts) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RawOpts) #

gmapT :: (forall b. Data b => b -> b) -> RawOpts -> RawOpts #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RawOpts -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RawOpts -> r #

gmapQ :: (forall d. Data d => d -> u) -> RawOpts -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RawOpts -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RawOpts -> m RawOpts #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RawOpts -> m RawOpts #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RawOpts -> m RawOpts #

Show RawOpts Source # 
Instance details

Defined in Hledger.Data.RawOptions

Default RawOpts Source # 
Instance details

Defined in Hledger.Data.RawOptions

Methods

def :: RawOpts #

inRawOpts :: String -> RawOpts -> Bool Source #

Is the named option present ?

choiceopt Source #

Arguments

:: (String -> Maybe a)

"parser" that returns Just value for valid choice

-> RawOpts

actual options where to look for flag

-> Maybe a

exclusive choice among those returned as Just from "parser"

From a list of RawOpts, get the last one (ie the right-most on the command line) for which the given predicate returns a Just value. Useful for exclusive choice flags like --daily|--weekly|--quarterly...

>>> choiceopt Just (RawOpts [("a",""), ("b",""), ("c","")])
Just "c"
>>> choiceopt (const Nothing) (RawOpts [("a","")])
Nothing
>>> choiceopt readMay (RawOpts [("LT",""),("EQ",""),("Neither","")]) :: Maybe Ordering
Just EQ

collectopts :: ((String, String) -> Maybe a) -> RawOpts -> [a] Source #

Collects processed and filtered list of options preserving their order

>>> collectopts (const Nothing) (RawOpts [("x","")])
[]
>>> collectopts Just (RawOpts [("a",""),("b","")])
[("a",""),("b","")]