Re: [Haskell-cafe] writing graphs with do-notation

2009-12-15 Thread Emil Axelsson
Yes, that's probably close to what I want. It would of course be nice to 
also have a monadic/applicative interface for building the graphs. In 
libraries like Wired where you're in a monad anyway, this would get rid 
of the need for IO.


Koen Claessen has made a sketch of a generic graph library that we were 
planning to use as a basis for the EDSLs at Chalmers. But as far as I 
remember it looked a lot like the graph in data-reify, so maybe we 
should just use that instead.


/ Emil



Levent Erkok skrev:
Andy Gill wrote a very nice recent paper on this topic which can serve  
as the basis for a generic implementation:


http://www.ittc.ku.edu/~andygill/paper.php?label=DSLExtract09

As long as you do your reification in the IO monad, Andy's library  
gives you the graph conversion for (almost-) free.


-Levent.

On Dec 13, 2009, at 10:48 PM, Emil Axelsson wrote:

Hi!

This technique has been used to define netlists in hardware  
description languages. The original Lava [1] used a monad, but later  
switched to using observable sharing [2]. Wired [3] uses a monad  
similar to yours (but more complicated).


I think it would be nice to have a single library for defining such  
graphs (or maybe there is one already?). The graph structure in  
Wired could probably be divided into a purely structural part and a  
hardware-specific part.


[1] http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.46.5221
[2] http://www.cs.chalmers.se/~dave/papers/observable-sharing.pdf
[3] http://hackage.haskell.org/package/Wired

/ Emil



Soenke Hahn skrev:

Hi!
Some time ago, i needed to write down graphs in Haskell. I wanted  
to be able to write them down without to much noise, to make them  
easily maintainable. I came up with a way to define graphs using  
monads and the do notation. I thought this might be interesting to  
someone, so i wrote a small script to illustrate the idea. Here's  
an example:

example :: Graph String
example = buildGraph $ do
   a - mkNode A []
   b - mkNode B [a]
   mkNode C [a, b]
In this graph there are three nodes identified by [A, B, C]  
and three edges ([(A, B), (A, C), (B, C)]). Think of  
the variables a and b as outputs of the nodes A and B. Note  
that each node identifier needs to be mentioned only once. Also the  
definition of edges (references to other nodes via the outputs) can  
be checked at compile time.
The attachment is a little script that defines a Graph-type  
(nothing elaborate), the buildGraph function and an example graph  
that is a little more complex than the above. The main function of  
the script prints the example graph to stdout to be read by dot (or  
similar).
By the way, it is possible to define cyclic graphs using mdo  
(RecursiveDo).
I haven't come across something similar, so i thought, i'd share  
it. What do you think?

Sönke

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] writing graphs with do-notation

2009-12-15 Thread Ivan Lazar Miljenovic
Emil Axelsson e...@chalmers.se writes:

 Yes, that's probably close to what I want. It would of course be nice
 to also have a monadic/applicative interface for building the
 graphs. In libraries like Wired where you're in a monad anyway, this
 would get rid of the need for IO.

IIRC, dotgen does this for Dot graphs for Graphviz.

 Koen Claessen has made a sketch of a generic graph library that we
 were planning to use as a basis for the EDSLs at Chalmers. But as far
 as I remember it looked a lot like the graph in data-reify, so maybe
 we should just use that instead.

Cale and I started on our own generic graph class... we should probably
get back to working on it...


 / Emil



 Levent Erkok skrev:
 Andy Gill wrote a very nice recent paper on this topic which can
 serve  as the basis for a generic implementation:

 http://www.ittc.ku.edu/~andygill/paper.php?label=DSLExtract09

 As long as you do your reification in the IO monad, Andy's library
 gives you the graph conversion for (almost-) free.

 -Levent.

 On Dec 13, 2009, at 10:48 PM, Emil Axelsson wrote:
 Hi!

 This technique has been used to define netlists in hardware
 description languages. The original Lava [1] used a monad, but
 later  switched to using observable sharing [2]. Wired [3] uses a
 monad  similar to yours (but more complicated).

 I think it would be nice to have a single library for defining such
 graphs (or maybe there is one already?). The graph structure in
 Wired could probably be divided into a purely structural part and a
 hardware-specific part.

 [1] http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.46.5221
 [2] http://www.cs.chalmers.se/~dave/papers/observable-sharing.pdf
 [3] http://hackage.haskell.org/package/Wired

 / Emil



 Soenke Hahn skrev:
 Hi!
 Some time ago, i needed to write down graphs in Haskell. I wanted
 to be able to write them down without to much noise, to make them
 easily maintainable. I came up with a way to define graphs using
 monads and the do notation. I thought this might be interesting to
 someone, so i wrote a small script to illustrate the idea. Here's
 an example:
 example :: Graph String
 example = buildGraph $ do
a - mkNode A []
b - mkNode B [a]
mkNode C [a, b]
 In this graph there are three nodes identified by [A, B, C]
 and three edges ([(A, B), (A, C), (B, C)]). Think of
 the variables a and b as outputs of the nodes A and B. Note
 that each node identifier needs to be mentioned only once. Also
 the  definition of edges (references to other nodes via the
 outputs) can  be checked at compile time.
 The attachment is a little script that defines a Graph-type
 (nothing elaborate), the buildGraph function and an example
 graph  that is a little more complex than the above. The main
 function of  the script prints the example graph to stdout to be
 read by dot (or  similar).
 By the way, it is possible to define cyclic graphs using mdo
 (RecursiveDo).
 I haven't come across something similar, so i thought, i'd share
 it. What do you think?
 Sönke
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] writing graphs with do-notation

2009-12-14 Thread Levent Erkok
Andy Gill wrote a very nice recent paper on this topic which can serve  
as the basis for a generic implementation:


   http://www.ittc.ku.edu/~andygill/paper.php?label=DSLExtract09

As long as you do your reification in the IO monad, Andy's library  
gives you the graph conversion for (almost-) free.


-Levent.

On Dec 13, 2009, at 10:48 PM, Emil Axelsson wrote:

Hi!

This technique has been used to define netlists in hardware  
description languages. The original Lava [1] used a monad, but later  
switched to using observable sharing [2]. Wired [3] uses a monad  
similar to yours (but more complicated).


I think it would be nice to have a single library for defining such  
graphs (or maybe there is one already?). The graph structure in  
Wired could probably be divided into a purely structural part and a  
hardware-specific part.


[1] http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.46.5221
[2] http://www.cs.chalmers.se/~dave/papers/observable-sharing.pdf
[3] http://hackage.haskell.org/package/Wired

/ Emil



Soenke Hahn skrev:

Hi!
Some time ago, i needed to write down graphs in Haskell. I wanted  
to be able to write them down without to much noise, to make them  
easily maintainable. I came up with a way to define graphs using  
monads and the do notation. I thought this might be interesting to  
someone, so i wrote a small script to illustrate the idea. Here's  
an example:

example :: Graph String
example = buildGraph $ do
   a - mkNode A []
   b - mkNode B [a]
   mkNode C [a, b]
In this graph there are three nodes identified by [A, B, C]  
and three edges ([(A, B), (A, C), (B, C)]). Think of  
the variables a and b as outputs of the nodes A and B. Note  
that each node identifier needs to be mentioned only once. Also the  
definition of edges (references to other nodes via the outputs) can  
be checked at compile time.
The attachment is a little script that defines a Graph-type  
(nothing elaborate), the buildGraph function and an example graph  
that is a little more complex than the above. The main function of  
the script prints the example graph to stdout to be read by dot (or  
similar).
By the way, it is possible to define cyclic graphs using mdo  
(RecursiveDo).
I haven't come across something similar, so i thought, i'd share  
it. What do you think?

Sönke

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] writing graphs with do-notation

2009-12-13 Thread Neil Davies

Neat

Surely there is somewhere in the haskell Twiki that something like  
this should live?


Neil

On 12 Dec 2009, at 21:00, Soenke Hahn wrote:


Hi!

Some time ago, i needed to write down graphs in Haskell. I wanted to  
be able
to write them down without to much noise, to make them easily  
maintainable. I
came up with a way to define graphs using monads and the do  
notation. I thought
this might be interesting to someone, so i wrote a small script to  
illustrate

the idea. Here's an example:

example :: Graph String
example = buildGraph $ do
   a - mkNode A []
   b - mkNode B [a]
   mkNode C [a, b]

In this graph there are three nodes identified by [A, B, C]  
and three
edges ([(A, B), (A, C), (B, C)]). Think of the variables  
a and b
as outputs of the nodes A and B. Note that each node identifier  
needs to be
mentioned only once. Also the definition of edges (references to  
other nodes

via the outputs) can be checked at compile time.

The attachment is a little script that defines a Graph-type (nothing
elaborate), the buildGraph function and an example graph that is a  
little
more complex than the above. The main function of the script prints  
the

example graph to stdout to be read by dot (or similar).

By the way, it is possible to define cyclic graphs using mdo  
(RecursiveDo).


I haven't come across something similar, so i thought, i'd share it.  
What do

you think?

Sönke
Graph-Monads.hs___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] writing graphs with do-notation

2009-12-13 Thread Emil Axelsson

Hi!

This technique has been used to define netlists in hardware description 
languages. The original Lava [1] used a monad, but later switched to 
using observable sharing [2]. Wired [3] uses a monad similar to yours 
(but more complicated).


I think it would be nice to have a single library for defining such 
graphs (or maybe there is one already?). The graph structure in Wired 
could probably be divided into a purely structural part and a 
hardware-specific part.


[1] http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.46.5221
[2] http://www.cs.chalmers.se/~dave/papers/observable-sharing.pdf
[3] http://hackage.haskell.org/package/Wired

/ Emil



Soenke Hahn skrev:

Hi!

Some time ago, i needed to write down graphs in Haskell. I wanted to be able 
to write them down without to much noise, to make them easily maintainable. I 
came up with a way to define graphs using monads and the do notation. I thought 
this might be interesting to someone, so i wrote a small script to illustrate 
the idea. Here's an example:


example :: Graph String
example = buildGraph $ do
a - mkNode A []
b - mkNode B [a]
mkNode C [a, b]

In this graph there are three nodes identified by [A, B, C] and three 
edges ([(A, B), (A, C), (B, C)]). Think of the variables a and b 
as outputs of the nodes A and B. Note that each node identifier needs to be 
mentioned only once. Also the definition of edges (references to other nodes 
via the outputs) can be checked at compile time.


The attachment is a little script that defines a Graph-type (nothing 
elaborate), the buildGraph function and an example graph that is a little 
more complex than the above. The main function of the script prints the 
example graph to stdout to be read by dot (or similar).


By the way, it is possible to define cyclic graphs using mdo (RecursiveDo).

I haven't come across something similar, so i thought, i'd share it. What do 
you think?


Sönke


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] writing graphs with do-notation

2009-12-12 Thread Soenke Hahn
Hi!

Some time ago, i needed to write down graphs in Haskell. I wanted to be able 
to write them down without to much noise, to make them easily maintainable. I 
came up with a way to define graphs using monads and the do notation. I thought 
this might be interesting to someone, so i wrote a small script to illustrate 
the idea. Here's an example:

example :: Graph String
example = buildGraph $ do
a - mkNode A []
b - mkNode B [a]
mkNode C [a, b]

In this graph there are three nodes identified by [A, B, C] and three 
edges ([(A, B), (A, C), (B, C)]). Think of the variables a and b 
as outputs of the nodes A and B. Note that each node identifier needs to be 
mentioned only once. Also the definition of edges (references to other nodes 
via the outputs) can be checked at compile time.

The attachment is a little script that defines a Graph-type (nothing 
elaborate), the buildGraph function and an example graph that is a little 
more complex than the above. The main function of the script prints the 
example graph to stdout to be read by dot (or similar).

By the way, it is possible to define cyclic graphs using mdo (RecursiveDo).

I haven't come across something similar, so i thought, i'd share it. What do 
you think?

Sönke
{-# language RecursiveDo #-}


import Data.Map ((!), fromList)

import Control.Monad.State

import qualified Text.Dot as Dot


-- * Graph definition

-- | type of Graphs.
data Graph node
= Graph {
nodes :: [node],
edges :: [(node, node)]
  }
  deriving Show

-- | The empty Graph.
emptyGraph :: Graph a
emptyGraph = Graph [] []

-- | Converts a Graph into dot format
toDot :: (Ord s, Show s) = Graph s - String
toDot (Graph nodes edges) = Dot.showDot $ do
ids - mapM (\ l - Dot.node [(label, show l)]) nodes
let idMap = fromList $ zip nodes ids
mapM_ (\ (a, b) - (idMap ! a) Dot..-. (idMap ! b)) edges


-- * GraphMonad

-- | Allows to write directed Graphs in form of monadic statements.
type GraphMonad n a = State (Graph n) a

data Output n = Output n

-- | Builds the Graph given a graph creation command.
buildGraph :: GraphMonad n () - Graph n
buildGraph cmd = snd $ runState cmd emptyGraph

-- | Constructs a node. $inputs$ are all nodes which should be
-- connected (via edges) to this new node.
mkNode :: n - [Output n] - GraphMonad n (Output n)
mkNode node inputs =
State $ \ (Graph nodes edges) -
let newEdges = map (\ (Output input) - (input, node)) inputs
in (Output node, Graph (node : nodes) (edges ++ newEdges))


-- * example graph

-- | This is just an example graph.
example :: Graph String
example = buildGraph $ mdo

mkNode unconnected []

a - mkNode A []
b - mkNode B [a]
mkNode C [a, b]

subgraph a b

c1 - mkNode cyclic [c1, c2]
c2 - mkNode cyclic2 [c1]

return ()

-- | example for encapsulating subgraphs.
-- This doesn't show in the resulting graph.
subgraph :: Output String - Output String - GraphMonad String ()
subgraph a b = do
x - mkNode x [a]
mkNode y [x, b]
return ()

-- | Print out the example graph in dot format to stdout
main = putStrLn $ toDot example

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe