swarm-0.2.0.0: 2D resource gathering game with programmable robots
CopyrightBrent Yorgey
LicenseBSD-3-Clause
Maintainerbyorgey@gmail.com
Safe HaskellSafe-Inferred
LanguageHaskell2010

Swarm.Game.Recipe

Description

A recipe represents some kind of process for transforming some input entities into some output entities.

Synopsis

Ingredient lists and recipes

type IngredientList e = [(Count, e)] Source #

An ingredient list is a list of entities with multiplicity. It is polymorphic in the entity type so that we can use either entity names when serializing, or actual entity objects while the game is running.

data Recipe e Source #

A recipe is just a list of input entities and a list of output entities (both with multiplicity). The idea is that it represents some kind of process where the inputs are transformed into the outputs.

Instances

Instances details
Foldable Recipe Source # 
Instance details

Defined in Swarm.Game.Recipe

Methods

fold :: Monoid m => Recipe m -> m #

foldMap :: Monoid m => (a -> m) -> Recipe a -> m #

foldMap' :: Monoid m => (a -> m) -> Recipe a -> m #

foldr :: (a -> b -> b) -> b -> Recipe a -> b #

foldr' :: (a -> b -> b) -> b -> Recipe a -> b #

foldl :: (b -> a -> b) -> b -> Recipe a -> b #

foldl' :: (b -> a -> b) -> b -> Recipe a -> b #

foldr1 :: (a -> a -> a) -> Recipe a -> a #

foldl1 :: (a -> a -> a) -> Recipe a -> a #

toList :: Recipe a -> [a] #

null :: Recipe a -> Bool #

length :: Recipe a -> Int #

elem :: Eq a => a -> Recipe a -> Bool #

maximum :: Ord a => Recipe a -> a #

minimum :: Ord a => Recipe a -> a #

sum :: Num a => Recipe a -> a #

product :: Num a => Recipe a -> a #

Traversable Recipe Source # 
Instance details

Defined in Swarm.Game.Recipe

Methods

traverse :: Applicative f => (a -> f b) -> Recipe a -> f (Recipe b) #

sequenceA :: Applicative f => Recipe (f a) -> f (Recipe a) #

mapM :: Monad m => (a -> m b) -> Recipe a -> m (Recipe b) #

sequence :: Monad m => Recipe (m a) -> m (Recipe a) #

Functor Recipe Source # 
Instance details

Defined in Swarm.Game.Recipe

Methods

fmap :: (a -> b) -> Recipe a -> Recipe b #

(<$) :: a -> Recipe b -> Recipe a #

FromJSONE EntityMap (Recipe Entity) Source # 
Instance details

Defined in Swarm.Game.Recipe

FromJSON (Recipe Entity) Source # 
Instance details

Defined in Swarm.Game.Recipe

FromJSON (Recipe Text) Source # 
Instance details

Defined in Swarm.Game.Recipe

ToJSON (Recipe Entity) Source # 
Instance details

Defined in Swarm.Game.Recipe

ToJSON (Recipe Text) Source # 
Instance details

Defined in Swarm.Game.Recipe

Generic (Recipe e) Source # 
Instance details

Defined in Swarm.Game.Recipe

Associated Types

type Rep (Recipe e) :: Type -> Type #

Methods

from :: Recipe e -> Rep (Recipe e) x #

to :: Rep (Recipe e) x -> Recipe e #

Show e => Show (Recipe e) Source # 
Instance details

Defined in Swarm.Game.Recipe

Methods

showsPrec :: Int -> Recipe e -> ShowS #

show :: Recipe e -> String #

showList :: [Recipe e] -> ShowS #

Eq e => Eq (Recipe e) Source # 
Instance details

Defined in Swarm.Game.Recipe

Methods

(==) :: Recipe e -> Recipe e -> Bool #

(/=) :: Recipe e -> Recipe e -> Bool #

Ord e => Ord (Recipe e) Source # 
Instance details

Defined in Swarm.Game.Recipe

Methods

compare :: Recipe e -> Recipe e -> Ordering #

(<) :: Recipe e -> Recipe e -> Bool #

(<=) :: Recipe e -> Recipe e -> Bool #

(>) :: Recipe e -> Recipe e -> Bool #

(>=) :: Recipe e -> Recipe e -> Bool #

max :: Recipe e -> Recipe e -> Recipe e #

min :: Recipe e -> Recipe e -> Recipe e #

type Rep (Recipe e) Source # 
Instance details

Defined in Swarm.Game.Recipe

type Rep (Recipe e) = D1 ('MetaData "Recipe" "Swarm.Game.Recipe" "swarm-0.2.0.0-D1mAmWsUEjoFqpCaq9DHG0" 'False) (C1 ('MetaCons "Recipe" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_recipeInputs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (IngredientList e)) :*: S1 ('MetaSel ('Just "_recipeOutputs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (IngredientList e))) :*: (S1 ('MetaSel ('Just "_recipeRequirements") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (IngredientList e)) :*: (S1 ('MetaSel ('Just "_recipeTime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Integer) :*: S1 ('MetaSel ('Just "_recipeWeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Integer)))))

recipeInputs :: Lens' (Recipe e) (IngredientList e) Source #

The inputs to a recipe.

recipeOutputs :: Lens' (Recipe e) (IngredientList e) Source #

The outputs from a recipe.

recipeRequirements :: Lens' (Recipe e) (IngredientList e) Source #

Other entities which the recipe requires you to have, but which are not consumed by the recipe (e.g. a furnace).

recipeTime :: Lens' (Recipe e) Integer Source #

The time required to finish a recipe.

recipeWeight :: Lens' (Recipe e) Integer Source #

How this recipe is weighted against other recipes. Any time there are multiple valid recipes that fit certain criteria, one of the recipes will be randomly chosen with probability proportional to its weight.

Loading recipes

loadRecipes :: Has (Lift IO) sig m => EntityMap -> m (Either Text [Recipe Entity]) Source #

Given an already loaded EntityMap, try to load a list of recipes from the data file recipes.yaml.

outRecipeMap :: [Recipe Entity] -> IntMap [Recipe Entity] Source #

Build a map of recipes indexed by output ingredients.

inRecipeMap :: [Recipe Entity] -> IntMap [Recipe Entity] Source #

Build a map of recipes indexed by input ingredients.

reqRecipeMap :: [Recipe Entity] -> IntMap [Recipe Entity] Source #

Build a map of recipes indexed by requirements.

Looking up recipes

data MissingType Source #

Instances

Instances details
Show MissingType Source # 
Instance details

Defined in Swarm.Game.Recipe

Eq MissingType Source # 
Instance details

Defined in Swarm.Game.Recipe

knowsIngredientsFor :: (Inventory, Inventory) -> Recipe Entity -> Bool Source #

Figure out if a recipe is available, but it can be lacking items.

recipesFor :: IntMap [Recipe Entity] -> Entity -> [Recipe Entity] Source #

Get a list of all the recipes for the given entity. Look up an entity in either an inRecipeMap or outRecipeMap depending on whether you want to know recipes that consume or produce the given entity, respectively.

make :: (Inventory, Inventory) -> Recipe Entity -> Either [MissingIngredient] (Inventory, Inventory -> Inventory, Recipe Entity) Source #

Try to make a recipe, deleting the recipe's inputs from the inventory. Return either a description of which items are lacking, if the inventory does not contain sufficient inputs, or an inventory without inputs and function adding outputs if it was successful.

make' :: (Inventory, Inventory) -> Recipe Entity -> Either [MissingIngredient] (Inventory, IngredientList Entity) Source #

Try to make a recipe, but do not insert it yet.