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

Swarm.Language.Requirements.Type

Description

A requirement is something that is needed in order to successfully build a robot running a certain program.

Synopsis

Requirements

The Requirement type

data Requirement Source #

A requirement is something a robot must have when it is built. There are three types: - A robot can require a certain Capability, which should be fulfilled by equipping an appropriate device. - A robot can require a specific device, which should be equipped. - A robot can stock some number of a specific entity in its inventory.

Constructors

ReqCap Capability

Require a specific capability. This must be fulfilled by equipping an appropriate device. Requiring the same capability multiple times is the same as requiring it once.

ReqDev Text

Require a specific device to be equipped. Note that at this point it is only a name, and has not been resolved to an actual Entity. That's because programs have to be type- and capability-checked independent of an EntityMap. The name will be looked up at runtime, when actually executing a Build or Reprogram command, and an appropriate exception thrown if a device with the given name does not exist.

Requiring the same device multiple times is the same as requiring it once.

ReqInv Int Text

Stock a certain number of a specific entity to be available in the inventory. The same comments apply re: resolving the entity name to an actual Entity.

Inventory requirements are additive, that is, say, requiring 5 of entity "e" and later requiring 7 is the same as requiring 12.

Instances

Instances details
FromJSON Requirement Source # 
Instance details

Defined in Swarm.Language.Requirements.Type

ToJSON Requirement Source # 
Instance details

Defined in Swarm.Language.Requirements.Type

Data Requirement Source # 
Instance details

Defined in Swarm.Language.Requirements.Type

Methods

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

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

toConstr :: Requirement -> Constr #

dataTypeOf :: Requirement -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Requirement Source # 
Instance details

Defined in Swarm.Language.Requirements.Type

Show Requirement Source # 
Instance details

Defined in Swarm.Language.Requirements.Type

Eq Requirement Source # 
Instance details

Defined in Swarm.Language.Requirements.Type

Ord Requirement Source # 
Instance details

Defined in Swarm.Language.Requirements.Type

Hashable Requirement Source # 
Instance details

Defined in Swarm.Language.Requirements.Type

type Rep Requirement Source # 
Instance details

Defined in Swarm.Language.Requirements.Type

The Requirements type and utility functions

data Requirements Source #

It is tempting to define Requirements = Set Requirement, but that would be wrong, since two identical ReqInv should have their counts added rather than simply being deduplicated.

Since we will eventually need to deal with the different types of requirements separately, it makes sense to store them separately anyway.

Constructors

Requirements 

Instances

Instances details
FromJSON Requirements Source # 
Instance details

Defined in Swarm.Language.Requirements.Type

ToJSON Requirements Source # 
Instance details

Defined in Swarm.Language.Requirements.Type

Data Requirements Source # 
Instance details

Defined in Swarm.Language.Requirements.Type

Methods

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

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

toConstr :: Requirements -> Constr #

dataTypeOf :: Requirements -> DataType #

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

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

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

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

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

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

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

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

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

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

Monoid Requirements Source # 
Instance details

Defined in Swarm.Language.Requirements.Type

Semigroup Requirements Source # 
Instance details

Defined in Swarm.Language.Requirements.Type

Generic Requirements Source # 
Instance details

Defined in Swarm.Language.Requirements.Type

Associated Types

type Rep Requirements 
Instance details

Defined in Swarm.Language.Requirements.Type

type Rep Requirements = D1 ('MetaData "Requirements" "Swarm.Language.Requirements.Type" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-lang" 'False) (C1 ('MetaCons "Requirements" 'PrefixI 'True) (S1 ('MetaSel ('Just "capReqs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Set Capability)) :*: (S1 ('MetaSel ('Just "devReqs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Set Text)) :*: S1 ('MetaSel ('Just "invReqs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Map Text Int)))))
Show Requirements Source # 
Instance details

Defined in Swarm.Language.Requirements.Type

Eq Requirements Source # 
Instance details

Defined in Swarm.Language.Requirements.Type

Ord Requirements Source # 
Instance details

Defined in Swarm.Language.Requirements.Type

Hashable Requirements Source # 
Instance details

Defined in Swarm.Language.Requirements.Type

type Rep Requirements Source # 
Instance details

Defined in Swarm.Language.Requirements.Type

type Rep Requirements = D1 ('MetaData "Requirements" "Swarm.Language.Requirements.Type" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-lang" 'False) (C1 ('MetaCons "Requirements" 'PrefixI 'True) (S1 ('MetaSel ('Just "capReqs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Set Capability)) :*: (S1 ('MetaSel ('Just "devReqs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Set Text)) :*: S1 ('MetaSel ('Just "invReqs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Map Text Int)))))

singletonCap :: Capability -> Requirements Source #

For convenience, create a Requirements set with a single Capability requirement.

singletonDev :: Text -> Requirements Source #

For convenience, create a Requirements set with a single device requirement.

singletonInv :: Int -> Text -> Requirements Source #

For convenience, create a Requirements set with a single inventory requirement.

type ReqCtx = Ctx Var Requirements Source #

A requirement context records the requirements for the definitions bound to variables.