Because GLfloat is simply a newtype wrapper for CFloat, which has a Random
instance, I would do:

{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
deriving instance Random GLFloat

On Wed, May 2, 2012 at 6:29 PM, Mark Spezzano
<mark.spezz...@chariot.net.au>wrote:

> Hi Haskellers,
>
> I'm trying to generate a random vertex in OpenGL as follows.
>
> genPosition :: IO (Vertex3 GLfloat)
> genPosition = do x <- getStdRandom $ randomR (-1.6,1.6)
>                               y <- getStdRandom $ randomR (-1.0,1.0)
>                              return (Vertex3 x y (-1))
>
> Unfortunately the compiler complains about me having to implement an
> instance of Random for  GLfloat.
>
> How do I do this (or avoid having to do this)?
>
> Cheers,
>
> Mark
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to