[Haskell-cafe] How to use randomized algorithm within the implementation of pure data structures?

Jun Inoue jun.lambda at gmail.com
Sat Nov 1 16:15:25 UTC 2014


Just an idea here, but would implicit-params work?  It only gives you
Reader-monad capabilities, but you can always split random generators.
There might be repercussions for the quality of the generated numbers,
though, for which I have no idea.

{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE RankNTypes #-}
import Data.Implicit
import System.Random
import Text.Printf
import Data.Default.Class

instance Default StdGen where
    def = mkStdGen 10

newtype AlgebraicNumber = AlgebraicNumber {- your data here -} String
    deriving Show

instance Implicit_ StdGen => Num AlgebraicNumber where
    AlgebraicNumber x + AlgebraicNumber y =
        -- You could tidy this up with a State monad.
        let g = param_ :: StdGen
            (g1, g2) = split g
            gx = fst $ next g1 -- compute on x using left generator
            gy = fst $ next g2 -- compute on y using right generator
        in
        AlgebraicNumber (printf ("%s computed with rand = %d,"
                                 ++ "%s computed with rand = %d")
                         x gx y gy)

On Sat, Nov 1, 2014 at 11:28 AM, Hiromi ISHII <konn.jinro at gmail.com> wrote:
> Hi Bardur,
>
>> You can just use the State monad to thread the StdGen around and
>> "update" it when you need to. You can get a pure interface by hiding
>> away the runState behind a function:
>
> Thank you for your rapid response!
> Unfortunately, I didn't describe my problem accurately.
>
> This approach (or using MonadRandom) to pass around random generator with Monad,
> works fine when it's just enough to feed generator to the algorithm.
>
> But my situation is slightly different: random generator has to be passed around to implement
> the instance method for `Num`, so it can't take random generator as its argument.
> So I need some way to hide random generator from function type signatures.
>
> Fortunately, your response suggested me the alternative approach: converting the data-type
> into continuation-passing style. This should work fine when we just do some operations on
> data-type, but we have to feed the generator when we want to inspect its value, so it's not
> sufficient, though...
>
> -- Hiromi ISHII
> konn.jinro at gmail.com
>
>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
Jun Inoue


More information about the Haskell-Cafe mailing list