harg-0.3.0.0: Haskell program configuration using higher kinded data

Safe HaskellSafe
LanguageHaskell2010

Options.Harg.Construct

Synopsis

Documentation

class HasLong o (attr :: [OptAttr]) where Source #

Methods

long :: String -> o attr a -> o attr a Source #

Add a long modifier to an option

Instances
HasLong FlagOpt a Source # 
Instance details

Defined in Options.Harg.Construct

Methods

long :: String -> FlagOpt a a0 -> FlagOpt a a0 Source #

HasLong OptionOpt a Source # 
Instance details

Defined in Options.Harg.Construct

Methods

long :: String -> OptionOpt a a0 -> OptionOpt a a0 Source #

class HasShort o (attr :: [OptAttr]) where Source #

Methods

short :: Char -> o attr a -> o attr a Source #

Add a short modifier to an option

Instances
HasShort FlagOpt a Source # 
Instance details

Defined in Options.Harg.Construct

Methods

short :: Char -> FlagOpt a a0 -> FlagOpt a a0 Source #

HasShort OptionOpt a Source # 
Instance details

Defined in Options.Harg.Construct

Methods

short :: Char -> OptionOpt a a0 -> OptionOpt a a0 Source #

class HasHelp o (attr :: [OptAttr]) where Source #

Methods

help :: String -> o attr a -> o attr a Source #

Add help to an option

Instances
HasHelp ArgumentOpt a Source # 
Instance details

Defined in Options.Harg.Construct

Methods

help :: String -> ArgumentOpt a a0 -> ArgumentOpt a a0 Source #

HasHelp FlagOpt a Source # 
Instance details

Defined in Options.Harg.Construct

Methods

help :: String -> FlagOpt a a0 -> FlagOpt a a0 Source #

HasHelp OptionOpt a Source # 
Instance details

Defined in Options.Harg.Construct

Methods

help :: String -> OptionOpt a a0 -> OptionOpt a a0 Source #

class HasMetavar o (attr :: [OptAttr]) where Source #

Methods

metavar :: String -> o attr a -> o attr a Source #

Add a metavar metavar to an option, to be displayed as the meta-parameter next to long/short modifiers

Instances
HasMetavar ArgumentOpt a Source # 
Instance details

Defined in Options.Harg.Construct

Methods

metavar :: String -> ArgumentOpt a a0 -> ArgumentOpt a a0 Source #

HasMetavar OptionOpt a Source # 
Instance details

Defined in Options.Harg.Construct

Methods

metavar :: String -> OptionOpt a a0 -> OptionOpt a a0 Source #

class HasEnvVar o (attr :: [OptAttr]) where Source #

Methods

envVar :: String -> o attr a -> o attr a Source #

Specify an environment variable to lookup for an option

Instances
HasEnvVar ArgumentOpt a Source # 
Instance details

Defined in Options.Harg.Construct

Methods

envVar :: String -> ArgumentOpt a a0 -> ArgumentOpt a a0 Source #

HasEnvVar FlagOpt a Source # 
Instance details

Defined in Options.Harg.Construct

Methods

envVar :: String -> FlagOpt a a0 -> FlagOpt a a0 Source #

HasEnvVar OptionOpt a Source # 
Instance details

Defined in Options.Harg.Construct

Methods

envVar :: String -> OptionOpt a a0 -> OptionOpt a a0 Source #

class HasDefaultVal o (attr :: [OptAttr]) where Source #

Methods

defaultVal :: (NotInAttrs OptDefault attr (DuplicateAttrMultipleErr "defaultVal" '["defaultStr", "required"]), NotInAttrs OptOptional attr (IncompatibleAttrsErr "defaultVal" "optional")) => a -> o attr a -> o (OptDefault ': attr) a Source #

Add a default value to an option. Cannot be used in conjuction with with required, defaultStr or optional.

Instances
HasDefaultVal ArgumentOpt a Source # 
Instance details

Defined in Options.Harg.Construct

Methods

defaultVal :: (NotInAttrs OptDefault a (DuplicateAttrMultipleErr "defaultVal" ("defaultStr" ': ("required" ': []))), NotInAttrs OptOptional a (IncompatibleAttrsErr "defaultVal" "optional")) => a0 -> ArgumentOpt a a0 -> ArgumentOpt (OptDefault ': a) a0 Source #

HasDefaultVal OptionOpt a Source # 
Instance details

Defined in Options.Harg.Construct

Methods

defaultVal :: (NotInAttrs OptDefault a (DuplicateAttrMultipleErr "defaultVal" ("defaultStr" ': ("required" ': []))), NotInAttrs OptOptional a (IncompatibleAttrsErr "defaultVal" "optional")) => a0 -> OptionOpt a a0 -> OptionOpt (OptDefault ': a) a0 Source #

class HasDefaultValStr o (attr :: [OptAttr]) where Source #

Methods

defaultStr :: (NotInAttrs OptDefault attr (DuplicateAttrMultipleErr "defaultStr" '["defaultVal", "required"]), NotInAttrs OptOptional attr (IncompatibleAttrsErr "defaultStr" "optional")) => String -> o attr a -> o (OptDefault ': attr) a Source #

Add a default unparsed value to an option. Cannot be used in conjuction with defaultVal, required or optional.

Instances
HasDefaultValStr ArgumentOpt a Source # 
Instance details

Defined in Options.Harg.Construct

Methods

defaultStr :: (NotInAttrs OptDefault a (DuplicateAttrMultipleErr "defaultStr" ("defaultVal" ': ("required" ': []))), NotInAttrs OptOptional a (IncompatibleAttrsErr "defaultStr" "optional")) => String -> ArgumentOpt a a0 -> ArgumentOpt (OptDefault ': a) a0 Source #

HasDefaultValStr OptionOpt a Source # 
Instance details

Defined in Options.Harg.Construct

Methods

defaultStr :: (NotInAttrs OptDefault a (DuplicateAttrMultipleErr "defaultStr" ("defaultVal" ': ("required" ': []))), NotInAttrs OptOptional a (IncompatibleAttrsErr "defaultStr" "optional")) => String -> OptionOpt a a0 -> OptionOpt (OptDefault ': a) a0 Source #

class HasRequired o (attr :: [OptAttr]) where Source #

Methods

required :: (NotInAttrs OptDefault attr (DuplicateAttrMultipleErr "required" '["defaultVal", "defaultStr"]), NotInAttrs OptOptional attr (IncompatibleAttrsErr "required" "optional")) => o attr a -> o (OptDefault ': attr) a Source #

Mark an option as required. Cannot be used in conjunction with optional, defaultVal or requiredStr.

Instances
HasRequired ArgumentOpt a Source # 
Instance details

Defined in Options.Harg.Construct

Methods

required :: (NotInAttrs OptDefault a (DuplicateAttrMultipleErr "required" ("defaultVal" ': ("defaultStr" ': []))), NotInAttrs OptOptional a (IncompatibleAttrsErr "required" "optional")) => ArgumentOpt a a0 -> ArgumentOpt (OptDefault ': a) a0 Source #

HasRequired OptionOpt a Source # 
Instance details

Defined in Options.Harg.Construct

Methods

required :: (NotInAttrs OptDefault a (DuplicateAttrMultipleErr "required" ("defaultVal" ': ("defaultStr" ': []))), NotInAttrs OptOptional a (IncompatibleAttrsErr "required" "optional")) => OptionOpt a a0 -> OptionOpt (OptDefault ': a) a0 Source #

class HasOptional o (attr :: [OptAttr]) where Source #

Class for options that can be optional. Cannot be used in conjunction with HasDefaultVal, HasDefaultValStr or HasRequired. Note that this will turn a parser for a into a parser for Maybe a, modifying the reader function appropriately. For example:

  someOpt :: Opt (Maybe Int)
  someOpt
    = optionWith readParser
        ( long "someopt"
        . optional
        )

Methods

optional :: (NotInAttrs OptOptional attr (DuplicateAttrErr "optional"), NotInAttrs OptDefault attr (IncompatibleAttrsErr "optional" "defaultVal")) => o attr a -> o (OptOptional ': attr) (Maybe a) Source #

Specify that an option is optional. This will convert an Opt a to an Opt (Maybe a). Cannot be used in conjunction with defaultVal, defaultStr or required.

Instances
HasOptional ArgumentOpt a Source # 
Instance details

Defined in Options.Harg.Construct

Methods

optional :: (NotInAttrs OptOptional a (DuplicateAttrErr "optional"), NotInAttrs OptDefault a (IncompatibleAttrsErr "optional" "defaultVal")) => ArgumentOpt a a0 -> ArgumentOpt (OptOptional ': a) (Maybe a0) Source #

HasOptional OptionOpt a Source # 
Instance details

Defined in Options.Harg.Construct

Methods

optional :: (NotInAttrs OptOptional a (DuplicateAttrErr "optional"), NotInAttrs OptDefault a (IncompatibleAttrsErr "optional" "defaultVal")) => OptionOpt a a0 -> OptionOpt (OptOptional ': a) (Maybe a0) Source #

class IsOpt o (attr :: [OptAttr]) where Source #

Class to convert an intermediate option type into Opt. Instances should set the appropriate _optType.

Methods

toOpt :: o attr a -> Opt a Source #

Convert an intermediate option to an Opt

Instances
IsOpt ArgumentOpt attr Source # 
Instance details

Defined in Options.Harg.Construct

Methods

toOpt :: ArgumentOpt attr a -> Opt a Source #

IsOpt FlagOpt attr Source # 
Instance details

Defined in Options.Harg.Construct

Methods

toOpt :: FlagOpt attr a -> Opt a Source #

IsOpt OptionOpt attr Source # 
Instance details

Defined in Options.Harg.Construct

Methods

toOpt :: OptionOpt attr a -> Opt a Source #

option :: OptReader a -> (OptionOpt '[] a -> OptionOpt attr b) -> Opt b Source #

Create an option parser, equivalent to option. The second argument is the modifiers to add to the option, and can be defined by using function composition (.).

  someOption :: Opt Int
  someOption
    = option readParser
        ( long "someopt"
        . help "Some option"
        . defaultVal 256
        )

flag Source #

Arguments

:: a

Default value

-> a

Active value

-> (FlagOpt '[] a -> FlagOpt attr b) 
-> Opt b 

Create a flag parser, equivalent to option. The first argument is the default value (returned when the flag modifier is absent), and the second is the active value (returned when the flag modifier is present). The second argument is the modifiers to add to the option, and can be defined by using function composition (.).

  someFlag :: Opt Int
  someFlag
    = flag 0 1
        ( long "someflag"
        . help "Some flag"
        )

switch :: (FlagOpt '[] Bool -> FlagOpt attr Bool) -> Opt Bool Source #

A flag parser, specialized to Bool. The parser (e.g. when parsing an environment variable) will accept true and false, but case insensitive, rather than using the Read instance for Bool. The default value is False, and the active value is True.

  someSwitch :: Opt Bool
  someSwitch
    = switch
        ( long "someswitch"
        . help "Some switch"
        )

switch' :: (FlagOpt '[] Bool -> FlagOpt attr Bool) -> Opt Bool Source #

Similar to switch, but the default value is True and the active is False.

argument :: OptReader a -> (ArgumentOpt '[] a -> ArgumentOpt attr b) -> Opt b Source #

Create an argument parser, equivalent to argument. The second argument is the modifiers to add to the option, and can be defined by using function composition (.).

  someArgument :: Opt Int
  someArgument
    = argument
        ( help "Some argument"
        . defaultVal "this is the default"
        )

parseWith Source #

Arguments

:: (String -> Maybe a)

Original parser

-> String

Input

-> Either String a 

Convert a parser that returns Maybe to a parser that returns Either, with the default Left value unable to parse: <input>.

readParser :: Read a => OptReader a Source #

A parser that uses the Read instance to parse into a type.

strParser :: IsString s => String -> Either String s Source #

A parser that returns a string. Any type that has an instance of IsString will work, and this parser always succeeds.

boolParser :: String -> Either String Bool Source #

A parser that returns a Bool. This will succeed for the strings true and false in a case-insensitive manner.

manyParser Source #

Arguments

:: String

Separator

-> OptReader a

Parser for each string

-> OptReader [a] 

A parser that can parse many items, returning a list.

type QuoteSym (s :: Symbol) = (Text "`" :<>: Text s) :<>: Text "`" Source #

Wrap a symbol in quotes, for pretty printing in type errors.

type family NotInAttrs (x :: k) (xs :: [k]) (err :: ErrorMessage) :: Constraint where ... Source #

Check if x is not an element of the type-level list xs. If it is print the appropriate error message using l and r for clarity.

Equations

NotInAttrs _ '[] _ = () 
NotInAttrs x (x ': _) err = TypeError err 
NotInAttrs x (y ': xs) err = NotInAttrs x xs err 

type family CommaSep (xs :: [Symbol]) :: Symbol where ... Source #

Equations

CommaSep '[] = "" 
CommaSep '[x] = " or " `AppendSymbol` x 
CommaSep (x ': xs) = " or one of " `AppendSymbol` CommaSep' x xs 

type family CommaSep' (s :: Symbol) (xs :: [Symbol]) :: Symbol where ... Source #

Equations

CommaSep' s '[] = s 
CommaSep' s (x ': xs) = CommaSep' ((s `AppendSymbol` ", ") `AppendSymbol` x) xs 

type DuplicateAttrErr attr = QuoteSym attr :<>: Text " is already specified." Source #

type DuplicateAttrMultipleErr attr rest = (QuoteSym attr :<>: Text (CommaSep rest)) :<>: Text " has already been specified." Source #

type IncompatibleAttrsErr l r = ((QuoteSym l :<>: Text " and ") :<>: QuoteSym r) :<>: Text " cannot be mixed in an option definition." Source #