hackage vector-space-opengl

Nikolay Orlyuk virkony at gmail.com
Sun May 20 11:59:47 CEST 2012


Hello

First of all I'd like to say that I like vector-space and
vector-space-opengl is something that I'd like to use together with OpenGL.
So while using that library I found some things that can be useful for
others, I think.

While looking into OpenGL/TH.hs I found that it quite incomplete and I
understand why. That suggestion at stackoverflow results in a bit
boilerplate code:

deriveScalar, deriveScalarAdditiveGroup, deriveScalarVectorSpace,
deriveScalarAffineSpace :: [Name] -> Q [Dec]
deriveScalar ts = concat <$> forM decls (\qf -> qf ts)
    where decls = [ deriveScalarAdditiveGroup
                  , deriveScalarVectorSpace
                  , deriveScalarAffineSpace
                  , deriveScalarInnerSpace
                  ]
deriveScalarVectorSpace ts = concat <$> mapM f ts where
    f tn = do
        t <- [t| $(conT tn) |]
        vs <- [t| VectorSpace |]
        (AppT (ConT s) _) <- [t| Scalar () |] -- dummy type to extract
Scalar name
        (VarE h) <- [e| (*^) |] -- refer to actual (*^) from VectorSpace
        e <- [e| (*) |] -- (*) from Num
        return [
            InstanceD [] (AppT vs t) [
                TySynInstD s [t] t,
                ValD (VarP h) (NormalB e) []
            ]]

It's kinda partially checked and partially constructed. BTW, rather than
depending on OpenGL its better to use Graphics.Rendering.OpenGL.Raw I
think. Also there is types GLclampd and GLclampf (I suspect that they
somehow related with OpenCL).

While scalar types doesn't differ whether they are absolute whether they
are not. Data.Tensor makes difference between Vertex and Vector. I suspect
that made especially for this case: instance AffineSpace a => AffineSpace
(Vertex2 a) where type Diff (Vertex2 a) = Vector2 (Diff a)
I.e. Diff Vertex shouldn't be Vertex and Vertex a should not belong to
AdditiveGroup

If anyone knows how to walk through the whole module in monad Q that might
bring more power to this library. I.e. walk through OpenGL.Raw and make
declarations  for all its scalar types.

Thank you
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/libraries/attachments/20120520/143da423/attachment.htm>


More information about the Libraries mailing list