module Codec.GlTF.Node
( NodeIx(..)
, Node(..)
, NodeMatrix(..)
, SkinIx(..)
, Skin(..)
) where
import Codec.GlTF.Prelude
import Codec.GlTF.Accessor (AccessorIx)
import Codec.GlTF.Camera (CameraIx)
import Codec.GlTF.Mesh (MeshIx)
newtype NodeIx = NodeIx { unNodeIx :: Int }
deriving (Eq, Ord, Show, FromJSON, ToJSON, Generic)
data Node = Node
{ camera :: Maybe CameraIx
, children :: Maybe (Vector NodeIx)
, skin :: Maybe SkinIx
, matrix :: Maybe NodeMatrix
, mesh :: Maybe MeshIx
, rotation :: Maybe (Float, Float, Float, Float)
, scale :: Maybe (Float, Float, Float)
, translation :: Maybe (Float, Float, Float)
, weights :: Maybe (Vector Float)
, name :: Maybe Text
, extensions :: Maybe Object
, extras :: Maybe Value
} deriving (Eq, Show, Generic)
instance FromJSON Node
instance ToJSON Node
newtype NodeMatrix = NodeMatrix { unNodeMatrix :: Vector Float }
deriving (Eq, Ord, Show, FromJSON, ToJSON, Generic)
newtype SkinIx = SkinIx { unSkinIx :: Int }
deriving (Eq, Ord, Show, FromJSON, ToJSON, Generic)
data Skin = Skin
{ joints :: Vector (NodeIx)
, skeleton :: Maybe NodeIx
, inverseBindMatrices :: Maybe AccessorIx
, name :: Maybe Text
, extensions :: Maybe Object
, extras :: Maybe Value
} deriving (Eq, Show, Generic)
instance FromJSON Skin
instance ToJSON Skin