gltf-codec-0.1.0.1: glTF scene loader

Safe HaskellNone
LanguageHaskell2010

Codec.GlTF.Node

Synopsis

Documentation

newtype NodeIx Source #

Constructors

NodeIx 

Fields

Instances
Eq NodeIx Source # 
Instance details

Defined in Codec.GlTF.Node

Methods

(==) :: NodeIx -> NodeIx -> Bool #

(/=) :: NodeIx -> NodeIx -> Bool #

Ord NodeIx Source # 
Instance details

Defined in Codec.GlTF.Node

Show NodeIx Source # 
Instance details

Defined in Codec.GlTF.Node

Generic NodeIx Source # 
Instance details

Defined in Codec.GlTF.Node

Associated Types

type Rep NodeIx :: Type -> Type #

Methods

from :: NodeIx -> Rep NodeIx x #

to :: Rep NodeIx x -> NodeIx #

ToJSON NodeIx Source # 
Instance details

Defined in Codec.GlTF.Node

FromJSON NodeIx Source # 
Instance details

Defined in Codec.GlTF.Node

type Rep NodeIx Source # 
Instance details

Defined in Codec.GlTF.Node

type Rep NodeIx = D1 (MetaData "NodeIx" "Codec.GlTF.Node" "gltf-codec-0.1.0.1-Gz344sJMz9cG5YV9y1ntpC" True) (C1 (MetaCons "NodeIx" PrefixI True) (S1 (MetaSel (Just "unNodeIx") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

data Node Source #

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 translationrotationscale (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.

Instances
Eq Node Source # 
Instance details

Defined in Codec.GlTF.Node

Methods

(==) :: Node -> Node -> Bool #

(/=) :: Node -> Node -> Bool #

Show Node Source # 
Instance details

Defined in Codec.GlTF.Node

Methods

showsPrec :: Int -> Node -> ShowS #

show :: Node -> String #

showList :: [Node] -> ShowS #

Generic Node Source # 
Instance details

Defined in Codec.GlTF.Node

Associated Types

type Rep Node :: Type -> Type #

Methods

from :: Node -> Rep Node x #

to :: Rep Node x -> Node #

ToJSON Node Source # 
Instance details

Defined in Codec.GlTF.Node

FromJSON Node Source # 
Instance details

Defined in Codec.GlTF.Node

type Rep Node Source # 
Instance details

Defined in Codec.GlTF.Node

type Rep Node = D1 (MetaData "Node" "Codec.GlTF.Node" "gltf-codec-0.1.0.1-Gz344sJMz9cG5YV9y1ntpC" False) (C1 (MetaCons "Node" PrefixI True) (((S1 (MetaSel (Just "camera") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe CameraIx)) :*: (S1 (MetaSel (Just "children") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe (Vector NodeIx))) :*: S1 (MetaSel (Just "skin") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe SkinIx)))) :*: (S1 (MetaSel (Just "matrix") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe NodeMatrix)) :*: (S1 (MetaSel (Just "mesh") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe MeshIx)) :*: S1 (MetaSel (Just "rotation") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe (Float, Float, Float, Float)))))) :*: ((S1 (MetaSel (Just "scale") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe (Float, Float, Float))) :*: (S1 (MetaSel (Just "translation") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe (Float, Float, Float))) :*: S1 (MetaSel (Just "weights") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe (Vector Float))))) :*: (S1 (MetaSel (Just "name") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "extensions") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe Object)) :*: S1 (MetaSel (Just "extras") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe Value)))))))

newtype NodeMatrix Source #

A floating-point 4x4 transformation matrix stored in column-major order.

Constructors

NodeMatrix 
Instances
Eq NodeMatrix Source # 
Instance details

Defined in Codec.GlTF.Node

Ord NodeMatrix Source # 
Instance details

Defined in Codec.GlTF.Node

Show NodeMatrix Source # 
Instance details

Defined in Codec.GlTF.Node

Generic NodeMatrix Source # 
Instance details

Defined in Codec.GlTF.Node

Associated Types

type Rep NodeMatrix :: Type -> Type #

ToJSON NodeMatrix Source # 
Instance details

Defined in Codec.GlTF.Node

FromJSON NodeMatrix Source # 
Instance details

Defined in Codec.GlTF.Node

type Rep NodeMatrix Source # 
Instance details

Defined in Codec.GlTF.Node

type Rep NodeMatrix = D1 (MetaData "NodeMatrix" "Codec.GlTF.Node" "gltf-codec-0.1.0.1-Gz344sJMz9cG5YV9y1ntpC" True) (C1 (MetaCons "NodeMatrix" PrefixI True) (S1 (MetaSel (Just "unNodeMatrix") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Vector Float))))

newtype SkinIx Source #

Constructors

SkinIx 

Fields

Instances
Eq SkinIx Source # 
Instance details

Defined in Codec.GlTF.Node

Methods

(==) :: SkinIx -> SkinIx -> Bool #

(/=) :: SkinIx -> SkinIx -> Bool #

Ord SkinIx Source # 
Instance details

Defined in Codec.GlTF.Node

Show SkinIx Source # 
Instance details

Defined in Codec.GlTF.Node

Generic SkinIx Source # 
Instance details

Defined in Codec.GlTF.Node

Associated Types

type Rep SkinIx :: Type -> Type #

Methods

from :: SkinIx -> Rep SkinIx x #

to :: Rep SkinIx x -> SkinIx #

ToJSON SkinIx Source # 
Instance details

Defined in Codec.GlTF.Node

FromJSON SkinIx Source # 
Instance details

Defined in Codec.GlTF.Node

type Rep SkinIx Source # 
Instance details

Defined in Codec.GlTF.Node

type Rep SkinIx = D1 (MetaData "SkinIx" "Codec.GlTF.Node" "gltf-codec-0.1.0.1-Gz344sJMz9cG5YV9y1ntpC" True) (C1 (MetaCons "SkinIx" PrefixI True) (S1 (MetaSel (Just "unSkinIx") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

data Skin Source #

Joints and matrices defining a skin.

Constructors

Skin 

Fields

Instances
Eq Skin Source # 
Instance details

Defined in Codec.GlTF.Node

Methods

(==) :: Skin -> Skin -> Bool #

(/=) :: Skin -> Skin -> Bool #

Show Skin Source # 
Instance details

Defined in Codec.GlTF.Node

Methods

showsPrec :: Int -> Skin -> ShowS #

show :: Skin -> String #

showList :: [Skin] -> ShowS #

Generic Skin Source # 
Instance details

Defined in Codec.GlTF.Node

Associated Types

type Rep Skin :: Type -> Type #

Methods

from :: Skin -> Rep Skin x #

to :: Rep Skin x -> Skin #

ToJSON Skin Source # 
Instance details

Defined in Codec.GlTF.Node

FromJSON Skin Source # 
Instance details

Defined in Codec.GlTF.Node

type Rep Skin Source # 
Instance details

Defined in Codec.GlTF.Node