harg-0.1.3.0: Haskell program configuration using higher kinded data

Safe HaskellSafe
LanguageHaskell2010

Options.Harg.Construct

Synopsis

Documentation

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

Methods

optLong :: 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

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

HasLong OptionOpt a Source # 
Instance details

Defined in Options.Harg.Construct

Methods

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

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

Methods

optShort :: 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

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

HasShort OptionOpt a Source # 
Instance details

Defined in Options.Harg.Construct

Methods

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

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

Methods

optHelp :: 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

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

HasHelp FlagOpt a Source # 
Instance details

Defined in Options.Harg.Construct

Methods

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

HasHelp OptionOpt a Source # 
Instance details

Defined in Options.Harg.Construct

Methods

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

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

Methods

optMetavar :: 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

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

HasMetavar OptionOpt a Source # 
Instance details

Defined in Options.Harg.Construct

Methods

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

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

Methods

optEnvVar :: 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

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

HasEnvVar FlagOpt a Source # 
Instance details

Defined in Options.Harg.Construct

Methods

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

HasEnvVar OptionOpt a Source # 
Instance details

Defined in Options.Harg.Construct

Methods

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

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

Methods

optDefault :: (NotInAttrs OptDefault attr (DuplicateAttrMultipleErr "optDefault" '["optDefaultStr", "optRequired"]), NotInAttrs OptOptional attr (IncompatibleAttrsErr "optDefault" "optOptional")) => a -> o attr a -> o (OptDefault ': attr) a Source #

Add a default value to an option. Cannot be used in conjuction with with optRequired, optDefaultStr or optOptional.

Instances
HasDefault ArgumentOpt a Source # 
Instance details

Defined in Options.Harg.Construct

Methods

optDefault :: (NotInAttrs OptDefault a (DuplicateAttrMultipleErr "optDefault" ("optDefaultStr" ': ("optRequired" ': []))), NotInAttrs OptOptional a (IncompatibleAttrsErr "optDefault" "optOptional")) => a0 -> ArgumentOpt a a0 -> ArgumentOpt (OptDefault ': a) a0 Source #

HasDefault OptionOpt a Source # 
Instance details

Defined in Options.Harg.Construct

Methods

optDefault :: (NotInAttrs OptDefault a (DuplicateAttrMultipleErr "optDefault" ("optDefaultStr" ': ("optRequired" ': []))), NotInAttrs OptOptional a (IncompatibleAttrsErr "optDefault" "optOptional")) => a0 -> OptionOpt a a0 -> OptionOpt (OptDefault ': a) a0 Source #

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

Methods

optDefaultStr :: (NotInAttrs OptDefault attr (DuplicateAttrMultipleErr "optDefaultStr" '["optDefault", "optRequired"]), NotInAttrs OptOptional attr (IncompatibleAttrsErr "optDefaultStr" "optOptional")) => String -> o attr a -> o (OptDefault ': attr) a Source #

Add a default unparsed value to an option. Cannot be used in conjuction with optDefault, optRequired or optOptional.

Instances
HasDefaultStr ArgumentOpt a Source # 
Instance details

Defined in Options.Harg.Construct

Methods

optDefaultStr :: (NotInAttrs OptDefault a (DuplicateAttrMultipleErr "optDefaultStr" ("optDefault" ': ("optRequired" ': []))), NotInAttrs OptOptional a (IncompatibleAttrsErr "optDefaultStr" "optOptional")) => String -> ArgumentOpt a a0 -> ArgumentOpt (OptDefault ': a) a0 Source #

HasDefaultStr OptionOpt a Source # 
Instance details

Defined in Options.Harg.Construct

Methods

optDefaultStr :: (NotInAttrs OptDefault a (DuplicateAttrMultipleErr "optDefaultStr" ("optDefault" ': ("optRequired" ': []))), NotInAttrs OptOptional a (IncompatibleAttrsErr "optDefaultStr" "optOptional")) => String -> OptionOpt a a0 -> OptionOpt (OptDefault ': a) a0 Source #

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

Methods

optRequired :: (NotInAttrs OptDefault attr (DuplicateAttrMultipleErr "optRequired" '["optDefault", "optDefaultStr"]), NotInAttrs OptOptional attr (IncompatibleAttrsErr "optRequired" "optOptional")) => o attr a -> o (OptDefault ': attr) a Source #

Mark an option as required. Cannot be used in conjunction with optOptional, optDefault or optRequiredStr.

Instances
HasRequired ArgumentOpt a Source # 
Instance details

Defined in Options.Harg.Construct

Methods

optRequired :: (NotInAttrs OptDefault a (DuplicateAttrMultipleErr "optRequired" ("optDefault" ': ("optDefaultStr" ': []))), NotInAttrs OptOptional a (IncompatibleAttrsErr "optRequired" "optOptional")) => ArgumentOpt a a0 -> ArgumentOpt (OptDefault ': a) a0 Source #

HasRequired OptionOpt a Source # 
Instance details

Defined in Options.Harg.Construct

Methods

optRequired :: (NotInAttrs OptDefault a (DuplicateAttrMultipleErr "optRequired" ("optDefault" ': ("optDefaultStr" ': []))), NotInAttrs OptOptional a (IncompatibleAttrsErr "optRequired" "optOptional")) => 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 HasDefault, HasDefaultStr 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
        ( optLong "someopt"
        . optOptional
        )

Methods

optOptional :: (NotInAttrs OptOptional attr (DuplicateAttrErr "optOptional"), NotInAttrs OptDefault attr (IncompatibleAttrsErr "optOptional" "optDefault")) => 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 optDefault, optDefaultStr or optRequired.

Instances
HasOptional ArgumentOpt a Source # 
Instance details

Defined in Options.Harg.Construct

Methods

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

HasOptional OptionOpt a Source # 
Instance details

Defined in Options.Harg.Construct

Methods

optOptional :: (NotInAttrs OptOptional a (DuplicateAttrErr "optOptional"), NotInAttrs OptDefault a (IncompatibleAttrsErr "optOptional" "optDefault")) => 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 Source #

Create an option parser, equivalent to option. The result can then be used with toOpt to convert into the global Opt type.

  someOption :: Opt Int
  someOption
    = toOpt ( option readParser
            & optLong "someopt"
            & optHelp "Some option"
            & optDefault 256
            )

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

Similar to option, but accepts a modifier function and returns an Opt directly.

  someOption :: Opt Int
  someOption
    = optionWith readParser
        ( optLong "someopt"
        . optHelp "Some option"
        . optDefault 256
        )

flag Source #

Arguments

:: a

Default value

-> a

Active value

-> FlagOpt '[] a 

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 result can then be used with toOpt to convert into the global Opt type.

  someFlag :: Opt Int
  someFlag
    = toOpt ( flag 0 1
            & optLong "someflag"
            & optHelp "Some flag"
            )

flagWith Source #

Arguments

:: a

Default value

-> a

Active value

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

Similar to flag, but accepts a modifier function and returns an Opt directly.

  someFlag :: Opt Int
  someFlag
    = flagWith 0 1
        ( optLong "someflag"
        . optHelp "Some flag"
        )

switch :: FlagOpt '[] 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
    = toOpt ( switch
            & optLong "someswitch"
            & optHelp "Some switch"
            )

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

Similar to switch, but accepts a modifier function and returns an Opt directly.

  someSwitch :: Opt Bool
  someSwitch
    = switchWith
        ( optLong "someswitch"
        . optHelp "Some switch"
        )

switch' :: FlagOpt '[] Bool Source #

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

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

Similar to switch', but accepts a modifier function and returns an Opt directly.

argument :: OptReader a -> ArgumentOpt '[] a Source #

Create an argument parser, equivalent to argument. The result can then be used with toOpt to convert into the global Opt type.

  someArgument :: Opt String
  someArgument
    = toOpt ( argument strParser
            & optHelp "Some argument"
            & optDefault "this is the default"
            )

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

Similar to argument, but accepts a modifier function and returns an Opt directly.

  someArgument :: Opt Int
  someArgument
    = argumentWith
        ( optHelp "Some argument"
        . optDefault "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 #