[Haskell-beginners] Type inference in ST monad?

David McBride toad3k at gmail.com
Mon Aug 19 04:04:26 CEST 2013


I'm not exactly sure why you get the error, but the easiest way to fix it
is just to type it this way:

runSimulation :: Word32 -> [Int]
runSimulation seed = runST $ do
  gen <- initialize (singleton seed)
  whileM  (do r1 <- uniformR (-1.0, 1.0 :: Double) gen
              if r1 > 0.0 then return True else return False)
          (do r2 <- uniformR (0, 10 :: Int) gen
              if r2 > 5 then return r2 else return 0)

It has something to do with the forall s in runST, although I'm not
completely sure what.



On Sun, Aug 18, 2013 at 9:18 PM, Aurimas <aurimas.anskaitis at vgtu.lt> wrote:

> I have the following code which does not compile due to explicit type
> annotation
> (ST s Double). Error message says usual thing about "s" type variables.
>
> ------------------------------**------------------------------**
> ------------------------------**----------------
> import Control.Monad.ST
> import System.Random.MWC (initialize, uniformR, Gen)
> import Control.Monad.Loops (whileM)
> import Data.Vector (singleton)
> import Data.Word(Word32)
>
> main :: IO ()
> main = do
>   print $ runSimulation 1
>
> runSimulation :: Word32 -> [Int]
> runSimulation seed = runST $ do
>   gen <- initialize (singleton seed)
>   whileM  (do r1 <- uniformR (-1.0, 1.0) gen :: ST s Double -- does not
> compile due to this
>               if r1 > 0.0 then return True else return False)
>           (do r2 <- uniformR (0, 10) gen
>               if r2 > 5 then return r2 else return 0)
> ------------------------------**------------------------------**
> ------------------------------**---------------
>
> if I rewrite runSimulation like this (below), everything is OK.
>
> ------------------------------**------------------------------**
> ------------------------------**---------------
> runSimulation :: Word32 -> [Int]
> runSimulation seed = runST $ do
>   gen <- initialize (singleton seed)
>   whileM  (do r1 <- tempFun gen
>               if r1 > 0.0 then return True else return False)
>           (do r2 <- uniformR (0, 10) gen
>               if r2 > 5 then return r2 else return 0)
>     where tempFun :: Gen s -> ST s Double    -- this line automatically
> provides required type annotation
>           tempFun g = uniformR (-1.0, 1.0) g
> ------------------------------**------------------------------**
> ------------------------------**---------------
>
> Ca somebody explain what's wrong with the first version?
>
> Best Regards,
> Aurimas
>
>
> ______________________________**_________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/**mailman/listinfo/beginners<http://www.haskell.org/mailman/listinfo/beginners>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/beginners/attachments/20130818/be2f64e1/attachment.htm>


More information about the Beginners mailing list