darcs-2.18.2: a distributed, interactive, smart revision control system
Safe HaskellSafe-Inferred
LanguageHaskell2010

Darcs.UI.Options.Util

Description

Constructing OptSpecs and OptDescrs

Synopsis

Documentation

type Flag = DarcsFlag Source #

This type synonym is here for brevity and because we want to import the data constructors (but not the type) of DarcsFlag qualified.

Instantiating OptSpec and PrimOptSpec

type DarcsOptDescr = Compose OptDescr ((->) AbsolutePath) Source #

We do not instantiate the d in OptSpec d f directly with OptDescr. Instead we (post-) compose it with (->) AbsolutePath. Modulo newtype noise, this is the same as

 type DarcsOptDescr f = OptDescr (AbsolutePath -> f)

This is so we can pass a directory relative to which an option argument is interpreted (if it has the form of a relative path).

type PrimDarcsOption v = forall a. PrimOptSpec DarcsOptDescr Flag a v Source #

This is PrimOptSpec instantiated with DarcsOptDescr and Flag.

Constructing DarcsOptDescrs

noArg :: [Char] -> [String] -> f -> String -> DarcsOptDescr f Source #

Construct a DarcsOptDescr with no arguments.

strArg :: SingleArgOptDescr String f Source #

Construct a DarcsOptDescr with a String argument.

optStrArg :: SingleArgOptDescr (Maybe String) f Source #

Construct a DarcsOptDescr with an optional String argument.

absPathArg :: SingleArgOptDescr AbsolutePath f Source #

Construct a DarcsOptDescr with an AbsolutePath argument.

absPathOrStdArg :: SingleArgOptDescr AbsolutePathOrStd f Source #

Construct a DarcsOptDescr with an AbsolutePathOrStd argument.

optAbsPathArg :: [Char] -> [String] -> String -> (AbsolutePath -> f) -> String -> String -> DarcsOptDescr f Source #

Construct a DarcsOptDescr with an optional AbsolutePath argument.

Raw option specs

data RawOptSpec f v Source #

The raw material from which multi-valued options are built. See withDefault.

Instances

Instances details
IsoFunctor (RawOptSpec f) Source # 
Instance details

Defined in Darcs.UI.Options.Util

Methods

imap :: Iso a b -> RawOptSpec f a -> RawOptSpec f b Source #

withDefault :: Eq v => v -> [RawOptSpec Flag v] -> PrimDarcsOption v Source #

Construct a PrimDarcsOption from a default value and a list of RawOptSpec.

Precondition: the list must have an entry for each possible value (type v).

Simple primitive scalar valued options

singleNoArg :: [Char] -> [String] -> Flag -> String -> PrimDarcsOption Bool Source #

Construct a Bool valued option with a single flag that takes no arguments and has no default flag.

The arguments are: short switches, long switches, flag value, help string.

singleStrArg :: [Char] -> [String] -> (String -> Flag) -> (Flag -> Maybe String) -> String -> String -> PrimDarcsOption (Maybe String) Source #

Construct a Maybe String valued option with a single flag that takes a String argument and has no default flag.

The arguments are: short switches, long switches, flag constructor, single flag parser, help string.

Simple primitive list valued options

multiStrArg :: [Char] -> [String] -> (String -> Flag) -> ([Flag] -> [String]) -> String -> String -> PrimDarcsOption [String] Source #

Similar to singleStrArg, except that the flag can be given more than once. The flag arguments are collected in a list of Strings.

multiOptStrArg :: [Char] -> [String] -> (Maybe String -> Flag) -> ([Flag] -> [Maybe String]) -> String -> String -> PrimDarcsOption [Maybe String] Source #

Similar to multiStrArg, except that the flag arguments are optional.

singleAbsPathArg :: [Char] -> [String] -> (AbsolutePath -> Flag) -> (Flag -> Maybe AbsolutePath) -> String -> String -> PrimDarcsOption (Maybe AbsolutePath) Source #

Construct a Maybe AbsolutePath valued option with a single flag that takes an AbsolutePath argument and has no default flag.

The arguments are: short switches, long switches, flag constructor, single flag parser, help string.

multiAbsPathArg :: [Char] -> [String] -> (AbsolutePath -> Flag) -> ([Flag] -> [AbsolutePath]) -> String -> String -> PrimDarcsOption [AbsolutePath] Source #

Similar to singleAbsPathArg, except that the flag can be given more than once. The flag arguments are collected in a list of AbsolutePaths.

deprecated :: [String] -> [RawOptSpec Flag v] -> PrimDarcsOption () Source #

A deprecated option. If you want to deprecate only some flags and not the whole option, extract the RawOptSpecs out of the original option and create a new deprecated option. The strings in the first argument are appended to the automatically generated error message in case additional hints should be provided.

Parsing/showing option arguments

Re-exports

data AbsolutePathOrStd Source #

This is for situations where a string (e.g. a command line argument) may take the value "-" to mean stdin or stdout (which one depends on context) instead of a normal file path.