[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
Mon Mar 19 03:06:21 EDT 2007
On Tue, 13 Mar 2007 14:44:46 +0100, Zara <me_zara at dea.spamcon.org>
wrote:
>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
<..>
>
>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
>
The problem seems to lie in base/System/Random.hs:
\begin{code}
{-
If we cannot unravel the StdGen from a string, create
one based on the string given.
-}
stdFromString :: String -> (StdGen, String)
stdFromString s = (mkStdGen num, rest)
where (cs, rest) = splitAt 6 s
num = foldl (\a x -> x + 3 * a) 1 (map ord cs)
\end{code}
If we change the number on splitAt, the string limit to give an error
changes.
I think that when we feed an arbitrary string to readsPrec of
Random.StdGen, we should return nothing, that is, we should consume
the whole string. So, I propose th change that function to be:
\begin{code}
{-
If we cannot unravel the StdGen from a string, create
one based on the string given. We consume it all.
-}
stdFromString :: String -> (StdGen, String)
stdFromString s = (mkStdGenBis num, "")
where num = foldl (\a x -> x + 3 * a) 1 (map ord s)
\end{code}
This solution solves *our* problem, but I would like to receive
comments to it. Where may I find someone responsible for this library,
to see if the change is adequate, or why not?
Best regards,
Zara
More information about the Haskell-Cafe
mailing list