-- | Definition of an IntGraph
-- | Make sure to only import one of Directed and Undirected - there function names will conflict

module Data.IntGraph (
  Node,
  NodeSet,
  Edge,
  IntGraph(..),
  empty,
  addNode,
  nodes,
  removeNode)
  where

import qualified Data.IntMap.Strict as I
import           Data.IntMap.Strict    (IntMap)
import qualified Data.Set           as S
import           Data.Set              (Set)

-- | The nodes of the graph are Ints
type Node = Int

-- | A NodeSet is a Set of Nodes
type NodeSet = Set Node

-- | An edge is a pair of nodes
type Edge = (Node, Node)

-- | An IntGraph is a maping of Ints (Nodes) to sets of Nodes (Ints)
newtype IntGraph
  = IG (IntMap NodeSet)

-- | Adds a single node with no neighbors.
-- | If node already in graph, does nothing.
addNode :: Node -> IntGraph -> IntGraph
addNode node (IG graph) = IG $ I.insertWith S.union node S.empty graph

-- | Returns a list of the nodes in the graph
nodes :: IntGraph -> [Node]
nodes (IG graph) = I.keys graph

-- | removes a node and all its incident edges
removeNode :: Node -> IntGraph -> IntGraph
removeNode node (IG graph) = IG $ I.map (S.delete node) $ I.delete node graph

-- | the empty graph
empty = IG I.empty