
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

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

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.

And the one liner:
(rand 1 10) >>= return . (\v -> take v [1..10])
On Wed, Sep 24, 2008 at 5:10 PM, 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
-- /jve

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
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

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

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

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] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

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

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

"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]
The reason why this doesn't work by default is the occurrence distribution of tutorials about warm, fuzzy things and warm, funky things. -- (c) this sig last receiving data processing entity. Inspect headers for copyright history. All rights reserved. Copying, hiring, renting, performance and/or broadcasting of this signature prohibited.

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.

On Wed, Sep 24, 2008 at 2:03 PM, 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]
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.

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_...

I just wanted to say thanks to everyone that helped me on this. I'm still reading/cogitating the stuff you gave me, but I did manage to write a Fisher-Yates shuffle using random numbers. I had a lightbulb moment while reading about sequence (so I suppose that might count as my 7th Monad tutorial :). The <- takes values out of monads[1]. So simple! -- let c = [11..18] --shuff (length c) c shuff :: Int -> [a] -> IO [a] shuff 0 xs = return xs shuff (len + 1) xs = (rand 1 (len + 1)) >>= \r -> shuff len $ requeue r xs where requeue = \z xs -> (init $ take z xs) ++ (drop z xs) ++ [last $ take z xs] rand :: Int -> Int -> IO Int rand low high = getStdRandom (randomR (low,high)) Since it's recursive I suspect there may be a way to do this with a fold, but I'll probably work that out at a later lightbulb moment (after more questions:) Thanks again. Iain [1] In a lot of IO tutorials it just seems to be the 'do' syntax for assigning a value to a symbol, but of course, :t getLine getLine :: IO String On 24 Sep 2008, at 10:03 pm, 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.
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

On Sun, 5 Oct 2008, Iain Barnett wrote:
I just wanted to say thanks to everyone that helped me on this. I'm still reading/cogitating the stuff you gave me, but I did manage to write a Fisher-Yates shuffle using random numbers. I had a lightbulb moment while reading about sequence (so I suppose that might count as my 7th Monad tutorial :). The <- takes values out of monads[1]. So simple!
-- let c = [11..18] --shuff (length c) c shuff :: Int -> [a] -> IO [a] shuff 0 xs = return xs shuff (len + 1) xs = (rand 1 (len + 1)) >>= \r -> shuff len $ requeue r xs where requeue = \z xs -> (init $ take z xs) ++ (drop z xs) ++ [last $ take z xs]
Instead of separate calls to 'take' and 'drop' you may prefer 'splitAt': requeue z xs = let (prefix,pivot:suffix) = splitAt (z-1) xs in prefix ++ suffix ++ [pivot] However, accessing list elements by index is pretty inefficient (linear time with respect to index). Is it possible to re-arrange the algorithm? Maybe using more efficient data structures?

On 5 Oct 2008, at 7:06 pm, Henning Thielemann wrote:
Instead of separate calls to 'take' and 'drop' you may prefer 'splitAt':
requeue z xs = let (prefix,pivot:suffix) = splitAt (z-1) xs in prefix ++ suffix ++ [pivot]
Thanks. Took me a while to get the function to shuffle properly again, but shuffle xs = shuffle' (length xs) xs shuffle' :: Int -> [a] -> IO [a] shuffle' 0 xs = return xs shuffle' (len + 1) xs = rand 0 len >>= \r -> shuffle' len $ requeue r xs where requeue z ys = let (prefix,pivot:suffix) = splitAt z ys in prefix ++ suffix ++ [pivot] *Main> shuffle [11..18] [14,11,13,16,12,15,18,17] *Main> shuffle [11..18] [16,13,12,11,17,14,18,15] Until I master Quickcheck, that will do for me :)
However, accessing list elements by index is pretty inefficient (linear time with respect to index). Is it possible to re-arrange the algorithm? Maybe using more efficient data structures?
Perhaps an array? I've not investigated any of the other list-like data structures in Haskell yet. I'll only be using it to try and create a few simple games in the beginning, cards and the like, so the performance aspect isn't high on the list (yet) due to the small sets being shuffled. Just trying to get things to work first! Iain

On Tue, Oct 07, 2008 at 06:40:22PM +0100, Iain Barnett wrote:
On 5 Oct 2008, at 7:06 pm, Henning Thielemann wrote:
Instead of separate calls to 'take' and 'drop' you may prefer 'splitAt':
requeue z xs = let (prefix,pivot:suffix) = splitAt (z-1) xs in prefix ++ suffix ++ [pivot]
Thanks. Took me a while to get the function to shuffle properly again, but
shuffle xs = shuffle' (length xs) xs
shuffle' :: Int -> [a] -> IO [a] shuffle' 0 xs = return xs shuffle' (len + 1) xs = rand 0 len >>= \r -> shuffle' len $ requeue r xs where requeue z ys = let (prefix,pivot:suffix) = splitAt z ys in prefix ++ suffix ++ [pivot]
*Main> shuffle [11..18] [14,11,13,16,12,15,18,17]
*Main> shuffle [11..18] [16,13,12,11,17,14,18,15]
Until I master Quickcheck, that will do for me :)
Using QuickCheck is actually pretty easy. It's made more difficult in this particular case since the result of your shuffle function is in the IO monad. But assuming you split out the shuffling functionality into a pureShuffle function which takes a random seed as an extra parameter, you could make a property to test it as follows: prop_shuffle :: Seed -> Seed -> [a] -> Bool prop_shuffle s1 s2 l = sort (pureShuffle s1 l) == sort (pureShuffle s2 l) Then you could test it by evaluating 'quickCheck prop_shuffle' at a ghci prompt. Nice and simple! -Brent
participants (11)
-
Achim Schneider
-
Ariel J. Birnbaum
-
Brandon S. Allbery KF8NH
-
Brent Yorgey
-
Evan Laforge
-
Henning Thielemann
-
Iain Barnett
-
John Van Enk
-
Jonathan Cast
-
Lev Walkin
-
wren ng thornton