[Haskell-cafe] Unboxing CFloat and GLfloat

Jason Dagit dagitj at gmail.com
Sun Mar 27 22:48:01 CEST 2011


First a bit of background.  Sometimes I would like to be able to create
unboxed arrays of CFloats and GLfloats.  Both of these are defined as
newtypes around types that can be unboxed (e.g., Float).  I'm assuming GHC
here.

As far as I can tell, the newtyping is there to help programmers pick a
representation that matches the C compiler's representation on their
platform without having to use CPP in their Haskell code.

Would it be possible to add instances like these?

instance MArray (STUArray s) GLfloat (ST s)
instance MArray IOUArray GLfloat IO

instance MArray (STUArray s) CFloat (ST s)
instance MArray IOUArray CFloat IO

I would also want instances for the other C types that map to Haskell types
that are unboxed and the other GL types too.

For example, in my program I imported all the right libraries and added this
instance as an experiment:
instance MArray (STUArray s) GLfloat (ST s) where
    {-# INLINE getBounds #-}
    getBounds (STUArray l u _ _) = return (l,u)
    {-# INLINE getNumElements #-}
    getNumElements (STUArray _ _ n _) = return n
    {-# INLINE unsafeNewArray_ #-}
    unsafeNewArray_ (l,u) = unsafeNewArraySTUArray_ (l,u) fLOAT_SCALE
    {-# INLINE newArray_ #-}
    newArray_ arrBounds = newArray arrBounds 0
    {-# INLINE unsafeRead #-}
    unsafeRead (STUArray _ _ _ marr#) (I# i#) = ST $ \s1# ->
        case readFloatArray# marr# i# s1# of { (# s2#, e# #) ->
        (# s2#, unsafeCoerce (F# e#) #) }
    {-# INLINE unsafeWrite #-}
    unsafeWrite (STUArray _ _ _ marr#) (I# i#) e = ST $ \s1# ->
        let F# e# = unsafeCoerce e in
        case writeFloatArray# marr# i# e# s1# of { s2# ->
        (# s2#, () #) }

I had to use an unsafeCoerce because the constructor for GLfloat is not
exposed, and realToFrac has terrible performance because the following rules
(suggested by Andy Gill) are missing from the OpenGL bindings:
{-# RULES "realToFrac/a->GLfloat" realToFrac = \x -> GLfloat (realToFrac x)
#-}
{-# RULES "realToFrac/GLfloat->a" realToFrac = \(GLfloat x) -> realToFrac x
#-}

Even if I had those rules, I would still need to get access to the
underlying representation (the e#) to have the right kind.  GLfloat is
defined in terms of CFloat which is defined in terms of other things.  On my
machine, CFloat happens to correspond to Float, although in general this
need not be the case.  So to do this instance correctly I would need to
know, in general, what the underlying type is for CFloat.  I think that
means I would need to use the same macros as GHC, although I don't think
that requires this instance to appear in base.  I could just borrow the
macros once I figure out the corresponding instance for CFloat.

While the GLfloat instances don't need to be in base, the CFloat instance
probably should be in base.  Is this something I should make a library
proposal for and submit patches?  Is there an easier way to get these
instances?  Has someone already done this?

Thanks,
Jason
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20110327/7a2f4b1f/attachment.htm>


More information about the Haskell-Cafe mailing list