-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | glTF scene loader -- -- The package provides basic types to process JSON and "binary" files. -- No further conversion is performed to keep dependencies to a minimum. @package gltf-codec @version 0.1.0.5 module Codec.GLB data GLB GLB :: Header -> Vector Chunk -> GLB [$sel:header:GLB] :: GLB -> Header [$sel:chunks:GLB] :: GLB -> Vector Chunk data Header Header :: Word32 -> Word32 -> Word32 -> Header [$sel:magic:Header] :: Header -> Word32 [$sel:version:Header] :: Header -> Word32 [$sel:length:Header] :: Header -> Word32 data Chunk Chunk :: Word32 -> Word32 -> ByteString -> Chunk [$sel:chunkLength:Chunk] :: Chunk -> Word32 [$sel:chunkType:Chunk] :: Chunk -> Word32 [$sel:chunkData:Chunk] :: Chunk -> ByteString fromByteString :: ByteString -> Either (ByteOffset, String) GLB fromFile :: FilePath -> IO (Either (ByteOffset, String) GLB) instance GHC.Generics.Generic Codec.GLB.Header instance GHC.Show.Show Codec.GLB.Header instance GHC.Classes.Eq Codec.GLB.Header instance GHC.Generics.Generic Codec.GLB.Chunk instance GHC.Show.Show Codec.GLB.Chunk instance GHC.Classes.Eq Codec.GLB.Chunk instance GHC.Generics.Generic Codec.GLB.GLB instance GHC.Show.Show Codec.GLB.GLB instance GHC.Classes.Eq Codec.GLB.GLB instance Data.Binary.Class.Binary Codec.GLB.GLB instance Data.Binary.Class.Binary Codec.GLB.Chunk instance Data.Binary.Class.Binary Codec.GLB.Header module Codec.GlTF.Prelude type Size = Int -- | A type that can be converted from JSON, with the possibility of -- failure. -- -- In many cases, you can get the compiler to generate parsing code for -- you (see below). To begin, let's cover writing an instance by hand. -- -- There are various reasons a conversion could fail. For example, an -- Object could be missing a required key, an Array could -- be of the wrong size, or a value could be of an incompatible type. -- -- The basic ways to signal a failed conversion are as follows: -- -- -- -- prependFailure (or modifyFailure) add more information -- to a parser's error messages. -- -- An example type and instance using typeMismatch and -- prependFailure: -- --
--   -- Allow ourselves to write Text literals.
--   {-# LANGUAGE OverloadedStrings #-}
--   
--   data Coord = Coord { x :: Double, y :: Double }
--   
--   instance FromJSON Coord where
--       parseJSON (Object v) = Coord
--           <$> v .: "x"
--           <*> v .: "y"
--   
--       -- We do not expect a non-Object value here.
--       -- We could use empty to fail, but typeMismatch
--       -- gives a much more informative error message.
--       parseJSON invalid    =
--           prependFailure "parsing Coord failed, "
--               (typeMismatch "Object" invalid)
--   
-- -- For this common case of only being concerned with a single type of -- JSON value, the functions withObject, withScientific, -- etc. are provided. Their use is to be preferred when possible, since -- they are more terse. Using withObject, we can rewrite the above -- instance (assuming the same language extension and data type) as: -- --
--   instance FromJSON Coord where
--       parseJSON = withObject "Coord" $ \v -> Coord
--           <$> v .: "x"
--           <*> v .: "y"
--   
-- -- Instead of manually writing your FromJSON instance, there are -- two options to do it automatically: -- -- -- -- To use the second, simply add a deriving Generic -- clause to your datatype and declare a FromJSON instance for -- your datatype without giving a definition for parseJSON. -- -- For example, the previous example can be simplified to just: -- --
--   {-# LANGUAGE DeriveGeneric #-}
--   
--   import GHC.Generics
--   
--   data Coord = Coord { x :: Double, y :: Double } deriving Generic
--   
--   instance FromJSON Coord
--   
-- -- or using the DerivingVia extension -- --
--   deriving via Generically Coord instance FromJSON Coord
--   
-- -- The default implementation will be equivalent to parseJSON = -- genericParseJSON defaultOptions; if you need -- different options, you can customize the generic decoding by defining: -- --
--   customOptions = defaultOptions
--                   { fieldLabelModifier = map toUpper
--                   }
--   
--   instance FromJSON Coord where
--       parseJSON = genericParseJSON customOptions
--   
class () => FromJSON a parseJSON :: FromJSON a => Value -> Parser a parseJSONList :: FromJSON a => Value -> Parser [a] -- | A type that can be converted to JSON. -- -- Instances in general must specify toJSON and -- should (but don't need to) specify toEncoding. -- -- An example type and instance: -- --
--   -- Allow ourselves to write Text literals.
--   {-# LANGUAGE OverloadedStrings #-}
--   
--   data Coord = Coord { x :: Double, y :: Double }
--   
--   instance ToJSON Coord where
--     toJSON (Coord x y) = object ["x" .= x, "y" .= y]
--   
--     toEncoding (Coord x y) = pairs ("x" .= x <> "y" .= y)
--   
-- -- Instead of manually writing your ToJSON instance, there are two -- options to do it automatically: -- -- -- -- To use the second, simply add a deriving Generic -- clause to your datatype and declare a ToJSON instance. If you -- require nothing other than defaultOptions, it is sufficient to -- write (and this is the only alternative where the default -- toJSON implementation is sufficient): -- --
--   {-# LANGUAGE DeriveGeneric #-}
--   
--   import GHC.Generics
--   
--   data Coord = Coord { x :: Double, y :: Double } deriving Generic
--   
--   instance ToJSON Coord where
--       toEncoding = genericToEncoding defaultOptions
--   
-- -- or more conveniently using the DerivingVia extension -- --
--   deriving via Generically Coord instance ToJSON Coord
--   
-- -- If on the other hand you wish to customize the generic decoding, you -- have to implement both methods: -- --
--   customOptions = defaultOptions
--                   { fieldLabelModifier = map toUpper
--                   }
--   
--   instance ToJSON Coord where
--       toJSON     = genericToJSON customOptions
--       toEncoding = genericToEncoding customOptions
--   
-- -- Previous versions of this library only had the toJSON method. -- Adding toEncoding had two reasons: -- --
    --
  1. toEncoding is more efficient for the common case that the -- output of toJSON is directly serialized to a -- ByteString. Further, expressing either method in terms of the -- other would be non-optimal.
  2. --
  3. The choice of defaults allows a smooth transition for existing -- users: Existing instances that do not define toEncoding still -- compile and have the correct semantics. This is ensured by making the -- default implementation of toEncoding use toJSON. This -- produces correct results, but since it performs an intermediate -- conversion to a Value, it will be less efficient than directly -- emitting an Encoding. (this also means that specifying nothing -- more than instance ToJSON Coord would be sufficient as a -- generically decoding instance, but there probably exists no good -- reason to not specify toEncoding in new instances.)
  4. --
class () => ToJSON a -- | Convert a Haskell value to a JSON-friendly intermediate type. toJSON :: ToJSON a => a -> Value -- | Encode a Haskell value as JSON. -- -- The default implementation of this method creates an intermediate -- Value using toJSON. This provides source-level -- compatibility for people upgrading from older versions of this -- library, but obviously offers no performance advantage. -- -- To benefit from direct encoding, you must provide an -- implementation for this method. The easiest way to do so is by having -- your types implement Generic using the DeriveGeneric -- extension, and then have GHC generate a method body as follows. -- --
--   instance ToJSON Coord where
--       toEncoding = genericToEncoding defaultOptions
--   
toEncoding :: ToJSON a => a -> Encoding toJSONList :: ToJSON a => [a] -> Value toEncodingList :: ToJSON a => [a] -> Encoding -- | Representable types of kind *. This class is derivable in GHC -- with the DeriveGeneric flag on. -- -- A Generic instance must satisfy the following laws: -- --
--   from . toid
--   to . fromid
--   
class () => Generic a gParseJSON :: _ => Value -> Parser a gToJSON :: _ => a -> Value -- | A map from keys to values. A map cannot contain duplicate keys; each -- key can map to at most one value. data () => HashMap k v -- | A JSON "object" (key/value map). type Object = KeyMap Value -- | An arbitrary-precision number represented using scientific -- notation. -- -- This type describes the set of all Reals which have a -- finite decimal expansion. -- -- A scientific number with coefficient c and -- base10Exponent e corresponds to the Fractional -- number: fromInteger c * 10 ^^ e data () => Scientific -- | A space efficient, packed, unboxed Unicode text type. data () => Text -- | A JSON value represented as a Haskell value. data () => Value data () => Vector a -- | withText name f value applies f to the -- Text when value is a String and fails -- otherwise. -- --

Error message example

-- --
--   withText "MyType" f Null
--   -- Error: "parsing MyType failed, expected String, but encountered Null"
--   
withText :: String -> (Text -> Parser a) -> Value -> Parser a -- | withObject name f value applies f to the -- Object when value is an Object and fails -- otherwise. -- --

Error message example

-- --
--   withObject "MyType" f (String "oops")
--   -- Error: "parsing MyType failed, expected Object, but encountered String"
--   
withObject :: String -> (Object -> Parser a) -> Value -> Parser a -- | Retrieve the value associated with the given key of an Object. -- The result is empty if the key is not present or the value -- cannot be converted to the desired type. -- -- This accessor is appropriate if the key and value must be -- present in an object for it to be valid. If the key and value are -- optional, use .:? instead. (.:) :: FromJSON a => Object -> Key -> Parser a -- | Retrieve the value associated with the given key of an Object. -- The result is Nothing if the key is not present or if its value -- is Null, or empty if the value cannot be converted to -- the desired type. -- -- This accessor is most useful if the key and value can be absent from -- an object without affecting its validity. If the key and value are -- mandatory, use .: instead. (.:?) :: FromJSON a => Object -> Key -> Parser (Maybe a) -- | Helper for use in combination with .:? to provide default -- values for optional JSON object fields. -- -- This combinator is most useful if the key and value can be absent from -- an object without affecting its validity and we know a default value -- to assign in that case. If the key and value are mandatory, use -- .: instead. -- -- Example usage: -- --
--   v1 <- o .:? "opt_field_with_dfl" .!= "default_val"
--   v2 <- o .:  "mandatory_field"
--   v3 <- o .:? "opt_field2"
--   
(.!=) :: Parser (Maybe a) -> a -> Parser a module Codec.GlTF.Camera newtype CameraIx CameraIx :: Int -> CameraIx [$sel:unCameraIx:CameraIx] :: CameraIx -> Int -- | A camera's projection. -- -- A node can reference a camera to apply a transform to place the camera -- in the scene. data Camera Camera :: CameraType -> Maybe CameraPerspective -> Maybe CameraOrthographic -> Maybe Text -> Maybe Object -> Maybe Value -> Camera [$sel:type':Camera] :: Camera -> CameraType [$sel:perspective:Camera] :: Camera -> Maybe CameraPerspective [$sel:orthographic:Camera] :: Camera -> Maybe CameraOrthographic [$sel:name:Camera] :: Camera -> Maybe Text [$sel:extensions:Camera] :: Camera -> Maybe Object [$sel:extras:Camera] :: Camera -> Maybe Value newtype CameraType CameraType :: Text -> CameraType [$sel:unCameraType:CameraType] :: CameraType -> Text pattern PERSPECTIVE :: CameraType pattern ORTHOGRAPHIC :: CameraType -- | A perspective camera containing properties to create a perspective -- projection matrix. data CameraPerspective CameraPerspective :: Float -> Float -> Maybe Float -> Maybe Float -> Maybe Object -> Maybe Value -> CameraPerspective [$sel:yfov:CameraPerspective] :: CameraPerspective -> Float [$sel:znear:CameraPerspective] :: CameraPerspective -> Float [$sel:aspectRatio:CameraPerspective] :: CameraPerspective -> Maybe Float [$sel:zfar:CameraPerspective] :: CameraPerspective -> Maybe Float [$sel:extensions:CameraPerspective] :: CameraPerspective -> Maybe Object [$sel:extras:CameraPerspective] :: CameraPerspective -> Maybe Value -- | An orthographic camera containing properties to create an orthographic -- projection matrix. data CameraOrthographic CameraOrthographic :: Float -> Float -> Float -> Float -> Maybe Object -> Maybe Value -> CameraOrthographic [$sel:xmag:CameraOrthographic] :: CameraOrthographic -> Float [$sel:ymag:CameraOrthographic] :: CameraOrthographic -> Float [$sel:zfar:CameraOrthographic] :: CameraOrthographic -> Float [$sel:znear:CameraOrthographic] :: CameraOrthographic -> Float [$sel:extensions:CameraOrthographic] :: CameraOrthographic -> Maybe Object [$sel:extras:CameraOrthographic] :: CameraOrthographic -> Maybe Value instance GHC.Generics.Generic Codec.GlTF.Camera.CameraIx instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Camera.CameraIx instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Camera.CameraIx instance GHC.Show.Show Codec.GlTF.Camera.CameraIx instance GHC.Classes.Ord Codec.GlTF.Camera.CameraIx instance GHC.Classes.Eq Codec.GlTF.Camera.CameraIx instance GHC.Generics.Generic Codec.GlTF.Camera.CameraType instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Camera.CameraType instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Camera.CameraType instance GHC.Show.Show Codec.GlTF.Camera.CameraType instance GHC.Classes.Ord Codec.GlTF.Camera.CameraType instance GHC.Classes.Eq Codec.GlTF.Camera.CameraType instance GHC.Generics.Generic Codec.GlTF.Camera.CameraPerspective instance GHC.Show.Show Codec.GlTF.Camera.CameraPerspective instance GHC.Classes.Eq Codec.GlTF.Camera.CameraPerspective instance GHC.Generics.Generic Codec.GlTF.Camera.CameraOrthographic instance GHC.Show.Show Codec.GlTF.Camera.CameraOrthographic instance GHC.Classes.Eq Codec.GlTF.Camera.CameraOrthographic instance GHC.Generics.Generic Codec.GlTF.Camera.Camera instance GHC.Show.Show Codec.GlTF.Camera.Camera instance GHC.Classes.Eq Codec.GlTF.Camera.Camera instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Camera.Camera instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Camera.Camera instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Camera.CameraOrthographic instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Camera.CameraOrthographic instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Camera.CameraPerspective instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Camera.CameraPerspective module Codec.GlTF.Asset -- | Metadata about the glTF asset. data Asset Asset :: Text -> Maybe Text -> Maybe Text -> Maybe Text -> Maybe Object -> Maybe Value -> Asset [$sel:version:Asset] :: Asset -> Text [$sel:copyright:Asset] :: Asset -> Maybe Text [$sel:generator:Asset] :: Asset -> Maybe Text [$sel:minVersion:Asset] :: Asset -> Maybe Text [$sel:extensions:Asset] :: Asset -> Maybe Object [$sel:extras:Asset] :: Asset -> Maybe Value instance GHC.Generics.Generic Codec.GlTF.Asset.Asset instance GHC.Show.Show Codec.GlTF.Asset.Asset instance GHC.Classes.Eq Codec.GlTF.Asset.Asset instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Asset.Asset instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Asset.Asset module Codec.GlTF.Sampler newtype SamplerIx SamplerIx :: Int -> SamplerIx [$sel:unSamplerIx:SamplerIx] :: SamplerIx -> Int -- | The root object for a glTF Sampler. data Sampler Sampler :: SamplerWrap -> SamplerWrap -> Maybe SamplerMagFilter -> Maybe SamplerMinFilter -> Maybe Text -> Maybe Object -> Maybe Value -> Sampler [$sel:wrapS:Sampler] :: Sampler -> SamplerWrap [$sel:wrapT:Sampler] :: Sampler -> SamplerWrap [$sel:magFilter:Sampler] :: Sampler -> Maybe SamplerMagFilter [$sel:minFilter:Sampler] :: Sampler -> Maybe SamplerMinFilter [$sel:name:Sampler] :: Sampler -> Maybe Text [$sel:extensions:Sampler] :: Sampler -> Maybe Object [$sel:extras:Sampler] :: Sampler -> Maybe Value -- | Wrapping mode. -- -- All valid values correspond to WebGL enums. newtype SamplerWrap SamplerWrap :: Int -> SamplerWrap [$sel:unSamplerWrap:SamplerWrap] :: SamplerWrap -> Int pattern CLAMP_TO_EDGE :: SamplerWrap pattern MIRRORED_REPEAT :: SamplerWrap pattern REPEAT :: SamplerWrap -- | Magnification filter. -- -- Valid values correspond to WebGL enums. newtype SamplerMagFilter SamplerMagFilter :: Int -> SamplerMagFilter [$sel:unSamplerMagFilter:SamplerMagFilter] :: SamplerMagFilter -> Int pattern MAG_NEAREST :: SamplerMagFilter pattern MAG_LINEAR :: SamplerMagFilter -- | Minification filter. -- -- All valid values correspond to WebGL enums. newtype SamplerMinFilter SamplerMinFilter :: Int -> SamplerMinFilter [$sel:unSamplerMinFilter:SamplerMinFilter] :: SamplerMinFilter -> Int pattern MIN_NEAREST :: SamplerMinFilter pattern MIN_LINEAR :: SamplerMinFilter pattern MIN_NEAREST_MIPMAP_NEAREST :: SamplerMinFilter pattern MIN_LINEAR_MIPMAP_NEAREST :: SamplerMinFilter pattern MIN_NEAREST_MIPMAP_LINEAR :: SamplerMinFilter pattern MIN_LINEAR_MIPMAP_LINEAR :: SamplerMinFilter instance GHC.Generics.Generic Codec.GlTF.Sampler.SamplerIx instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Sampler.SamplerIx instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Sampler.SamplerIx instance GHC.Show.Show Codec.GlTF.Sampler.SamplerIx instance GHC.Classes.Ord Codec.GlTF.Sampler.SamplerIx instance GHC.Classes.Eq Codec.GlTF.Sampler.SamplerIx instance GHC.Generics.Generic Codec.GlTF.Sampler.SamplerWrap instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Sampler.SamplerWrap instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Sampler.SamplerWrap instance GHC.Show.Show Codec.GlTF.Sampler.SamplerWrap instance GHC.Classes.Ord Codec.GlTF.Sampler.SamplerWrap instance GHC.Classes.Eq Codec.GlTF.Sampler.SamplerWrap instance GHC.Generics.Generic Codec.GlTF.Sampler.SamplerMagFilter instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Sampler.SamplerMagFilter instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Sampler.SamplerMagFilter instance GHC.Show.Show Codec.GlTF.Sampler.SamplerMagFilter instance GHC.Classes.Ord Codec.GlTF.Sampler.SamplerMagFilter instance GHC.Classes.Eq Codec.GlTF.Sampler.SamplerMagFilter instance GHC.Generics.Generic Codec.GlTF.Sampler.SamplerMinFilter instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Sampler.SamplerMinFilter instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Sampler.SamplerMinFilter instance GHC.Show.Show Codec.GlTF.Sampler.SamplerMinFilter instance GHC.Classes.Ord Codec.GlTF.Sampler.SamplerMinFilter instance GHC.Classes.Eq Codec.GlTF.Sampler.SamplerMinFilter instance GHC.Generics.Generic Codec.GlTF.Sampler.Sampler instance GHC.Show.Show Codec.GlTF.Sampler.Sampler instance GHC.Classes.Eq Codec.GlTF.Sampler.Sampler instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Sampler.Sampler instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Sampler.Sampler module Codec.GlTF.TextureInfo -- | Reference to a texture. data TextureInfo a TextureInfo :: Int -> Int -> a -> Maybe Object -> Maybe Value -> TextureInfo a [$sel:index:TextureInfo] :: TextureInfo a -> 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. [$sel:texCoord:TextureInfo] :: TextureInfo a -> Int [$sel:subtype:TextureInfo] :: TextureInfo a -> a [$sel:extensions:TextureInfo] :: TextureInfo a -> Maybe Object [$sel:extras:TextureInfo] :: TextureInfo a -> Maybe Value -- | TextureInfo without extra fields. type TextureInfo_ = TextureInfo Basic -- | Placeholder for TextureInfo objects without extra fields. data Basic Basic :: Basic instance GHC.Generics.Generic (Codec.GlTF.TextureInfo.TextureInfo a) instance GHC.Show.Show a => GHC.Show.Show (Codec.GlTF.TextureInfo.TextureInfo a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Codec.GlTF.TextureInfo.TextureInfo a) instance GHC.Generics.Generic Codec.GlTF.TextureInfo.Basic instance GHC.Show.Show Codec.GlTF.TextureInfo.Basic instance GHC.Classes.Ord Codec.GlTF.TextureInfo.Basic instance GHC.Classes.Eq Codec.GlTF.TextureInfo.Basic instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.TextureInfo.Basic instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.TextureInfo.Basic instance Data.Aeson.Types.FromJSON.FromJSON a => Data.Aeson.Types.FromJSON.FromJSON (Codec.GlTF.TextureInfo.TextureInfo a) instance Data.Aeson.Types.ToJSON.ToJSON a => Data.Aeson.Types.ToJSON.ToJSON (Codec.GlTF.TextureInfo.TextureInfo a) module Codec.GlTF.PbrMetallicRoughness -- | A set of parameter values that are used to define the -- metallic-roughness material model from Physically-Based Rendering -- (PBR) methodology. data PbrMetallicRoughness PbrMetallicRoughness :: (Float, Float, Float, Float) -> Float -> Float -> Maybe TextureInfo_ -> Maybe TextureInfo_ -> Maybe Object -> Maybe Value -> PbrMetallicRoughness [$sel:baseColorFactor:PbrMetallicRoughness] :: PbrMetallicRoughness -> (Float, Float, Float, Float) [$sel:metallicFactor:PbrMetallicRoughness] :: PbrMetallicRoughness -> Float [$sel:roughnessFactor:PbrMetallicRoughness] :: PbrMetallicRoughness -> Float [$sel:metallicRoughnessTexture:PbrMetallicRoughness] :: PbrMetallicRoughness -> Maybe TextureInfo_ [$sel:baseColorTexture:PbrMetallicRoughness] :: PbrMetallicRoughness -> Maybe TextureInfo_ [$sel:extensions:PbrMetallicRoughness] :: PbrMetallicRoughness -> Maybe Object [$sel:extras:PbrMetallicRoughness] :: PbrMetallicRoughness -> Maybe Value instance GHC.Generics.Generic Codec.GlTF.PbrMetallicRoughness.PbrMetallicRoughness instance GHC.Show.Show Codec.GlTF.PbrMetallicRoughness.PbrMetallicRoughness instance GHC.Classes.Eq Codec.GlTF.PbrMetallicRoughness.PbrMetallicRoughness instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.PbrMetallicRoughness.PbrMetallicRoughness instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.PbrMetallicRoughness.PbrMetallicRoughness module Codec.GlTF.Material newtype MaterialIx MaterialIx :: Int -> MaterialIx [$sel:unMaterialIx:MaterialIx] :: MaterialIx -> Int -- | The material appearance of a primitive. data Material Material :: (Float, Float, Float) -> MaterialAlphaMode -> Float -> Bool -> Maybe PbrMetallicRoughness -> Maybe (TextureInfo MaterialNormal) -> Maybe (TextureInfo MaterialOcclusion) -> Maybe TextureInfo_ -> Maybe Text -> Maybe Object -> Maybe Value -> Material [$sel:emissiveFactor:Material] :: Material -> (Float, Float, Float) [$sel:alphaMode:Material] :: Material -> MaterialAlphaMode [$sel:alphaCutoff:Material] :: Material -> Float [$sel:doubleSided:Material] :: Material -> Bool [$sel:pbrMetallicRoughness:Material] :: Material -> Maybe PbrMetallicRoughness [$sel:normalTexture:Material] :: Material -> Maybe (TextureInfo MaterialNormal) [$sel:occlusionTexture:Material] :: Material -> Maybe (TextureInfo MaterialOcclusion) [$sel:emissiveTexture:Material] :: Material -> Maybe TextureInfo_ [$sel:name:Material] :: Material -> Maybe Text [$sel:extensions:Material] :: Material -> Maybe Object [$sel:extras:Material] :: Material -> Maybe Value -- | The alpha rendering mode of the material. newtype MaterialAlphaMode MaterialAlphaMode :: Text -> MaterialAlphaMode [$sel:unMaterialAlphaMode:MaterialAlphaMode] :: MaterialAlphaMode -> Text pattern OPAQUE :: MaterialAlphaMode pattern MASK :: MaterialAlphaMode pattern BLEND :: MaterialAlphaMode data MaterialNormal MaterialNormal :: Float -> MaterialNormal -- | The scalar multiplier applied to each normal vector of the normal -- texture. [$sel:scale:MaterialNormal] :: MaterialNormal -> Float data MaterialOcclusion MaterialOcclusion :: Float -> MaterialOcclusion -- | A scalar multiplier controlling the amount of occlusion applied. -- [0.0-1.0] [$sel:strength:MaterialOcclusion] :: MaterialOcclusion -> Float instance GHC.Generics.Generic Codec.GlTF.Material.MaterialIx instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Material.MaterialIx instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Material.MaterialIx instance GHC.Show.Show Codec.GlTF.Material.MaterialIx instance GHC.Classes.Ord Codec.GlTF.Material.MaterialIx instance GHC.Classes.Eq Codec.GlTF.Material.MaterialIx instance GHC.Generics.Generic Codec.GlTF.Material.MaterialAlphaMode instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Material.MaterialAlphaMode instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Material.MaterialAlphaMode instance GHC.Show.Show Codec.GlTF.Material.MaterialAlphaMode instance GHC.Classes.Ord Codec.GlTF.Material.MaterialAlphaMode instance GHC.Classes.Eq Codec.GlTF.Material.MaterialAlphaMode instance GHC.Generics.Generic Codec.GlTF.Material.MaterialNormal instance GHC.Show.Show Codec.GlTF.Material.MaterialNormal instance GHC.Classes.Eq Codec.GlTF.Material.MaterialNormal instance GHC.Generics.Generic Codec.GlTF.Material.MaterialOcclusion instance GHC.Show.Show Codec.GlTF.Material.MaterialOcclusion instance GHC.Classes.Eq Codec.GlTF.Material.MaterialOcclusion instance GHC.Generics.Generic Codec.GlTF.Material.Material instance GHC.Show.Show Codec.GlTF.Material.Material instance GHC.Classes.Eq Codec.GlTF.Material.Material instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Material.Material instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Material.Material instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Material.MaterialOcclusion instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Material.MaterialOcclusion instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Material.MaterialNormal instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Material.MaterialNormal module Codec.GlTF.URI -- | The URI of the buffer or image. -- -- Relative paths are relative to the .gltf file. Instead of referencing -- an external file, the uri can also be a data-uri. newtype URI URI :: Text -> URI loadURI :: HasCallStack => (FilePath -> IO (Either String ByteString)) -> URI -> IO (Either String ByteString) instance GHC.Generics.Generic Codec.GlTF.URI.URI instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.URI.URI instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.URI.URI instance GHC.Show.Show Codec.GlTF.URI.URI instance GHC.Classes.Ord Codec.GlTF.URI.URI instance GHC.Classes.Eq Codec.GlTF.URI.URI module Codec.GlTF.Buffer newtype BufferIx BufferIx :: Int -> BufferIx [$sel:unBufferIx:BufferIx] :: BufferIx -> Int -- | A buffer points to binary geometry, animation, or skins. -- -- glTF Buffer referring to GLB-stored BIN chunk, must have -- buffer.uri property undefined, and it must be the first -- element of buffers array; byte length of BIN chunk could be up to 3 -- bytes bigger than JSON-defined buffer.byteLength to satisfy GLB -- padding requirements. data Buffer Buffer :: Size -> Maybe URI -> Maybe Text -> Maybe Object -> Maybe Value -> Buffer [$sel:byteLength:Buffer] :: Buffer -> Size [$sel:uri:Buffer] :: Buffer -> Maybe URI [$sel:name:Buffer] :: Buffer -> Maybe Text [$sel:extensions:Buffer] :: Buffer -> Maybe Object [$sel:extras:Buffer] :: Buffer -> Maybe Value instance GHC.Generics.Generic Codec.GlTF.Buffer.BufferIx instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Buffer.BufferIx instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Buffer.BufferIx instance GHC.Show.Show Codec.GlTF.Buffer.BufferIx instance GHC.Classes.Ord Codec.GlTF.Buffer.BufferIx instance GHC.Classes.Eq Codec.GlTF.Buffer.BufferIx instance GHC.Generics.Generic Codec.GlTF.Buffer.Buffer instance GHC.Show.Show Codec.GlTF.Buffer.Buffer instance GHC.Classes.Eq Codec.GlTF.Buffer.Buffer instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Buffer.Buffer instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Buffer.Buffer module Codec.GlTF.BufferView newtype BufferViewIx BufferViewIx :: Int -> BufferViewIx [$sel:unBufferViewIx:BufferViewIx] :: BufferViewIx -> Int -- | A view into a buffer generally representing a subset of the buffer. data BufferView BufferView :: BufferIx -> Size -> Size -> Maybe Size -> Maybe BufferViewTarget -> Maybe Text -> Maybe Object -> Maybe Value -> BufferView [$sel:buffer:BufferView] :: BufferView -> BufferIx [$sel:byteOffset:BufferView] :: BufferView -> Size [$sel:byteLength:BufferView] :: BufferView -> Size -- | The stride, in bytes, between vertex attributes. When this is not -- defined, data is tightly packed. When two or more accessors use the -- same bufferView, this field must be defined. [$sel:byteStride:BufferView] :: BufferView -> Maybe Size -- | The target that the GPU buffer should be bound to. [$sel:target:BufferView] :: BufferView -> Maybe BufferViewTarget [$sel:name:BufferView] :: BufferView -> Maybe Text [$sel:extensions:BufferView] :: BufferView -> Maybe Object [$sel:extras:BufferView] :: BufferView -> Maybe Value newtype BufferViewTarget BufferViewTarget :: Int -> BufferViewTarget [$sel:unBufferViewTarget:BufferViewTarget] :: BufferViewTarget -> Int pattern ARRAY_BUFFER :: BufferViewTarget pattern ELEMENT_ARRAY_BUFFER :: BufferViewTarget instance GHC.Generics.Generic Codec.GlTF.BufferView.BufferViewIx instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.BufferView.BufferViewIx instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.BufferView.BufferViewIx instance GHC.Show.Show Codec.GlTF.BufferView.BufferViewIx instance GHC.Classes.Ord Codec.GlTF.BufferView.BufferViewIx instance GHC.Classes.Eq Codec.GlTF.BufferView.BufferViewIx instance GHC.Generics.Generic Codec.GlTF.BufferView.BufferViewTarget instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.BufferView.BufferViewTarget instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.BufferView.BufferViewTarget instance GHC.Show.Show Codec.GlTF.BufferView.BufferViewTarget instance GHC.Classes.Ord Codec.GlTF.BufferView.BufferViewTarget instance GHC.Classes.Eq Codec.GlTF.BufferView.BufferViewTarget instance GHC.Generics.Generic Codec.GlTF.BufferView.BufferView instance GHC.Show.Show Codec.GlTF.BufferView.BufferView instance GHC.Classes.Eq Codec.GlTF.BufferView.BufferView instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.BufferView.BufferView instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.BufferView.BufferView module Codec.GlTF.Image newtype ImageIx ImageIx :: Int -> ImageIx [$sel:unImageIx:ImageIx] :: ImageIx -> Int -- | Image data used to create a texture. -- -- Image can be referenced by URI or bufferView index. mimeType -- is required in the latter case. data Image Image :: Maybe URI -> Maybe Text -> Maybe BufferViewIx -> Maybe Text -> Maybe Object -> Maybe Value -> Image [$sel:uri:Image] :: Image -> Maybe URI [$sel:mimeType:Image] :: Image -> Maybe Text [$sel:bufferView:Image] :: Image -> Maybe BufferViewIx [$sel:name:Image] :: Image -> Maybe Text [$sel:extensions:Image] :: Image -> Maybe Object [$sel:extras:Image] :: Image -> Maybe Value instance GHC.Generics.Generic Codec.GlTF.Image.ImageIx instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Image.ImageIx instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Image.ImageIx instance GHC.Show.Show Codec.GlTF.Image.ImageIx instance GHC.Classes.Ord Codec.GlTF.Image.ImageIx instance GHC.Classes.Eq Codec.GlTF.Image.ImageIx instance GHC.Generics.Generic Codec.GlTF.Image.Image instance GHC.Show.Show Codec.GlTF.Image.Image instance GHC.Classes.Eq Codec.GlTF.Image.Image instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Image.Image instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Image.Image module Codec.GlTF.Texture newtype TextureIx TextureIx :: Int -> TextureIx [$sel:unTextureIx:TextureIx] :: TextureIx -> Int data Texture Texture :: Maybe SamplerIx -> Maybe ImageIx -> Maybe Text -> Maybe Object -> Maybe Value -> Texture [$sel:sampler:Texture] :: Texture -> Maybe SamplerIx [$sel:source:Texture] :: Texture -> Maybe ImageIx [$sel:name:Texture] :: Texture -> Maybe Text [$sel:extensions:Texture] :: Texture -> Maybe Object [$sel:extras:Texture] :: Texture -> Maybe Value instance GHC.Generics.Generic Codec.GlTF.Texture.TextureIx instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Texture.TextureIx instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Texture.TextureIx instance GHC.Show.Show Codec.GlTF.Texture.TextureIx instance GHC.Classes.Ord Codec.GlTF.Texture.TextureIx instance GHC.Classes.Eq Codec.GlTF.Texture.TextureIx instance GHC.Generics.Generic Codec.GlTF.Texture.Texture instance GHC.Show.Show Codec.GlTF.Texture.Texture instance GHC.Classes.Eq Codec.GlTF.Texture.Texture instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Texture.Texture instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Texture.Texture module Codec.GlTF.Accessor newtype AccessorIx AccessorIx :: Int -> AccessorIx [$sel:unAccessorIx:AccessorIx] :: AccessorIx -> Int -- | The root object for a glTF Accessor. data Accessor Accessor :: ComponentType -> Bool -> Size -> Size -> AttributeType -> Maybe BufferViewIx -> Maybe (Vector Scientific) -> Maybe (Vector Scientific) -> Maybe AccessorSparse -> Maybe Text -> Maybe Object -> Maybe Value -> Accessor [$sel:componentType:Accessor] :: Accessor -> ComponentType [$sel:normalized:Accessor] :: Accessor -> Bool [$sel:byteOffset:Accessor] :: Accessor -> Size [$sel:count:Accessor] :: Accessor -> Size [$sel:type':Accessor] :: Accessor -> AttributeType [$sel:bufferView:Accessor] :: Accessor -> Maybe BufferViewIx [$sel:min:Accessor] :: Accessor -> Maybe (Vector Scientific) [$sel:max:Accessor] :: Accessor -> Maybe (Vector Scientific) [$sel:sparse:Accessor] :: Accessor -> Maybe AccessorSparse [$sel:name:Accessor] :: Accessor -> Maybe Text [$sel:extensions:Accessor] :: Accessor -> Maybe Object [$sel:extras:Accessor] :: Accessor -> Maybe Value -- | Sparse storage of attributes that deviate from their initialization -- value. data AccessorSparse AccessorSparse :: Size -> AccessorSparseIndices -> AccessorSparseValues -> AccessorSparse [$sel:count:AccessorSparse] :: AccessorSparse -> Size [$sel:indices:AccessorSparse] :: AccessorSparse -> AccessorSparseIndices [$sel:values:AccessorSparse] :: AccessorSparse -> AccessorSparseValues -- | Indices of those attributes that deviate from their initialization -- value. data AccessorSparseIndices AccessorSparseIndices :: Maybe BufferViewIx -> Size -> ComponentType -> AccessorSparseIndices [$sel:bufferView:AccessorSparseIndices] :: AccessorSparseIndices -> Maybe BufferViewIx [$sel:byteOffset:AccessorSparseIndices] :: AccessorSparseIndices -> Size [$sel:componentType:AccessorSparseIndices] :: AccessorSparseIndices -> ComponentType -- | Array of size accessor.sparse.count times number of -- components storing the displaced accessor attributes pointed by -- accessor.sparse.indices. data AccessorSparseValues AccessorSparseValues :: Maybe BufferViewIx -> Size -> AccessorSparseValues [$sel:bufferView:AccessorSparseValues] :: AccessorSparseValues -> Maybe BufferViewIx [$sel:byteOffset:AccessorSparseValues] :: AccessorSparseValues -> Size newtype ComponentType ComponentType :: Int -> ComponentType [$sel:unComponentType:ComponentType] :: ComponentType -> Int pattern BYTE :: ComponentType pattern UNSIGNED_BYTE :: ComponentType pattern SHORT :: ComponentType pattern UNSIGNED_SHORT :: ComponentType pattern UNSIGNED_INT :: ComponentType pattern FLOAT :: ComponentType newtype AttributeType AttributeType :: Text -> AttributeType [$sel:unAttributeType:AttributeType] :: AttributeType -> Text pattern SCALAR :: AttributeType pattern VEC2 :: AttributeType pattern VEC3 :: AttributeType pattern VEC4 :: AttributeType pattern MAT2 :: AttributeType pattern MAT3 :: AttributeType pattern MAT4 :: AttributeType instance GHC.Generics.Generic Codec.GlTF.Accessor.AccessorIx instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Accessor.AccessorIx instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Accessor.AccessorIx instance GHC.Show.Show Codec.GlTF.Accessor.AccessorIx instance GHC.Classes.Ord Codec.GlTF.Accessor.AccessorIx instance GHC.Classes.Eq Codec.GlTF.Accessor.AccessorIx instance GHC.Generics.Generic Codec.GlTF.Accessor.ComponentType instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Accessor.ComponentType instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Accessor.ComponentType instance GHC.Show.Show Codec.GlTF.Accessor.ComponentType instance GHC.Classes.Ord Codec.GlTF.Accessor.ComponentType instance GHC.Classes.Eq Codec.GlTF.Accessor.ComponentType instance GHC.Generics.Generic Codec.GlTF.Accessor.AttributeType instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Accessor.AttributeType instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Accessor.AttributeType instance GHC.Show.Show Codec.GlTF.Accessor.AttributeType instance GHC.Classes.Ord Codec.GlTF.Accessor.AttributeType instance GHC.Classes.Eq Codec.GlTF.Accessor.AttributeType instance GHC.Generics.Generic Codec.GlTF.Accessor.AccessorSparseIndices instance GHC.Show.Show Codec.GlTF.Accessor.AccessorSparseIndices instance GHC.Classes.Eq Codec.GlTF.Accessor.AccessorSparseIndices instance GHC.Generics.Generic Codec.GlTF.Accessor.AccessorSparseValues instance GHC.Show.Show Codec.GlTF.Accessor.AccessorSparseValues instance GHC.Classes.Eq Codec.GlTF.Accessor.AccessorSparseValues instance GHC.Generics.Generic Codec.GlTF.Accessor.AccessorSparse instance GHC.Show.Show Codec.GlTF.Accessor.AccessorSparse instance GHC.Classes.Eq Codec.GlTF.Accessor.AccessorSparse instance GHC.Generics.Generic Codec.GlTF.Accessor.Accessor instance GHC.Show.Show Codec.GlTF.Accessor.Accessor instance GHC.Classes.Eq Codec.GlTF.Accessor.Accessor instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Accessor.Accessor instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Accessor.Accessor instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Accessor.AccessorSparse instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Accessor.AccessorSparse instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Accessor.AccessorSparseValues instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Accessor.AccessorSparseValues instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Accessor.AccessorSparseIndices instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Accessor.AccessorSparseIndices module Codec.GlTF.Mesh newtype MeshIx MeshIx :: Int -> MeshIx [$sel:unMeshIx:MeshIx] :: MeshIx -> Int -- | A set of primitives to be rendered. -- -- A node can contain one mesh. A node's transform places the mesh in the -- scene. data Mesh Mesh :: Vector MeshPrimitive -> Maybe (Vector Float) -> Maybe Text -> Maybe Object -> Maybe Value -> Mesh [$sel:primitives:Mesh] :: Mesh -> Vector MeshPrimitive [$sel:weights:Mesh] :: Mesh -> Maybe (Vector Float) [$sel:name:Mesh] :: Mesh -> Maybe Text [$sel:extensions:Mesh] :: Mesh -> Maybe Object [$sel:extras:Mesh] :: Mesh -> Maybe Value -- | Geometry to be rendered with the given material. data MeshPrimitive MeshPrimitive :: HashMap Text AccessorIx -> MeshPrimitiveMode -> Maybe AccessorIx -> Maybe MaterialIx -> Maybe (Vector (HashMap Text AccessorIx)) -> Maybe Object -> Maybe Value -> MeshPrimitive [$sel:attributes:MeshPrimitive] :: MeshPrimitive -> HashMap Text AccessorIx [$sel:mode:MeshPrimitive] :: MeshPrimitive -> MeshPrimitiveMode [$sel:indices:MeshPrimitive] :: MeshPrimitive -> Maybe AccessorIx [$sel:material:MeshPrimitive] :: MeshPrimitive -> Maybe MaterialIx [$sel:targets:MeshPrimitive] :: MeshPrimitive -> Maybe (Vector (HashMap Text AccessorIx)) [$sel:extensions:MeshPrimitive] :: MeshPrimitive -> Maybe Object [$sel:extras:MeshPrimitive] :: MeshPrimitive -> Maybe Value -- | The type of primitives to render. newtype MeshPrimitiveMode MeshPrimitiveMode :: Int -> MeshPrimitiveMode [$sel:unMeshPrimitiveMode:MeshPrimitiveMode] :: MeshPrimitiveMode -> Int pattern POINTS :: MeshPrimitiveMode pattern LINES :: MeshPrimitiveMode pattern LINE_LOOP :: MeshPrimitiveMode pattern LINE_STRIP :: MeshPrimitiveMode pattern TRIANGLES :: MeshPrimitiveMode pattern TRIANGLE_STRIP :: MeshPrimitiveMode pattern TRIANGLE_FAN :: MeshPrimitiveMode instance GHC.Generics.Generic Codec.GlTF.Mesh.MeshIx instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Mesh.MeshIx instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Mesh.MeshIx instance GHC.Show.Show Codec.GlTF.Mesh.MeshIx instance GHC.Classes.Ord Codec.GlTF.Mesh.MeshIx instance GHC.Classes.Eq Codec.GlTF.Mesh.MeshIx instance GHC.Generics.Generic Codec.GlTF.Mesh.MeshPrimitiveMode instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Mesh.MeshPrimitiveMode instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Mesh.MeshPrimitiveMode instance GHC.Show.Show Codec.GlTF.Mesh.MeshPrimitiveMode instance GHC.Classes.Ord Codec.GlTF.Mesh.MeshPrimitiveMode instance GHC.Classes.Eq Codec.GlTF.Mesh.MeshPrimitiveMode instance GHC.Generics.Generic Codec.GlTF.Mesh.MeshPrimitive instance GHC.Show.Show Codec.GlTF.Mesh.MeshPrimitive instance GHC.Classes.Eq Codec.GlTF.Mesh.MeshPrimitive instance GHC.Generics.Generic Codec.GlTF.Mesh.Mesh instance GHC.Show.Show Codec.GlTF.Mesh.Mesh instance GHC.Classes.Eq Codec.GlTF.Mesh.Mesh instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Mesh.Mesh instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Mesh.Mesh instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Mesh.MeshPrimitive instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Mesh.MeshPrimitive module Codec.GlTF.Node newtype NodeIx NodeIx :: Int -> NodeIx [$sel:unNodeIx:NodeIx] :: NodeIx -> Int -- | 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. data Node Node :: Maybe CameraIx -> Maybe (Vector NodeIx) -> Maybe SkinIx -> Maybe NodeMatrix -> Maybe MeshIx -> Maybe (Float, Float, Float, Float) -> Maybe (Float, Float, Float) -> Maybe (Float, Float, Float) -> Maybe (Vector Float) -> Maybe Text -> Maybe Object -> Maybe Value -> Node [$sel:camera:Node] :: Node -> Maybe CameraIx [$sel:children:Node] :: Node -> Maybe (Vector NodeIx) [$sel:skin:Node] :: Node -> Maybe SkinIx [$sel:matrix:Node] :: Node -> Maybe NodeMatrix [$sel:mesh:Node] :: Node -> Maybe MeshIx [$sel:rotation:Node] :: Node -> Maybe (Float, Float, Float, Float) [$sel:scale:Node] :: Node -> Maybe (Float, Float, Float) [$sel:translation:Node] :: Node -> Maybe (Float, Float, Float) [$sel:weights:Node] :: Node -> Maybe (Vector Float) [$sel:name:Node] :: Node -> Maybe Text [$sel:extensions:Node] :: Node -> Maybe Object [$sel:extras:Node] :: Node -> Maybe Value -- | A floating-point 4x4 transformation matrix stored in column-major -- order. newtype NodeMatrix NodeMatrix :: Vector Float -> NodeMatrix [$sel:unNodeMatrix:NodeMatrix] :: NodeMatrix -> Vector Float newtype SkinIx SkinIx :: Int -> SkinIx [$sel:unSkinIx:SkinIx] :: SkinIx -> Int -- | Joints and matrices defining a skin. data Skin Skin :: Vector NodeIx -> Maybe NodeIx -> Maybe AccessorIx -> Maybe Text -> Maybe Object -> Maybe Value -> Skin [$sel:joints:Skin] :: Skin -> Vector NodeIx [$sel:skeleton:Skin] :: Skin -> Maybe NodeIx -- | 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. [$sel:inverseBindMatrices:Skin] :: Skin -> Maybe AccessorIx [$sel:name:Skin] :: Skin -> Maybe Text [$sel:extensions:Skin] :: Skin -> Maybe Object [$sel:extras:Skin] :: Skin -> Maybe Value instance GHC.Generics.Generic Codec.GlTF.Node.NodeIx instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Node.NodeIx instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Node.NodeIx instance GHC.Show.Show Codec.GlTF.Node.NodeIx instance GHC.Classes.Ord Codec.GlTF.Node.NodeIx instance GHC.Classes.Eq Codec.GlTF.Node.NodeIx instance GHC.Generics.Generic Codec.GlTF.Node.NodeMatrix instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Node.NodeMatrix instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Node.NodeMatrix instance GHC.Show.Show Codec.GlTF.Node.NodeMatrix instance GHC.Classes.Ord Codec.GlTF.Node.NodeMatrix instance GHC.Classes.Eq Codec.GlTF.Node.NodeMatrix instance GHC.Generics.Generic Codec.GlTF.Node.SkinIx instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Node.SkinIx instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Node.SkinIx instance GHC.Show.Show Codec.GlTF.Node.SkinIx instance GHC.Classes.Ord Codec.GlTF.Node.SkinIx instance GHC.Classes.Eq Codec.GlTF.Node.SkinIx instance GHC.Generics.Generic Codec.GlTF.Node.Node instance GHC.Show.Show Codec.GlTF.Node.Node instance GHC.Classes.Eq Codec.GlTF.Node.Node instance GHC.Generics.Generic Codec.GlTF.Node.Skin instance GHC.Show.Show Codec.GlTF.Node.Skin instance GHC.Classes.Eq Codec.GlTF.Node.Skin instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Node.Skin instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Node.Skin instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Node.Node instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Node.Node module Codec.GlTF.Skin newtype SkinIx SkinIx :: Int -> SkinIx [$sel:unSkinIx:SkinIx] :: SkinIx -> Int -- | Joints and matrices defining a skin. data Skin Skin :: Vector NodeIx -> Maybe NodeIx -> Maybe AccessorIx -> Maybe Text -> Maybe Object -> Maybe Value -> Skin [$sel:joints:Skin] :: Skin -> Vector NodeIx [$sel:skeleton:Skin] :: Skin -> Maybe NodeIx -- | 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. [$sel:inverseBindMatrices:Skin] :: Skin -> Maybe AccessorIx [$sel:name:Skin] :: Skin -> Maybe Text [$sel:extensions:Skin] :: Skin -> Maybe Object [$sel:extras:Skin] :: Skin -> Maybe Value module Codec.GlTF.Scene newtype SceneIx SceneIx :: Int -> SceneIx [$sel:unSceneIx:SceneIx] :: SceneIx -> Int data Scene Scene :: Maybe (Vector NodeIx) -> Maybe Text -> Maybe Object -> Maybe Value -> Scene [$sel:nodes:Scene] :: Scene -> Maybe (Vector NodeIx) [$sel:name:Scene] :: Scene -> Maybe Text [$sel:extensions:Scene] :: Scene -> Maybe Object [$sel:extras:Scene] :: Scene -> Maybe Value instance GHC.Generics.Generic Codec.GlTF.Scene.SceneIx instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Scene.SceneIx instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Scene.SceneIx instance GHC.Show.Show Codec.GlTF.Scene.SceneIx instance GHC.Classes.Ord Codec.GlTF.Scene.SceneIx instance GHC.Classes.Eq Codec.GlTF.Scene.SceneIx instance GHC.Generics.Generic Codec.GlTF.Scene.Scene instance GHC.Show.Show Codec.GlTF.Scene.Scene instance GHC.Classes.Eq Codec.GlTF.Scene.Scene instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Scene.Scene instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Scene.Scene module Codec.GlTF.Animation newtype AnimationIx AnimationIx :: Int -> AnimationIx [$sel:unAnimationIx:AnimationIx] :: AnimationIx -> Int -- | A keyframe animation. data Animation Animation :: Vector AnimationChannel -> Vector AnimationSampler -> Maybe Text -> Maybe Object -> Maybe Value -> Animation [$sel:channels:Animation] :: Animation -> Vector AnimationChannel [$sel:samplers:Animation] :: Animation -> Vector AnimationSampler [$sel:name:Animation] :: Animation -> Maybe Text [$sel:extensions:Animation] :: Animation -> Maybe Object [$sel:extras:Animation] :: Animation -> Maybe Value newtype AnimationSamplerIx AnimationSamplerIx :: Int -> AnimationSamplerIx [$sel:unAnimationSamplerIx:AnimationSamplerIx] :: AnimationSamplerIx -> Int -- | Combines input and output accessors with an interpolation algorithm to -- define a keyframe graph (but not its target). data AnimationSampler AnimationSampler :: AccessorIx -> AnimationSamplerInterpolation -> AccessorIx -> Maybe Object -> Maybe Value -> AnimationSampler -- | The values represent time in seconds with time[0] >= 0.0, -- and strictly increasing values. [$sel:input:AnimationSampler] :: AnimationSampler -> AccessorIx [$sel:interpolation:AnimationSampler] :: AnimationSampler -> AnimationSamplerInterpolation -- | The index of an accessor containing keyframe output values. [$sel:output:AnimationSampler] :: AnimationSampler -> AccessorIx [$sel:extensions:AnimationSampler] :: AnimationSampler -> Maybe Object [$sel:extras:AnimationSampler] :: AnimationSampler -> Maybe Value newtype AnimationSamplerInterpolation AnimationSamplerInterpolation :: Text -> AnimationSamplerInterpolation [$sel:unAnimationSamplerInterpolation:AnimationSamplerInterpolation] :: AnimationSamplerInterpolation -> Text pattern LINEAR :: AnimationSamplerInterpolation pattern STEP :: AnimationSamplerInterpolation pattern CUBICSPLINE :: AnimationSamplerInterpolation -- | Targets an animation's sampler at a node's property. data AnimationChannel AnimationChannel :: AnimationSamplerIx -> AnimationChannelTarget -> Maybe Object -> Maybe Value -> AnimationChannel [$sel:sampler:AnimationChannel] :: AnimationChannel -> AnimationSamplerIx [$sel:target:AnimationChannel] :: AnimationChannel -> AnimationChannelTarget [$sel:extensions:AnimationChannel] :: AnimationChannel -> Maybe Object [$sel:extras:AnimationChannel] :: AnimationChannel -> Maybe Value -- | The index of the node and TRS property that an animation channel -- targets. data AnimationChannelTarget AnimationChannelTarget :: Maybe NodeIx -> AnimationChannelTargetPath -> Maybe Object -> Maybe Value -> AnimationChannelTarget [$sel:node:AnimationChannelTarget] :: AnimationChannelTarget -> Maybe NodeIx [$sel:path:AnimationChannelTarget] :: AnimationChannelTarget -> AnimationChannelTargetPath [$sel:extensions:AnimationChannelTarget] :: AnimationChannelTarget -> Maybe Object [$sel:extras:AnimationChannelTarget] :: AnimationChannelTarget -> Maybe Value -- | The name of the node's TRS property to modify, or the weights -- of the Morph Targets it instantiates. For the translation -- property, the values that are provided by the sampler are the -- translation along the x, y, and z axes. For the rotation -- property, the values are a quaternion in the order (x, y, z, w), where -- w is the scalar. For the scale property, the values are the -- scaling factors along the x, y, and z axes.", newtype AnimationChannelTargetPath AnimationChannelTargetPath :: Text -> AnimationChannelTargetPath [$sel:unAnimationChannelTargetPath:AnimationChannelTargetPath] :: AnimationChannelTargetPath -> Text pattern TRANSLATION :: AnimationChannelTargetPath pattern ROTATION :: AnimationChannelTargetPath pattern SCALE :: AnimationChannelTargetPath pattern WEIGHTS :: AnimationChannelTargetPath instance GHC.Generics.Generic Codec.GlTF.Animation.AnimationIx instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Animation.AnimationIx instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Animation.AnimationIx instance GHC.Show.Show Codec.GlTF.Animation.AnimationIx instance GHC.Classes.Ord Codec.GlTF.Animation.AnimationIx instance GHC.Classes.Eq Codec.GlTF.Animation.AnimationIx instance GHC.Generics.Generic Codec.GlTF.Animation.AnimationSamplerIx instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Animation.AnimationSamplerIx instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Animation.AnimationSamplerIx instance GHC.Show.Show Codec.GlTF.Animation.AnimationSamplerIx instance GHC.Classes.Ord Codec.GlTF.Animation.AnimationSamplerIx instance GHC.Classes.Eq Codec.GlTF.Animation.AnimationSamplerIx instance GHC.Generics.Generic Codec.GlTF.Animation.AnimationSamplerInterpolation instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Animation.AnimationSamplerInterpolation instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Animation.AnimationSamplerInterpolation instance GHC.Show.Show Codec.GlTF.Animation.AnimationSamplerInterpolation instance GHC.Classes.Ord Codec.GlTF.Animation.AnimationSamplerInterpolation instance GHC.Classes.Eq Codec.GlTF.Animation.AnimationSamplerInterpolation instance GHC.Generics.Generic Codec.GlTF.Animation.AnimationSampler instance GHC.Show.Show Codec.GlTF.Animation.AnimationSampler instance GHC.Classes.Eq Codec.GlTF.Animation.AnimationSampler instance GHC.Generics.Generic Codec.GlTF.Animation.AnimationChannelTargetPath instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Animation.AnimationChannelTargetPath instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Animation.AnimationChannelTargetPath instance GHC.Show.Show Codec.GlTF.Animation.AnimationChannelTargetPath instance GHC.Classes.Ord Codec.GlTF.Animation.AnimationChannelTargetPath instance GHC.Classes.Eq Codec.GlTF.Animation.AnimationChannelTargetPath instance GHC.Generics.Generic Codec.GlTF.Animation.AnimationChannelTarget instance GHC.Show.Show Codec.GlTF.Animation.AnimationChannelTarget instance GHC.Classes.Eq Codec.GlTF.Animation.AnimationChannelTarget instance GHC.Generics.Generic Codec.GlTF.Animation.AnimationChannel instance GHC.Show.Show Codec.GlTF.Animation.AnimationChannel instance GHC.Classes.Eq Codec.GlTF.Animation.AnimationChannel instance GHC.Generics.Generic Codec.GlTF.Animation.Animation instance GHC.Show.Show Codec.GlTF.Animation.Animation instance GHC.Classes.Eq Codec.GlTF.Animation.Animation instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Animation.Animation instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Animation.Animation instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Animation.AnimationChannel instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Animation.AnimationChannel instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Animation.AnimationChannelTarget instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Animation.AnimationChannelTarget instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Animation.AnimationSampler instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Animation.AnimationSampler module Codec.GlTF.Root -- | The root object for a glTF asset. data GlTF GlTF :: Asset -> Maybe (Vector Text) -> Maybe (Vector Text) -> Maybe (Vector Accessor) -> Maybe (Vector Animation) -> Maybe (Vector Buffer) -> Maybe (Vector BufferView) -> Maybe (Vector Camera) -> Maybe (Vector Image) -> Maybe (Vector Material) -> Maybe (Vector Mesh) -> Maybe (Vector Node) -> Maybe (Vector Sampler) -> Maybe (Vector Scene) -> Maybe SceneIx -> Maybe (Vector Skin) -> Maybe (Vector Texture) -> Maybe Object -> Maybe Value -> GlTF [$sel:asset:GlTF] :: GlTF -> Asset [$sel:extensionsUsed:GlTF] :: GlTF -> Maybe (Vector Text) [$sel:extensionsRequired:GlTF] :: GlTF -> Maybe (Vector Text) [$sel:accessors:GlTF] :: GlTF -> Maybe (Vector Accessor) [$sel:animations:GlTF] :: GlTF -> Maybe (Vector Animation) [$sel:buffers:GlTF] :: GlTF -> Maybe (Vector Buffer) [$sel:bufferViews:GlTF] :: GlTF -> Maybe (Vector BufferView) [$sel:cameras:GlTF] :: GlTF -> Maybe (Vector Camera) [$sel:images:GlTF] :: GlTF -> Maybe (Vector Image) [$sel:materials:GlTF] :: GlTF -> Maybe (Vector Material) [$sel:meshes:GlTF] :: GlTF -> Maybe (Vector Mesh) [$sel:nodes:GlTF] :: GlTF -> Maybe (Vector Node) [$sel:samplers:GlTF] :: GlTF -> Maybe (Vector Sampler) [$sel:scenes:GlTF] :: GlTF -> Maybe (Vector Scene) [$sel:scene:GlTF] :: GlTF -> Maybe SceneIx [$sel:skins:GlTF] :: GlTF -> Maybe (Vector Skin) [$sel:textures:GlTF] :: GlTF -> Maybe (Vector Texture) [$sel:extensions:GlTF] :: GlTF -> Maybe Object [$sel:extras:GlTF] :: GlTF -> Maybe Value instance GHC.Generics.Generic Codec.GlTF.Root.GlTF instance GHC.Show.Show Codec.GlTF.Root.GlTF instance GHC.Classes.Eq Codec.GlTF.Root.GlTF instance Data.Aeson.Types.FromJSON.FromJSON Codec.GlTF.Root.GlTF instance Data.Aeson.Types.ToJSON.ToJSON Codec.GlTF.Root.GlTF module Codec.GlTF -- | The root object for a glTF asset. data GlTF GlTF :: Asset -> Maybe (Vector Text) -> Maybe (Vector Text) -> Maybe (Vector Accessor) -> Maybe (Vector Animation) -> Maybe (Vector Buffer) -> Maybe (Vector BufferView) -> Maybe (Vector Camera) -> Maybe (Vector Image) -> Maybe (Vector Material) -> Maybe (Vector Mesh) -> Maybe (Vector Node) -> Maybe (Vector Sampler) -> Maybe (Vector Scene) -> Maybe SceneIx -> Maybe (Vector Skin) -> Maybe (Vector Texture) -> Maybe Object -> Maybe Value -> GlTF [$sel:asset:GlTF] :: GlTF -> Asset [$sel:extensionsUsed:GlTF] :: GlTF -> Maybe (Vector Text) [$sel:extensionsRequired:GlTF] :: GlTF -> Maybe (Vector Text) [$sel:accessors:GlTF] :: GlTF -> Maybe (Vector Accessor) [$sel:animations:GlTF] :: GlTF -> Maybe (Vector Animation) [$sel:buffers:GlTF] :: GlTF -> Maybe (Vector Buffer) [$sel:bufferViews:GlTF] :: GlTF -> Maybe (Vector BufferView) [$sel:cameras:GlTF] :: GlTF -> Maybe (Vector Camera) [$sel:images:GlTF] :: GlTF -> Maybe (Vector Image) [$sel:materials:GlTF] :: GlTF -> Maybe (Vector Material) [$sel:meshes:GlTF] :: GlTF -> Maybe (Vector Mesh) [$sel:nodes:GlTF] :: GlTF -> Maybe (Vector Node) [$sel:samplers:GlTF] :: GlTF -> Maybe (Vector Sampler) [$sel:scenes:GlTF] :: GlTF -> Maybe (Vector Scene) [$sel:scene:GlTF] :: GlTF -> Maybe SceneIx [$sel:skins:GlTF] :: GlTF -> Maybe (Vector Skin) [$sel:textures:GlTF] :: GlTF -> Maybe (Vector Texture) [$sel:extensions:GlTF] :: GlTF -> Maybe Object [$sel:extras:GlTF] :: GlTF -> Maybe Value fromByteString :: ByteString -> Either String GlTF fromFile :: FilePath -> IO (Either String GlTF) fromChunk :: Chunk -> Either String GlTF