OpenGL: No instance for Random GLfloat

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

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
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

Hi, I tried this but now I get another error: The data constructors of `GLfloat' are not all in scope so you cannot derive an instance for it In the stand-alone deriving instance for `Random GLfloat' Mark On 03/05/2012, at 10:39 AM, Patrick Palka wrote:
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
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

Hi,
GLfloat haskell is instance of several number related typeclasses. A
function like 'fromRational' could be used to create a GLfloat from another
number that has a random instance.
L
On May 3, 2012 4:39 AM, "Mark Spezzano"
Hi,
I tried this but now I get another error:
The data constructors of `GLfloat' are not all in scope so you cannot derive an instance for it In the stand-alone deriving instance for `Random GLfloat'
Mark
On 03/05/2012, at 10:39 AM, Patrick Palka wrote:
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.spezzano@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
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (3)
-
L Corbijn
-
Mark Spezzano
-
Patrick Palka