module Text.GLTF.Loader.Gltf
(
Gltf(..),
Asset(..),
Material(..),
MaterialAlphaMode(..),
Mesh(..),
Node(..),
MeshPrimitive(..),
PbrMetallicRoughness(..),
MeshPrimitiveMode(..),
_asset,
_materials,
_meshes,
_nodes,
_assetVersion,
_assetCopyright,
_assetGenerator,
_assetMinVersion,
_materialAlphaCutoff,
_materialAlphaMode,
_materialDoubleSided,
_materialEmissiveFactor,
_materialName,
_materialPbrMetallicRoughness,
_meshPrimitives,
_meshWeights,
_meshName,
_nodeMeshId,
_nodeName,
_nodeRotation,
_nodeScale,
_nodeTranslation,
_nodeWeights,
_meshPrimitiveMaterial,
_meshPrimitiveIndices,
_meshPrimitiveMode,
_meshPrimitiveNormals,
_meshPrimitivePositions,
_pbrBaseColorFactor,
_pbrMetallicFactor,
_pbrRoughnessFactor
) where
import Linear
import RIO
data Gltf = Gltf
{ Gltf -> Asset
gltfAsset :: Asset,
Gltf -> Vector Material
gltfMaterials :: Vector Material,
Gltf -> Vector Mesh
gltfMeshes :: Vector Mesh,
Gltf -> Vector Node
gltfNodes :: Vector Node
} deriving (Gltf -> Gltf -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Gltf -> Gltf -> Bool
$c/= :: Gltf -> Gltf -> Bool
== :: Gltf -> Gltf -> Bool
$c== :: Gltf -> Gltf -> Bool
Eq, Int -> Gltf -> ShowS
[Gltf] -> ShowS
Gltf -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Gltf] -> ShowS
$cshowList :: [Gltf] -> ShowS
show :: Gltf -> String
$cshow :: Gltf -> String
showsPrec :: Int -> Gltf -> ShowS
$cshowsPrec :: Int -> Gltf -> ShowS
Show)
data Asset = Asset
{ Asset -> Text
assetVersion :: Text,
Asset -> Maybe Text
assetCopyright :: Maybe Text,
Asset -> Maybe Text
assetGenerator :: Maybe Text,
Asset -> Maybe Text
assetMinVersion :: Maybe Text
} deriving (Asset -> Asset -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Asset -> Asset -> Bool
$c/= :: Asset -> Asset -> Bool
== :: Asset -> Asset -> Bool
$c== :: Asset -> Asset -> Bool
Eq, Int -> Asset -> ShowS
[Asset] -> ShowS
Asset -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Asset] -> ShowS
$cshowList :: [Asset] -> ShowS
show :: Asset -> String
$cshow :: Asset -> String
showsPrec :: Int -> Asset -> ShowS
$cshowsPrec :: Int -> Asset -> ShowS
Show)
data Material = Material
{ Material -> Float
materialAlphaCutoff :: Float,
Material -> MaterialAlphaMode
materialAlphaMode :: MaterialAlphaMode,
Material -> Bool
materialDoubleSided :: Bool,
Material -> V3 Float
materialEmissiveFactor :: V3 Float,
Material -> Maybe Text
materialName :: Maybe Text,
Material -> Maybe PbrMetallicRoughness
materialPbrMetallicRoughness :: Maybe PbrMetallicRoughness
} deriving (Material -> Material -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Material -> Material -> Bool
$c/= :: Material -> Material -> Bool
== :: Material -> Material -> Bool
$c== :: Material -> Material -> Bool
Eq, Int -> Material -> ShowS
[Material] -> ShowS
Material -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Material] -> ShowS
$cshowList :: [Material] -> ShowS
show :: Material -> String
$cshow :: Material -> String
showsPrec :: Int -> Material -> ShowS
$cshowsPrec :: Int -> Material -> ShowS
Show)
data Mesh = Mesh
{ Mesh -> Vector MeshPrimitive
meshPrimitives :: Vector MeshPrimitive,
Mesh -> Vector Float
meshWeights :: Vector Float,
Mesh -> Maybe Text
meshName :: Maybe Text
} deriving (Mesh -> Mesh -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Mesh -> Mesh -> Bool
$c/= :: Mesh -> Mesh -> Bool
== :: Mesh -> Mesh -> Bool
$c== :: Mesh -> Mesh -> Bool
Eq, Int -> Mesh -> ShowS
[Mesh] -> ShowS
Mesh -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Mesh] -> ShowS
$cshowList :: [Mesh] -> ShowS
show :: Mesh -> String
$cshow :: Mesh -> String
showsPrec :: Int -> Mesh -> ShowS
$cshowsPrec :: Int -> Mesh -> ShowS
Show)
data Node = Node
{ Node -> Maybe Int
nodeMeshId :: Maybe Int,
Node -> Maybe Text
nodeName :: Maybe Text,
Node -> Maybe (V4 Float)
nodeRotation :: Maybe (V4 Float),
Node -> Maybe (V3 Float)
nodeScale :: Maybe (V3 Float),
Node -> Maybe (V3 Float)
nodeTranslation :: Maybe (V3 Float),
Node -> [Float]
nodeWeights :: [Float]
} deriving (Node -> Node -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Node -> Node -> Bool
$c/= :: Node -> Node -> Bool
== :: Node -> Node -> Bool
$c== :: Node -> Node -> Bool
Eq, Int -> Node -> ShowS
[Node] -> ShowS
Node -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Node] -> ShowS
$cshowList :: [Node] -> ShowS
show :: Node -> String
$cshow :: Node -> String
showsPrec :: Int -> Node -> ShowS
$cshowsPrec :: Int -> Node -> ShowS
Show)
data MeshPrimitive = MeshPrimitive
{ MeshPrimitive -> Vector Int
meshPrimitiveIndices :: Vector Int,
MeshPrimitive -> Maybe Int
meshPrimitiveMaterial :: Maybe Int,
MeshPrimitive -> MeshPrimitiveMode
meshPrimitiveMode :: MeshPrimitiveMode,
MeshPrimitive -> Vector (V3 Float)
meshPrimitiveNormals :: Vector (V3 Float),
MeshPrimitive -> Vector (V3 Float)
meshPrimitivePositions :: Vector (V3 Float),
MeshPrimitive -> Vector (V2 Float)
meshPrimitiveTexCoords :: Vector (V2 Float)
} deriving (MeshPrimitive -> MeshPrimitive -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MeshPrimitive -> MeshPrimitive -> Bool
$c/= :: MeshPrimitive -> MeshPrimitive -> Bool
== :: MeshPrimitive -> MeshPrimitive -> Bool
$c== :: MeshPrimitive -> MeshPrimitive -> Bool
Eq, Int -> MeshPrimitive -> ShowS
[MeshPrimitive] -> ShowS
MeshPrimitive -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MeshPrimitive] -> ShowS
$cshowList :: [MeshPrimitive] -> ShowS
show :: MeshPrimitive -> String
$cshow :: MeshPrimitive -> String
showsPrec :: Int -> MeshPrimitive -> ShowS
$cshowsPrec :: Int -> MeshPrimitive -> ShowS
Show)
data MaterialAlphaMode
= Blend
| Mask
| Opaque
deriving (MaterialAlphaMode -> MaterialAlphaMode -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MaterialAlphaMode -> MaterialAlphaMode -> Bool
$c/= :: MaterialAlphaMode -> MaterialAlphaMode -> Bool
== :: MaterialAlphaMode -> MaterialAlphaMode -> Bool
$c== :: MaterialAlphaMode -> MaterialAlphaMode -> Bool
Eq, Int -> MaterialAlphaMode
MaterialAlphaMode -> Int
MaterialAlphaMode -> [MaterialAlphaMode]
MaterialAlphaMode -> MaterialAlphaMode
MaterialAlphaMode -> MaterialAlphaMode -> [MaterialAlphaMode]
MaterialAlphaMode
-> MaterialAlphaMode -> MaterialAlphaMode -> [MaterialAlphaMode]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: MaterialAlphaMode
-> MaterialAlphaMode -> MaterialAlphaMode -> [MaterialAlphaMode]
$cenumFromThenTo :: MaterialAlphaMode
-> MaterialAlphaMode -> MaterialAlphaMode -> [MaterialAlphaMode]
enumFromTo :: MaterialAlphaMode -> MaterialAlphaMode -> [MaterialAlphaMode]
$cenumFromTo :: MaterialAlphaMode -> MaterialAlphaMode -> [MaterialAlphaMode]
enumFromThen :: MaterialAlphaMode -> MaterialAlphaMode -> [MaterialAlphaMode]
$cenumFromThen :: MaterialAlphaMode -> MaterialAlphaMode -> [MaterialAlphaMode]
enumFrom :: MaterialAlphaMode -> [MaterialAlphaMode]
$cenumFrom :: MaterialAlphaMode -> [MaterialAlphaMode]
fromEnum :: MaterialAlphaMode -> Int
$cfromEnum :: MaterialAlphaMode -> Int
toEnum :: Int -> MaterialAlphaMode
$ctoEnum :: Int -> MaterialAlphaMode
pred :: MaterialAlphaMode -> MaterialAlphaMode
$cpred :: MaterialAlphaMode -> MaterialAlphaMode
succ :: MaterialAlphaMode -> MaterialAlphaMode
$csucc :: MaterialAlphaMode -> MaterialAlphaMode
Enum, Int -> MaterialAlphaMode -> ShowS
[MaterialAlphaMode] -> ShowS
MaterialAlphaMode -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MaterialAlphaMode] -> ShowS
$cshowList :: [MaterialAlphaMode] -> ShowS
show :: MaterialAlphaMode -> String
$cshow :: MaterialAlphaMode -> String
showsPrec :: Int -> MaterialAlphaMode -> ShowS
$cshowsPrec :: Int -> MaterialAlphaMode -> ShowS
Show)
data PbrMetallicRoughness = PbrMetallicRoughness
{ PbrMetallicRoughness -> V4 Float
pbrBaseColorFactor :: V4 Float,
PbrMetallicRoughness -> Float
pbrMetallicFactor :: Float,
PbrMetallicRoughness -> Float
pbrRoughnessFactor :: Float
} deriving (PbrMetallicRoughness -> PbrMetallicRoughness -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PbrMetallicRoughness -> PbrMetallicRoughness -> Bool
$c/= :: PbrMetallicRoughness -> PbrMetallicRoughness -> Bool
== :: PbrMetallicRoughness -> PbrMetallicRoughness -> Bool
$c== :: PbrMetallicRoughness -> PbrMetallicRoughness -> Bool
Eq, Int -> PbrMetallicRoughness -> ShowS
[PbrMetallicRoughness] -> ShowS
PbrMetallicRoughness -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PbrMetallicRoughness] -> ShowS
$cshowList :: [PbrMetallicRoughness] -> ShowS
show :: PbrMetallicRoughness -> String
$cshow :: PbrMetallicRoughness -> String
showsPrec :: Int -> PbrMetallicRoughness -> ShowS
$cshowsPrec :: Int -> PbrMetallicRoughness -> ShowS
Show)
data MeshPrimitiveMode
= Points
| Lines
| LineLoop
| LineStrip
| Triangles
| TriangleStrip
| TriangleFan
deriving (MeshPrimitiveMode -> MeshPrimitiveMode -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MeshPrimitiveMode -> MeshPrimitiveMode -> Bool
$c/= :: MeshPrimitiveMode -> MeshPrimitiveMode -> Bool
== :: MeshPrimitiveMode -> MeshPrimitiveMode -> Bool
$c== :: MeshPrimitiveMode -> MeshPrimitiveMode -> Bool
Eq, Int -> MeshPrimitiveMode
MeshPrimitiveMode -> Int
MeshPrimitiveMode -> [MeshPrimitiveMode]
MeshPrimitiveMode -> MeshPrimitiveMode
MeshPrimitiveMode -> MeshPrimitiveMode -> [MeshPrimitiveMode]
MeshPrimitiveMode
-> MeshPrimitiveMode -> MeshPrimitiveMode -> [MeshPrimitiveMode]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: MeshPrimitiveMode
-> MeshPrimitiveMode -> MeshPrimitiveMode -> [MeshPrimitiveMode]
$cenumFromThenTo :: MeshPrimitiveMode
-> MeshPrimitiveMode -> MeshPrimitiveMode -> [MeshPrimitiveMode]
enumFromTo :: MeshPrimitiveMode -> MeshPrimitiveMode -> [MeshPrimitiveMode]
$cenumFromTo :: MeshPrimitiveMode -> MeshPrimitiveMode -> [MeshPrimitiveMode]
enumFromThen :: MeshPrimitiveMode -> MeshPrimitiveMode -> [MeshPrimitiveMode]
$cenumFromThen :: MeshPrimitiveMode -> MeshPrimitiveMode -> [MeshPrimitiveMode]
enumFrom :: MeshPrimitiveMode -> [MeshPrimitiveMode]
$cenumFrom :: MeshPrimitiveMode -> [MeshPrimitiveMode]
fromEnum :: MeshPrimitiveMode -> Int
$cfromEnum :: MeshPrimitiveMode -> Int
toEnum :: Int -> MeshPrimitiveMode
$ctoEnum :: Int -> MeshPrimitiveMode
pred :: MeshPrimitiveMode -> MeshPrimitiveMode
$cpred :: MeshPrimitiveMode -> MeshPrimitiveMode
succ :: MeshPrimitiveMode -> MeshPrimitiveMode
$csucc :: MeshPrimitiveMode -> MeshPrimitiveMode
Enum, Int -> MeshPrimitiveMode -> ShowS
[MeshPrimitiveMode] -> ShowS
MeshPrimitiveMode -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MeshPrimitiveMode] -> ShowS
$cshowList :: [MeshPrimitiveMode] -> ShowS
show :: MeshPrimitiveMode -> String
$cshow :: MeshPrimitiveMode -> String
showsPrec :: Int -> MeshPrimitiveMode -> ShowS
$cshowsPrec :: Int -> MeshPrimitiveMode -> ShowS
Show)
_asset :: Lens' Gltf Asset
_asset :: Lens' Gltf Asset
_asset = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Gltf -> Asset
gltfAsset (\Gltf
gltf Asset
asset -> Gltf
gltf { gltfAsset :: Asset
gltfAsset = Asset
asset })
_materials :: Lens' Gltf (Vector Material)
_materials :: Lens' Gltf (Vector Material)
_materials = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Gltf -> Vector Material
gltfMaterials (\Gltf
gltf Vector Material
mats -> Gltf
gltf { gltfMaterials :: Vector Material
gltfMaterials = Vector Material
mats })
_meshes :: Lens' Gltf (Vector Mesh)
_meshes :: Lens' Gltf (Vector Mesh)
_meshes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Gltf -> Vector Mesh
gltfMeshes (\Gltf
gltf Vector Mesh
meshes -> Gltf
gltf { gltfMeshes :: Vector Mesh
gltfMeshes = Vector Mesh
meshes })
_nodes :: Lens' Gltf (Vector Node)
_nodes :: Lens' Gltf (Vector Node)
_nodes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Gltf -> Vector Node
gltfNodes (\Gltf
gltf Vector Node
nodes -> Gltf
gltf { gltfNodes :: Vector Node
gltfNodes = Vector Node
nodes })
_assetVersion :: Lens' Asset Text
_assetVersion :: Lens' Asset Text
_assetVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Asset -> Text
assetVersion (\Asset
asset Text
version' -> Asset
asset { assetVersion :: Text
assetVersion = Text
version' })
_assetCopyright :: Lens' Asset (Maybe Text)
_assetCopyright :: Lens' Asset (Maybe Text)
_assetCopyright = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
Asset -> Maybe Text
assetCopyright
(\Asset
asset Maybe Text
copyright' -> Asset
asset { assetCopyright :: Maybe Text
assetCopyright = Maybe Text
copyright' })
_assetGenerator :: Lens' Asset (Maybe Text)
_assetGenerator :: Lens' Asset (Maybe Text)
_assetGenerator = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
Asset -> Maybe Text
assetGenerator
(\Asset
asset Maybe Text
generator' -> Asset
asset { assetGenerator :: Maybe Text
assetGenerator = Maybe Text
generator' })
_assetMinVersion :: Lens' Asset (Maybe Text)
_assetMinVersion :: Lens' Asset (Maybe Text)
_assetMinVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
Asset -> Maybe Text
assetMinVersion
(\Asset
asset Maybe Text
minVersion' -> Asset
asset { assetMinVersion :: Maybe Text
assetMinVersion = Maybe Text
minVersion' })
_materialAlphaCutoff :: Lens' Material Float
_materialAlphaCutoff :: Lens' Material Float
_materialAlphaCutoff = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
Material -> Float
materialAlphaCutoff
(\Material
material Float
alphaCutoff -> Material
material { materialAlphaCutoff :: Float
materialAlphaCutoff = Float
alphaCutoff })
_materialAlphaMode :: Lens' Material MaterialAlphaMode
_materialAlphaMode :: Lens' Material MaterialAlphaMode
_materialAlphaMode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
Material -> MaterialAlphaMode
materialAlphaMode
(\Material
material MaterialAlphaMode
mode -> Material
material { materialAlphaMode :: MaterialAlphaMode
materialAlphaMode = MaterialAlphaMode
mode })
_materialDoubleSided :: Lens' Material Bool
_materialDoubleSided :: Lens' Material Bool
_materialDoubleSided = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
Material -> Bool
materialDoubleSided
(\Material
material Bool
doubleSided -> Material
material { materialDoubleSided :: Bool
materialDoubleSided = Bool
doubleSided })
_materialEmissiveFactor :: Lens' Material (V3 Float)
_materialEmissiveFactor :: Lens' Material (V3 Float)
_materialEmissiveFactor = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
Material -> V3 Float
materialEmissiveFactor
(\Material
material V3 Float
emissiveFactor -> Material
material { materialEmissiveFactor :: V3 Float
materialEmissiveFactor = V3 Float
emissiveFactor })
_materialName :: Lens' Material (Maybe Text)
_materialName :: Lens' Material (Maybe Text)
_materialName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
Material -> Maybe Text
materialName
(\Material
material Maybe Text
name -> Material
material { materialName :: Maybe Text
materialName = Maybe Text
name })
_materialPbrMetallicRoughness :: Lens' Material (Maybe PbrMetallicRoughness)
_materialPbrMetallicRoughness :: Lens' Material (Maybe PbrMetallicRoughness)
_materialPbrMetallicRoughness = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
Material -> Maybe PbrMetallicRoughness
materialPbrMetallicRoughness
(\Material
material Maybe PbrMetallicRoughness
roughness -> Material
material { materialPbrMetallicRoughness :: Maybe PbrMetallicRoughness
materialPbrMetallicRoughness = Maybe PbrMetallicRoughness
roughness })
_meshWeights :: Lens' Mesh (Vector Float)
_meshWeights :: Lens' Mesh (Vector Float)
_meshWeights = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Mesh -> Vector Float
meshWeights (\Mesh
mesh Vector Float
weights -> Mesh
mesh { meshWeights :: Vector Float
meshWeights = Vector Float
weights })
_meshName :: Lens' Mesh (Maybe Text)
_meshName :: Lens' Mesh (Maybe Text)
_meshName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Mesh -> Maybe Text
meshName (\Mesh
mesh Maybe Text
name -> Mesh
mesh { meshName :: Maybe Text
meshName = Maybe Text
name })
_meshPrimitives :: Lens' Mesh (Vector MeshPrimitive)
_meshPrimitives :: Lens' Mesh (Vector MeshPrimitive)
_meshPrimitives = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
Mesh -> Vector MeshPrimitive
meshPrimitives
(\Mesh
mesh Vector MeshPrimitive
primitives -> Mesh
mesh { meshPrimitives :: Vector MeshPrimitive
meshPrimitives = Vector MeshPrimitive
primitives })
_nodeMeshId :: Lens' Node (Maybe Int)
_nodeMeshId :: Lens' Node (Maybe Int)
_nodeMeshId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Node -> Maybe Int
nodeMeshId (\Node
node Maybe Int
meshId -> Node
node { nodeMeshId :: Maybe Int
nodeMeshId = Maybe Int
meshId })
_nodeName :: Lens' Node (Maybe Text)
_nodeName :: Lens' Node (Maybe Text)
_nodeName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Node -> Maybe Text
nodeName (\Node
node Maybe Text
name' -> Node
node { nodeName :: Maybe Text
nodeName = Maybe Text
name' })
_nodeRotation :: Lens' Node (Maybe (V4 Float))
_nodeRotation :: Lens' Node (Maybe (V4 Float))
_nodeRotation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Node -> Maybe (V4 Float)
nodeRotation (\Node
node Maybe (V4 Float)
rotation' -> Node
node { nodeRotation :: Maybe (V4 Float)
nodeRotation = Maybe (V4 Float)
rotation' })
_nodeScale :: Lens' Node (Maybe (V3 Float))
_nodeScale :: Lens' Node (Maybe (V3 Float))
_nodeScale = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Node -> Maybe (V3 Float)
nodeScale (\Node
node Maybe (V3 Float)
scale' -> Node
node { nodeScale :: Maybe (V3 Float)
nodeScale = Maybe (V3 Float)
scale' })
_nodeTranslation :: Lens' Node (Maybe (V3 Float))
_nodeTranslation :: Lens' Node (Maybe (V3 Float))
_nodeTranslation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
Node -> Maybe (V3 Float)
nodeTranslation
(\Node
node Maybe (V3 Float)
translation' -> Node
node { nodeTranslation :: Maybe (V3 Float)
nodeTranslation = Maybe (V3 Float)
translation' })
_nodeWeights :: Lens' Node [Float]
_nodeWeights :: Lens' Node [Float]
_nodeWeights = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Node -> [Float]
nodeWeights (\Node
node [Float]
weights' -> Node
node { nodeWeights :: [Float]
nodeWeights = [Float]
weights' })
_meshPrimitiveIndices :: Lens' MeshPrimitive (Vector Int)
_meshPrimitiveIndices :: Lens' MeshPrimitive (Vector Int)
_meshPrimitiveIndices = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
MeshPrimitive -> Vector Int
meshPrimitiveIndices
(\MeshPrimitive
primitive' Vector Int
indices -> MeshPrimitive
primitive' { meshPrimitiveIndices :: Vector Int
meshPrimitiveIndices = Vector Int
indices })
_meshPrimitiveMaterial :: Lens' MeshPrimitive (Maybe Int)
_meshPrimitiveMaterial :: Lens' MeshPrimitive (Maybe Int)
_meshPrimitiveMaterial = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
MeshPrimitive -> Maybe Int
meshPrimitiveMaterial
(\MeshPrimitive
primitive' Maybe Int
material -> MeshPrimitive
primitive' { meshPrimitiveMaterial :: Maybe Int
meshPrimitiveMaterial = Maybe Int
material })
_meshPrimitiveMode :: Lens' MeshPrimitive MeshPrimitiveMode
_meshPrimitiveMode :: Lens' MeshPrimitive MeshPrimitiveMode
_meshPrimitiveMode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
MeshPrimitive -> MeshPrimitiveMode
meshPrimitiveMode
(\MeshPrimitive
primitive' MeshPrimitiveMode
mode -> MeshPrimitive
primitive' { meshPrimitiveMode :: MeshPrimitiveMode
meshPrimitiveMode = MeshPrimitiveMode
mode })
_meshPrimitiveNormals :: Lens' MeshPrimitive (Vector (V3 Float))
_meshPrimitiveNormals :: Lens' MeshPrimitive (Vector (V3 Float))
_meshPrimitiveNormals = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
MeshPrimitive -> Vector (V3 Float)
meshPrimitiveNormals
(\MeshPrimitive
primitive' Vector (V3 Float)
normals -> MeshPrimitive
primitive' { meshPrimitiveNormals :: Vector (V3 Float)
meshPrimitiveNormals = Vector (V3 Float)
normals })
_meshPrimitivePositions :: Lens' MeshPrimitive (Vector (V3 Float))
_meshPrimitivePositions :: Lens' MeshPrimitive (Vector (V3 Float))
_meshPrimitivePositions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
MeshPrimitive -> Vector (V3 Float)
meshPrimitivePositions
(\MeshPrimitive
primitive' Vector (V3 Float)
positions -> MeshPrimitive
primitive' { meshPrimitivePositions :: Vector (V3 Float)
meshPrimitivePositions = Vector (V3 Float)
positions })
_meshPrimitiveTexCoords :: Lens' MeshPrimitive (Vector (V2 Float))
_meshPrimitiveTexCoords :: Lens' MeshPrimitive (Vector (V2 Float))
_meshPrimitiveTexCoords = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
MeshPrimitive -> Vector (V2 Float)
meshPrimitiveTexCoords
(\MeshPrimitive
primitive' Vector (V2 Float)
coords -> MeshPrimitive
primitive' { meshPrimitiveTexCoords :: Vector (V2 Float)
meshPrimitiveTexCoords = Vector (V2 Float)
coords })
_pbrBaseColorFactor :: Lens' PbrMetallicRoughness (V4 Float)
_pbrBaseColorFactor :: Lens' PbrMetallicRoughness (V4 Float)
_pbrBaseColorFactor = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
PbrMetallicRoughness -> V4 Float
pbrBaseColorFactor
(\PbrMetallicRoughness
pbr V4 Float
baseColor -> PbrMetallicRoughness
pbr { pbrBaseColorFactor :: V4 Float
pbrBaseColorFactor = V4 Float
baseColor })
_pbrMetallicFactor :: Lens' PbrMetallicRoughness Float
_pbrMetallicFactor :: Lens' PbrMetallicRoughness Float
_pbrMetallicFactor = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
PbrMetallicRoughness -> Float
pbrMetallicFactor
(\PbrMetallicRoughness
pbr Float
metallicFactor -> PbrMetallicRoughness
pbr { pbrMetallicFactor :: Float
pbrMetallicFactor = Float
metallicFactor })
_pbrRoughnessFactor :: Lens' PbrMetallicRoughness Float
_pbrRoughnessFactor :: Lens' PbrMetallicRoughness Float
_pbrRoughnessFactor = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
PbrMetallicRoughness -> Float
pbrRoughnessFactor
(\PbrMetallicRoughness
pbr Float
roughnessFactor -> PbrMetallicRoughness
pbr { pbrRoughnessFactor :: Float
pbrRoughnessFactor = Float
roughnessFactor })