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 <not...@gmail.com>: > 2009/1/8 Ertugrul Soeylemez <e...@ertes.de>: >> "minh thu" <not...@gmail.com> 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 <lenn...@augustsson.net>: >>> > Look at >>> > http://www.haskell.org/ghc/docs/latest/html/libraries/base/System-Mem-StableName.html. >>> > >>> > But what's wrong with constructing the graph in a monad? >>> > >>> > On Thu, Jan 8, 2009 at 9:53 AM, minh thu <not...@gmail.com> 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 <lenn...@augustsson.net>: >>> >>> 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 <not...@gmail.com> 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 >> >
-- 2009.01.08 -- 2009.01.08 -- -- Given a graph following this type -- -- data DS = A [DS] String | B String, -- -- the problem is to detect sharing so -- that shared nodes are used only once -- (for instance to output the name of -- the node or to malloc it, ...). -- -- Here, the goal is to clone the graph -- into the following type -- -- type NDS = [(Int,N)] -- data N = NA [Int] String | B String -- -- that is, each child of A is an Int in -- a association list (N means 'named'). -- -- I see two possibility based on a Map -- mapping already processed node to their -- name : -- - Map DS Int -- - Map Int Int -- -- The key in the first possibility is the -- processed node itself. This mean it should be -- an instance of Ord and the graph should be -- acyclic. -- -- The key in the second possibility is given -- as the hash of the StableName of the node. -- This need to be done in the IO monad. -- This FAILS to detect the sharing. -- -- Another possibility, which doesn't respect -- exactly the problem as given above, is to -- produce the graph directly in a monad that -- holds the book-keeping of the name. -- (Not implemented here.) -- module Graph where import Data.Map import System.Mem.StableName data DS = A [DS] String | B String deriving (Eq, Ord, Show) -- Ord for Data.Map.insert type NDS = [(Int,N)] data N = NA [Int] String | NB String deriving Show ex1 = A [b,b] "arthur" where b = B "belzebuth" -- This one will not terminate if show'd or namePure'd. ex2 = let a = A [a] "arthur" in a namePure :: DS -> NDS namePure node = nds where (_,_,nds,_) = namePure1 node empty [1..] [] -- node : the node to name and add to the graph (i.e. the NDS). -- dict : the map to remember which node has already been added -- (it is a bit redundant with the NDS). -- names : available names to name the nodes. -- nds : the graph in construction. namePure1 node dict names nds = if node `member` dict then (dict,names,nds,dict ! node) else case node of A children info -> let (dict',names',nds',children') = namePureMany children dict names nds [] in (insert node (head names') dict', tail names', (head names',NA children' info):nds', head names) B info -> (insert node (head names) dict, tail names, (head names,NB info):nds, head names) -- nodes : the nodes to name and add to the graph. -- dict : see above. -- names : see above. -- nds : see above. -- rnames : the names used in the graph, they are accumulated -- while traversing the DS, then returned. namePureMany [] dict names nds rnames = (dict,names,nds,rnames) namePureMany nodes dict names nds rnames = let (dict',names',nds',name) = namePure1 (head nodes) dict names nds in namePureMany (tail nodes) dict' names' nds' (name:rnames) nameIO :: DS -> IO NDS nameIO node = do (_,_,nds,_) <- nameIO1 node empty [1..] [] return nds nameIO1 node dict names nds = do sname <- makeStableName node let key = hashStableName sname if key `member` dict then return (dict,names,nds,dict ! key) else case node of A children info -> do (dict',names',nds',children') <- nameIOMany children dict names nds [] return (insert key (head names') dict', tail names', (head names',NA children' info):nds', head names) B info -> do return (insert key (head names) dict, tail names, (head names,NB info):nds, head names) nameIOMany [] dict names nds rnames = return (dict,names,nds,rnames) nameIOMany nodes dict names nds rnames = do (dict',names',nds',name) <- nameIO1 (head nodes) dict names nds nameIOMany (tail nodes) dict' names' nds' (name:rnames)
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe