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

Vulkan.Core10.Shader

Synopsis

Documentation

createShaderModule Source #

Arguments

:: forall a io. (Extendss ShaderModuleCreateInfo a, PokeChain a, MonadIO io) 
=> Device

device is the logical device that creates the shader module.

-> ShaderModuleCreateInfo a

pCreateInfo is a pointer to a ShaderModuleCreateInfo structure.

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

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

-> io ShaderModule 

vkCreateShaderModule - Creates a new shader module object

Description

Once a shader module has been created, any entry points it contains can be used in pipeline shader stages as described in Compute Pipelines and Graphics Pipelines.

If the shader stage fails to compile ERROR_INVALID_SHADER_NV will be generated and the compile log will be reported back to the application by VK_EXT_debug_report if enabled.

Valid Usage (Implicit)

  • device must be a valid Device handle

Return Codes

Success
Failure

See Also

AllocationCallbacks, Device, ShaderModule, ShaderModuleCreateInfo

withShaderModule :: forall a io r. (Extendss ShaderModuleCreateInfo a, PokeChain a, MonadIO io) => Device -> ShaderModuleCreateInfo a -> Maybe AllocationCallbacks -> (io ShaderModule -> (ShaderModule -> io ()) -> r) -> r Source #

A convenience wrapper to make a compatible pair of calls to createShaderModule and destroyShaderModule

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

destroyShaderModule Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that destroys the shader module.

-> ShaderModule

shaderModule is the handle of the shader module to destroy.

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

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

-> io () 

vkDestroyShaderModule - Destroy a shader module

Description

A shader module can be destroyed while pipelines created using its shaders are still in use.

Valid Usage

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

Valid Usage (Implicit)

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

Host Synchronization

  • Host access to shaderModule must be externally synchronized

See Also

AllocationCallbacks, Device, ShaderModule

data ShaderModuleCreateInfo (es :: [Type]) Source #

VkShaderModuleCreateInfo - Structure specifying parameters of a newly created shader module

Valid Usage

  • codeSize must be greater than 0
  • If pCode is a pointer to SPIR-V code, codeSize must be a multiple of 4
  • pCode must point to either valid SPIR-V code, formatted and packed as described by the Khronos SPIR-V Specification or valid GLSL code which must be written to the GL_KHR_vulkan_glsl extension specification
  • If pCode is a pointer to SPIR-V code, that code must adhere to the validation rules described by the Validation Rules within a Module section of the SPIR-V Environment appendix
  • If pCode is a pointer to GLSL code, it must be valid GLSL code written to the GL_KHR_vulkan_glsl GLSL extension specification
  • pCode must declare the Shader capability for SPIR-V code
  • pCode must not declare any capability that is not supported by the API, as described by the Capabilities section of the SPIR-V Environment appendix
  • If pCode declares any of the capabilities listed in the SPIR-V Environment appendix, one of the corresponding requirements must be satisfied

Valid Usage (Implicit)

  • pNext must be NULL or a pointer to a valid instance of ShaderModuleValidationCacheCreateInfoEXT
  • The sType value of each struct in the pNext chain must be unique
  • flags must be 0
  • pCode must be a valid pointer to an array of \(\textrm{codeSize} \over 4\) uint32_t values

See Also

ShaderModuleCreateFlags, StructureType, createShaderModule

Constructors

ShaderModuleCreateInfo 

Fields

  • next :: Chain es

    pNext is NULL or a pointer to a structure extending this structure.

  • flags :: ShaderModuleCreateFlags

    flags is reserved for future use.

  • code :: ByteString

    pCode is a pointer to code that is used to create the shader module. The type and format of the code is determined from the content of the memory addressed by pCode.

Instances

Instances details
Extensible ShaderModuleCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Shader

Methods

extensibleType :: StructureType Source #

getNext :: forall (es :: [Type]). ShaderModuleCreateInfo es -> Chain es Source #

setNext :: forall (ds :: [Type]) (es :: [Type]). ShaderModuleCreateInfo ds -> Chain es -> ShaderModuleCreateInfo es Source #

extends :: forall e b proxy. Typeable e => proxy e -> (Extends ShaderModuleCreateInfo e => b) -> Maybe b Source #

Show (Chain es) => Show (ShaderModuleCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Shader

Generic (ShaderModuleCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Shader

Associated Types

type Rep (ShaderModuleCreateInfo es) :: Type -> Type #

(Extendss ShaderModuleCreateInfo es, PeekChain es) => FromCStruct (ShaderModuleCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Shader

(Extendss ShaderModuleCreateInfo es, PokeChain es) => ToCStruct (ShaderModuleCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Shader

es ~ ('[] :: [Type]) => Zero (ShaderModuleCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Shader

type Rep (ShaderModuleCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Shader

type Rep (ShaderModuleCreateInfo es) = D1 ('MetaData "ShaderModuleCreateInfo" "Vulkan.Core10.Shader" "vulkan-3.6-inplace" 'False) (C1 ('MetaCons "ShaderModuleCreateInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "next") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Chain es)) :*: (S1 ('MetaSel ('Just "flags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ShaderModuleCreateFlags) :*: S1 ('MetaSel ('Just "code") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ByteString))))

newtype ShaderModule Source #

VkShaderModule - Opaque handle to a shader module object

See Also

PipelineShaderStageCreateInfo, createShaderModule, destroyShaderModule

Constructors

ShaderModule Word64 

Instances

Instances details
Eq ShaderModule Source # 
Instance details

Defined in Vulkan.Core10.Handles

Ord ShaderModule Source # 
Instance details

Defined in Vulkan.Core10.Handles

Show ShaderModule Source # 
Instance details

Defined in Vulkan.Core10.Handles

Storable ShaderModule Source # 
Instance details

Defined in Vulkan.Core10.Handles

Zero ShaderModule Source # 
Instance details

Defined in Vulkan.Core10.Handles

HasObjectType ShaderModule Source # 
Instance details

Defined in Vulkan.Core10.Handles

IsHandle ShaderModule Source # 
Instance details

Defined in Vulkan.Core10.Handles

newtype ShaderModuleCreateFlagBits Source #

Instances

Instances details
Eq ShaderModuleCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ShaderModuleCreateFlagBits

Ord ShaderModuleCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ShaderModuleCreateFlagBits

Read ShaderModuleCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ShaderModuleCreateFlagBits

Show ShaderModuleCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ShaderModuleCreateFlagBits

Storable ShaderModuleCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ShaderModuleCreateFlagBits

Bits ShaderModuleCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ShaderModuleCreateFlagBits

Methods

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

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

xor :: ShaderModuleCreateFlagBits -> ShaderModuleCreateFlagBits -> ShaderModuleCreateFlagBits #

complement :: ShaderModuleCreateFlagBits -> ShaderModuleCreateFlagBits #

shift :: ShaderModuleCreateFlagBits -> Int -> ShaderModuleCreateFlagBits #

rotate :: ShaderModuleCreateFlagBits -> Int -> ShaderModuleCreateFlagBits #

zeroBits :: ShaderModuleCreateFlagBits #

bit :: Int -> ShaderModuleCreateFlagBits #

setBit :: ShaderModuleCreateFlagBits -> Int -> ShaderModuleCreateFlagBits #

clearBit :: ShaderModuleCreateFlagBits -> Int -> ShaderModuleCreateFlagBits #

complementBit :: ShaderModuleCreateFlagBits -> Int -> ShaderModuleCreateFlagBits #

testBit :: ShaderModuleCreateFlagBits -> Int -> Bool #

bitSizeMaybe :: ShaderModuleCreateFlagBits -> Maybe Int #

bitSize :: ShaderModuleCreateFlagBits -> Int #

isSigned :: ShaderModuleCreateFlagBits -> Bool #

shiftL :: ShaderModuleCreateFlagBits -> Int -> ShaderModuleCreateFlagBits #

unsafeShiftL :: ShaderModuleCreateFlagBits -> Int -> ShaderModuleCreateFlagBits #

shiftR :: ShaderModuleCreateFlagBits -> Int -> ShaderModuleCreateFlagBits #

unsafeShiftR :: ShaderModuleCreateFlagBits -> Int -> ShaderModuleCreateFlagBits #

rotateL :: ShaderModuleCreateFlagBits -> Int -> ShaderModuleCreateFlagBits #

rotateR :: ShaderModuleCreateFlagBits -> Int -> ShaderModuleCreateFlagBits #

popCount :: ShaderModuleCreateFlagBits -> Int #

Zero ShaderModuleCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ShaderModuleCreateFlagBits