[Haskell-cafe] Graph type

C K Kashyap ckkashyap at gmail.com
Sun Jun 13 23:35:48 EDT 2010


Thanks Roman.
I think I'll try out Data.Graph in that case.

On Mon, Jun 14, 2010 at 8:53 AM, Ivan Lazar Miljenovic <
ivan.miljenovic at gmail.com> wrote:

> C K Kashyap <ckkashyap at gmail.com> writes:
>
> > I love this list ... thanks Roman.
> >
> > I take it that there is nothing obviously inefficient about this approach
> to
> > graph - as in the graph type.
>
> Sure there is (using p = |V|, q = |E|):
>
> * Finding a particular node is O(p).
>
> * Adding an edge to an already existing node is also O(p).
>
> * Finding reverse edges is O(q) (probably more actually since you'd be
>  checking every node that you have and then checking if the other end
>  is in the list of relationships).
>
> etc.
>
> The main advantage of your type is that it's O(1) to add a new node +
> successor edges.
>
> Now, depending upon what you're wanting to do, this may suffice.
> However, there are a couple of alternatives:
>
> * Use Data.Graph from containers
>
> * Use either Data.Graph.Inductive.Tree or
>  Data.Graph.Inductive.PatriciaTree (which has better performance but
>  doesn't allow multiple edges) from fgl.
>
> * If you still want a custom type, then something like "Map v (Set v)"
>  would be much more efficient than using [(v, [v])] (this could be
>  improved at the expense of disk space and more bookkeeping by using
>  "Map v (Set v, Set v)" to store both successor and predecessor edges).
>
> >
> >
> > On Mon, Jun 14, 2010 at 12:02 AM, Roman Cheplyaka <roma at ro-che.info>
> wrote:
> >
> >> * C K Kashyap <ckkashyap at gmail.com> [2010-06-13 22:45:44+0530]
> >> > Hi,
> >> > I am trying to write a routine that would generate a graph - where
> each
> >> > vertex would be a string.
> >> >
> >> > type Graph v = [(v,[v])]  -- list of tuples of vertices and adjacent
> >> > vertices list
> >> >
> >> > addEdgeToGraph :: Graph -> String -> String -> Graph
> >> >
> >> > I am having trouble coming up with the body of this function - that
> takes
> >> > the original graph, and an edge (string -> string) and the produces
> the
> >> new
> >> > graph.
> >>
> >> If you know that the vertices already exist and you need only to add an
> >> edge, then you just go through all the vertices, compare current vertex
> >> to given ones and if they match add a vertex.
> >>
> >> \begin{code}
> >> addEdgeToGraph :: Graph String -> String -> String -> Graph String
> >> addEdgeToGraph gr v1 v2 = map modify gr
> >>    where
> >>    modify (v,vs) | v == v1 = (v,v2:vs)
> >>    modify (v,vs) | v == v2 = (v,v1:vs)
> >>    modify x = x
> >> \end{code}
> >>
> >> Otherwise it is possible that one (or both) vertex doesn't exist yet, so
> >> you first need to "try" the first version, and if at least one of the
> >> vertex is not found, add it to the list. You can use fold for this.
> >>
> >> \begin{code}
> >> addEdgeToGraph' :: Graph String -> String -> String -> Graph String
> >> addEdgeToGraph' gr v1 v2 =
> >>    let (newgr, (foundV1, foundV2)) = foldr modify ([],(False,False)) gr
> >>    in
> >>        (if foundV1 then [] else [(v1,[v2])]) ++
> >>        (if foundV2 then [] else [(v2,[v1])]) ++
> >>        newgr
> >>    where
> >>    modify (v,vs) (lst,(_,foundV2)) | v == v1 = ((v,v2:vs):lst,
> >> (True,foundV2))
> >>    modify (v,vs) (lst,(foundV1,_)) | v == v2 = ((v,v1:vs):lst,
> >> (foundV1,True))
> >>    modify v (lst,f) = (v:lst,f)
> >> \end{code}
> >>
> >> --
> >> Roman I. Cheplyaka :: http://ro-che.info/
> >> "Don't let school get in the way of your education." - Mark Twain
> >> _______________________________________________
> >> Haskell-Cafe mailing list
> >> Haskell-Cafe at haskell.org
> >> http://www.haskell.org/mailman/listinfo/haskell-cafe
> >>
>
> --
> Ivan Lazar Miljenovic
> Ivan.Miljenovic at gmail.com
> IvanMiljenovic.wordpress.com
>



-- 
Regards,
Kashyap
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20100613/9df95bc4/attachment.html


More information about the Haskell-Cafe mailing list