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

Vulkan.Extensions.VK_EXT_private_data

Synopsis

Documentation

createPrivateDataSlotEXT Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device associated with the creation of the object(s) holding the private data slot.

-> PrivateDataSlotCreateInfoEXT

pCreateInfo is a pointer to a PrivateDataSlotCreateInfoEXT

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

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

-> io PrivateDataSlotEXT 

vkCreatePrivateDataSlotEXT - Create a slot for private data storage

Valid Usage (Implicit)

  • device must be a valid Device handle

Return Codes

Success
Failure

See Also

AllocationCallbacks, Device, PrivateDataSlotCreateInfoEXT, PrivateDataSlotEXT

withPrivateDataSlotEXT :: forall io r. MonadIO io => Device -> PrivateDataSlotCreateInfoEXT -> Maybe AllocationCallbacks -> (io PrivateDataSlotEXT -> (PrivateDataSlotEXT -> io ()) -> r) -> r Source #

A convenience wrapper to make a compatible pair of calls to createPrivateDataSlotEXT and destroyPrivateDataSlotEXT

To ensure that destroyPrivateDataSlotEXT 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.

destroyPrivateDataSlotEXT Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device associated with the creation of the object(s) holding the private data slot.

-> PrivateDataSlotEXT

privateDataSlot is the private data slot to destroy.

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

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

-> io () 

vkDestroyPrivateDataSlotEXT - Destroy a private data slot

Valid Usage

  • If AllocationCallbacks were provided when privateDataSlot was created, a compatible set of callbacks must be provided here
  • If no AllocationCallbacks were provided when privateDataSlot was created, pAllocator must be NULL

Valid Usage (Implicit)

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

Host Synchronization

  • Host access to privateDataSlot must be externally synchronized

See Also

AllocationCallbacks, Device, PrivateDataSlotEXT

setPrivateDataEXT Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the device that created the object.

device must be a valid Device handle

-> ObjectType

objectType is a ObjectType specifying the type of object to associate data with.

objectType must be a valid ObjectType value

-> ("objectHandle" ::: Word64)

objectHandle is a handle to the object to associate data with.

objectHandle must be device or a child of device

objectHandle must be a valid handle to an object of type objectType

-> PrivateDataSlotEXT

privateDataSlot is a handle to a PrivateDataSlotEXT specifying location of private data storage.

privateDataSlot must be a valid PrivateDataSlotEXT handle

privateDataSlot must have been created, allocated, or retrieved from device

-> ("data" ::: Word64)

data is user defined data to associate the object with. This data will be stored at privateDataSlot.

-> io () 

vkSetPrivateDataEXT - Associate data with a Vulkan object

Return Codes

Success
Failure

See Also

Device, ObjectType, PrivateDataSlotEXT

getPrivateDataEXT Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the device that created the object

device must be a valid Device handle

-> ObjectType

objectType is a ObjectType specifying the type of object data is associated with.

objectType must be Device or an object type whose parent is Device

objectType must be a valid ObjectType value

-> ("objectHandle" ::: Word64)

objectHandle is a handle to the object data is associated with.

-> PrivateDataSlotEXT

privateDataSlot is a handle to a PrivateDataSlotEXT specifying location of private data pointer storage.

privateDataSlot must be a valid PrivateDataSlotEXT handle

privateDataSlot must have been created, allocated, or retrieved from device

-> io ("data" ::: Word64) 

vkGetPrivateDataEXT - Retrieve data associated with a Vulkan object

Description

Note

Due to platform details on Android, implementations might not be able to reliably return 0 from calls to getPrivateDataEXT for SwapchainKHR objects on which setPrivateDataEXT has not previously been called. This erratum is exclusive to the Android platform and objects of type SwapchainKHR.

Valid Usage (Implicit)

See Also

Device, ObjectType, PrivateDataSlotEXT

data DevicePrivateDataCreateInfoEXT Source #

VkDevicePrivateDataCreateInfoEXT - Reserve private data slots

Valid Usage (Implicit)

See Also

StructureType

Constructors

DevicePrivateDataCreateInfoEXT 

Fields

Instances

Instances details
Eq DevicePrivateDataCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_private_data

Show DevicePrivateDataCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_private_data

Generic DevicePrivateDataCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_private_data

Associated Types

type Rep DevicePrivateDataCreateInfoEXT :: Type -> Type #

Storable DevicePrivateDataCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_private_data

FromCStruct DevicePrivateDataCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_private_data

ToCStruct DevicePrivateDataCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_private_data

Zero DevicePrivateDataCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_private_data

type Rep DevicePrivateDataCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_private_data

type Rep DevicePrivateDataCreateInfoEXT = D1 ('MetaData "DevicePrivateDataCreateInfoEXT" "Vulkan.Extensions.VK_EXT_private_data" "vulkan-3.6-inplace" 'False) (C1 ('MetaCons "DevicePrivateDataCreateInfoEXT" 'PrefixI 'True) (S1 ('MetaSel ('Just "privateDataSlotRequestCount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word32)))

data PrivateDataSlotCreateInfoEXT Source #

VkPrivateDataSlotCreateInfoEXT - Structure specifying the parameters of private data slot construction

Valid Usage (Implicit)

See Also

PrivateDataSlotCreateFlagsEXT, StructureType, createPrivateDataSlotEXT

Constructors

PrivateDataSlotCreateInfoEXT 

Fields

Instances

Instances details
Eq PrivateDataSlotCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_private_data

Show PrivateDataSlotCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_private_data

Generic PrivateDataSlotCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_private_data

Associated Types

type Rep PrivateDataSlotCreateInfoEXT :: Type -> Type #

Storable PrivateDataSlotCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_private_data

FromCStruct PrivateDataSlotCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_private_data

ToCStruct PrivateDataSlotCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_private_data

Zero PrivateDataSlotCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_private_data

type Rep PrivateDataSlotCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_private_data

type Rep PrivateDataSlotCreateInfoEXT = D1 ('MetaData "PrivateDataSlotCreateInfoEXT" "Vulkan.Extensions.VK_EXT_private_data" "vulkan-3.6-inplace" 'False) (C1 ('MetaCons "PrivateDataSlotCreateInfoEXT" 'PrefixI 'True) (S1 ('MetaSel ('Just "flags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 PrivateDataSlotCreateFlagsEXT)))

data PhysicalDevicePrivateDataFeaturesEXT Source #

VkPhysicalDevicePrivateDataFeaturesEXT - Structure specifying physical device support

Members

The members of the PhysicalDevicePrivateDataFeaturesEXT structure describe the following features:

Description

If the PhysicalDevicePrivateDataFeaturesEXT structure is included in the pNext chain of PhysicalDeviceFeatures2, it is filled with values indicating whether the feature is supported. PhysicalDevicePrivateDataFeaturesEXT can also be used in the pNext chain of DeviceCreateInfo to enable the features.

Valid Usage (Implicit)

See Also

Bool32, StructureType

Constructors

PhysicalDevicePrivateDataFeaturesEXT 

Fields

Instances

Instances details
Eq PhysicalDevicePrivateDataFeaturesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_private_data

Show PhysicalDevicePrivateDataFeaturesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_private_data

Generic PhysicalDevicePrivateDataFeaturesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_private_data

Storable PhysicalDevicePrivateDataFeaturesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_private_data

FromCStruct PhysicalDevicePrivateDataFeaturesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_private_data

ToCStruct PhysicalDevicePrivateDataFeaturesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_private_data

Zero PhysicalDevicePrivateDataFeaturesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_private_data

type Rep PhysicalDevicePrivateDataFeaturesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_private_data

type Rep PhysicalDevicePrivateDataFeaturesEXT = D1 ('MetaData "PhysicalDevicePrivateDataFeaturesEXT" "Vulkan.Extensions.VK_EXT_private_data" "vulkan-3.6-inplace" 'False) (C1 ('MetaCons "PhysicalDevicePrivateDataFeaturesEXT" 'PrefixI 'True) (S1 ('MetaSel ('Just "privateData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool)))

newtype PrivateDataSlotCreateFlagBitsEXT Source #

VkPrivateDataSlotCreateFlagBitsEXT - Bitmask specifying additional parameters for private data slot creation

See Also

PrivateDataSlotCreateFlagsEXT

Instances

Instances details
Eq PrivateDataSlotCreateFlagBitsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_private_data

Ord PrivateDataSlotCreateFlagBitsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_private_data

Read PrivateDataSlotCreateFlagBitsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_private_data

Show PrivateDataSlotCreateFlagBitsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_private_data

Storable PrivateDataSlotCreateFlagBitsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_private_data

Bits PrivateDataSlotCreateFlagBitsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_private_data

Methods

(.&.) :: PrivateDataSlotCreateFlagBitsEXT -> PrivateDataSlotCreateFlagBitsEXT -> PrivateDataSlotCreateFlagBitsEXT #

(.|.) :: PrivateDataSlotCreateFlagBitsEXT -> PrivateDataSlotCreateFlagBitsEXT -> PrivateDataSlotCreateFlagBitsEXT #

xor :: PrivateDataSlotCreateFlagBitsEXT -> PrivateDataSlotCreateFlagBitsEXT -> PrivateDataSlotCreateFlagBitsEXT #

complement :: PrivateDataSlotCreateFlagBitsEXT -> PrivateDataSlotCreateFlagBitsEXT #

shift :: PrivateDataSlotCreateFlagBitsEXT -> Int -> PrivateDataSlotCreateFlagBitsEXT #

rotate :: PrivateDataSlotCreateFlagBitsEXT -> Int -> PrivateDataSlotCreateFlagBitsEXT #

zeroBits :: PrivateDataSlotCreateFlagBitsEXT #

bit :: Int -> PrivateDataSlotCreateFlagBitsEXT #

setBit :: PrivateDataSlotCreateFlagBitsEXT -> Int -> PrivateDataSlotCreateFlagBitsEXT #

clearBit :: PrivateDataSlotCreateFlagBitsEXT -> Int -> PrivateDataSlotCreateFlagBitsEXT #

complementBit :: PrivateDataSlotCreateFlagBitsEXT -> Int -> PrivateDataSlotCreateFlagBitsEXT #

testBit :: PrivateDataSlotCreateFlagBitsEXT -> Int -> Bool #

bitSizeMaybe :: PrivateDataSlotCreateFlagBitsEXT -> Maybe Int #

bitSize :: PrivateDataSlotCreateFlagBitsEXT -> Int #

isSigned :: PrivateDataSlotCreateFlagBitsEXT -> Bool #

shiftL :: PrivateDataSlotCreateFlagBitsEXT -> Int -> PrivateDataSlotCreateFlagBitsEXT #

unsafeShiftL :: PrivateDataSlotCreateFlagBitsEXT -> Int -> PrivateDataSlotCreateFlagBitsEXT #

shiftR :: PrivateDataSlotCreateFlagBitsEXT -> Int -> PrivateDataSlotCreateFlagBitsEXT #

unsafeShiftR :: PrivateDataSlotCreateFlagBitsEXT -> Int -> PrivateDataSlotCreateFlagBitsEXT #

rotateL :: PrivateDataSlotCreateFlagBitsEXT -> Int -> PrivateDataSlotCreateFlagBitsEXT #

rotateR :: PrivateDataSlotCreateFlagBitsEXT -> Int -> PrivateDataSlotCreateFlagBitsEXT #

popCount :: PrivateDataSlotCreateFlagBitsEXT -> Int #

Zero PrivateDataSlotCreateFlagBitsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_private_data

pattern EXT_PRIVATE_DATA_SPEC_VERSION :: forall a. Integral a => a Source #

type EXT_PRIVATE_DATA_EXTENSION_NAME = "VK_EXT_private_data" Source #

pattern EXT_PRIVATE_DATA_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a Source #

newtype PrivateDataSlotEXT Source #

VkPrivateDataSlotEXT - Opaque handle to a private data slot object

See Also

createPrivateDataSlotEXT, destroyPrivateDataSlotEXT, getPrivateDataEXT, setPrivateDataEXT

Instances

Instances details
Eq PrivateDataSlotEXT Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Ord PrivateDataSlotEXT Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Show PrivateDataSlotEXT Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Storable PrivateDataSlotEXT Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Zero PrivateDataSlotEXT Source # 
Instance details

Defined in Vulkan.Extensions.Handles

HasObjectType PrivateDataSlotEXT Source # 
Instance details

Defined in Vulkan.Extensions.Handles

IsHandle PrivateDataSlotEXT Source # 
Instance details

Defined in Vulkan.Extensions.Handles