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 { AnimationIx -> Int
unAnimationIx :: Int }
deriving (AnimationIx -> AnimationIx -> Bool
(AnimationIx -> AnimationIx -> Bool)
-> (AnimationIx -> AnimationIx -> Bool) -> Eq AnimationIx
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AnimationIx -> AnimationIx -> Bool
$c/= :: AnimationIx -> AnimationIx -> Bool
== :: AnimationIx -> AnimationIx -> Bool
$c== :: AnimationIx -> AnimationIx -> Bool
Eq, Eq AnimationIx
Eq AnimationIx
-> (AnimationIx -> AnimationIx -> Ordering)
-> (AnimationIx -> AnimationIx -> Bool)
-> (AnimationIx -> AnimationIx -> Bool)
-> (AnimationIx -> AnimationIx -> Bool)
-> (AnimationIx -> AnimationIx -> Bool)
-> (AnimationIx -> AnimationIx -> AnimationIx)
-> (AnimationIx -> AnimationIx -> AnimationIx)
-> Ord AnimationIx
AnimationIx -> AnimationIx -> Bool
AnimationIx -> AnimationIx -> Ordering
AnimationIx -> AnimationIx -> AnimationIx
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AnimationIx -> AnimationIx -> AnimationIx
$cmin :: AnimationIx -> AnimationIx -> AnimationIx
max :: AnimationIx -> AnimationIx -> AnimationIx
$cmax :: AnimationIx -> AnimationIx -> AnimationIx
>= :: AnimationIx -> AnimationIx -> Bool
$c>= :: AnimationIx -> AnimationIx -> Bool
> :: AnimationIx -> AnimationIx -> Bool
$c> :: AnimationIx -> AnimationIx -> Bool
<= :: AnimationIx -> AnimationIx -> Bool
$c<= :: AnimationIx -> AnimationIx -> Bool
< :: AnimationIx -> AnimationIx -> Bool
$c< :: AnimationIx -> AnimationIx -> Bool
compare :: AnimationIx -> AnimationIx -> Ordering
$ccompare :: AnimationIx -> AnimationIx -> Ordering
$cp1Ord :: Eq AnimationIx
Ord, Int -> AnimationIx -> ShowS
[AnimationIx] -> ShowS
AnimationIx -> String
(Int -> AnimationIx -> ShowS)
-> (AnimationIx -> String)
-> ([AnimationIx] -> ShowS)
-> Show AnimationIx
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AnimationIx] -> ShowS
$cshowList :: [AnimationIx] -> ShowS
show :: AnimationIx -> String
$cshow :: AnimationIx -> String
showsPrec :: Int -> AnimationIx -> ShowS
$cshowsPrec :: Int -> AnimationIx -> ShowS
Show, Value -> Parser [AnimationIx]
Value -> Parser AnimationIx
(Value -> Parser AnimationIx)
-> (Value -> Parser [AnimationIx]) -> FromJSON AnimationIx
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [AnimationIx]
$cparseJSONList :: Value -> Parser [AnimationIx]
parseJSON :: Value -> Parser AnimationIx
$cparseJSON :: Value -> Parser AnimationIx
FromJSON, [AnimationIx] -> Encoding
[AnimationIx] -> Value
AnimationIx -> Encoding
AnimationIx -> Value
(AnimationIx -> Value)
-> (AnimationIx -> Encoding)
-> ([AnimationIx] -> Value)
-> ([AnimationIx] -> Encoding)
-> ToJSON AnimationIx
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [AnimationIx] -> Encoding
$ctoEncodingList :: [AnimationIx] -> Encoding
toJSONList :: [AnimationIx] -> Value
$ctoJSONList :: [AnimationIx] -> Value
toEncoding :: AnimationIx -> Encoding
$ctoEncoding :: AnimationIx -> Encoding
toJSON :: AnimationIx -> Value
$ctoJSON :: AnimationIx -> Value
ToJSON, (forall x. AnimationIx -> Rep AnimationIx x)
-> (forall x. Rep AnimationIx x -> AnimationIx)
-> Generic AnimationIx
forall x. Rep AnimationIx x -> AnimationIx
forall x. AnimationIx -> Rep AnimationIx x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AnimationIx x -> AnimationIx
$cfrom :: forall x. AnimationIx -> Rep AnimationIx x
Generic)
data Animation = Animation
{ Animation -> Vector AnimationChannel
channels :: Vector AnimationChannel
, Animation -> Vector AnimationSampler
samplers :: Vector AnimationSampler
, Animation -> Maybe Text
name :: Maybe Text
, Animation -> Maybe Object
extensions :: Maybe Object
, :: Maybe Value
} deriving (Animation -> Animation -> Bool
(Animation -> Animation -> Bool)
-> (Animation -> Animation -> Bool) -> Eq Animation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Animation -> Animation -> Bool
$c/= :: Animation -> Animation -> Bool
== :: Animation -> Animation -> Bool
$c== :: Animation -> Animation -> Bool
Eq, Int -> Animation -> ShowS
[Animation] -> ShowS
Animation -> String
(Int -> Animation -> ShowS)
-> (Animation -> String)
-> ([Animation] -> ShowS)
-> Show Animation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Animation] -> ShowS
$cshowList :: [Animation] -> ShowS
show :: Animation -> String
$cshow :: Animation -> String
showsPrec :: Int -> Animation -> ShowS
$cshowsPrec :: Int -> Animation -> ShowS
Show, (forall x. Animation -> Rep Animation x)
-> (forall x. Rep Animation x -> Animation) -> Generic Animation
forall x. Rep Animation x -> Animation
forall x. Animation -> Rep Animation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Animation x -> Animation
$cfrom :: forall x. Animation -> Rep Animation x
Generic)
instance FromJSON Animation
instance ToJSON Animation
newtype AnimationSamplerIx = AnimationSamplerIx { AnimationSamplerIx -> Int
unAnimationSamplerIx :: Int }
deriving (AnimationSamplerIx -> AnimationSamplerIx -> Bool
(AnimationSamplerIx -> AnimationSamplerIx -> Bool)
-> (AnimationSamplerIx -> AnimationSamplerIx -> Bool)
-> Eq AnimationSamplerIx
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AnimationSamplerIx -> AnimationSamplerIx -> Bool
$c/= :: AnimationSamplerIx -> AnimationSamplerIx -> Bool
== :: AnimationSamplerIx -> AnimationSamplerIx -> Bool
$c== :: AnimationSamplerIx -> AnimationSamplerIx -> Bool
Eq, Eq AnimationSamplerIx
Eq AnimationSamplerIx
-> (AnimationSamplerIx -> AnimationSamplerIx -> Ordering)
-> (AnimationSamplerIx -> AnimationSamplerIx -> Bool)
-> (AnimationSamplerIx -> AnimationSamplerIx -> Bool)
-> (AnimationSamplerIx -> AnimationSamplerIx -> Bool)
-> (AnimationSamplerIx -> AnimationSamplerIx -> Bool)
-> (AnimationSamplerIx -> AnimationSamplerIx -> AnimationSamplerIx)
-> (AnimationSamplerIx -> AnimationSamplerIx -> AnimationSamplerIx)
-> Ord AnimationSamplerIx
AnimationSamplerIx -> AnimationSamplerIx -> Bool
AnimationSamplerIx -> AnimationSamplerIx -> Ordering
AnimationSamplerIx -> AnimationSamplerIx -> AnimationSamplerIx
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AnimationSamplerIx -> AnimationSamplerIx -> AnimationSamplerIx
$cmin :: AnimationSamplerIx -> AnimationSamplerIx -> AnimationSamplerIx
max :: AnimationSamplerIx -> AnimationSamplerIx -> AnimationSamplerIx
$cmax :: AnimationSamplerIx -> AnimationSamplerIx -> AnimationSamplerIx
>= :: AnimationSamplerIx -> AnimationSamplerIx -> Bool
$c>= :: AnimationSamplerIx -> AnimationSamplerIx -> Bool
> :: AnimationSamplerIx -> AnimationSamplerIx -> Bool
$c> :: AnimationSamplerIx -> AnimationSamplerIx -> Bool
<= :: AnimationSamplerIx -> AnimationSamplerIx -> Bool
$c<= :: AnimationSamplerIx -> AnimationSamplerIx -> Bool
< :: AnimationSamplerIx -> AnimationSamplerIx -> Bool
$c< :: AnimationSamplerIx -> AnimationSamplerIx -> Bool
compare :: AnimationSamplerIx -> AnimationSamplerIx -> Ordering
$ccompare :: AnimationSamplerIx -> AnimationSamplerIx -> Ordering
$cp1Ord :: Eq AnimationSamplerIx
Ord, Int -> AnimationSamplerIx -> ShowS
[AnimationSamplerIx] -> ShowS
AnimationSamplerIx -> String
(Int -> AnimationSamplerIx -> ShowS)
-> (AnimationSamplerIx -> String)
-> ([AnimationSamplerIx] -> ShowS)
-> Show AnimationSamplerIx
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AnimationSamplerIx] -> ShowS
$cshowList :: [AnimationSamplerIx] -> ShowS
show :: AnimationSamplerIx -> String
$cshow :: AnimationSamplerIx -> String
showsPrec :: Int -> AnimationSamplerIx -> ShowS
$cshowsPrec :: Int -> AnimationSamplerIx -> ShowS
Show, Value -> Parser [AnimationSamplerIx]
Value -> Parser AnimationSamplerIx
(Value -> Parser AnimationSamplerIx)
-> (Value -> Parser [AnimationSamplerIx])
-> FromJSON AnimationSamplerIx
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [AnimationSamplerIx]
$cparseJSONList :: Value -> Parser [AnimationSamplerIx]
parseJSON :: Value -> Parser AnimationSamplerIx
$cparseJSON :: Value -> Parser AnimationSamplerIx
FromJSON, [AnimationSamplerIx] -> Encoding
[AnimationSamplerIx] -> Value
AnimationSamplerIx -> Encoding
AnimationSamplerIx -> Value
(AnimationSamplerIx -> Value)
-> (AnimationSamplerIx -> Encoding)
-> ([AnimationSamplerIx] -> Value)
-> ([AnimationSamplerIx] -> Encoding)
-> ToJSON AnimationSamplerIx
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [AnimationSamplerIx] -> Encoding
$ctoEncodingList :: [AnimationSamplerIx] -> Encoding
toJSONList :: [AnimationSamplerIx] -> Value
$ctoJSONList :: [AnimationSamplerIx] -> Value
toEncoding :: AnimationSamplerIx -> Encoding
$ctoEncoding :: AnimationSamplerIx -> Encoding
toJSON :: AnimationSamplerIx -> Value
$ctoJSON :: AnimationSamplerIx -> Value
ToJSON, (forall x. AnimationSamplerIx -> Rep AnimationSamplerIx x)
-> (forall x. Rep AnimationSamplerIx x -> AnimationSamplerIx)
-> Generic AnimationSamplerIx
forall x. Rep AnimationSamplerIx x -> AnimationSamplerIx
forall x. AnimationSamplerIx -> Rep AnimationSamplerIx x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AnimationSamplerIx x -> AnimationSamplerIx
$cfrom :: forall x. AnimationSamplerIx -> Rep AnimationSamplerIx x
Generic)
data AnimationSampler = AnimationSampler
{ AnimationSampler -> AccessorIx
input :: AccessorIx
, AnimationSampler -> AnimationSamplerInterpolation
interpolation :: AnimationSamplerInterpolation
, AnimationSampler -> AccessorIx
output :: AccessorIx
, AnimationSampler -> Maybe Object
extensions :: Maybe Object
, :: Maybe Value
} deriving (AnimationSampler -> AnimationSampler -> Bool
(AnimationSampler -> AnimationSampler -> Bool)
-> (AnimationSampler -> AnimationSampler -> Bool)
-> Eq AnimationSampler
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AnimationSampler -> AnimationSampler -> Bool
$c/= :: AnimationSampler -> AnimationSampler -> Bool
== :: AnimationSampler -> AnimationSampler -> Bool
$c== :: AnimationSampler -> AnimationSampler -> Bool
Eq, Int -> AnimationSampler -> ShowS
[AnimationSampler] -> ShowS
AnimationSampler -> String
(Int -> AnimationSampler -> ShowS)
-> (AnimationSampler -> String)
-> ([AnimationSampler] -> ShowS)
-> Show AnimationSampler
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AnimationSampler] -> ShowS
$cshowList :: [AnimationSampler] -> ShowS
show :: AnimationSampler -> String
$cshow :: AnimationSampler -> String
showsPrec :: Int -> AnimationSampler -> ShowS
$cshowsPrec :: Int -> AnimationSampler -> ShowS
Show, (forall x. AnimationSampler -> Rep AnimationSampler x)
-> (forall x. Rep AnimationSampler x -> AnimationSampler)
-> Generic AnimationSampler
forall x. Rep AnimationSampler x -> AnimationSampler
forall x. AnimationSampler -> Rep AnimationSampler x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AnimationSampler x -> AnimationSampler
$cfrom :: forall x. AnimationSampler -> Rep AnimationSampler x
Generic)
instance FromJSON AnimationSampler where
parseJSON :: Value -> Parser AnimationSampler
parseJSON = String
-> (Object -> Parser AnimationSampler)
-> Value
-> Parser AnimationSampler
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"AnimationSampler" \Object
o -> do
AccessorIx
input <- Object
o Object -> Key -> Parser AccessorIx
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"input"
AnimationSamplerInterpolation
interpolation <- Object
o Object -> Key -> Parser (Maybe AnimationSamplerInterpolation)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"interpolation" Parser (Maybe AnimationSamplerInterpolation)
-> AnimationSamplerInterpolation
-> Parser AnimationSamplerInterpolation
forall a. Parser (Maybe a) -> a -> Parser a
.!= AnimationSamplerInterpolation
LINEAR
AccessorIx
output <- Object
o Object -> Key -> Parser AccessorIx
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"output"
Maybe Object
extensions <- Object
o Object -> Key -> Parser (Maybe Object)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"extensions"
Maybe Value
extras <- Object
o Object -> Key -> Parser (Maybe Value)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"extras"
pure AnimationSampler :: AccessorIx
-> AnimationSamplerInterpolation
-> AccessorIx
-> Maybe Object
-> Maybe Value
-> AnimationSampler
AnimationSampler{Maybe Value
Maybe Object
AccessorIx
AnimationSamplerInterpolation
extras :: Maybe Value
extensions :: Maybe Object
output :: AccessorIx
interpolation :: AnimationSamplerInterpolation
input :: AccessorIx
$sel:extras:AnimationSampler :: Maybe Value
$sel:extensions:AnimationSampler :: Maybe Object
$sel:output:AnimationSampler :: AccessorIx
$sel:interpolation:AnimationSampler :: AnimationSamplerInterpolation
$sel:input:AnimationSampler :: AccessorIx
..}
instance ToJSON AnimationSampler
newtype AnimationSamplerInterpolation = AnimationSamplerInterpolation { AnimationSamplerInterpolation -> Text
unAnimationSamplerInterpolation :: Text }
deriving (AnimationSamplerInterpolation
-> AnimationSamplerInterpolation -> Bool
(AnimationSamplerInterpolation
-> AnimationSamplerInterpolation -> Bool)
-> (AnimationSamplerInterpolation
-> AnimationSamplerInterpolation -> Bool)
-> Eq AnimationSamplerInterpolation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AnimationSamplerInterpolation
-> AnimationSamplerInterpolation -> Bool
$c/= :: AnimationSamplerInterpolation
-> AnimationSamplerInterpolation -> Bool
== :: AnimationSamplerInterpolation
-> AnimationSamplerInterpolation -> Bool
$c== :: AnimationSamplerInterpolation
-> AnimationSamplerInterpolation -> Bool
Eq, Eq AnimationSamplerInterpolation
Eq AnimationSamplerInterpolation
-> (AnimationSamplerInterpolation
-> AnimationSamplerInterpolation -> Ordering)
-> (AnimationSamplerInterpolation
-> AnimationSamplerInterpolation -> Bool)
-> (AnimationSamplerInterpolation
-> AnimationSamplerInterpolation -> Bool)
-> (AnimationSamplerInterpolation
-> AnimationSamplerInterpolation -> Bool)
-> (AnimationSamplerInterpolation
-> AnimationSamplerInterpolation -> Bool)
-> (AnimationSamplerInterpolation
-> AnimationSamplerInterpolation -> AnimationSamplerInterpolation)
-> (AnimationSamplerInterpolation
-> AnimationSamplerInterpolation -> AnimationSamplerInterpolation)
-> Ord AnimationSamplerInterpolation
AnimationSamplerInterpolation
-> AnimationSamplerInterpolation -> Bool
AnimationSamplerInterpolation
-> AnimationSamplerInterpolation -> Ordering
AnimationSamplerInterpolation
-> AnimationSamplerInterpolation -> AnimationSamplerInterpolation
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AnimationSamplerInterpolation
-> AnimationSamplerInterpolation -> AnimationSamplerInterpolation
$cmin :: AnimationSamplerInterpolation
-> AnimationSamplerInterpolation -> AnimationSamplerInterpolation
max :: AnimationSamplerInterpolation
-> AnimationSamplerInterpolation -> AnimationSamplerInterpolation
$cmax :: AnimationSamplerInterpolation
-> AnimationSamplerInterpolation -> AnimationSamplerInterpolation
>= :: AnimationSamplerInterpolation
-> AnimationSamplerInterpolation -> Bool
$c>= :: AnimationSamplerInterpolation
-> AnimationSamplerInterpolation -> Bool
> :: AnimationSamplerInterpolation
-> AnimationSamplerInterpolation -> Bool
$c> :: AnimationSamplerInterpolation
-> AnimationSamplerInterpolation -> Bool
<= :: AnimationSamplerInterpolation
-> AnimationSamplerInterpolation -> Bool
$c<= :: AnimationSamplerInterpolation
-> AnimationSamplerInterpolation -> Bool
< :: AnimationSamplerInterpolation
-> AnimationSamplerInterpolation -> Bool
$c< :: AnimationSamplerInterpolation
-> AnimationSamplerInterpolation -> Bool
compare :: AnimationSamplerInterpolation
-> AnimationSamplerInterpolation -> Ordering
$ccompare :: AnimationSamplerInterpolation
-> AnimationSamplerInterpolation -> Ordering
$cp1Ord :: Eq AnimationSamplerInterpolation
Ord, Int -> AnimationSamplerInterpolation -> ShowS
[AnimationSamplerInterpolation] -> ShowS
AnimationSamplerInterpolation -> String
(Int -> AnimationSamplerInterpolation -> ShowS)
-> (AnimationSamplerInterpolation -> String)
-> ([AnimationSamplerInterpolation] -> ShowS)
-> Show AnimationSamplerInterpolation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AnimationSamplerInterpolation] -> ShowS
$cshowList :: [AnimationSamplerInterpolation] -> ShowS
show :: AnimationSamplerInterpolation -> String
$cshow :: AnimationSamplerInterpolation -> String
showsPrec :: Int -> AnimationSamplerInterpolation -> ShowS
$cshowsPrec :: Int -> AnimationSamplerInterpolation -> ShowS
Show, Value -> Parser [AnimationSamplerInterpolation]
Value -> Parser AnimationSamplerInterpolation
(Value -> Parser AnimationSamplerInterpolation)
-> (Value -> Parser [AnimationSamplerInterpolation])
-> FromJSON AnimationSamplerInterpolation
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [AnimationSamplerInterpolation]
$cparseJSONList :: Value -> Parser [AnimationSamplerInterpolation]
parseJSON :: Value -> Parser AnimationSamplerInterpolation
$cparseJSON :: Value -> Parser AnimationSamplerInterpolation
FromJSON, [AnimationSamplerInterpolation] -> Encoding
[AnimationSamplerInterpolation] -> Value
AnimationSamplerInterpolation -> Encoding
AnimationSamplerInterpolation -> Value
(AnimationSamplerInterpolation -> Value)
-> (AnimationSamplerInterpolation -> Encoding)
-> ([AnimationSamplerInterpolation] -> Value)
-> ([AnimationSamplerInterpolation] -> Encoding)
-> ToJSON AnimationSamplerInterpolation
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [AnimationSamplerInterpolation] -> Encoding
$ctoEncodingList :: [AnimationSamplerInterpolation] -> Encoding
toJSONList :: [AnimationSamplerInterpolation] -> Value
$ctoJSONList :: [AnimationSamplerInterpolation] -> Value
toEncoding :: AnimationSamplerInterpolation -> Encoding
$ctoEncoding :: AnimationSamplerInterpolation -> Encoding
toJSON :: AnimationSamplerInterpolation -> Value
$ctoJSON :: AnimationSamplerInterpolation -> Value
ToJSON, (forall x.
AnimationSamplerInterpolation
-> Rep AnimationSamplerInterpolation x)
-> (forall x.
Rep AnimationSamplerInterpolation x
-> AnimationSamplerInterpolation)
-> Generic AnimationSamplerInterpolation
forall x.
Rep AnimationSamplerInterpolation x
-> AnimationSamplerInterpolation
forall x.
AnimationSamplerInterpolation
-> Rep AnimationSamplerInterpolation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AnimationSamplerInterpolation x
-> AnimationSamplerInterpolation
$cfrom :: forall x.
AnimationSamplerInterpolation
-> Rep AnimationSamplerInterpolation x
Generic)
pattern LINEAR :: AnimationSamplerInterpolation
pattern $bLINEAR :: AnimationSamplerInterpolation
$mLINEAR :: forall r.
AnimationSamplerInterpolation -> (Void# -> r) -> (Void# -> r) -> r
LINEAR = AnimationSamplerInterpolation "LINEAR"
pattern STEP :: AnimationSamplerInterpolation
pattern $bSTEP :: AnimationSamplerInterpolation
$mSTEP :: forall r.
AnimationSamplerInterpolation -> (Void# -> r) -> (Void# -> r) -> r
STEP = AnimationSamplerInterpolation "STEP"
pattern CUBICSPLINE :: AnimationSamplerInterpolation
pattern $bCUBICSPLINE :: AnimationSamplerInterpolation
$mCUBICSPLINE :: forall r.
AnimationSamplerInterpolation -> (Void# -> r) -> (Void# -> r) -> r
CUBICSPLINE = AnimationSamplerInterpolation "CUBICSPLINE"
data AnimationChannel = AnimationChannel
{ AnimationChannel -> AnimationSamplerIx
sampler :: AnimationSamplerIx
, AnimationChannel -> AnimationChannelTarget
target :: AnimationChannelTarget
, AnimationChannel -> Maybe Object
extensions :: Maybe Object
, :: Maybe Value
} deriving (AnimationChannel -> AnimationChannel -> Bool
(AnimationChannel -> AnimationChannel -> Bool)
-> (AnimationChannel -> AnimationChannel -> Bool)
-> Eq AnimationChannel
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AnimationChannel -> AnimationChannel -> Bool
$c/= :: AnimationChannel -> AnimationChannel -> Bool
== :: AnimationChannel -> AnimationChannel -> Bool
$c== :: AnimationChannel -> AnimationChannel -> Bool
Eq, Int -> AnimationChannel -> ShowS
[AnimationChannel] -> ShowS
AnimationChannel -> String
(Int -> AnimationChannel -> ShowS)
-> (AnimationChannel -> String)
-> ([AnimationChannel] -> ShowS)
-> Show AnimationChannel
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AnimationChannel] -> ShowS
$cshowList :: [AnimationChannel] -> ShowS
show :: AnimationChannel -> String
$cshow :: AnimationChannel -> String
showsPrec :: Int -> AnimationChannel -> ShowS
$cshowsPrec :: Int -> AnimationChannel -> ShowS
Show, (forall x. AnimationChannel -> Rep AnimationChannel x)
-> (forall x. Rep AnimationChannel x -> AnimationChannel)
-> Generic AnimationChannel
forall x. Rep AnimationChannel x -> AnimationChannel
forall x. AnimationChannel -> Rep AnimationChannel x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AnimationChannel x -> AnimationChannel
$cfrom :: forall x. AnimationChannel -> Rep AnimationChannel x
Generic)
instance FromJSON AnimationChannel
instance ToJSON AnimationChannel
data AnimationChannelTarget = AnimationChannelTarget
{ AnimationChannelTarget -> Maybe NodeIx
node :: Maybe NodeIx
, AnimationChannelTarget -> AnimationChannelTargetPath
path :: AnimationChannelTargetPath
, AnimationChannelTarget -> Maybe Object
extensions :: Maybe Object
, :: Maybe Value
} deriving (AnimationChannelTarget -> AnimationChannelTarget -> Bool
(AnimationChannelTarget -> AnimationChannelTarget -> Bool)
-> (AnimationChannelTarget -> AnimationChannelTarget -> Bool)
-> Eq AnimationChannelTarget
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AnimationChannelTarget -> AnimationChannelTarget -> Bool
$c/= :: AnimationChannelTarget -> AnimationChannelTarget -> Bool
== :: AnimationChannelTarget -> AnimationChannelTarget -> Bool
$c== :: AnimationChannelTarget -> AnimationChannelTarget -> Bool
Eq, Int -> AnimationChannelTarget -> ShowS
[AnimationChannelTarget] -> ShowS
AnimationChannelTarget -> String
(Int -> AnimationChannelTarget -> ShowS)
-> (AnimationChannelTarget -> String)
-> ([AnimationChannelTarget] -> ShowS)
-> Show AnimationChannelTarget
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AnimationChannelTarget] -> ShowS
$cshowList :: [AnimationChannelTarget] -> ShowS
show :: AnimationChannelTarget -> String
$cshow :: AnimationChannelTarget -> String
showsPrec :: Int -> AnimationChannelTarget -> ShowS
$cshowsPrec :: Int -> AnimationChannelTarget -> ShowS
Show, (forall x. AnimationChannelTarget -> Rep AnimationChannelTarget x)
-> (forall x.
Rep AnimationChannelTarget x -> AnimationChannelTarget)
-> Generic AnimationChannelTarget
forall x. Rep AnimationChannelTarget x -> AnimationChannelTarget
forall x. AnimationChannelTarget -> Rep AnimationChannelTarget x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AnimationChannelTarget x -> AnimationChannelTarget
$cfrom :: forall x. AnimationChannelTarget -> Rep AnimationChannelTarget x
Generic)
instance FromJSON AnimationChannelTarget
instance ToJSON AnimationChannelTarget
newtype AnimationChannelTargetPath = AnimationChannelTargetPath { AnimationChannelTargetPath -> Text
unAnimationChannelTargetPath :: Text }
deriving (AnimationChannelTargetPath -> AnimationChannelTargetPath -> Bool
(AnimationChannelTargetPath -> AnimationChannelTargetPath -> Bool)
-> (AnimationChannelTargetPath
-> AnimationChannelTargetPath -> Bool)
-> Eq AnimationChannelTargetPath
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AnimationChannelTargetPath -> AnimationChannelTargetPath -> Bool
$c/= :: AnimationChannelTargetPath -> AnimationChannelTargetPath -> Bool
== :: AnimationChannelTargetPath -> AnimationChannelTargetPath -> Bool
$c== :: AnimationChannelTargetPath -> AnimationChannelTargetPath -> Bool
Eq, Eq AnimationChannelTargetPath
Eq AnimationChannelTargetPath
-> (AnimationChannelTargetPath
-> AnimationChannelTargetPath -> Ordering)
-> (AnimationChannelTargetPath
-> AnimationChannelTargetPath -> Bool)
-> (AnimationChannelTargetPath
-> AnimationChannelTargetPath -> Bool)
-> (AnimationChannelTargetPath
-> AnimationChannelTargetPath -> Bool)
-> (AnimationChannelTargetPath
-> AnimationChannelTargetPath -> Bool)
-> (AnimationChannelTargetPath
-> AnimationChannelTargetPath -> AnimationChannelTargetPath)
-> (AnimationChannelTargetPath
-> AnimationChannelTargetPath -> AnimationChannelTargetPath)
-> Ord AnimationChannelTargetPath
AnimationChannelTargetPath -> AnimationChannelTargetPath -> Bool
AnimationChannelTargetPath
-> AnimationChannelTargetPath -> Ordering
AnimationChannelTargetPath
-> AnimationChannelTargetPath -> AnimationChannelTargetPath
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AnimationChannelTargetPath
-> AnimationChannelTargetPath -> AnimationChannelTargetPath
$cmin :: AnimationChannelTargetPath
-> AnimationChannelTargetPath -> AnimationChannelTargetPath
max :: AnimationChannelTargetPath
-> AnimationChannelTargetPath -> AnimationChannelTargetPath
$cmax :: AnimationChannelTargetPath
-> AnimationChannelTargetPath -> AnimationChannelTargetPath
>= :: AnimationChannelTargetPath -> AnimationChannelTargetPath -> Bool
$c>= :: AnimationChannelTargetPath -> AnimationChannelTargetPath -> Bool
> :: AnimationChannelTargetPath -> AnimationChannelTargetPath -> Bool
$c> :: AnimationChannelTargetPath -> AnimationChannelTargetPath -> Bool
<= :: AnimationChannelTargetPath -> AnimationChannelTargetPath -> Bool
$c<= :: AnimationChannelTargetPath -> AnimationChannelTargetPath -> Bool
< :: AnimationChannelTargetPath -> AnimationChannelTargetPath -> Bool
$c< :: AnimationChannelTargetPath -> AnimationChannelTargetPath -> Bool
compare :: AnimationChannelTargetPath
-> AnimationChannelTargetPath -> Ordering
$ccompare :: AnimationChannelTargetPath
-> AnimationChannelTargetPath -> Ordering
$cp1Ord :: Eq AnimationChannelTargetPath
Ord, Int -> AnimationChannelTargetPath -> ShowS
[AnimationChannelTargetPath] -> ShowS
AnimationChannelTargetPath -> String
(Int -> AnimationChannelTargetPath -> ShowS)
-> (AnimationChannelTargetPath -> String)
-> ([AnimationChannelTargetPath] -> ShowS)
-> Show AnimationChannelTargetPath
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AnimationChannelTargetPath] -> ShowS
$cshowList :: [AnimationChannelTargetPath] -> ShowS
show :: AnimationChannelTargetPath -> String
$cshow :: AnimationChannelTargetPath -> String
showsPrec :: Int -> AnimationChannelTargetPath -> ShowS
$cshowsPrec :: Int -> AnimationChannelTargetPath -> ShowS
Show, Value -> Parser [AnimationChannelTargetPath]
Value -> Parser AnimationChannelTargetPath
(Value -> Parser AnimationChannelTargetPath)
-> (Value -> Parser [AnimationChannelTargetPath])
-> FromJSON AnimationChannelTargetPath
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [AnimationChannelTargetPath]
$cparseJSONList :: Value -> Parser [AnimationChannelTargetPath]
parseJSON :: Value -> Parser AnimationChannelTargetPath
$cparseJSON :: Value -> Parser AnimationChannelTargetPath
FromJSON, [AnimationChannelTargetPath] -> Encoding
[AnimationChannelTargetPath] -> Value
AnimationChannelTargetPath -> Encoding
AnimationChannelTargetPath -> Value
(AnimationChannelTargetPath -> Value)
-> (AnimationChannelTargetPath -> Encoding)
-> ([AnimationChannelTargetPath] -> Value)
-> ([AnimationChannelTargetPath] -> Encoding)
-> ToJSON AnimationChannelTargetPath
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [AnimationChannelTargetPath] -> Encoding
$ctoEncodingList :: [AnimationChannelTargetPath] -> Encoding
toJSONList :: [AnimationChannelTargetPath] -> Value
$ctoJSONList :: [AnimationChannelTargetPath] -> Value
toEncoding :: AnimationChannelTargetPath -> Encoding
$ctoEncoding :: AnimationChannelTargetPath -> Encoding
toJSON :: AnimationChannelTargetPath -> Value
$ctoJSON :: AnimationChannelTargetPath -> Value
ToJSON, (forall x.
AnimationChannelTargetPath -> Rep AnimationChannelTargetPath x)
-> (forall x.
Rep AnimationChannelTargetPath x -> AnimationChannelTargetPath)
-> Generic AnimationChannelTargetPath
forall x.
Rep AnimationChannelTargetPath x -> AnimationChannelTargetPath
forall x.
AnimationChannelTargetPath -> Rep AnimationChannelTargetPath x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AnimationChannelTargetPath x -> AnimationChannelTargetPath
$cfrom :: forall x.
AnimationChannelTargetPath -> Rep AnimationChannelTargetPath x
Generic)
pattern TRANSLATION :: AnimationChannelTargetPath
pattern $bTRANSLATION :: AnimationChannelTargetPath
$mTRANSLATION :: forall r.
AnimationChannelTargetPath -> (Void# -> r) -> (Void# -> r) -> r
TRANSLATION = AnimationChannelTargetPath "translation"
pattern ROTATION :: AnimationChannelTargetPath
pattern $bROTATION :: AnimationChannelTargetPath
$mROTATION :: forall r.
AnimationChannelTargetPath -> (Void# -> r) -> (Void# -> r) -> r
ROTATION = AnimationChannelTargetPath "rotation"
pattern SCALE :: AnimationChannelTargetPath
pattern $bSCALE :: AnimationChannelTargetPath
$mSCALE :: forall r.
AnimationChannelTargetPath -> (Void# -> r) -> (Void# -> r) -> r
SCALE = AnimationChannelTargetPath "scale"
pattern WEIGHTS :: AnimationChannelTargetPath
pattern $bWEIGHTS :: AnimationChannelTargetPath
$mWEIGHTS :: forall r.
AnimationChannelTargetPath -> (Void# -> r) -> (Void# -> r) -> r
WEIGHTS = AnimationChannelTargetPath "weights"