Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Compute the command options and arguments based on handler function parameters.
Synopsis
- data ArgCount
- data OptionState = OptionState {}
- class SpecialParam (state :: OptionState) (a :: Type) where
- type TransSpecial state a :: OptionState
- specialOpt :: Map Text Object
- specialArg :: Maybe Text
- type family BeforeRegular (allowed :: Bool) (a :: Type) :: Constraint where ...
- class RegularParam (state :: OptionState) (isMaybe :: Bool) a where
- type TransRegular state isMaybe a :: OptionState
- class CommandParam (special :: Bool) (state :: OptionState) (a :: Type) where
- type TransState special state a :: OptionState
- paramOpt :: Map Text Object
- paramArg :: Maybe Text
- class CommandHandler (state :: OptionState) (h :: Type) where
- commandOptions :: (Map Text Object, [Text])
Documentation
Represents the value for the command option -nargs
.
data OptionState Source #
Determines how different special command handler parameter types may interact.
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.
Nothing
type TransSpecial state a :: OptionState Source #
type TransSpecial s _ = s
Instances
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.
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
.
type TransRegular state isMaybe a :: OptionState Source #
Instances
RegularParam ('OptionState al count ('Just consumer)) m (a :: k) Source # | |
Defined in Ribosome.Host.Handler.Command type TransRegular ('OptionState al count ('Just consumer)) m a :: OptionState Source # | |
RegularParam ('OptionState al count ('Nothing :: Maybe Type)) 'False (a :: k) Source # | |
Defined in Ribosome.Host.Handler.Command type TransRegular ('OptionState al count 'Nothing) 'False a :: OptionState Source # | |
RegularParam ('OptionState al count ('Nothing :: Maybe Type)) 'True (Maybe a :: Type) Source # | |
Defined in Ribosome.Host.Handler.Command 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.
Nothing
type TransState special state a :: OptionState Source #
Transition the current OptionState
.
Instances
RegularParam state (IsMaybe a) a => CommandParam 'False state a Source # | |
SpecialParam state a => CommandParam 'True state a 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
.
commandOptions :: (Map Text Object, [Text]) Source #
Return the list of command options and special arguments determined by the handler function's parameters.
Instances
(special ~ CommandSpecial a, next ~ TransState special state a, CommandParam special state a, CommandHandler next b) => CommandHandler state (a -> b) Source # | |
Defined in Ribosome.Host.Handler.Command | |
CommandHandler ('OptionState _a 'MinOne c) (Sem r a) Source # | |
Defined in Ribosome.Host.Handler.Command | |
CommandHandler ('OptionState _a 'MinZero c) (Sem r a) Source # | |
Defined in Ribosome.Host.Handler.Command | |
CommandHandler ('OptionState _a 'Zero c) (Sem r a) Source # | |
Defined in Ribosome.Host.Handler.Command |