Safe Haskell | None |
---|---|
Language | Haskell2010 |
Utilities for command line options parsing
(we use optparse-applicative
).
Some names exported from this module are quite general when if you
do not assume optparse-applicative
usage, so consider using
explicit imports for it.
Synopsis
- maybeAddDefault :: HasValue f => (a -> String) -> Maybe a -> Mod f a
- outputOption :: Parser (Maybe FilePath)
- class HasCLReader a where
- getReader :: ReadM a
- getMetavar :: String
- mkCLOptionParser :: forall a. (Buildable a, HasCLReader a) => Maybe a -> ("name" :! String) -> ("help" :! String) -> Parser a
- mkCLOptionParserExt :: forall a. (Buildable a, HasCLReader a) => Maybe a -> ("name" :! String) -> ("help" :! String) -> [Mod OptionFields a] -> Parser a
- mkCLArgumentParser :: forall a. (Buildable a, HasCLReader a) => Maybe a -> ("help" :! String) -> Parser a
- mkCLArgumentParserExt :: forall a. (Buildable a, HasCLReader a) => Maybe a -> ("help" :! String) -> [Mod ArgumentFields a] -> Parser a
- namedParser :: forall (a :: Type) (name :: Symbol). (Buildable a, HasCLReader a, KnownSymbol name) => Maybe a -> String -> Parser (name :! a)
- eitherReader :: (String -> Either String a) -> ReadM a
- readerError :: String -> ReadM a
General helpers
maybeAddDefault :: HasValue f => (a -> String) -> Maybe a -> Mod f a Source #
Maybe add the default value and make sure it will be shown in help message.
outputOption :: Parser (Maybe FilePath) Source #
Parser for path to a file where output will be writen.
Named and type class based parsing
class HasCLReader a where Source #
Supporting typeclass for namedParser
.
It specifies how a value should be parsed from command line.
Even though the main purpose of this class is to implement
helpers below, feel free to use it for other goals.
getMetavar :: String Source #
Instances
HasCLReader Int Source # | |
HasCLReader Integer Source # | |
HasCLReader Natural Source # | |
HasCLReader Word64 Source # | |
HasCLReader Text Source # | |
HasCLReader EpName Source # | |
Defined in Michelson.Untyped.EntryPoints | |
HasCLReader MText Source # | |
Defined in Michelson.Text | |
HasCLReader KeyHash Source # | |
Defined in Tezos.Crypto | |
HasCLReader Mutez Source # | |
Defined in Tezos.Core | |
HasCLReader Address Source # | |
Defined in Tezos.Address | |
HasCLReader Value Source # | |
Defined in Morley.CLI |
mkCLOptionParser :: forall a. (Buildable a, HasCLReader a) => Maybe a -> ("name" :! String) -> ("help" :! String) -> Parser a Source #
Create a Parser
for a value using HasCLReader
instance
(hence CL
in the name). It uses reader and metavar from that
class, the rest should be supplied as arguments.
We expect some common modifiers to be always provided, a list of extra modifies can be provided as well.
mkCLOptionParserExt :: forall a. (Buildable a, HasCLReader a) => Maybe a -> ("name" :! String) -> ("help" :! String) -> [Mod OptionFields a] -> Parser a Source #
A more general version of mkCLOptionParser
which takes a list
of extra (not as widely used) modifiers.
mkCLArgumentParser :: forall a. (Buildable a, HasCLReader a) => Maybe a -> ("help" :! String) -> Parser a Source #
Akin to mkCLOptionParser
, but for arguments rather than options.
mkCLArgumentParserExt :: forall a. (Buildable a, HasCLReader a) => Maybe a -> ("help" :! String) -> [Mod ArgumentFields a] -> Parser a Source #
Akin to mkCLOptionParserExt
, but for arguments rather than options.
namedParser :: forall (a :: Type) (name :: Symbol). (Buildable a, HasCLReader a, KnownSymbol name) => Maybe a -> String -> Parser (name :! a) Source #
Create a Parser
for a value using its type-level name.
Helpers for defining HasCLReader
eitherReader :: (String -> Either String a) -> ReadM a #
Convert a function producing an Either
into a reader.
As an example, one can create a ReadM from an attoparsec Parser easily with
import qualified Data.Attoparsec.Text as A import qualified Data.Text as T attoparsecReader :: A.Parser a -> ReadM a attoparsecReader p = eitherReader (A.parseOnly p . T.pack)
readerError :: String -> ReadM a #
Abort option reader by exiting with an error message.