How to give unique name/id to nodes outside any monad ?

Hi, I'd like to process some kind of graph data structure, say something like data DS = A [DS] | B DS DS | C. but I want to be able to discover any sharing. Thus, in b = B a a where a = A [C], if I want to malloc a similar data structure, I have to handle to the node representing B two times the same pointer (the one returned after allocating A [C]). To discover sharing, I thought it would be necessary to give unique name to node and then compare them while traversing the graph. I could give the name by hand but it would be cumbersome. But at least it would not require any monad for the bookkeeping of ungiven names. Is it possible to give those names automatically but outside any monad ? Thanks, Thu

On Thu, Jan 8, 2009 at 1:28 AM, minh thu
Hi,
I'd like to process some kind of graph data structure, say something like
data DS = A [DS] | B DS DS | C.
but I want to be able to discover any sharing. Thus, in
b = B a a where a = A [C],
if I want to malloc a similar data structure, I have to handle to the node representing B two times the same pointer (the one returned after allocating A [C]).
To discover sharing, I thought it would be necessary to give unique name to node and then compare them while traversing the graph. I could give the name by hand but it would be cumbersome. But at least it would not require any monad for the bookkeeping of ungiven names. Is it possible to give those names automatically but outside any monad ?
If your graphs are acyclic, then you can label each node with a hash and use that for comparison. This usually works very well in practice. Luke

2009/1/8 Luke Palmer
On Thu, Jan 8, 2009 at 1:28 AM, minh thu
wrote: Hi,
I'd like to process some kind of graph data structure, say something like
data DS = A [DS] | B DS DS | C.
but I want to be able to discover any sharing. Thus, in
b = B a a where a = A [C],
if I want to malloc a similar data structure, I have to handle to the node representing B two times the same pointer (the one returned after allocating A [C]).
To discover sharing, I thought it would be necessary to give unique name to node and then compare them while traversing the graph. I could give the name by hand but it would be cumbersome. But at least it would not require any monad for the bookkeeping of ungiven names. Is it possible to give those names automatically but outside any monad ?
If your graphs are acyclic, then you can label each node with a hash and use that for comparison. This usually works very well in practice.
Precisely ! How do you give that label to each node; i.e. how to ensure they are unique ? I don't want to end up with do c <- newNodeC a <- newNodeA [c] b <- newNodeB a a where newNodeX hides the handling of label. I'd like to simply write, like above, b = B a a where a = A [C] or, maybe, b = B label a a where a = A label [C] The question is : how can label be different each time ? Thanks, Thu

On Thu, Jan 8, 2009 at 1:49 AM, minh thu
I'd like to simply write, like above,
b = B a a where a = A [C]
or, maybe,
b = B label a a where a = A label [C]
The question is : how can label be different each time ?
Haskell is pure, so I can answer this precisely: obviously you cannot. Sharing is *not* observable in Haskell, because it breaks referential transparency, a very important property. So what I meant by hashing was, eg.: newtype Hash = ... data Foo = Foo Hash Int [Foo] mkFoo :: Int -> [Foo] -> Foo mkFoo n xs = Foo (hash (show n ++ concatMap (\(Foo h _ _) -> show h))) n xs hash :: String -> Hash hash = ... -- some cryptographic hash function Probably going through Strings is not the smartest way, but you get the idea? Then when two Foos have the same hash, you have odds of 1/2^64 or whatever that they are the same object. You could also compare directly without hashes, but that is slower for large data structures (more correct though -- hash comparisons always gave me the creeps). I just saw your reply to the StableName suggestion. I should warn you -- you should use this information only for optimization internal to your program. If you use it for observable effects, e.g. generating code or writing to a file[1], you are writing *bad haskell*, and you will not only lose the benefits of Haskell's purity, but you will be bitten by the unpredictable zeal of the optimizer. Luke [1] Unless you read the file back into the data structure, where the sharing is once again not observable.

Of course you don't need a monad, but you need to do the same
operations as you would with a state monad to number the nodes. This
is the only way in (pure) Haskell. There is no object identity in
Haskell, so if you want the nodes to have identity you need to provide
it.
GHC does have a library for stable names which (in the IO monad)
allows you to get something akin to the address of a value in memory.
But that's not the functional way of doing this.
-- Lennart
On Thu, Jan 8, 2009 at 9:28 AM, minh thu
Hi,
I'd like to process some kind of graph data structure, say something like
data DS = A [DS] | B DS DS | C.
but I want to be able to discover any sharing. Thus, in
b = B a a where a = A [C],
if I want to malloc a similar data structure, I have to handle to the node representing B two times the same pointer (the one returned after allocating A [C]).
To discover sharing, I thought it would be necessary to give unique name to node and then compare them while traversing the graph. I could give the name by hand but it would be cumbersome. But at least it would not require any monad for the bookkeeping of ungiven names. Is it possible to give those names automatically but outside any monad ?
Thanks, Thu _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Well, the processing of the data structure has to be done in the IO monad.
What is the library you talk about ? Could it give the "stable names"
(in IO) for
each node of the mentioned graph (I mean, after the graph has been constructed
purely) ?
Thanks,
Thu
2009/1/8 Lennart Augustsson
Of course you don't need a monad, but you need to do the same operations as you would with a state monad to number the nodes. This is the only way in (pure) Haskell. There is no object identity in Haskell, so if you want the nodes to have identity you need to provide it.
GHC does have a library for stable names which (in the IO monad) allows you to get something akin to the address of a value in memory. But that's not the functional way of doing this.
-- Lennart
On Thu, Jan 8, 2009 at 9:28 AM, minh thu
wrote: Hi,
I'd like to process some kind of graph data structure, say something like
data DS = A [DS] | B DS DS | C.
but I want to be able to discover any sharing. Thus, in
b = B a a where a = A [C],
if I want to malloc a similar data structure, I have to handle to the node representing B two times the same pointer (the one returned after allocating A [C]).
To discover sharing, I thought it would be necessary to give unique name to node and then compare them while traversing the graph. I could give the name by hand but it would be cumbersome. But at least it would not require any monad for the bookkeeping of ungiven names. Is it possible to give those names automatically but outside any monad ?
Thanks, Thu _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Great, System.Mem.StableName [1] seems to be able to do the trick.
Thank you.
[1] http://www.haskell.org/ghc/docs/latest/html/libraries/base/System-Mem-Stable...
2009/1/8 minh thu
Well, the processing of the data structure has to be done in the IO monad. What is the library you talk about ? Could it give the "stable names" (in IO) for each node of the mentioned graph (I mean, after the graph has been constructed purely) ?
Thanks, Thu
2009/1/8 Lennart Augustsson
: Of course you don't need a monad, but you need to do the same operations as you would with a state monad to number the nodes. This is the only way in (pure) Haskell. There is no object identity in Haskell, so if you want the nodes to have identity you need to provide it.
GHC does have a library for stable names which (in the IO monad) allows you to get something akin to the address of a value in memory. But that's not the functional way of doing this.
-- Lennart
On Thu, Jan 8, 2009 at 9:28 AM, minh thu
wrote: Hi,
I'd like to process some kind of graph data structure, say something like
data DS = A [DS] | B DS DS | C.
but I want to be able to discover any sharing. Thus, in
b = B a a where a = A [C],
if I want to malloc a similar data structure, I have to handle to the node representing B two times the same pointer (the one returned after allocating A [C]).
To discover sharing, I thought it would be necessary to give unique name to node and then compare them while traversing the graph. I could give the name by hand but it would be cumbersome. But at least it would not require any monad for the bookkeeping of ungiven names. Is it possible to give those names automatically but outside any monad ?
Thanks, Thu _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Look at http://www.haskell.org/ghc/docs/latest/html/libraries/base/System-Mem-Stable....
But what's wrong with constructing the graph in a monad?
On Thu, Jan 8, 2009 at 9:53 AM, minh thu
Well, the processing of the data structure has to be done in the IO monad. What is the library you talk about ? Could it give the "stable names" (in IO) for each node of the mentioned graph (I mean, after the graph has been constructed purely) ?
Thanks, Thu
2009/1/8 Lennart Augustsson
: Of course you don't need a monad, but you need to do the same operations as you would with a state monad to number the nodes. This is the only way in (pure) Haskell. There is no object identity in Haskell, so if you want the nodes to have identity you need to provide it.
GHC does have a library for stable names which (in the IO monad) allows you to get something akin to the address of a value in memory. But that's not the functional way of doing this.
-- Lennart
On Thu, Jan 8, 2009 at 9:28 AM, minh thu
wrote: Hi,
I'd like to process some kind of graph data structure, say something like
data DS = A [DS] | B DS DS | C.
but I want to be able to discover any sharing. Thus, in
b = B a a where a = A [C],
if I want to malloc a similar data structure, I have to handle to the node representing B two times the same pointer (the one returned after allocating A [C]).
To discover sharing, I thought it would be necessary to give unique name to node and then compare them while traversing the graph. I could give the name by hand but it would be cumbersome. But at least it would not require any monad for the bookkeeping of ungiven names. Is it possible to give those names automatically but outside any monad ?
Thanks, Thu _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Nothing, simply the notation. Now, with the remark of Luke, I'm
wondering how bad it is to use makeStableName/hashStableName to "copy"
the data structure in a similar one with explicit reference (that is,
using pointer or keys in a map or whatever).
Thank you,
Thu
2009/1/8 Lennart Augustsson
Look at http://www.haskell.org/ghc/docs/latest/html/libraries/base/System-Mem-Stable....
But what's wrong with constructing the graph in a monad?
On Thu, Jan 8, 2009 at 9:53 AM, minh thu
wrote: Well, the processing of the data structure has to be done in the IO monad. What is the library you talk about ? Could it give the "stable names" (in IO) for each node of the mentioned graph (I mean, after the graph has been constructed purely) ?
Thanks, Thu
2009/1/8 Lennart Augustsson
: Of course you don't need a monad, but you need to do the same operations as you would with a state monad to number the nodes. This is the only way in (pure) Haskell. There is no object identity in Haskell, so if you want the nodes to have identity you need to provide it.
GHC does have a library for stable names which (in the IO monad) allows you to get something akin to the address of a value in memory. But that's not the functional way of doing this.
-- Lennart
On Thu, Jan 8, 2009 at 9:28 AM, minh thu
wrote: Hi,
I'd like to process some kind of graph data structure, say something like
data DS = A [DS] | B DS DS | C.
but I want to be able to discover any sharing. Thus, in
b = B a a where a = A [C],
if I want to malloc a similar data structure, I have to handle to the node representing B two times the same pointer (the one returned after allocating A [C]).
To discover sharing, I thought it would be necessary to give unique name to node and then compare them while traversing the graph. I could give the name by hand but it would be cumbersome. But at least it would not require any monad for the bookkeeping of ungiven names. Is it possible to give those names automatically but outside any monad ?
Thanks, Thu _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

"minh thu"
Nothing, simply the notation. Now, with the remark of Luke, I'm wondering how bad it is to use makeStableName/hashStableName to "copy" the data structure in a similar one with explicit reference (that is, using pointer or keys in a map or whatever).
Probably you're misusing the notation. I don't see any reason, why monadic notation should be less readable. Usually it's even more readable. Luke's remark is very valid. Haskell is the wrong language for imperative programming. You don't have _any_ benefit of Haskell, if you use it like C. Try to change your mind. Monads aren't evil. They are there to make your life easier. Way easier than imperative methods. Greets, Ertugrul.
Thank you, Thu
2009/1/8 Lennart Augustsson
: Look at http://www.haskell.org/ghc/docs/latest/html/libraries/base/System-Mem-Stable....
But what's wrong with constructing the graph in a monad?
On Thu, Jan 8, 2009 at 9:53 AM, minh thu
wrote: Well, the processing of the data structure has to be done in the IO monad. What is the library you talk about ? Could it give the "stable names" (in IO) for each node of the mentioned graph (I mean, after the graph has been constructed purely) ?
Thanks, Thu
2009/1/8 Lennart Augustsson
: Of course you don't need a monad, but you need to do the same operations as you would with a state monad to number the nodes. This is the only way in (pure) Haskell. There is no object identity in Haskell, so if you want the nodes to have identity you need to provide it.
GHC does have a library for stable names which (in the IO monad) allows you to get something akin to the address of a value in memory. But that's not the functional way of doing this.
-- Lennart
On Thu, Jan 8, 2009 at 9:28 AM, minh thu
wrote: Hi,
I'd like to process some kind of graph data structure, say something like
data DS = A [DS] | B DS DS | C.
but I want to be able to discover any sharing. Thus, in
b = B a a where a = A [C],
if I want to malloc a similar data structure, I have to handle to the node representing B two times the same pointer (the one returned after allocating A [C]).
To discover sharing, I thought it would be necessary to give unique name to node and then compare them while traversing the graph. I could give the name by hand but it would be cumbersome. But at least it would not require any monad for the bookkeeping of ungiven names. Is it possible to give those names automatically but outside any monad ?
Thanks, Thu _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- nightmare = unsafePerformIO (getWrongWife >>= sex) http://blog.ertes.de/

2009/1/8 Ertugrul Soeylemez
"minh thu"
wrote: Nothing, simply the notation. Now, with the remark of Luke, I'm wondering how bad it is to use makeStableName/hashStableName to "copy" the data structure in a similar one with explicit reference (that is, using pointer or keys in a map or whatever).
Probably you're misusing the notation. I don't see any reason, why monadic notation should be less readable. Usually it's even more readable. Luke's remark is very valid. Haskell is the wrong language for imperative programming. You don't have _any_ benefit of Haskell, if you use it like C. Try to change your mind. Monads aren't evil. They are there to make your life easier. Way easier than imperative methods.
Well, maybe it's is just my opinion, but I found the non-monadic code in the previous mail easier to write than the monadic one... I don't know against what you're making the compareason to say it's more readable. Although I agree using Haskell requires some change of thinking, statement like yours are a bit too much for me. I find Haskell a nice language even for imperative programming... Cheers, Thu
Greets, Ertugrul.
Thank you, Thu
2009/1/8 Lennart Augustsson
: Look at http://www.haskell.org/ghc/docs/latest/html/libraries/base/System-Mem-Stable....
But what's wrong with constructing the graph in a monad?
On Thu, Jan 8, 2009 at 9:53 AM, minh thu
wrote: Well, the processing of the data structure has to be done in the IO monad. What is the library you talk about ? Could it give the "stable names" (in IO) for each node of the mentioned graph (I mean, after the graph has been constructed purely) ?
Thanks, Thu
2009/1/8 Lennart Augustsson
: Of course you don't need a monad, but you need to do the same operations as you would with a state monad to number the nodes. This is the only way in (pure) Haskell. There is no object identity in Haskell, so if you want the nodes to have identity you need to provide it.
GHC does have a library for stable names which (in the IO monad) allows you to get something akin to the address of a value in memory. But that's not the functional way of doing this.
-- Lennart
On Thu, Jan 8, 2009 at 9:28 AM, minh thu
wrote: Hi,
I'd like to process some kind of graph data structure, say something like
data DS = A [DS] | B DS DS | C.
but I want to be able to discover any sharing. Thus, in
b = B a a where a = A [C],
if I want to malloc a similar data structure, I have to handle to the node representing B two times the same pointer (the one returned after allocating A [C]).
To discover sharing, I thought it would be necessary to give unique name to node and then compare them while traversing the graph. I could give the name by hand but it would be cumbersome. But at least it would not require any monad for the bookkeeping of ungiven names. Is it possible to give those names automatically but outside any monad ?
Thanks, Thu _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- nightmare = unsafePerformIO (getWrongWife >>= sex) http://blog.ertes.de/
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Interestingly, I failed to detect sharing with StableName.
But using the graph node as a key turned to work...
If you're interested in the experiment, see attached code.
Cheers,
Thu
2009/1/8 minh thu
2009/1/8 Ertugrul Soeylemez
: "minh thu"
wrote: Nothing, simply the notation. Now, with the remark of Luke, I'm wondering how bad it is to use makeStableName/hashStableName to "copy" the data structure in a similar one with explicit reference (that is, using pointer or keys in a map or whatever).
Probably you're misusing the notation. I don't see any reason, why monadic notation should be less readable. Usually it's even more readable. Luke's remark is very valid. Haskell is the wrong language for imperative programming. You don't have _any_ benefit of Haskell, if you use it like C. Try to change your mind. Monads aren't evil. They are there to make your life easier. Way easier than imperative methods.
Well, maybe it's is just my opinion, but I found the non-monadic code in the previous mail easier to write than the monadic one... I don't know against what you're making the compareason to say it's more readable.
Although I agree using Haskell requires some change of thinking, statement like yours are a bit too much for me. I find Haskell a nice language even for imperative programming...
Cheers, Thu
Greets, Ertugrul.
Thank you, Thu
2009/1/8 Lennart Augustsson
: Look at http://www.haskell.org/ghc/docs/latest/html/libraries/base/System-Mem-Stable....
But what's wrong with constructing the graph in a monad?
On Thu, Jan 8, 2009 at 9:53 AM, minh thu
wrote: Well, the processing of the data structure has to be done in the IO monad. What is the library you talk about ? Could it give the "stable names" (in IO) for each node of the mentioned graph (I mean, after the graph has been constructed purely) ?
Thanks, Thu
2009/1/8 Lennart Augustsson
: Of course you don't need a monad, but you need to do the same operations as you would with a state monad to number the nodes. This is the only way in (pure) Haskell. There is no object identity in Haskell, so if you want the nodes to have identity you need to provide it.
GHC does have a library for stable names which (in the IO monad) allows you to get something akin to the address of a value in memory. But that's not the functional way of doing this.
-- Lennart
On Thu, Jan 8, 2009 at 9:28 AM, minh thu
wrote: > Hi, > > I'd like to process some kind of graph data structure, > say something like > > data DS = A [DS] | B DS DS | C. > > but I want to be able to discover any sharing. > Thus, in > > b = B a a where a = A [C], > > if I want to malloc a similar data structure, > I have to handle to the node representing B > two times the same pointer (the one returned > after allocating A [C]). > > To discover sharing, I thought it would be > necessary to give unique name to node and > then compare them while traversing the graph. > I could give the name by hand but it would be > cumbersome. But at least it would not require > any monad for the bookkeeping of ungiven > names. Is it possible to give those names > automatically but outside any monad ? > > Thanks, > Thu > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://blog.ertes.de/
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Using StableName is really a last resort when you need to do low level
strange things.
I would not use it when there's another way. Which there is.
-- Lennart
2009/1/8 minh thu
Interestingly, I failed to detect sharing with StableName. But using the graph node as a key turned to work... If you're interested in the experiment, see attached code.
Cheers, Thu
2009/1/8 minh thu
: 2009/1/8 Ertugrul Soeylemez
: "minh thu"
wrote: Nothing, simply the notation. Now, with the remark of Luke, I'm wondering how bad it is to use makeStableName/hashStableName to "copy" the data structure in a similar one with explicit reference (that is, using pointer or keys in a map or whatever).
Probably you're misusing the notation. I don't see any reason, why monadic notation should be less readable. Usually it's even more readable. Luke's remark is very valid. Haskell is the wrong language for imperative programming. You don't have _any_ benefit of Haskell, if you use it like C. Try to change your mind. Monads aren't evil. They are there to make your life easier. Way easier than imperative methods.
Well, maybe it's is just my opinion, but I found the non-monadic code in the previous mail easier to write than the monadic one... I don't know against what you're making the compareason to say it's more readable.
Although I agree using Haskell requires some change of thinking, statement like yours are a bit too much for me. I find Haskell a nice language even for imperative programming...
Cheers, Thu
Greets, Ertugrul.
Thank you, Thu
2009/1/8 Lennart Augustsson
: Look at http://www.haskell.org/ghc/docs/latest/html/libraries/base/System-Mem-Stable....
But what's wrong with constructing the graph in a monad?
On Thu, Jan 8, 2009 at 9:53 AM, minh thu
wrote: Well, the processing of the data structure has to be done in the IO monad. What is the library you talk about ? Could it give the "stable names" (in IO) for each node of the mentioned graph (I mean, after the graph has been constructed purely) ?
Thanks, Thu
2009/1/8 Lennart Augustsson
: > Of course you don't need a monad, but you need to do the same > operations as you would with a state monad to number the nodes. This > is the only way in (pure) Haskell. There is no object identity in > Haskell, so if you want the nodes to have identity you need to provide > it. > > GHC does have a library for stable names which (in the IO monad) > allows you to get something akin to the address of a value in memory. > But that's not the functional way of doing this. > > -- Lennart > > On Thu, Jan 8, 2009 at 9:28 AM, minh thu wrote: >> Hi, >> >> I'd like to process some kind of graph data structure, >> say something like >> >> data DS = A [DS] | B DS DS | C. >> >> but I want to be able to discover any sharing. >> Thus, in >> >> b = B a a where a = A [C], >> >> if I want to malloc a similar data structure, >> I have to handle to the node representing B >> two times the same pointer (the one returned >> after allocating A [C]). >> >> To discover sharing, I thought it would be >> necessary to give unique name to node and >> then compare them while traversing the graph. >> I could give the name by hand but it would be >> cumbersome. But at least it would not require >> any monad for the bookkeeping of ungiven >> names. Is it possible to give those names >> automatically but outside any monad ? >> >> Thanks, >> Thu >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe@haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://blog.ertes.de/
_______________________________________________ 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

I seem to recall reading somewhere that an object's StableName can change when it becomes evaluated; so it's possible you aren't detecting sharing because of this. You might try this instead:
mkStableName' a = mkStableName $! a
This forces the object to become evaluated before calling mkStableName.
Of course I haven't tested this, it's just a shot in the dark.
-- ryan
2009/1/8 minh thu
Interestingly, I failed to detect sharing with StableName. But using the graph node as a key turned to work... If you're interested in the experiment, see attached code.
Cheers, Thu
2009/1/8 minh thu
: 2009/1/8 Ertugrul Soeylemez
: "minh thu"
wrote: Nothing, simply the notation. Now, with the remark of Luke, I'm wondering how bad it is to use makeStableName/hashStableName to "copy" the data structure in a similar one with explicit reference (that is, using pointer or keys in a map or whatever).
Probably you're misusing the notation. I don't see any reason, why monadic notation should be less readable. Usually it's even more readable. Luke's remark is very valid. Haskell is the wrong language for imperative programming. You don't have _any_ benefit of Haskell, if you use it like C. Try to change your mind. Monads aren't evil. They are there to make your life easier. Way easier than imperative methods.
Well, maybe it's is just my opinion, but I found the non-monadic code in the previous mail easier to write than the monadic one... I don't know against what you're making the compareason to say it's more readable.
Although I agree using Haskell requires some change of thinking, statement like yours are a bit too much for me. I find Haskell a nice language even for imperative programming...
Cheers, Thu
Greets, Ertugrul.
Thank you, Thu
2009/1/8 Lennart Augustsson
: Look at http://www.haskell.org/ghc/docs/latest/html/libraries/base/System-Mem-Stable....
But what's wrong with constructing the graph in a monad?
On Thu, Jan 8, 2009 at 9:53 AM, minh thu
wrote: Well, the processing of the data structure has to be done in the IO monad. What is the library you talk about ? Could it give the "stable names" (in IO) for each node of the mentioned graph (I mean, after the graph has been constructed purely) ?
Thanks, Thu
2009/1/8 Lennart Augustsson
: > Of course you don't need a monad, but you need to do the same > operations as you would with a state monad to number the nodes. This > is the only way in (pure) Haskell. There is no object identity in > Haskell, so if you want the nodes to have identity you need to provide > it. > > GHC does have a library for stable names which (in the IO monad) > allows you to get something akin to the address of a value in memory. > But that's not the functional way of doing this. > > -- Lennart > > On Thu, Jan 8, 2009 at 9:28 AM, minh thu wrote: >> Hi, >> >> I'd like to process some kind of graph data structure, >> say something like >> >> data DS = A [DS] | B DS DS | C. >> >> but I want to be able to discover any sharing. >> Thus, in >> >> b = B a a where a = A [C], >> >> if I want to malloc a similar data structure, >> I have to handle to the node representing B >> two times the same pointer (the one returned >> after allocating A [C]). >> >> To discover sharing, I thought it would be >> necessary to give unique name to node and >> then compare them while traversing the graph. >> I could give the name by hand but it would be >> cumbersome. But at least it would not require >> any monad for the bookkeeping of ungiven >> names. Is it possible to give those names >> automatically but outside any monad ? >> >> Thanks, >> Thu >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe@haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://blog.ertes.de/
_______________________________________________ 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

On Thu, 08 Jan 2009 21:28:27 minh thu wrote:
Hi,
I'd like to process some kind of graph data structure, say something like
data DS = A [DS] | B DS DS | C.
Graphs in funtional languages aren't usually represented in this sort of manner. Trees are fine to represent like that as they're acyclic and have exactly one parent for each node but for graphs it's much more difficult. Say that you have a graph with directed connections like this: 0 -> 1 1 -> 2 2 -> 3 1 -> 3 3 -> 4 Now you want to alter node 4. Node 3 has to be updated to point to the new version of 4, node 1 has to be changed to point to the new version of 3, node 2 has to be changed to point to the new version of node 3, then node 1 has to be changed again to point to the new version of 2, then finally 0 can be changed to point to the new version of 1 and returned. There is no simple way using this representation to handle that double-update to node 1, or to handle disconnected or cyclic graphs. Updates are extremely difficult since Haskell data structures are not mutable and have no concept of identity. The approach of treating nodes as structures with pointers to each other cannot be cleanly and efficiently implemented in an immutable fashion. It only really makes sense in a stateful, imperative context. An approach that suits functional languages better is to store a flat structure listing the edges leaving each node. This, I believe, is the approach taken by Haskell's main graph library, FGL (http://hackage.haskell.org/cgi-bin/hackage-scripts/package/fgl). You would now have something like: data MyNode nv = MyNode {nodeId::Int, nodeValue::nv} data MyEdge ev = MyEdge {edgeDestination::Int, edgeValue::ev} data MyGraph nv ev = MyGraph { maxNode :: Int, nodes :: (Map Int nv), edges :: (Map Int [MyEdge ev])} emptyGraph :: MyGraph nv ev emptyGraph = MyGraph 0 (Data.Map.empty) (Data.Map.empty) getNode :: MyGraph nv ev -> Int -> Maybe (MyNode nv) getNode g id = ((nodes g) `lookup` id) >>= (\v -> MyNode id v) getEdgesLeaving :: MyGraph nv ev -> Int -> [MyEdge ev] getEdgesLeaving g id = fromMaybe [] ((edges g) `lookup` id) addNode :: nv -> MyGraph nv ev -> (Int, MyGraph nv ev) addNode val g = (maxNode newGraph, newGraph) where newNodeId = (maxNode g) + 1 newGraph = MyGraph newNodeId (insert newNodeId val (nodes g)) (edges g) ... and so on. (This is all totally untested - use at your own peril.) Each node in the graph has a unique identifying number, issued in sequence using maxNode as a counter. This makes identifying cycles easy. The nodes map contains the value for each node based on its id. The edges map contains a list of links from each node to others in the graph. Finding links entering a node is quite expensive - if you need to do this often then maintaining a second list of edges entering each node would speed it up. Each node and each edge can have a custom data structure attached. New nodes and edges can be added without having to modify references elsewhere, nodes have a distinct identity given by the associated Int and the graph is immutable - operations on it produce modified copies. Cheers, Tim

2009/1/9 Timothy Goddard
On Thu, 08 Jan 2009 21:28:27 minh thu wrote:
Hi,
I'd like to process some kind of graph data structure, say something like
data DS = A [DS] | B DS DS | C.
Graphs in funtional languages aren't usually represented in this sort of manner. Trees are fine to represent like that as they're acyclic and have exactly one parent for each node but for graphs it's much more difficult. Say that you have a graph with directed connections like this:
0 -> 1 1 -> 2 2 -> 3 1 -> 3 3 -> 4
Now you want to alter node 4. Node 3 has to be updated to point to the new version of 4, node 1 has to be changed to point to the new version of 3, node 2 has to be changed to point to the new version of node 3, then node 1 has to be changed again to point to the new version of 2, then finally 0 can be changed to point to the new version of 1 and returned.
There is no simple way using this representation to handle that double-update to node 1, or to handle disconnected or cyclic graphs. Updates are extremely difficult since Haskell data structures are not mutable and have no concept of identity. The approach of treating nodes as structures with pointers to each other cannot be cleanly and efficiently implemented in an immutable fashion. It only really makes sense in a stateful, imperative context.
An approach that suits functional languages better is to store a flat structure listing the edges leaving each node. This, I believe, is the approach taken by Haskell's main graph library, FGL (http://hackage.haskell.org/cgi-bin/hackage-scripts/package/fgl). You would now have something like:
data MyNode nv = MyNode {nodeId::Int, nodeValue::nv}
data MyEdge ev = MyEdge {edgeDestination::Int, edgeValue::ev}
data MyGraph nv ev = MyGraph { maxNode :: Int, nodes :: (Map Int nv), edges :: (Map Int [MyEdge ev])}
emptyGraph :: MyGraph nv ev emptyGraph = MyGraph 0 (Data.Map.empty) (Data.Map.empty)
getNode :: MyGraph nv ev -> Int -> Maybe (MyNode nv) getNode g id = ((nodes g) `lookup` id) >>= (\v -> MyNode id v)
getEdgesLeaving :: MyGraph nv ev -> Int -> [MyEdge ev] getEdgesLeaving g id = fromMaybe [] ((edges g) `lookup` id)
addNode :: nv -> MyGraph nv ev -> (Int, MyGraph nv ev) addNode val g = (maxNode newGraph, newGraph) where newNodeId = (maxNode g) + 1 newGraph = MyGraph newNodeId (insert newNodeId val (nodes g)) (edges g)
... and so on. (This is all totally untested - use at your own peril.)
Each node in the graph has a unique identifying number, issued in sequence using maxNode as a counter. This makes identifying cycles easy. The nodes map contains the value for each node based on its id. The edges map contains a list of links from each node to others in the graph. Finding links entering a node is quite expensive - if you need to do this often then maintaining a second list of edges entering each node would speed it up.
Each node and each edge can have a custom data structure attached. New nodes and edges can be added without having to modify references elsewhere, nodes have a distinct identity given by the associated Int and the graph is immutable - operations on it produce modified copies.
Indeed, the processing I'm refering to is to copy something like my representation into something like yours. Thanks ! Thu
participants (6)
-
Ertugrul Soeylemez
-
Lennart Augustsson
-
Luke Palmer
-
minh thu
-
Ryan Ingram
-
Timothy Goddard