-- CallyDump.hs -- CallyDump Cal3D example module Main where import Control.Monad import Foreign import Graphics.Rendering.OpenGL import Graphics.Animation.Cal3D import CallyCommon main :: IO () main = do { coreModel <- loadCallyCoreModel True ; model <- newCallyInstance coreModel True -- Mix animations. -- NOTE: In real life, you would not want to do these three -- without some elapsed time! -- Set an animation mix, reaching 100% jog after 0.5 second ; mixer <- getMixer model ; require 50 "cycle jog animation" (blendCycle mixer (jogAnim coreModel) 1.0 0.5) -- Use clearCycle to "fade out" the jog animation in 3 seconds ; require 51 "clear jog animation cycle" (clearCycle mixer (jogAnim coreModel) 3.0) -- use executeAction to perform an action once, -- with delayIn, delayOut, weightTarget, and autoLock arguments ; require 52 "execute idle action" (executeAction mixer (idleAnim coreModel) 2.5 7.5 0.95 True) -- Update model state for time = 0 ; update model 0.0 -- Update the model state, given 0.05 second elapsed time -- ; update model 0.05 -- Render the model (big job here) ; require 53 "render model" (renderModel model dumpRenderInfo) -- Destroy the model -- Contrary to user guide, there is no "destroy" method. ; deleteModel model ; putStrLn "Model deleted." -- Finish ; return () } lshow :: (Show a) => String -> a -> IO () lshow label x = putStrLn $ label ++ " = " ++ show x dumpRenderInfo :: RenderAction dumpRenderInfo renderInfo = do { lshow "Mesh, Submesh = " (riMeshId renderInfo, riSubmeshId renderInfo) -- show coloring ; lshow "ambient = " (riAmbient renderInfo) ; lshow "diffuse = " (riDiffuse renderInfo) ; lshow "specular = " (riSpecular renderInfo) ; lshow "shininess = " (riShininess renderInfo) ; let faceStride = 3 vtxStride = 3 normStride = 3 -- show faces ; lshow "Number of faces" (riFaceCount renderInfo) ; showBuffer (riFaceBuf renderInfo) 0 (riFaceCount renderInfo) faceStride -- show vertices ; lshow "Number of vertex elements" (riVtxCount renderInfo) ; showBuffer (riVtxBuf renderInfo) 0 (riVtxCount renderInfo) vtxStride -- show normals ; lshow "Number of normal elements" (riNormCount renderInfo) ; showBuffer (riNormBuf renderInfo) 0 (riNormCount renderInfo) normStride } showBuffer :: (Storable a, Show a) => Ptr a -> Int -> Int -> Int -> IO () showBuffer buf irow nrows ncols = -- nrows = number of rows, e.g., faces (3 ints) or vertices (3 floats) -- ncols = number of columns, e.g., 3 per face or 3 per vertex when (irow < nrows) (do { xs <- peekRow buf irow ncols ; print (irow, xs) ; showBuffer buf (irow + 1) nrows ncols } ) peekRow :: (Storable a) => Ptr a -> Int -> Int -> IO [a] peekRow buf irow ncols = -- return a list of elements of row irow mapM (\ i -> peekElemOff buf (irow * ncols + i)) [0 .. ncols - 1]