[Haskell-cafe] Re: System.Random StdGen read fails on some strings? [also continues: Random/StdGen/read: there is something unclear (or misunderstood!)]

Zara me_zara at dea.spamcon.org
Tue Mar 13 09:44:46 EDT 2007


On Tue, 13 Mar 2007 00:37:46 -0700, Fritz Ruehr
<fruehr at willamette.edu> wrote:

>According to the documentation for System.Random (see <http:// 
>haskell.org/ghc/docs/latest/html/libraries/base/System-Random.html>):
>
>> 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.
>>     * ...
>
>On the other hand, I get the following on the (admittedly stupid,  
>spur-of-the-moment) String argument "whateva":
>
>> Hugs> :l System.Random
>> System.Random> read "whateva" :: StdGen
>>
>> Program error: Prelude.read: no parse
>>
>> System.Random> map read $ words "this is a test of the System dot  
>> Random StdGen read, which seems to fail only on ... whateva" ::  
>> [StdGen]
>> [4580 1,440 1,101 1,4584 1,445 1,1485 1,35261 1,1377 1,32825  
>> 1,34047 1,13422 1,14037 1,13637 1,469 1,4132 1,4514 1,453 1,626 1,
>> Program error: Prelude.read: no parse
>
>Am I missing something here? Or am I just being punished for the  
>stupidity of my particular choice of String? :)
>
>   --  Fritz
>
>PS: this happens with both Hugs Version: September 2006 and GHC  
>Interactive, version 6.6, running on Mac/Tiger, for what that's worth.

There seems to be a limit on 6 characters. Any string under 6
characters works nice, any over that limit will fail.

test program:

\begin{code}
module Test where

import Random

rd :: String -> StdGen
rd = read

testit :: String -> [Int]
testit [] = []
testit xt@(_:xs) = (testit xs) ++ [fst (randomR (1::Int,50) (rd xt))]

\end{code}

testit "thing" wotks nice,

testit "morethanthing" stops after the sixth number in the list.

Both in HUGS and GHC, last versions

Best regards,

Zara



More information about the Haskell-Cafe mailing list