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

Vulkan.Extensions.VK_EXT_validation_cache

Synopsis

Documentation

createValidationCacheEXT Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that creates the validation cache object.

-> ValidationCacheCreateInfoEXT

pCreateInfo is a pointer to a ValidationCacheCreateInfoEXT structure containing the initial parameters for the validation cache object.

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

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

-> io ValidationCacheEXT 

vkCreateValidationCacheEXT - Creates a new validation cache

Description

Note

Applications can track and manage the total host memory size of a validation cache object using the pAllocator. Applications can limit the amount of data retrieved from a validation cache object in getValidationCacheDataEXT. Implementations should not internally limit the total number of entries added to a validation cache object or the total host memory consumed.

Once created, a validation cache can be passed to the createShaderModule command by adding this object to the ShaderModuleCreateInfo structure’s pNext chain. If a ShaderModuleValidationCacheCreateInfoEXT object is included in the ShaderModuleCreateInfo::pNext chain, and its validationCache field is not NULL_HANDLE, the implementation will query it for possible reuse opportunities and update it with new content. The use of the validation cache object in these commands is internally synchronized, and the same validation cache object can be used in multiple threads simultaneously.

Note

Implementations should make every effort to limit any critical sections to the actual accesses to the cache, which is expected to be significantly shorter than the duration of the createShaderModule command.

Valid Usage (Implicit)

  • device must be a valid Device handle

Return Codes

Success
Failure

See Also

AllocationCallbacks, Device, ValidationCacheCreateInfoEXT, ValidationCacheEXT

withValidationCacheEXT :: forall io r. MonadIO io => Device -> ValidationCacheCreateInfoEXT -> Maybe AllocationCallbacks -> (io ValidationCacheEXT -> (ValidationCacheEXT -> io ()) -> r) -> r Source #

A convenience wrapper to make a compatible pair of calls to createValidationCacheEXT and destroyValidationCacheEXT

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

destroyValidationCacheEXT Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that destroys the validation cache object.

-> ValidationCacheEXT

validationCache is the handle of the validation cache to destroy.

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

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

-> io () 

vkDestroyValidationCacheEXT - Destroy a validation cache object

Valid Usage

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

Valid Usage (Implicit)

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

Host Synchronization

  • Host access to validationCache must be externally synchronized

See Also

AllocationCallbacks, Device, ValidationCacheEXT

getValidationCacheDataEXT Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that owns the validation cache.

-> ValidationCacheEXT

validationCache is the validation cache to retrieve data from.

-> io (Result, "data" ::: ByteString) 

vkGetValidationCacheDataEXT - Get the data store from a validation cache

Description

If pData is NULL, then the maximum size of the data that can be retrieved from the validation cache, in bytes, is returned in pDataSize. Otherwise, pDataSize must point to a variable set by the user to the size of the buffer, in bytes, pointed to by pData, and on return the variable is overwritten with the amount of data actually written to pData.

If pDataSize is less than the maximum size that can be retrieved by the validation cache, at most pDataSize bytes will be written to pData, and getValidationCacheDataEXT will return INCOMPLETE. Any data written to pData is valid and can be provided as the pInitialData member of the ValidationCacheCreateInfoEXT structure passed to createValidationCacheEXT.

Two calls to getValidationCacheDataEXT with the same parameters must retrieve the same data unless a command that modifies the contents of the cache is called between them.

Applications can store the data retrieved from the validation cache, and use these data, possibly in a future run of the application, to populate new validation cache objects. The results of validation, however, may depend on the vendor ID, device ID, driver version, and other details of the device. To enable applications to detect when previously retrieved data is incompatible with the device, the initial bytes written to pData must be a header consisting of the following members:

Offset Size Meaning
0 4 length in bytes of the entire validation cache header written as a stream of bytes, with the least significant byte first
4 4 a ValidationCacheHeaderVersionEXT value written as a stream of bytes, with the least significant byte first
8 UUID_SIZE a layer commit ID expressed as a UUID, which uniquely identifies the version of the validation layers used to generate these validation results

Layout for validation cache header version VALIDATION_CACHE_HEADER_VERSION_ONE_EXT

The first four bytes encode the length of the entire validation cache header, in bytes. This value includes all fields in the header including the validation cache version field and the size of the length field.

The next four bytes encode the validation cache version, as described for ValidationCacheHeaderVersionEXT. A consumer of the validation cache should use the cache version to interpret the remainder of the cache header.

If pDataSize is less than what is necessary to store this header, nothing will be written to pData and zero will be written to pDataSize.

Valid Usage (Implicit)

  • device must be a valid Device handle
  • validationCache must be a valid ValidationCacheEXT handle
  • pDataSize must be a valid pointer to a size_t value
  • If the value referenced by pDataSize is not 0, and pData is not NULL, pData must be a valid pointer to an array of pDataSize bytes
  • validationCache must have been created, allocated, or retrieved from device

Return Codes

Success
Failure

See Also

Device, ValidationCacheEXT

mergeValidationCachesEXT Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that owns the validation cache objects.

-> ("dstCache" ::: ValidationCacheEXT)

dstCache is the handle of the validation cache to merge results into.

-> ("srcCaches" ::: Vector ValidationCacheEXT)

pSrcCaches is a pointer to an array of validation cache handles, which will be merged into dstCache. The previous contents of dstCache are included after the merge.

-> io () 

vkMergeValidationCachesEXT - Combine the data stores of validation caches

Description

Note

The details of the merge operation are implementation dependent, but implementations should merge the contents of the specified validation caches and prune duplicate entries.

Valid Usage

  • dstCache must not appear in the list of source caches

Valid Usage (Implicit)

  • device must be a valid Device handle
  • dstCache must be a valid ValidationCacheEXT handle
  • pSrcCaches must be a valid pointer to an array of srcCacheCount valid ValidationCacheEXT handles
  • srcCacheCount must be greater than 0
  • dstCache must have been created, allocated, or retrieved from device
  • Each element of pSrcCaches must have been created, allocated, or retrieved from device

Host Synchronization

  • Host access to dstCache must be externally synchronized

Return Codes

Success
Failure

See Also

Device, ValidationCacheEXT

data ValidationCacheCreateInfoEXT Source #

VkValidationCacheCreateInfoEXT - Structure specifying parameters of a newly created validation cache

Valid Usage

  • If initialDataSize is not 0, it must be equal to the size of pInitialData, as returned by getValidationCacheDataEXT when pInitialData was originally retrieved

Valid Usage (Implicit)

  • pNext must be NULL
  • flags must be 0
  • If initialDataSize is not 0, pInitialData must be a valid pointer to an array of initialDataSize bytes

See Also

StructureType, ValidationCacheCreateFlagsEXT, createValidationCacheEXT

Constructors

ValidationCacheCreateInfoEXT 

Fields

  • flags :: ValidationCacheCreateFlagsEXT

    flags is reserved for future use.

  • initialDataSize :: Word64

    initialDataSize is the number of bytes in pInitialData. If initialDataSize is zero, the validation cache will initially be empty.

  • initialData :: Ptr ()

    pInitialData is a pointer to previously retrieved validation cache data. If the validation cache data is incompatible (as defined below) with the device, the validation cache will be initially empty. If initialDataSize is zero, pInitialData is ignored.

Instances

Instances details
Show ValidationCacheCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_validation_cache

Generic ValidationCacheCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_validation_cache

Associated Types

type Rep ValidationCacheCreateInfoEXT :: Type -> Type #

Storable ValidationCacheCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_validation_cache

FromCStruct ValidationCacheCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_validation_cache

ToCStruct ValidationCacheCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_validation_cache

Zero ValidationCacheCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_validation_cache

type Rep ValidationCacheCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_validation_cache

type Rep ValidationCacheCreateInfoEXT = D1 ('MetaData "ValidationCacheCreateInfoEXT" "Vulkan.Extensions.VK_EXT_validation_cache" "vulkan-3.6.1-inplace" 'False) (C1 ('MetaCons "ValidationCacheCreateInfoEXT" 'PrefixI 'True) (S1 ('MetaSel ('Just "flags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ValidationCacheCreateFlagsEXT) :*: (S1 ('MetaSel ('Just "initialDataSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word64) :*: S1 ('MetaSel ('Just "initialData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Ptr ())))))

data ShaderModuleValidationCacheCreateInfoEXT Source #

VkShaderModuleValidationCacheCreateInfoEXT - Specify validation cache to use during shader module creation

Valid Usage (Implicit)

See Also

StructureType, ValidationCacheEXT

Constructors

ShaderModuleValidationCacheCreateInfoEXT 

Fields

Instances

Instances details
Eq ShaderModuleValidationCacheCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_validation_cache

Show ShaderModuleValidationCacheCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_validation_cache

Generic ShaderModuleValidationCacheCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_validation_cache

Storable ShaderModuleValidationCacheCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_validation_cache

FromCStruct ShaderModuleValidationCacheCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_validation_cache

ToCStruct ShaderModuleValidationCacheCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_validation_cache

Zero ShaderModuleValidationCacheCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_validation_cache

type Rep ShaderModuleValidationCacheCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_validation_cache

type Rep ShaderModuleValidationCacheCreateInfoEXT = D1 ('MetaData "ShaderModuleValidationCacheCreateInfoEXT" "Vulkan.Extensions.VK_EXT_validation_cache" "vulkan-3.6.1-inplace" 'False) (C1 ('MetaCons "ShaderModuleValidationCacheCreateInfoEXT" 'PrefixI 'True) (S1 ('MetaSel ('Just "validationCache") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ValidationCacheEXT)))

newtype ValidationCacheCreateFlagsEXT Source #

VkValidationCacheCreateFlagsEXT - Reserved for future use

Description

ValidationCacheCreateFlagsEXT is a bitmask type for setting a mask, but is currently reserved for future use.

See Also

ValidationCacheCreateInfoEXT

Instances

Instances details
Eq ValidationCacheCreateFlagsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_validation_cache

Ord ValidationCacheCreateFlagsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_validation_cache

Read ValidationCacheCreateFlagsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_validation_cache

Show ValidationCacheCreateFlagsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_validation_cache

Storable ValidationCacheCreateFlagsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_validation_cache

Bits ValidationCacheCreateFlagsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_validation_cache

Methods

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

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

xor :: ValidationCacheCreateFlagsEXT -> ValidationCacheCreateFlagsEXT -> ValidationCacheCreateFlagsEXT #

complement :: ValidationCacheCreateFlagsEXT -> ValidationCacheCreateFlagsEXT #

shift :: ValidationCacheCreateFlagsEXT -> Int -> ValidationCacheCreateFlagsEXT #

rotate :: ValidationCacheCreateFlagsEXT -> Int -> ValidationCacheCreateFlagsEXT #

zeroBits :: ValidationCacheCreateFlagsEXT #

bit :: Int -> ValidationCacheCreateFlagsEXT #

setBit :: ValidationCacheCreateFlagsEXT -> Int -> ValidationCacheCreateFlagsEXT #

clearBit :: ValidationCacheCreateFlagsEXT -> Int -> ValidationCacheCreateFlagsEXT #

complementBit :: ValidationCacheCreateFlagsEXT -> Int -> ValidationCacheCreateFlagsEXT #

testBit :: ValidationCacheCreateFlagsEXT -> Int -> Bool #

bitSizeMaybe :: ValidationCacheCreateFlagsEXT -> Maybe Int #

bitSize :: ValidationCacheCreateFlagsEXT -> Int #

isSigned :: ValidationCacheCreateFlagsEXT -> Bool #

shiftL :: ValidationCacheCreateFlagsEXT -> Int -> ValidationCacheCreateFlagsEXT #

unsafeShiftL :: ValidationCacheCreateFlagsEXT -> Int -> ValidationCacheCreateFlagsEXT #

shiftR :: ValidationCacheCreateFlagsEXT -> Int -> ValidationCacheCreateFlagsEXT #

unsafeShiftR :: ValidationCacheCreateFlagsEXT -> Int -> ValidationCacheCreateFlagsEXT #

rotateL :: ValidationCacheCreateFlagsEXT -> Int -> ValidationCacheCreateFlagsEXT #

rotateR :: ValidationCacheCreateFlagsEXT -> Int -> ValidationCacheCreateFlagsEXT #

popCount :: ValidationCacheCreateFlagsEXT -> Int #

Zero ValidationCacheCreateFlagsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_validation_cache

newtype ValidationCacheHeaderVersionEXT Source #

VkValidationCacheHeaderVersionEXT - Encode validation cache version

See Also

createValidationCacheEXT, getValidationCacheDataEXT

Bundled Patterns

pattern VALIDATION_CACHE_HEADER_VERSION_ONE_EXT :: ValidationCacheHeaderVersionEXT

VALIDATION_CACHE_HEADER_VERSION_ONE_EXT specifies version one of the validation cache.

Instances

Instances details
Eq ValidationCacheHeaderVersionEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_validation_cache

Ord ValidationCacheHeaderVersionEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_validation_cache

Read ValidationCacheHeaderVersionEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_validation_cache

Show ValidationCacheHeaderVersionEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_validation_cache

Storable ValidationCacheHeaderVersionEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_validation_cache

Zero ValidationCacheHeaderVersionEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_validation_cache

type EXT_VALIDATION_CACHE_EXTENSION_NAME = "VK_EXT_validation_cache" Source #

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

newtype ValidationCacheEXT Source #

Instances

Instances details
Eq ValidationCacheEXT Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Ord ValidationCacheEXT Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Show ValidationCacheEXT Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Storable ValidationCacheEXT Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Zero ValidationCacheEXT Source # 
Instance details

Defined in Vulkan.Extensions.Handles

HasObjectType ValidationCacheEXT Source # 
Instance details

Defined in Vulkan.Extensions.Handles

IsHandle ValidationCacheEXT Source # 
Instance details

Defined in Vulkan.Extensions.Handles