Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Args = Args {}
- emptyArgs :: Args
- parseArgs :: [String] -> Args
- consumeArgument :: Args -> [(Maybe String, Args)]
- consumeOption :: [Dashed] -> Args -> Maybe (String, Args)
- consumeSwitch :: [Dashed] -> Args -> Maybe Args
- recogniseLeftovers :: Args -> Maybe (NonEmpty String)
- data Tomb a
- data Arg
- = ArgBareDoubleDash
- | ArgBareDash
- | ArgDashed !Bool !(NonEmpty Char)
- | ArgPlain !String
- parseArg :: String -> Arg
- renderArg :: Arg -> String
- data Dashed
- = DashedShort !Char
- | DashedLong !(NonEmpty Char)
- renderDashed :: Dashed -> String
- prefixDashed :: String -> Dashed -> Dashed
Public API
An abstraction over '[String]' that makes it easier to implement
consumeArgument
, consumeOption
and consumeSwitch
.
In order to implement folded short dashed options, we need to use tombstones for consumed argumentsn
Instances
Generic Args Source # | |
IsList Args Source # | |
Show Args Source # | |
Eq Args Source # | |
Validity Args Source # | |
Defined in OptEnvConf.Args validate :: Args -> Validation # | |
type Rep Args Source # | |
Defined in OptEnvConf.Args type Rep Args = D1 ('MetaData "Args" "OptEnvConf.Args" "opt-env-conf-0.4.0.5-BgXhiXR3q4fAqP7ng8XQdq" 'False) (C1 ('MetaCons "Args" 'PrefixI 'True) (S1 ('MetaSel ('Just "argsBefore") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Tomb Arg]) :*: S1 ('MetaSel ('Just "argsAfter") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Tomb Arg]))) | |
type Item Args Source # | |
Defined in OptEnvConf.Args |
consumeArgument :: Args -> [(Maybe String, Args)] Source #
Consume a single positional argument.
The result are all possible results
consumeOption :: [Dashed] -> Args -> Maybe (String, Args) Source #
Consume an option.
This supports:
["-f", "foo"]
["--foo", "foo"]
["-df", "foo"]
["--foo=foo"]
["-ffoo"]
consumeSwitch :: [Dashed] -> Args -> Maybe Args Source #
Consume a switch.
This supports:
["-f"]
["--foo"]
["-df"]
Internals
Tombstone for leftovers of consumed arguments
Instances
IsString a => IsString (Tomb a) Source # | |
Defined in OptEnvConf.Args fromString :: String -> Tomb a # | |
Generic (Tomb a) Source # | |
Show a => Show (Tomb a) Source # | |
Eq a => Eq (Tomb a) Source # | |
Validity a => Validity (Tomb a) Source # | |
Defined in OptEnvConf.Args validate :: Tomb a -> Validation # | |
type Rep (Tomb a) Source # | |
Defined in OptEnvConf.Args type Rep (Tomb a) = D1 ('MetaData "Tomb" "OptEnvConf.Args" "opt-env-conf-0.4.0.5-BgXhiXR3q4fAqP7ng8XQdq" 'False) (C1 ('MetaCons "Dead" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Live" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))) |
Instances
IsString Arg Source # | |
Defined in OptEnvConf.Args fromString :: String -> Arg # | |
Generic Arg Source # | |
Show Arg Source # | |
Eq Arg Source # | |
Validity Arg Source # | |
Defined in OptEnvConf.Args validate :: Arg -> Validation # | |
type Rep Arg Source # | |
Defined in OptEnvConf.Args type Rep Arg = D1 ('MetaData "Arg" "OptEnvConf.Args" "opt-env-conf-0.4.0.5-BgXhiXR3q4fAqP7ng8XQdq" 'False) ((C1 ('MetaCons "ArgBareDoubleDash" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ArgBareDash" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ArgDashed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty Char))) :+: C1 ('MetaCons "ArgPlain" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String)))) |
Instances
IsString Dashed Source # | |
Defined in OptEnvConf.Args fromString :: String -> Dashed # | |
Generic Dashed Source # | |
Show Dashed Source # | |
Eq Dashed Source # | |
Validity Dashed Source # | |
Defined in OptEnvConf.Args validate :: Dashed -> Validation # | |
type Rep Dashed Source # | |
Defined in OptEnvConf.Args type Rep Dashed = D1 ('MetaData "Dashed" "OptEnvConf.Args" "opt-env-conf-0.4.0.5-BgXhiXR3q4fAqP7ng8XQdq" 'False) (C1 ('MetaCons "DashedShort" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Char)) :+: C1 ('MetaCons "DashedLong" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty Char)))) |
renderDashed :: Dashed -> String Source #