gltf-codec-0.1.0.4: glTF scene loader
Safe HaskellNone
LanguageHaskell2010

Codec.GlTF.TextureInfo

Synopsis

Documentation

data TextureInfo a Source #

Reference to a texture.

Constructors

TextureInfo 

Fields

  • index :: Int
     
  • texCoord :: Int

    This integer value is used to construct a string in the format TEXCOORD_index which is a reference to a key in mesh.primitives.attributes (e.g. A value of 0 corresponds to TEXCOORD_0).

    Mesh must have corresponding texture coordinate attributes for the material to be applicable to it.

  • subtype :: a
     
  • extensions :: Maybe Object
     
  • extras :: Maybe Value
     

Instances

Instances details
Eq a => Eq (TextureInfo a) Source # 
Instance details

Defined in Codec.GlTF.TextureInfo

Show a => Show (TextureInfo a) Source # 
Instance details

Defined in Codec.GlTF.TextureInfo

Generic (TextureInfo a) Source # 
Instance details

Defined in Codec.GlTF.TextureInfo

Associated Types

type Rep (TextureInfo a) :: Type -> Type #

Methods

from :: TextureInfo a -> Rep (TextureInfo a) x #

to :: Rep (TextureInfo a) x -> TextureInfo a #

ToJSON a => ToJSON (TextureInfo a) Source # 
Instance details

Defined in Codec.GlTF.TextureInfo

FromJSON a => FromJSON (TextureInfo a) Source # 
Instance details

Defined in Codec.GlTF.TextureInfo

type Rep (TextureInfo a) Source # 
Instance details

Defined in Codec.GlTF.TextureInfo

type Rep (TextureInfo a) = D1 ('MetaData "TextureInfo" "Codec.GlTF.TextureInfo" "gltf-codec-0.1.0.4-4VoQsGaCivs2IcxkZWD1XT" 'False) (C1 ('MetaCons "TextureInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "index") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "texCoord") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "subtype") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a) :*: (S1 ('MetaSel ('Just "extensions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Object)) :*: S1 ('MetaSel ('Just "extras") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Value))))))

type TextureInfo_ = TextureInfo Basic Source #

TextureInfo without extra fields.

data Basic Source #

Placeholder for TextureInfo objects without extra fields.

Constructors

Basic 

Instances

Instances details
Eq Basic Source # 
Instance details

Defined in Codec.GlTF.TextureInfo

Methods

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

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

Ord Basic Source # 
Instance details

Defined in Codec.GlTF.TextureInfo

Methods

compare :: Basic -> Basic -> Ordering #

(<) :: Basic -> Basic -> Bool #

(<=) :: Basic -> Basic -> Bool #

(>) :: Basic -> Basic -> Bool #

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

max :: Basic -> Basic -> Basic #

min :: Basic -> Basic -> Basic #

Show Basic Source # 
Instance details

Defined in Codec.GlTF.TextureInfo

Methods

showsPrec :: Int -> Basic -> ShowS #

show :: Basic -> String #

showList :: [Basic] -> ShowS #

Generic Basic Source # 
Instance details

Defined in Codec.GlTF.TextureInfo

Associated Types

type Rep Basic :: Type -> Type #

Methods

from :: Basic -> Rep Basic x #

to :: Rep Basic x -> Basic #

ToJSON Basic Source # 
Instance details

Defined in Codec.GlTF.TextureInfo

FromJSON Basic Source # 
Instance details

Defined in Codec.GlTF.TextureInfo

type Rep Basic Source # 
Instance details

Defined in Codec.GlTF.TextureInfo

type Rep Basic = D1 ('MetaData "Basic" "Codec.GlTF.TextureInfo" "gltf-codec-0.1.0.4-4VoQsGaCivs2IcxkZWD1XT" 'False) (C1 ('MetaCons "Basic" 'PrefixI 'False) (U1 :: Type -> Type))