| Safe Haskell | None |
|---|
Game.Antisplice.Call
Description
Provides a powerful language for user input evaluation
- data Cons a b = :-: a b
- data Nil = Nil
- class Append a b ab | a b -> ab where
- tappend :: a -> b -> ab
- class Tuplify l t | l -> t where
- tuplify :: l -> t
- processMask :: (CallMask m r, Append r Nil r, Tuplify r t) => m -> [String] -> DungeonM t
- tryMask :: (Append r Nil r, CallMask m r) => m -> [String] -> DungeonM Bool
- class CallMask cm l | cm -> l 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
Heterogenous list
The Cons type for a heterogenous list
Constructors
| :-: a b |
Instances
| CallMask CatchObj (Cons ObjectState Nil) | |
| CallMask Remaining (Cons [String] Nil) | |
| CallMask CatchOrd (Cons Int Nil) | |
| CallMask CatchToken (Cons Token Nil) | |
| CallMask CatchByType (Cons String Nil) | |
| Tuplify (Cons a Nil) a | |
| (CallMask x r, CallMask xs rs, Append r rs rx) => CallMask (Cons x xs) rx | |
| Append b c bc => Append (Cons a b) c (Cons a bc) | |
| Tuplify (Cons a (Cons b Nil)) (a, b) | |
| Tuplify (Cons a (Cons b (Cons c Nil))) (a, b, c) | |
| Tuplify (Cons a (Cons b (Cons c (Cons d Nil)))) (a, b, c, d) | |
| Tuplify (Cons a (Cons b (Cons c (Cons d (Cons e Nil))))) (a, b, c, d, e) | |
| Tuplify (Cons a (Cons b (Cons c (Cons d (Cons e (Cons f Nil)))))) (a, b, c, d, e, f) |
The empty list
Constructors
| Nil |
Instances
| Tuplify Nil () | |
| CallMask String Nil | |
| CallMask Token Nil | |
| CallMask EnsureLineEnd Nil | |
| CallMask Nil Nil | |
| Append Nil b b | |
| CallMask CatchObj (Cons ObjectState Nil) | |
| CallMask Remaining (Cons [String] Nil) | |
| CallMask CatchOrd (Cons Int Nil) | |
| CallMask CatchToken (Cons Token Nil) | |
| CallMask CatchByType (Cons String Nil) | |
| Tuplify (Cons a Nil) a | |
| Tuplify (Cons a (Cons b Nil)) (a, b) | |
| Tuplify (Cons a (Cons b (Cons c Nil))) (a, b, c) | |
| Tuplify (Cons a (Cons b (Cons c (Cons d Nil)))) (a, b, c, d) | |
| Tuplify (Cons a (Cons b (Cons c (Cons d (Cons e Nil))))) (a, b, c, d, e) | |
| Tuplify (Cons a (Cons b (Cons c (Cons d (Cons e (Cons f Nil)))))) (a, b, c, d, e, f) |
class Append a b ab | a b -> ab whereSource
Typeclass for appending one heterogenous list to another one
class Tuplify l t | l -> t whereSource
Typeclass for everything that may be converted to a tuple
Instances
| Tuplify Int Int | |
| Tuplify String String | |
| Tuplify ObjectState ObjectState | |
| Tuplify Nil () | |
| Tuplify (Cons a Nil) a | |
| Tuplify (Cons a (Cons b Nil)) (a, b) | |
| Tuplify (Cons a (Cons b (Cons c Nil))) (a, b, c) | |
| Tuplify (Cons a (Cons b (Cons c (Cons d Nil)))) (a, b, c, d) | |
| Tuplify (Cons a (Cons b (Cons c (Cons d (Cons e Nil))))) (a, b, c, d, e) | |
| Tuplify (Cons a (Cons b (Cons c (Cons d (Cons e (Cons f Nil)))))) (a, b, c, d, e, f) |
Using call masks
processMask :: (CallMask m 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 r Nil r, CallMask m r) => m -> [String] -> DungeonM BoolSource
Try to use a mask on a list of tokens. Only return whether it succeeded.
Call mask segments
class CallMask cm l | cm -> l whereSource
Typeclass for use input masks (either single modules or lists of modules)
Instances
| CallMask String Nil | |
| CallMask Token Nil | |
| CallMask EnsureLineEnd Nil | |
| CallMask Nil Nil | |
| CallMask CatchObj (Cons ObjectState Nil) | |
| CallMask Remaining (Cons [String] Nil) | |
| CallMask CatchOrd (Cons Int Nil) | |
| CallMask CatchToken (Cons Token Nil) | |
| CallMask CatchByType (Cons String Nil) | |
| (CallMask x r, CallMask xs rs, Append r rs rx) => CallMask (Cons x xs) rx |
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 |
Instances