teams-0.0.2.1: Graphical modeling tools for sequential teamsSource codeContentsIndex
Data.Teams.Graph
Contents
Classes
Types
Constructors for nodes
Constructor for edges
Constructors for teams
Select specific nodes
Graph elements
Display functions
Utility functions for Data.Graph.Inductive
Description

This Haskell library implements the algorithm for simplifying sequential teams presented

Aditya Mahajan and Sekhar Tatikonda, A graphical modeling approach to simplifying sequential teams, proceedings of 7th International Symposium on Modeling and Optimization in Mobile, Ad Hoc, and Wireless Networks (WiOpt), Control over Communication Channels (ConCom) Workshop, Seoul, South Korea, June 27, 2009.

The paper can be obtained from http://pantheon.yale.edu/~am894/publications.html#concom-2009. See http://pantheon.yale.edu/~am894/code/teams/ for a usage example.

A team is a multi-agent stochastic control problem in which all agents have a common objective. A team is sequential if and only if there is a partial order between all the system variables. These partial order relationship can be represented using a directed graph, in particular, using a directed factor graph. The variable nodes of the factor graph represent the system variables and the factor nodes represent the system dynamics and control functions. The structural results for these system are equivalent to simplification of the factor graph. An automated algorithm for graph simplification is presented in the Data.Teams.Structure module.

Synopsis
class Vertex a where
name :: a -> String
names :: [a] -> String
isReward :: a -> Bool
isNonReward :: a -> Bool
isVariable :: a -> Bool
isStochastic :: a -> Bool
isDeterministic :: a -> Bool
isControl :: a -> Bool
isFactor :: a -> Bool
attribute :: a -> [Attribute]
type Time = Int
data Variable
= Reward String
| NonReward String
data Factor
= Deterministic String
| Stochastic String
| Control String
type Node = Either Factor Variable
type Edge = (Node, Node, EdgeType)
data EdgeType
= Influence
| Belief
type Team = Gr Node EdgeType
mkVertex :: (String -> a) -> String -> Time -> a
mkReward :: String -> Time -> Variable
mkNonReward :: String -> Time -> Variable
mkControl :: String -> Time -> Factor
mkDeterministic :: String -> Time -> Factor
mkStochastic :: String -> Time -> Factor
(.$.) :: Factor -> (Variable, [Variable]) -> [Edge]
(.|.) :: Variable -> [Variable] -> (Variable, [Variable])
mkTeam :: [Edge] -> Team
mkTeamTime :: (Time -> [Edge]) -> Time -> Team
mkTeamTimeBy :: [Edge] -> (Time -> [Edge]) -> (Time -> [Edge]) -> Time -> Team
selNodes :: Graph gr => (a -> Bool) -> gr a b -> [Node]
variables :: Team -> [Node]
rewards :: Team -> [Node]
factors :: Team -> [Node]
controls :: Team -> [Node]
parents :: Team -> Node -> [Node]
children :: Team -> Node -> [Node]
ancestors :: Team -> Node -> [Node]
ancestoral :: Team -> [Node] -> [Node]
descendants :: Team -> Node -> [Node]
futureNodes :: Team -> (Node -> Bool) -> Node -> [Node]
pastNodes :: Team -> (Node -> Bool) -> Node -> [Node]
printTeam :: Team -> IO ()
showTeam :: Team -> String
graphToDot :: Team -> DotGraph
printGraph :: Team -> FilePath -> IO Bool
label :: Graph gr => gr a b -> Node -> a
labels :: Graph gr => gr a b -> [Node] -> [a]
Classes
class Vertex a whereSource
A type class for defining operations on all nodes
Methods
name :: a -> StringSource
Name of node a
names :: [a] -> StringSource
Name of a list of nodes
isReward :: a -> BoolSource
Check if node a is a reward node
isNonReward :: a -> BoolSource
Check if node a is a non reward node
isVariable :: a -> BoolSource
Check if node a is a variable node
isStochastic :: a -> BoolSource
Check if node a is a stochastic system dynamics
isDeterministic :: a -> BoolSource
Check if node a is a deterministic stochastic system dynamics
isControl :: a -> BoolSource
Check if node a is a control node
isFactor :: a -> BoolSource
Check if node a is a factor node
attribute :: a -> [Attribute]Source
The attributes of the node. Used to contruct the dot file.
show/hide Instances
Types
type Time = IntSource
Time
data Variable Source
Variable nodes
Constructors
Reward StringReward variable node
NonReward StringNon reard variable node
show/hide Instances
data Factor Source
Factor Vertexs
Constructors
Deterministic StringFactor node representing deterministic system dynamics
Stochastic StringFactor node representing stochastic system dynamics
Control StringFactor node representing control function
show/hide Instances
type Node = Either Factor VariableSource
A generic node of a graph
type Edge = (Node, Node, EdgeType)Source
An edge in a graph
data EdgeType Source
Currently all edges are Influence edges. Future versions will have belief edges.
Constructors
Influence
Belief
show/hide Instances
type Team = Gr Node EdgeTypeSource
A sequential team as a directed acyclic factor graph (DAFG)
Constructors for nodes
mkVertex :: (String -> a) -> String -> Time -> aSource
Create a sequence of nodes of a specific type
mkReward :: String -> Time -> VariableSource
Create a sequence of reward nodes
mkNonReward :: String -> Time -> VariableSource
Create a sequence of non reward nodes
mkControl :: String -> Time -> FactorSource
Create a sequence of control nodes
mkDeterministic :: String -> Time -> FactorSource
Create a sequence of deterministic system dynamics nodes
mkStochastic :: String -> Time -> FactorSource
Create a sequence of stochastic system dynamics nodes
Constructor for edges
(.$.) :: Factor -> (Variable, [Variable]) -> [Edge]Source

Used with (.|.) to specify relation between the nodes. For example, if x is a function of y and z, we can write

f.$.(x.|.[y,z]).

(.|.) :: Variable -> [Variable] -> (Variable, [Variable])Source

Used with (.$.) to specify relation between the nodes. For example, if x is a function of y and z, we can write

f.$.(x.|.[y,z]).

Constructors for teams
mkTeam :: [Edge] -> TeamSource

Construct a DAFG from a set of edges. For example,

 f = Control "f"
 x = Reward  "x"
 y = NonReward "y"
 z = NonReward "z"
 g = mkTeam $ f.$.(x.|.[y,z])
mkTeamTime :: (Time -> [Edge]) -> Time -> TeamSource

To make a time homogeneous system. As an example, an MDP can be created as follows

x = mkNonReward "x"
u = mkNonReward "u"
r = mkReward    "r"

f = mkStochastic  "f"
g = mkControl     "g"
d = mkStochastic  "d"

dynamics t =  f(t-1).$.( x(t) .|. if t == 1 then [] else [x(t-1), u(t-1)] )
          ++  g(t)  .$.( u(t) .|. map x[1..t] ++ map u[1..t-1]    )
          ++  d(t)  .$.( r(t) .|. [ x(t), u(t) ]                  )

mdp = mkTeamTime dynamics 3
mkTeamTimeBy :: [Edge] -> (Time -> [Edge]) -> (Time -> [Edge]) -> Time -> TeamSource
Select specific nodes
selNodes :: Graph gr => (a -> Bool) -> gr a b -> [Node]Source
Select nodes whose label satisfy a particular predicate
variables :: Team -> [Node]Source
All variable nods
rewards :: Team -> [Node]Source
All reward nodes
factors :: Team -> [Node]Source
All factors
controls :: Team -> [Node]Source
All control factors
Graph elements
parents :: Team -> Node -> [Node]Source
find indices of parents from the index of a node
children :: Team -> Node -> [Node]Source
find indices of children from the index of a node
ancestors :: Team -> Node -> [Node]Source
find indices of ancestors from the index of a node
ancestoral :: Team -> [Node] -> [Node]Source
find the indices of the ancestoral set from the indices of a given set.
descendants :: Team -> Node -> [Node]Source
find indices of descendants from the index of a node
futureNodes :: Team -> (Node -> Bool) -> Node -> [Node]Source
find the indices of future nodes that satisfy a particular predicate
pastNodes :: Team -> (Node -> Bool) -> Node -> [Node]Source
find the indices of past nodes that satisfy a particular predicate
Display functions
printTeam :: Team -> IO ()Source
Pretty print the team specification
showTeam :: Team -> StringSource
Pretty print the team specification
graphToDot :: Team -> DotGraphSource
Convert the graph to a dot file
printGraph :: Team -> FilePath -> IO BoolSource
Convert the dot file to a pdf
Utility functions for Data.Graph.Inductive
label :: Graph gr => gr a b -> Node -> aSource

Extensions of Data.Graph.Inductive

Label of a particular node

labels :: Graph gr => gr a b -> [Node] -> [a]Source
Labels of a list of nodes
Produced by Haddock version 2.4.2