extensible-0.6: Extensible, efficient, optics-friendly data types and effects

Copyright(c) Fumiaki Kinoshita 2018
LicenseBSD3
MaintainerFumiaki Kinoshita <fumiexcel@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Data.Extensible.GetOpt

Contents

Description

Synopsis

Documentation

data OptionDescr h a Source #

OptDescr with a default

Constructors

OptionDescr (s -> h a) !s (OptDescr (s -> s)) 
Instances
Wrapper (OptionDescr h :: k -> Type) Source # 
Instance details

Defined in Data.Extensible.GetOpt

Associated Types

type Repr (OptionDescr h) v :: Type Source #

Functor h => Functor (OptionDescr h) Source # 
Instance details

Defined in Data.Extensible.GetOpt

Methods

fmap :: (a -> b) -> OptionDescr h a -> OptionDescr h b #

(<$) :: a -> OptionDescr h b -> OptionDescr h a #

type Repr (OptionDescr h :: k -> Type) (a :: k) Source # 
Instance details

Defined in Data.Extensible.GetOpt

type Repr (OptionDescr h :: k -> Type) (a :: k) = OptionDescr h a

type OptDescr' = OptionDescr Identity Source #

Simple option descriptor

getOptRecord Source #

Arguments

:: RecordOf (OptionDescr h) xs

a record of option descriptors

-> [String]

arguments

-> (RecordOf h xs, [String], [String], String -> String)

(result, remaining non-options, errors, usageInfo)

Parse option arguments.

withGetOpt Source #

Arguments

:: MonadIO m 
=> String

Non-option usage

-> RecordOf (OptionDescr h) xs

option desciptors

-> (RecordOf h xs -> [String] -> m a)

the result and non-option arguments

-> m a 

An all-in-one utility function. When there's an error, print it along with the usage info to stderr and terminate with exitFailure.

Basic descriptors

optFlag Source #

Arguments

:: [Char]

short option

-> [String]

long option

-> String

explanation

-> OptDescr' Bool 

True when specified

optLastArg Source #

Arguments

:: [Char]

short option

-> [String]

long option

-> String

placeholder

-> String

explanation

-> OptDescr' (Maybe String) 

Takes the last argument when more than one is specified.

More generic descriptors

optNoArg Source #

Arguments

:: [Char]

short option

-> [String]

long option

-> String

explanation

-> OptDescr' Int 

Option without an argument; the result is the total count of this option.

optReqArg Source #

Arguments

:: [Char]

short option

-> [String]

long option

-> String

placeholder

-> String

explanation

-> OptDescr' [String] 

Option with an argument

optionNoArg :: (Int -> h a) -> [Char] -> [String] -> String -> OptionDescr h a Source #

Wrapper-generic version of optNoArg

optionReqArg :: ([String] -> h a) -> [Char] -> [String] -> String -> String -> OptionDescr h a Source #

Wrapper-generic version of optReqArg

optionOptArg :: ([Maybe String] -> h a) -> [Char] -> [String] -> String -> String -> OptionDescr h a Source #

Construct an option with an optional argument