gore-and-ash-actor-1.2.2.0: Gore&Ash engine extension that implements actor style of programming

Copyright(c) Anton Gushcha, 2015-2016
LicenseBSD3
Maintainerncrashed@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Game.GoreAndAsh.Actor.Collection

Description

 

Synopsis

Documentation

dynCollection Source #

Arguments

:: (ActorMonad m, Eq i, DynCollection c, FilterConstraint c (GameWireIndexed m i a b), FilterConstraint c (Either () b), Foldable c2) 
=> c (GameActor m i a b)

Inital set of wires

-> GameWire m (a, Event (c (GameActor m i a b)), Event (c2 i)) (c b) 

Makes dynamic collection of wires.

  • First input of wire is input for each inner wire.
  • Second input is event for adding several wires to collection.
  • Third input is event for removing several wires from collection.
  • Wire returns list of outputs of inner wires.

Note: if ihibits one of the wires, it is removed from output result during its inhibition

dDynCollection Source #

Arguments

:: (ActorMonad m, Eq i, DynCollection c, FilterConstraint c (GameWireIndexed m i a b), FilterConstraint c (Either () b), Foldable c2) 
=> c (GameActor m i a b)

Inital set of wires

-> GameWire m (a, Event (c (GameActor m i a b)), Event (c2 i)) (c b) 

Makes dynamic collection of wires.

  • First input of wire is input for each inner wire.
  • Second input is event for adding several wires to collection.
  • Third input is event for removing several wires from collection.
  • Wire returns list of outputs of inner wires.

Note: it is delayed version of dynCollection, removing and adding of agents performs on next step after current.

Note: if ihibits one of the wires, it is removed from output result while it inhibits.

class (Filterable c, Foldable c, Functor c, Traversable c) => DynCollection c where Source #

Dynamic collection for control wire that automates handling collections of FRP actors. The class defines minimum set of actions that collection should support to be used as base for collection of actors.

Associated Types

type DynConsConstr c o :: Constraint Source #

Instance specific constraint for appending function

Methods

concatDynColl :: c a -> c a -> c a Source #

Concat of two collections

unzipDynColl :: c (a, b) -> (c a, c b) Source #

Unzipping of collection

zipDynColl :: c a -> c b -> c (a, b) Source #

Ziping collection

emptyDynColl :: c a Source #

Getting empty collection

consDynColl :: DynConsConstr c a => a -> c a -> c a Source #

Adding element to the begining of collection

Instances

DynCollection [] Source # 

Associated Types

type DynConsConstr ([] :: * -> *) o :: Constraint Source #

Methods

concatDynColl :: [a] -> [a] -> [a] Source #

unzipDynColl :: [(a, b)] -> ([a], [b]) Source #

zipDynColl :: [a] -> [b] -> [(a, b)] Source #

emptyDynColl :: [a] Source #

consDynColl :: DynConsConstr [] a => a -> [a] -> [a] Source #

DynCollection Seq Source # 

Associated Types

type DynConsConstr (Seq :: * -> *) o :: Constraint Source #

Methods

concatDynColl :: Seq a -> Seq a -> Seq a Source #

unzipDynColl :: Seq (a, b) -> (Seq a, Seq b) Source #

zipDynColl :: Seq a -> Seq b -> Seq (a, b) Source #

emptyDynColl :: Seq a Source #

consDynColl :: DynConsConstr Seq a => a -> Seq a -> Seq a Source #

(Eq k, Hashable k) => DynCollection (HashMap k) Source #

Order of elements is not preserved

Associated Types

type DynConsConstr (HashMap k :: * -> *) o :: Constraint Source #

Methods

concatDynColl :: HashMap k a -> HashMap k a -> HashMap k a Source #

unzipDynColl :: HashMap k (a, b) -> (HashMap k a, HashMap k b) Source #

zipDynColl :: HashMap k a -> HashMap k b -> HashMap k (a, b) Source #

emptyDynColl :: HashMap k a Source #

consDynColl :: DynConsConstr (HashMap k) a => a -> HashMap k a -> HashMap k a Source #