Re: [Haskell-cafe] Generating random graph

2011-04-13 Thread Bertram Felgenhauer
Hi Mitar,

> 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)) [1..graphSize]
>   es <- fmap concat $ forM [1..graphSize] $ \node -> do
> nedges <- randomRIO (0, graphSize)
> others <- fmap (filter (node /=) . nub) $ forM [1..nedges] $ \_ ->
> randomRIO (1, graphSize)
> gen <- getStdGen

Others have already remarked that you could implement this as a pure
function. However, the mistake is the use of  getStdGen  here, which
is (almost?) never what you need: two consecutive valls of getStdGen
will return the same generator. You should call newStdGen  instead.

Best regards,

Bertram

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Generating random graph

2011-04-11 Thread Mitar
Hi!

On Mon, Apr 11, 2011 at 7:36 AM, Steffen Schuldenzucker
 wrote:
> So when using randomRs, the state of the global random number generator is
> not updated, but it is used again in the next iteration of the toplevel forM
> [1..graphSize] loop.

I thought it would be interleaved.

Thanks.


Mitar

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Generating random graph

2011-04-11 Thread Henning Thielemann


On Mon, 11 Apr 2011, Mitar wrote:


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)) [1..graphSize]
 es <- fmap concat $ forM [1..graphSize] $ \node -> do
   nedges <- randomRIO (0, graphSize)
   others <- fmap (filter (node /=) . nub) $ forM [1..nedges] $ \_ -> randomRIO 
(1, graphSize)
   gen <- getStdGen
   let weights = randomRs (1, 10) gen
   return $ zip3 (repeat node) others weights
 return $ mkGraph ns es


Just a note on style: This function can perfectly be written without IO.

http://www.haskell.org/haskellwiki/Avoiding_IO#State_monad

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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<  1) $ throwIO $ AssertionFailed $ "Graph size out
of bounds " ++ show graphSize
   let ns = map (\n ->  (n, show n)) [1..graphSize]
   es<- fmap concat $ forM [1..graphSize] $ \node ->  do
 nedges<- randomRIO (0, graphSize)
 others<- fmap (filter (node /=) . nub) $ forM [1..nedges] $ \_ ->
randomRIO (1, graphSize)
 gen<- getStdGen
 let weights = randomRs (1, 10) gen


^ this use of randomRs looks wrong.


 return $ zip3 (repeat node) others weights
   return $ mkGraph ns es


http://hackage.haskell.org/packages/archive/random/latest/doc/html/System-Random.html

tells me:

  randomRs :: RandomGen g => (a, a) -> g -> [a]

  Plural variant of randomR, producing an infinite list of random
  values instead of returning a new generator.

So when using randomRs, the state of the global random number generator 
is not updated, but it is used again in the next iteration of the 
toplevel forM [1..graphSize] loop. Try:


> weights <- replicateM (length others) $ randomRIO (1, 10)

instead.

-- Steffen



But I noticed that graph has sometimes same weights on different
edges. This is very unlikely to happen so probably I have some error
using random generators. Could somebody tell me where?


Mitar

___
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


[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)) [1..graphSize]
  es <- fmap concat $ forM [1..graphSize] $ \node -> do
nedges <- randomRIO (0, graphSize)
others <- fmap (filter (node /=) . nub) $ forM [1..nedges] $ \_ ->
randomRIO (1, graphSize)
gen <- getStdGen
let weights = randomRs (1, 10) gen
return $ zip3 (repeat node) others weights
  return $ mkGraph ns es

But I noticed that graph has sometimes same weights on different
edges. This is very unlikely to happen so probably I have some error
using random generators. Could somebody tell me where?


Mitar

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe