[Haskell-cafe] OpenGL: No instance for Random GLfloat

Mark Spezzano mark.spezzano at chariot.net.au
Thu May 3 04:37:36 CEST 2012


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 at 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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe

-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20120503/492e75a4/attachment.htm>


More information about the Haskell-Cafe mailing list