Re: [Haskell-cafe] (...) Random generators

2011-12-30 Thread Jerzy Karczmarczuk

Bardur Arantsson:

Random streams are not referentially transparent, though, AFAICT...?

Either way this thread has gone on long enough, let's not prolong it 
needlessly with this side discussion. 


Sure.
But the discussion on randomness is /per se/ interesting, especially in 
a functional setting.


Anyway, nobody can convince Steve Horne. Perhaps as an unintentional  
side-effect...


But random streams, or rather pseudo-random streals (infinite lazy 
lists, as the example I gave, the `iterate` of `next`) are as 
referentially transparent as any Haskell data. Really.


What I find really amazing, since I converted my soul from physics to 
computer since (many, many years ago...) is that most comments about 
random number generators come from people who don't need them, don't use 
them, and usually don't care about them...
I taught random numbers, and I did some Monte-Carlo calculation in High 
Energy Physics, when many people here were not born. I *NEVER* used 
true random numbers, even to initialize a generator, since in the 
simulation business it is essential that you can repeat the sequence on 
some other platform, with some other parameters, etc.


Of course, they are useful (don't need to convince an ancien 
physicist... And I lied. I used them, e.g. when I programmed some games 
for my children.) --


but why should we forget about them? The usual approach(*) is to 
gather entropy from a truly(**) random source

and use that to seed (and perhaps periodically re-seed) a PRNG.
So, sorry, I didn't mean really forget, only to change the subject 
which was irrelevant for the purity (but somehow has shown once more 
that Steve Horne had strange ideas about random generators).


The generator of L'Ecuyer, or Mersenne Twister, or anything, don't care 
about the entropy. For a typical user, the only interesting thing is 
that the random streams pass the usual statistical tests : moments, 
correlation, spectrum... Otherwise it is as deterministic as 1 2 3 4. 
(For a typical user from my mafia. The mafia of cryptographists has 
different criteria ; from time to time we shoot ourselves in the 
coffee-machine corner of our dept.)


Thank you for the discussion. You are right, I brake.

Jerzy


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


Re: [Haskell-cafe] (...) Random generators

2011-12-30 Thread Bardur Arantsson

On 12/30/2011 04:38 PM, Jerzy Karczmarczuk wrote:
 Bardur Arantsson:
 Random streams are not referentially transparent, though, AFAICT...?

 Either way this thread has gone on long enough, let's not prolong it
 needlessly with this side discussion.

 Sure.
 But the discussion on randomness is /per se/ interesting, especially in
 a functional setting.

 Anyway, nobody can convince Steve Horne. Perhaps as an unintentional
 side-effect...

 But random streams, or rather pseudo-random streals (infinite lazy
 lists, as the example I gave, the `iterate` of `next`) are as
 referentially transparent as any Haskell data. Really.


Of course -- if you just have a starting seed and the rest of the 
sequence is known from there. I was thinking of e.g. those periodic 
re-initialization ways of doing RNG.


 I *NEVER* used
 true random numbers, even to initialize a generator, since in the
 simulation business it is essential that you can repeat the sequence on
 some other platform, with some other parameters, etc.


I've heard this a lot from physicists -- of course if you run a 
simulation reproducibility can be extremely important (e.g. for 
double-checking computations across different machines). However, if 
you're doing crypto it may not be so desirable :).


Anyway, I'm out of this thread too :).

Cheers,


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


Re: [Haskell-cafe] Random thoughts about typeclasses

2011-05-18 Thread Dominique Devriese
Robert,

2011/5/16 Robert Clausecker fuz...@gmail.com:
 I found out, that GHC implements typeclasses as an extra argument, a
 record that stores all functions of the typeclass. So I was wondering,
 is there a way (apart from using newtype) to pass a custom record as the
 typeclass record, to modify the behavior of the typeclass? I thought
 about something like this:

You may be interested in Agda's upcoming instance arguments
(inspired upon Scala implicits and Agda's implicit arguments). These
will be available in Agda 2.2.12 (you may find references to an older
name non-canonical implicit arguments). The new type of function
arguments are automatically inferred from call-site scope unless they
are explicitly provided. Type classes are directly (not just under the
hood) modelled as records, and you can do what you suggest. You can
also define local instances, and there are other advantages. We have
chosen a more limited-power instance search though. More discussion
online.

  
http://wiki.portal.chalmers.se/agda/pmwiki.php?n=ReferenceManual.InstanceArguments
  http://people.cs.kuleuven.be/~dominique.devriese/agda-instance-arguments/

I believe a similar Haskell extension (perhaps with a less principled
instance search) would improve and simplify Haskell's type class
system.

By the way, Kahl and Scheffczyk proposed extending Haskell with named
instances in 2001 which allowed something like this to a limited
extent. Look for Named instances for Haskell Type Classes in Google
Scholar.

Dominique

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


[Haskell-cafe] Random thoughts about typeclasses

2011-05-16 Thread Robert Clausecker
Hello!

I found out, that GHC implements typeclasses as an extra argument, a
record that stores all functions of the typeclass. So I was wondering,
is there a way (apart from using newtype) to pass a custom record as the
typeclass record, to modify the behavior of the typeclass? I thought
about something like this:

f :: Show a = [a] - String
f = (= show)

-- So, f becomes something like this?
__f :: ClassShow a - [a] - String
__f (ClassShow __show) x = x = __show

-- And if I call the function, it looks somewhat like this:
g :: [Int] - String
g = f

__g = __f instanceShowInt

-- But is it possible to do something like this?
g2 = __f (ClassShow (return . fromEnum))

Tis is just a random thought, some compilers like JHC implement them by
another way. But would this theoretically be possible?

Yours, FUZxxl


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


Re: [Haskell-cafe] Random thoughts about typeclasses

2011-05-16 Thread Ertugrul Soeylemez
Robert Clausecker fuz...@gmail.com wrote:

 I found out, that GHC implements typeclasses as an extra argument, a
 record that stores all functions of the typeclass. So I was wondering,
 is there a way (apart from using newtype) to pass a custom record as
 the typeclass record, to modify the behavior of the typeclass? I
 thought about something like this:

 f :: Show a = [a] - String
 f = (= show)

 -- So, f becomes something like this?
 __f :: ClassShow a - [a] - String
 __f (ClassShow __show) x = x = __show

 -- And if I call the function, it looks somewhat like this:
 g :: [Int] - String
 g = f

 __g = __f instanceShowInt

 -- But is it possible to do something like this?
 g2 = __f (ClassShow (return . fromEnum))

 Tis is just a random thought, some compilers like JHC implement them
 by another way. But would this theoretically be possible?

If I understand you right, you would like to decide about the instance
at run-time instead of at compile-time.  This is actually possible in
practice.  A suitable search term is implicit configurations, in
particular reification.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/



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


Re: [Haskell-cafe] Random thoughts about typeclasses

2011-05-16 Thread Casey McCann
On Mon, May 16, 2011 at 8:10 AM, Robert Clausecker fuz...@gmail.com wrote:
 I found out, that GHC implements typeclasses as an extra argument, a
 record that stores all functions of the typeclass. So I was wondering,
 is there a way (apart from using newtype) to pass a custom record as the
 typeclass record, to modify the behavior of the typeclass? I thought
 about something like this:

Would GHC's implicit parameter extension possibly suit your purposes
here? Your example would translate as:

{-# LANGUAGE ImplicitParams #-}

type ShowClass a = a - String

f :: (?showC :: ShowClass a) = [a] - String
f x = x = ?showC

g :: [Int] - String
g = let ?showC = show in f

g2 :: [Int] - String
g2 = let ?showC = (return . toEnum) in f

...where:

 g [72, 97, 115, 107, 101, 108, 108]
7297115107101108108
 g2 [72, 97, 115, 107, 101, 108, 108]
Haskell

Clearly this doesn't allow you retrofit such functionality onto
existing code using existing type classes, but I'd be wary of doing
that anyway--type class instances are not something that code will
expect to have changing out from under it. Otherwise, this seems to be
exactly what the implicit parameters extension is designed for,
judging from the way the GHC user's guide describes it.

- C.

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


Re: [Haskell-cafe] random-fu confusion

2010-09-07 Thread James Andrew Cook
A PureMT generator is immutable, so must be threaded through the monad in which 
you are sampling.  There are RandomSource instances provided for a few special 
cases, including IORef PureMT in the IO monad.  For example:

main = do
mt - newPureMT
src - newIORef mt
flips - runRVar (replicateM 20 flipCoin) src
print flips

Alternatively, the functions in the module you mentioned can be used to define 
additional instances, such as:

instance MonadRandom (State PureMT) where
supportedPrims _ _ = True
getSupportedRandomPrim = getRandomPrimFromPureMTState

And RandomSource instances look almost the same.  See the 
Data.Random.Source.PureMT source for examples.  (I thought I had included this 
particular instance in the distribution but I apparently missed it.  The next 
release will probably include this as well as corresponding instances for the 
'transformers' package, possibly separated out into 'random-fu-mtl' and 
'random-fu-transformers' packages).

The StdRandom type is a convenient RandomSource designating this instance 
in the State PureMT monad.  Personally, I prefer to use the sample function 
for this purpose, as well as the sampleFrom function in place of 
runRVar/runRVarT.  GHCi does not display the sample functions' types properly 
- they are defined for RVarT as well as for all Distribution instances.

Sorry it took so long responding.

-- James

On Sep 2, 2010, at 10:01 AM, Alex Rozenshteyn wrote:

 I seem to be having confusion at the runRVar level of random-fu.
 
 I can't figure out how to use the Data.Random.Source.PureMT module to get a 
 meaningful random source (I can't get my code to type-check).
 
 I wrote a [trivial] flipCoin function
  flipCoin = uniform False True
 and am trying to fill in the final place of runRVar
  :t runRVar (replicateM 20 flipCoin)
 runRVar (replicateM 20 flipCoin)
   :: (RandomSource m s) = s - m [Bool]
 
 
 -- 
   Alex R
 
 ___
 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


Re: [Haskell-cafe] random-fu confusion

2010-09-07 Thread Alex Rozenshteyn
Okay, I figured the immutability bit out and I got the IORef example
working, but I can't get it to work with state.

 put (pureMT 0) = runRVar flipCoin

gives me two type errors: No instance for (MonadState PureMT m) and No
instance for (RandomSource m ())

 runState $ put (pureMT 0) = runRVar flipCoin
 runState $ put (pureMT 0)  get = runRVar flipCoin
 put (pureMT 0)  get = runRVar flipCoin

and other desperate attempts, some of which in hindsight are too
embarrassing to list give me similar errors.  I'm trying to do figure out
how to do this without going to the IO monad (so I can run it with the same
seed to replicate results).

On Tue, Sep 7, 2010 at 3:14 PM, James Andrew Cook mo...@deepbondi.netwrote:

 A PureMT generator is immutable, so must be threaded through the monad in
 which you are sampling.  There are RandomSource instances provided for a few
 special cases, including IORef PureMT in the IO monad.  For example:

 main = do
mt - newPureMT
src - newIORef mt
flips - runRVar (replicateM 20 flipCoin) src
print flips

 Alternatively, the functions in the module you mentioned can be used to
 define additional instances, such as:

 instance MonadRandom (State PureMT) where
supportedPrims _ _ = True
getSupportedRandomPrim = getRandomPrimFromPureMTState

 And RandomSource instances look almost the same.  See the
 Data.Random.Source.PureMT source for examples.  (I thought I had included
 this particular instance in the distribution but I apparently missed it.
  The next release will probably include this as well as corresponding
 instances for the 'transformers' package, possibly separated out into
 'random-fu-mtl' and 'random-fu-transformers' packages).

 The StdRandom type is a convenient RandomSource designating this
 instance in the State PureMT monad.  Personally, I prefer to use the
 sample function for this purpose, as well as the sampleFrom function in
 place of runRVar/runRVarT.  GHCi does not display the sample functions'
 types properly - they are defined for RVarT as well as for all Distribution
 instances.

 Sorry it took so long responding.

 -- James

 On Sep 2, 2010, at 10:01 AM, Alex Rozenshteyn wrote:

  I seem to be having confusion at the runRVar level of random-fu.
 
  I can't figure out how to use the Data.Random.Source.PureMT module to get
 a meaningful random source (I can't get my code to type-check).
 
  I wrote a [trivial] flipCoin function
   flipCoin = uniform False True
  and am trying to fill in the final place of runRVar
   :t runRVar (replicateM 20 flipCoin)
  runRVar (replicateM 20 flipCoin)
:: (RandomSource m s) = s - m [Bool]
 
 
  --
Alex R
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe




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


Re: [Haskell-cafe] random-fu confusion

2010-09-07 Thread James Andrew Cook
On Sep 7, 2010, at 10:21 AM, Alex Rozenshteyn wrote:

 Okay, I figured the immutability bit out and I got the IORef example working, 
 but I can't get it to work with state.
 
  put (pureMT 0) = runRVar flipCoin
 
 gives me two type errors: No instance for (MonadState PureMT m) and No 
 instance for (RandomSource m ())
 

The first error is because put has the general type: put :: (MonadState s m) 
= s - m () and GHC doesn't know what monad you want to evaluate it in.  Just 
off the bat there are 2 possibilities provided by Control.Monad.State: State 
and StateT.
The second is because runRVar requires an additional argument specifying the 
source from which to sample.  In your case, you want to sample from the 
standard source, the MonadRandom instance.  The type StdRandom with a 
single constructor of the same name designates the MonadRandom instance.  So 
for your example, a working incantation would be:

 put (pureMT 0) = runRVar flipCoin StdRandom :: State PureMT Bool

To actually run this action you would then use runState or evalState, in which 
case the type annotation would no longer be necessary because the use of 
runState or evalState would give the compiler enough information to know what 
you want.  These functions both also accept an initial state as an argument, so 
you don't actually need put either:

 evalState (runRVar flipCoin StdRandom) (pureMT 0)

Using the sample function I mentioned earlier you can leave off the mention 
of StdRandom:

 evalState (sample flipCoin) (pureMT 0)

  I'm trying to do figure out how to do this without going to the IO monad (so 
 I can run it with the same seed to replicate results).

Incidentally, you can use the 'pureMT' function to seed your generator in the 
IO monad just as easily:

 newIORef (pureMT 0) = \src - runRVar flipCoin src
 
or

 do src - newIORef (pureMT 0); runRVar flipCoin src

A large part of the point of the RVar monad as its own independent construct is 
to allow you to use random variables such as flipCoin in any monad that can 
support them while at the same time guaranteeing all the same purity / safety 
as if you had used something obviously pure such as State.

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


[Haskell-cafe] random-fu confusion

2010-09-02 Thread Alex Rozenshteyn
I seem to be having confusion at the runRVar level of random-fu.

I can't figure out how to use the Data.Random.Source.PureMT module to get a
meaningful random source (I can't get my code to type-check).

I wrote a [trivial] flipCoin function
 flipCoin = uniform False True
and am trying to fill in the final place of runRVar
 :t runRVar (replicateM 20 flipCoin)
runRVar (replicateM 20 flipCoin)
  :: (RandomSource m s) = s - m [Bool]


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


Re: [Haskell-cafe] Random this! ;-)

2010-07-26 Thread Lyndon Maydwell
I find it useful to have a seed argument to nearly all random
functions rather than using ones with an IO signature. This way you
can speed up your program quite a bit and also make testing much
easier. I think that MonadRandom does this automatically too.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Random this! ;-)

2010-07-26 Thread Edward Kmett
On Sun, Jul 25, 2010 at 11:39 AM, michael rice nowg...@yahoo.com wrote:

 Hi All,

 From: http://en.wikibooks.org/wiki/Haskell/Understanding_monads/State

Exercises

1. Implement a function rollNDiceIO :: Int - IO [Int] that,
   given an integer, returns a list with that number of pseudo-
   random integers between 1 and 6.


 After a lot of learning what not to do, this is the best I could come up
 with.

 rollNDiceIO :: Int - IO [Int]
 rollNDiceIO n = mapM (\x - randomRIO(1,6)) (replicate n 1)

 I know, ugly, but at least I got it to work. What's a better way to
 generate this list?


An even better method lets the list be generated lazily.

import Data.Functor (($))
import Random

rollDice :: IO [Int]
rollDice =  randomRs (1,6) $ newStdGen

rollNDice :: Int - IO [Int]
rollNDice n = take n $ rollDice

This is important because randomRIO has to peek at an MVar to determine the
current value of the random number seed _for each die rolled_, but using
randomRs on a fresh StdGen only has does so once.

Moreover, it gives you the more general 'rollDice' funtion, which can give
you an infinite list of random dice rolls. Trying to implement that function
using the approach you used will lead to a computation that won't terminate.

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


Re: [Haskell-cafe] Random this! ;-)

2010-07-26 Thread michael rice
Hi Lyndon,

Since the example immediately above the exercise used randomRIO, I assumed that 
randomRIO was to be used as part of the solution to the exercise.

http://en.wikibooks.org/wiki/Haskell/Understanding_monads/State

Also, it was the above mentioned example that introduced me to *liftM2*, about 
which I posted a question a couple of days ago (subject line: Heavy lift-ing).

The next topic on the wiki page is Getting Rid of the IO which seems to be 
the direction of your post. No doubt I'll have more questions as I plod on.

Thanks for your input,

Michael


--- On Mon, 7/26/10, Lyndon Maydwell maydw...@gmail.com wrote:

From: Lyndon Maydwell maydw...@gmail.com
Subject: Re: [Haskell-cafe] Random this! ;-)
To: michael rice nowg...@yahoo.com
Cc: Max Rabkin max.rab...@gmail.com, Ozgur Akgun ozgurak...@gmail.com, 
haskell-cafe@haskell.org
Date: Monday, July 26, 2010, 8:29 AM

I find it useful to have a seed argument to nearly all random
functions rather than using ones with an IO signature. This way you
can speed up your program quite a bit and also make testing much
easier. I think that MonadRandom does this automatically too.



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


[Haskell-cafe] Random this! ;-)

2010-07-25 Thread michael rice
Hi All,

From: http://en.wikibooks.org/wiki/Haskell/Understanding_monads/State

   Exercises

   1. Implement a function rollNDiceIO :: Int - IO [Int] that,
  given an integer, returns a list with that number of pseudo-
  random integers between 1 and 6.


After a lot of learning what not to do, this is the best I could come up with.

rollNDiceIO :: Int - IO [Int]
rollNDiceIO n = mapM (\x - randomRIO(1,6)) (replicate n 1)

I know, ugly, but at least I got it to work. What's a better way to generate 
this list?

Michael




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


Re: [Haskell-cafe] Random this! ;-)

2010-07-25 Thread Max Rabkin
On Sun, Jul 25, 2010 at 5:39 PM, michael rice nowg...@yahoo.com wrote:

 I know, ugly, but at least I got it to work. What's a better way to generate 
 this list?

rollNDiceIO n
   = sequence . replicate n $ randomRIO (1,6)
{{ sequence . replicate n = replicateM n }}
   = replicateM n $ randomRIO (1, 6)

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


Re: [Haskell-cafe] Random this! ;-)

2010-07-25 Thread Tobias Brandt
Look for the function replicateM in the module Control.Monad.

On 25 July 2010 17:39, michael rice nowg...@yahoo.com wrote:

 Hi All,

 From: http://en.wikibooks.org/wiki/Haskell/Understanding_monads/State

Exercises

1. Implement a function rollNDiceIO :: Int - IO [Int] that,
   given an integer, returns a list with that number of pseudo-
   random integers between 1 and 6.


 After a lot of learning what not to do, this is the best I could come up
 with.

 rollNDiceIO :: Int - IO [Int]
 rollNDiceIO n = mapM (\x - randomRIO(1,6)) (replicate n 1)

 I know, ugly, but at least I got it to work. What's a better way to
 generate this list?

 Michael



 ___
 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


Re: [Haskell-cafe] Random this! ;-)

2010-07-25 Thread michael rice
Hi Max,

Wow!

I tried both *sequence* and *replicate* but guess I didn't put them together 
properly. I didn't even know there was a *replicateM*.

Much cleaner.

Thanks

Michael

--- On Sun, 7/25/10, Max Rabkin max.rab...@gmail.com wrote:

From: Max Rabkin max.rab...@gmail.com
Subject: Re: [Haskell-cafe] Random this! ;-)
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Sunday, July 25, 2010, 11:44 AM

On Sun, Jul 25, 2010 at 5:39 PM, michael rice nowg...@yahoo.com wrote:

 I know, ugly, but at least I got it to work. What's a better way to generate 
 this list?

rollNDiceIO n
   = sequence . replicate n $ randomRIO (1,6)
{{ sequence . replicate n = replicateM n }}
   = replicateM n $ randomRIO (1, 6)

--Max



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


Re: [Haskell-cafe] Random this! ;-)

2010-07-25 Thread Ozgur Akgun
Sorry but I'll just go ahead and eta reduce it :)

rollNDiceIO = flip replicateM $ randomRIO (1,6)

On 25 July 2010 16:44, Max Rabkin max.rab...@gmail.com wrote:

 On Sun, Jul 25, 2010 at 5:39 PM, michael rice nowg...@yahoo.com wrote:
 
  I know, ugly, but at least I got it to work. What's a better way to
 generate this list?

 rollNDiceIO n
   = sequence . replicate n $ randomRIO (1,6)
 {{ sequence . replicate n = replicateM n }}
   = replicateM n $ randomRIO (1, 6)

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




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


Re: [Haskell-cafe] Random this! ;-)

2010-07-25 Thread michael rice
Cool. Everything's there but the N.

Learning Haskell is a lot like learning to dance.

Michael


--- On Sun, 7/25/10, Ozgur Akgun ozgurak...@gmail.com wrote:

From: Ozgur Akgun ozgurak...@gmail.com
Subject: Re: [Haskell-cafe] Random this! ;-)
To: Max Rabkin max.rab...@gmail.com
Cc: michael rice nowg...@yahoo.com, haskell-cafe@haskell.org
Date: Sunday, July 25, 2010, 3:17 PM

Sorry but I'll just go ahead and eta reduce it :)

rollNDiceIO = flip replicateM $ randomRIO (1,6)

On 25 July 2010 16:44, Max Rabkin max.rab...@gmail.com wrote:

On Sun, Jul 25, 2010 at 5:39 PM, michael rice nowg...@yahoo.com wrote:




 I know, ugly, but at least I got it to work. What's a better way to generate 
 this list?



rollNDiceIO n

   = sequence . replicate n $ randomRIO (1,6)

{{ sequence . replicate n = replicateM n }}

   = replicateM n $ randomRIO (1, 6)



--Max

___

Haskell-Cafe mailing list

Haskell-Cafe@haskell.org

http://www.haskell.org/mailman/listinfo/haskell-cafe




-- 
Ozgur Akgun




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


Re: [Haskell-cafe] random question

2009-10-08 Thread Nicolas Pouillard
Excerpts from Bryan O'Sullivan's message of Wed Oct 07 23:25:10 +0200 2009:
 On Wed, Oct 7, 2009 at 1:59 PM, Michael Mossey m...@alumni.caltech.eduwrote:
 
  My thread about randomness got hijacked so I need to restate my remaining
  question here. Is it acceptable to write pure routines that use but do not
  return generators, and then call several of them from an IO monad with a
  generator obtained by several calls to newStdGen?
 
  shuffle :: RandomGen g = g - [a] - [a]
  shuffle = ...
 
  foo :: [a] - [a] - IO ()
  foo xs ys = do
   g1 - newStdGen
   print $ shuffle g1 xs
   g2 - newStdGen
   print $ shuffle g2 ys
 
  Does this kind of thing exhibit good pseudorandomness?
 
 
 If you believe in the safety of the split operation (which I don't), then
  
 |
Can you elaborate on that?  -+

Best regards,

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


[Haskell-cafe] random question

2009-10-07 Thread Michael Mossey
My thread about randomness got hijacked so I need to restate my remaining 
question here. Is it acceptable to write pure routines that use but do not 
return generators, and then call several of them from an IO monad with a 
generator obtained by several calls to newStdGen?


shuffle :: RandomGen g = g - [a] - [a]
shuffle = ...

foo :: [a] - [a] - IO ()
foo xs ys = do
  g1 - newStdGen
  print $ shuffle g1 xs
  g2 - newStdGen
  print $ shuffle g2 ys

Does this kind of thing exhibit good pseudorandomness?

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


Re: [Haskell-cafe] random question

2009-10-07 Thread Luke Palmer
On Wed, Oct 7, 2009 at 2:59 PM, Michael Mossey m...@alumni.caltech.edu wrote:
 My thread about randomness got hijacked so I need to restate my remaining
 question here. Is it acceptable to write pure routines that use but do not
 return generators, and then call several of them from an IO monad with a
 generator obtained by several calls to newStdGen?

It's gross.  What if you don't want IO as part of this computation?

If you have a random generator that supports splitting (something
rather hard to do from what I understand), I prefer not to return the
new generator but instead to split it.  So, using your shuffle:

 shuffle :: RandomGen g = g - [a] - [a]
 shuffle = ...

foo :: RandomGen g = [a] - [a] - g - ([a],[a])
foo xs ys gen =
  let (gen1, gen2) = split gen in
  (shuffle gen1 xs, shuffle gen2 ys)

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


Re: [Haskell-cafe] random question

2009-10-07 Thread Bryan O'Sullivan
On Wed, Oct 7, 2009 at 1:59 PM, Michael Mossey m...@alumni.caltech.eduwrote:

 My thread about randomness got hijacked so I need to restate my remaining
 question here. Is it acceptable to write pure routines that use but do not
 return generators, and then call several of them from an IO monad with a
 generator obtained by several calls to newStdGen?

 shuffle :: RandomGen g = g - [a] - [a]
 shuffle = ...

 foo :: [a] - [a] - IO ()
 foo xs ys = do
  g1 - newStdGen
  print $ shuffle g1 xs
  g2 - newStdGen
  print $ shuffle g2 ys

 Does this kind of thing exhibit good pseudorandomness?


If you believe in the safety of the split operation (which I don't), then
yes, since use of it is what's happening behind the scenes. In other words,
provided you're a faithful sort and split doesn't make you squirm too much,
you don't need to plug all that ugly IO in there.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] random question

2009-10-07 Thread Michael Mossey



Luke Palmer wrote:

On Wed, Oct 7, 2009 at 2:59 PM, Michael Mossey m...@alumni.caltech.edu wrote:

My thread about randomness got hijacked so I need to restate my remaining
question here. Is it acceptable to write pure routines that use but do not
return generators, and then call several of them from an IO monad with a
generator obtained by several calls to newStdGen?


It's gross.  What if you don't want IO as part of this computation?



I don't quite follow your response. I want a program that initializes the 
generator from the global generator because I want different behavior every 
time I run it. So it will need IO. That's what I was trying to demonstrate. 
And I was wondering if one can get around the difficulty of passing the 
generator from call to call by using newStdGen in this way.


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


Re: [Haskell-cafe] random question

2009-10-07 Thread Daniel Fischer
Am Mittwoch 07 Oktober 2009 23:28:59 schrieb Michael Mossey:
 Luke Palmer wrote:
  On Wed, Oct 7, 2009 at 2:59 PM, Michael Mossey m...@alumni.caltech.edu 
  wrote:
  My thread about randomness got hijacked so I need to restate my
  remaining question here. Is it acceptable to write pure routines that
  use but do not return generators, and then call several of them from an
  IO monad with a generator obtained by several calls to newStdGen?
 
  It's gross.  What if you don't want IO as part of this computation?

 I don't quite follow your response. I want a program that initializes the
 generator from the global generator because I want different behavior every
 time I run it. So it will need IO. That's what I was trying to demonstrate.
 And I was wondering if one can get around the difficulty of passing the
 generator from call to call by using newStdGen in this way.

 Mike

Documentation says:

newStdGen :: IO StdGen
Applies split to the current global random generator, updates it with one of 
the results, 
and returns the other.

So it's as safe as split is.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] random question

2009-10-07 Thread Ryan Ingram
On Wed, Oct 7, 2009 at 2:28 PM, Michael Mossey m...@alumni.caltech.eduwrote:

 I don't quite follow your response. I want a program that initializes the
 generator from the global generator because I want different behavior every
 time I run it. So it will need IO. That's what I was trying to demonstrate.
 And I was wondering if one can get around the difficulty of passing the
 generator from call to call by using newStdGen in this way.


You should only have to call newStdGen once:

main = do
   g - newStdGen
   let (g1,g2) = split g
   let xs = [1..10]
   print $ shuffle g1 xs
   print $ shuffle g2 xs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Random Number

2009-06-07 Thread ptrash

Hi, 

is the are way (or a build in method) in haskell to get a random number from
a number bottom to a number top?

Something like

let randomNumber = random 1 30

to get a random number between 1 and 30.
-- 
View this message in context: 
http://www.nabble.com/Random-Number-tp23914474p23914474.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Random Number

2009-06-07 Thread José Prous
look in System.Random
randomRIO :: (Random a) = (a, a) - IO a

you can do
randomNumber-randomRIO (1,30)


On Sun, Jun 7, 2009 at 3:33 PM, ptrash ptr...@web.de wrote:


 Hi,

 is the are way (or a build in method) in haskell to get a random number
 from
 a number bottom to a number top?

 Something like

 let randomNumber = random 1 30

 to get a random number between 1 and 30.
 --
 View this message in context:
 http://www.nabble.com/Random-Number-tp23914474p23914474.html
 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

 ___
 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


Re: [Haskell-cafe] Random Number

2009-06-07 Thread Krzysztof Skrzętnicki
On Sun, Jun 7, 2009 at 21:33, ptrashptr...@web.de wrote:

 Hi,

 is the are way (or a build in method) in haskell to get a random number from
 a number bottom to a number top?

 Something like

 let randomNumber = random 1 30

 to get a random number between 1 and 30.

I don't mean to be rude, but did you even tried to read the
documentation? The function you want is here:
http://www.haskell.org/ghc/docs/latest/html/libraries/random/System-Random.html

Before you ask any other questions please read this essay:
http://mattgemmell.com/2008/12/08/what-have-you-tried

Best regards

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


Re: [Haskell-cafe] Random Number

2009-06-07 Thread Iain Barnett

On 7 Jun 2009, at 8:33 pm, ptrash wrote:



Hi,

is the are way (or a build in method) in haskell to get a random  
number from

a number bottom to a number top?

Something like

let randomNumber = random 1 30

to get a random number between 1 and 30.



rand :: Int - Int - IO Int
rand low high = getStdRandom (randomR (low,high))

this worked for me, I also had quite a few random questions on here a  
few months ago! :)


Beware it is an IO int.


On 7 Jun 2009, at 8:55 pm, Krzysztof Skrzętnicki wrote:

I don't mean to be rude, but did you even tried to read the
documentation? The function you want is here:
http://www.haskell.org/ghc/docs/latest/html/libraries/random/System- 
Random.html


Before you ask any other questions please read this essay:
http://mattgemmell.com/2008/12/08/what-have-you-tried

Best regards

Krzysztof Skrzętnicki




Bit harsh isn't it? He asked for an example function, not an entire  
program.


Iain





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


Re: [Haskell-cafe] Random Number

2009-06-07 Thread michael rice
Good essay.

Try this one for a laugh:


http://www.mcs.vuw.ac.nz/comp/Publications/CS-TR-02-9.abs.html


A good place to begin is PDF pg. 19.

Michael


--- On Sun, 6/7/09, Krzysztof Skrzętnicki gte...@gmail.com wrote:

From: Krzysztof Skrzętnicki gte...@gmail.com
Subject: Re: [Haskell-cafe] Random Number
To: ptrash ptr...@web.de
Cc: haskell-cafe@haskell.org
Date: Sunday, June 7, 2009, 3:55 PM

On Sun, Jun 7, 2009 at 21:33, ptrashptr...@web.de wrote:

 Hi,

 is the are way (or a build in method) in haskell to get a random number from
 a number bottom to a number top?

 Something like

 let randomNumber = random 1 30

 to get a random number between 1 and 30.

I don't mean to be rude, but did you even tried to read the
documentation? The function you want is here:
http://www.haskell.org/ghc/docs/latest/html/libraries/random/System-Random.html

Before you ask any other questions please read this essay:
http://mattgemmell.com/2008/12/08/what-have-you-tried

Best regards

Krzysztof Skrzętnicki
___
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


Re: [Haskell-cafe] Random number example

2009-04-28 Thread Ross Mellgren
I'm not sure what you're asking by define type Random [Int]? Your  
type Random a will allow a to be any type, e.g. [Int] is perfectly fine.


If what you're asking is how do you get from Random Int to Random  
[Int], the usual answer would be to use


replicateM :: Monad m = Int - m a - m [a]

which is formulated from

replicate :: Int - a - [a]

and

sequence :: Monad m = [m a] - m [a]

of course, you're implementing Monad all over again without using the  
Monad typeclass, so you can't use the library functions pertaining to  
monads. In your case, I'd build it up the same way the library does it  
-- create a list of actions, and then use a function to bind all the  
actions together, e.g.


rolls :: Int - [Random Int]
rolls n = replicate n rollDie

and then create something that binds them together, usually a foldr,  
so you could use it like this:


sequenceRandom :: [Random a] - Random [a]
sequenceRandom = ...

rollNDice :: Int - Random [Int]
rollNDice = sequenceRandom . rolls

-Ross


On Apr 26, 2009, at 8:45 PM, michael rice wrote:

How do I define type Random [Int] for rollNDice in Exercise 1, given  
the code below?


Michael



Exercises

   1. Implement rollNDice :: Int - Random [Int] from the previous  
subsection with = and return.


NOTE: Since = and return are already present in the Prelude, you  
may want to use import Prelude hiding ((=),return) to avoid  
compilation errors.


=

{-# LANGUAGE NoImplicitPrelude #-}

import Prelude hiding ((), (=), return)

type Seed = Int
type Random a = Seed - (a, Seed)

randomNext :: Seed - Seed
randomNext rand = if newRand  0 then newRand else newRand +  
2147483647

where newRand = 16807 * lo - 2836 * hi
  (hi,lo) = rand `divMod` 127773

rollDie :: Random Int
rollDie seed = ((seed `mod` 6) + 1, randomNext seed)

() :: Random a - Random b - Random b
() m n = \seed0 -
  let (result1, seed1) = m seed0
  (result2, seed2) = n seed1
  in (result2, seed2)

(=) :: Random a - (a - Random b) - Random b
(=) m g = \seed0 -
  let (result1, seed1) = m seed0
  (result2, seed2) = (g result1) seed1
  in (result2, seed2)

return :: a - Random a
return x = \seed0 - (x, seed0)

sumTwoDice :: Random Int
sumTwoDice = rollDie = (\die1 - rollDie = (\die2 - return  
(die1 + die2)))


rollNDice :: Int - Random [Int]


--- On Thu, 4/23/09, michael rice nowg...@yahoo.com wrote:

From: michael rice nowg...@yahoo.com
Subject: Re: [Haskell-cafe] Random number example
To: Ross Mellgren rmm-hask...@z.odi.ac
Cc: haskell-cafe@haskell.org
Date: Thursday, April 23, 2009, 5:49 PM

Hi Ross,

Thanks for going the extra mile. A lot of what you did I haven't  
seen before, so it's going to take me some time to go through it.  
But I'll be back.


Michael

--- On Thu, 4/23/09, Ross Mellgren rmm-hask...@z.odi.ac wrote:

From: Ross Mellgren rmm-hask...@z.odi.ac
Subject: Re: [Haskell-cafe] Random number example
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Thursday, April 23, 2009, 11:51 AM

So there are a couple problems. First is you are trying to rebind  
prelude functions, when instead you should be creating an instance  
of Monad. This requires a bit of shuffling because without language  
extensions you can't instance Monad Random for your type of Random,  
as it is a type synonym. So, changing the type synonym to a newtype  
and instancing monad, you get:


module Rand9b where

import Control.Applicative (Applicative(..), ($), (*))
import Control.Monad (ap, liftM)

type Seed = Int
newtype Random a = Rand { unRand :: (Seed - (a, Seed)) }

randomNext :: Seed - Seed
randomNext rand = if newRand  0 then newRand else newRand +  
2147483647

where newRand = 16807 * lo - 2836 * hi
  (hi,lo) = rand `divMod` 127773

rollDie :: Random Int
rollDie = Rand $ \ seed - ((seed `mod` 6) + 1, randomNext seed)

instance Monad Random where
(=) = randomBind
return = randomReturn

instance Functor Random where
fmap = liftM

instance Applicative Random where
pure = return
(*) = ap

randomBind :: Random a - (a - Random b) - Random b
m `randomBind` g = Rand $ \seed0 -
  let (result1, seed1) = unRand m $ seed0
  (result2, seed2) = unRand (g result1) $ seed1
  in (result2, seed2)

randomReturn :: a - Random a
randomReturn x = Rand $ \ seed0 - (x, seed0)

sumTwoDice :: Random Int
sumTwoDice = (+) $ rollDie * rollDie


I also threw in instances of Functor and Applicative, so that I  
could simplify sumTwoDice using applicative form (much nicer, no?  
Applicative is totally rockin')


Now you need one more thing, a way to convert a series of Random  
actions into a pure function:



runRandom :: Seed - Random a - a
runRandom s f = fst . unRand f $ s

which now makes what you want to do in GHCi easy and well wrapped:

Prelude :reload
[1 of 1] Compiling Rand9b   ( rand9b.hs, interpreted )
Ok, modules loaded: Rand9b.
*Rand9b runRandom 0 sumTwoDice
3


Hope this helps,
-Ross


On Apr 23, 2009, at 11:28 AM

Re: [Haskell-cafe] Random number example

2009-04-26 Thread michael rice
How do I define type Random [Int] for rollNDice in Exercise 1, given the code 
below?

Michael



Exercises

   1. Implement rollNDice :: Int - Random [Int] from the previous subsection 
with = and return.

NOTE: Since = and return are already present in the Prelude, you may want to 
use import Prelude hiding ((=),return) to avoid compilation errors.

=

{-# LANGUAGE NoImplicitPrelude #-}

import Prelude hiding ((), (=), return)

type Seed = Int
type Random a = Seed - (a, Seed)

randomNext :: Seed - Seed
randomNext rand = if newRand  0 then newRand else newRand + 2147483647
    where newRand = 16807 * lo - 2836 * hi
  (hi,lo) = rand `divMod` 127773

rollDie :: Random Int
rollDie seed = ((seed `mod` 6) + 1, randomNext seed)

() :: Random a - Random b - Random b
() m n = \seed0 -
  let (result1, seed1) = m seed0
  (result2, seed2) = n seed1
  in (result2, seed2)

(=) :: Random a - (a - Random b) - Random b
(=) m g = \seed0 - 
  let (result1, seed1) = m seed0
  (result2, seed2) = (g result1) seed1
  in (result2, seed2)

return :: a - Random a
return x = \seed0 - (x, seed0)

sumTwoDice :: Random Int
sumTwoDice = rollDie = (\die1 - rollDie = (\die2 - return (die1 + die2)))

rollNDice :: Int - Random [Int]


--- On Thu, 4/23/09, michael rice nowg...@yahoo.com wrote:

From: michael rice nowg...@yahoo.com
Subject: Re: [Haskell-cafe] Random number example
To: Ross Mellgren rmm-hask...@z.odi.ac
Cc: haskell-cafe@haskell.org
Date: Thursday, April 23, 2009, 5:49 PM

Hi Ross,

Thanks for going the extra mile. A lot of what you did I haven't seen before, 
so it's going to take me some time to go through it. But I'll be back.

Michael

--- On Thu, 4/23/09, Ross Mellgren rmm-hask...@z.odi.ac wrote:

From: Ross Mellgren rmm-hask...@z.odi.ac
Subject: Re: [Haskell-cafe] Random number example
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Thursday, April 23, 2009, 11:51 AM

So there are a couple problems. First is you are trying to rebind prelude 
functions, when instead you should be creating an instance of Monad. This 
requires a bit of shuffling because without language extensions you can't 
instance Monad
 Random for your type of Random, as it is a type synonym. So, changing the type 
synonym to a newtype and instancing monad, you get:
module Rand9b where
import Control.Applicative (Applicative(..), ($), (*))import Control.Monad 
(ap, liftM)
type Seed = Intnewtype Random a = Rand { unRand :: (Seed - (a, Seed)) }
randomNext :: Seed - SeedrandomNext rand = if newRand  0 then newRand else 
newRand + 2147483647    where newRand = 16807 * lo - 2836 * hi          (hi,lo) 
= rand `divMod` 127773
rollDie :: Random IntrollDie = Rand $ \ seed - ((seed `mod` 6) + 1, randomNext 
seed)
instance Monad Random where    (=) =
 randomBind    return = randomReturn
instance Functor Random where    fmap = liftM
instance Applicative Random where    pure = return    (*) = ap
randomBind :: Random a - (a - Random b) - Random bm `randomBind` g = Rand $ 
\seed0 -   let (result1, seed1) = unRand m $ seed0      (result2, seed2) = 
unRand (g result1) $ seed1  in (result2, seed2)
randomReturn :: a - Random arandomReturn x = Rand $ \ seed0 - (x, seed0)
sumTwoDice :: Random IntsumTwoDice = (+) $ rollDie * rollDie

I also threw in instances of Functor and Applicative,
 so that I could simplify sumTwoDice using applicative form (much nicer, no? 
Applicative is totally rockin')
Now you need one more thing, a way to convert a series of Random actions into a 
pure function:

runRandom :: Seed - Random a - arunRandom s f = fst . unRand f $ s 
which now makes what you want to do in GHCi easy and well wrapped:
Prelude :reload[1 of 1] Compiling Rand9b           ( rand9b.hs, interpreted 
)Ok, modules loaded: Rand9b.*Rand9b runRandom 0 sumTwoDice3

Hope this helps,-Ross

On Apr 23, 2009, at 11:28 AM, michael rice wrote:
I pretty much followed the sequence of steps that led to this final code (see 
below), but will be looking it over for a while to make sure it sinks in. In 
the meantime, I get this when I try to use it (sumTwoDice) at the command line:

[mich...@localhost ~]$ ghci rand9
GHCi, version 6.10.1: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer ... linking ... done.
Loading package base ... linking ... done.
[1 of 1] Compiling Main ( rand9.hs, interpreted )
Ok,
 modules loaded: Main.
*Main sumTwoDice

interactive:1:0:
    No instance for (Show (Seed - (Int, Seed)))
  arising from a use of `print' at interactive:1:0-9
    Possible fix:
  add an instance declaration for (Show (Seed - (Int, Seed)))
    In a stmt of a 'do' expression: print it
*Main 


Can I employ a 'do' expression from the command line?

Also, can I now use functions () (=) and 'return' defined in the Prelude 
and still have this code work?

Michael

==

{-# LANGUAGE NoImplicitPrelude #-}

import Prelude hiding

[Haskell-cafe] Random number example

2009-04-23 Thread michael rice
I pretty much followed the sequence of steps that led to this final code (see 
below), but will be looking it over for a while to make sure it sinks in. In 
the meantime, I get this when I try to use it (sumTwoDice) at the command line:

[mich...@localhost ~]$ ghci rand9
GHCi, version 6.10.1: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer ... linking ... done.
Loading package base ... linking ... done.
[1 of 1] Compiling Main ( rand9.hs, interpreted )
Ok, modules loaded: Main.
*Main sumTwoDice

interactive:1:0:
    No instance for (Show (Seed - (Int, Seed)))
  arising from a use of `print' at interactive:1:0-9
    Possible fix:
  add an instance declaration for (Show (Seed - (Int, Seed)))
    In a stmt of a 'do' expression: print it
*Main 


Can I employ a 'do' expression from the command line?

Also, can I now use functions () (=) and 'return' defined in the Prelude 
and still have this code work?

Michael

==

{-# LANGUAGE NoImplicitPrelude #-}

import Prelude hiding ((), (=), return)

type Seed = Int
type Random a = Seed - (a, Seed)

randomNext :: Seed - Seed
randomNext rand = if newRand  0 then newRand else newRand + 2147483647
    where newRand = 16807 * lo - 2836 * hi
  (hi,lo) = rand `divMod` 127773

rollDie :: Random Int
rollDie seed = ((seed `mod` 6) + 1, randomNext seed)

() :: Random a - Random b - Random b
() m n = \seed0 -
  let (result1, seed1) = m seed0
  (result2, seed2) = n seed1
  in (result2, seed2)

(=) :: Random a - (a - Random b) - Random b
(=) m g = \seed0 - 
  let (result1, seed1) = m seed0
  (result2, seed2) = (g result1) seed1
  in (result2, seed2)

return :: a - Random a
return x = \seed0 - (x, seed0)

sumTwoDice :: Random Int
sumTwoDice = rollDie = (\die1 - rollDie = (\die2 - return (die1 + die2)))




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


Re: [Haskell-cafe] Random number example

2009-04-23 Thread Daniel Fischer
Am Donnerstag 23 April 2009 17:28:58 schrieb michael rice:
 I pretty much followed the sequence of steps that led to this final code
 (see below), but will be looking it over for a while to make sure it sinks
 in. In the meantime, I get this when I try to use it (sumTwoDice) at the
 command line:

 [mich...@localhost ~]$ ghci rand9
 GHCi, version 6.10.1: http://www.haskell.org/ghc/  :? for help
 Loading package ghc-prim ... linking ... done.
 Loading package integer ... linking ... done.
 Loading package base ... linking ... done.
 [1 of 1] Compiling Main ( rand9.hs, interpreted )
 Ok, modules loaded: Main.
 *Main sumTwoDice

 interactive:1:0:
     No instance for (Show (Seed - (Int, Seed)))
   arising from a use of `print' at interactive:1:0-9
     Possible fix:
   add an instance declaration for (Show (Seed - (Int, Seed)))
     In a stmt of a 'do' expression: print it
 *Main


sumTwoDice is a function, those have no (meaningful) Show instance.
What you probably wanted is

*Main sumTwoDice 123456
*Main 789


 Can I employ a 'do' expression from the command line?

Sure:
Prelude do { line - getLine; putStrLn (reverse line); putStrLn (drop 4 line) }
some input
tupni emos
 input

Just the do-expression must be an IO-action (which is then executed, like the 
above 
example) or it must have a showable type like

Prelude do { x - [1 .. 5]; let { y = x^2+1 }; [1,5 .. y] }
[1,1,5,1,5,9,1,5,9,13,17,1,5,9,13,17,21,25]



 Also, can I now use functions () (=) and 'return' defined in the
 Prelude and still have this code work?

Almost. You would have to make Random an instance of Monad to use the Prelude 
(=), () 
and return, but you cant make a type synonym like

type Random a = Seed - (a,Seed)

an instance of a type class. So you have to put it inside a newtype wrapper:

newtype Random a = R (Seed - (a,Seed))

instance Monad Random where
return x = R (\s - (x,s))
(R r) = f = R $ \s - let { (x,s') = r s; R g = f x } in g s'

 Michael


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


Re: [Haskell-cafe] Random number example

2009-04-23 Thread Ross Mellgren
So there are a couple problems. First is you are trying to rebind  
prelude functions, when instead you should be creating an instance of  
Monad. This requires a bit of shuffling because without language  
extensions you can't instance Monad Random for your type of Random, as  
it is a type synonym. So, changing the type synonym to a newtype and  
instancing monad, you get:


module Rand9b where

import Control.Applicative (Applicative(..), ($), (*))
import Control.Monad (ap, liftM)

type Seed = Int
newtype Random a = Rand { unRand :: (Seed - (a, Seed)) }

randomNext :: Seed - Seed
randomNext rand = if newRand  0 then newRand else newRand + 2147483647
where newRand = 16807 * lo - 2836 * hi
  (hi,lo) = rand `divMod` 127773

rollDie :: Random Int
rollDie = Rand $ \ seed - ((seed `mod` 6) + 1, randomNext seed)

instance Monad Random where
(=) = randomBind
return = randomReturn

instance Functor Random where
fmap = liftM

instance Applicative Random where
pure = return
(*) = ap

randomBind :: Random a - (a - Random b) - Random b
m `randomBind` g = Rand $ \seed0 -
  let (result1, seed1) = unRand m $ seed0
  (result2, seed2) = unRand (g result1) $ seed1
  in (result2, seed2)

randomReturn :: a - Random a
randomReturn x = Rand $ \ seed0 - (x, seed0)

sumTwoDice :: Random Int
sumTwoDice = (+) $ rollDie * rollDie


I also threw in instances of Functor and Applicative, so that I could  
simplify sumTwoDice using applicative form (much nicer, no?  
Applicative is totally rockin')


Now you need one more thing, a way to convert a series of Random  
actions into a pure function:



runRandom :: Seed - Random a - a
runRandom s f = fst . unRand f $ s

which now makes what you want to do in GHCi easy and well wrapped:

Prelude :reload
[1 of 1] Compiling Rand9b   ( rand9b.hs, interpreted )
Ok, modules loaded: Rand9b.
*Rand9b runRandom 0 sumTwoDice
3


Hope this helps,
-Ross


On Apr 23, 2009, at 11:28 AM, michael rice wrote:

I pretty much followed the sequence of steps that led to this final  
code (see below), but will be looking it over for a while to make  
sure it sinks in. In the meantime, I get this when I try to use it  
(sumTwoDice) at the command line:


[mich...@localhost ~]$ ghci rand9
GHCi, version 6.10.1: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer ... linking ... done.
Loading package base ... linking ... done.
[1 of 1] Compiling Main ( rand9.hs, interpreted )
Ok, modules loaded: Main.
*Main sumTwoDice

interactive:1:0:
No instance for (Show (Seed - (Int, Seed)))
  arising from a use of `print' at interactive:1:0-9
Possible fix:
  add an instance declaration for (Show (Seed - (Int, Seed)))
In a stmt of a 'do' expression: print it
*Main


Can I employ a 'do' expression from the command line?

Also, can I now use functions () (=) and 'return' defined in the  
Prelude and still have this code work?


Michael

==

{-# LANGUAGE NoImplicitPrelude #-}

import Prelude hiding ((), (=), return)

type Seed = Int
type Random a = Seed - (a, Seed)

randomNext :: Seed - Seed
randomNext rand = if newRand  0 then newRand else newRand +  
2147483647

where newRand = 16807 * lo - 2836 * hi
  (hi,lo) = rand `divMod` 127773

rollDie :: Random Int
rollDie seed = ((seed `mod` 6) + 1, randomNext seed)

() :: Random a - Random b - Random b
() m n = \seed0 -
  let (result1, seed1) = m seed0
  (result2, seed2) = n seed1
  in (result2, seed2)

(=) :: Random a - (a - Random b) - Random b
(=) m g = \seed0 -
  let (result1, seed1) = m seed0
  (result2, seed2) = (g result1) seed1
  in (result2, seed2)

return :: a - Random a
return x = \seed0 - (x, seed0)

sumTwoDice :: Random Int
sumTwoDice = rollDie = (\die1 - rollDie = (\die2 - return  
(die1 + die2)))



___
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


Re: [Haskell-cafe] Random number example

2009-04-23 Thread Brandon S. Allbery KF8NH

On Apr 23, 2009, at 11:28 , michael rice wrote:

interactive:1:0:
No instance for (Show (Seed - (Int, Seed)))
  arising from a use of `print' at interactive:1:0-9
Possible fix:
  add an instance declaration for (Show (Seed - (Int, Seed)))
In a stmt of a 'do' expression: print it


Pretty much any time you get this kind of message, you've forgotten to  
include one or more arguments (how many is indicated by the number of  
-s) so ghci is trying to print a function.


In this case, while the definition of sumTwoDice *looks* like it  
doesn't take any arguments, if you look at the definition of the  
Random type, it is a function (in fact, the very type ghci is trying  
to print).  You need to give it a seed before it will produce a result.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH




PGP.sig
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Random number example

2009-04-23 Thread michael rice
Hi Ross,

Thanks for going the extra mile. A lot of what you did I haven't seen before, 
so it's going to take me some time to go through it. But I'll be back.

Michael

--- On Thu, 4/23/09, Ross Mellgren rmm-hask...@z.odi.ac wrote:

From: Ross Mellgren rmm-hask...@z.odi.ac
Subject: Re: [Haskell-cafe] Random number example
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Thursday, April 23, 2009, 11:51 AM

So there are a couple problems. First is you are trying to rebind prelude 
functions, when instead you should be creating an instance of Monad. This 
requires a bit of shuffling because without language extensions you can't 
instance Monad Random for your type of Random, as it is a type synonym. So, 
changing the type synonym to a newtype and instancing monad, you get:
module Rand9b where
import Control.Applicative (Applicative(..), ($), (*))import Control.Monad 
(ap, liftM)
type Seed = Intnewtype Random a = Rand { unRand :: (Seed - (a, Seed)) }
randomNext :: Seed - SeedrandomNext rand = if newRand  0 then newRand else 
newRand + 2147483647    where newRand = 16807 * lo - 2836 * hi          (hi,lo) 
= rand `divMod` 127773
rollDie :: Random IntrollDie = Rand $ \ seed - ((seed `mod` 6) + 1, randomNext 
seed)
instance Monad Random where    (=) = randomBind    return = randomReturn
instance Functor Random where    fmap = liftM
instance Applicative Random where    pure = return    (*) = ap
randomBind :: Random a - (a - Random b) - Random bm `randomBind` g = Rand $ 
\seed0 -   let (result1, seed1) = unRand m $ seed0      (result2, seed2) = 
unRand (g result1) $ seed1  in (result2, seed2)
randomReturn :: a - Random arandomReturn x = Rand $ \ seed0 - (x, seed0)
sumTwoDice :: Random IntsumTwoDice = (+) $ rollDie * rollDie

I also threw in instances of Functor and Applicative, so that I could simplify 
sumTwoDice using applicative form (much nicer, no? Applicative is totally 
rockin')
Now you need one more thing, a way to convert a series of Random actions into a 
pure function:

runRandom :: Seed - Random a - arunRandom s f = fst . unRand f $ s 
which now makes what you want to do in GHCi easy and well wrapped:
Prelude :reload[1 of 1] Compiling Rand9b           ( rand9b.hs, interpreted 
)Ok, modules loaded: Rand9b.*Rand9b runRandom 0 sumTwoDice3

Hope this helps,-Ross

On Apr 23, 2009, at 11:28 AM, michael rice wrote:
I pretty much followed the sequence of steps that led to this final code (see 
below), but will be looking it over for a while to make sure it sinks in. In 
the meantime, I get this when I try to use it (sumTwoDice) at the command line:

[mich...@localhost ~]$ ghci rand9
GHCi, version 6.10.1: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer ... linking ... done.
Loading package base ... linking ... done.
[1 of 1] Compiling Main ( rand9.hs, interpreted )
Ok, modules loaded: Main.
*Main sumTwoDice

interactive:1:0:
    No instance for (Show (Seed - (Int, Seed)))
  arising from a use of `print' at interactive:1:0-9
    Possible fix:
  add an instance declaration for (Show (Seed - (Int, Seed)))
    In a stmt of a 'do' expression: print it
*Main 


Can I employ a 'do' expression from the command line?

Also, can I now use functions () (=) and 'return' defined in the Prelude 
and still have this code work?

Michael

==

{-# LANGUAGE NoImplicitPrelude #-}

import Prelude hiding ((), (=), return)

type Seed = Int
type Random a = Seed - (a, Seed)

randomNext :: Seed - Seed
randomNext rand = if newRand  0 then newRand else newRand + 2147483647
    where newRand = 16807 * lo - 2836 * hi
  (hi,lo) = rand `divMod` 127773

rollDie :: Random Int
rollDie seed = ((seed `mod` 6) + 1, randomNext seed)

() :: Random a - Random b - Random b
() m n = \seed0 -
  let (result1, seed1) = m seed0
  (result2, seed2) = n seed1
  in (result2, seed2)

(=) :: Random a - (a - Random b) - Random b
(=) m g = \seed0 - 
  let (result1, seed1) = m seed0
  (result2, seed2) = (g result1) seed1
  in (result2, seed2)

return :: a - Random a
return x = \seed0 - (x, seed0)

sumTwoDice :: Random Int
sumTwoDice = rollDie = (\die1 - rollDie = (\die2 - return (die1 + die2)))


   ___
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


Re: [Haskell-cafe] random shuffle and random list partition

2009-03-20 Thread Manlio Perillo

Yitzchak Gale ha scritto:

Hi Manlio,

Manlio Perillo wrote:

For my Netflix Prize project I have implemented two reusable modules.
The first module implements a random shuffle on immutable lists...
The second module implements a function used to partition a list into n
sublists of random length.


[...]



As you point out, your partition algorithm is not fair.
Using your Random.Shuffle and a well-know trick
from combinatorics, you can easily get a fair
partitions function:

http://hpaste.org/fastcgi/hpaste.fcgi/view?id=2485#a2495



Someone added an alternative implementation:
http://hpaste.org/fastcgi/hpaste.fcgi/view?id=2485#a2497


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


Re: [Haskell-cafe] random shuffle and random list partition

2009-03-17 Thread Yitzchak Gale
Hi Manlio,

Manlio Perillo wrote:
 For my Netflix Prize project I have implemented two reusable modules.
 The first module implements a random shuffle on immutable lists...
 The second module implements a function used to partition a list into n
 sublists of random length.

Very nice!

 If someone is interested (and if Oleg give me permission), I can release
 them as a package on Hackage.

Please do that.

While I think Oleg's tree method is beautiful, in practice
it may be re-inventing the wheel. I haven't tested it, but
I doubt that this implementation is much better than
using the classical shuffle algorithm on an IntMap.
It's essentially the same tree inside. That's what I
usually use for this, and it works fine.

 In future I can add an implementation of the random
 shuffle algorithm on mutable arrays in the ST monad.

I've tried that in the past. Surprisingly, it wasn't faster
than using trees. Perhaps I did something wrong. Or
perhaps the difference only becomes apparent for
huge lists.

As you point out, your partition algorithm is not fair.
Using your Random.Shuffle and a well-know trick
from combinatorics, you can easily get a fair
partitions function:

http://hpaste.org/fastcgi/hpaste.fcgi/view?id=2485#a2495

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


Re: [Haskell-cafe] random shuffle and random list partition

2009-03-17 Thread Manlio Perillo

Yitzchak Gale ha scritto:

[...]
While I think Oleg's tree method is beautiful, in practice
it may be re-inventing the wheel. I haven't tested it, but
I doubt that this implementation is much better than
using the classical shuffle algorithm on an IntMap.


Do you have a working implementation?


It's essentially the same tree inside. That's what I
usually use for this, and it works fine.



Oleg implementation is rather efficient, but it requires a lot of memory 
for huge lists.


Here, as an example, two programs, one in Python and one in Haskell.
The default Python generator in Python use the Mersenne Twister, but 
returning floats number in the range [0, 1].



# Python version
from random import shuffle

n = 1000
m = 10
l = range(1, n + 1)

shuffle(l)
print l[:m]


-- Haskell version
module Main where

import Random.Shuffle
import System.Random.Mersenne.Pure64 (newPureMT)

n = 1000
m = 10
l = [1 .. n]

main = do
  gen - newPureMT
  print $ take m $ shuffle' l n gen



The Python version performances are:

real0m16.812s
user0m16.469s
sys 0m0.280s

150 MB memory usage


The Haskell version performances are:

real0m8.757s
user0m7.920s
sys 0m0.792s

800 MB memory usage



In future I can add an implementation of the random
shuffle algorithm on mutable arrays in the ST monad.


I've tried that in the past. Surprisingly, it wasn't faster
than using trees. Perhaps I did something wrong. Or
perhaps the difference only becomes apparent for
huge lists.



Can you try it on the list I have posted above?



As you point out, your partition algorithm is not fair.
Using your Random.Shuffle and a well-know trick
from combinatorics, you can easily get a fair
partitions function:

http://hpaste.org/fastcgi/hpaste.fcgi/view?id=2485#a2495



Thanks, this is very nice.
I have to run some benchmarks to see if it is efficient.


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


[Haskell-cafe] random shuffle and random list partition

2009-03-16 Thread Manlio Perillo

Hi.

For my Netflix Prize project I have implemented two reusable modules.
The first module implements a random shuffle on immutable lists.
It uses http://okmij.org/ftp/Haskell/perfect-shuffle.txt, with an 
additional wrapper function, having a more friendly interface.


The second module implements a function used to partition a list into n 
sublists of random length.



I have pasted the modules here:
http://hpaste.org/fastcgi/hpaste.fcgi/view?id=2483
http://hpaste.org/fastcgi/hpaste.fcgi/view?id=2485

If someone is interested (and if Oleg give me permission), I can release 
them as a package on Hackage.

I need to improve documentation, however.

In future I can add an implementation of the random shuffle algorithm on 
mutable arrays in the ST monad.





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


[Haskell-cafe] Random language humour

2008-12-16 Thread Andrew Coppin

http://www.aegisub.net/2008/12/if-programming-languages-were-religions.html

Seems pretty accurate, actually...

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


Re: [Haskell-cafe] Random question

2008-09-25 Thread Ariel J. Birnbaum
 And the one liner:
 (rand 1 10) = return . (\v - take v [1..10])

What about:
take $ rand 1 10 * pure [1..10]
(more readable IMHO).

One could even define:
f % x = f * pure x
and have
take $ rand 1 10 % [1..10]

Also, why not using getRandomR(1,10) instead?
take $ getRandomR (1,10) % [1..10] :: (MonadRandom m) = m Int
That way you separate the generation from the IO.

My getRandomR(0,3) % cents.
-- 
Ariel J. Birnbaum
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Random question

2008-09-25 Thread wren ng thornton

Iain Barnett wrote:

On 24 Sep 2008, at 10:13 pm, Evan Laforge wrote:
  For one approach, check
 out 'replicate' to make copies of something, and then 'sequence' to
 run them and return a list.


Thanks, I haven't found anything that explains 'sequence' well yet, but 
I'll keep looking.


Yet another explanation that might be helpful...

Consider a functor as a container (hence an |F a| value is an F-shaped 
container of values of type |a|). And remember that every monad is also 
a functor. We could imagine a value of type |F (G a)|, that is, a big 
F-shaped box containing many G-shaped boxes each containing a's. When G 
is a monad and not just a plain old functor, values of this sort are 
rather irksome to deal with because of the side effects.


But, if the functor F has certain properties[1] then it is possible to 
have a function that takes an |F (G a)| and distributes F over G to 
yield an analogous |G (F a)| value that preserves the internal 
structures of F and G. This function essentially runs a string through 
all the little |G a| beads in order to run them in some canonical 
sequence[2], it then collects their results and wraps them up in 
F-shaped boxes.


One of the places such a function is helpful is this. Consider if you 
have an |F a| value and you then fmap a monadic function |a - G b| over 
it. You now have an |F (G b)| but no simple way to get back what you 
really want: an |F b| value. If you have a function to distribute the 
functors then you can get a |G (F b)| which is a program that computes 
an |F b| subject to the state in G which it threads through each of 
those calls to that monadic function we fmapped over the |F a|.


The |sequence| function from the Prelude is exactly such a function, 
except that it fixes F to be [ ] and is only polymorphic over G and a. 
We could in principle have a more general function that doesn't force 
you to use lists. In fact, it exists as Data.Traversable.sequenceA which 
allows F to be any Data.Traversable structure and allows G to be any 
applicative functor (which are halfway between functors and monads).



[1] Namely being Data.Foldable and Data.Traversable so that we can, 
respectively, consume and reconstruct F containers. It's these 
mathematical properties we need, not the type classes themselves. 
Alternatively, if we can define for |f| a function |fsequence :: (Monad 
m) = f (m a) - m (f a)| then we can use that function to define 
instances for both of those type classes; this is what 
Data.Traversable's fmapDefault and foldMapDefault functions are about.


[2] What sequence this threading occurs in matches whatever order the 
folding function iterates over the elements in the F functor.


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Random question

2008-09-24 Thread Iain Barnett

Hi,

I have a function, that produces a random number between two given  
numbers


rand :: Int - Int - IO Int
rand low high = getStdRandom (randomR (low,high))


(Naively) I'd like to write something like

take (rand 1 10 ) [1..10]

and see [1,2,3,4] ... or anything but nasty type-error messages.



I'm reading about 6 tutorials on monads simultaneously but still  
can't crack this simple task, and won't pain you with all the  
permutations of code I've already tried. It's a lot, and it ain't  
pretty.


Would anyone be able to break away from C/C++ vs Haskell to help?  
Just a point in the right direction or a good doc to read, anything  
that helps will be much appreciated.



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


Re: [Haskell-cafe] Random question

2008-09-24 Thread Lev Walkin

Iain Barnett wrote:

Hi,

I have a function, that produces a random number between two given numbers

rand :: Int - Int - IO Int
rand low high = getStdRandom (randomR (low,high))


(Naively) I'd like to write something like

take (rand 1 10 ) [1..10]

and see [1,2,3,4] ... or anything but nasty type-error messages.


myTake :: IO [Int]
myTake = do
n - rand 1 10
take n [1..10]

or

myTake = rand 1 10 = \n - take n [1..10]

or

myTake = rand 1 10 = flip take [1..10]

I'm reading about 6 tutorials on monads simultaneously but still can't 
crack this simple task, and won't pain you with all the permutations of 
code I've already tried. It's a lot, and it ain't pretty.


Would anyone be able to break away from C/C++ vs Haskell to help? Just a 
point in the right direction or a good doc to read, anything that helps 
will be much appreciated.



Monad enlightenment happens after 7'th monad tutorial. Verified by me
and a few of my friends.

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


Re: [Haskell-cafe] Random question

2008-09-24 Thread Lev Walkin

forgot return, of course:

 myTake :: IO [Int]
 myTake = do
 n - rand 1 10
 return $ take n [1..10]


Lev Walkin wrote:

Iain Barnett wrote:

Hi,

I have a function, that produces a random number between two given 
numbers


rand :: Int - Int - IO Int
rand low high = getStdRandom (randomR (low,high))


(Naively) I'd like to write something like

take (rand 1 10 ) [1..10]

and see [1,2,3,4] ... or anything but nasty type-error messages.


myTake :: IO [Int]
myTake = do
n - rand 1 10
take n [1..10]

or

myTake = rand 1 10 = \n - take n [1..10]

or

myTake = rand 1 10 = flip take [1..10]

I'm reading about 6 tutorials on monads simultaneously but still can't 
crack this simple task, and won't pain you with all the permutations 
of code I've already tried. It's a lot, and it ain't pretty.


Would anyone be able to break away from C/C++ vs Haskell to help? Just 
a point in the right direction or a good doc to read, anything that 
helps will be much appreciated.



Monad enlightenment happens after 7'th monad tutorial. Verified by me
and a few of my friends.



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


Re: [Haskell-cafe] Random question

2008-09-24 Thread Evan Laforge
On Wed, Sep 24, 2008 at 2:03 PM, Iain Barnett [EMAIL PROTECTED] wrote:
 Hi,

 I have a function, that produces a random number between two given numbers

 rand :: Int - Int - IO Int
 rand low high = getStdRandom (randomR (low,high))


 (Naively) I'd like to write something like

 take (rand 1 10 ) [1..10]

So once you apply those two Ints, the type of the expression is no
longer a function, it's (IO Int), which is an action that produces and
Int.  So you want to do the action 10 times.  For one approach, check
out 'replicate' to make copies of something, and then 'sequence' to
run them and return a list.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Random question

2008-09-24 Thread John Van Enk
And the one liner:
(rand 1 10) = return . (\v - take v [1..10])

On Wed, Sep 24, 2008 at 5:10 PM, Lev Walkin [EMAIL PROTECTED] wrote:

 forgot return, of course:

  myTake :: IO [Int]
  myTake = do
  n - rand 1 10
  return $ take n [1..10]


 Lev Walkin wrote:

 Iain Barnett wrote:

 Hi,

 I have a function, that produces a random number between two given
 numbers

 rand :: Int - Int - IO Int
 rand low high = getStdRandom (randomR (low,high))


 (Naively) I'd like to write something like

 take (rand 1 10 ) [1..10]

 and see [1,2,3,4] ... or anything but nasty type-error messages.


 myTake :: IO [Int]
 myTake = do
n - rand 1 10
take n [1..10]

 or

 myTake = rand 1 10 = \n - take n [1..10]

 or

 myTake = rand 1 10 = flip take [1..10]

  I'm reading about 6 tutorials on monads simultaneously but still can't
 crack this simple task, and won't pain you with all the permutations of code
 I've already tried. It's a lot, and it ain't pretty.

 Would anyone be able to break away from C/C++ vs Haskell to help? Just a
 point in the right direction or a good doc to read, anything that helps will
 be much appreciated.



 Monad enlightenment happens after 7'th monad tutorial. Verified by me
 and a few of my friends.


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




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


Re: [Haskell-cafe] Random question

2008-09-24 Thread Iain Barnett
Your forgetfulness boosted my ego for a few seconds - I wasn't the  
only one! :)


Thanks very much, that's a big help.

Iain


On 24 Sep 2008, at 10:10 pm, Lev Walkin wrote:


forgot return, of course:

 myTake :: IO [Int]
 myTake = do
 n - rand 1 10
 return $ take n [1..10]


Lev Walkin wrote:

Iain Barnett wrote:

Hi,

I have a function, that produces a random number between two  
given numbers


rand :: Int - Int - IO Int
rand low high = getStdRandom (randomR (low,high))


(Naively) I'd like to write something like

take (rand 1 10 ) [1..10]

and see [1,2,3,4] ... or anything but nasty type-error messages.

myTake :: IO [Int]
myTake = do
n - rand 1 10
take n [1..10]
or
myTake = rand 1 10 = \n - take n [1..10]
or
myTake = rand 1 10 = flip take [1..10]
I'm reading about 6 tutorials on monads simultaneously but still  
can't crack this simple task, and won't pain you with all the  
permutations of code I've already tried. It's a lot, and it ain't  
pretty.


Would anyone be able to break away from C/C++ vs Haskell to help?  
Just a point in the right direction or a good doc to read,  
anything that helps will be much appreciated.

Monad enlightenment happens after 7'th monad tutorial. Verified by me
and a few of my friends.




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


Re: [Haskell-cafe] Random question

2008-09-24 Thread Henning Thielemann


On Wed, 24 Sep 2008, Iain Barnett wrote:


Hi,

I have a function, that produces a random number between two given numbers

rand :: Int - Int - IO Int
rand low high = getStdRandom (randomR (low,high))


If you only need arbitrary numbers, not really random ones, you should 
stay away from IO:

  http://www.haskell.org/haskellwiki/Humor/Erlk%C3%B6nig
  
http://www.haskell.org/haskellwiki/Haskell_programming_tips#Separate_IO_and_data_processing
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Random question

2008-09-24 Thread Iain Barnett

On 24 Sep 2008, at 10:13 pm, Evan Laforge wrote:

 For one approach, check
out 'replicate' to make copies of something, and then 'sequence' to
run them and return a list.



Thanks, I haven't found anything that explains 'sequence' well yet,  
but I'll keep looking.


On 24 Sep 2008, at 10:13 pm, John Van Enk wrote:

And the one liner:

(rand 1 10) = return . (\v - take v [1..10])



my last attempt before emailing was

(rand 1 10 ) = (\x - take x [1..10])

So close! :)

I can see now, with all the examples, why the return is needed, but  
not why the composition operator is. Something for me to look into.  
Thanks for the input.



On 24 Sep 2008, at 10:25 pm, Henning Thielemann wrote:


If you only need arbitrary numbers, not really random ones, you  
should stay away from IO:

  http://www.haskell.org/haskellwiki/Humor/Erlk%C3%B6nig
  http://www.haskell.org/haskellwiki/ 
Haskell_programming_tips#Separate_IO_and_data_processing



You're right, arbritary will be fine. It's relatively easy to get  
random numbers in other languages so I just started there, but while  
researching I had seen a few people lament the tying up of IO with  
rands, but I couldn't understand some of the other solutions  
presented. Thanks for the links, I'll give them a read.





On Wed, Sep 24, 2008 at 5:10 PM, Lev Walkin [EMAIL PROTECTED] wrote:
forgot return, of course:


 myTake :: IO [Int]
 myTake = do
 n - rand 1 10
 return $ take n [1..10]



Lev Walkin wrote:
Iain Barnett wrote:
Hi,

I have a function, that produces a random number between two given  
numbers


rand :: Int - Int - IO Int
rand low high = getStdRandom (randomR (low,high))


(Naively) I'd like to write something like

take (rand 1 10 ) [1..10]

and see [1,2,3,4] ... or anything but nasty type-error messages.

myTake :: IO [Int]
myTake = do
   n - rand 1 10
   take n [1..10]

or

myTake = rand 1 10 = \n - take n [1..10]

or

myTake = rand 1 10 = flip take [1..10]

I'm reading about 6 tutorials on monads simultaneously but still  
can't crack this simple task, and won't pain you with all the  
permutations of code I've already tried. It's a lot, and it ain't  
pretty.


Would anyone be able to break away from C/C++ vs Haskell to help?  
Just a point in the right direction or a good doc to read, anything  
that helps will be much appreciated.



Monad enlightenment happens after 7'th monad tutorial. Verified by me
and a few of my friends.


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



--
/jve


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


Re: [Haskell-cafe] Random question

2008-09-24 Thread Henning Thielemann


On Wed, 24 Sep 2008, Iain Barnett wrote:


On 24 Sep 2008, at 10:13 pm, Evan Laforge wrote:

For one approach, check
out 'replicate' to make copies of something, and then 'sequence' to
run them and return a list.



Thanks, I haven't found anything that explains 'sequence' well yet, but I'll 
keep looking.


... and then replicateM

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


Re: [Haskell-cafe] Random question

2008-09-24 Thread Jonathan Cast
On Wed, 2008-09-24 at 22:44 +0100, Iain Barnett wrote:
 On 24 Sep 2008, at 10:13 pm, Evan Laforge wrote:
   For one approach, check
  out 'replicate' to make copies of something, and then 'sequence' to
  run them and return a list.

 Thanks, I haven't found anything that explains 'sequence' well yet,
 but I'll keep looking.

sequence is one of your more general-purpose loop functions in Haskell.
Frequently, the number of passes in a loop and the job of each pass are
fixed before-hand.  Standard lazy-evaluation constructs like iterate,
replicate, and map make it easy to produce a list of the passes you want
to use.  (This is the data-structure-as-control-construct pattern).
sequence then supplies the last step: it takes a list (in the principle
examples, a list of passes through some loop) and returns a loop that
goes through and executes all the passes.  In sequence, ironically
enough.

 On 24 Sep 2008, at 10:13 pm, John Van Enk wrote:
  And the one liner:

  (rand 1 10) = return . (\v - take v [1..10])

 my last attempt before emailing was

 (rand 1 10 ) = (\x - take x [1..10])

 So close! :)

 I can see now, with all the examples, why the return is needed, but
 not why the composition operator is. Something for me to look into.

Btw: the composition operator isn't needed.  You can inline it into your
example and get

(rand 1 10) = (\ v - return ((\ v - take v [1..10]) v))

(which is equivalent to the clearer

(rand 1 10) = (\ v - return (take v [1..10]))

by a step closely related to inlining (beta-contraction, to be specific)).

I don't know why composition was used in this case.  Using the version

   (\ v - take v [1..10]) $ (rand 1 10)

and using the definition

f $ a = a = return . f

gives rise to it.

jcc



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


Re: [Haskell-cafe] Random question

2008-09-24 Thread Brandon S. Allbery KF8NH

On 2008 Sep 24, at 17:44, Iain Barnett wrote:

On 24 Sep 2008, at 10:13 pm, Evan Laforge wrote:

 For one approach, check
out 'replicate' to make copies of something, and then 'sequence' to
run them and return a list.


Thanks, I haven't found anything that explains 'sequence' well yet,  
but I'll keep looking.


sequence turns a list of monadic values into a monadic list of values,  
i.e. [m a] becomes m [a].  In IO, this is [IO a] - IO [a].  This lets  
you do something like replicate an I/O action, then turn the list of I/ 
O actions into a single I/O action on a list.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


[Haskell-cafe] random colors, stack space overflow, mersenne and mersenne.pure64

2008-09-12 Thread Cetin Sert
Hi,

The following piece of code runs just fine, if I say:

instance Random RGB where
  random  = color
  randomR = colorR

instead of:

instance Random RGB where
  random  = color2
  randomR = colorR

When I use random  = color2 I encounter a stack space overflow:

[EMAIL PROTECTED]:~/lab/test/colors ./var2 +RTS -K3000
Stack space overflow: current size 3000 bytes.
Use `+RTS -Ksize' to increase it.

I think I'm doing something wrong with the definition of colorR.

Can anyone explain me what's wrong?

import GHC.Word
import Data.Word
import System.Random
import System.Random.Mersenne.Pure64

type RGB = (Int,Int,Int)

instance Bounded RGB where
  minBound = minRGB
  maxBound = maxRGB

minRGB = (0  ,0  ,0  )
maxRGB = (255,255,255)

instance Random RGB where
  random  = color2
  randomR = colorR

color2 :: RandomGen g ⇒ g → (RGB,g)
color2 = colorR (minRGB,maxRGB)

color :: RandomGen g ⇒ g → (RGB,g)
color s0 = ((r,g,b),s3)
  where
(r,s1) = q s0
(g,s2) = q s1
(b,s3) = q s2
q = randomR (0,255)

colorR :: RandomGen g ⇒ (RGB,RGB) → g → (RGB,g)
colorR ((a,b,c),(x,y,z)) s0 = ((r,g,b),s3)
  where
(r,s1) = q (a,x) s0
(g,s2) = q (b,y) s1
(b,s3) = q (c,z) s2
q = randomR

main :: IO ()
main = do
  mt ← newPureMT
  let cs = randoms mt :: [RGB]
  print cs

--

This one also just works fine:

import Data.Word
import System.Random.Mersenne

type RGB = (Word8,Word8,Word8)

instance MTRandom RGB where
  random m = do
r ← random m :: IO Word8
g ← random m :: IO Word8
b ← random m :: IO Word8
return (r,g,b)

main :: IO ()
main = do
  g  ← newMTGen Nothing
  cs ← randoms g :: IO [RGB]
  print cs

but I really need the range constraints colorR might provide me and would
greatly appreciate any help to understand/solve the issue.

Best Regards,
Cetin

P/s:
uname -a
Linux linux-d312 2.6.25.16-0.1-default #1 SMP 2008-08-21 00:34:25 +0200
x86_64 x86_64 x86_64 GNU/Linux
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] random colors, stack space overflow, mersenne and mersenne.pure64

2008-09-12 Thread Don Stewart
cetin.sert:
  random  = color2
  randomR = colorR
 
color2 :: RandomGen g .$BM.(B g .$B*.(B (RGB,g)
color2 = colorR (minRGB,maxRGB)
 
color :: RandomGen g .$BM.(B g .$B*.(B (RGB,g)
color s0 = ((r,g,b),s3)
  where

^^

There's some corruption in this text. Could you post the file somewhere?

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


Re: [Haskell-cafe] random colors, stack space overflow, mersenne and mersenne.pure64

2008-09-12 Thread Cetin Sert
Oh, hi *^o^*

mersenne.pure64
http://sert.homedns.org/lab/colors/var2.hs

mersenne
http://sert.homedns.org/lab/colors/var.hs

the problem seems to be with the definition of colorR in var2.hs

CS

2008/9/13 Don Stewart [EMAIL PROTECTED]

 cetin.sert:
   random  = color2
   randomR = colorR
 
 color2 :: RandomGen g .$BM.(B g .$B*.(B (RGB,g)
 color2 = colorR (minRGB,maxRGB)
 
 color :: RandomGen g .$BM.(B g .$B*.(B (RGB,g)
 color s0 = ((r,g,b),s3)
   where

 ^^

 There's some corruption in this text. Could you post the file somewhere?

 -- Don

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


Re: [Haskell-cafe] random colors, stack space overflow, mersenne and mersenne.pure64

2008-09-12 Thread Don Stewart
Oh, you've got unicode source. What's the flag to get this to actually
compile? (Note to readers, using extensions , you should always include
the LANGUAGE pragmas required to build the file when asking for help :)

How are you compiling this?

-- Don

cetin.sert:
Oh, hi *^o^*
 
mersenne.pure64
[1]http://sert.homedns.org/lab/colors/var2.hs
 
mersenne
[2]http://sert.homedns.org/lab/colors/var.hs
 
the problem seems to be with the definition of colorR in var2.hs
 
CS
 
2008/9/13 Don Stewart [EMAIL PROTECTED]
 
  cetin.sert:
random  = color2
randomR = colorR
  
  color2 :: RandomGen g .$BM.(B g .$B*.(B (RGB,g)
  color2 = colorR (minRGB,maxRGB)
  
  color :: RandomGen g .$BM.(B g .$B*.(B (RGB,g)
  color s0 = ((r,g,b),s3)
where
 
  ^^
 
  There's some corruption in this text. Could you post the file somewhere?
  -- Don
 
 References
 
Visible links
1. http://sert.homedns.org/lab/colors/var2.hs
2. http://sert.homedns.org/lab/colors/var.hs
3. mailto:[EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] random colors, stack space overflow, mersenne and mersenne.pure64

2008-09-12 Thread Bertram Felgenhauer
Cetin Sert wrote:
[snip]
 colorR :: RandomGen g ⇒ (RGB,RGB) → g → (RGB,g)
 colorR ((a,b,c),(x,y,z)) s0 = ((r,g,b),s3)
   where
 (r,s1) = q (a,x) s0
 (g,s2) = q (b,y) s1
 (b,s3) = q (c,z) s2
 q = randomR

Look closely at how you use the variable 'b'.

HTH,

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


Re: [Haskell-cafe] random colors, stack space overflow, mersenne and mersenne.pure64

2008-09-12 Thread Cetin Sert
Oh, sorry... ^__^

ghc -fglasgow-exts -O2 --make var
ghc -fglasgow-exts -O2 --make var2

I've not used pragmas in any source file o_O so far... should go fix that
sometime. Thanks for reminding...

Using ghc 6.8.3, mersenne-random-0.1.3 and mersenne-random-pure64-0.2.0.2.
(Cause I could not find out how to check things out with darcs from hackage
o__O google was not very helpful there so I used the latest tar packages.)

@don: sorry I sent my reply twice only to you and then to the list and
you... it's because of gmail... I'll be very careful not to repeat my
mistake.


2008/9/13 Don Stewart [EMAIL PROTECTED]

 Oh, you've got unicode source. What's the flag to get this to actually
 compile? (Note to readers, using extensions , you should always include
 the LANGUAGE pragmas required to build the file when asking for help :)

 How are you compiling this?

 -- Don

 cetin.sert:
 Oh, hi *^o^*
 
 mersenne.pure64
 [1]http://sert.homedns.org/lab/colors/var2.hs
 
 mersenne
 [2]http://sert.homedns.org/lab/colors/var.hs
 
 the problem seems to be with the definition of colorR in var2.hs
 
 CS
 
 2008/9/13 Don Stewart [EMAIL PROTECTED]
 
   cetin.sert:
 random  = color2
 randomR = colorR
   
   color2 :: RandomGen g .$BM.(B g .$B*.(B (RGB,g)
   color2 = colorR (minRGB,maxRGB)
   
   color :: RandomGen g .$BM.(B g .$B*.(B (RGB,g)
   color s0 = ((r,g,b),s3)
 where
 
   ^^
 
   There's some corruption in this text. Could you post the file
 somewhere?
   -- Don
 
  References
 
 Visible links
 1. http://sert.homedns.org/lab/colors/var2.hs
 2. http://sert.homedns.org/lab/colors/var.hs
 3. mailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] random colors, stack space overflow, mersenne and mersenne.pure64

2008-09-12 Thread Don Stewart
bertram.felgenhauer:
 Cetin Sert wrote:
 [snip]
  colorR :: RandomGen g ⇒ (RGB,RGB) → g → (RGB,g)
  colorR ((a,b,c),(x,y,z)) s0 = ((r,g,b),s3)
where
  (r,s1) = q (a,x) s0
  (g,s2) = q (b,y) s1
  (b,s3) = q (c,z) s2
  q = randomR
 
 Look closely at how you use the variable 'b'.

:-) fast eyes.

Btw, Cetin, this is good practice, along with -funbox-strict-fields:

data RGB = RGB !Int !Int !Int
deriving Show

Much better code than using a lazy triple.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] random colors, stack space overflow, mersenne and mersenne.pure64

2008-09-12 Thread Cetin Sert
Oh thank you both *^o^*... now works like a charm again.

Btw, Cetin, this is good practice, along with -funbox-strict-fields:

   data RGB = RGB !Int !Int !Int
   deriving Show

Much better code than using a lazy triple.

Where can I read more of such good practice? Looking forward to Real World
Haskell to read lots of code, hope it'll help lots of people interested in
learning haskell. (Will be released around Christmas here in Germany, I
think.)

CS

2008/9/13 Don Stewart [EMAIL PROTECTED]

 bertram.felgenhauer:
  Cetin Sert wrote:
  [snip]
   colorR :: RandomGen g ⇒ (RGB,RGB) → g → (RGB,g)
   colorR ((a,b,c),(x,y,z)) s0 = ((r,g,b),s3)
 where
   (r,s1) = q (a,x) s0
   (g,s2) = q (b,y) s1
   (b,s3) = q (c,z) s2
   q = randomR
 
  Look closely at how you use the variable 'b'.

 :-) fast eyes.

 Btw, Cetin, this is good practice, along with -funbox-strict-fields:

data RGB = RGB !Int !Int !Int
deriving Show

 Much better code than using a lazy triple.
 ___
 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


Re: [Haskell-cafe] random colors, stack space overflow, mersenne and mersenne.pure64

2008-09-12 Thread Don Stewart
cetin.sert:
Where can I read more of such good practice? Looking forward to Real World
Haskell to read lots of code, hope it'll help lots of people interested in
learning haskell. (Will be released around Christmas here in Germany, I
think.)

Yeah, that's right. November some time.

There's a chapter that talks about performance and data structures,

http://book.realworldhaskell.org/read/profiling-and-optimization.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] random colors, stack space overflow, mersenne and mersenne.pure64

2008-09-12 Thread Brandon S. Allbery KF8NH

On 2008 Sep 12, at 21:57, Don Stewart wrote:

cetin.sert:

random  = color2
randomR = colorR

  color2 :: RandomGen g .$BM.(B g .$B*.(B (RGB,g)
  color2 = colorR (minRGB,maxRGB)

  color :: RandomGen g .$BM.(B g .$B*.(B (RGB,g)
  color s0 = ((r,g,b),s3)
where


There's some corruption in this text. Could you post the file  
somewhere?


It's not corrupt; he used UTF-8 symbols.  It shows up properly in  
Mail.app but doesn't quote right (admittedly I force plaintext).


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] random colors, stack space overflow, mersenne and mersenne.pure64

2008-09-12 Thread Cetin Sert
main :: IO ()
main = do
  as - getArgs
  mt - newPureMT
  let colors = randomRs (lo,hi) mt :: [RGB]
  print $ zip tx cs
  where
lo = read $ as !! 0
hi = read $ as !! 1
tx =as !! 2

Why is as not visible in the where block?

2008/9/13 Brandon S. Allbery KF8NH [EMAIL PROTECTED]

 On 2008 Sep 12, at 21:57, Don Stewart wrote:

 cetin.sert:

random  = color2
randomR = colorR

  color2 :: RandomGen g .$BM.(B g .$B*.(B (RGB,g)
  color2 = colorR (minRGB,maxRGB)

  color :: RandomGen g .$BM.(B g .$B*.(B (RGB,g)
  color s0 = ((r,g,b),s3)
where


 There's some corruption in this text. Could you post the file somewhere?


 It's not corrupt; he used UTF-8 symbols.  It shows up properly in Mail.app
 but doesn't quote right (admittedly I force plaintext).

 --
 brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
 system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
 electrical and computer engineering, carnegie mellon universityKF8NH



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


Re: [Haskell-cafe] random colors, stack space overflow, mersenne and mersenne.pure64

2008-09-12 Thread Don Stewart
cetin.sert:

main :: IO ()
main = do
  as - getArgs
  mt - newPureMT
  let colors = randomRs (lo,hi) mt :: [RGB]
  print $ zip tx cs
  where
lo = read $ as !! 0
hi = read $ as !! 1
tx =as !! 2
Why is as not visible in the where block?

Same as:

 main =
   let
 lo = read $ as !! 0
 hi = read $ as !! 1
 tx =as !! 2
   in do
 as - getArgs
 mt - newPureMT
 let colors = randomRs (lo,hi) mt :: [RGB]
 print $ zip tx cs

If that helps think about when things are bound.

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


Re: [Haskell-cafe] random colors, stack space overflow, mersenne and mersenne.pure64

2008-09-12 Thread Jason Dagit
On Fri, Sep 12, 2008 at 8:53 PM, Don Stewart [EMAIL PROTECTED] wrote:
 cetin.sert:

main :: IO ()
main = do
  as - getArgs
  mt - newPureMT
  let colors = randomRs (lo,hi) mt :: [RGB]
  print $ zip tx cs
  where
lo = read $ as !! 0
hi = read $ as !! 1
tx =as !! 2
Why is as not visible in the where block?

 Same as:

 main =
   let
 lo = read $ as !! 0
 hi = read $ as !! 1
 tx =as !! 2
   in do
 as - getArgs
 mt - newPureMT
 let colors = randomRs (lo,hi) mt :: [RGB]
 print $ zip tx cs

 If that helps think about when things are bound.

And you probably want this rewrite (untested):
main :: IO ()
main = do
  as - getArgs
  let lo = read $ as !! 0
   hi = read $ as !! 1
   tx = as !! 2
  mt - newPureMT
  let colors = randomRs (lo,hi) mt :: [RGB]
  print $ zip tx cs

My indentation may be a bit off as I didn't use a fixed width font to type it.

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


[Haskell-cafe] Random numbers and splitting

2008-05-18 Thread Lauri Oksanen
Hi,

Does there exists any random number generator in Haskell that is suitable
for doing heavy simulations and that can be splitted?
At least there exists some c implementations of such generators, see
http://www.iro.umontreal.ca/~lecuyer/myftp/papers/streams00.pdf

Also some new theory for Mersenne Twister and its relatives exists, see
http://www.iro.umontreal.ca/~lecuyer/myftp/papers/jumpf2.pdf
http://www.iro.umontreal.ca/~lecuyer/myftp/papers/jumpmt.pdf

I'm trying to implement Metropolis algorithm with lazy mutations and a state
space that is infinite dimensional in theory (although, of course, not in
practice).
Without good splitting I'm forced to write as ugly code as with non-lazy
language.

Thanks in advance,
Lauri
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Random numbers / monads - beginner question

2008-05-08 Thread Madoc

Hello,


I am just learning Haskell. Now, I encountered something that I cannot solve
by myself. Your advice will be greatly appreciated.


Given a list of numbers, I want to modify each of those numbers by adding a
random offset. However, each such modified number shall stay within certain
bounds, given by the integers minValue and maxValue. After that, I want to
continue computation with the resulting list of type [Int]. But for
demonstration, I made a program that just prints out the list:


import IO; import Random

minValue = 0::Int
maxValue = 1000::Int

normalize a | a  minValue = minValue
| a  maxValue = maxValue
| otherwise = a

modify a = do
  offset - randomRIO(-100::Int, 100)
  return(normalize(a + offset))

main = putStrLn $ show $ map (modify) [0, 200, 400, 600, 800, 1000]


This program will not compile. GHC complains:


test.hs:14:18:
No instance for (Show (IO Int))
  arising from a use of `show' at test.hs:14:18-21
Possible fix: add an instance declaration for (Show (IO Int))
In the first argument of `($)', namely `show'
In the second argument of `($)', namely
`show $ map (modify) [0, 200, 400, 600, ]'
In the expression:
  putStrLn $ show $ map (modify) [0, 200, 400, 600, ]


I understand that the result of the modify function is not an Int, as I
would like to have it, but instead IO Int, and that cannot be applied to
show. (I also did not quite understand why I need those brackets around the
return value of the modify value. It won't compile if I leave them out, but
I can accept that for now.)


I also figured out how to generate a modified list of type [IO Int] and of
type IO [Int]. However, I could not find out how to completely get rid of
the IO monad and just get a mofied list of type [Int], which is what I
really want.


Please, do You have any advice for me? I tried for some hours, and now I am
really angry at that IO monad that sticks to my pretty integers like glue!


Also, any comment on the programming style and how I could achive my goals
easier would be appreciated. (I left out comments and function types for the
sake of brevity.)


Thanks a lot in advance.

Madoc.
-- 
View this message in context: 
http://www.nabble.com/Random-numbers---monads---beginner-question-tp17124380p17124380.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Random numbers / monads - beginner question

2008-05-08 Thread Claude Heiland-Allen

Madoc wrote:

Given a list of numbers, I want to modify each of those numbers by adding a
random offset. However, each such modified number shall stay within certain
bounds, given by the integers minValue and maxValue. After that, I want to
continue computation with the resulting list of type [Int].


Personally, I'd do something like this, isolate the IO code outside the 
algorithm to keep the algorithm pure:



modify' :: Int - Int - Int
modify' offset a =  normalize (a + offset)

generateInfiniteListOfRandomNumbers :: IO [Int]
-- implementation left as an exercise

main = do
  randomNumbers - generateInfiniteListOfRandomNumbers
  print $ zipWith modify' randomNumbers [0, 200, 400, 600, 800, 1000]


hope this helps,


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


Re: [Haskell-cafe] Random numbers / monads - beginner question

2008-05-08 Thread Thomas Dinsdale-Young
 Madoc wrote:

Given a list of numbers, I want to modify each of those numbers by adding a
random offset. However, each such modified number shall stay within certain
bounds, given by the integers minValue and maxValue. After that, I want to
continue computation with the resulting list of type [Int].


Personally, I'd do something like this, isolate the IO code outside the
algorithm to keep the algorithm pure:


modify' :: Int - Int - Int
modify' offset a =  normalize (a + offset)

generateInfiniteListOfRandomNumbers :: IO [Int]
-- implementation left as an exercise

main = do
  randomNumbers - generateInfiniteListOfRandomNumbers
  print $ zipWith modify' randomNumbers [0, 200, 400, 600, 800, 1000]

I may be wrong, but generateInfiniteListOfRandomNumbers won't terminate and
I think it has to before the next IO action occurs.  (Laziness is great, but
I don't think you can really do lazy IO like that.)

Instead of map :: (a - b) - [a] - [b], I think you are looking for mapM
:: Monad m = (a - m b) - [a] - m [b].
* *
* *Hope this helps,
Thomas


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


Re: [Haskell-cafe] Random numbers / monads - beginner question

2008-05-08 Thread Brent Yorgey
2008/5/8 Thomas Dinsdale-Young [EMAIL PROTECTED]:

 Madoc wrote:

 Given a list of numbers, I want to modify each of those numbers by adding a

 random offset. However, each such modified number shall stay within certain

 bounds, given by the integers minValue and maxValue. After that, I want to
 continue computation with the resulting list of type [Int].


 Personally, I'd do something like this, isolate the IO code outside the
 algorithm to keep the algorithm pure:


 modify' :: Int - Int - Int
 modify' offset a =  normalize (a + offset)

 generateInfiniteListOfRandomNumbers :: IO [Int]
 -- implementation left as an exercise

 main = do
   randomNumbers - generateInfiniteListOfRandomNumbers
   print $ zipWith modify' randomNumbers [0, 200, 400, 600, 800, 1000]

 I may be wrong, but generateInfiniteListOfRandomNumbers won't terminate
 and I think it has to before the next IO action occurs.  (Laziness is great,
 but I don't think you can really do lazy IO like that.)


Sure it will.  You're right that you cannot do lazy IO like this, but no
lazy IO needs to happen here.  The key is that an IO action does not have to
be performed in order to generate each element of the list -- one IO action
is performed at the beginning to produce a random generator, and then this
generator is used (functionally and purely) to produce a lazy infinite list
of pseudorandom numbers.  For example see the 'newStdGen' and 'randoms'
functions from System.Random.

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


Re: [Haskell-cafe] Random numbers / monads - beginner question

2008-05-08 Thread Henning Thielemann


On Thu, 8 May 2008, Madoc wrote:


Given a list of numbers, I want to modify each of those numbers by adding a
random offset. However, each such modified number shall stay within certain
bounds, given by the integers minValue and maxValue. After that, I want to
continue computation with the resulting list of type [Int]. But for
demonstration, I made a program that just prints out the list:


import IO; import Random

minValue = 0::Int
maxValue = 1000::Int

normalize a | a  minValue = minValue
   | a  maxValue = maxValue
   | otherwise = a



normalize = min maxValue . max minValue



modify a = do
 offset - randomRIO(-100::Int, 100)
 return(normalize(a + offset))



Stay away from IO whereever possible, use randomR instead.
Say
  map normalize (zipWith (+) (randomRs (-100::Int, 100)) x)

http://haskell.org/haskellwiki/Humor/Erlkönig
http://haskell.org/haskellwiki/Things_to_avoid#Separate_IO_and_data_processing___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Random numbers / monads - beginner question

2008-05-08 Thread Sebastian Sylvan
2008/5/8 Madoc [EMAIL PROTECTED]:

 Hello,

 I am just learning Haskell. Now, I encountered something that I cannot
 solve by myself. Your advice will be greatly appreciated.

 Given a list of numbers, I want to modify each of those numbers by adding a
 random offset. However, each such modified number shall stay within certain
 bounds, given by the integers minValue and maxValue. After that, I want to
 continue computation with the resulting list of type [Int]. But for
 demonstration, I made a program that just prints out the list:

 import IO; import Random

 minValue = 0::Int
 maxValue = 1000::Int

 normalize a | a  minValue = minValue
 | a  maxValue = maxValue
 | otherwise = a

 modify a = do
   offset - randomRIO(-100::Int, 100)
   return(normalize(a + offset))

 main = putStrLn $ show $ map (modify) [0, 200, 400, 600, 800, 1000]

 This program will not compile. GHC complains:

 test.hs:14:18:
 No instance for (Show (IO Int))
   arising from a use of `show' at test.hs:14:18-21
 Possible fix: add an instance declaration for (Show (IO Int))
 In the first argument of `($)', namely `show'
 In the second argument of `($)', namely
 `show $ map (modify) [0, 200, 400, 600, ]'
 In the expression:
   putStrLn $ show $ map (modify) [0, 200, 400, 600, ]

 I understand that the result of the modify function is not an Int, as I
 would like to have it, but instead IO Int, and that cannot be applied to
 show. (I also did not quite understand why I need those brackets around
 the return value of the modify value. It won't compile if I leave them
 out, but I can accept that for now.)

 I also figured out how to generate a modified list of type [IO Int] and of
 type IO [Int]. However, I could not find out how to completely get rid of
 the IO monad and just get a mofied list of type [Int], which is what I
 really want.

 Please, do You have any advice for me? I tried for some hours, and now I am
 really angry at that IO monad that sticks to my pretty integers like glue!

 Also, any comment on the programming style and how I could achive my goals
 easier would be appreciated. (I left out comments and function types for the
 sake of brevity.)


You should use newStdGen to produce a random generator, then randomRs to
produce a list of random numbers (without using IO!).

But if you really want this version with IO interspersed through the
algorithm to work, then something like this should do it (uncompiled):

main = do
 xs - mapM  (modify) [0, 200, 400, 600, 800, 1000]
 putStrLn $ show $ xs

The only way to get rid of the IO monad, is to use - to bind it to a
value from within the IO monad.



-- 
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Random numbers / monads - beginner question

2008-05-08 Thread Dan Weston

Henning Thielemann wrote:


On Thu, 8 May 2008, Madoc wrote:


minValue = 0::Int
maxValue = 1000::Int

normalize a | a  minValue = minValue
   | a  maxValue = maxValue
   | otherwise = a



normalize' = min maxValue . max minValue


There is a curiosity here. The functions normalize and normalize' are 
extensionally equal only because minValue = maxValue, but intensionally 
different. The intensional equivalent is to reverse order of composition:


normalize'' = max minValue . min maxValue

which remains equal to to normalize whatever the values of minValue and 
maxValue.


That the order of composition (or of guarded expressions) matters 
conditionally base on its parameters is reason enough for the original 
poster to decide what the right answer should be if maxValue  
minValue. These corner cases are often where future bugs lie dormant. My 
choice would be:


normalize'''= max trueMin . min trueMax
  where trueMin = min minValue maxValue
trueMax = max minValue maxValue

Now the function makes no assumptions about external values. This is no 
less efficient than before, since trueMin and trueMax are CAFs evaluated 
only once.



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


[Haskell-cafe] Random Monad

2008-03-24 Thread Matthew Pocock
Hi,

Who currently maintains the Random monad code? I have some patches to 
contribute.

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


Re: [Haskell-cafe] Random Monad

2008-03-24 Thread Henning Thielemann


On Mon, 24 Mar 2008, Matthew Pocock wrote:


Who currently maintains the Random monad code? I have some patches to
contribute.


Do you refer to the code on the wiki?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Random Monad

2008-03-24 Thread Matthew Pocock
On Monday 24 March 2008, Henning Thielemann wrote:
 On Mon, 24 Mar 2008, Matthew Pocock wrote:
  Who currently maintains the Random monad code? I have some patches to
  contribute.

 Do you refer to the code on the wiki?

No, to the code in darcs at http://code.haskell.org/monadrandom

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


Re: [Haskell-cafe] Random Monad

2008-03-24 Thread Bryan O'Sullivan
Matthew Pocock wrote:
 On Monday 24 March 2008, Henning Thielemann wrote:
 On Mon, 24 Mar 2008, Matthew Pocock wrote:
 Who currently maintains the Random monad code? I have some patches to
 contribute.
 Do you refer to the code on the wiki?
 
 No, to the code in darcs at http://code.haskell.org/monadrandom

I believe it's Cale's baby.

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


[Haskell-cafe] Random ramble

2007-05-28 Thread Andrew Coppin

[You may want to just hit delete now? ;-) ]


I don't know where everybody else is, but where I live, we have various 
science programs on TV from time to time. (Horizon being a fairly 
regular one.) They grab a bunch of eggheads, and try to get them to 
explain (in soundbites) some topic or other. Sometimes it's string 
theory, or quantum dynamics, or chaos theory, or something like that. 
(And sometimes it's economics - and then I change channel.) Usually the 
producers go to great lengths to make the subject seem interesting - 
that is, try to be as over-dramatic as possible. Often accompanied with 
copious computer graphics, which mainly just look pretty.


Anyway, I was sitting here thinking to myself hey, what if they got a 
bunch of people to talk about Haskell? (That's *one* way to get 
publicity...!)


I don't know how many of you are as neurotically familiar with The 
Matrix as I am, but... I found myself visualising that scene from about 
mid-way through the film.


Morpheus: This may feel... a little weird.

[6 inch metal plug injected into the back of Neo's skull]

Neo: AAARRGH!!

[They turn on the computer.]

[Neo finds himself floating in a sea of lambda functions, higher-kinded 
class instances and parametric polymorphism.]


...and then I find myself thinking of http://xkcd.com/c224.html



Erm... OK, I'll go sit in the corner and be quiet now.

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


[Haskell-cafe] Random idea

2007-05-20 Thread Andrew Coppin

Greetings.

I was thinking... we already have Lambdabot sitting in an IRC channel. 
How hard would it be to mangle Lambdabot to the point where it works 
over HTTP? You know - so you could type some Haskell into a form on a 
web page, hit [submit], and get the result sent back to you? (Again, 
assuming it can be computed in a sane amount of time/space, and 
truncated to some reasonable textual length.)


I think it might be kinda neat to have such a thing linked from the 
Haskell.org homepage. You know, sort of hey, wanna try Haskell without 
installing any stuff? Click here!


...on the other hand, maybe I'm just strange... :-$

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


Re: [Haskell-cafe] Random idea

2007-05-20 Thread Rodrigo Queiro

http://lambdabot.codersbase.com/

Still, an interface like the fancy Web 2.0 ones that Ruby has could be nice.

On 20/05/07, Andrew Coppin [EMAIL PROTECTED] wrote:


Greetings.

I was thinking... we already have Lambdabot sitting in an IRC channel.
How hard would it be to mangle Lambdabot to the point where it works
over HTTP? You know - so you could type some Haskell into a form on a
web page, hit [submit], and get the result sent back to you? (Again,
assuming it can be computed in a sane amount of time/space, and
truncated to some reasonable textual length.)

I think it might be kinda neat to have such a thing linked from the
Haskell.org homepage. You know, sort of hey, wanna try Haskell without
installing any stuff? Click here!

...on the other hand, maybe I'm just strange... :-$

___
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


Re: [Haskell-cafe] Random idea

2007-05-20 Thread Donald Bruce Stewart
andrewcoppin:
 Greetings.
 
 I was thinking... we already have Lambdabot sitting in an IRC channel. 
 How hard would it be to mangle Lambdabot to the point where it works 
 over HTTP? You know - so you could type some Haskell into a form on a 

Lambdabot web server is here:

http://lambdabot.codersbase.com/

Thought we never announced it off channel, and it hasn't been updated in
a while.

 web page, hit [submit], and get the result sent back to you? (Again, 
 assuming it can be computed in a sane amount of time/space, and 
 truncated to some reasonable textual length.)
 
 I think it might be kinda neat to have such a thing linked from the 
 Haskell.org homepage. You know, sort of hey, wanna try Haskell without 
 installing any stuff? Click here!

yeah, we've had this in mind as a base for an online haskell
quiz/tutorial series. Perhaps someone would like to make this happen :-)

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


Re: [Haskell-cafe] Random idea

2007-05-20 Thread Andrew Coppin

Rodrigo Queiro wrote:

http://lambdabot.codersbase.com/


OMG! That was really fast... o_O

Still, an interface like the fancy Web 2.0 ones that Ruby has could be 
nice.


I have no idea what Web 2.0 is, but from what I hear it's overrated...

Well, a web interface potentially provides for nicer output formatting 
than the plain text of an IRC channel. Could be interesting to actually 
make use of it...


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


Re: [Haskell-cafe] Random idea

2007-05-20 Thread Andrew Coppin

Rodrigo Queiro wrote:

http://lambdabot.codersbase.com/


Wait, what the hell...?


 1 + 1
/usr/lib/ghc-6.4.2/package.conf: openFile: does not exist (No such file 
or directory)


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


Re: [Haskell-cafe] Random idea

2007-05-20 Thread Philipp Volgger


For me it gives:
 1 + 1
Maybe you meant: . v

But the rest of the commands seems working ;)



Andrew Coppin schrieb:

Rodrigo Queiro wrote:

http://lambdabot.codersbase.com/


Wait, what the hell...?


 1 + 1
/usr/lib/ghc-6.4.2/package.conf: openFile: does not exist (No such 
file or directory)


___
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


Re: [Haskell-cafe] Random idea

2007-05-20 Thread Jason Dagit

On 5/20/07, Andrew Coppin [EMAIL PROTECTED] wrote:

Rodrigo Queiro wrote:
 http://lambdabot.codersbase.com/

Wait, what the hell...?


  1 + 1
/usr/lib/ghc-6.4.2/package.conf: openFile: does not exist (No such file
or directory)


Sorry about that, I upgraded my ghc package without realizing it would
affect lambdabot.  I'll see if I can fix it.

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


[Haskell-cafe] random number generators

2007-03-22 Thread david karapetyan

hi, i have been trying to learn haskell and i would like to translate the
following object-oriented pseudo-code into working haskell code but i'm
stumped on how to write the next function in the haskell code. any help is
appreciated.

class Random
...
end

ran = Random.new(300)
ran.next() - this call generates a random number
ran.next() - this one generates a different random number


so far what i have in haskell is:

data Random = Ran Int Int
next :: Random-Int - i have no idea how to write the next function that
would give me the desired effect
   because the object in the
object-oriented code can remember how many times 'next'
   was called and i would like to
do the same for 'ran' in the haskell code.
ran = Ran 300 0
next ran - this generates a random number
next ran - this generates another random number but since
  haskell is purely functional it is going to be the same
as from
  the previous call of 'next' which is not what i want
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] random number generators

2007-03-22 Thread Paul Johnson

david karapetyan wrote:
hi, i have been trying to learn haskell and i would like to translate 
the following object-oriented pseudo-code into working haskell code 
but i'm stumped on how to write the next function in the haskell code. 
any help is appreciated.


class Random
...
end

ran = Random.new(300)
ran.next() - this call generates a random number
ran.next() - this one generates a different random number


so far what i have in haskell is:

data Random = Ran Int Int
next :: Random-Int - i have no idea how to write the next function 
that would give me the desired effect
because the object in the 
object-oriented code can remember how many times 'next'
was called and i would 
like to do the same for 'ran' in the haskell code.

ran = Ran 300 0
next ran - this generates a random number
next ran - this generates another random number but since
   haskell is purely functional it is going to be the 
same as from

   the previous call of 'next' which is not what i want

Is this homework?

There is a chapter on random numbers in the Wikibook.  You will find it 
useful. 


http://en.wikibooks.org/wiki/Haskell/Hierarchical_libraries/Randoms

Are you trying to define your own random number generator, or use the 
standard one?


Your use of - arrows seems to indicate you want to use code in a do 
block (i.e. monadic code).  This allows side effects to propagate.  The 
random number stuff has an interface to IO for this reason.   The 
Wikibook has the details.


For extra credit, define your own random monad rather than using IO.  
Wrap a random generator in a State monad, and then write appropriate 
functions to use the state.  See All About Monads for an explanation 
of the state monad.


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


[Haskell-cafe] Random/StdGen/read: there is something unclear (or misunderstood!)

2007-03-13 Thread Zara
Sorry if this question is too basic, but I am trying to learn Haskell
and from tiem to time I get stuck. (And forgive me, I haev a heavy
procedural background, so functional programming is hard for me)

I am trying to use 'read' to create a random generator, applying it on
some text. As the Report, says:

#   In addition, 'read' may be used to map an arbitrary string (not
#  necessarily one produced by 'show') onto a value of type 'StdGen'.
# In general, the 'read' instance of 'StdGen' has the following
#  properties: 
#   
#   * It guarantees to succeed on any string. 
#   
#   * It guarantees to consume only a finite portion of the string. 
#   
#   * Different argument strings are likely to result in different
#  results.

But it does not succeed on any string. Code follows

\begin{code}
module Pepe where

import Random

pepin :: StdGen
pepin = read cosita

pepe :: StdGen
pepe = read cositaLinda

\end{code}

If I evaluate pepin, results are:

Hugs pepin
38273 1 :: StdGen
(360 reductions, 554 cells)

But if I evaluate pepe, all changes:

Hugs pepe

Program error: Prelude.read: no parse

(380 reductions, 694 cells)

Am I misunderstanding something, or is StdGen - read buggy?

As you can see, I am using Hugs, version Sep 2006 to test.

TIA, best regards,

Zara

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


Re: [Haskell-cafe] Random/StdGen/read: there is something unclear (or misunderstood!)

2007-03-13 Thread Kirsten Chevalier

This does seem to be a bug; see:
http://www.haskell.org/pipermail/libraries/2007-March/007034.html
(from a few minutes ago)

Cheers,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in doubt
and the things I'm working on are invisible to everyone--Meg Hutchinson
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Random numbers without IO

2007-02-09 Thread Dougal Stanton
Well, nobody likes tainting their beautiful pure code with IO, so I
rewrote the Random module to take advantage of the latest research [1]:


 module Random where

 getRandom = 4


Cheers,

D.

[1] http://xkcd.com/c221.html

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


Re: [Haskell-cafe] Random numbers without IO

2007-02-09 Thread Andrew Wagner

That's definitely the lazy approach!

On 2/9/07, Dougal Stanton [EMAIL PROTECTED] wrote:

Well, nobody likes tainting their beautiful pure code with IO, so I
rewrote the Random module to take advantage of the latest research [1]:


 module Random where

 getRandom = 4


Cheers,

D.

[1] http://xkcd.com/c221.html

--
Dougal Stanton
___
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] Random State Monad and Stochastics

2005-05-02 Thread Dominic Steinitz
I don't think they are in the standard libraries but there was some discussion 
about them a few months ago but I couldn't find a reference.

Peter, Can you supply one? I think you were a participant in the discussion. 
Did you put a library of this sort of thing together?

Here's my tuppenceworth which I used to send a sequence of ip packets (as 
actions) and to stop when I got a destination unreachable:

sequenceWhile_ :: Monad m = (a - Bool) - [m a] - m ()
sequenceWhile_ p [] =
   return ()
sequenceWhile_ p (x:xs) =
   x = \c - if (p c) then sequenceWhile_ p xs else return ()

Dominic.

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


[Haskell-cafe] Random obeservations from my playing with Haskell

2004-12-05 Thread Rolf Wilms
[Newbie warning on] Here's a few random obeservations from my playing with 
Haskell:

1. Switched to exploring Haskell from SML after finding out that it supports 
polymorphism in contrast to SML and has nicer syntax. Good.

2. Frequently saw a quick sort implementation in Haskell as a proof for 
its nice syntax. Realized that an implementation in Smalltalk would have 
been as nice.

2. Tried to implement a modular arithmetic module. Soon realized that a 
type parameterized over the modulus would be cool. Found out that it could 
be done, is rather
tricky (to an extent that I don't really understand it) and requires 
non-standard extensions to Haskell '98.

3. Considered Haskell as a replacement for an untyped DSL used in financial 
services. Soon realized that generic programming (e.g. sum premium over all 
covers) was not
possible and everything would have to be explicit. Bad. Recently discovered 
scrap your boilerplate. Sounds like the solution but again requires 
nonstandard extensions.

4. Tried to implement the game of nim, my version of hello world, in 
Haskell. My god, this even works out nicer than in Prolog! But: in order to 
make it efficient a function
needs to be memoized. Tried to implement a generic function memoizer using 
FiniteMap and Monads. Didn't get it right, might be me lacking intellect. 
Recently found a
memoization modulue in Hugs, but no docs. There's a reference to the Haskell 
'97 Report, but I didn't find it online.

5. Again Haskell as a replacement for DSL: the error messages give too 
little hint about what's wrong, thus inadequate for DSL users. This foils 
all the benefits of type
inference.

6. While googeling for solutions w.r.t. Haskell I saw a lot of papers 
using scientific style. There's nothing wrong with papers but I'm glad that 
cooking receipts usually use a
simpler style.

7. There's a lot of discussion w.r.t state, at least on this list. Is 
threading state through many functions respectivley polluting many functions 
with monads the solution?

My overall impression is that Haskell has a very nice syntax and offers 
sophisticated concepts (i.e.non-strictness, type inference) making it 
attractive for computer science.
But for most real-world applications it is intellectually too demanding (me 
included). There is hope though. Haskell seems to be in a state of 
adaptilbiliy. And it may influence
other languages.

BTW: here's that sweet (but inefficient) Haskell code for the game of nim:
moves [] = []
moves (x:xs) = xs:[y:xs | y - [1..x-1]] ++ [x:z | z - moves xs]
win [] = True
win x = foldr ((||) . not . win) False (moves x)
To find your next move, consider
filter (not . win) (moves [1,2,2])
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Random obeservations from my playing with Haskell

2004-12-05 Thread Scott Turner
On 2004 December 05 Sunday 18:19, Rolf Wilms wrote:
 [Newbie warning on] Here's a few random obeservations from my playing with
 Haskell:
You've got into Haskell with unusual rapidity. Most of your observations are 
fairly aimed.

 Recently found a memoization modulue in Hugs, but no docs. 
 There's a reference to the Haskell '97 Report, but I didn't find it online. 
http://www.cse.ogi.edu/~jl/ACM/Haskell.html
http://www.cse.ogi.edu/~byron/memo/dispose.ps

 7. There's a lot of discussion w.r.t state, at least on this list. Is
 threading state through many functions respectivley polluting many
 functions with monads the solution?
If a function is pure, there's never any need to involve it with a monad.  
Monads don't cause pollution. They serve to indicate what functions have 
side effects, while the choice of monad tells what kinds of side effects may 
occur. 

Haskell people enjoy pure functions, but are not shy of side effects, which 
are recognized as an essential feature of every program. Functions that 
return monadic values provide an excellent way to organize side effects.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Random Numbers for the beginner ?

2004-07-06 Thread Crypt Master
Hi
I have tried I swear, even googled for 45 minutes, but I cant seem to get 
random numbers working.

In the documentation is has:
rollDice :: IO Int
rollDice = getStdRandom (randomR (1,6))
But if I type getStdRandom (randomR (1,6)) into hugs in the context of 
module which imports Random, I get get errors.

ERROR - Unresolved overloading
*** Type   : (Random a, Num a) = IO a
*** Expression : getStdRandom (randomR (1,6))
Roll dice takes no parameters and returns an IO Int. So in thoery (mine at 
least ;-) ) running this as an expresion should work. I should get an IO Int 
back from the interpreter ?

So I added RollDice to my module. This doesnt error, but it doesnt return 
anything except blank spaces:

HasGal rollDice
HasGal
Integers or nums should automatically have show correct? So this should show 
me something ?

Ultimatly I want to get randomRs infinite list working so I can build
   randNums = (take (length popList) [1..])
where the length of pop list is how many random numbers I want.  My code 
works as it, just need to replace [1..] with some random numbers.

Thanks,
C
_
Add photos to your e-mail with MSN 8. Get 2 months FREE*. 
http://join.msn.com/?page=features/featuredemail

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe