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

Vulkan.Core10.Sampler

Synopsis

Documentation

createSampler Source #

Arguments

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

device is the logical device that creates the sampler.

-> SamplerCreateInfo a

pCreateInfo is a pointer to a SamplerCreateInfo structure specifying the state of the sampler object.

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

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

-> io Sampler 

vkCreateSampler - Create a new sampler object

Valid Usage

  • There must be less than PhysicalDeviceLimits::maxSamplerAllocationCount VkSampler objects currently created on the device.

Valid Usage (Implicit)

  • device must be a valid Device handle
  • pCreateInfo must be a valid pointer to a valid SamplerCreateInfo structure
  • If pAllocator is not NULL, pAllocator must be a valid pointer to a valid AllocationCallbacks structure
  • pSampler must be a valid pointer to a Sampler handle

Return Codes

Success
Failure

See Also

AllocationCallbacks, Device, Sampler, SamplerCreateInfo

withSampler :: forall a io r. (Extendss SamplerCreateInfo a, PokeChain a, MonadIO io) => Device -> SamplerCreateInfo a -> Maybe AllocationCallbacks -> (io Sampler -> (Sampler -> io ()) -> r) -> r Source #

A convenience wrapper to make a compatible pair of calls to createSampler and destroySampler

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

destroySampler Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that destroys the sampler.

-> Sampler

sampler is the sampler to destroy.

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

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

-> io () 

vkDestroySampler - Destroy a sampler object

Valid Usage

  • All submitted commands that refer to sampler must have completed execution
  • If AllocationCallbacks were provided when sampler was created, a compatible set of callbacks must be provided here
  • If no AllocationCallbacks were provided when sampler was created, pAllocator must be NULL

Valid Usage (Implicit)

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

Host Synchronization

  • Host access to sampler must be externally synchronized

See Also

AllocationCallbacks, Device, Sampler

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

VkSamplerCreateInfo - Structure specifying parameters of a newly created sampler

Description

Mapping of OpenGL to Vulkan filter modes

magFilter values of FILTER_NEAREST and FILTER_LINEAR directly correspond to GL_NEAREST and GL_LINEAR magnification filters. minFilter and mipmapMode combine to correspond to the similarly named OpenGL minification filter of GL_minFilter_MIPMAP_mipmapMode (e.g. minFilter of FILTER_LINEAR and mipmapMode of SAMPLER_MIPMAP_MODE_NEAREST correspond to GL_LINEAR_MIPMAP_NEAREST).

There are no Vulkan filter modes that directly correspond to OpenGL minification filters of GL_LINEAR or GL_NEAREST, but they can be emulated using SAMPLER_MIPMAP_MODE_NEAREST, minLod = 0, and maxLod = 0.25, and using minFilter = FILTER_LINEAR or minFilter = FILTER_NEAREST, respectively.

Note that using a maxLod of zero would cause magnification to always be performed, and the magFilter to always be used. This is valid, just not an exact match for OpenGL behavior. Clamping the maximum LOD to 0.25 allows the λ value to be non-zero and minification to be performed, while still always rounding down to the base level. If the minFilter and magFilter are equal, then using a maxLod of zero also works.

The maximum number of sampler objects which can be simultaneously created on a device is implementation-dependent and specified by the maxSamplerAllocationCount member of the PhysicalDeviceLimits structure. If maxSamplerAllocationCount is exceeded, createSampler will return ERROR_TOO_MANY_OBJECTS.

Since Sampler is a non-dispatchable handle type, implementations may return the same handle for sampler state vectors that are identical. In such cases, all such objects would only count once against the maxSamplerAllocationCount limit.

Valid Usage

  • The absolute value of mipLodBias must be less than or equal to PhysicalDeviceLimits::maxSamplerLodBias

Valid Usage (Implicit)

See Also

Bool32, BorderColor, CompareOp, Filter, SamplerAddressMode, SamplerCreateFlags, SamplerMipmapMode, StructureType, createSampler

Constructors

SamplerCreateInfo 

Fields

Instances

Instances details
Extensible SamplerCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Sampler

Methods

extensibleType :: StructureType Source #

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

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

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

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

Defined in Vulkan.Core10.Sampler

Generic (SamplerCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Sampler

Associated Types

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

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

Defined in Vulkan.Core10.Sampler

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

Defined in Vulkan.Core10.Sampler

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

Defined in Vulkan.Core10.Sampler

type Rep (SamplerCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Sampler

type Rep (SamplerCreateInfo es) = D1 ('MetaData "SamplerCreateInfo" "Vulkan.Core10.Sampler" "vulkan-3.6-inplace" 'False) (C1 ('MetaCons "SamplerCreateInfo" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "next") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Chain es)) :*: S1 ('MetaSel ('Just "flags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SamplerCreateFlags)) :*: (S1 ('MetaSel ('Just "magFilter") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Filter) :*: S1 ('MetaSel ('Just "minFilter") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Filter))) :*: ((S1 ('MetaSel ('Just "mipmapMode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SamplerMipmapMode) :*: S1 ('MetaSel ('Just "addressModeU") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SamplerAddressMode)) :*: (S1 ('MetaSel ('Just "addressModeV") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SamplerAddressMode) :*: S1 ('MetaSel ('Just "addressModeW") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SamplerAddressMode)))) :*: (((S1 ('MetaSel ('Just "mipLodBias") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Float) :*: S1 ('MetaSel ('Just "anisotropyEnable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "maxAnisotropy") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Float) :*: S1 ('MetaSel ('Just "compareEnable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool))) :*: ((S1 ('MetaSel ('Just "compareOp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CompareOp) :*: S1 ('MetaSel ('Just "minLod") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Float)) :*: (S1 ('MetaSel ('Just "maxLod") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Float) :*: (S1 ('MetaSel ('Just "borderColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 BorderColor) :*: S1 ('MetaSel ('Just "unnormalizedCoordinates") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool)))))))

newtype Sampler Source #

Constructors

Sampler Word64 

Instances

Instances details
Eq Sampler Source # 
Instance details

Defined in Vulkan.Core10.Handles

Methods

(==) :: Sampler -> Sampler -> Bool #

(/=) :: Sampler -> Sampler -> Bool #

Ord Sampler Source # 
Instance details

Defined in Vulkan.Core10.Handles

Show Sampler Source # 
Instance details

Defined in Vulkan.Core10.Handles

Storable Sampler Source # 
Instance details

Defined in Vulkan.Core10.Handles

Zero Sampler Source # 
Instance details

Defined in Vulkan.Core10.Handles

Methods

zero :: Sampler Source #

HasObjectType Sampler Source # 
Instance details

Defined in Vulkan.Core10.Handles

IsHandle Sampler Source # 
Instance details

Defined in Vulkan.Core10.Handles

newtype BorderColor Source #

VkBorderColor - Specify border color used for texture lookups

Description

These colors are described in detail in Texel Replacement.

See Also

SamplerCreateInfo

Constructors

BorderColor Int32 

Bundled Patterns

pattern BORDER_COLOR_FLOAT_TRANSPARENT_BLACK :: BorderColor

BORDER_COLOR_FLOAT_TRANSPARENT_BLACK specifies a transparent, floating-point format, black color.

pattern BORDER_COLOR_INT_TRANSPARENT_BLACK :: BorderColor

BORDER_COLOR_INT_TRANSPARENT_BLACK specifies a transparent, integer format, black color.

pattern BORDER_COLOR_FLOAT_OPAQUE_BLACK :: BorderColor

BORDER_COLOR_FLOAT_OPAQUE_BLACK specifies an opaque, floating-point format, black color.

pattern BORDER_COLOR_INT_OPAQUE_BLACK :: BorderColor

BORDER_COLOR_INT_OPAQUE_BLACK specifies an opaque, integer format, black color.

pattern BORDER_COLOR_FLOAT_OPAQUE_WHITE :: BorderColor

BORDER_COLOR_FLOAT_OPAQUE_WHITE specifies an opaque, floating-point format, white color.

pattern BORDER_COLOR_INT_OPAQUE_WHITE :: BorderColor

BORDER_COLOR_INT_OPAQUE_WHITE specifies an opaque, integer format, white color.

pattern BORDER_COLOR_INT_CUSTOM_EXT :: BorderColor

BORDER_COLOR_INT_CUSTOM_EXT indicates that a SamplerCustomBorderColorCreateInfoEXT structure is present in the SamplerCreateInfo::pNext chain which contains the color data in integer format.

pattern BORDER_COLOR_FLOAT_CUSTOM_EXT :: BorderColor

BORDER_COLOR_FLOAT_CUSTOM_EXT indicates that a SamplerCustomBorderColorCreateInfoEXT structure is present in the SamplerCreateInfo::pNext chain which contains the color data in floating-point format.

Instances

Instances details
Eq BorderColor Source # 
Instance details

Defined in Vulkan.Core10.Enums.BorderColor

Ord BorderColor Source # 
Instance details

Defined in Vulkan.Core10.Enums.BorderColor

Read BorderColor Source # 
Instance details

Defined in Vulkan.Core10.Enums.BorderColor

Show BorderColor Source # 
Instance details

Defined in Vulkan.Core10.Enums.BorderColor

Storable BorderColor Source # 
Instance details

Defined in Vulkan.Core10.Enums.BorderColor

Zero BorderColor Source # 
Instance details

Defined in Vulkan.Core10.Enums.BorderColor

newtype Filter Source #

VkFilter - Specify filters used for texture lookups

Description

These filters are described in detail in Texel Filtering.

See Also

SamplerCreateInfo, SamplerYcbcrConversionCreateInfo, cmdBlitImage

Constructors

Filter Int32 

Bundled Patterns

pattern FILTER_NEAREST :: Filter

FILTER_NEAREST specifies nearest filtering.

pattern FILTER_LINEAR :: Filter

FILTER_LINEAR specifies linear filtering.

pattern FILTER_CUBIC_IMG :: Filter 

Instances

Instances details
Eq Filter Source # 
Instance details

Defined in Vulkan.Core10.Enums.Filter

Methods

(==) :: Filter -> Filter -> Bool #

(/=) :: Filter -> Filter -> Bool #

Ord Filter Source # 
Instance details

Defined in Vulkan.Core10.Enums.Filter

Read Filter Source # 
Instance details

Defined in Vulkan.Core10.Enums.Filter

Show Filter Source # 
Instance details

Defined in Vulkan.Core10.Enums.Filter

Storable Filter Source # 
Instance details

Defined in Vulkan.Core10.Enums.Filter

Zero Filter Source # 
Instance details

Defined in Vulkan.Core10.Enums.Filter

Methods

zero :: Filter Source #

newtype SamplerMipmapMode Source #

VkSamplerMipmapMode - Specify mipmap mode used for texture lookups

Description

These modes are described in detail in Texel Filtering.

See Also

SamplerCreateInfo

Constructors

SamplerMipmapMode Int32 

Bundled Patterns

pattern SAMPLER_MIPMAP_MODE_NEAREST :: SamplerMipmapMode

SAMPLER_MIPMAP_MODE_NEAREST specifies nearest filtering.

pattern SAMPLER_MIPMAP_MODE_LINEAR :: SamplerMipmapMode

SAMPLER_MIPMAP_MODE_LINEAR specifies linear filtering.

Instances

Instances details
Eq SamplerMipmapMode Source # 
Instance details

Defined in Vulkan.Core10.Enums.SamplerMipmapMode

Ord SamplerMipmapMode Source # 
Instance details

Defined in Vulkan.Core10.Enums.SamplerMipmapMode

Read SamplerMipmapMode Source # 
Instance details

Defined in Vulkan.Core10.Enums.SamplerMipmapMode

Show SamplerMipmapMode Source # 
Instance details

Defined in Vulkan.Core10.Enums.SamplerMipmapMode

Storable SamplerMipmapMode Source # 
Instance details

Defined in Vulkan.Core10.Enums.SamplerMipmapMode

Zero SamplerMipmapMode Source # 
Instance details

Defined in Vulkan.Core10.Enums.SamplerMipmapMode

newtype SamplerAddressMode Source #

VkSamplerAddressMode - Specify behavior of sampling with texture coordinates outside an image

See Also

SamplerCreateInfo

Bundled Patterns

pattern SAMPLER_ADDRESS_MODE_REPEAT :: SamplerAddressMode

SAMPLER_ADDRESS_MODE_REPEAT specifies that the repeat wrap mode will be used.

pattern SAMPLER_ADDRESS_MODE_MIRRORED_REPEAT :: SamplerAddressMode

SAMPLER_ADDRESS_MODE_MIRRORED_REPEAT specifies that the mirrored repeat wrap mode will be used.

pattern SAMPLER_ADDRESS_MODE_CLAMP_TO_EDGE :: SamplerAddressMode

SAMPLER_ADDRESS_MODE_CLAMP_TO_EDGE specifies that the clamp to edge wrap mode will be used.

pattern SAMPLER_ADDRESS_MODE_CLAMP_TO_BORDER :: SamplerAddressMode

SAMPLER_ADDRESS_MODE_CLAMP_TO_BORDER specifies that the clamp to border wrap mode will be used.

pattern SAMPLER_ADDRESS_MODE_MIRROR_CLAMP_TO_EDGE :: SamplerAddressMode

SAMPLER_ADDRESS_MODE_MIRROR_CLAMP_TO_EDGE specifies that the mirror clamp to edge wrap mode will be used. This is only valid if samplerMirrorClampToEdge is enabled, or if the VK_KHR_sampler_mirror_clamp_to_edge extension is enabled.

Instances

Instances details
Eq SamplerAddressMode Source # 
Instance details

Defined in Vulkan.Core10.Enums.SamplerAddressMode

Ord SamplerAddressMode Source # 
Instance details

Defined in Vulkan.Core10.Enums.SamplerAddressMode

Read SamplerAddressMode Source # 
Instance details

Defined in Vulkan.Core10.Enums.SamplerAddressMode

Show SamplerAddressMode Source # 
Instance details

Defined in Vulkan.Core10.Enums.SamplerAddressMode

Storable SamplerAddressMode Source # 
Instance details

Defined in Vulkan.Core10.Enums.SamplerAddressMode

Zero SamplerAddressMode Source # 
Instance details

Defined in Vulkan.Core10.Enums.SamplerAddressMode

newtype SamplerCreateFlagBits Source #

VkSamplerCreateFlagBits - Bitmask specifying additional parameters of sampler

Description

Note

The approximations used when SAMPLER_CREATE_SUBSAMPLED_COARSE_RECONSTRUCTION_BIT_EXT is specified are implementation defined. Some implementations may interpolate between fragment density levels in a subsampled image. In that case, this bit may be used to decide whether the interpolation factors are calculated per fragment or at a coarser granularity.

See Also

SamplerCreateFlags

Bundled Patterns

pattern SAMPLER_CREATE_SUBSAMPLED_COARSE_RECONSTRUCTION_BIT_EXT :: SamplerCreateFlagBits

SAMPLER_CREATE_SUBSAMPLED_COARSE_RECONSTRUCTION_BIT_EXT specifies that the implementation may use approximations when reconstructing a full color value for texture access from a subsampled image.

pattern SAMPLER_CREATE_SUBSAMPLED_BIT_EXT :: SamplerCreateFlagBits

SAMPLER_CREATE_SUBSAMPLED_BIT_EXT specifies that the sampler will read from an image created with flags containing IMAGE_CREATE_SUBSAMPLED_BIT_EXT.

Instances

Instances details
Eq SamplerCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.SamplerCreateFlagBits

Ord SamplerCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.SamplerCreateFlagBits

Read SamplerCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.SamplerCreateFlagBits

Show SamplerCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.SamplerCreateFlagBits

Storable SamplerCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.SamplerCreateFlagBits

Bits SamplerCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.SamplerCreateFlagBits

Zero SamplerCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.SamplerCreateFlagBits