Safe Haskell | None |
---|
Game.Antisplice.Call
Description
Provides a powerful language for user input evaluation
- processMask :: (Append m (Cons EnsureLineEnd Nil) s, CallMask s r, Append r Nil r, Tuplify r t) => m -> [String] -> DungeonM t
- tryMask :: (Append m (Cons EnsureLineEnd Nil) s, Append r Nil r, CallMask s r) => m -> [String] -> DungeonM (Either ReError r)
- class CallMask cm l | cm -> l where
- usemask :: (MonadRoom m, MonadPlayer m) => cm -> StateT [(String, Token)] m (Either ReError l)
- verbosemask :: cm -> String
- class PredMask rm im where
- usepmask :: rm -> im -> ChattyDungeonM (Maybe ReError)
- class PostMask pm im rm | pm im -> rm where
- usepost :: pm -> im -> ChattyDungeonM rm
- class CombiMask cm rm pm pom | cm rm -> pm pom where
- data EnsureLineEnd = EnsureLineEnd
- data CatchByType
- = CatchVerb
- | CatchPrep
- | CatchNoun
- | CatchAdj
- | CatchOrdn Int
- | CatchFixe
- | CatchSkilln
- | CatchUnint
- | CatchAny
- data CatchToken
- = CatchToken
- | CatchNounc
- data CatchOrd = CatchOrd
- data Remaining = Remaining
- data CatchObj
- data Which a = Which [a]
- data Optional a = Optional a
- data Ignore = Ignore
- data Pass = Pass
Using call masks
processMask :: (Append m (Cons EnsureLineEnd Nil) s, CallMask s r, Append r Nil r, Tuplify r t) => m -> [String] -> DungeonM tSource
Use a mask on a list of tokens and tuplify the result. Dispatch errors to the underlying monad.
tryMask :: (Append m (Cons EnsureLineEnd Nil) s, Append r Nil r, CallMask s r) => m -> [String] -> DungeonM (Either ReError r)Source
Try to use a mask on a list of tokens.
Mask classes
class CallMask cm l | cm -> l whereSource
Typeclass for input masks (either single modules or lists of modules)
Methods
usemask :: (MonadRoom m, MonadPlayer m) => cm -> StateT [(String, Token)] m (Either ReError l)Source
verbosemask :: cm -> StringSource
Instances
CallMask String Nil | |
CallMask Nil Nil | |
CallMask Token Nil | |
CallMask Ignore Nil | |
CallMask EnsureLineEnd Nil | |
CallMask CatchObj (Cons (Titled ObjectState) Nil) | |
CallMask Remaining (Cons [String] Nil) | |
CallMask CatchOrd (Cons Int Nil) | |
CallMask CatchToken (Cons Token Nil) | |
CallMask CatchByType (Cons String Nil) | |
(CallMask a ar, IntoMaybe ar am, Append am Nil am) => CallMask (Optional a) am | |
(CallMask a r, Append (Cons a Nil) r ar) => CallMask (Which a) ar | |
(CallMask x r, CallMask xs rs, Append r rs rx) => CallMask (Cons x xs) rx |
class PredMask rm im whereSource
Typeclass for evaluation result predicate masks
Methods
usepmask :: rm -> im -> ChattyDungeonM (Maybe ReError)Source
class PostMask pm im rm | pm im -> rm whereSource
Typeclass for evaluation result post-processing masks
Methods
usepost :: pm -> im -> ChattyDungeonM rmSource
class CombiMask cm rm pm pom | cm rm -> pm pom whereSource
Typeclass for evaluation result combi masks
Instances
CombiMask Nil Nil Nil Nil | |
CombiMask Pass a Ignore Pass | |
CombiMask Ignore a Ignore Ignore | |
CombiMask (a -> Either ReError b) a (a -> Maybe ReError) (a -> b) | |
CombiMask (a -> Maybe b, String) a (a -> Bool, String) (a -> b) | |
(CombiMask m i p po, CombiMask ms is ps pos) => CombiMask (Cons m ms) (Cons i is) (Cons p ps) (Cons po pos) |
Mask segments
data EnsureLineEnd Source
Ensures that the end of the input is reached
Constructors
EnsureLineEnd |
Instances
data CatchByType Source
Catches the string of a token matching the given token type
Constructors
CatchVerb | |
CatchPrep | |
CatchNoun | |
CatchAdj | |
CatchOrdn Int | |
CatchFixe | |
CatchSkilln | |
CatchUnint | |
CatchAny |
Instances
Catches the number of an Ordn token
Constructors
CatchOrd |
Catches the remaining part of the line
Constructors
Remaining |
Catches an available, carried or seen object
Constructors
AvailableObject | |
SeenObject | |
CarriedObject |
Provide multiple alternatives and catch the first matching one as well as its result
Constructors
Which [a] |
Provide an optional mask part
Constructors
Optional a |
Ignore a token or result
Constructors
Ignore |