License | BSD-3-Clause |
---|---|
Safe Haskell | None |
Language | Haskell2010 |
Swarm.Language.Requirements.Type
Description
A requirement is something that is needed in order to successfully build a robot running a certain program.
Synopsis
- data Requirement
- data Requirements = Requirements {}
- singleton :: Requirement -> Requirements
- singletonCap :: Capability -> Requirements
- singletonDev :: Text -> Requirements
- singletonInv :: Int -> Text -> Requirements
- insert :: Requirement -> Requirements -> Requirements
- type ReqCtx = Ctx Var Requirements
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
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 Inventory requirements are additive, that is, say, requiring 5
of entity |
Instances
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
FromJSON Requirements Source # | |||||
Defined in Swarm.Language.Requirements.Type | |||||
ToJSON Requirements Source # | |||||
Defined in Swarm.Language.Requirements.Type Methods toJSON :: Requirements -> Value # toEncoding :: Requirements -> Encoding # toJSONList :: [Requirements] -> Value # toEncodingList :: [Requirements] -> Encoding # omitField :: Requirements -> Bool # | |||||
Data Requirements Source # | |||||
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 # | |||||
Defined in Swarm.Language.Requirements.Type Methods mempty :: Requirements # mappend :: Requirements -> Requirements -> Requirements # mconcat :: [Requirements] -> Requirements # | |||||
Semigroup Requirements Source # | |||||
Defined in Swarm.Language.Requirements.Type Methods (<>) :: Requirements -> Requirements -> Requirements # sconcat :: NonEmpty Requirements -> Requirements # stimes :: Integral b => b -> Requirements -> Requirements # | |||||
Generic Requirements Source # | |||||
Defined in Swarm.Language.Requirements.Type Associated Types
| |||||
Show Requirements Source # | |||||
Defined in Swarm.Language.Requirements.Type Methods showsPrec :: Int -> Requirements -> ShowS # show :: Requirements -> String # showList :: [Requirements] -> ShowS # | |||||
Eq Requirements Source # | |||||
Defined in Swarm.Language.Requirements.Type | |||||
Ord Requirements Source # | |||||
Defined in Swarm.Language.Requirements.Type Methods compare :: Requirements -> Requirements -> Ordering # (<) :: Requirements -> Requirements -> Bool # (<=) :: Requirements -> Requirements -> Bool # (>) :: Requirements -> Requirements -> Bool # (>=) :: Requirements -> Requirements -> Bool # max :: Requirements -> Requirements -> Requirements # min :: Requirements -> Requirements -> Requirements # | |||||
Hashable Requirements Source # | |||||
Defined in Swarm.Language.Requirements.Type | |||||
type Rep Requirements Source # | |||||
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))))) |
singleton :: Requirement -> Requirements Source #
Create a Requirements
set with a single Requirement
.
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.
insert :: Requirement -> Requirements -> Requirements Source #