opt-env-conf-0.4.0.5: Settings parsing for Haskell: command-line arguments, environment variables, and configuration values.
Safe HaskellSafe-Inferred
LanguageHaskell2010

OptEnvConf.Args

Synopsis

Public API

data Args Source #

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

Constructors

Args 

Fields

Instances

Instances details
Generic Args Source # 
Instance details

Defined in OptEnvConf.Args

Associated Types

type Rep Args :: Type -> Type #

Methods

from :: Args -> Rep Args x #

to :: Rep Args x -> Args #

IsList Args Source # 
Instance details

Defined in OptEnvConf.Args

Associated Types

type Item Args #

Methods

fromList :: [Item Args] -> Args #

fromListN :: Int -> [Item Args] -> Args #

toList :: Args -> [Item Args] #

Show Args Source # 
Instance details

Defined in OptEnvConf.Args

Methods

showsPrec :: Int -> Args -> ShowS #

show :: Args -> String #

showList :: [Args] -> ShowS #

Eq Args Source # 
Instance details

Defined in OptEnvConf.Args

Methods

(==) :: Args -> Args -> Bool #

(/=) :: Args -> Args -> Bool #

Validity Args Source # 
Instance details

Defined in OptEnvConf.Args

Methods

validate :: Args -> Validation #

type Rep Args Source # 
Instance details

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 # 
Instance details

Defined in OptEnvConf.Args

type Item Args = Tomb Arg

emptyArgs :: Args Source #

Empty list of arguments

parseArgs :: [String] -> Args Source #

Create Args with all-live arguments and cursor at the start.

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

data Tomb a Source #

Tombstone for leftovers of consumed arguments

Constructors

Dead

Consumed

Live a

Unconsumed

Instances

Instances details
IsString a => IsString (Tomb a) Source # 
Instance details

Defined in OptEnvConf.Args

Methods

fromString :: String -> Tomb a #

Generic (Tomb a) Source # 
Instance details

Defined in OptEnvConf.Args

Associated Types

type Rep (Tomb a) :: Type -> Type #

Methods

from :: Tomb a -> Rep (Tomb a) x #

to :: Rep (Tomb a) x -> Tomb a #

Show a => Show (Tomb a) Source # 
Instance details

Defined in OptEnvConf.Args

Methods

showsPrec :: Int -> Tomb a -> ShowS #

show :: Tomb a -> String #

showList :: [Tomb a] -> ShowS #

Eq a => Eq (Tomb a) Source # 
Instance details

Defined in OptEnvConf.Args

Methods

(==) :: Tomb a -> Tomb a -> Bool #

(/=) :: Tomb a -> Tomb a -> Bool #

Validity a => Validity (Tomb a) Source # 
Instance details

Defined in OptEnvConf.Args

Methods

validate :: Tomb a -> Validation #

type Rep (Tomb a) Source # 
Instance details

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)))

data Arg Source #

Instances

Instances details
IsString Arg Source # 
Instance details

Defined in OptEnvConf.Args

Methods

fromString :: String -> Arg #

Generic Arg Source # 
Instance details

Defined in OptEnvConf.Args

Associated Types

type Rep Arg :: Type -> Type #

Methods

from :: Arg -> Rep Arg x #

to :: Rep Arg x -> Arg #

Show Arg Source # 
Instance details

Defined in OptEnvConf.Args

Methods

showsPrec :: Int -> Arg -> ShowS #

show :: Arg -> String #

showList :: [Arg] -> ShowS #

Eq Arg Source # 
Instance details

Defined in OptEnvConf.Args

Methods

(==) :: Arg -> Arg -> Bool #

(/=) :: Arg -> Arg -> Bool #

Validity Arg Source # 
Instance details

Defined in OptEnvConf.Args

Methods

validate :: Arg -> Validation #

type Rep Arg Source # 
Instance details

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))))

data Dashed Source #

Instances

Instances details
IsString Dashed Source # 
Instance details

Defined in OptEnvConf.Args

Methods

fromString :: String -> Dashed #

Generic Dashed Source # 
Instance details

Defined in OptEnvConf.Args

Associated Types

type Rep Dashed :: Type -> Type #

Methods

from :: Dashed -> Rep Dashed x #

to :: Rep Dashed x -> Dashed #

Show Dashed Source # 
Instance details

Defined in OptEnvConf.Args

Eq Dashed Source # 
Instance details

Defined in OptEnvConf.Args

Methods

(==) :: Dashed -> Dashed -> Bool #

(/=) :: Dashed -> Dashed -> Bool #

Validity Dashed Source # 
Instance details

Defined in OptEnvConf.Args

type Rep Dashed Source # 
Instance details

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))))