-- | This modules provides variants of the functions in "GraphRewriting.Graph.Write" for transforming the graph, but without checking for changed port assignments, which could lead to an inconsistent state. Therefore these should only be used (for increased efficiency) if the modifications do not change the graph structure (such as in layouting), or you really know what you are doing. Note that the functions provided by this library never change the length of the port list

-- (TODO: use Functor/Traversable/Foldable instead of lists?)
module GraphRewriting.Graph.Write.Unsafe
	(module GraphRewriting.Graph.Write.Unsafe, module GraphRewriting.Graph.Types, module Data.View)
where

import Prelude.Unicode
import Data.Maybe (fromMaybe)
import GraphRewriting.Graph.Types
import GraphRewriting.Graph.Internal
import GraphRewriting.Graph.Read
import Data.View
import qualified Data.IntMap as Map
import qualified Data.IntSet as Set


-- TODO: For the major version change Adjust parameter orders to the ones used in GraphRewriting.Graph.Write

modifyNode  Node  (n  n)  Rewrite n ()
modifyNode n@(Node i) f = modifyNodeMap . Map.insert i . f =<< readNode n

updateNode  View v n  v  Node  Rewrite n ()
updateNode v = adjustNode (const v)

adjustNode  View v n  (v  v)  Node  Rewrite n ()
adjustNode f n = modifyNode n $ adjust f

adjustNodeM  (View [Port] n, View v n)  (v  Rewrite n v)  Node  Rewrite n ()
adjustNodeM f n = do
	v'  f =<< inspectNode n
	updateNode v' n

writeNode  Node  n  Rewrite n ()
writeNode r = modifyNode r . const

unregister  Node  [Edge]  Rewrite n ()
unregister (Node n) es = modifyEdgeMap $ flip (foldr $ Map.update deleteN) (map eKey es)
	where deleteN ns = if ns  Set.singleton n then Nothing else Just $ Set.delete n ns

register  Node  [Edge]  Rewrite n ()
register (Node n) es = modifyEdgeMap $ flip (foldr $ Map.alter addN) (map eKey es)
	where addN ns = Just (Set.insert n $ fromMaybe Set.empty ns)