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

Vulkan.Extensions.VK_EXT_transform_feedback

Synopsis

Documentation

cmdBindTransformFeedbackBuffersEXT Source #

Arguments

:: forall io. MonadIO io 
=> CommandBuffer

commandBuffer is the command buffer into which the command is recorded.

-> ("firstBinding" ::: Word32)

firstBinding is the index of the first transform feedback binding whose state is updated by the command.

-> ("buffers" ::: Vector Buffer)

pBuffers is a pointer to an array of buffer handles.

-> ("offsets" ::: Vector DeviceSize)

pOffsets is a pointer to an array of buffer offsets.

-> ("sizes" ::: Vector DeviceSize)

pSizes is an optional array of buffer sizes, specifying the maximum number of bytes to capture to the corresponding transform feedback buffer. If pSizes is NULL, or the value of the pSizes array element is WHOLE_SIZE, then the maximum bytes captured will be the size of the corresponding buffer minus the buffer offset.

-> io () 

vkCmdBindTransformFeedbackBuffersEXT - Bind transform feedback buffers to a command buffer

Description

The values taken from elements i of pBuffers, pOffsets and pSizes replace the current state for the transform feedback binding firstBinding + i, for i in [0, bindingCount). The transform feedback binding is updated to start at the offset indicated by pOffsets[i] from the start of the buffer pBuffers[i].

Valid Usage

Valid Usage (Implicit)

  • pBuffers must be a valid pointer to an array of bindingCount valid Buffer handles
  • pOffsets must be a valid pointer to an array of bindingCount DeviceSize values
  • commandBuffer must be in the recording state
  • The CommandPool that commandBuffer was allocated from must support graphics operations
  • bindingCount must be greater than 0
  • Both of commandBuffer, and the elements of pBuffers must have been created, allocated, or retrieved from the same Device

Host Synchronization

  • Host access to commandBuffer must be externally synchronized
  • Host access to the CommandPool that commandBuffer was allocated from must be externally synchronized

Command Properties

'

Command Buffer Levels Render Pass Scope Supported Queue Types Pipeline Type
Primary Secondary Both Graphics

See Also

Buffer, CommandBuffer, DeviceSize

cmdBeginTransformFeedbackEXT Source #

Arguments

:: forall io. MonadIO io 
=> CommandBuffer

commandBuffer is the command buffer into which the command is recorded.

-> ("firstCounterBuffer" ::: Word32)

firstCounterBuffer is the index of the first transform feedback buffer corresponding to pCounterBuffers[0] and pCounterBufferOffsets[0].

-> ("counterBuffers" ::: Vector Buffer)

pCounterBuffers is an optional array of buffer handles to the counter buffers which contain a 4 byte integer value representing the byte offset from the start of the corresponding transform feedback buffer from where to start capturing vertex data. If the byte offset stored to the counter buffer location was done using cmdEndTransformFeedbackEXT it can be used to resume transform feedback from the previous location. If pCounterBuffers is NULL, then transform feedback will start capturing vertex data to byte offset zero in all bound transform feedback buffers. For each element of pCounterBuffers that is NULL_HANDLE, transform feedback will start capturing vertex data to byte zero in the corresponding bound transform feedback buffer.

-> ("counterBufferOffsets" ::: Vector DeviceSize)

pCounterBufferOffsets is an optional array of offsets within each of the pCounterBuffers where the counter values were previously written. The location in each counter buffer at these offsets must be large enough to contain 4 bytes of data. This data is the number of bytes captured by the previous transform feedback to this buffer. If pCounterBufferOffsets is NULL, then it is assumed the offsets are zero.

-> io () 

vkCmdBeginTransformFeedbackEXT - Make transform feedback active in the command buffer

Description

The active transform feedback buffers will capture primitives emitted from the corresponding XfbBuffer in the bound graphics pipeline. Any XfbBuffer emitted that does not output to an active transform feedback buffer will not be captured.

Valid Usage

  • Transform feedback must not be active
  • firstCounterBuffer must be less than PhysicalDeviceTransformFeedbackPropertiesEXT::maxTransformFeedbackBuffers
  • The sum of firstCounterBuffer and counterBufferCount must be less than or equal to PhysicalDeviceTransformFeedbackPropertiesEXT::maxTransformFeedbackBuffers
  • If counterBufferCount is not 0, and pCounterBuffers is not NULL, pCounterBuffers must be a valid pointer to an array of counterBufferCount Buffer handles that are either valid or NULL_HANDLE
  • For each buffer handle in the array, if it is not NULL_HANDLE it must reference a buffer large enough to hold 4 bytes at the corresponding offset from the pCounterBufferOffsets array
  • If pCounterBuffer is NULL, then pCounterBufferOffsets must also be NULL
  • For each buffer handle in the pCounterBuffers array that is not NULL_HANDLE it must have been created with a usage value containing BUFFER_USAGE_TRANSFORM_FEEDBACK_COUNTER_BUFFER_BIT_EXT
  • The last vertex processing stage of the bound graphics pipeline must have been declared with the Xfb execution mode
  • Transform feedback must not be made active in a render pass instance with multiview enabled

Valid Usage (Implicit)

  • If counterBufferCount is not 0, and pCounterBufferOffsets is not NULL, pCounterBufferOffsets must be a valid pointer to an array of counterBufferCount DeviceSize values
  • commandBuffer must be in the recording state
  • The CommandPool that commandBuffer was allocated from must support graphics operations
  • This command must only be called inside of a render pass instance
  • Both of commandBuffer, and the elements of pCounterBuffers that are valid handles of non-ignored parameters must have been created, allocated, or retrieved from the same Device

Host Synchronization

  • Host access to commandBuffer must be externally synchronized
  • Host access to the CommandPool that commandBuffer was allocated from must be externally synchronized

Command Properties

'

Command Buffer Levels Render Pass Scope Supported Queue Types Pipeline Type
Primary Secondary Inside Graphics

See Also

Buffer, CommandBuffer, DeviceSize

cmdUseTransformFeedbackEXT :: forall io r. MonadIO io => CommandBuffer -> Word32 -> Vector Buffer -> Vector DeviceSize -> io r -> io r Source #

This function will call the supplied action between calls to cmdBeginTransformFeedbackEXT and cmdEndTransformFeedbackEXT

Note that cmdEndTransformFeedbackEXT is *not* called if an exception is thrown by the inner action.

cmdEndTransformFeedbackEXT Source #

Arguments

:: forall io. MonadIO io 
=> CommandBuffer

commandBuffer is the command buffer into which the command is recorded.

-> ("firstCounterBuffer" ::: Word32)

firstCounterBuffer is the index of the first transform feedback buffer corresponding to pCounterBuffers[0] and pCounterBufferOffsets[0].

-> ("counterBuffers" ::: Vector Buffer)

pCounterBuffers is an optional array of buffer handles to the counter buffers used to record the current byte positions of each transform feedback buffer where the next vertex output data would be captured. This can be used by a subsequent cmdBeginTransformFeedbackEXT call to resume transform feedback capture from this position. It can also be used by cmdDrawIndirectByteCountEXT to determine the vertex count of the draw call.

-> ("counterBufferOffsets" ::: Vector DeviceSize)

pCounterBufferOffsets is an optional array of offsets within each of the pCounterBuffers where the counter values can be written. The location in each counter buffer at these offsets must be large enough to contain 4 bytes of data. The data stored at this location is the byte offset from the start of the transform feedback buffer binding where the next vertex data would be written. If pCounterBufferOffsets is NULL, then it is assumed the offsets are zero.

-> io () 

vkCmdEndTransformFeedbackEXT - Make transform feedback inactive in the command buffer

Valid Usage

  • Transform feedback must be active
  • firstCounterBuffer must be less than PhysicalDeviceTransformFeedbackPropertiesEXT::maxTransformFeedbackBuffers
  • The sum of firstCounterBuffer and counterBufferCount must be less than or equal to PhysicalDeviceTransformFeedbackPropertiesEXT::maxTransformFeedbackBuffers
  • If counterBufferCount is not 0, and pCounterBuffers is not NULL, pCounterBuffers must be a valid pointer to an array of counterBufferCount Buffer handles that are either valid or NULL_HANDLE
  • For each buffer handle in the array, if it is not NULL_HANDLE it must reference a buffer large enough to hold 4 bytes at the corresponding offset from the pCounterBufferOffsets array
  • If pCounterBuffer is NULL, then pCounterBufferOffsets must also be NULL
  • For each buffer handle in the pCounterBuffers array that is not NULL_HANDLE it must have been created with a usage value containing BUFFER_USAGE_TRANSFORM_FEEDBACK_COUNTER_BUFFER_BIT_EXT

Valid Usage (Implicit)

  • If counterBufferCount is not 0, and pCounterBufferOffsets is not NULL, pCounterBufferOffsets must be a valid pointer to an array of counterBufferCount DeviceSize values
  • commandBuffer must be in the recording state
  • The CommandPool that commandBuffer was allocated from must support graphics operations
  • This command must only be called inside of a render pass instance
  • Both of commandBuffer, and the elements of pCounterBuffers that are valid handles of non-ignored parameters must have been created, allocated, or retrieved from the same Device

Host Synchronization

  • Host access to commandBuffer must be externally synchronized
  • Host access to the CommandPool that commandBuffer was allocated from must be externally synchronized

Command Properties

'

Command Buffer Levels Render Pass Scope Supported Queue Types Pipeline Type
Primary Secondary Inside Graphics

See Also

Buffer, CommandBuffer, DeviceSize

cmdBeginQueryIndexedEXT Source #

Arguments

:: forall io. MonadIO io 
=> CommandBuffer

commandBuffer is the command buffer into which this command will be recorded.

-> QueryPool

queryPool is the query pool that will manage the results of the query.

-> ("query" ::: Word32)

query is the query index within the query pool that will contain the results.

-> QueryControlFlags

flags is a bitmask of QueryControlFlagBits specifying constraints on the types of queries that can be performed.

-> ("index" ::: Word32)

index is the query type specific index. When the query type is QUERY_TYPE_TRANSFORM_FEEDBACK_STREAM_EXT the index represents the vertex stream.

-> io () 

vkCmdBeginQueryIndexedEXT - Begin an indexed query

Description

The cmdBeginQueryIndexedEXT command operates the same as the cmdBeginQuery command, except that it also accepts a query type specific index parameter.

Valid Usage

  • queryPool must have been created with a queryType that differs from that of any queries that are active within commandBuffer

Valid Usage (Implicit)

  • queryPool must be a valid QueryPool handle
  • flags must be a valid combination of QueryControlFlagBits values
  • commandBuffer must be in the recording state
  • The CommandPool that commandBuffer was allocated from must support graphics, or compute operations
  • Both of commandBuffer, and queryPool must have been created, allocated, or retrieved from the same Device

Host Synchronization

  • Host access to commandBuffer must be externally synchronized
  • Host access to the CommandPool that commandBuffer was allocated from must be externally synchronized

Command Properties

'

Command Buffer Levels Render Pass Scope Supported Queue Types Pipeline Type
Primary Secondary Both Graphics Compute

See Also

CommandBuffer, QueryControlFlags, QueryPool

cmdUseQueryIndexedEXT :: forall io r. MonadIO io => CommandBuffer -> QueryPool -> Word32 -> QueryControlFlags -> Word32 -> io r -> io r Source #

This function will call the supplied action between calls to cmdBeginQueryIndexedEXT and cmdEndQueryIndexedEXT

Note that cmdEndQueryIndexedEXT is *not* called if an exception is thrown by the inner action.

cmdEndQueryIndexedEXT Source #

Arguments

:: forall io. MonadIO io 
=> CommandBuffer

commandBuffer is the command buffer into which this command will be recorded.

-> QueryPool

queryPool is the query pool that is managing the results of the query.

-> ("query" ::: Word32)

query is the query index within the query pool where the result is stored.

-> ("index" ::: Word32)

index is the query type specific index.

-> io () 

vkCmdEndQueryIndexedEXT - Ends a query

Description

The cmdEndQueryIndexedEXT command operates the same as the cmdEndQuery command, except that it also accepts a query type specific index parameter.

Valid Usage

  • All queries used by the command must be active

Valid Usage (Implicit)

  • queryPool must be a valid QueryPool handle
  • commandBuffer must be in the recording state
  • The CommandPool that commandBuffer was allocated from must support graphics, or compute operations
  • Both of commandBuffer, and queryPool must have been created, allocated, or retrieved from the same Device

Host Synchronization

  • Host access to commandBuffer must be externally synchronized
  • Host access to the CommandPool that commandBuffer was allocated from must be externally synchronized

Command Properties

'

Command Buffer Levels Render Pass Scope Supported Queue Types Pipeline Type
Primary Secondary Both Graphics Compute

See Also

CommandBuffer, QueryPool

cmdDrawIndirectByteCountEXT Source #

Arguments

:: forall io. MonadIO io 
=> CommandBuffer

commandBuffer is the command buffer into which the command is recorded.

-> ("instanceCount" ::: Word32)

instanceCount is the number of instances to draw.

-> ("firstInstance" ::: Word32)

firstInstance is the instance ID of the first instance to draw.

-> ("counterBuffer" ::: Buffer)

counterBuffer is the buffer handle from where the byte count is read.

-> ("counterBufferOffset" ::: DeviceSize)

counterBufferOffset is the offset into the buffer used to read the byte count, which is used to calculate the vertex count for this draw call.

-> ("counterOffset" ::: Word32)

counterOffset is subtracted from the byte count read from the counterBuffer at the counterBufferOffset

-> ("vertexStride" ::: Word32)

vertexStride is the stride in bytes between each element of the vertex data that is used to calculate the vertex count from the counter value. This value is typically the same value that was used in the graphics pipeline state when the transform feedback was captured as the XfbStride.

-> io () 

vkCmdDrawIndirectByteCountEXT - Draw primitives where the vertex count is derived from the counter byte value in the counter buffer

Description

When the command is executed, primitives are assembled in the same way as done with cmdDraw except the vertexCount is calculated based on the byte count read from counterBuffer at offset counterBufferOffset. The assembled primitives execute the bound graphics pipeline.

The effective vertexCount is calculated as follows:

const uint32_t * counterBufferPtr = (const uint8_t *)counterBuffer.address + counterBufferOffset;
vertexCount = floor(max(0, (*counterBufferPtr - counterOffset)) / vertexStride);

The effective firstVertex is zero.

Valid Usage

Valid Usage (Implicit)

  • counterBuffer must be a valid Buffer handle
  • commandBuffer must be in the recording state
  • The CommandPool that commandBuffer was allocated from must support graphics operations
  • This command must only be called inside of a render pass instance
  • Both of commandBuffer, and counterBuffer must have been created, allocated, or retrieved from the same Device

Host Synchronization

  • Host access to commandBuffer must be externally synchronized
  • Host access to the CommandPool that commandBuffer was allocated from must be externally synchronized

Command Properties

'

Command Buffer Levels Render Pass Scope Supported Queue Types Pipeline Type
Primary Secondary Inside Graphics Graphics

See Also

Buffer, CommandBuffer, DeviceSize

data PhysicalDeviceTransformFeedbackFeaturesEXT Source #

VkPhysicalDeviceTransformFeedbackFeaturesEXT - Structure describing transform feedback features that can be supported by an implementation

Members

The members of the PhysicalDeviceTransformFeedbackFeaturesEXT structure describe the following features:

Description

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

Valid Usage (Implicit)

See Also

Bool32, StructureType

Constructors

PhysicalDeviceTransformFeedbackFeaturesEXT 

Fields

  • transformFeedback :: Bool

    transformFeedback indicates whether the implementation supports transform feedback and shader modules can declare the TransformFeedback capability.

  • geometryStreams :: Bool

    geometryStreams indicates whether the implementation supports the GeometryStreams SPIR-V capability.

Instances

Instances details
Eq PhysicalDeviceTransformFeedbackFeaturesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_transform_feedback

Show PhysicalDeviceTransformFeedbackFeaturesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_transform_feedback

Storable PhysicalDeviceTransformFeedbackFeaturesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_transform_feedback

FromCStruct PhysicalDeviceTransformFeedbackFeaturesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_transform_feedback

ToCStruct PhysicalDeviceTransformFeedbackFeaturesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_transform_feedback

Zero PhysicalDeviceTransformFeedbackFeaturesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_transform_feedback

data PhysicalDeviceTransformFeedbackPropertiesEXT Source #

VkPhysicalDeviceTransformFeedbackPropertiesEXT - Structure describing transform feedback properties that can be supported by an implementation

Members

The members of the PhysicalDeviceTransformFeedbackPropertiesEXT structure describe the following implementation-dependent limits:

Description

If the PhysicalDeviceTransformFeedbackPropertiesEXT structure is included in the pNext chain of PhysicalDeviceProperties2, it is filled with the implementation-dependent limits and properties.

Valid Usage (Implicit)

See Also

Bool32, DeviceSize, StructureType

Constructors

PhysicalDeviceTransformFeedbackPropertiesEXT 

Fields

Instances

Instances details
Eq PhysicalDeviceTransformFeedbackPropertiesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_transform_feedback

Show PhysicalDeviceTransformFeedbackPropertiesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_transform_feedback

Storable PhysicalDeviceTransformFeedbackPropertiesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_transform_feedback

FromCStruct PhysicalDeviceTransformFeedbackPropertiesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_transform_feedback

ToCStruct PhysicalDeviceTransformFeedbackPropertiesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_transform_feedback

Zero PhysicalDeviceTransformFeedbackPropertiesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_transform_feedback

data PipelineRasterizationStateStreamCreateInfoEXT Source #

VkPipelineRasterizationStateStreamCreateInfoEXT - Structure defining the geometry stream used for rasterization

Description

If this structure is not present, rasterizationStream is assumed to be zero.

Valid Usage (Implicit)

See Also

PipelineRasterizationStateStreamCreateFlagsEXT, StructureType

Constructors

PipelineRasterizationStateStreamCreateInfoEXT 

Fields

Instances

Instances details
Eq PipelineRasterizationStateStreamCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_transform_feedback

Show PipelineRasterizationStateStreamCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_transform_feedback

Storable PipelineRasterizationStateStreamCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_transform_feedback

FromCStruct PipelineRasterizationStateStreamCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_transform_feedback

ToCStruct PipelineRasterizationStateStreamCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_transform_feedback

Zero PipelineRasterizationStateStreamCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_transform_feedback

newtype PipelineRasterizationStateStreamCreateFlagsEXT Source #

VkPipelineRasterizationStateStreamCreateFlagsEXT - Reserved for future use

Description

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

See Also

PipelineRasterizationStateStreamCreateInfoEXT

Instances

Instances details
Eq PipelineRasterizationStateStreamCreateFlagsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_transform_feedback

Ord PipelineRasterizationStateStreamCreateFlagsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_transform_feedback

Read PipelineRasterizationStateStreamCreateFlagsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_transform_feedback

Show PipelineRasterizationStateStreamCreateFlagsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_transform_feedback

Storable PipelineRasterizationStateStreamCreateFlagsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_transform_feedback

Bits PipelineRasterizationStateStreamCreateFlagsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_transform_feedback

Methods

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

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

xor :: PipelineRasterizationStateStreamCreateFlagsEXT -> PipelineRasterizationStateStreamCreateFlagsEXT -> PipelineRasterizationStateStreamCreateFlagsEXT #

complement :: PipelineRasterizationStateStreamCreateFlagsEXT -> PipelineRasterizationStateStreamCreateFlagsEXT #

shift :: PipelineRasterizationStateStreamCreateFlagsEXT -> Int -> PipelineRasterizationStateStreamCreateFlagsEXT #

rotate :: PipelineRasterizationStateStreamCreateFlagsEXT -> Int -> PipelineRasterizationStateStreamCreateFlagsEXT #

zeroBits :: PipelineRasterizationStateStreamCreateFlagsEXT #

bit :: Int -> PipelineRasterizationStateStreamCreateFlagsEXT #

setBit :: PipelineRasterizationStateStreamCreateFlagsEXT -> Int -> PipelineRasterizationStateStreamCreateFlagsEXT #

clearBit :: PipelineRasterizationStateStreamCreateFlagsEXT -> Int -> PipelineRasterizationStateStreamCreateFlagsEXT #

complementBit :: PipelineRasterizationStateStreamCreateFlagsEXT -> Int -> PipelineRasterizationStateStreamCreateFlagsEXT #

testBit :: PipelineRasterizationStateStreamCreateFlagsEXT -> Int -> Bool #

bitSizeMaybe :: PipelineRasterizationStateStreamCreateFlagsEXT -> Maybe Int #

bitSize :: PipelineRasterizationStateStreamCreateFlagsEXT -> Int #

isSigned :: PipelineRasterizationStateStreamCreateFlagsEXT -> Bool #

shiftL :: PipelineRasterizationStateStreamCreateFlagsEXT -> Int -> PipelineRasterizationStateStreamCreateFlagsEXT #

unsafeShiftL :: PipelineRasterizationStateStreamCreateFlagsEXT -> Int -> PipelineRasterizationStateStreamCreateFlagsEXT #

shiftR :: PipelineRasterizationStateStreamCreateFlagsEXT -> Int -> PipelineRasterizationStateStreamCreateFlagsEXT #

unsafeShiftR :: PipelineRasterizationStateStreamCreateFlagsEXT -> Int -> PipelineRasterizationStateStreamCreateFlagsEXT #

rotateL :: PipelineRasterizationStateStreamCreateFlagsEXT -> Int -> PipelineRasterizationStateStreamCreateFlagsEXT #

rotateR :: PipelineRasterizationStateStreamCreateFlagsEXT -> Int -> PipelineRasterizationStateStreamCreateFlagsEXT #

popCount :: PipelineRasterizationStateStreamCreateFlagsEXT -> Int #

Zero PipelineRasterizationStateStreamCreateFlagsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_transform_feedback

type EXT_TRANSFORM_FEEDBACK_EXTENSION_NAME = "VK_EXT_transform_feedback" Source #

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