module Codec.GlTF.Animation
( AnimationIx(..)
, Animation(..)
, AnimationSamplerIx(..)
, AnimationSampler(..)
, AnimationSamplerInterpolation(..)
, pattern LINEAR
, pattern STEP
, pattern CUBICSPLINE
, AnimationChannel(..)
, AnimationChannelTarget(..)
, AnimationChannelTargetPath(..)
, pattern TRANSLATION
, pattern ROTATION
, pattern SCALE
, pattern WEIGHTS
) where
import Codec.GlTF.Prelude
import Codec.GlTF.Accessor (AccessorIx)
import Codec.GlTF.Node (NodeIx)
newtype AnimationIx = AnimationIx { unAnimationIx :: Int }
deriving (Eq, Ord, Show, FromJSON, ToJSON, Generic)
data Animation = Animation
{ channels :: Vector AnimationChannel
, samplers :: Vector AnimationSampler
, name :: Maybe Text
, extensions :: Maybe Object
, extras :: Maybe Value
} deriving (Eq, Show, Generic)
instance FromJSON Animation
instance ToJSON Animation
newtype AnimationSamplerIx = AnimationSamplerIx { unAnimationSamplerIx :: Int }
deriving (Eq, Ord, Show, FromJSON, ToJSON, Generic)
data AnimationSampler = AnimationSampler
{ input :: AccessorIx
, interpolation :: AnimationSamplerInterpolation
, output :: AccessorIx
, extensions :: Maybe Object
, extras :: Maybe Value
} deriving (Eq, Show, Generic)
instance FromJSON AnimationSampler where
parseJSON = withObject "AnimationSampler" \o -> do
input <- o .: "input"
interpolation <- o .:? "interpolation" .!= LINEAR
output <- o .: "output"
extensions <- o .:? "extensions"
extras <- o .:? "extras"
pure AnimationSampler{..}
instance ToJSON AnimationSampler
newtype AnimationSamplerInterpolation = AnimationSamplerInterpolation { unAnimationSamplerInterpolation :: Text }
deriving (Eq, Ord, Show, FromJSON, ToJSON, Generic)
pattern LINEAR :: AnimationSamplerInterpolation
pattern LINEAR = AnimationSamplerInterpolation "LINEAR"
pattern STEP :: AnimationSamplerInterpolation
pattern STEP = AnimationSamplerInterpolation "STEP"
pattern CUBICSPLINE :: AnimationSamplerInterpolation
pattern CUBICSPLINE = AnimationSamplerInterpolation "CUBICSPLINE"
data AnimationChannel = AnimationChannel
{ sampler :: AnimationSamplerIx
, target :: AnimationChannelTarget
, extensions :: Maybe Object
, extras :: Maybe Value
} deriving (Eq, Show, Generic)
instance FromJSON AnimationChannel
instance ToJSON AnimationChannel
data AnimationChannelTarget = AnimationChannelTarget
{ node :: Maybe NodeIx
, path :: AnimationChannelTargetPath
, extensions :: Maybe Object
, extras :: Maybe Value
} deriving (Eq, Show, Generic)
instance FromJSON AnimationChannelTarget
instance ToJSON AnimationChannelTarget
newtype AnimationChannelTargetPath = AnimationChannelTargetPath { unAnimationChannelTargetPath :: Text }
deriving (Eq, Ord, Show, FromJSON, ToJSON, Generic)
pattern TRANSLATION :: AnimationChannelTargetPath
pattern TRANSLATION = AnimationChannelTargetPath "translation"
pattern ROTATION :: AnimationChannelTargetPath
pattern ROTATION = AnimationChannelTargetPath "rotation"
pattern SCALE :: AnimationChannelTargetPath
pattern SCALE = AnimationChannelTargetPath "scale"
pattern WEIGHTS :: AnimationChannelTargetPath
pattern WEIGHTS = AnimationChannelTargetPath "weights"