Re: [Haskell-cafe] Generating random graph

2011-04-10 Thread Steffen Schuldenzucker
Hello. I don't know if that is the reason for the strange behaviour, but On 04/11/2011 03:03 AM, Mitar wrote: I have made this function to generate a random graph for Data.Graph.Inductive library: generateGraph :: Int -> IO (Gr String Double) generateGraph graphSize = do when (graphSize<

Re: [Haskell-cafe] [Haskell-beginners] Calling a foreign function: superlinear comlexity

2011-04-10 Thread Antoine Latter
On Sun, Apr 10, 2011 at 6:26 PM, Serguei Son wrote: > I call GSL's gsl_ran_ugaussian function in the following way (using > bindings-gsl): > > module Main where > > import Bindings.Gsl.RandomNumberGeneration > import Bindings.Gsl.RandomNumberDistributions > import Foreign > import Control.Monad >

[Haskell-cafe] Generating random graph

2011-04-10 Thread Mitar
Hi! I have made this function to generate a random graph for Data.Graph.Inductive library: generateGraph :: Int -> IO (Gr String Double) generateGraph graphSize = do when (graphSize < 1) $ throwIO $ AssertionFailed $ "Graph size out of bounds " ++ show graphSize let ns = map (\n -> (n, show n

Re: [Haskell-cafe] Parsing HTML tables with HXT

2011-04-10 Thread Albert Y. C. Lai
On 11-04-08 06:29 AM, Dmitry Simonchik wrote: Can someone please help me with getting the value of the table cell with HXT in the following html: x y a b I need the value of the second cell in a row that has first cell with some predefined value (in the example above it can be x or a) I n

Re: [Haskell-cafe] Current heap size and other runtime statistics -- API for accessing in GHC?

2011-04-10 Thread Don Stewart
I'd like a proper FFI binding for getting at Stats.c dynamically. So I can write programs that determine their own stats about the GC and so on. On Sun, Apr 10, 2011 at 2:30 PM, Ryan Newton wrote: > Hi cafe, > The rtsopts (-s etc) can provide some nice debugging information regarding > memory man

[Haskell-cafe] ghc6: Re: Update: ... compiling ghc6

2011-04-10 Thread Svante Signell
Addressing both Haskell and Hurd people here. Any hints by anyone? On Wed, 2011-04-06 at 09:30 +0200, Svante Signell wrote: ... > #5 0x011d3ce0 in __libc_read (fd=DWARF-2 expression error: DW_OP_reg > operations must be used either alone or in conjuction with DW_OP_piece > or DW_OP_bit_piece. > )

Re: [Haskell-cafe] Tuple

2011-04-10 Thread Henk-Jan van Tuyl
On Sun, 10 Apr 2011 18:49:59 +0200, Anwar Bari wrote: HI Cafe I have to make a function to check that I have one occurrence of the last element (z) of the same list [a,b] in the tuple [([a,b],z)] For example [([1,2],3),([1,1],5),([1,3],6)...] this is true because there is one s

Re: [Haskell-cafe] Current heap size and other runtime statistics -- API for accessing in GHC?

2011-04-10 Thread Edward Z. Yang
Simon Marlow and I had this conversation not too long ago, and the answer is no. However, this is definitely something that would be useful for a lot of people (GHC developers included!) Cheers, Edward Excerpts from Ryan Newton's message of Sun Apr 10 17:30:50 -0400 2011: > Hi cafe, > > The rtso

[Haskell-cafe] Current heap size and other runtime statistics -- API for accessing in GHC?

2011-04-10 Thread Ryan Newton
Hi cafe, The rtsopts (-s etc) can provide some nice debugging information regarding memory management. And System.Mem.performGC can initiate garbage collection. But are there APIs for querying the current state of the heap? I've googled and come up dry. In this case I'm running benchmarks and

Re: [Haskell-cafe] haskell-src-meta installation failed

2011-04-10 Thread Rob Nikander
I don't know what would cause this, but it's saying that a file in your installed haskell-src-exts package is corrupt, so maybe try reinstalling that package. Rob 2011/4/10 Qiuchi Jian : > Hi guys, > > I tried to install haskell-src-meta and got the error below.  I checked all > dependencies whic

Re: [Haskell-cafe] Tuple

2011-04-10 Thread Rob Nikander
On Sun, Apr 10, 2011 at 12:49 PM, Anwar Bari wrote: > HI Cafe >     I have to make a function to check that I have one occurrence of the last > element (z) of the same list [a,b] in the tuple > >  [([a,b],z)] > For example > [([1,2],3),([1,1],5),([1,3],6)...]  this is true because there is one

[Haskell-cafe] haskell-src-meta installation failed

2011-04-10 Thread Qiuchi Jian
Hi guys, I tried to install haskell-src-meta and got the error below. I checked all dependencies which are listed on the hackage page, they are all installed with the right version. Can anyone tell me what is the problem? Thanks a lot. jqc@ubuntu:~$ cabal install haskell-src-meta Resolving

[Haskell-cafe] CFP -- Haskell Symposium 2011

2011-04-10 Thread Haskell Symposium
                     "Haskell 2011"              ACM SIGPLAN Haskell Symposium 2011                       Tokyo, Japan                   22nd September, 2011                      CALL FOR PAPERS       http://www.haskell.org/haskell-symposium/2011/ The ACM SIGPLAN Haskell Symposium 2011 will be

[Haskell-cafe] Tuple

2011-04-10 Thread Anwar Bari
HI Cafe I have to make a function to check that I have one occurrence of the last element (z) of the same list [a,b] in the tuple [([a,b],z)] For example [([1,2],3),([1,1],5),([1,3],6)...] this is true because there is one single z for each single list. while this one is false [

[Haskell-cafe] ImProve Tutorial

2011-04-10 Thread Tom Hawkins
ImProve is a Haskell eDSL for embedded control systems -- we use it for automotive and off-highway powertrain control. I've started writing a tutorial for ImProve. So far it has a basic tour of the language and a handful of examples. Comments and suggestions are welcome. In other recent news, I

Re: [Haskell-cafe] Deciding equality of functions.

2011-04-10 Thread Claus Reinke
It is a common situation when one has two implementations of the same function, one being straightforward but slow, and the other being fast but complex. It would be nice to be able to check if these two versions are equal to catch bugs in the more complex implementation. This common situatio

Re: [Haskell-cafe] Deciding equality of functions.

2011-04-10 Thread Patrick Browne
On 10/04/2011 04:22, wren ng thornton wrote: > The thing is that a lot of the common optimizations (e.g., TCO) > completely wreck the inductive structure of the function which, in turn, > makes it difficult to say interesting things about them.[1] Could you point me to some Haskell references conc