calamity-commands-0.1.3.0: A library for declaring, parsing, and invoking text-input based commands
Safe HaskellNone
LanguageHaskell2010

CalamityCommands.Parser

Description

Something that can parse user input

Synopsis

Documentation

class Typeable a => ParameterParser (a :: Type) c r where Source #

A typeclass for things that can be parsed as parameters to commands.

Any type that is an instance of ParamerParser can be used in the type level parameter ps of command, buildCommand, etc.

Minimal complete definition

parameterDescription, parse

Associated Types

type ParserResult a Source #

type ParserResult a = a

Instances

Instances details
ParameterParser Float c r Source # 
Instance details

Defined in CalamityCommands.Parser

Associated Types

type ParserResult Float Source #

ParameterParser Int c r Source # 
Instance details

Defined in CalamityCommands.Parser

Associated Types

type ParserResult Int Source #

ParameterParser Integer c r Source # 
Instance details

Defined in CalamityCommands.Parser

Associated Types

type ParserResult Integer Source #

ParameterParser Natural c r Source # 
Instance details

Defined in CalamityCommands.Parser

Associated Types

type ParserResult Natural Source #

ParameterParser Word c r Source # 
Instance details

Defined in CalamityCommands.Parser

Associated Types

type ParserResult Word Source #

ParameterParser () c r Source # 
Instance details

Defined in CalamityCommands.Parser

Associated Types

type ParserResult () Source #

ParameterParser Text c r Source # 
Instance details

Defined in CalamityCommands.Parser

Associated Types

type ParserResult Text Source #

ParameterParser Text c r Source # 
Instance details

Defined in CalamityCommands.Parser

Associated Types

type ParserResult Text Source #

ParameterParser a c r => ParameterParser [a] c r Source # 
Instance details

Defined in CalamityCommands.Parser

Associated Types

type ParserResult [a] Source #

ParameterParser a c r => ParameterParser (Maybe a) c r Source # 
Instance details

Defined in CalamityCommands.Parser

Associated Types

type ParserResult (Maybe a) Source #

(ParameterParser a c r, Typeable a) => ParameterParser (NonEmpty a) c r Source # 
Instance details

Defined in CalamityCommands.Parser

Associated Types

type ParserResult (NonEmpty a) Source #

(Semigroup (ParserResult a), ParameterParser a c r) => ParameterParser (KleenePlusConcat a) c r Source # 
Instance details

Defined in CalamityCommands.Parser

Associated Types

type ParserResult (KleenePlusConcat a) Source #

ParameterParser (KleenePlusConcat Text) c r Source # 
Instance details

Defined in CalamityCommands.Parser

Associated Types

type ParserResult (KleenePlusConcat Text) Source #

ParameterParser (KleenePlusConcat Text) c r Source # 
Instance details

Defined in CalamityCommands.Parser

Associated Types

type ParserResult (KleenePlusConcat Text) Source #

(Monoid (ParserResult a), ParameterParser a c r) => ParameterParser (KleeneStarConcat a) c r Source # 
Instance details

Defined in CalamityCommands.Parser

Associated Types

type ParserResult (KleeneStarConcat a) Source #

ParameterParser (KleeneStarConcat Text) c r Source # 
Instance details

Defined in CalamityCommands.Parser

Associated Types

type ParserResult (KleeneStarConcat Text) Source #

ParameterParser (KleeneStarConcat Text) c r Source # 
Instance details

Defined in CalamityCommands.Parser

Associated Types

type ParserResult (KleeneStarConcat Text) Source #

(ParameterParser a c r, ParameterParser b c r) => ParameterParser (Either a b) c r Source # 
Instance details

Defined in CalamityCommands.Parser

Associated Types

type ParserResult (Either a b) Source #

(ParameterParser a c r, ParameterParser b c r) => ParameterParser (a, b) c r Source # 
Instance details

Defined in CalamityCommands.Parser

Associated Types

type ParserResult (a, b) Source #

(KnownSymbol s, ParameterParser a c r) => ParameterParser (Named s a) c r Source # 
Instance details

Defined in CalamityCommands.Parser

Associated Types

type ParserResult (Named s a) Source #

data Named (s :: Symbol) (a :: Type) Source #

A named parameter, used to attach the name s to a type in the command's help output

Instances

Instances details
(KnownSymbol s, ParameterParser a c r) => ParameterParser (Named s a) c r Source # 
Instance details

Defined in CalamityCommands.Parser

Associated Types

type ParserResult (Named s a) Source #

type ParserResult (Named s a) Source # 
Instance details

Defined in CalamityCommands.Parser

data KleeneStarConcat (a :: Type) Source #

A parser that consumes zero or more of a then concatenates them together.

KleeneStarConcat Text therefore consumes all remaining input.

Instances

Instances details
(Monoid (ParserResult a), ParameterParser a c r) => ParameterParser (KleeneStarConcat a) c r Source # 
Instance details

Defined in CalamityCommands.Parser

Associated Types

type ParserResult (KleeneStarConcat a) Source #

ParameterParser (KleeneStarConcat Text) c r Source # 
Instance details

Defined in CalamityCommands.Parser

Associated Types

type ParserResult (KleeneStarConcat Text) Source #

ParameterParser (KleeneStarConcat Text) c r Source # 
Instance details

Defined in CalamityCommands.Parser

Associated Types

type ParserResult (KleeneStarConcat Text) Source #

type ParserResult (KleeneStarConcat a) Source # 
Instance details

Defined in CalamityCommands.Parser

type ParserResult (KleeneStarConcat Text) Source # 
Instance details

Defined in CalamityCommands.Parser

type ParserResult (KleeneStarConcat Text) Source # 
Instance details

Defined in CalamityCommands.Parser

data KleenePlusConcat (a :: Type) Source #

A parser that consumes one or more of a then concatenates them together.

KleenePlusConcat Text therefore consumes all remaining input.

Instances

Instances details
(Semigroup (ParserResult a), ParameterParser a c r) => ParameterParser (KleenePlusConcat a) c r Source # 
Instance details

Defined in CalamityCommands.Parser

Associated Types

type ParserResult (KleenePlusConcat a) Source #

ParameterParser (KleenePlusConcat Text) c r Source # 
Instance details

Defined in CalamityCommands.Parser

Associated Types

type ParserResult (KleenePlusConcat Text) Source #

ParameterParser (KleenePlusConcat Text) c r Source # 
Instance details

Defined in CalamityCommands.Parser

Associated Types

type ParserResult (KleenePlusConcat Text) Source #

type ParserResult (KleenePlusConcat a) Source # 
Instance details

Defined in CalamityCommands.Parser

type ParserResult (KleenePlusConcat Text) Source # 
Instance details

Defined in CalamityCommands.Parser

type ParserResult (KleenePlusConcat Text) Source # 
Instance details

Defined in CalamityCommands.Parser

Parameter parsing utilities

type ParserEffs c r = State ParserState ': (Error (Text, Text) ': (Reader c ': r)) Source #

 

runCommandParser :: c -> Text -> Sem (ParserEffs c r) a -> Sem r (Either (Text, Text) a) Source #

Run a command parser, ctx is the context, t is the text input

data ParserState Source #

The current state of the parser, used so that the entire remaining input is available.

This is used instead of just concatenating parsers to allow for more flexibility, for example, this could be used to construct flag-style parsers that parse a parameter from anywhere in the input message.

Constructors

ParserState 

Fields

  • off :: Int

    The current offset, or where the next parser should start parsing at

  • msg :: Text

    The input message ot parse

Instances

Instances details
Show ParserState Source # 
Instance details

Defined in CalamityCommands.Parser

Generic ParserState Source # 
Instance details

Defined in CalamityCommands.Parser

Associated Types

type Rep ParserState :: Type -> Type #

type Rep ParserState Source # 
Instance details

Defined in CalamityCommands.Parser

type Rep ParserState = D1 ('MetaData "ParserState" "CalamityCommands.Parser" "calamity-commands-0.1.3.0-inplace" 'False) (C1 ('MetaCons "ParserState" 'PrefixI 'True) (S1 ('MetaSel ('Just "off") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "msg") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)))

parseMP Source #

Arguments

:: Text

The name of the parser

-> ParsecT SpannedError Text (Sem (Reader c ': r)) a

The megaparsec parser

-> Sem (ParserEffs c r) a 

Parse a paremeter using a MegaParsec parser.

On failure this constructs a nice-looking megaparsec error for the failed parameter.