swarm-0.7.0.0: 2D resource gathering game with programmable robots
LicenseBSD-3-Clause
Safe HaskellNone
LanguageHaskell2010

Swarm.Language.Capability

Description

Capabilities needed to evaluate and execute programs. Language constructs or commands require certain capabilities, and in turn capabilities are provided by various devices. A robot must have an appropriate device equipped in order to make use of each language construct or command.

Synopsis

Documentation

data Capability Source #

Various capabilities which robots can have.

Constructors

CExecute Const

Execute the command or function.

CPower

Be powered, i.e. execute anything at all

CMoveHeavy

Allow a heavy robot to perform movements (e.g. move, backup and stride).

CFloat

Don't drown in liquid.

COrient

Allow using absolute directions.

CEnv

Store and look up definitions in an environment

CLambda

Interpret lambda abstractions

CRecursion

Enable recursive definitions

CSum

Capability for working with sum types.

CProd

Capability for working with product types.

CRecord

Capability for working with record types.

CDebug

Debug capability.

CRectype

Capability to handle recursive types.

CGod

God-like capabilities. For e.g. commands intended only for checking challenge mode win conditions, and not for use by players.

Instances

Instances details
FromJSON Capability Source # 
Instance details

Defined in Swarm.Language.Capability

FromJSONKey Capability Source # 
Instance details

Defined in Swarm.Language.Capability

ToJSON Capability Source # 
Instance details

Defined in Swarm.Language.Capability

ToJSONKey Capability Source # 
Instance details

Defined in Swarm.Language.Capability

Data Capability Source # 
Instance details

Defined in Swarm.Language.Capability

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Capability -> c Capability #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Capability #

toConstr :: Capability -> Constr #

dataTypeOf :: Capability -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Capability) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Capability) #

gmapT :: (forall b. Data b => b -> b) -> Capability -> Capability #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Capability -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Capability -> r #

gmapQ :: (forall d. Data d => d -> u) -> Capability -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Capability -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Capability -> m Capability #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Capability -> m Capability #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Capability -> m Capability #

Bounded Capability Source # 
Instance details

Defined in Swarm.Language.Capability

Enum Capability Source # 
Instance details

Defined in Swarm.Language.Capability

Generic Capability Source # 
Instance details

Defined in Swarm.Language.Capability

Associated Types

type Rep Capability 
Instance details

Defined in Swarm.Language.Capability

type Rep Capability = D1 ('MetaData "Capability" "Swarm.Language.Capability" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-lang" 'False) (((C1 ('MetaCons "CExecute" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Const)) :+: (C1 ('MetaCons "CPower" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CMoveHeavy" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "CFloat" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "COrient" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CEnv" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CLambda" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "CRecursion" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CSum" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CProd" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "CRecord" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CDebug" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CRectype" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CGod" 'PrefixI 'False) (U1 :: Type -> Type)))))
Show Capability Source # 
Instance details

Defined in Swarm.Language.Capability

Eq Capability Source # 
Instance details

Defined in Swarm.Language.Capability

Ord Capability Source # 
Instance details

Defined in Swarm.Language.Capability

Hashable Capability Source # 
Instance details

Defined in Swarm.Language.Capability

PrettyPrec Capability Source # 
Instance details

Defined in Swarm.Language.Capability

Methods

prettyPrec :: Int -> Capability -> Doc ann

type Rep Capability Source # 
Instance details

Defined in Swarm.Language.Capability

type Rep Capability = D1 ('MetaData "Capability" "Swarm.Language.Capability" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-lang" 'False) (((C1 ('MetaCons "CExecute" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Const)) :+: (C1 ('MetaCons "CPower" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CMoveHeavy" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "CFloat" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "COrient" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CEnv" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CLambda" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "CRecursion" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CSum" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CProd" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "CRecord" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CDebug" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CRectype" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CGod" 'PrefixI 'False) (U1 :: Type -> Type)))))

capabilityName :: Capability -> Text Source #

Get the name of the capability for use in UI and YAML.

parseCapability :: Text -> Maybe Capability Source #

Parse the capability name - inverse of capabilityName.

>>> import Data.List.Extra (enumerate)
>>> all (\c -> Just c == parseCapability (capabilityName c)) enumerate
True

constCaps :: Const -> Maybe Capability Source #

Capabilities needed to evaluate or execute a constant.