{-# LANGUAGE OverloadedStrings #-}
module Swarm.Language.Syntax.Constants (
Const (..),
allConst,
ConstInfo (..),
ConstDoc (..),
ConstMeta (..),
MBinAssoc (..),
MUnAssoc (..),
constInfo,
arity,
isCmd,
isUserFunc,
isOperator,
isBuiltinFunction,
isTangible,
isLong,
maxSniffRange,
maxScoutRange,
maxStrideRange,
maxPathRange,
globalMaxVolume,
) where
import Data.Aeson.Types hiding (Key)
import Data.Data (Data)
import Data.Hashable (Hashable)
import Data.Int (Int32)
import Data.List.Extra (enumerate)
import Data.Set (Set)
import Data.Set qualified as Set
import Data.Text (Text)
import Data.Text qualified as T
import GHC.Generics (Generic)
import Prettyprinter (pretty)
import Swarm.Language.Syntax.CommandMetadata
import Swarm.Pretty (PrettyPrec (..), pparens)
import Swarm.Util (showT)
data Const
=
Noop
|
Wait
|
Selfdestruct
|
Move
|
Backup
|
Volume
|
Path
|
Push
|
Stride
|
Turn
|
Grab
|
Harvest
|
Sow
|
Ignite
|
Place
|
Ping
|
Give
|
Equip
|
Unequip
|
Make
|
Has
|
Equipped
|
Count
|
Drill
|
Use
|
Build
|
Salvage
|
Reprogram
|
Say
|
Listen
|
Log
|
View
|
Appear
|
Create
|
Halt
|
Time
|
Scout
|
Whereami
|
LocateMe
|
Waypoints
|
Structures
|
Floorplan
|
HasTag
|
TagMembers
|
Detect
|
Resonate
|
Density
|
Sniff
|
Chirp
|
Watch
|
Surveil
|
Heading
|
Blocked
|
Scan
|
Upload
|
Ishere
|
Isempty
|
Self
|
Parent
|
Base
|
Meet
|
MeetAll
|
Whoami
|
Setname
|
Random
|
Run
|
If
|
Inl
|
Inr
|
Case
|
Match
|
Force
|
Pure
|
Try
|
Undefined
|
Fail
|
Not
|
Neg
|
Eq
|
Neq
|
Lt
|
Gt
|
Leq
|
Geq
|
Or
|
And
|
Add
|
Sub
|
Mul
|
Div
|
Exp
|
Format
|
Read
|
Print
|
Erase
|
Concat
|
Chars
|
Split
|
CharAt
|
ToChar
|
AppF
|
Swap
|
Atomic
|
Instant
|
Key
|
InstallKeyHandler
|
Teleport
|
Warp
|
As
|
RobotNamed
|
RobotNumbered
|
Knows
deriving (Const -> Const -> Bool
(Const -> Const -> Bool) -> (Const -> Const -> Bool) -> Eq Const
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Const -> Const -> Bool
== :: Const -> Const -> Bool
$c/= :: Const -> Const -> Bool
/= :: Const -> Const -> Bool
Eq, Eq Const
Eq Const =>
(Const -> Const -> Ordering)
-> (Const -> Const -> Bool)
-> (Const -> Const -> Bool)
-> (Const -> Const -> Bool)
-> (Const -> Const -> Bool)
-> (Const -> Const -> Const)
-> (Const -> Const -> Const)
-> Ord Const
Const -> Const -> Bool
Const -> Const -> Ordering
Const -> Const -> Const
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Const -> Const -> Ordering
compare :: Const -> Const -> Ordering
$c< :: Const -> Const -> Bool
< :: Const -> Const -> Bool
$c<= :: Const -> Const -> Bool
<= :: Const -> Const -> Bool
$c> :: Const -> Const -> Bool
> :: Const -> Const -> Bool
$c>= :: Const -> Const -> Bool
>= :: Const -> Const -> Bool
$cmax :: Const -> Const -> Const
max :: Const -> Const -> Const
$cmin :: Const -> Const -> Const
min :: Const -> Const -> Const
Ord, Int -> Const
Const -> Int
Const -> [Const]
Const -> Const
Const -> Const -> [Const]
Const -> Const -> Const -> [Const]
(Const -> Const)
-> (Const -> Const)
-> (Int -> Const)
-> (Const -> Int)
-> (Const -> [Const])
-> (Const -> Const -> [Const])
-> (Const -> Const -> [Const])
-> (Const -> Const -> Const -> [Const])
-> Enum Const
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Const -> Const
succ :: Const -> Const
$cpred :: Const -> Const
pred :: Const -> Const
$ctoEnum :: Int -> Const
toEnum :: Int -> Const
$cfromEnum :: Const -> Int
fromEnum :: Const -> Int
$cenumFrom :: Const -> [Const]
enumFrom :: Const -> [Const]
$cenumFromThen :: Const -> Const -> [Const]
enumFromThen :: Const -> Const -> [Const]
$cenumFromTo :: Const -> Const -> [Const]
enumFromTo :: Const -> Const -> [Const]
$cenumFromThenTo :: Const -> Const -> Const -> [Const]
enumFromThenTo :: Const -> Const -> Const -> [Const]
Enum, Const
Const -> Const -> Bounded Const
forall a. a -> a -> Bounded a
$cminBound :: Const
minBound :: Const
$cmaxBound :: Const
maxBound :: Const
Bounded, Typeable Const
Typeable Const =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Const -> c Const)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Const)
-> (Const -> Constr)
-> (Const -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Const))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Const))
-> ((forall b. Data b => b -> b) -> Const -> Const)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Const -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Const -> r)
-> (forall u. (forall d. Data d => d -> u) -> Const -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Const -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Const -> m Const)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Const -> m Const)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Const -> m Const)
-> Data Const
Const -> Constr
Const -> DataType
(forall b. Data b => b -> b) -> Const -> Const
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Const -> u
forall u. (forall d. Data d => d -> u) -> Const -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Const -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Const -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Const -> m Const
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Const -> m Const
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Const
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Const -> c Const
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Const)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Const)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Const -> c Const
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Const -> c Const
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Const
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Const
$ctoConstr :: Const -> Constr
toConstr :: Const -> Constr
$cdataTypeOf :: Const -> DataType
dataTypeOf :: Const -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Const)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Const)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Const)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Const)
$cgmapT :: (forall b. Data b => b -> b) -> Const -> Const
gmapT :: (forall b. Data b => b -> b) -> Const -> Const
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Const -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Const -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Const -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Const -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Const -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Const -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Const -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Const -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Const -> m Const
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Const -> m Const
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Const -> m Const
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Const -> m Const
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Const -> m Const
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Const -> m Const
Data, Int -> Const -> ShowS
[Const] -> ShowS
Const -> [Char]
(Int -> Const -> ShowS)
-> (Const -> [Char]) -> ([Const] -> ShowS) -> Show Const
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Const -> ShowS
showsPrec :: Int -> Const -> ShowS
$cshow :: Const -> [Char]
show :: Const -> [Char]
$cshowList :: [Const] -> ShowS
showList :: [Const] -> ShowS
Show, (forall x. Const -> Rep Const x)
-> (forall x. Rep Const x -> Const) -> Generic Const
forall x. Rep Const x -> Const
forall x. Const -> Rep Const x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Const -> Rep Const x
from :: forall x. Const -> Rep Const x
$cto :: forall x. Rep Const x -> Const
to :: forall x. Rep Const x -> Const
Generic, Eq Const
Eq Const =>
(Int -> Const -> Int) -> (Const -> Int) -> Hashable Const
Int -> Const -> Int
Const -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> Const -> Int
hashWithSalt :: Int -> Const -> Int
$chash :: Const -> Int
hash :: Const -> Int
Hashable, Maybe Const
Value -> Parser [Const]
Value -> Parser Const
(Value -> Parser Const)
-> (Value -> Parser [Const]) -> Maybe Const -> FromJSON Const
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Const
parseJSON :: Value -> Parser Const
$cparseJSONList :: Value -> Parser [Const]
parseJSONList :: Value -> Parser [Const]
$comittedField :: Maybe Const
omittedField :: Maybe Const
FromJSON, [Const] -> Value
[Const] -> Encoding
Const -> Bool
Const -> Value
Const -> Encoding
(Const -> Value)
-> (Const -> Encoding)
-> ([Const] -> Value)
-> ([Const] -> Encoding)
-> (Const -> Bool)
-> ToJSON Const
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Const -> Value
toJSON :: Const -> Value
$ctoEncoding :: Const -> Encoding
toEncoding :: Const -> Encoding
$ctoJSONList :: [Const] -> Value
toJSONList :: [Const] -> Value
$ctoEncodingList :: [Const] -> Encoding
toEncodingList :: [Const] -> Encoding
$comitField :: Const -> Bool
omitField :: Const -> Bool
ToJSON, FromJSONKeyFunction [Const]
FromJSONKeyFunction Const
FromJSONKeyFunction Const
-> FromJSONKeyFunction [Const] -> FromJSONKey Const
forall a.
FromJSONKeyFunction a -> FromJSONKeyFunction [a] -> FromJSONKey a
$cfromJSONKey :: FromJSONKeyFunction Const
fromJSONKey :: FromJSONKeyFunction Const
$cfromJSONKeyList :: FromJSONKeyFunction [Const]
fromJSONKeyList :: FromJSONKeyFunction [Const]
FromJSONKey, ToJSONKeyFunction [Const]
ToJSONKeyFunction Const
ToJSONKeyFunction Const
-> ToJSONKeyFunction [Const] -> ToJSONKey Const
forall a.
ToJSONKeyFunction a -> ToJSONKeyFunction [a] -> ToJSONKey a
$ctoJSONKey :: ToJSONKeyFunction Const
toJSONKey :: ToJSONKeyFunction Const
$ctoJSONKeyList :: ToJSONKeyFunction [Const]
toJSONKeyList :: ToJSONKeyFunction [Const]
ToJSONKey)
instance PrettyPrec Const where
prettyPrec :: forall ann. Int -> Const -> Doc ann
prettyPrec Int
p Const
c = Bool -> Doc ann -> Doc ann
forall ann. Bool -> Doc ann -> Doc ann
pparens (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> ConstInfo -> Int
fixity (Const -> ConstInfo
constInfo Const
c)) (Doc ann -> Doc ann) -> Doc ann -> Doc ann
forall a b. (a -> b) -> a -> b
$ Text -> Doc ann
forall ann. Text -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (Text -> Doc ann) -> (Const -> Text) -> Const -> Doc ann
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConstInfo -> Text
syntax (ConstInfo -> Text) -> (Const -> ConstInfo) -> Const -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Const -> ConstInfo
constInfo (Const -> Doc ann) -> Const -> Doc ann
forall a b. (a -> b) -> a -> b
$ Const
c
allConst :: [Const]
allConst :: [Const]
allConst = [Const]
forall a. (Enum a, Bounded a) => [a]
enumerate
data ConstInfo = ConstInfo
{ ConstInfo -> Text
syntax :: Text
, ConstInfo -> Int
fixity :: Int
, ConstInfo -> ConstMeta
constMeta :: ConstMeta
, ConstInfo -> ConstDoc
constDoc :: ConstDoc
, ConstInfo -> Tangibility
tangibility :: Tangibility
}
deriving (ConstInfo -> ConstInfo -> Bool
(ConstInfo -> ConstInfo -> Bool)
-> (ConstInfo -> ConstInfo -> Bool) -> Eq ConstInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ConstInfo -> ConstInfo -> Bool
== :: ConstInfo -> ConstInfo -> Bool
$c/= :: ConstInfo -> ConstInfo -> Bool
/= :: ConstInfo -> ConstInfo -> Bool
Eq, Eq ConstInfo
Eq ConstInfo =>
(ConstInfo -> ConstInfo -> Ordering)
-> (ConstInfo -> ConstInfo -> Bool)
-> (ConstInfo -> ConstInfo -> Bool)
-> (ConstInfo -> ConstInfo -> Bool)
-> (ConstInfo -> ConstInfo -> Bool)
-> (ConstInfo -> ConstInfo -> ConstInfo)
-> (ConstInfo -> ConstInfo -> ConstInfo)
-> Ord ConstInfo
ConstInfo -> ConstInfo -> Bool
ConstInfo -> ConstInfo -> Ordering
ConstInfo -> ConstInfo -> ConstInfo
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ConstInfo -> ConstInfo -> Ordering
compare :: ConstInfo -> ConstInfo -> Ordering
$c< :: ConstInfo -> ConstInfo -> Bool
< :: ConstInfo -> ConstInfo -> Bool
$c<= :: ConstInfo -> ConstInfo -> Bool
<= :: ConstInfo -> ConstInfo -> Bool
$c> :: ConstInfo -> ConstInfo -> Bool
> :: ConstInfo -> ConstInfo -> Bool
$c>= :: ConstInfo -> ConstInfo -> Bool
>= :: ConstInfo -> ConstInfo -> Bool
$cmax :: ConstInfo -> ConstInfo -> ConstInfo
max :: ConstInfo -> ConstInfo -> ConstInfo
$cmin :: ConstInfo -> ConstInfo -> ConstInfo
min :: ConstInfo -> ConstInfo -> ConstInfo
Ord, Int -> ConstInfo -> ShowS
[ConstInfo] -> ShowS
ConstInfo -> [Char]
(Int -> ConstInfo -> ShowS)
-> (ConstInfo -> [Char])
-> ([ConstInfo] -> ShowS)
-> Show ConstInfo
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ConstInfo -> ShowS
showsPrec :: Int -> ConstInfo -> ShowS
$cshow :: ConstInfo -> [Char]
show :: ConstInfo -> [Char]
$cshowList :: [ConstInfo] -> ShowS
showList :: [ConstInfo] -> ShowS
Show)
data ConstDoc = ConstDoc
{ ConstDoc -> Set CommandEffect
effectInfo :: Set CommandEffect
, ConstDoc -> Text
briefDoc :: Text
, ConstDoc -> Text
longDoc :: Text
}
deriving (ConstDoc -> ConstDoc -> Bool
(ConstDoc -> ConstDoc -> Bool)
-> (ConstDoc -> ConstDoc -> Bool) -> Eq ConstDoc
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ConstDoc -> ConstDoc -> Bool
== :: ConstDoc -> ConstDoc -> Bool
$c/= :: ConstDoc -> ConstDoc -> Bool
/= :: ConstDoc -> ConstDoc -> Bool
Eq, Eq ConstDoc
Eq ConstDoc =>
(ConstDoc -> ConstDoc -> Ordering)
-> (ConstDoc -> ConstDoc -> Bool)
-> (ConstDoc -> ConstDoc -> Bool)
-> (ConstDoc -> ConstDoc -> Bool)
-> (ConstDoc -> ConstDoc -> Bool)
-> (ConstDoc -> ConstDoc -> ConstDoc)
-> (ConstDoc -> ConstDoc -> ConstDoc)
-> Ord ConstDoc
ConstDoc -> ConstDoc -> Bool
ConstDoc -> ConstDoc -> Ordering
ConstDoc -> ConstDoc -> ConstDoc
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ConstDoc -> ConstDoc -> Ordering
compare :: ConstDoc -> ConstDoc -> Ordering
$c< :: ConstDoc -> ConstDoc -> Bool
< :: ConstDoc -> ConstDoc -> Bool
$c<= :: ConstDoc -> ConstDoc -> Bool
<= :: ConstDoc -> ConstDoc -> Bool
$c> :: ConstDoc -> ConstDoc -> Bool
> :: ConstDoc -> ConstDoc -> Bool
$c>= :: ConstDoc -> ConstDoc -> Bool
>= :: ConstDoc -> ConstDoc -> Bool
$cmax :: ConstDoc -> ConstDoc -> ConstDoc
max :: ConstDoc -> ConstDoc -> ConstDoc
$cmin :: ConstDoc -> ConstDoc -> ConstDoc
min :: ConstDoc -> ConstDoc -> ConstDoc
Ord, Int -> ConstDoc -> ShowS
[ConstDoc] -> ShowS
ConstDoc -> [Char]
(Int -> ConstDoc -> ShowS)
-> (ConstDoc -> [Char]) -> ([ConstDoc] -> ShowS) -> Show ConstDoc
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ConstDoc -> ShowS
showsPrec :: Int -> ConstDoc -> ShowS
$cshow :: ConstDoc -> [Char]
show :: ConstDoc -> [Char]
$cshowList :: [ConstDoc] -> ShowS
showList :: [ConstDoc] -> ShowS
Show)
data ConstMeta
=
ConstMFunc
Int
Bool
|
ConstMUnOp MUnAssoc
|
ConstMBinOp MBinAssoc
deriving (ConstMeta -> ConstMeta -> Bool
(ConstMeta -> ConstMeta -> Bool)
-> (ConstMeta -> ConstMeta -> Bool) -> Eq ConstMeta
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ConstMeta -> ConstMeta -> Bool
== :: ConstMeta -> ConstMeta -> Bool
$c/= :: ConstMeta -> ConstMeta -> Bool
/= :: ConstMeta -> ConstMeta -> Bool
Eq, Eq ConstMeta
Eq ConstMeta =>
(ConstMeta -> ConstMeta -> Ordering)
-> (ConstMeta -> ConstMeta -> Bool)
-> (ConstMeta -> ConstMeta -> Bool)
-> (ConstMeta -> ConstMeta -> Bool)
-> (ConstMeta -> ConstMeta -> Bool)
-> (ConstMeta -> ConstMeta -> ConstMeta)
-> (ConstMeta -> ConstMeta -> ConstMeta)
-> Ord ConstMeta
ConstMeta -> ConstMeta -> Bool
ConstMeta -> ConstMeta -> Ordering
ConstMeta -> ConstMeta -> ConstMeta
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ConstMeta -> ConstMeta -> Ordering
compare :: ConstMeta -> ConstMeta -> Ordering
$c< :: ConstMeta -> ConstMeta -> Bool
< :: ConstMeta -> ConstMeta -> Bool
$c<= :: ConstMeta -> ConstMeta -> Bool
<= :: ConstMeta -> ConstMeta -> Bool
$c> :: ConstMeta -> ConstMeta -> Bool
> :: ConstMeta -> ConstMeta -> Bool
$c>= :: ConstMeta -> ConstMeta -> Bool
>= :: ConstMeta -> ConstMeta -> Bool
$cmax :: ConstMeta -> ConstMeta -> ConstMeta
max :: ConstMeta -> ConstMeta -> ConstMeta
$cmin :: ConstMeta -> ConstMeta -> ConstMeta
min :: ConstMeta -> ConstMeta -> ConstMeta
Ord, Int -> ConstMeta -> ShowS
[ConstMeta] -> ShowS
ConstMeta -> [Char]
(Int -> ConstMeta -> ShowS)
-> (ConstMeta -> [Char])
-> ([ConstMeta] -> ShowS)
-> Show ConstMeta
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ConstMeta -> ShowS
showsPrec :: Int -> ConstMeta -> ShowS
$cshow :: ConstMeta -> [Char]
show :: ConstMeta -> [Char]
$cshowList :: [ConstMeta] -> ShowS
showList :: [ConstMeta] -> ShowS
Show)
data MBinAssoc
=
L
|
N
|
R
deriving (MBinAssoc -> MBinAssoc -> Bool
(MBinAssoc -> MBinAssoc -> Bool)
-> (MBinAssoc -> MBinAssoc -> Bool) -> Eq MBinAssoc
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MBinAssoc -> MBinAssoc -> Bool
== :: MBinAssoc -> MBinAssoc -> Bool
$c/= :: MBinAssoc -> MBinAssoc -> Bool
/= :: MBinAssoc -> MBinAssoc -> Bool
Eq, Eq MBinAssoc
Eq MBinAssoc =>
(MBinAssoc -> MBinAssoc -> Ordering)
-> (MBinAssoc -> MBinAssoc -> Bool)
-> (MBinAssoc -> MBinAssoc -> Bool)
-> (MBinAssoc -> MBinAssoc -> Bool)
-> (MBinAssoc -> MBinAssoc -> Bool)
-> (MBinAssoc -> MBinAssoc -> MBinAssoc)
-> (MBinAssoc -> MBinAssoc -> MBinAssoc)
-> Ord MBinAssoc
MBinAssoc -> MBinAssoc -> Bool
MBinAssoc -> MBinAssoc -> Ordering
MBinAssoc -> MBinAssoc -> MBinAssoc
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: MBinAssoc -> MBinAssoc -> Ordering
compare :: MBinAssoc -> MBinAssoc -> Ordering
$c< :: MBinAssoc -> MBinAssoc -> Bool
< :: MBinAssoc -> MBinAssoc -> Bool
$c<= :: MBinAssoc -> MBinAssoc -> Bool
<= :: MBinAssoc -> MBinAssoc -> Bool
$c> :: MBinAssoc -> MBinAssoc -> Bool
> :: MBinAssoc -> MBinAssoc -> Bool
$c>= :: MBinAssoc -> MBinAssoc -> Bool
>= :: MBinAssoc -> MBinAssoc -> Bool
$cmax :: MBinAssoc -> MBinAssoc -> MBinAssoc
max :: MBinAssoc -> MBinAssoc -> MBinAssoc
$cmin :: MBinAssoc -> MBinAssoc -> MBinAssoc
min :: MBinAssoc -> MBinAssoc -> MBinAssoc
Ord, Int -> MBinAssoc -> ShowS
[MBinAssoc] -> ShowS
MBinAssoc -> [Char]
(Int -> MBinAssoc -> ShowS)
-> (MBinAssoc -> [Char])
-> ([MBinAssoc] -> ShowS)
-> Show MBinAssoc
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MBinAssoc -> ShowS
showsPrec :: Int -> MBinAssoc -> ShowS
$cshow :: MBinAssoc -> [Char]
show :: MBinAssoc -> [Char]
$cshowList :: [MBinAssoc] -> ShowS
showList :: [MBinAssoc] -> ShowS
Show)
data MUnAssoc
=
P
|
S
deriving (MUnAssoc -> MUnAssoc -> Bool
(MUnAssoc -> MUnAssoc -> Bool)
-> (MUnAssoc -> MUnAssoc -> Bool) -> Eq MUnAssoc
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MUnAssoc -> MUnAssoc -> Bool
== :: MUnAssoc -> MUnAssoc -> Bool
$c/= :: MUnAssoc -> MUnAssoc -> Bool
/= :: MUnAssoc -> MUnAssoc -> Bool
Eq, Eq MUnAssoc
Eq MUnAssoc =>
(MUnAssoc -> MUnAssoc -> Ordering)
-> (MUnAssoc -> MUnAssoc -> Bool)
-> (MUnAssoc -> MUnAssoc -> Bool)
-> (MUnAssoc -> MUnAssoc -> Bool)
-> (MUnAssoc -> MUnAssoc -> Bool)
-> (MUnAssoc -> MUnAssoc -> MUnAssoc)
-> (MUnAssoc -> MUnAssoc -> MUnAssoc)
-> Ord MUnAssoc
MUnAssoc -> MUnAssoc -> Bool
MUnAssoc -> MUnAssoc -> Ordering
MUnAssoc -> MUnAssoc -> MUnAssoc
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: MUnAssoc -> MUnAssoc -> Ordering
compare :: MUnAssoc -> MUnAssoc -> Ordering
$c< :: MUnAssoc -> MUnAssoc -> Bool
< :: MUnAssoc -> MUnAssoc -> Bool
$c<= :: MUnAssoc -> MUnAssoc -> Bool
<= :: MUnAssoc -> MUnAssoc -> Bool
$c> :: MUnAssoc -> MUnAssoc -> Bool
> :: MUnAssoc -> MUnAssoc -> Bool
$c>= :: MUnAssoc -> MUnAssoc -> Bool
>= :: MUnAssoc -> MUnAssoc -> Bool
$cmax :: MUnAssoc -> MUnAssoc -> MUnAssoc
max :: MUnAssoc -> MUnAssoc -> MUnAssoc
$cmin :: MUnAssoc -> MUnAssoc -> MUnAssoc
min :: MUnAssoc -> MUnAssoc -> MUnAssoc
Ord, Int -> MUnAssoc -> ShowS
[MUnAssoc] -> ShowS
MUnAssoc -> [Char]
(Int -> MUnAssoc -> ShowS)
-> (MUnAssoc -> [Char]) -> ([MUnAssoc] -> ShowS) -> Show MUnAssoc
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MUnAssoc -> ShowS
showsPrec :: Int -> MUnAssoc -> ShowS
$cshow :: MUnAssoc -> [Char]
show :: MUnAssoc -> [Char]
$cshowList :: [MUnAssoc] -> ShowS
showList :: [MUnAssoc] -> ShowS
Show)
data Tangibility = Intangible | Tangible Length
deriving (Tangibility -> Tangibility -> Bool
(Tangibility -> Tangibility -> Bool)
-> (Tangibility -> Tangibility -> Bool) -> Eq Tangibility
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Tangibility -> Tangibility -> Bool
== :: Tangibility -> Tangibility -> Bool
$c/= :: Tangibility -> Tangibility -> Bool
/= :: Tangibility -> Tangibility -> Bool
Eq, Eq Tangibility
Eq Tangibility =>
(Tangibility -> Tangibility -> Ordering)
-> (Tangibility -> Tangibility -> Bool)
-> (Tangibility -> Tangibility -> Bool)
-> (Tangibility -> Tangibility -> Bool)
-> (Tangibility -> Tangibility -> Bool)
-> (Tangibility -> Tangibility -> Tangibility)
-> (Tangibility -> Tangibility -> Tangibility)
-> Ord Tangibility
Tangibility -> Tangibility -> Bool
Tangibility -> Tangibility -> Ordering
Tangibility -> Tangibility -> Tangibility
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Tangibility -> Tangibility -> Ordering
compare :: Tangibility -> Tangibility -> Ordering
$c< :: Tangibility -> Tangibility -> Bool
< :: Tangibility -> Tangibility -> Bool
$c<= :: Tangibility -> Tangibility -> Bool
<= :: Tangibility -> Tangibility -> Bool
$c> :: Tangibility -> Tangibility -> Bool
> :: Tangibility -> Tangibility -> Bool
$c>= :: Tangibility -> Tangibility -> Bool
>= :: Tangibility -> Tangibility -> Bool
$cmax :: Tangibility -> Tangibility -> Tangibility
max :: Tangibility -> Tangibility -> Tangibility
$cmin :: Tangibility -> Tangibility -> Tangibility
min :: Tangibility -> Tangibility -> Tangibility
Ord, Int -> Tangibility -> ShowS
[Tangibility] -> ShowS
Tangibility -> [Char]
(Int -> Tangibility -> ShowS)
-> (Tangibility -> [Char])
-> ([Tangibility] -> ShowS)
-> Show Tangibility
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Tangibility -> ShowS
showsPrec :: Int -> Tangibility -> ShowS
$cshow :: Tangibility -> [Char]
show :: Tangibility -> [Char]
$cshowList :: [Tangibility] -> ShowS
showList :: [Tangibility] -> ShowS
Show, ReadPrec [Tangibility]
ReadPrec Tangibility
Int -> ReadS Tangibility
ReadS [Tangibility]
(Int -> ReadS Tangibility)
-> ReadS [Tangibility]
-> ReadPrec Tangibility
-> ReadPrec [Tangibility]
-> Read Tangibility
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Tangibility
readsPrec :: Int -> ReadS Tangibility
$creadList :: ReadS [Tangibility]
readList :: ReadS [Tangibility]
$creadPrec :: ReadPrec Tangibility
readPrec :: ReadPrec Tangibility
$creadListPrec :: ReadPrec [Tangibility]
readListPrec :: ReadPrec [Tangibility]
Read)
short :: Tangibility
short :: Tangibility
short = Length -> Tangibility
Tangible Length
Short
long :: Tangibility
long :: Tangibility
long = Length -> Tangibility
Tangible Length
Long
data Length = Short | Long
deriving (Length -> Length -> Bool
(Length -> Length -> Bool)
-> (Length -> Length -> Bool) -> Eq Length
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Length -> Length -> Bool
== :: Length -> Length -> Bool
$c/= :: Length -> Length -> Bool
/= :: Length -> Length -> Bool
Eq, Eq Length
Eq Length =>
(Length -> Length -> Ordering)
-> (Length -> Length -> Bool)
-> (Length -> Length -> Bool)
-> (Length -> Length -> Bool)
-> (Length -> Length -> Bool)
-> (Length -> Length -> Length)
-> (Length -> Length -> Length)
-> Ord Length
Length -> Length -> Bool
Length -> Length -> Ordering
Length -> Length -> Length
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Length -> Length -> Ordering
compare :: Length -> Length -> Ordering
$c< :: Length -> Length -> Bool
< :: Length -> Length -> Bool
$c<= :: Length -> Length -> Bool
<= :: Length -> Length -> Bool
$c> :: Length -> Length -> Bool
> :: Length -> Length -> Bool
$c>= :: Length -> Length -> Bool
>= :: Length -> Length -> Bool
$cmax :: Length -> Length -> Length
max :: Length -> Length -> Length
$cmin :: Length -> Length -> Length
min :: Length -> Length -> Length
Ord, Int -> Length -> ShowS
[Length] -> ShowS
Length -> [Char]
(Int -> Length -> ShowS)
-> (Length -> [Char]) -> ([Length] -> ShowS) -> Show Length
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Length -> ShowS
showsPrec :: Int -> Length -> ShowS
$cshow :: Length -> [Char]
show :: Length -> [Char]
$cshowList :: [Length] -> ShowS
showList :: [Length] -> ShowS
Show, ReadPrec [Length]
ReadPrec Length
Int -> ReadS Length
ReadS [Length]
(Int -> ReadS Length)
-> ReadS [Length]
-> ReadPrec Length
-> ReadPrec [Length]
-> Read Length
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Length
readsPrec :: Int -> ReadS Length
$creadList :: ReadS [Length]
readList :: ReadS [Length]
$creadPrec :: ReadPrec Length
readPrec :: ReadPrec Length
$creadListPrec :: ReadPrec [Length]
readListPrec :: ReadPrec [Length]
Read, Length
Length -> Length -> Bounded Length
forall a. a -> a -> Bounded a
$cminBound :: Length
minBound :: Length
$cmaxBound :: Length
maxBound :: Length
Bounded, Int -> Length
Length -> Int
Length -> [Length]
Length -> Length
Length -> Length -> [Length]
Length -> Length -> Length -> [Length]
(Length -> Length)
-> (Length -> Length)
-> (Int -> Length)
-> (Length -> Int)
-> (Length -> [Length])
-> (Length -> Length -> [Length])
-> (Length -> Length -> [Length])
-> (Length -> Length -> Length -> [Length])
-> Enum Length
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Length -> Length
succ :: Length -> Length
$cpred :: Length -> Length
pred :: Length -> Length
$ctoEnum :: Int -> Length
toEnum :: Int -> Length
$cfromEnum :: Length -> Int
fromEnum :: Length -> Int
$cenumFrom :: Length -> [Length]
enumFrom :: Length -> [Length]
$cenumFromThen :: Length -> Length -> [Length]
enumFromThen :: Length -> Length -> [Length]
$cenumFromTo :: Length -> Length -> [Length]
enumFromTo :: Length -> Length -> [Length]
$cenumFromThenTo :: Length -> Length -> Length -> [Length]
enumFromThenTo :: Length -> Length -> Length -> [Length]
Enum)
arity :: Const -> Int
arity :: Const -> Int
arity Const
c = case ConstInfo -> ConstMeta
constMeta (ConstInfo -> ConstMeta) -> ConstInfo -> ConstMeta
forall a b. (a -> b) -> a -> b
$ Const -> ConstInfo
constInfo Const
c of
ConstMUnOp {} -> Int
1
ConstMBinOp {} -> Int
2
ConstMFunc Int
a Bool
_ -> Int
a
isCmd :: Const -> Bool
isCmd :: Const -> Bool
isCmd Const
c = case ConstInfo -> ConstMeta
constMeta (ConstInfo -> ConstMeta) -> ConstInfo -> ConstMeta
forall a b. (a -> b) -> a -> b
$ Const -> ConstInfo
constInfo Const
c of
ConstMFunc Int
_ Bool
cmd -> Bool
cmd
ConstMeta
_ -> Bool
False
isUserFunc :: Const -> Bool
isUserFunc :: Const -> Bool
isUserFunc Const
c = case ConstInfo -> ConstMeta
constMeta (ConstInfo -> ConstMeta) -> ConstInfo -> ConstMeta
forall a b. (a -> b) -> a -> b
$ Const -> ConstInfo
constInfo Const
c of
ConstMFunc {} -> Bool
True
ConstMeta
_ -> Bool
False
isOperator :: Const -> Bool
isOperator :: Const -> Bool
isOperator Const
c = case ConstInfo -> ConstMeta
constMeta (ConstInfo -> ConstMeta) -> ConstInfo -> ConstMeta
forall a b. (a -> b) -> a -> b
$ Const -> ConstInfo
constInfo Const
c of
ConstMUnOp {} -> Bool
True
ConstMBinOp {} -> Bool
True
ConstMFunc {} -> Bool
False
isBuiltinFunction :: Const -> Bool
isBuiltinFunction :: Const -> Bool
isBuiltinFunction Const
c = case ConstInfo -> ConstMeta
constMeta (ConstInfo -> ConstMeta) -> ConstInfo -> ConstMeta
forall a b. (a -> b) -> a -> b
$ Const -> ConstInfo
constInfo Const
c of
ConstMFunc Int
_ Bool
cmd -> Bool -> Bool
not Bool
cmd
ConstMeta
_ -> Bool
False
isTangible :: Const -> Bool
isTangible :: Const -> Bool
isTangible Const
c = case ConstInfo -> Tangibility
tangibility (Const -> ConstInfo
constInfo Const
c) of
Tangible {} -> Bool
True
Tangibility
_ -> Bool
False
isLong :: Const -> Bool
isLong :: Const -> Bool
isLong Const
c = case ConstInfo -> Tangibility
tangibility (Const -> ConstInfo
constInfo Const
c) of
Tangible Length
Long -> Bool
True
Tangibility
_ -> Bool
False
constInfo :: Const -> ConstInfo
constInfo :: Const -> ConstInfo
constInfo Const
c = case Const
c of
Const
Wait ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
0 Tangibility
long (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$
Set CommandEffect -> Text -> ConstDoc
shortDoc
(CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ MutationType -> CommandEffect
Mutation (MutationType -> CommandEffect) -> MutationType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ RobotChangeType -> MutationType
RobotChange RobotChangeType
BehaviorChange)
Text
"Wait for a number of time steps."
Const
Noop ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
0 Tangibility
Intangible (ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc Set CommandEffect
forall a. Set a
Set.empty Text
"Do nothing." ([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$
[ Text
"This is different than `Wait` in that it does not take up a time step."
, Text
"It is useful for commands like if, which requires you to provide both branches."
, Text
"Usually it is automatically inserted where needed, so you do not have to worry about it."
]
Const
Selfdestruct ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
0 Tangibility
short
(ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc
(CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ MutationType -> CommandEffect
Mutation (MutationType -> CommandEffect) -> MutationType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ RobotChangeType -> MutationType
RobotChange RobotChangeType
ExistenceChange)
Text
"Self-destruct a robot."
([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$ [ Text
"Useful to not clutter the world."
, Text
"This destroys the robot's inventory, so consider `salvage` as an alternative."
]
Const
Move ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
0 Tangibility
short (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$
Set CommandEffect -> Text -> ConstDoc
shortDoc
(CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ MutationType -> CommandEffect
Mutation (MutationType -> CommandEffect) -> MutationType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ RobotChangeType -> MutationType
RobotChange RobotChangeType
PositionChange)
Text
"Move forward one step."
Const
Backup ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
0 Tangibility
short (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$
Set CommandEffect -> Text -> ConstDoc
shortDoc
(CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ MutationType -> CommandEffect
Mutation (MutationType -> CommandEffect) -> MutationType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ RobotChangeType -> MutationType
RobotChange RobotChangeType
PositionChange)
Text
"Move backward one step."
Const
Volume ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
short
(ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc
(CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ QueryType -> CommandEffect
Query (QueryType -> CommandEffect) -> QueryType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ SensingType -> QueryType
Sensing SensingType
EntitySensing)
Text
"Measure enclosed volume."
([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$ [ Text
"Specify the max volume to check for."
, Text
"Returns either the measured volume bounded by \"unwalkable\" cells,"
, Text
"or `unit` if the search exceeds the limit."
, [Text] -> Text
T.unwords
[ Text
"There is also an implicit hard-coded maximum of"
, [Char] -> Text
T.pack ([Char] -> Text) -> [Char] -> Text
forall a b. (a -> b) -> a -> b
$ Integer -> [Char]
forall a. Show a => a -> [Char]
show Integer
globalMaxVolume
]
]
Const
Path ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
2 Tangibility
short
(ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc
(CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ QueryType -> CommandEffect
Query (QueryType -> CommandEffect) -> QueryType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ SensingType -> QueryType
Sensing SensingType
EntitySensing)
Text
"Obtain shortest path to the destination."
([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$ [ Text
"Optionally supply a distance limit as the first argument."
, Text
"Supply either a location (`inL`) or an entity (`inR`) as the second argument."
, Text
"If a path exists, returns the immediate direction to proceed along and the remaining distance."
]
Const
Push ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
short
(ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc
([CommandEffect] -> Set CommandEffect
forall a. Ord a => [a] -> Set a
Set.fromList [MutationType -> CommandEffect
Mutation MutationType
EntityChange, MutationType -> CommandEffect
Mutation (MutationType -> CommandEffect) -> MutationType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ RobotChangeType -> MutationType
RobotChange RobotChangeType
PositionChange])
Text
"Push an entity forward one step."
([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$ [ Text
"Both entity and robot moves forward one step."
, Text
"Destination must not contain an entity."
]
Const
Stride ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
short
(ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc
(CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ MutationType -> CommandEffect
Mutation (MutationType -> CommandEffect) -> MutationType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ RobotChangeType -> MutationType
RobotChange RobotChangeType
PositionChange)
Text
"Move forward multiple steps."
([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$ [ [Text] -> Text
T.unwords [Text
"Has a max range of", [Char] -> Text
T.pack ([Char] -> Text) -> [Char] -> Text
forall a b. (a -> b) -> a -> b
$ Int -> [Char]
forall a. Show a => a -> [Char]
show Int
maxStrideRange, Text
"units."]
]
Const
Turn ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
short (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$
Set CommandEffect -> Text -> ConstDoc
shortDoc
(CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ MutationType -> CommandEffect
Mutation (MutationType -> CommandEffect) -> MutationType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ RobotChangeType -> MutationType
RobotChange RobotChangeType
PositionChange)
Text
"Turn in some direction."
Const
Grab ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
0 Tangibility
short (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$
Set CommandEffect -> Text -> ConstDoc
shortDoc
([CommandEffect] -> Set CommandEffect
forall a. Ord a => [a] -> Set a
Set.fromList [MutationType -> CommandEffect
Mutation MutationType
EntityChange, MutationType -> CommandEffect
Mutation (MutationType -> CommandEffect) -> MutationType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ RobotChangeType -> MutationType
RobotChange RobotChangeType
InventoryChange])
Text
"Grab an item from the current location."
Const
Harvest ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
0 Tangibility
short (ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc ([CommandEffect] -> Set CommandEffect
forall a. Ord a => [a] -> Set a
Set.fromList [MutationType -> CommandEffect
Mutation MutationType
EntityChange, MutationType -> CommandEffect
Mutation (MutationType -> CommandEffect) -> MutationType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ RobotChangeType -> MutationType
RobotChange RobotChangeType
InventoryChange]) Text
"Harvest an item from the current location." ([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$
[ Text
"Leaves behind a growing seed if the harvested item is growable."
, Text
"Otherwise it works exactly like `grab`."
]
Const
Sow ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
short (ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ MutationType -> CommandEffect
Mutation MutationType
EntityChange) Text
"Plant a seed at current location" ([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$
[ Text
"The entity this matures into may be something else."
]
Const
Ignite ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
short
(ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc
(CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ MutationType -> CommandEffect
Mutation MutationType
EntityChange)
Text
"Ignite a combustible item in the specified direction."
([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$ [ Text
"Combustion persists for a random duration and may spread."
]
Const
Place ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
short
(ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc
([CommandEffect] -> Set CommandEffect
forall a. Ord a => [a] -> Set a
Set.fromList [MutationType -> CommandEffect
Mutation MutationType
EntityChange, MutationType -> CommandEffect
Mutation (MutationType -> CommandEffect) -> MutationType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ RobotChangeType -> MutationType
RobotChange RobotChangeType
InventoryChange])
Text
"Place an item at the current location."
([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$ [Text
"The current location has to be empty for this to work."]
Const
Ping ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
short
(ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc
(CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ QueryType -> CommandEffect
Query (QueryType -> CommandEffect) -> QueryType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ SensingType -> QueryType
Sensing SensingType
RobotSensing)
Text
"Obtain the relative location of another robot."
([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$ [ Text
"The other robot must be within transmission range, accounting for antennas installed on either end, and the invoking robot must be oriented in a cardinal direction."
, Text
"The location (x, y) is given relative to one's current orientation:"
, Text
"Positive x value is to the right, negative left. Likewise, positive y value is forward, negative back."
]
Const
Give ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
2 Tangibility
short (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$
Set CommandEffect -> Text -> ConstDoc
shortDoc
(CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ MutationType -> CommandEffect
Mutation (MutationType -> CommandEffect) -> MutationType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ RobotChangeType -> MutationType
RobotChange RobotChangeType
InventoryChange)
Text
"Give an item to another actor nearby."
Const
Equip ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
short (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$
Set CommandEffect -> Text -> ConstDoc
shortDoc
([CommandEffect] -> Set CommandEffect
forall a. Ord a => [a] -> Set a
Set.fromList [MutationType -> CommandEffect
Mutation (MutationType -> CommandEffect) -> MutationType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ RobotChangeType -> MutationType
RobotChange RobotChangeType
InventoryChange, MutationType -> CommandEffect
Mutation (MutationType -> CommandEffect) -> MutationType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ RobotChangeType -> MutationType
RobotChange RobotChangeType
BehaviorChange])
Text
"Equip a device on oneself."
Const
Unequip ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
short (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$
Set CommandEffect -> Text -> ConstDoc
shortDoc
([CommandEffect] -> Set CommandEffect
forall a. Ord a => [a] -> Set a
Set.fromList [MutationType -> CommandEffect
Mutation (MutationType -> CommandEffect) -> MutationType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ RobotChangeType -> MutationType
RobotChange RobotChangeType
InventoryChange, MutationType -> CommandEffect
Mutation (MutationType -> CommandEffect) -> MutationType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ RobotChangeType -> MutationType
RobotChange RobotChangeType
BehaviorChange])
Text
"Unequip an equipped device, returning to inventory."
Const
Make ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
long (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$
Set CommandEffect -> Text -> ConstDoc
shortDoc
(CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ MutationType -> CommandEffect
Mutation (MutationType -> CommandEffect) -> MutationType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ RobotChangeType -> MutationType
RobotChange RobotChangeType
InventoryChange)
Text
"Make an item using a recipe."
Const
Has ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
Intangible (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$
Set CommandEffect -> Text -> ConstDoc
shortDoc
(CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ QueryType -> CommandEffect
Query (QueryType -> CommandEffect) -> QueryType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ SensingType -> QueryType
Sensing SensingType
RobotSensing)
Text
"Sense whether the robot has a given item in its inventory."
Const
Equipped ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
Intangible (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$
Set CommandEffect -> Text -> ConstDoc
shortDoc
(CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ QueryType -> CommandEffect
Query (QueryType -> CommandEffect) -> QueryType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ SensingType -> QueryType
Sensing SensingType
RobotSensing)
Text
"Sense whether the robot has a specific device equipped."
Const
Count ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
Intangible (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$
Set CommandEffect -> Text -> ConstDoc
shortDoc
(CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ QueryType -> CommandEffect
Query (QueryType -> CommandEffect) -> QueryType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ SensingType -> QueryType
Sensing SensingType
RobotSensing)
Text
"Get the count of a given item in a robot's inventory."
Const
Reprogram ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
2 Tangibility
long
(ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc
(CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ MutationType -> CommandEffect
Mutation (MutationType -> CommandEffect) -> MutationType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ RobotChangeType -> MutationType
RobotChange RobotChangeType
BehaviorChange)
Text
"Reprogram another robot with a new command."
([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$ [Text
"The other robot has to be nearby and idle."]
Const
Drill ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
long
(ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc
([CommandEffect] -> Set CommandEffect
forall a. Ord a => [a] -> Set a
Set.fromList [MutationType -> CommandEffect
Mutation MutationType
EntityChange, MutationType -> CommandEffect
Mutation (MutationType -> CommandEffect) -> MutationType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ RobotChangeType -> MutationType
RobotChange RobotChangeType
InventoryChange])
Text
"Drill through an entity."
([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$ [ Text
"Usually you want to `drill forward` when exploring to clear out obstacles."
, Text
"When you have found a source to drill, you can stand on it and `drill down`."
, Text
"See what recipes with drill you have available."
, Text
"The `drill` command may return the name of an entity added to your inventory."
]
Const
Use ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
2 Tangibility
long (ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ MutationType -> CommandEffect
Mutation MutationType
EntityChange) Text
"Use one entity upon another." ([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$
[ Text
"Which entities you can `use` with others depends on the available recipes."
, Text
"The object being used must be a 'stocked' entity in a recipe."
]
Const
Build ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
long (ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ MutationType -> CommandEffect
Mutation (MutationType -> CommandEffect) -> MutationType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ RobotChangeType -> MutationType
RobotChange RobotChangeType
ExistenceChange) Text
"Construct a new robot." ([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$
[ Text
"You can specify a command for the robot to execute."
, Text
"If the command requires devices they will be taken from your inventory and "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"equipped on the new robot."
]
Const
Salvage ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
0 Tangibility
long (ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ MutationType -> CommandEffect
Mutation (MutationType -> CommandEffect) -> MutationType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ RobotChangeType -> MutationType
RobotChange RobotChangeType
ExistenceChange) Text
"Deconstruct an old robot." ([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$
[Text
"Salvaging a robot will give you its inventory, equipped devices and log."]
Const
Say ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
short (ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ MutationType -> CommandEffect
Mutation (MutationType -> CommandEffect) -> MutationType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ RobotChangeType -> MutationType
RobotChange RobotChangeType
BehaviorChange) Text
"Emit a message." ([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$
[ Text
"The message will be in the robot's log (if it has one) and the global log."
, Text
"You can view the message that would be picked by `listen` from the global log "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"in the messages panel, along with your own messages and logs."
, Text
"This means that to see messages from other robots you have to be able to listen for them, "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"so once you have a listening device equipped messages will be added to your log."
, Text
"In creative mode, there is of course no such limitation."
]
Const
Listen ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
long (ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ QueryType -> CommandEffect
Query (QueryType -> CommandEffect) -> QueryType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ SensingType -> QueryType
Sensing SensingType
RobotSensing) Text
"Listen for a message from other actors." ([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$
[ Text
"It will take the first message said by the closest actor."
, Text
"You do not need to actively listen for the message to be logged though, "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"that is done automatically once you have a listening device equipped."
, Text
"Note that you can see the messages either in your logger device or the message panel."
]
Const
Log -> Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
Intangible (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ MutationType -> CommandEffect
Mutation MutationType
LogEmission) Text
"Log the string in the robot's logger."
Const
View ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
short (ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ QueryType -> CommandEffect
Query (QueryType -> CommandEffect) -> QueryType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ SensingType -> QueryType
Sensing SensingType
RobotSensing) Text
"View the given actor." ([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$
[ Text
"This will recenter the map on the target robot and allow its inventory and logs to be inspected."
]
Const
Appear ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
2 Tangibility
short (ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ MutationType -> CommandEffect
Mutation MutationType
Cosmetic) Text
"Set how the robot is displayed." ([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$
[ Text
"You can either specify one character or five (one for each direction: down, north, east, south, west)."
, Text
"The default is \"X^>v<\"."
, Text
"The second argument is for optionally setting a display attribute (i.e. color)."
]
Const
Create ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
short (ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc ([CommandEffect] -> Set CommandEffect
forall a. Ord a => [a] -> Set a
Set.fromList [MutationType -> CommandEffect
Mutation MutationType
EntityChange, MutationType -> CommandEffect
Mutation (MutationType -> CommandEffect) -> MutationType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ RobotChangeType -> MutationType
RobotChange RobotChangeType
InventoryChange]) Text
"Create an item out of thin air." ([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$
[Text
"Only available in creative mode."]
Const
Halt -> Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
short (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ MutationType -> CommandEffect
Mutation (MutationType -> CommandEffect) -> MutationType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ RobotChangeType -> MutationType
RobotChange RobotChangeType
BehaviorChange) Text
"Tell a robot to halt."
Const
Time ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
0 Tangibility
Intangible (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$
Set CommandEffect -> Text -> ConstDoc
shortDoc
(CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ QueryType -> CommandEffect
Query (QueryType -> CommandEffect) -> QueryType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ SensingType -> QueryType
Sensing SensingType
WorldCondition)
Text
"Get the current time."
Const
Scout ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
short (ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ QueryType -> CommandEffect
Query (QueryType -> CommandEffect) -> QueryType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ SensingType -> QueryType
Sensing SensingType
RobotSensing) Text
"Detect whether a robot is within line-of-sight in a direction." ([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$
[ Text
"Perception is blocked by 'Opaque' entities."
, [Text] -> Text
T.unwords [Text
"Has a max range of", [Char] -> Text
T.pack ([Char] -> Text) -> [Char] -> Text
forall a b. (a -> b) -> a -> b
$ Int -> [Char]
forall a. Show a => a -> [Char]
show Int
maxScoutRange, Text
"units."]
]
Const
Whereami ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
0 Tangibility
Intangible (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$
Set CommandEffect -> Text -> ConstDoc
shortDoc
(CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ QueryType -> CommandEffect
Query (QueryType -> CommandEffect) -> QueryType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ SensingType -> QueryType
Sensing SensingType
RobotSensing)
Text
"Get the current x and y coordinates."
Const
LocateMe ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
0 Tangibility
Intangible (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$
Set CommandEffect -> Text -> ConstDoc
shortDoc
(CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ QueryType -> CommandEffect
Query (QueryType -> CommandEffect) -> QueryType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ SensingType -> QueryType
Sensing SensingType
RobotSensing)
Text
"Get the current subworld and x, y coordinates."
Const
Waypoints ->
Int -> ConstDoc -> ConstInfo
function Int
1 (ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ QueryType -> CommandEffect
Query QueryType
APriori) Text
"Get the list of x, y coordinates of a named waypoint" ([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$
[ Text
"Returns only the waypoints in the same subworld as the calling robot."
, Text
"Since waypoint names can have plural multiplicity, returns a list of (x, y) coordinates)."
]
Const
Structures ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
Intangible (ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ QueryType -> CommandEffect
Query (QueryType -> CommandEffect) -> QueryType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ SensingType -> QueryType
Sensing SensingType
EntitySensing) Text
"Get the x, y coordinates of the southwest corner of all constructed structures of a given name" ([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$
[Text
"Since structures can have multiple occurrences, returns a list of (x, y) coordinates."]
Const
Floorplan ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
Intangible (ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ QueryType -> CommandEffect
Query QueryType
APriori) Text
"Get the dimensions of a structure template" ([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$
[ Text
"Returns a tuple of (width, height) for the structure of the requested name."
, Text
"Yields an error if the supplied string is not the name of a structure."
]
Const
HasTag ->
Int -> ConstDoc -> ConstInfo
function Int
2 (ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ QueryType -> CommandEffect
Query QueryType
APriori) Text
"Check whether the given entity has the given tag" ([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$
[ Text
"Returns true if the first argument is an entity that is labeled by the tag in the second argument."
, Text
"Yields an error if the first argument is not a valid entity."
]
Const
TagMembers ->
Int -> ConstDoc -> ConstInfo
function Int
1 (ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ QueryType -> CommandEffect
Query QueryType
APriori) Text
"Get the entities labeled by a tag." ([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$
[ Text
"Returns a list of all entities with the given tag."
, Text
"The order of the list is determined by the definition sequence in the scenario file."
]
Const
Detect ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
2 Tangibility
Intangible (ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ QueryType -> CommandEffect
Query (QueryType -> CommandEffect) -> QueryType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ SensingType -> QueryType
Sensing SensingType
EntitySensing) Text
"Detect an entity within a rectangle." ([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$
[Text
"Locate the closest instance of a given entity within the rectangle specified by opposite corners, relative to the current location."]
Const
Resonate ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
2 Tangibility
Intangible (ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ QueryType -> CommandEffect
Query (QueryType -> CommandEffect) -> QueryType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ SensingType -> QueryType
Sensing SensingType
EntitySensing) Text
"Count specific entities within a rectangle." ([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$
[ Text
"Applies a strong magnetic field over a given area and stimulates the matter within, generating a non-directional radio signal. A receiver tuned to the resonant frequency of the target entity is able to measure its quantity."
, Text
"Counts the entities within the rectangle specified by opposite corners, relative to the current location."
]
Const
Density ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
Intangible (ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ QueryType -> CommandEffect
Query (QueryType -> CommandEffect) -> QueryType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ SensingType -> QueryType
Sensing SensingType
EntitySensing) Text
"Count all entities within a rectangle." ([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$
[ Text
"Applies a strong magnetic field over a given area and stimulates the matter within, generating a non-directional radio signal. A receiver measured the signal intensity to measure the quantity."
, Text
"Counts the entities within the rectangle specified by opposite corners, relative to the current location."
]
Const
Sniff ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
short (ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ QueryType -> CommandEffect
Query (QueryType -> CommandEffect) -> QueryType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ SensingType -> QueryType
Sensing SensingType
EntitySensing) Text
"Determine distance to entity." ([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$
[ Text
"Measures concentration of airborne particles to infer distance to a certain kind of entity."
, Text
"If none is detected, returns (-1)."
, [Text] -> Text
T.unwords [Text
"Has a max range of", [Char] -> Text
T.pack ([Char] -> Text) -> [Char] -> Text
forall a b. (a -> b) -> a -> b
$ Int32 -> [Char]
forall a. Show a => a -> [Char]
show Int32
maxSniffRange, Text
"units."]
]
Const
Chirp ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
short (ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ QueryType -> CommandEffect
Query (QueryType -> CommandEffect) -> QueryType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ SensingType -> QueryType
Sensing SensingType
EntitySensing) Text
"Determine direction to entity." ([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$
[ Text
"Uses a directional sonic emitter and microphone tuned to the acoustic signature of a specific entity to determine its direction."
, Text
"Returns 'down' if out of range or the direction is indeterminate."
, Text
"Provides absolute directions if \"compass\" equipped, relative directions otherwise."
, [Text] -> Text
T.unwords [Text
"Has a max range of", [Char] -> Text
T.pack ([Char] -> Text) -> [Char] -> Text
forall a b. (a -> b) -> a -> b
$ Int32 -> [Char]
forall a. Show a => a -> [Char]
show Int32
maxSniffRange, Text
"units."]
]
Const
Watch ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
short (ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ QueryType -> CommandEffect
Query (QueryType -> CommandEffect) -> QueryType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ SensingType -> QueryType
Sensing SensingType
EntitySensing) Text
"Interrupt `wait` upon location changes." ([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$
[ Text
"Place seismic detectors to alert upon entity changes to the specified location."
, Text
"Supply a direction, as with the `scan` command, to specify a nearby location."
, Text
"Can be invoked more than once until the next `wait` command, at which time the only the registered locations that are currently nearby are preserved."
, Text
"Any change to entities at the monitored locations will cause the robot to wake up before the `wait` timeout."
]
Const
Surveil ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
Intangible (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$
Set CommandEffect -> Text -> [Text] -> ConstDoc
doc
(CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ QueryType -> CommandEffect
Query (QueryType -> CommandEffect) -> QueryType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ SensingType -> QueryType
Sensing SensingType
EntitySensing)
Text
"Interrupt `wait` upon (remote) location changes."
[ Text
"Like `watch`, but instantaneous and with no restriction on distance."
, Text
"Supply absolute coordinates."
]
Const
Heading -> Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
0 Tangibility
Intangible (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ QueryType -> CommandEffect
Query (QueryType -> CommandEffect) -> QueryType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ SensingType -> QueryType
Sensing SensingType
RobotSensing) Text
"Get the current heading."
Const
Blocked -> Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
0 Tangibility
Intangible (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ QueryType -> CommandEffect
Query (QueryType -> CommandEffect) -> QueryType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ SensingType -> QueryType
Sensing SensingType
EntitySensing) Text
"See if the robot can move forward."
Const
Scan ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
Intangible (ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ QueryType -> CommandEffect
Query (QueryType -> CommandEffect) -> QueryType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ SensingType -> QueryType
Sensing SensingType
EntitySensing) Text
"Scan a nearby location for entities." ([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$
[ Text
"Adds the entity (not actor) to your inventory with count 0 if there is any."
, Text
"If you can use sum types, you can also inspect the result directly."
]
Const
Upload -> Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
short (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ MutationType -> CommandEffect
Mutation (MutationType -> CommandEffect) -> MutationType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ RobotChangeType -> MutationType
RobotChange RobotChangeType
BehaviorChange) Text
"Upload a robot's known entities and log to another robot."
Const
Ishere -> Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
Intangible (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ QueryType -> CommandEffect
Query (QueryType -> CommandEffect) -> QueryType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ SensingType -> QueryType
Sensing SensingType
EntitySensing) Text
"See if a specific entity is in the current location."
Const
Isempty ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
0 Tangibility
Intangible (ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ QueryType -> CommandEffect
Query (QueryType -> CommandEffect) -> QueryType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ SensingType -> QueryType
Sensing SensingType
EntitySensing) Text
"Check if the current location is empty." ([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$
[ Text
"Detects whether or not the current location contains an entity."
, Text
"Does not detect robots or other actors."
]
Const
Self -> Int -> ConstDoc -> ConstInfo
function Int
0 (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ QueryType -> CommandEffect
Query QueryType
APriori) Text
"Get a reference to the current robot."
Const
Parent -> Int -> ConstDoc -> ConstInfo
function Int
0 (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ QueryType -> CommandEffect
Query QueryType
APriori) Text
"Get a reference to the robot's parent."
Const
Base -> Int -> ConstDoc -> ConstInfo
function Int
0 (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ QueryType -> CommandEffect
Query QueryType
APriori) Text
"Get a reference to the base."
Const
Meet -> Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
0 Tangibility
Intangible (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ QueryType -> CommandEffect
Query (QueryType -> CommandEffect) -> QueryType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ SensingType -> QueryType
Sensing SensingType
RobotSensing) Text
"Get a reference to a nearby actor, if there is one."
Const
MeetAll -> Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
0 Tangibility
Intangible (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ QueryType -> CommandEffect
Query (QueryType -> CommandEffect) -> QueryType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ SensingType -> QueryType
Sensing SensingType
RobotSensing) Text
"Return a list of all the nearby actors."
Const
Whoami -> Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
0 Tangibility
Intangible (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ QueryType -> CommandEffect
Query (QueryType -> CommandEffect) -> QueryType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ SensingType -> QueryType
Sensing SensingType
RobotSensing) Text
"Get the robot's display name."
Const
Setname -> Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
short (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ MutationType -> CommandEffect
Mutation (MutationType -> CommandEffect) -> MutationType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ RobotChangeType -> MutationType
RobotChange RobotChangeType
BehaviorChange) Text
"Set the robot's display name."
Const
Random ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
Intangible (ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ QueryType -> CommandEffect
Query QueryType
PRNG) Text
"Get a uniformly random integer." ([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$
[Text
"The random integer will be chosen from the range 0 to n-1, exclusive of the argument."]
Const
Run -> Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
long (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ MutationType -> CommandEffect
Mutation (MutationType -> CommandEffect) -> MutationType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ RobotChangeType -> MutationType
RobotChange RobotChangeType
BehaviorChange) Text
"Run a program loaded from a file."
Const
Pure -> Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
Intangible (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc Set CommandEffect
forall a. Set a
Set.empty Text
"Create a pure `Cmd a`{=type} computation that yields the given value."
Const
Try -> Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
2 Tangibility
Intangible (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc Set CommandEffect
forall a. Set a
Set.empty Text
"Execute a command, catching errors."
Const
Undefined -> Int -> ConstDoc -> ConstInfo
function Int
0 (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc Set CommandEffect
forall a. Set a
Set.empty Text
"A value of any type, that is evaluated as error."
Const
Fail -> Int -> ConstDoc -> ConstInfo
function Int
1 (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc Set CommandEffect
forall a. Set a
Set.empty Text
"A value of any type, that is evaluated as error with message."
Const
If ->
Int -> ConstDoc -> ConstInfo
function Int
3 (ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc Set CommandEffect
forall a. Set a
Set.empty Text
"If-Then-Else function." ([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$
[Text
"If the bool predicate is true then evaluate the first expression, otherwise the second."]
Const
Inl -> Int -> ConstDoc -> ConstInfo
function Int
1 (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc Set CommandEffect
forall a. Set a
Set.empty Text
"Put the value into the left component of a sum type."
Const
Inr -> Int -> ConstDoc -> ConstInfo
function Int
1 (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc Set CommandEffect
forall a. Set a
Set.empty Text
"Put the value into the right component of a sum type."
Const
Case -> Int -> ConstDoc -> ConstInfo
function Int
3 (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc Set CommandEffect
forall a. Set a
Set.empty Text
"Evaluate one of the given functions on a value of sum type."
Const
Match -> Int -> ConstDoc -> ConstInfo
function Int
2 (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc Set CommandEffect
forall a. Set a
Set.empty Text
"Do something with both components of a pair."
Const
Force -> Int -> ConstDoc -> ConstInfo
function Int
1 (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc Set CommandEffect
forall a. Set a
Set.empty Text
"Force the evaluation of a delayed value."
Const
Not -> Int -> ConstDoc -> ConstInfo
function Int
1 (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc Set CommandEffect
forall a. Set a
Set.empty Text
"Negate the boolean value."
Const
Neg -> Text -> Int -> MUnAssoc -> ConstDoc -> ConstInfo
unaryOp Text
"-" Int
7 MUnAssoc
P (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc Set CommandEffect
forall a. Set a
Set.empty Text
"Negate the given integer value."
Const
Add -> Text -> Int -> MBinAssoc -> ConstDoc -> ConstInfo
binaryOp Text
"+" Int
6 MBinAssoc
L (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc Set CommandEffect
forall a. Set a
Set.empty Text
"Add the given integer values."
Const
And -> Text -> Int -> MBinAssoc -> ConstDoc -> ConstInfo
binaryOp Text
"&&" Int
3 MBinAssoc
R (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc Set CommandEffect
forall a. Set a
Set.empty Text
"Logical and (true if both values are true)."
Const
Or -> Text -> Int -> MBinAssoc -> ConstDoc -> ConstInfo
binaryOp Text
"||" Int
2 MBinAssoc
R (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc Set CommandEffect
forall a. Set a
Set.empty Text
"Logical or (true if either value is true)."
Const
Sub -> Text -> Int -> MBinAssoc -> ConstDoc -> ConstInfo
binaryOp Text
"-" Int
6 MBinAssoc
L (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc Set CommandEffect
forall a. Set a
Set.empty Text
"Subtract the given integer values."
Const
Mul -> Text -> Int -> MBinAssoc -> ConstDoc -> ConstInfo
binaryOp Text
"*" Int
7 MBinAssoc
L (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc Set CommandEffect
forall a. Set a
Set.empty Text
"Multiply the given integer values."
Const
Div -> Text -> Int -> MBinAssoc -> ConstDoc -> ConstInfo
binaryOp Text
"/" Int
7 MBinAssoc
L (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc Set CommandEffect
forall a. Set a
Set.empty Text
"Divide the left integer value by the right one, rounding down."
Const
Exp -> Text -> Int -> MBinAssoc -> ConstDoc -> ConstInfo
binaryOp Text
"^" Int
8 MBinAssoc
R (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc Set CommandEffect
forall a. Set a
Set.empty Text
"Raise the left integer value to the power of the right one."
Const
Eq -> Text -> Int -> MBinAssoc -> ConstDoc -> ConstInfo
binaryOp Text
"==" Int
4 MBinAssoc
N (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc Set CommandEffect
forall a. Set a
Set.empty Text
"Check that the left value is equal to the right one."
Const
Neq -> Text -> Int -> MBinAssoc -> ConstDoc -> ConstInfo
binaryOp Text
"!=" Int
4 MBinAssoc
N (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc Set CommandEffect
forall a. Set a
Set.empty Text
"Check that the left value is not equal to the right one."
Const
Lt -> Text -> Int -> MBinAssoc -> ConstDoc -> ConstInfo
binaryOp Text
"<" Int
4 MBinAssoc
N (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc Set CommandEffect
forall a. Set a
Set.empty Text
"Check that the left value is lesser than the right one."
Const
Gt -> Text -> Int -> MBinAssoc -> ConstDoc -> ConstInfo
binaryOp Text
">" Int
4 MBinAssoc
N (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc Set CommandEffect
forall a. Set a
Set.empty Text
"Check that the left value is greater than the right one."
Const
Leq -> Text -> Int -> MBinAssoc -> ConstDoc -> ConstInfo
binaryOp Text
"<=" Int
4 MBinAssoc
N (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc Set CommandEffect
forall a. Set a
Set.empty Text
"Check that the left value is lesser or equal to the right one."
Const
Geq -> Text -> Int -> MBinAssoc -> ConstDoc -> ConstInfo
binaryOp Text
">=" Int
4 MBinAssoc
N (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc Set CommandEffect
forall a. Set a
Set.empty Text
"Check that the left value is greater or equal to the right one."
Const
Format -> Int -> ConstDoc -> ConstInfo
function Int
1 (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc Set CommandEffect
forall a. Set a
Set.empty Text
"Turn an arbitrary value into a string."
Const
Read -> Int -> ConstDoc -> ConstInfo
function Int
2 (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc Set CommandEffect
forall a. Set a
Set.empty Text
"Try to read a string into a value of the expected type."
Const
Print ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
2 Tangibility
short
(ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc
(CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ MutationType -> CommandEffect
Mutation (MutationType -> CommandEffect) -> MutationType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ RobotChangeType -> MutationType
RobotChange RobotChangeType
InventoryChange)
Text
"Print text onto an entity."
([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$ [ Text
"`print p txt` Consumes one printable `p` entity from your inventory, and produces an entity"
, Text
"whose name is concatenated with a colon and the given text."
, Text
"In conjunction with `format`, this can be used to print values onto entities such as `paper`{=entity}"
, Text
"and give them to other robots, which can reconstitute the values with `read`."
]
Const
Erase ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
short
(ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc
(CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ MutationType -> CommandEffect
Mutation (MutationType -> CommandEffect) -> MutationType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ RobotChangeType -> MutationType
RobotChange RobotChangeType
InventoryChange)
Text
"Erase an entity."
([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$ [ Text
"Consumes the named printable entity from your inventory, which must have something"
, Text
"printed on it, and produces an erased entity. This can be used to undo"
, Text
"the effects of a `print` command."
]
Const
Concat -> Text -> Int -> MBinAssoc -> ConstDoc -> ConstInfo
binaryOp Text
"++" Int
6 MBinAssoc
R (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc Set CommandEffect
forall a. Set a
Set.empty Text
"Concatenate the given strings."
Const
Chars -> Int -> ConstDoc -> ConstInfo
function Int
1 (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc Set CommandEffect
forall a. Set a
Set.empty Text
"Counts the number of characters in the text."
Const
Split ->
Int -> ConstDoc -> ConstInfo
function Int
2 (ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc Set CommandEffect
forall a. Set a
Set.empty Text
"Split the text into two at given position." ([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$
[ Text
"To be more specific, the following holds for all `text` values `s1` and `s2`:"
, Text
"`(s1,s2) == split (chars s1) (s1 ++ s2)`"
, Text
"So split can be used to undo concatenation if you know the length of the original string."
]
Const
CharAt ->
Int -> ConstDoc -> ConstInfo
function Int
2 (ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc Set CommandEffect
forall a. Set a
Set.empty Text
"Get the character at a given index." ([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$
[ Text
"Gets the character (as an `int` representing a Unicode codepoint) at a specific index in a `text` value. Valid indices are 0 through `chars t - 1`."
, Text
"Throws an exception if given an out-of-bounds index."
]
Const
ToChar ->
Int -> ConstDoc -> ConstInfo
function Int
1 (ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc Set CommandEffect
forall a. Set a
Set.empty Text
"Create a singleton `text` value from the given character code." ([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$
[ Text
"That is, `chars (toChar c) == 1` and `charAt 0 (toChar c) == c`."
]
Const
AppF ->
Text -> Int -> MBinAssoc -> ConstDoc -> ConstInfo
binaryOp Text
"$" Int
0 MBinAssoc
R (ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc Set CommandEffect
forall a. Set a
Set.empty Text
"Apply the function on the left to the value on the right." ([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$
[ Text
"This operator is useful to avoid nesting parentheses."
, Text
"For example:"
, Text
"`f $ g $ h x = f (g (h x))`"
]
Const
Swap ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
short (ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc ([CommandEffect] -> Set CommandEffect
forall a. Ord a => [a] -> Set a
Set.fromList [MutationType -> CommandEffect
Mutation MutationType
EntityChange, MutationType -> CommandEffect
Mutation (MutationType -> CommandEffect) -> MutationType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ RobotChangeType -> MutationType
RobotChange RobotChangeType
InventoryChange]) Text
"Swap placed entity with one in inventory." ([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$
[ Text
"This essentially works like atomic grab and place."
, Text
"Use this to avoid race conditions where more robots grab, scan or place in one location."
]
Const
Atomic ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
Intangible (ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton CommandEffect
MetaEffect) Text
"Execute a block of commands atomically." ([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$
[ Text
"When executing `atomic c`, a robot will not be interrupted, that is, no other robots will execute any commands while the robot is executing @c@."
]
Const
Instant ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
Intangible (ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton CommandEffect
MetaEffect) Text
"Execute a block of commands instantly." ([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$
[ Text
"Like `atomic`, but with no restriction on program size."
]
Const
Key ->
Int -> ConstDoc -> ConstInfo
function Int
1 (ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc Set CommandEffect
forall a. Set a
Set.empty Text
"Create a key value from a text description." ([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$
[ Text
"The key description can optionally start with modifiers like 'C-', 'M-', 'A-', or 'S-', followed by either a regular key, or a special key name like 'Down' or 'End'"
, Text
"For example, 'M-C-x', 'Down', or 'S-4'."
, Text
"Which key combinations are actually possible to type may vary by keyboard and terminal program."
]
Const
InstallKeyHandler ->
Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
2 Tangibility
Intangible (ConstDoc -> ConstInfo)
-> ([Text] -> ConstDoc) -> [Text] -> ConstInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set CommandEffect -> Text -> [Text] -> ConstDoc
doc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ MutationType -> CommandEffect
Mutation (MutationType -> CommandEffect) -> MutationType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ RobotChangeType -> MutationType
RobotChange RobotChangeType
BehaviorChange) Text
"Install a keyboard input handler." ([Text] -> ConstInfo) -> [Text] -> ConstInfo
forall a b. (a -> b) -> a -> b
$
[ Text
"The first argument is a hint line that will be displayed when the input handler is active."
, Text
"The second argument is a function to handle keyboard inputs."
]
Const
Teleport -> Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
2 Tangibility
short (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ MutationType -> CommandEffect
Mutation (MutationType -> CommandEffect) -> MutationType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ RobotChangeType -> MutationType
RobotChange RobotChangeType
PositionChange) Text
"Teleport a robot to the given location."
Const
Warp -> Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
2 Tangibility
short (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ MutationType -> CommandEffect
Mutation (MutationType -> CommandEffect) -> MutationType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ RobotChangeType -> MutationType
RobotChange RobotChangeType
PositionChange) Text
"Relocate a robot to the given cosmic location."
Const
As -> Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
2 Tangibility
Intangible (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ MutationType -> CommandEffect
Mutation (MutationType -> CommandEffect) -> MutationType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ RobotChangeType -> MutationType
RobotChange RobotChangeType
BehaviorChange) Text
"Hypothetically run a command as if you were another robot."
Const
RobotNamed -> Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
Intangible (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ QueryType -> CommandEffect
Query (QueryType -> CommandEffect) -> QueryType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ SensingType -> QueryType
Sensing SensingType
RobotSensing) Text
"Find an actor by name."
Const
RobotNumbered -> Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
Intangible (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ QueryType -> CommandEffect
Query (QueryType -> CommandEffect) -> QueryType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ SensingType -> QueryType
Sensing SensingType
RobotSensing) Text
"Find an actor by number."
Const
Knows -> Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
1 Tangibility
Intangible (ConstDoc -> ConstInfo) -> ConstDoc -> ConstInfo
forall a b. (a -> b) -> a -> b
$ Set CommandEffect -> Text -> ConstDoc
shortDoc (CommandEffect -> Set CommandEffect
forall a. a -> Set a
Set.singleton (CommandEffect -> Set CommandEffect)
-> CommandEffect -> Set CommandEffect
forall a b. (a -> b) -> a -> b
$ QueryType -> CommandEffect
Query (QueryType -> CommandEffect) -> QueryType -> CommandEffect
forall a b. (a -> b) -> a -> b
$ SensingType -> QueryType
Sensing SensingType
RobotSensing) Text
"Check if the robot knows about an entity."
where
doc :: Set CommandEffect -> Text -> [Text] -> ConstDoc
doc Set CommandEffect
e Text
b [Text]
ls = Set CommandEffect -> Text -> Text -> ConstDoc
ConstDoc Set CommandEffect
e Text
b ([Text] -> Text
T.unlines [Text]
ls)
shortDoc :: Set CommandEffect -> Text -> ConstDoc
shortDoc Set CommandEffect
e Text
b = Set CommandEffect -> Text -> Text -> ConstDoc
ConstDoc Set CommandEffect
e Text
b Text
""
unaryOp :: Text -> Int -> MUnAssoc -> ConstDoc -> ConstInfo
unaryOp Text
s Int
p MUnAssoc
side ConstDoc
d =
ConstInfo
{ syntax :: Text
syntax = Text
s
, fixity :: Int
fixity = Int
p
, constMeta :: ConstMeta
constMeta = MUnAssoc -> ConstMeta
ConstMUnOp MUnAssoc
side
, constDoc :: ConstDoc
constDoc = ConstDoc
d
, tangibility :: Tangibility
tangibility = Tangibility
Intangible
}
binaryOp :: Text -> Int -> MBinAssoc -> ConstDoc -> ConstInfo
binaryOp Text
s Int
p MBinAssoc
side ConstDoc
d =
ConstInfo
{ syntax :: Text
syntax = Text
s
, fixity :: Int
fixity = Int
p
, constMeta :: ConstMeta
constMeta = MBinAssoc -> ConstMeta
ConstMBinOp MBinAssoc
side
, constDoc :: ConstDoc
constDoc = ConstDoc
d
, tangibility :: Tangibility
tangibility = Tangibility
Intangible
}
command :: Int -> Tangibility -> ConstDoc -> ConstInfo
command Int
a Tangibility
f ConstDoc
d =
ConstInfo
{ syntax :: Text
syntax = Const -> Text
forall a. Show a => a -> Text
lowShow Const
c
, fixity :: Int
fixity = Int
11
, constMeta :: ConstMeta
constMeta = Int -> Bool -> ConstMeta
ConstMFunc Int
a Bool
True
, constDoc :: ConstDoc
constDoc = ConstDoc
d
, tangibility :: Tangibility
tangibility = Tangibility
f
}
function :: Int -> ConstDoc -> ConstInfo
function Int
a ConstDoc
d =
ConstInfo
{ syntax :: Text
syntax = Const -> Text
forall a. Show a => a -> Text
lowShow Const
c
, fixity :: Int
fixity = Int
11
, constMeta :: ConstMeta
constMeta = Int -> Bool -> ConstMeta
ConstMFunc Int
a Bool
False
, constDoc :: ConstDoc
constDoc = ConstDoc
d
, tangibility :: Tangibility
tangibility = Tangibility
Intangible
}
lowShow :: Show a => a -> Text
lowShow :: forall a. Show a => a -> Text
lowShow = Text -> Text
T.toLower (Text -> Text) -> (a -> Text) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Text
forall a. Show a => a -> Text
showT
maxSniffRange :: Int32
maxSniffRange :: Int32
maxSniffRange = Int32
256
maxScoutRange :: Int
maxScoutRange :: Int
maxScoutRange = Int
64
maxStrideRange :: Int
maxStrideRange :: Int
maxStrideRange = Int
64
maxPathRange :: Integer
maxPathRange :: Integer
maxPathRange = Integer
128
globalMaxVolume :: Integer
globalMaxVolume :: Integer
globalMaxVolume = Integer
64 Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Integer
64