Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type Model buf = Indexed buf Packed VertexAttrs
- type VertexAttrs = "uv" ::: Vec2
- vkVertexAttrs :: [Format]
- data InstanceAttrs = InstanceAttrs {}
- instanceAttrs :: Int32 -> Int32 -> [Transform] -> InstanceAttrs
- type StorableAttrs = (Vector TextureParams, Vector Transform)
- storableAttrs1 :: Int32 -> Int32 -> [Transform] -> StorableAttrs
- data InstanceBuffers textureStage transformStage = InstanceBuffers {
- ibTexture :: InstanceTexture textureStage
- ibTransform :: InstanceTransform transformStage
- data TextureParams = TextureParams {
- tpScale :: Vec2
- tpOffset :: Vec2
- tpGamma :: Vec4
- tpSamplerId :: Int32
- tpTextureId :: Int32
- vkInstanceTexture :: [Format]
- allocateInstancesWith :: (MonadResource m, MonadUnliftIO m) => (BufferUsageFlagBits -> Int -> Vector TextureParams -> m (InstanceTexture texture)) -> (BufferUsageFlagBits -> Int -> Vector Transform -> m (InstanceTransform transform)) -> (forall stage a. Allocated stage a -> m ()) -> [InstanceAttrs] -> m (ReleaseKey, InstanceBuffers texture transform)
- allocateInstancesCoherent :: (MonadReader env m, HasVulkan env, MonadResource m, MonadUnliftIO m) => [InstanceAttrs] -> m (ReleaseKey, InstanceBuffers 'Coherent 'Coherent)
- allocateInstancesCoherent_ :: HasVulkan env => Int -> ResourceT (RIO env) (InstanceBuffers 'Coherent 'Coherent)
- updateCoherentResize_ :: (HasVulkan context, MonadUnliftIO m) => context -> InstanceBuffers 'Coherent 'Coherent -> (Vector TextureParams, Vector Transform) -> m (InstanceBuffers 'Coherent 'Coherent)
- data Transform
Documentation
type Model buf = Indexed buf Packed VertexAttrs Source #
type VertexAttrs = "uv" ::: Vec2 Source #
vkVertexAttrs :: [Format] Source #
data InstanceAttrs Source #
Data for a single element.
Instances
Zero InstanceAttrs Source # | |
Defined in Render.Unlit.Textured.Model |
instanceAttrs :: Int32 -> Int32 -> [Transform] -> InstanceAttrs Source #
type StorableAttrs = (Vector TextureParams, Vector Transform) Source #
Intermediate data to be shipped.
storableAttrs1 :: Int32 -> Int32 -> [Transform] -> StorableAttrs Source #
data InstanceBuffers textureStage transformStage Source #
GPU-bound data.
InstanceBuffers | |
|
Instances
HasVertexBuffers (InstanceBuffers textureStage transformStage) Source # | |
Defined in Render.Unlit.Textured.Model type VertexBuffersOf (InstanceBuffers textureStage transformStage) getVertexBuffers :: InstanceBuffers textureStage transformStage -> [Buffer] getInstanceCount :: InstanceBuffers textureStage transformStage -> Word32 | |
type VertexBuffersOf (InstanceBuffers textureStage transformStage) Source # | |
Defined in Render.Unlit.Textured.Model |
data TextureParams Source #
TextureParams | |
|
Instances
Show TextureParams Source # | |
Defined in Render.Unlit.Textured.Model showsPrec :: Int -> TextureParams -> ShowS # show :: TextureParams -> String # showList :: [TextureParams] -> ShowS # | |
Storable TextureParams Source # | |
Defined in Render.Unlit.Textured.Model sizeOf :: TextureParams -> Int # alignment :: TextureParams -> Int # peekElemOff :: Ptr TextureParams -> Int -> IO TextureParams # pokeElemOff :: Ptr TextureParams -> Int -> TextureParams -> IO () # peekByteOff :: Ptr b -> Int -> IO TextureParams # pokeByteOff :: Ptr b -> Int -> TextureParams -> IO () # peek :: Ptr TextureParams -> IO TextureParams # poke :: Ptr TextureParams -> TextureParams -> IO () # | |
Zero TextureParams Source # | |
Defined in Render.Unlit.Textured.Model |
vkInstanceTexture :: [Format] Source #
allocateInstancesWith :: (MonadResource m, MonadUnliftIO m) => (BufferUsageFlagBits -> Int -> Vector TextureParams -> m (InstanceTexture texture)) -> (BufferUsageFlagBits -> Int -> Vector Transform -> m (InstanceTransform transform)) -> (forall stage a. Allocated stage a -> m ()) -> [InstanceAttrs] -> m (ReleaseKey, InstanceBuffers texture transform) Source #
allocateInstancesCoherent :: (MonadReader env m, HasVulkan env, MonadResource m, MonadUnliftIO m) => [InstanceAttrs] -> m (ReleaseKey, InstanceBuffers 'Coherent 'Coherent) Source #
allocateInstancesCoherent_ :: HasVulkan env => Int -> ResourceT (RIO env) (InstanceBuffers 'Coherent 'Coherent) Source #
updateCoherentResize_ :: (HasVulkan context, MonadUnliftIO m) => context -> InstanceBuffers 'Coherent 'Coherent -> (Vector TextureParams, Vector Transform) -> m (InstanceBuffers 'Coherent 'Coherent) Source #
Instances
Show Transform | |
Semigroup Transform | |
Monoid Transform | |
Storable Transform | |
Defined in Geomancy.Transform |