module Graphics.LambdaCube.Skeleton where import Graphics.LambdaCube.Types import Data.Map (Map) import Data.Tree import qualified Data.Vector as V data Bone = Bone { bnPosition :: Vec3 , bnRotation :: U } deriving Show data KeyFrame = KeyFrame { kfPosition :: Vec3 , kfRotation :: U , kfTime :: FloatType } deriving Show data Animation = Animation { anTracks :: V.Vector [KeyFrame] , anLength :: FloatType , anName :: String } deriving Show data Skeleton = Skeleton { skBones :: V.Vector Bone , skBoneTree :: Tree Int , skAnimations :: Map String Animation } deriving Show data PoseData = PoseData { pdJointMatrix :: Proj4 , pdInverseBindMatrix :: Proj4 , pdWorldMatrix :: Proj4 , pdSkinningMatrix :: Proj4 } -- FIXME: remove Data.Vec.LinAlg.Transform3D dependency {- mat33ToMat44 (a:.b:.c:.()) = (h a):.(h b):.(h c):.(0:.0:.0:.1:.()):.() where h x = Vec.snoc 0 x poseData :: Skeleton -> Animation -> FloatType -> Vector PoseData poseData s a t = visit Nothing idPD $ skBoneTree s where bones = skBones s idPD = V.replicate (V.length $ skBones s) $ PoseData idMat idMat idMat idMat idMat = Vec.identity visit p v (Node i []) = f p i v visit p v (Node i l) = foldl' (visit $ Just i) (f p i v) l f p i v = v // [(i,PoseData jm ibm wm sm)] where b = bones V.! i rot = mat33ToMat44 $ quatToMat $ bnRotation b trans = translation $ bnPosition b jm = rot `multmm` trans ibm = invertMat44 jm wm = pwm `multmm` jm sm = idMat pwm = maybe idMat (\n -> pdWorldMatrix $ v V.! n) p -}