summaryrefslogtreecommitdiff
path: root/src/LambdaCube/GL/Input.hs
diff options
context:
space:
mode:
authorCsaba Hruska <csaba.hruska@gmail.com>2016-01-10 22:58:12 +0100
committerCsaba Hruska <csaba.hruska@gmail.com>2016-01-10 22:58:12 +0100
commit2344d2af7eb3e5515408d134a074b989e7b5efde (patch)
tree01b905a55d0b8e0560097241dd2cd277f6bfab46 /src/LambdaCube/GL/Input.hs
parente936d3c32c17c0d00939893fa85996c3807ed3e7 (diff)
update example
Diffstat (limited to 'src/LambdaCube/GL/Input.hs')
-rw-r--r--src/LambdaCube/GL/Input.hs33
1 files changed, 32 insertions, 1 deletions
diff --git a/src/LambdaCube/GL/Input.hs b/src/LambdaCube/GL/Input.hs
index 742fc35..7e4ba74 100644
--- a/src/LambdaCube/GL/Input.hs
+++ b/src/LambdaCube/GL/Input.hs
@@ -1,8 +1,10 @@
1{-# LANGUAGE FlexibleContexts #-}
1module LambdaCube.GL.Input where 2module LambdaCube.GL.Input where
2 3
3import Control.Applicative 4import Control.Applicative
4import Control.Exception 5import Control.Exception
5import Control.Monad 6import Control.Monad
7import Control.Monad.Writer
6import Data.IORef 8import Data.IORef
7import Data.Map (Map) 9import Data.Map (Map)
8import Data.IntMap (IntMap) 10import Data.IntMap (IntMap)
@@ -68,7 +70,7 @@ allocStorage sch = do
68 } 70 }
69 71
70disposeStorage :: GLStorage -> IO () 72disposeStorage :: GLStorage -> IO ()
71disposeStorage = error "not implemented: disposeStorage" 73disposeStorage _ = putStrLn "not implemented: disposeStorage"
72 74
73-- object 75-- object
74addObject :: GLStorage -> String -> Primitive -> Maybe (IndexStream Buffer) -> Map String (Stream Buffer) -> [String] -> IO Object 76addObject :: GLStorage -> String -> Primitive -> Maybe (IndexStream Buffer) -> Map String (Stream Buffer) -> [String] -> IO Object
@@ -137,6 +139,7 @@ addObject input slotName prim indices attribs uniformNames = do
137 let emptyV = V.replicate (V.length $ glPrograms p) [] 139 let emptyV = V.replicate (V.length $ glPrograms p) []
138 return $ emptyV // [(prgIdx,createObjectCommands (glTexUnitMapping p) topUnis obj (glPrograms p ! prgIdx))| prgIdx <- glSlotPrograms p ! pSlotIdx] 140 return $ emptyV // [(prgIdx,createObjectCommands (glTexUnitMapping p) topUnis obj (glPrograms p ! prgIdx))| prgIdx <- glSlotPrograms p ! pSlotIdx]
139 writeIORef cmdsRef cmds 141 writeIORef cmdsRef cmds
142 sortSlotObjects input
140 return obj 143 return obj
141 144
142removeObject :: GLStorage -> Object -> IO () 145removeObject :: GLStorage -> Object -> IO ()
@@ -149,6 +152,7 @@ setObjectOrder :: GLStorage -> Object -> Int -> IO ()
149setObjectOrder p obj i = do 152setObjectOrder p obj i = do
150 writeIORef (objOrder obj) i 153 writeIORef (objOrder obj) i
151 modifyIORef (slotVector p ! objSlot obj) $ \(GLSlot objs sorted _) -> GLSlot objs sorted Reorder 154 modifyIORef (slotVector p ! objSlot obj) $ \(GLSlot objs sorted _) -> GLSlot objs sorted Reorder
155 sortSlotObjects p
152 156
153objectUniformSetter :: Object -> Map GLUniformName InputSetter 157objectUniformSetter :: Object -> Map GLUniformName InputSetter
154objectUniformSetter = objUniSetter 158objectUniformSetter = objUniSetter
@@ -387,3 +391,30 @@ uniformM44F n is = case Map.lookup n is of
387uniformFTexture2D n is = case Map.lookup n is of 391uniformFTexture2D n is = case Map.lookup n is of
388 Just (SFTexture2D fun) -> fun 392 Just (SFTexture2D fun) -> fun
389 _ -> nullSetter n "FTexture2D" 393 _ -> nullSetter n "FTexture2D"
394
395a @: b = tell [(a,b)]
396defObjectArray n p m = mapM_ tell [PipelineSchema (Map.singleton n $ ObjectArraySchema p $ Map.singleton a t) mempty | (a,t) <- execWriter m]
397defUniforms m = tell $ PipelineSchema mempty $ Map.fromList $ execWriter m
398makeSchema a = execWriter a :: PipelineSchema
399
400unionObjectArraySchema (ObjectArraySchema a1 b1) (ObjectArraySchema a2 b2) =
401 ObjectArraySchema (if a1 == a2 then a1 else error $ "object array schema primitive mismatch " ++ show (a1,a2))
402 (Map.unionWith (\a b -> if a == b then a else error $ "object array schema attribute type mismatch " ++ show (a,b)) b1 b2)
403
404instance Monoid PipelineSchema where
405 mempty = PipelineSchema mempty mempty
406 mappend (PipelineSchema a1 b1) (PipelineSchema a2 b2) =
407 PipelineSchema (Map.unionWith unionObjectArraySchema a1 a2) (Map.unionWith (\a b -> if a == b then a else error $ "schema type mismatch " ++ show (a,b)) b1 b2)
408
409type UniM = Writer [GLStorage -> IO ()]
410
411class UniformSetter a where
412 (@=) :: GLUniformName -> IO a -> UniM ()
413
414instance UniformSetter Float where
415 n @= act = tell [\s -> let f = uniformFloat n (uniformSetter s) in f =<< act]
416
417instance UniformSetter TextureData where
418 n @= act = tell [\s -> let f = uniformFTexture2D n (uniformSetter s) in f =<< act]
419
420updateUniforms storage m = sequence_ $ let l = map ($ storage) $ execWriter m in l