ribosome-host-0.9.9.9: Neovim plugin host for Polysemy
Safe HaskellSafe-Inferred
LanguageHaskell2010

Ribosome.Host.Data.Args

Description

Special command parameters governing the aggregation of the entire (rest of the) argument list into one value.

Synopsis

Documentation

newtype Args Source #

When this type is used as the (last) parameter of a command handler function, all remaining tokens passed to the command will be consumed and stored in this type.

The command will be declared with the -nargs=* or -nargs=+ option.

See CommandHandler.

Constructors

Args 

Fields

Instances

Instances details
IsString Args Source # 
Instance details

Defined in Ribosome.Host.Data.Args

Methods

fromString :: String -> Args #

Show Args Source # 
Instance details

Defined in Ribosome.Host.Data.Args

Methods

showsPrec :: Int -> Args -> ShowS #

show :: Args -> String #

showList :: [Args] -> ShowS #

Eq Args Source # 
Instance details

Defined in Ribosome.Host.Data.Args

Methods

(==) :: Args -> Args -> Bool #

(/=) :: Args -> Args -> Bool #

Ord Args Source # 
Instance details

Defined in Ribosome.Host.Data.Args

Methods

compare :: Args -> Args -> Ordering #

(<) :: Args -> Args -> Bool #

(<=) :: Args -> Args -> Bool #

(>) :: Args -> Args -> Bool #

(>=) :: Args -> Args -> Bool #

max :: Args -> Args -> Args #

min :: Args -> Args -> Args #

Member (Stop Report) r => HandlerArg Args r Source # 
Instance details

Defined in Ribosome.Host.Handler.Codec

Methods

handlerArg :: [Object] -> Sem r ([Object], Args) Source #

SpecialParam ('OptionState al count ('Nothing :: Maybe Type)) Args Source # 
Instance details

Defined in Ribosome.Host.Handler.Command

Associated Types

type TransSpecial ('OptionState al count 'Nothing) Args :: OptionState Source #

type TransSpecial ('OptionState al count ('Nothing :: Maybe Type)) Args Source # 
Instance details

Defined in Ribosome.Host.Handler.Command

newtype ArgList Source #

When this type is used as the (last) parameter of a command handler function, all remaining tokens passed to the command will be consumed and stored in this type, as a list of whitespace separated tokens.

The command will be declared with the -nargs=* or -nargs=+ option.

See CommandHandler.

Constructors

ArgList 

Fields

Instances

Instances details
Show ArgList Source # 
Instance details

Defined in Ribosome.Host.Data.Args

Eq ArgList Source # 
Instance details

Defined in Ribosome.Host.Data.Args

Methods

(==) :: ArgList -> ArgList -> Bool #

(/=) :: ArgList -> ArgList -> Bool #

Member (Stop Report) r => HandlerArg ArgList r Source # 
Instance details

Defined in Ribosome.Host.Handler.Codec

Methods

handlerArg :: [Object] -> Sem r ([Object], ArgList) Source #

SpecialParam ('OptionState al count ac) ArgList Source # 
Instance details

Defined in Ribosome.Host.Handler.Command

Associated Types

type TransSpecial ('OptionState al count ac) ArgList :: OptionState Source #

type TransSpecial ('OptionState al count ac) ArgList Source # 
Instance details

Defined in Ribosome.Host.Handler.Command

type TransSpecial ('OptionState al count ac) ArgList = 'OptionState 'True (Max count 'MinZero) ('Just ArgList)

newtype JsonArgs a Source #

When this type is used as the (last) parameter of a command handler function, all remaining tokens passed to the command will be consumed, decoded as JSON and stored in this type.

The command will be declared with the -nargs=* or -nargs=+ option.

See CommandHandler.

Constructors

JsonArgs 

Fields

Instances

Instances details
Show a => Show (JsonArgs a) Source # 
Instance details

Defined in Ribosome.Host.Data.Args

Methods

showsPrec :: Int -> JsonArgs a -> ShowS #

show :: JsonArgs a -> String #

showList :: [JsonArgs a] -> ShowS #

Eq a => Eq (JsonArgs a) Source # 
Instance details

Defined in Ribosome.Host.Data.Args

Methods

(==) :: JsonArgs a -> JsonArgs a -> Bool #

(/=) :: JsonArgs a -> JsonArgs a -> Bool #

(Member (Stop Report) r, FromJSON a) => HandlerArg (JsonArgs a) r Source # 
Instance details

Defined in Ribosome.Host.Handler.Codec

Methods

handlerArg :: [Object] -> Sem r ([Object], JsonArgs a) Source #

SpecialParam ('OptionState al count ac) (JsonArgs a) Source # 
Instance details

Defined in Ribosome.Host.Handler.Command

Associated Types

type TransSpecial ('OptionState al count ac) (JsonArgs a) :: OptionState Source #

type TransSpecial ('OptionState al count ac) (JsonArgs a) Source # 
Instance details

Defined in Ribosome.Host.Handler.Command

type TransSpecial ('OptionState al count ac) (JsonArgs a) = 'OptionState 'True (Max count 'MinZero) ('Just (JsonArgs a))

newtype Options a Source #

When this type is used as the (last) parameter of a command handler function, all remaining tokens passed to the command will be consumed, parsed via optparse-applicative and stored in this type.

The parser associated with a must be defined as an instance of OptionParser a.

The command will be declared with the -nargs=* or -nargs=+ option.

See CommandHandler.

Constructors

Options a 

Instances

Instances details
Show a => Show (Options a) Source # 
Instance details

Defined in Ribosome.Host.Data.Args

Methods

showsPrec :: Int -> Options a -> ShowS #

show :: Options a -> String #

showList :: [Options a] -> ShowS #

Eq a => Eq (Options a) Source # 
Instance details

Defined in Ribosome.Host.Data.Args

Methods

(==) :: Options a -> Options a -> Bool #

(/=) :: Options a -> Options a -> Bool #

(Member (Stop Report) r, OptionParser a) => HandlerArg (Options a) r Source # 
Instance details

Defined in Ribosome.Host.Handler.Codec

Methods

handlerArg :: [Object] -> Sem r ([Object], Options a) Source #

SpecialParam ('OptionState al count ('Nothing :: Maybe Type)) (Options a) Source # 
Instance details

Defined in Ribosome.Host.Handler.Command

Associated Types

type TransSpecial ('OptionState al count 'Nothing) (Options a) :: OptionState Source #

type TransSpecial ('OptionState al count ('Nothing :: Maybe Type)) (Options a) Source # 
Instance details

Defined in Ribosome.Host.Handler.Command

type TransSpecial ('OptionState al count ('Nothing :: Maybe Type)) (Options a) = 'OptionState 'True (Max count 'MinZero) ('Just (Options a))

class OptionParser a where Source #

The parser used when declaring command handlers with the special parameter Options a.