module Spark.Core.Internal.ComputeDag where
import Data.Foldable(toList)
import qualified Data.Map.Strict as M
import qualified Data.Vector as V
import Data.Vector(Vector)
import Spark.Core.Internal.DAGStructures
import Spark.Core.Internal.DAGFunctions
data ComputeDag v e = ComputeDag {
cdEdges :: !(AdjacencyMap v e),
cdVertices :: !(Vector (Vertex v)),
cdInputs :: !(Vector (Vertex v)),
cdOutputs :: !(Vector (Vertex v))
} deriving (Show)
computeGraphToGraph :: ComputeDag v e -> Graph v e
computeGraphToGraph cg =
Graph (cdEdges cg) (cdVertices cg)
graphToComputeGraph :: Graph v e -> ComputeDag v e
graphToComputeGraph g =
ComputeDag {
cdEdges = gEdges g,
cdVertices = gVertices g,
cdInputs = V.fromList $ graphSinks g,
cdOutputs = V.fromList $ graphSources g
}
_mapVerticesAdj :: (Vertex v -> v') -> AdjacencyMap v e -> AdjacencyMap v' e
_mapVerticesAdj f m =
let f1 ve =
let vx = veEndVertex ve
d' = f vx in
ve { veEndVertex = vx { vertexData = d' } }
f' v = f1 <$> v
in M.map f' m
mapVertices :: (Vertex v -> v') -> ComputeDag v e -> ComputeDag v' e
mapVertices f cd =
let f' vx = vx { vertexData = f vx }
in ComputeDag {
cdEdges = _mapVerticesAdj f (cdEdges cd),
cdVertices = f' <$> cdVertices cd,
cdInputs = f' <$> cdInputs cd,
cdOutputs = f' <$> cdOutputs cd
}
mapVertexData :: (v -> v') -> ComputeDag v e -> ComputeDag v' e
mapVertexData f = mapVertices (f . vertexData)
buildCGraph :: (GraphOperations v e, Show v, Show e) =>
v -> DagTry (ComputeDag v e)
buildCGraph n = graphToComputeGraph <$> buildGraph n
graphDataLexico :: ComputeDag v e -> [v]
graphDataLexico cd = vertexData <$> toList (cdVertices cd)