algebraic-graphs-0.0.5: A library for algebraic graph construction and transformation

Copyright(c) Andrey Mokhov 2016-2017
LicenseMIT (see the file LICENSE)
Maintainerandrey.mokhov@gmail.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Algebra.Graph.Export

Contents

Description

Alga is a library for algebraic construction and manipulation of graphs in Haskell. See this paper for the motivation behind the library, the underlying theory, and implementation details.

This module defines basic data types and functions for exporting graphs in textual and binary formats. Algebra.Graph.Export.Dot provides DOT-specific functionality.

Synopsis

Constructing and exporting documents

data Doc s Source #

An abstract document type, where s is the type of strings or words (text or binary). Doc s is a Monoid, therefore mempty corresponds to the empty document and two documents can be concatenated with mappend (or operator <>). Note that most functions on Doc s require that the underlying type s is also a Monoid.

Instances

(Monoid s, Eq s) => Eq (Doc s) Source # 

Methods

(==) :: Doc s -> Doc s -> Bool #

(/=) :: Doc s -> Doc s -> Bool #

(Monoid s, Ord s) => Ord (Doc s) Source # 

Methods

compare :: Doc s -> Doc s -> Ordering #

(<) :: Doc s -> Doc s -> Bool #

(<=) :: Doc s -> Doc s -> Bool #

(>) :: Doc s -> Doc s -> Bool #

(>=) :: Doc s -> Doc s -> Bool #

max :: Doc s -> Doc s -> Doc s #

min :: Doc s -> Doc s -> Doc s #

(Monoid s, Show s) => Show (Doc s) Source # 

Methods

showsPrec :: Int -> Doc s -> ShowS #

show :: Doc s -> String #

showList :: [Doc s] -> ShowS #

IsString s => IsString (Doc s) Source # 

Methods

fromString :: String -> Doc s #

Semigroup (Doc s) Source # 

Methods

(<>) :: Doc s -> Doc s -> Doc s #

sconcat :: NonEmpty (Doc s) -> Doc s #

stimes :: Integral b => b -> Doc s -> Doc s #

Monoid (Doc s) Source # 

Methods

mempty :: Doc s #

mappend :: Doc s -> Doc s -> Doc s #

mconcat :: [Doc s] -> Doc s #

literal :: s -> Doc s Source #

Construct a document comprising a single string or word. If s is an instance of class IsString, then documents of type Doc s can be constructed directly from string literals (see the second example below).

literal "Hello, " <> literal "World!" == literal "Hello, World!"
literal "I am just a string literal"  == "I am just a string literal"
literal mempty                        == mempty
render . literal                      == id
literal . render                      == id

render :: Monoid s => Doc s -> s Source #

Render a document as a single string or word. An inverse of the function literal.

render (literal "al" <> literal "ga") :: (IsString s, Monoid s) => s
render (literal "al" <> literal "ga") == "alga"
render mempty                         == mempty
render . literal                      == id
literal . render                      == id

Common combinators for text documents

(<+>) :: (Eq s, IsString s, Monoid s) => Doc s -> Doc s -> Doc s infixl 7 Source #

Concatenate two documents, separated by a single space, unless one of the documents is empty. The operator <+> is associative with identity mempty.

x <+> mempty         == x
mempty <+> x         == x
x <+> (y <+> z)      == (x <+> y) <+> z
"name" <+> "surname" == "name surname"

brackets :: IsString s => Doc s -> Doc s Source #

Wrap a document in square brackets.

brackets "i"    == "[i]"
brackets mempty == "[]"

doubleQuotes :: IsString s => Doc s -> Doc s Source #

Wrap a document into double quotes.

doubleQuotes "/path/with spaces"   == "\"/path/with spaces\""
doubleQuotes (doubleQuotes mempty) == "\"\"\"\""

indent :: IsString s => Int -> Doc s -> Doc s Source #

Prepend a given number of spaces to a document.

indent 0        == id
indent 1 mempty == " "

unlines :: IsString s => [Doc s] -> Doc s Source #

Concatenate documents after appending a terminating newline symbol to each.

unlines []                    == mempty
unlines [mempty]              == "\n"
unlines ["title", "subtitle"] == "title\nsubtitle\n"

Generic graph export

export :: (Ord a, ToGraph g, ToVertex g ~ a) => (a -> Doc s) -> (a -> a -> Doc s) -> g -> Doc s Source #

Export a graph into a document given two functions that construct documents for individual vertices and edges. The order of export is: vertices, sorted by Ord a, and then edges, sorted by Ord (a, a).

For example:

vDoc x   = literal (show x) <> "\n"
eDoc x y = literal (show x) <> " -> " <> literal (show y) <> "\n"
> putStrLn $ render $ export vDoc eDoc (1 + 2 * (3 + 4) :: Graph Int)

1
2
3
4
2 -> 3
2 -> 4