karps-0.2.0.0: Haskell bindings for Spark Dataframes and Datasets

Safe HaskellNone
LanguageHaskell2010

Spark.Core.Internal.DAGFunctions

Description

A set of utility functions to build and transform DAGs.

Because I could not find a public library for such transforms.

Most Karps manipulations are converted into graph manipulations.

Synopsis

Documentation

type DagTry a = Either Text a Source #

Separate type of error to make it more general and easier to test.

data FilterOp Source #

The different filter modes when pruning a graph.

Keep: keep the current node. CutChildren: keep the current node, but do not consider the children. Remove: remove the current node, do not consider the children.

Constructors

Keep 
Remove 
CutChildren 

buildGraph :: forall v e. (GraphOperations v e, Show v) => v -> DagTry (Graph v e) Source #

Builds a graph by expanding a start vertex.

buildVertexList :: (GraphVertexOperations v, Show v) => v -> DagTry [v] Source #

Starts from a vertex and expands the vertex to reach all the transitive closure of the vertex.

Returns a list in lexicographic order of dependencies: the graph corresponding to this list of elements has one sink (the start element) and potentially multiple sources. The nodes are ordered so that all the parents are visited before the node itself.

buildGraphFromList :: forall v e. Show v => [Vertex v] -> [Edge e] -> DagTry (Graph v e) Source #

Attempts to build a graph from a collection of vertices and edges.

This collection may be invalid (cycles, etc.) and the vertices need not be in topological order.

All the vertices referred by edges must be present in the list of vertices.

graphSinks :: Graph v e -> [Vertex v] Source #

The sinks of a graph (nodes with no descendant).

graphSources :: Graph v e -> [Vertex v] Source #

The sources of a DAG (nodes with no parent).

graphMapVertices :: forall m v e v2. (HasCallStack, Show v2, Monad m) => Graph v e -> (v -> [(v2, e)] -> m v2) -> m (Graph v2 e) Source #

A generic transform over the graph that may account for potential failures in the process.

graphMapVertices' :: (Show v, Show e, Show v') => (v -> v') -> Graph v e -> Graph v' e Source #

(internal) Maps the vertices.

vertexMap :: Graph v e -> Map VertexId v Source #

The map of vertices, by vertex id.

graphFlatMapEdges :: Graph v e -> (e -> [e']) -> Graph v e' Source #

(internal) Maps and the edges, and may create more or less.

graphMapEdges :: Graph v e -> (e -> e') -> Graph v e' Source #

(internal) Maps the edges

reverseGraph :: forall v e. Graph v e -> Graph v e Source #

Flips the edges of this graph (it is also a DAG)

verticesAndEdges :: Graph v e -> [([(v, e)], v)] Source #

graphFilterVertices :: (Show v, Show e) => (v -> FilterOp) -> Graph v e -> Graph v e Source #

Given a graph, prunes out a subset of vertices.

All the corresponding edges and the unreachable chunks of the graph are removed.

pruneLexicographic :: VertexId -> [(VertexId, [VertexId], a)] -> [a] Source #

Given a list of elements with vertex/edge information and a start vertex, builds the graph from all the reachable vertices in the list.

It returns the vertices in a DAG traversal order.

Note that this function is robust and silently drops the missing vertices.