morley-1.19.0: Developer tools for the Michelson Language
Safe HaskellSafe-Inferred
LanguageHaskell2010

Morley.Util.CLI

Description

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

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.

Methods

getReader :: ReadM a Source #

getMetavar :: String Source #

This string will be passed to the metavar function, hence we use String type rather Text (even though we use Text almost everywhere).

Instances

Instances details
HasCLReader Int16 Source # 
Instance details

Defined in Morley.Util.CLI

HasCLReader Int32 Source # 
Instance details

Defined in Morley.Util.CLI

HasCLReader Int64 Source # 
Instance details

Defined in Morley.Util.CLI

HasCLReader Int8 Source # 
Instance details

Defined in Morley.Util.CLI

HasCLReader Word16 Source # 
Instance details

Defined in Morley.Util.CLI

HasCLReader Word32 Source # 
Instance details

Defined in Morley.Util.CLI

HasCLReader Word64 Source # 
Instance details

Defined in Morley.Util.CLI

HasCLReader MText Source # 
Instance details

Defined in Morley.Michelson.Text

HasCLReader Value Source # 
Instance details

Defined in Morley.CLI

HasCLReader EpName Source # 
Instance details

Defined in Morley.Michelson.Untyped.Entrypoints

HasCLReader SomeAddressOrAlias Source # 
Instance details

Defined in Morley.Tezos.Address.Alias

HasCLReader Mutez Source # 
Instance details

Defined in Morley.Tezos.Core

HasCLReader SecretKey Source # 
Instance details

Defined in Morley.Tezos.Crypto

HasCLReader TLTime Source # 
Instance details

Defined in Morley.Tezos.Crypto.Timelock

HasCLReader Text Source # 
Instance details

Defined in Morley.Util.CLI

HasCLReader String Source # 
Instance details

Defined in Morley.Util.CLI

HasCLReader Word8 Source # 
Instance details

Defined in Morley.Util.CLI

HasCLReader Integer Source # 
Instance details

Defined in Morley.Util.CLI

HasCLReader Natural Source # 
Instance details

Defined in Morley.Util.CLI

HasCLReader Int Source # 
Instance details

Defined in Morley.Util.CLI

HasCLReader Word Source # 
Instance details

Defined in Morley.Util.CLI

SingI kind => HasCLReader (KindedAddress kind) Source # 
Instance details

Defined in Morley.Tezos.Address

(SingI kind, L1AddressKind kind) => HasCLReader (AddressOrAlias kind) Source # 
Instance details

Defined in Morley.Tezos.Address.Alias

AllHashTags kind => HasCLReader (Hash kind) Source # 
Instance details

Defined in Morley.Tezos.Crypto

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.

mkCommandParser :: String -> Parser a -> String -> Mod CommandFields a Source #

Parser for command 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.

This expects type-level name to be in camelCase as appropriate for Haskell and transforms the variable inside.

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.

integralReader :: (Integral a, Bits a) => ReadM a Source #

Parse a number, checking for overflows and other stuff.