-- | 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,
  null,
  nullEdges)
  where

import Prelude hiding (null)

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

import Data.Semigroup
import Data.Monoid

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

-- | A NodeSet is a IntSet of Nodes
type NodeSet = IntSet

-- | 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

-- | Is the graph empty
null :: IntGraph -> Bool
null (IG graph) = I.null graph

-- | Is the edge set empty
nullEdges :: IntGraph -> Bool
nullEdges (IG graph) = I.null $ I.filter (not . S.null) graph

-- | Joins to graphs by unioning the vertex and edge sets
overlay :: IntGraph -> IntGraph -> IntGraph
overlay (IG g1) (IG g2) = IG $ I.unionWith (S.union) g1 g2

instance Eq IntGraph where
  (IG g1) == (IG g2) = g1 == g2

instance Semigroup IntGraph where
  (<>) = overlay

instance Monoid IntGraph where
  mempty = empty

  mappend = overlay