
Hello I'm trying to write a simple graph library for a project of mine (actually, I'm porting it from OCaml) but I've got a design question right in the beginning. My Graph type is the following. data Graph a b = Graph { adjacencies :: Map Int (a, (Map Int b)) , numVertices :: Int , numEdges :: Int } Types "a" and "b" refer to vertex and edge labels (I know it's kind of weird to use a Map of Maps to represent a graph, but it helps me removing vertices later, which is something I'll need to do.) Creating an empty graph is trivial: empty :: Graph a b empty = Graph Map.empty 0 0 The issue I hit was when writing the function to add a vertex to the graph. Since I need to update the vertex counter, I've used the state monad: addVertex :: Int -> a -> State (Graph a b) () addVertex vertex label = do g <- get let adj = Map.insert vertex (label, Map.empty) (adjacencies g) put $ g { adjacencies = adj, numVertices = numVertices g + 1 } That works fine, but from the point of view of a user of the library, the addVertex function should take a "Graph a b" as its first argument, as one would expect to be able to say which graph is going to be modified. So I'm confused right now about how I should proceed. Any hints regarding that? Best regards, Andre

2008/9/18 Andre Nathan
Hello
I'm trying to write a simple graph library for a project of mine (actually, I'm porting it from OCaml) but I've got a design question right in the beginning.
My Graph type is the following.
data Graph a b = Graph { adjacencies :: Map Int (a, (Map Int b)) , numVertices :: Int , numEdges :: Int }
Types "a" and "b" refer to vertex and edge labels (I know it's kind of weird to use a Map of Maps to represent a graph, but it helps me removing vertices later, which is something I'll need to do.)
Creating an empty graph is trivial:
empty :: Graph a b empty = Graph Map.empty 0 0
The issue I hit was when writing the function to add a vertex to the graph. Since I need to update the vertex counter, I've used the state monad:
addVertex :: Int -> a -> State (Graph a b) () addVertex vertex label = do g <- get let adj = Map.insert vertex (label, Map.empty) (adjacencies g) put $ g { adjacencies = adj, numVertices = numVertices g + 1 }
That works fine, but from the point of view of a user of the library, the addVertex function should take a "Graph a b" as its first argument, as one would expect to be able to say which graph is going to be modified.
So I'm confused right now about how I should proceed. Any hints regarding that?
Hi, Why not simply addVertex (Graph adj nv ne) vertex label = Graph (Map.insert ...) (nv+1) ne ? If you don't want to pattern match because you expect you Graph data type to change later, you can instead use addVertex g vertex label = Graph (Map.insert ...) (nv+1) ne where adj = adjacencies g nv = numVertices g ne = numEdges g If you need the one inside the State monad, you can reuse the new version of addVertex. Or, why do you want the user of your library give the graph as an argument if that argument is implicit (because it is inside the State monad) ? Hope this helps, Thu

On Thu, 2008-09-18 at 21:13 +0200, minh thu wrote:
If you need the one inside the State monad, you can reuse the new version of addVertex.
You mean making the graph creation functions (which will call addVertex/Edge) use the State monad instead? Interesting idea... what I really wanted was to hide from the user how the graph library is implemented, so he wouldn't need to know about the state monad to use the library, but maybe I should keep these basic functions pure and let the user decide. I'll think about it :) Best, Andre

On Thu, 18 Sep 2008, Andre Nathan wrote:
The issue I hit was when writing the function to add a vertex to the graph. Since I need to update the vertex counter, I've used the state monad:
addVertex :: Int -> a -> State (Graph a b) () addVertex vertex label = do g <- get let adj = Map.insert vertex (label, Map.empty) (adjacencies g) put $ g { adjacencies = adj, numVertices = numVertices g + 1 }
That works fine, but from the point of view of a user of the library, the addVertex function should take a "Graph a b" as its first argument, as one would expect to be able to say which graph is going to be modified.
Think of the state monad as processing a graph in-place. Which graph is addressed is declared when running the State monad using runState or evalState.

On Thu, 2008-09-18 at 21:15 +0200, Henning Thielemann wrote:
Think of the state monad as processing a graph in-place. Which graph is addressed is declared when running the State monad using runState or evalState.
Interesting. Is it good practice then to do something like type GraphM a b = State (Graph a b) to hide from the user that I'm using the State monad underneath? Best, Andre

On Thu, 18 Sep 2008, Andre Nathan wrote:
On Thu, 2008-09-18 at 21:15 +0200, Henning Thielemann wrote:
Think of the state monad as processing a graph in-place. Which graph is addressed is declared when running the State monad using runState or evalState.
Interesting. Is it good practice then to do something like
type GraphM a b = State (Graph a b)
to hide from the user that I'm using the State monad underneath?
'type' won't hide anything but reduces writing. With 'newtype' you could hide the State monad. You could do this, if you plan to change the representation of a Graph to something based on mutable structures. On the other hand with 'newtype GraphM' the user could not easily work on several states of the graph simultaneously.

On Thu, 2008-09-18 at 15:43 -0300, Andre Nathan wrote:
My Graph type is the following.
data Graph a b = Graph { adjacencies :: Map Int (a, (Map Int b)) , numVertices :: Int , numEdges :: Int }
addVertex :: Int -> a -> State (Graph a b) () addVertex vertex label = do g <- get let adj = Map.insert vertex (label, Map.empty) (adjacencies g) put $ g { adjacencies = adj, numVertices = numVertices g + 1 }
So I'm confused right now about how I should proceed. Any hints regarding that?
To be honest I would not bother with the state monad and just make them pure operations returning new graphs: addVertex :: Int -> a -> Graph a b -> Graph a b It's very common to have this style, ie returning a new/updated structure explicitly rather than implicitly in a state monad. Just look at the Data.Map api for example. If you later want to stick it in a state monad then that would be straightforward but also easy to use directly. Duncan

Duncan Coutts wrote:
On Thu, 2008-09-18 at 15:43 -0300, Andre Nathan wrote:
My Graph type is the following.
data Graph a b = Graph { adjacencies :: Map Int (a, (Map Int b)) , numVertices :: Int , numEdges :: Int }
addVertex :: Int -> a -> State (Graph a b) () addVertex vertex label = do g <- get let adj = Map.insert vertex (label, Map.empty) (adjacencies g) put $ g { adjacencies = adj, numVertices = numVertices g + 1 }
So I'm confused right now about how I should proceed. Any hints regarding that?
To be honest I would not bother with the state monad and just make them pure operations returning new graphs:
addVertex :: Int -> a -> Graph a b -> Graph a b
It's very common to have this style, ie returning a new/updated structure explicitly rather than implicitly in a state monad. Just look at the Data.Map api for example. If you later want to stick it in a state monad then that would be straightforward but also easy to use directly.
I agree. Duncan's version also looks more atomic to me, because Andre's version (that's renamed to addVertexM below) could be easily derived by: addVertexM v l = modify (addVertex v l) The opposite derivation is also possible but does additional wrapping into and out of a state: addVertex v l = execState (addVertexM v l) (Furthermore the module Control.Monad.State is "non-portable", because get, put, modify and gets come in via the MonadState class, but separate not overloaded versions for these function would make sense in the same way we have "map" despite "fmap".) Cheers Christian

On Fri, 2008-09-19 at 10:35 +0200, Christian Maeder wrote:
I agree. Duncan's version also looks more atomic to me, [...]
OK, so what I have now is addVertex :: Int -> a -> Graph a b -> Graph a b addVertex v l g = Graph adj (numVertices g + 1) (numEdges g) where adj = Map.insert v (l, Map.empty) (adjacencies g) addEdge :: Int -> Int -> b -> Graph a b -> Graph a b addEdge v w l g = Graph adj (numVertices g) (numEdges g + 1) where adj = Map.insert v (vl, ns') (adjacencies g) ns' = Map.insert w l ns (vl, ns) = fromJust $ Map.lookup v (adjacencies g) Creating a random graph [G(n,p) model] the naive way: type RandomGraph a b = StateT (Graph a b) IO () randomGraph :: Int -> Double -> IO (Graph Int Int) randomGraph n p = execStateT create Graph.empty where create = mapM_ (uncurry $ createVertex p) vls vls = zip [1..n] (repeat 1) createVertex :: Double -> Int -> a -> RandomGraph a Int createVertex p v l = do modify (Graph.addVertex v l) createEdges v p createEdges :: Int -> Double -> RandomGraph a Int createEdges n p = mapM_ (maybeAddEdges n) [1..n-1] where maybeAddEdges v w = do maybeAddEdge v w maybeAddEdge w v maybeAddEdge v w = do r <- lift randomDouble when (r < p) $ modify (addEdge v w 1) randomDouble :: IO Double randomDouble = randomIO So, to reference another thread, does this make anyone cry? :) Thanks a lot for the suggestions, Andre

Am Freitag, 19. September 2008 22:55 schrieb Andre Nathan:
On Fri, 2008-09-19 at 10:35 +0200, Christian Maeder wrote:
I agree. Duncan's version also looks more atomic to me,
[...]
OK, so what I have now is
addVertex :: Int -> a -> Graph a b -> Graph a b addVertex v l g = Graph adj (numVertices g + 1) (numEdges g) where adj = Map.insert v (l, Map.empty) (adjacencies g)
addEdge :: Int -> Int -> b -> Graph a b -> Graph a b addEdge v w l g = Graph adj (numVertices g) (numEdges g + 1) where adj = Map.insert v (vl, ns') (adjacencies g) ns' = Map.insert w l ns (vl, ns) = fromJust $ Map.lookup v (adjacencies g)
Creating a random graph [G(n,p) model] the naive way:
type RandomGraph a b = StateT (Graph a b) IO ()
randomGraph :: Int -> Double -> IO (Graph Int Int) randomGraph n p = execStateT create Graph.empty where create = mapM_ (uncurry $ createVertex p) vls vls = zip [1..n] (repeat 1)
createVertex :: Double -> Int -> a -> RandomGraph a Int createVertex p v l = do modify (Graph.addVertex v l) createEdges v p
createEdges :: Int -> Double -> RandomGraph a Int createEdges n p = mapM_ (maybeAddEdges n) [1..n-1] where maybeAddEdges v w = do maybeAddEdge v w maybeAddEdge w v maybeAddEdge v w = do r <- lift randomDouble when (r < p) $ modify (addEdge v w 1)
randomDouble :: IO Double randomDouble = randomIO
So, to reference another thread, does this make anyone cry? :)
Yes. What's IO gotta do with it? It's much cleaner to pass the PRNG as an explicit argument (or what about StateT (Graph a b) (State StdGen) ?). And in addVertex/addEdge, it might be good to check whether the vertex/edge is already present.
Thanks a lot for the suggestions, Andre

On Fri, 2008-09-19 at 23:16 +0200, Daniel Fischer wrote:
Yes. What's IO gotta do with it?
I did it because of randomIO :(
(or what about StateT (Graph a b) (State StdGen) ?).
Now there's something I wouldn't have thought of... I changed the RandomGraph type to type RandomGraph a b = StateT (Graph a b) (State StdGen) () and randomFloat to randomDouble :: State StdGen Double randomDouble = State random and randomGraph to randomGraph :: StdGen -> Int -> Double -> Graph Int Int randomGraph gen n p = evalState (execStateT create Graph.empty) gen where create = mapM_ (uncurry $ createVertex p) vls vls = zip [1..n] (repeat 42) However, when I try to create a graph with 1000 vertices I get a stack overflow, which didn't happen in the IO version. Any idea why that happens? Thanks, Andre

On Fri, Sep 19, 2008 at 7:02 PM, Andre Nathan
On Fri, 2008-09-19 at 23:16 +0200, Daniel Fischer wrote:
Yes. What's IO gotta do with it?
I did it because of randomIO :(
(or what about StateT (Graph a b) (State StdGen) ?).
Now there's something I wouldn't have thought of... I changed the RandomGraph type to
type RandomGraph a b = StateT (Graph a b) (State StdGen) ()
and randomFloat to
randomDouble :: State StdGen Double randomDouble = State random
and randomGraph to
randomGraph :: StdGen -> Int -> Double -> Graph Int Int randomGraph gen n p = evalState (execStateT create Graph.empty) gen where create = mapM_ (uncurry $ createVertex p) vls vls = zip [1..n] (repeat 42)
However, when I try to create a graph with 1000 vertices I get a stack overflow, which didn't happen in the IO version. Any idea why that happens?
I believe modify is lazy. Try replacing it with a stricter version,
modify' f = do
s <- get
put $! f s
--
Dave Menendez

Am Samstag, 20. September 2008 08:53 schrieb David Menendez:
On Fri, Sep 19, 2008 at 7:02 PM, Andre Nathan
wrote: On Fri, 2008-09-19 at 23:16 +0200, Daniel Fischer wrote:
Yes. What's IO gotta do with it?
I did it because of randomIO :(
(or what about StateT (Graph a b) (State StdGen) ?).
Now there's something I wouldn't have thought of... I changed the RandomGraph type to
type RandomGraph a b = StateT (Graph a b) (State StdGen) ()
and randomFloat to
randomDouble :: State StdGen Double randomDouble = State random
and randomGraph to
randomGraph :: StdGen -> Int -> Double -> Graph Int Int randomGraph gen n p = evalState (execStateT create Graph.empty) gen where create = mapM_ (uncurry $ createVertex p) vls vls = zip [1..n] (repeat 42)
However, when I try to create a graph with 1000 vertices I get a stack overflow, which didn't happen in the IO version. Any idea why that happens?
I believe modify is lazy. Try replacing it with a stricter version,
modify' f = do s <- get put $! f s
Or try Control.Monad.State.Strict.

On Sat, 2008-09-20 at 14:56 +0200, Daniel Fischer wrote:
modify' f = do s <- get put $! f s
Or try Control.Monad.State.Strict.
Control.Monad.State.Strict did it for me, but the strict modify didn't. I tried using modify' and also randomDouble = do g <- get let (r, g') = random g put $! g' return r instead of randomDouble = State random Any hints on how I could find where else the program is being too lazy? Thanks, Andre

Am Samstag, 20. September 2008 17:46 schrieb Andre Nathan:
On Sat, 2008-09-20 at 14:56 +0200, Daniel Fischer wrote:
modify' f = do s <- get put $! f s
Or try Control.Monad.State.Strict.
Control.Monad.State.Strict did it for me, but the strict modify didn't. I tried using modify' and also
randomDouble = do g <- get let (r, g') = random g put $! g' return r
instead of
randomDouble = State random
Any hints on how I could find where else the program is being too lazy?
Profiling. Find out where your programme spends its time and what uses the memory. Add lots of {-# SCC #-} pragmas to get a more detailed picture.
Thanks, Andre
participants (8)
-
Andre Nathan
-
apfelmus
-
Christian Maeder
-
Daniel Fischer
-
David Menendez
-
Duncan Coutts
-
Henning Thielemann
-
minh thu