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

Ribosome.Host.Handler.Command

Description

Compute the command options and arguments based on handler function parameters.

Synopsis

Documentation

data ArgCount Source #

Represents the value for the command option -nargs.

Constructors

Zero
-nargs=0
MinZero
-nargs=*
MinOne
-nargs=+

Instances

Instances details
Show ArgCount Source # 
Instance details

Defined in Ribosome.Host.Handler.Command

Eq ArgCount Source # 
Instance details

Defined in Ribosome.Host.Handler.Command

data OptionState Source #

Determines how different special command handler parameter types may interact.

Constructors

OptionState 

Fields

class SpecialParam (state :: OptionState) (a :: Type) where Source #

Determine the command options and arguments that need to be specified when registering a command, for a special command option parameter.

See Command params for the list of supported special types.

Minimal complete definition

Nothing

Associated Types

type TransSpecial state a :: OptionState Source #

type TransSpecial s _ = s

Instances

Instances details
BeforeRegular al Bang => SpecialParam ('OptionState al c ac) Bang Source # 
Instance details

Defined in Ribosome.Host.Handler.Command

Associated Types

type TransSpecial ('OptionState al c ac) Bang :: OptionState Source #

BeforeRegular al Bar => SpecialParam ('OptionState al c ac) Bar Source # 
Instance details

Defined in Ribosome.Host.Handler.Command

Associated Types

type TransSpecial ('OptionState al c ac) Bar :: OptionState Source #

BeforeRegular al CommandMods => SpecialParam ('OptionState al c ac) CommandMods Source # 
Instance details

Defined in Ribosome.Host.Handler.Command

Associated Types

type TransSpecial ('OptionState al c ac) CommandMods :: OptionState Source #

BeforeRegular al CommandRegister => SpecialParam ('OptionState al c ac) CommandRegister Source # 
Instance details

Defined in Ribosome.Host.Handler.Command

Associated Types

type TransSpecial ('OptionState al c ac) CommandRegister :: OptionState 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 #

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 #

(BeforeRegular al (Range rs), RangeStyleOpt rs) => SpecialParam ('OptionState al c ac) (Range rs) Source # 
Instance details

Defined in Ribosome.Host.Handler.Command

Associated Types

type TransSpecial ('OptionState al c ac) (Range rs) :: OptionState 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 #

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 family BeforeRegular (allowed :: Bool) (a :: Type) :: Constraint where ... Source #

Emit a compile error if a special command option type is used as a handler parameter after a regular, value parameter.

The parameter allowed is set to False when the first non-option parameter is encountered.

Equations

BeforeRegular 'False a = TypeError (("Command option type " <> a) <> " may not come after non-option") ~ () 
BeforeRegular 'True _ = () 

class RegularParam (state :: OptionState) (isMaybe :: Bool) a Source #

Determines whether a regular, value parameter is allowed (it isn't after types like ArgList that consume all remaining arguments), and increases the minimum argument count if the parameter isn't Maybe.

Associated Types

type TransRegular state isMaybe a :: OptionState Source #

Instances

Instances details
RegularParam ('OptionState al count ('Just consumer)) m (a :: k) Source # 
Instance details

Defined in Ribosome.Host.Handler.Command

Associated Types

type TransRegular ('OptionState al count ('Just consumer)) m a :: OptionState Source #

RegularParam ('OptionState al count ('Nothing :: Maybe Type)) 'False (a :: k) Source # 
Instance details

Defined in Ribosome.Host.Handler.Command

Associated Types

type TransRegular ('OptionState al count 'Nothing) 'False a :: OptionState Source #

RegularParam ('OptionState al count ('Nothing :: Maybe Type)) 'True (Maybe a :: Type) Source # 
Instance details

Defined in Ribosome.Host.Handler.Command

Associated Types

type TransRegular ('OptionState al count 'Nothing) 'True (Maybe a) :: OptionState Source #

class CommandParam (special :: Bool) (state :: OptionState) (a :: Type) where Source #

Determine the command option and parameter that a handler parameter type requires, if any.

Minimal complete definition

Nothing

Associated Types

type TransState special state a :: OptionState Source #

Transition the current OptionState.

Instances

Instances details
RegularParam state (IsMaybe a) a => CommandParam 'False state a Source # 
Instance details

Defined in Ribosome.Host.Handler.Command

Associated Types

type TransState 'False state a :: OptionState Source #

SpecialParam state a => CommandParam 'True state a Source # 
Instance details

Defined in Ribosome.Host.Handler.Command

Associated Types

type TransState 'True state a :: OptionState Source #

class CommandHandler (state :: OptionState) (h :: Type) where Source #

Derive the command options and arguments that should be used when registering the Neovim command, from the parameters of the handler function.

See Command params for the list of supported special types.

The parameter state is a type level value that determines which parameter types may be used after another and counts the number of command arguments that are required or allowed. It is transitioned by families in the classes CommandParam, SpecialParam and RegularParam.

Methods

commandOptions :: (Map Text Object, [Text]) Source #

Return the list of command options and special arguments determined by the handler function's parameters.

Instances

Instances details
(special ~ CommandSpecial a, next ~ TransState special state a, CommandParam special state a, CommandHandler next b) => CommandHandler state (a -> b) Source # 
Instance details

Defined in Ribosome.Host.Handler.Command

CommandHandler ('OptionState _a 'MinOne c) (Sem r a) Source # 
Instance details

Defined in Ribosome.Host.Handler.Command

CommandHandler ('OptionState _a 'MinZero c) (Sem r a) Source # 
Instance details

Defined in Ribosome.Host.Handler.Command

CommandHandler ('OptionState _a 'Zero c) (Sem r a) Source # 
Instance details

Defined in Ribosome.Host.Handler.Command