vulkan-3.6.1: Bindings to the Vulkan graphics API.
Safe HaskellNone
LanguageHaskell2010

Vulkan.Core10.PipelineLayout

Synopsis

Documentation

createPipelineLayout Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that creates the pipeline layout.

-> PipelineLayoutCreateInfo

pCreateInfo is a pointer to a PipelineLayoutCreateInfo structure specifying the state of the pipeline layout object.

-> ("allocator" ::: Maybe AllocationCallbacks)

pAllocator controls host memory allocation as described in the Memory Allocation chapter.

-> io PipelineLayout 

vkCreatePipelineLayout - Creates a new pipeline layout object

Valid Usage (Implicit)

  • device must be a valid Device handle

Return Codes

Success
Failure

See Also

AllocationCallbacks, Device, PipelineLayout, PipelineLayoutCreateInfo

withPipelineLayout :: forall io r. MonadIO io => Device -> PipelineLayoutCreateInfo -> Maybe AllocationCallbacks -> (io PipelineLayout -> (PipelineLayout -> io ()) -> r) -> r Source #

A convenience wrapper to make a compatible pair of calls to createPipelineLayout and destroyPipelineLayout

To ensure that destroyPipelineLayout is always called: pass bracket (or the allocate function from your favourite resource management library) as the first argument. To just extract the pair pass (,) as the first argument.

destroyPipelineLayout Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that destroys the pipeline layout.

-> PipelineLayout

pipelineLayout is the pipeline layout to destroy.

-> ("allocator" ::: Maybe AllocationCallbacks)

pAllocator controls host memory allocation as described in the Memory Allocation chapter.

-> io () 

vkDestroyPipelineLayout - Destroy a pipeline layout object

Valid Usage

  • If AllocationCallbacks were provided when pipelineLayout was created, a compatible set of callbacks must be provided here

Valid Usage (Implicit)

  • device must be a valid Device handle
  • If pipelineLayout is not NULL_HANDLE, pipelineLayout must be a valid PipelineLayout handle
  • If pAllocator is not NULL, pAllocator must be a valid pointer to a valid AllocationCallbacks structure
  • If pipelineLayout is a valid handle, it must have been created, allocated, or retrieved from device

Host Synchronization

  • Host access to pipelineLayout must be externally synchronized

See Also

AllocationCallbacks, Device, PipelineLayout

data PushConstantRange Source #

VkPushConstantRange - Structure specifying a push constant range

Valid Usage (Implicit)

See Also

PipelineLayoutCreateInfo, ShaderStageFlags

Constructors

PushConstantRange 

Fields

  • stageFlags :: ShaderStageFlags

    stageFlags is a set of stage flags describing the shader stages that will access a range of push constants. If a particular stage is not included in the range, then accessing members of that range of push constants from the corresponding shader stage will return undefined values.

    stageFlags must be a valid combination of ShaderStageFlagBits values

    stageFlags must not be 0

  • offset :: Word32

    offset and size are the start offset and size, respectively, consumed by the range. Both offset and size are in units of bytes and must be a multiple of 4. The layout of the push constant variables is specified in the shader.

    offset must be less than PhysicalDeviceLimits::maxPushConstantsSize

    offset must be a multiple of 4

  • size :: Word32

    size must be greater than 0

    size must be a multiple of 4

    size must be less than or equal to PhysicalDeviceLimits::maxPushConstantsSize minus offset

Instances

Instances details
Eq PushConstantRange Source # 
Instance details

Defined in Vulkan.Core10.PipelineLayout

Show PushConstantRange Source # 
Instance details

Defined in Vulkan.Core10.PipelineLayout

Generic PushConstantRange Source # 
Instance details

Defined in Vulkan.Core10.PipelineLayout

Associated Types

type Rep PushConstantRange :: Type -> Type #

Storable PushConstantRange Source # 
Instance details

Defined in Vulkan.Core10.PipelineLayout

FromCStruct PushConstantRange Source # 
Instance details

Defined in Vulkan.Core10.PipelineLayout

ToCStruct PushConstantRange Source # 
Instance details

Defined in Vulkan.Core10.PipelineLayout

Zero PushConstantRange Source # 
Instance details

Defined in Vulkan.Core10.PipelineLayout

type Rep PushConstantRange Source # 
Instance details

Defined in Vulkan.Core10.PipelineLayout

type Rep PushConstantRange = D1 ('MetaData "PushConstantRange" "Vulkan.Core10.PipelineLayout" "vulkan-3.6.1-inplace" 'False) (C1 ('MetaCons "PushConstantRange" 'PrefixI 'True) (S1 ('MetaSel ('Just "stageFlags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ShaderStageFlags) :*: (S1 ('MetaSel ('Just "offset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word32) :*: S1 ('MetaSel ('Just "size") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word32))))

data PipelineLayoutCreateInfo Source #

VkPipelineLayoutCreateInfo - Structure specifying the parameters of a newly created pipeline layout object

Valid Usage

Valid Usage (Implicit)

  • pNext must be NULL
  • flags must be 0
  • If setLayoutCount is not 0, pSetLayouts must be a valid pointer to an array of setLayoutCount valid DescriptorSetLayout handles
  • If pushConstantRangeCount is not 0, pPushConstantRanges must be a valid pointer to an array of pushConstantRangeCount valid PushConstantRange structures

See Also

DescriptorSetLayout, PipelineLayoutCreateFlags, PushConstantRange, StructureType, createPipelineLayout

Constructors

PipelineLayoutCreateInfo 

Fields

Instances

Instances details
Show PipelineLayoutCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.PipelineLayout

Generic PipelineLayoutCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.PipelineLayout

Associated Types

type Rep PipelineLayoutCreateInfo :: Type -> Type #

FromCStruct PipelineLayoutCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.PipelineLayout

ToCStruct PipelineLayoutCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.PipelineLayout

Zero PipelineLayoutCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.PipelineLayout

type Rep PipelineLayoutCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.PipelineLayout

type Rep PipelineLayoutCreateInfo = D1 ('MetaData "PipelineLayoutCreateInfo" "Vulkan.Core10.PipelineLayout" "vulkan-3.6.1-inplace" 'False) (C1 ('MetaCons "PipelineLayoutCreateInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "flags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 PipelineLayoutCreateFlags) :*: (S1 ('MetaSel ('Just "setLayouts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Vector DescriptorSetLayout)) :*: S1 ('MetaSel ('Just "pushConstantRanges") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Vector PushConstantRange)))))

newtype PipelineLayout Source #

Constructors

PipelineLayout Word64 

Instances

Instances details
Eq PipelineLayout Source # 
Instance details

Defined in Vulkan.Core10.Handles

Ord PipelineLayout Source # 
Instance details

Defined in Vulkan.Core10.Handles

Show PipelineLayout Source # 
Instance details

Defined in Vulkan.Core10.Handles

Storable PipelineLayout Source # 
Instance details

Defined in Vulkan.Core10.Handles

Zero PipelineLayout Source # 
Instance details

Defined in Vulkan.Core10.Handles

HasObjectType PipelineLayout Source # 
Instance details

Defined in Vulkan.Core10.Handles

IsHandle PipelineLayout Source # 
Instance details

Defined in Vulkan.Core10.Handles