{-# LANGUAGE ForeignFunctionInterface #-} {-# INCLUDE "cal3d_c.h" #-} {- | A Renderer provides information needed for graphics rendering; it does not output any graphics by itself, but needs the cooperation of a graphics API. Consider using 'Graphics.Animation.Cal3D.OpenGL' from the cal3d-opengl package. -} module Graphics.Animation.Cal3D.Renderer (newRenderer, deleteRenderer , renderAnimation , getMeshCount, getSubmeshCount , selectMeshSubmesh , CalIndex, getFaceCount, getFaces , withAmbientColorPtr, withDiffuseColorPtr, withSpecularColorPtr , getShininess , getVertexCount, getVertices, getNormals ) where import Foreign import Foreign.C.Types import Foreign.C.String import Graphics.Animation.Cal3D.Types import Graphics.Animation.Cal3D.Error -- | Create a Renderer. foreign import ccall safe "newRenderer" newRenderer :: Model -> IO Renderer -- | Destroy a Renderer. foreign import ccall safe "deleteRenderer" deleteRenderer :: Renderer -> IO () {- | Executes a rendering action. > renderAnimation renderer action corresponds to > renderer->beginRendering(); > action(); > renderer->endRendering(); in the Cal3D C++ API. -} renderAnimation :: Renderer -> IO () -- ^ rendering action -> IO (Either String ()) renderAnimation renderer action = do { ok <- c_beginRendering renderer ; result <- if not (toBool ok) then return $ Left "renderAnimation: unable to begin rendering" else do { action ; return $ Right () } ; c_endRendering renderer ; return result } foreign import ccall safe "beginRendering" c_beginRendering :: Renderer -> IO Int foreign import ccall safe "endRendering" c_endRendering :: Renderer -> IO () -- | The number of meshes in the Renderer's 'Model'. getMeshCount :: Renderer -> IO Int getMeshCount renderer = return . fromIntegral =<< c_getMeshCount renderer foreign import ccall safe "getMeshCount" c_getMeshCount :: Renderer -> IO CInt -- | The number of submeshes in the given mesh of the Renderer's 'Model'. getSubmeshCount :: Renderer -> Int -- ^ mesh ID -> IO Int getSubmeshCount renderer meshId = return . fromIntegral =<< c_getSubmeshCount renderer (fromIntegral meshId) foreign import ccall safe "getSubmeshCount" c_getSubmeshCount :: Renderer -> CInt -> IO CInt {- | Selects a particular (mesh, submesh) so that all subsequent operations refer to this (mesh, submesh) pair. -} selectMeshSubmesh :: Renderer -> Int -- ^ mesh ID -> Int -- ^ submesh ID -> IO (Either String ()) selectMeshSubmesh renderer meshId submeshId = checkError (c_selectMeshSubmesh renderer (fromIntegral meshId) (fromIntegral submeshId)) 0 ("unable to select submesh " ++ (show (meshId, submeshId))) foreign import ccall safe "selectMeshSubmesh" c_selectMeshSubmesh :: Renderer -> CInt -> CInt -> IO CInt -- | The number of faces in the current (mesh, submesh). getFaceCount :: Renderer -> IO Int getFaceCount renderer = return . fromIntegral =<< c_getFaceCount renderer foreign import ccall safe "getFaceCount" c_getFaceCount :: Renderer -> IO CInt -- | Used to index faces. type CalIndex = CInt -- | Fills a buffer with the face numbers. getFaces :: Renderer -> Ptr CalIndex -- ^ buffer -> IO Int getFaces renderer ptr = return . fromIntegral =<< c_getFaces renderer ptr foreign import ccall safe "getFaces" c_getFaces :: Renderer -> Ptr CalIndex -> IO CInt -- | The number of vertices, also the number of normals, -- in the current (mesh, submesh). getVertexCount :: Renderer -> IO Int getVertexCount renderer = return . fromIntegral =<< c_getVertexCount renderer foreign import ccall safe "getVertexCount" c_getVertexCount :: Renderer -> IO CInt -- | Fills a buffer with the vertex data of the current (mesh, submesh). getVertices :: Renderer -> Ptr Float -- ^ buffer -> Int -- ^ stride -> IO Int getVertices renderer ptr stride = return . fromIntegral =<< c_getVertices renderer ptr (fromIntegral stride) foreign import ccall safe "getVertices" c_getVertices :: Renderer -> Ptr Float -> CInt -> IO CInt -- | Fills a buffer with the normal data for the current (mesh, submesh). getNormals :: Renderer -> Ptr Float -> Int -> IO Int getNormals renderer buf stride = return . fromIntegral =<< c_getNormals renderer buf (fromIntegral stride) foreign import ccall safe "getNormals" c_getNormals :: Renderer -> Ptr Float -> Int -> IO CInt -- ---------------------------------------------------------------------- -- Getting colors -- ---------------------------------------------------------------------- -- Intended usage: -- c_getColor is the C function that "reads" the color, storing 4 bytes -- into a pointer -- convert is a function that takes the pointer and converts the -- 4 bytes into a color suitable for the rendering engine, -- for example, in OpenGL, Color4 GLfloat. withColorPtr :: Storable c => (Renderer -> Ptr Word8 -> IO ()) -> (Ptr Word8 -> IO c) -> Renderer -> IO c withColorPtr c_getColor convert renderer = alloca (\ ptr -> do {c_getColor renderer ptr; convert ptr}) {- | Calls an action with a pointer to the ambient color data. The color data are four bytes (red, green, blue, alpha). If you are using OpenGL, use 'Graphics.Animation.Cal3D.OpenGL.getAmbientColor' instead. You almost certainly don't want to use @withAmbientColorPtr@ directly, unless your are connecting Cal3D to a different graphics API. -} withAmbientColorPtr :: (Storable c) => (Ptr Word8 -> IO c) -- ^ action -> Renderer -> IO c withAmbientColorPtr = withColorPtr c_getAmbientColor -- | Diffuse color, like 'withAmbientColorPtr'. withDiffuseColorPtr :: (Storable c) => (Ptr Word8 -> IO c) -> Renderer -> IO c withDiffuseColorPtr = withColorPtr c_getDiffuseColor -- | Specular color, like 'withAmbientColorPtr'. withSpecularColorPtr :: (Storable c) => (Ptr Word8 -> IO c) -> Renderer -> IO c withSpecularColorPtr = withColorPtr c_getSpecularColor foreign import ccall safe "getAmbientColor" c_getAmbientColor :: Renderer -> Ptr Word8 -> IO () foreign import ccall safe "getDiffuseColor" c_getDiffuseColor :: Renderer -> Ptr Word8 -> IO () foreign import ccall safe "getSpecularColor" c_getSpecularColor :: Renderer -> Ptr Word8 -> IO () -- | The shininess, which affects the extent of speculr effects. getShininess :: Renderer -> IO Float getShininess = c_getShininess foreign import ccall safe "getShininess" c_getShininess :: Renderer -> IO Float -- ------------------------------------------------------------------------ -- DEBUG AID -- ------------------------------------------------------------------------ foreign import ccall safe "calVectorSize" dbgCalVectorSize :: IO CInt foreign import ccall safe "dumpVertices" dbgDumpVertices :: Renderer -> IO ()