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

CalamityCommands.Check

Description

Command invokation preconditions

Synopsis

Documentation

data Check m c Source #

A check for a command.

Every check for a command must return Nothing for the command to be run.

Constructors

MkCheck 

Fields

  • name :: Text

    The name of the check.

  • callback :: c -> m (Maybe Text)

    The callback for the check, returns Nothing if it passes, otherwise returns the reason for it not passing.

Instances

Instances details
Generic (Check m c) Source # 
Instance details

Defined in CalamityCommands.Check

Associated Types

type Rep (Check m c) :: Type -> Type #

Methods

from :: Check m c -> Rep (Check m c) x #

to :: Rep (Check m c) x -> Check m c #

type Rep (Check m c) Source # 
Instance details

Defined in CalamityCommands.Check

type Rep (Check m c) = D1 ('MetaData "Check" "CalamityCommands.Check" "calamity-commands-0.2.0.0-inplace" 'False) (C1 ('MetaCons "MkCheck" 'PrefixI 'True) (S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "callback") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (c -> m (Maybe Text)))))

buildCheck :: (Monad m, Member (Final m) r) => Text -> (c -> Sem r (Maybe Text)) -> Sem r (Check m c) Source #

Given the name of a check and a callback in the Sem monad, build a check by transforming the Polysemy action into an m action.

buildCheckPure :: Monad m => Text -> (c -> Maybe Text) -> Check m c Source #

Given the name of a check and a pure callback function, build a check.

runCheck :: (Monad m, Member (Embed m) r) => c -> Check m c -> Sem r (Either CommandError ()) Source #

Given an invokation context c, run a check and transform the result into an Either CommandError ().