| License | BSD-3-Clause |
|---|---|
| Safe Haskell | None |
| Language | Haskell2010 |
Swarm.Game.Exception
Contents
Description
Runtime exceptions for the Swarm language interpreter.
Synopsis
- data Exn
- = Fatal Text
- | Cancel
- | InfiniteLoop
- | Incapable IncapableFix Requirements Term
- | CmdFailed Const Text (Maybe GameplayAchievement)
- | User Text
- data IncapableFix
- formatExn :: EntityMap -> Exn -> Text
- exnSeverity :: Exn -> Severity
- data IncapableFixWords = IncapableFixWords {}
- formatIncapable :: EntityMap -> IncapableFix -> Requirements -> Term -> Text
- formatIncapableFix :: IncapableFix -> IncapableFixWords
Documentation
The type of exceptions that can be thrown by robot programs.
Constructors
| Fatal Text | Something went very wrong. This is a bug in Swarm and cannot
be caught by a |
| Cancel | The user manually cancelled the computation (e.g. by hitting
Ctrl-C). This cannot be caught by a |
| InfiniteLoop | An infinite loop was detected via a blackhole. This cannot
be caught by a |
| Incapable IncapableFix Requirements Term | A robot tried to do something for which it does not have some
of the required capabilities. This cannot be caught by a
|
| CmdFailed Const Text (Maybe GameplayAchievement) | A command failed in some "normal" way (e.g. a |
| User Text | The user program explicitly called |
Instances
data IncapableFix Source #
Suggested way to fix things when a robot does not meet the requirements to run a command.
Constructors
| FixByEquip |
|
| FixByObtainDevice | Add the missing device to your inventory |
| FixByObtainConsumables | Add the missing consumables to your inventory |
Instances
| FromJSON IncapableFix Source # | |||||
Defined in Swarm.Game.Exception | |||||
| ToJSON IncapableFix Source # | |||||
Defined in Swarm.Game.Exception Methods toJSON :: IncapableFix -> Value # toEncoding :: IncapableFix -> Encoding # toJSONList :: [IncapableFix] -> Value # toEncodingList :: [IncapableFix] -> Encoding # omitField :: IncapableFix -> Bool # | |||||
| Generic IncapableFix Source # | |||||
Defined in Swarm.Game.Exception Associated Types
| |||||
| Show IncapableFix Source # | |||||
Defined in Swarm.Game.Exception Methods showsPrec :: Int -> IncapableFix -> ShowS # show :: IncapableFix -> String # showList :: [IncapableFix] -> ShowS # | |||||
| Eq IncapableFix Source # | |||||
Defined in Swarm.Game.Exception | |||||
| type Rep IncapableFix Source # | |||||
Defined in Swarm.Game.Exception type Rep IncapableFix = D1 ('MetaData "IncapableFix" "Swarm.Game.Exception" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-engine" 'False) (C1 ('MetaCons "FixByEquip" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "FixByObtainDevice" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FixByObtainConsumables" 'PrefixI 'False) (U1 :: Type -> Type))) | |||||
formatExn :: EntityMap -> Exn -> Text Source #
Pretty-print an exception for displaying to the player.
exnSeverity :: Exn -> Severity Source #
data IncapableFixWords Source #
Constructors
| IncapableFixWords | |
Helper functions
formatIncapable :: EntityMap -> IncapableFix -> Requirements -> Term -> Text Source #
Pretty print the incapable exception with an actionable suggestion on how to fix it.
>>>import Data.Either (fromRight)>>>import Control.Carrier.Throw.Either (runThrow)>>>import Control.Algebra (run)>>>import Swarm.Failure (LoadingFailure)>>>import qualified Data.Set as S>>>:set -XTypeApplications>>>w = mkEntity (defaultEntityDisplay 'l') "magic wand" mempty mempty (S.singleton $ CExecute Appear)>>>r = mkEntity (defaultEntityDisplay 'o') "the one ring" mempty mempty (S.singleton $ CExecute Appear)>>>m = fromRight mempty . run . runThrow @LoadingFailure $ buildEntityMap [w,r]>>>incapableError cs t = putStr . unpack $ formatIncapable m FixByEquip cs t
>>>incapableError (R.singletonCap CGod) (TConst As)Thou shalt not utter such blasphemy: 'as' If God in troth thou wantest to play, try thou a Creative game.
>>>incapableError (R.singletonCap $ CExecute Appear) (TConst Appear)You do not have the device(s) required for: 'appear' Please equip: - magic wand or the one ring
>>>incapableError (R.singletonCap $ CExecute Random) (TConst Random)Missing the random capability for: 'random' but no device yet provides it. See https://github.com/swarm-game/swarm/issues/26
>>>incapableError (R.singletonInv 3 "tree") (TConst Noop)You are missing required inventory for: 'noop' Please obtain: - tree (3)
formatIncapableFix :: IncapableFix -> IncapableFixWords Source #
Pretty-print an IncapableFix: either "equip device",
"obtain device", or "obtain consumables".