Skip to content
Adithya Kumar edited this page May 23, 2019 · 26 revisions

This page is for discussing and tracking the ongoing development of support for acyclic graphs.

Motivation

Acyclic graphs are both common and heavily used in dependency management. Improvements in this area would therefore directly benefit downstream packages like build, plutus or aura, as well as a few commercial users of the library.

In particular, the result should be a type-safe abstraction, that makes it easier to work with algorithms like scc or topSort as has been remarked in some issues.

Requirements

An abstract data type for acyclic graphs should first be provided in the module Algebra.Graph.Acyclic.AdjacencyMap designed to be imported qualified as Acyclic. We will therefore refer to the data type as Acyclic.AdjacencyMap in this page.

Here is a proposed definition for Acyclic.AdjacencyMap:

module Algebra.Graph.Acyclic.AdjacencyMap where

import qualified Algebra.Graph.AdjacencyMap as AM
import qualified Algebra.Graph.AdjacencyMap.Algorithm as AMA
import qualified Algebra.Graph.AdjacencyMap.Internal as AMI

newtype AdjacencyMap a = AAM { aam :: AM.AdjacencyMap a }

consistent :: Ord a => AdjacencyMap a -> Bool
consistent (AAM m) = AMI.consistent m && AMA.isAcyclic m

General adjacency maps will be referred to as AdjacencyMap and non-empty adjacency maps as NonEmpty.AdjacencyMap.

Construct an acyclic graph via the SCC algorithm (high priority)

The SCC algorithm guarantees the absence of cycles in the component graph, so it is a natural choice for an acyclic graph construction primitive.

scc :: Ord a => AdjacencyMap a -> Acyclic.AdjacencyMap (NonEmpty.AdjacencyMap a)

TODO: Add small example.

Construct from an algebraic graph and a partial order (high priority)

TODO: Add a description of the idea.

import Algebra.Graph

type PartialOrder a = a -> a -> Bool

fromGraph :: Ord a => PartialOrder a -> Graph a -> Acyclic.AdjacencyMap a

Adithya: Should fromGraph create all possible edges satisfying the partial order or filter edges in the given graph using the partial order?

Example:

Here is a simple example where we do have a partial order in advance:

  • Every object file depends only on C source files: file.c < file.o.
  • Every executable depends only on object files: file.o < file.exe.

Here we could just use < from the derived Ord instance for the extension data type:

data Extension = C | O | Exe deriving (Eq, Ord)

type File = (FilePath, Extension)

partialOrder :: PartialOrder File
partialOrder (_, x) (_, y) = x < y

I find this a convincing example, where we can have a type-safe construction of an acyclic graph thanks to some domain knowledge.

Basic graph construction primitives (medium priority)

We could easily support the following graph construction primitives:

empty :: Acyclic.AdjacencyMap a
vertex :: a -> Acyclic.AdjacencyMap a
vertices :: [a] -> Acyclic.AdjacencyMap a
-- D stands for "disjoint"
overlayD :: Acyclic.AdjacencyMap a -> Acyclic.AdjacencyMap b -> Acyclic.AdjacencyMap (Either a b)
connectD :: Acyclic.AdjacencyMap a -> Acyclic.AdjacencyMap b -> Acyclic.AdjacencyMap (Either a b)

I'm not entirely sure how useful these will be in practice, but they are cheap to add, so why not.

Construct via transitive closure (medium priority)

A transitive closure of an acyclic graph is acyclic, so we can support transitiveClousre:

transitiveClosure :: Ord a => Acyclic.AdjacencyMap a -> Acyclic.AdjacencyMap a

Construct an acyclic graph via the "acyclic monad" (low priority)

The priority of this requirement is low, because it seems to work only for graphs that are fixed at compile time. (Andrey: Is this really true?)

The basic idea in this method is to incrementally build the graph The safety comes from the fact that one can only define edges only when the vertex is being defined. The directed edges can only be towards vertices which have been defined previously. One can notice an implicit ordering on vertices in this case. The structure of the graph is the main property in consideration here. Any kind of generic implementation will be treated as vertex labels.

For eg,

graph = do
  x1 <- vertex "x1"
  x2 <- vertex "x1"
  return ()

In the example above x1 and x2 are not the same vertices. They are 2 different vertices with the same label.

See: https://gist.github.com/adithyaov/f87b5b496fd88ef91cfe438dfaf3a955

Question (Adithya): Is this kind of an implementation acceptable?

Response (Andrey): I don't know: this is a question to be answered by you during GSoC. Your task is to implement the function runAcyclicMonad, whose type signature is given below, so that the resulting Acyclic.AdjacencyMap is guaranteed to be consistent. If you succeed, then the answer is "Yes", if not, then the answer is "No".

Problem (Adithya): The main problem is that, in a way, to create the graph one needs to know the topological sorting of the graph itself. So for implementing something like scc one needs to topologically sort the strongly connected components and then construct the graph!

Comment (Andrey): I don't understand why scc is mixed into this requirement. This requirement has nothing to do with strongly connected components. The goal is to provide a way to construct acyclic graphs using do-notation. I don't know if this is achievable, but scc is not a part of this requirement at all.

data AcyclicMonad a
instance Monad AcyclicMonad

runAcyclicMonad :: Ord a => AcyclicMonad a -> Acyclic.AdjacencyMap a

TODO: Add example.

Deconstruct obtaining a topological sort (high priority)

Since the graph is acyclic, we are guaranteed that it can be topologically sorted:

topSort :: Ord a => Acyclic.AdjacencyMap a -> [a]

Status

A first prototype available here: https://github.com/snowleopard/alga/pull/199.

Clone this wiki locally