aboutsummaryrefslogtreecommitdiff
path: root/Graphics/Glyph/GlyphObject.hs
diff options
context:
space:
mode:
Diffstat (limited to 'Graphics/Glyph/GlyphObject.hs')
-rw-r--r--Graphics/Glyph/GlyphObject.hs57
1 files changed, 48 insertions, 9 deletions
diff --git a/Graphics/Glyph/GlyphObject.hs b/Graphics/Glyph/GlyphObject.hs
index 29d25bb..db7b47c 100644
--- a/Graphics/Glyph/GlyphObject.hs
+++ b/Graphics/Glyph/GlyphObject.hs
@@ -1,5 +1,3 @@
-{-# LANGUAGE TemplateHaskell #-}
-
module Graphics.Glyph.GlyphObject (
GlyphObject,
getBufferObject,
@@ -32,9 +30,8 @@ module Graphics.Glyph.GlyphObject (
import Graphics.Glyph.BufferBuilder
import Graphics.Glyph.Util
-import Graphics.Rendering.OpenGL
+import Graphics.Rendering.OpenGL as GL
import Graphics.Glyph.ExtendedGL as Ex
-import Data.Setters
import Control.Monad
import Control.Applicative
@@ -59,7 +56,6 @@ data GlyphObject a = GlyphObject {
numInstances :: Int
}
-$(declareSetters ''GlyphObject)
getBufferObject :: GlyphObject a -> BufferObject
getBufferObject = bufferObject
@@ -90,6 +86,43 @@ getTeardownRoutine = teardownRoutine
getPrimitiveMode :: GlyphObject a -> ExPrimitiveMode
getPrimitiveMode = primitiveMode
+setBufferObject :: GlyphObject a -> BufferObject -> GlyphObject a
+setBufferObject o a = o {bufferObject = a}
+
+setCompiledData :: GlyphObject a -> (CompiledBuild GLfloat) -> GlyphObject a
+setCompiledData o a = o {compiledData = a}
+
+setVertexAttribute :: GlyphObject a -> AttribLocation -> GlyphObject a
+setVertexAttribute o a = o {vertexAttribute = a}
+
+setNormalAttribute :: GlyphObject a -> (Maybe AttribLocation) -> GlyphObject a
+setNormalAttribute o a = o {normalAttribute = a}
+
+setColorAttribute :: GlyphObject a -> (Maybe AttribLocation) -> GlyphObject a
+setColorAttribute o a = o {colorAttribute = a}
+
+setTextureAttribute :: GlyphObject a -> (Maybe AttribLocation) -> GlyphObject a
+setTextureAttribute o a = o {textureAttribute = a}
+
+setResources :: GlyphObject a -> a -> GlyphObject a
+setResources o a = o {resources = a}
+
+setSetupRoutine :: GlyphObject a -> (Maybe (GlyphObject a -> IO ())) -> GlyphObject a
+setSetupRoutine o a = o {setupRoutine = a}
+
+setSetupRoutine2 :: GlyphObject a -> (Maybe (GlyphObject a -> IO ())) -> GlyphObject a
+setSetupRoutine2 o a = o {setupRoutine2 = a}
+
+setTeardownRoutine :: GlyphObject a -> (Maybe (GlyphObject a -> IO ())) -> GlyphObject a
+setTeardownRoutine o a = o {teardownRoutine = a}
+
+setPrimitiveMode :: GlyphObject a -> ExPrimitiveMode -> GlyphObject a
+setPrimitiveMode o a = o {primitiveMode = a}
+
+setNumInstances :: GlyphObject a -> Int -> GlyphObject a
+setNumInstances o a = o {numInstances = a}
+
+
newGlyphObject :: BuilderM GLfloat x ->
AttribLocation ->
Maybe AttribLocation ->
@@ -107,13 +140,13 @@ newGlyphObject builder vertAttr normAttr colorAttr textureAttr res setup tear mo
return $ GlyphObject buffer compiled vertAttr normAttr colorAttr textureAttr res setup Nothing tear mode 1
prepare :: GlyphObject a -> (GlyphObject a -> IO()) -> GlyphObject a
-prepare a b = setSetupRoutine2 (Just b) a
+prepare a b = setSetupRoutine2 a (Just b)
startClosure :: GlyphObject a -> (GlyphObject a -> IO()) -> GlyphObject a
-startClosure a b = setSetupRoutine (Just b) a
+startClosure a b = setSetupRoutine a (Just b)
teardown :: GlyphObject a -> (GlyphObject a -> IO()) -> GlyphObject a
-teardown a b = setTeardownRoutine (Just b) a
+teardown a b = setTeardownRoutine a (Just b)
instance Drawable (GlyphObject a) where
draw = drawInstances <..> numInstances
@@ -139,7 +172,13 @@ drawInstances n obj@(GlyphObject bo co vAttr nAttr cAttr tAttr _ setup1 setup2 t
vertexAttribPointer attr $= (ToFloat, ad)
vertexAttribArray attr $= Enabled
- drawArraysInstanced p 0 (bufferLength co) $ fromIntegral n
+ let p' = case p of
+ Ex.Points -> GL.Points
+ Ex.Lines -> GL.Lines
+ Ex.Triangles -> GL.Triangles
+ Ex.Patches -> GL.Patches
+
+ drawArraysInstanced p' 0 (bufferLength co) $ fromIntegral n
forM_ enabled $ \(attr, _) -> do
vertexAttribArray attr $= Disabled