module Codec.GlTF.Node
  ( NodeIx(..)
  , Node(..)
  , NodeMatrix(..)

    -- XXX: Misplaced here due to mutual recursion.
  , 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)

-- | A node in the node hierarchy.
--
-- When the node contains skin, all mesh.primitives must contain JOINTS_0 and WEIGHTS_0 attributes.
--
-- A node can have either a matrix or any combination of translation/rotation/scale (TRS) properties.
--
-- TRS properties are converted to matrices and postmultiplied in the T * R * S order to
-- compose the transformation matrix; first the scale is applied to the vertices, then
-- the rotation, and then the translation.
-- If none are provided, the transform is the identity.
--
-- When a node is targeted for animation (referenced by an animation.channel.target),
-- only TRS properties may be present; matrix will not be present.
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

-- | A floating-point 4x4 transformation matrix stored in column-major order.
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)

-- | Joints and matrices defining a skin.
data Skin = Skin
  { joints              :: Vector (NodeIx)
  , skeleton            :: Maybe NodeIx
  , inverseBindMatrices :: Maybe AccessorIx
    -- ^ The index of the accessor containing the floating-point
    -- 4x4 inverse-bind matrices.
    -- The default is that each matrix is a 4x4 identity matrix,
    -- which implies that inverse-bind matrices were pre-applied.
  , name                :: Maybe Text
  , extensions          :: Maybe Object
  , extras              :: Maybe Value
  } deriving (Eq, Show, Generic)

instance FromJSON Skin
instance ToJSON Skin