vulkan-api-1.1.2.1: Low-level low-overhead vulkan api bindings

Safe HaskellNone
LanguageHaskell2010

Graphics.Vulkan.Ext.VK_KHR_swapchain

Contents

Synopsis

Vulkan extension: VK_KHR_swapchain

supported: vulkan

contact: James Jones cubanismo,Ian Elliott ianelliottgoogle.com

author: KHR

type: device

Extension number: 2

Required extensions: VK_KHR_surface.

Required extensions: VK_KHR_surface.

type VkCreateSwapchainKHR = "vkCreateSwapchainKHR" Source #

type HS_vkCreateSwapchainKHR Source #

Arguments

 = VkDevice

device

-> Ptr VkSwapchainCreateInfoKHR

pCreateInfo

-> Ptr VkAllocationCallbacks

pAllocator

-> Ptr VkSwapchainKHR

pSwapchain

-> IO VkResult 

Success codes: VK_SUCCESS.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY, VK_ERROR_DEVICE_LOST, VK_ERROR_SURFACE_LOST_KHR, VK_ERROR_NATIVE_WINDOW_IN_USE_KHR.

VkResult vkCreateSwapchainKHR
    ( VkDevice device
    , const VkSwapchainCreateInfoKHR* pCreateInfo
    , const VkAllocationCallbacks* pAllocator
    , VkSwapchainKHR* pSwapchain
    )

vkCreateSwapchainKHR registry at www.khronos.org

vkCreateSwapchainKHR Source #

Arguments

:: VkDevice

device

-> Ptr VkSwapchainCreateInfoKHR

pCreateInfo

-> Ptr VkAllocationCallbacks

pAllocator

-> Ptr VkSwapchainKHR

pSwapchain

-> IO VkResult 

Success codes: VK_SUCCESS.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY, VK_ERROR_DEVICE_LOST, VK_ERROR_SURFACE_LOST_KHR, VK_ERROR_NATIVE_WINDOW_IN_USE_KHR.

VkResult vkCreateSwapchainKHR
    ( VkDevice device
    , const VkSwapchainCreateInfoKHR* pCreateInfo
    , const VkAllocationCallbacks* pAllocator
    , VkSwapchainKHR* pSwapchain
    )

vkCreateSwapchainKHR registry at www.khronos.org

Note: When useNativeFFI-1-0 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myCreateSwapchainKHR <- vkGetDeviceProc @VkCreateSwapchainKHR vkDevice

or less efficient:

myCreateSwapchainKHR <- vkGetProc @VkCreateSwapchainKHR

Note: vkXxx and vkXxxSafe versions of the call refer to using unsafe of safe FFI respectively.

vkCreateSwapchainKHRSafe Source #

Arguments

:: VkDevice

device

-> Ptr VkSwapchainCreateInfoKHR

pCreateInfo

-> Ptr VkAllocationCallbacks

pAllocator

-> Ptr VkSwapchainKHR

pSwapchain

-> IO VkResult 

Success codes: VK_SUCCESS.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY, VK_ERROR_DEVICE_LOST, VK_ERROR_SURFACE_LOST_KHR, VK_ERROR_NATIVE_WINDOW_IN_USE_KHR.

VkResult vkCreateSwapchainKHR
    ( VkDevice device
    , const VkSwapchainCreateInfoKHR* pCreateInfo
    , const VkAllocationCallbacks* pAllocator
    , VkSwapchainKHR* pSwapchain
    )

vkCreateSwapchainKHR registry at www.khronos.org

Note: When useNativeFFI-1-0 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myCreateSwapchainKHR <- vkGetDeviceProc @VkCreateSwapchainKHR vkDevice

or less efficient:

myCreateSwapchainKHR <- vkGetProc @VkCreateSwapchainKHR

Note: vkXxx and vkXxxSafe versions of the call refer to using unsafe of safe FFI respectively.

type VkDestroySwapchainKHR = "vkDestroySwapchainKHR" Source #

type HS_vkDestroySwapchainKHR Source #

Arguments

 = VkDevice

device

-> VkSwapchainKHR

swapchain

-> Ptr VkAllocationCallbacks

pAllocator

-> IO () 
void vkDestroySwapchainKHR
    ( VkDevice device
    , VkSwapchainKHR swapchain
    , const VkAllocationCallbacks* pAllocator
    )

vkDestroySwapchainKHR registry at www.khronos.org

vkDestroySwapchainKHR Source #

Arguments

:: VkDevice

device

-> VkSwapchainKHR

swapchain

-> Ptr VkAllocationCallbacks

pAllocator

-> IO () 
void vkDestroySwapchainKHR
    ( VkDevice device
    , VkSwapchainKHR swapchain
    , const VkAllocationCallbacks* pAllocator
    )

vkDestroySwapchainKHR registry at www.khronos.org

Note: When useNativeFFI-1-0 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myDestroySwapchainKHR <- vkGetDeviceProc @VkDestroySwapchainKHR vkDevice

or less efficient:

myDestroySwapchainKHR <- vkGetProc @VkDestroySwapchainKHR

Note: vkXxx and vkXxxSafe versions of the call refer to using unsafe of safe FFI respectively.

vkDestroySwapchainKHRSafe Source #

Arguments

:: VkDevice

device

-> VkSwapchainKHR

swapchain

-> Ptr VkAllocationCallbacks

pAllocator

-> IO () 
void vkDestroySwapchainKHR
    ( VkDevice device
    , VkSwapchainKHR swapchain
    , const VkAllocationCallbacks* pAllocator
    )

vkDestroySwapchainKHR registry at www.khronos.org

Note: When useNativeFFI-1-0 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myDestroySwapchainKHR <- vkGetDeviceProc @VkDestroySwapchainKHR vkDevice

or less efficient:

myDestroySwapchainKHR <- vkGetProc @VkDestroySwapchainKHR

Note: vkXxx and vkXxxSafe versions of the call refer to using unsafe of safe FFI respectively.

type VkGetSwapchainImagesKHR = "vkGetSwapchainImagesKHR" Source #

type HS_vkGetSwapchainImagesKHR Source #

Arguments

 = VkDevice

device

-> VkSwapchainKHR

swapchain

-> Ptr Word32

pSwapchainImageCount

-> Ptr VkImage

pSwapchainImages

-> IO VkResult 

Success codes: VK_SUCCESS, VK_INCOMPLETE.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY.

VkResult vkGetSwapchainImagesKHR
    ( VkDevice device
    , VkSwapchainKHR swapchain
    , uint32_t* pSwapchainImageCount
    , VkImage* pSwapchainImages
    )

vkGetSwapchainImagesKHR registry at www.khronos.org

vkGetSwapchainImagesKHR Source #

Arguments

:: VkDevice

device

-> VkSwapchainKHR

swapchain

-> Ptr Word32

pSwapchainImageCount

-> Ptr VkImage

pSwapchainImages

-> IO VkResult 

Success codes: VK_SUCCESS, VK_INCOMPLETE.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY.

VkResult vkGetSwapchainImagesKHR
    ( VkDevice device
    , VkSwapchainKHR swapchain
    , uint32_t* pSwapchainImageCount
    , VkImage* pSwapchainImages
    )

vkGetSwapchainImagesKHR registry at www.khronos.org

Note: When useNativeFFI-1-0 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetSwapchainImagesKHR <- vkGetDeviceProc @VkGetSwapchainImagesKHR vkDevice

or less efficient:

myGetSwapchainImagesKHR <- vkGetProc @VkGetSwapchainImagesKHR

Note: vkXxx and vkXxxSafe versions of the call refer to using unsafe of safe FFI respectively.

vkGetSwapchainImagesKHRSafe Source #

Arguments

:: VkDevice

device

-> VkSwapchainKHR

swapchain

-> Ptr Word32

pSwapchainImageCount

-> Ptr VkImage

pSwapchainImages

-> IO VkResult 

Success codes: VK_SUCCESS, VK_INCOMPLETE.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY.

VkResult vkGetSwapchainImagesKHR
    ( VkDevice device
    , VkSwapchainKHR swapchain
    , uint32_t* pSwapchainImageCount
    , VkImage* pSwapchainImages
    )

vkGetSwapchainImagesKHR registry at www.khronos.org

Note: When useNativeFFI-1-0 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetSwapchainImagesKHR <- vkGetDeviceProc @VkGetSwapchainImagesKHR vkDevice

or less efficient:

myGetSwapchainImagesKHR <- vkGetProc @VkGetSwapchainImagesKHR

Note: vkXxx and vkXxxSafe versions of the call refer to using unsafe of safe FFI respectively.

type VkAcquireNextImageKHR = "vkAcquireNextImageKHR" Source #

type HS_vkAcquireNextImageKHR Source #

Arguments

 = VkDevice

device

-> VkSwapchainKHR

swapchain

-> Word64

timeout

-> VkSemaphore

semaphore

-> VkFence

fence

-> Ptr Word32

pImageIndex

-> IO VkResult 

Success codes: VK_SUCCESS, VK_TIMEOUT, VK_NOT_READY, VK_SUBOPTIMAL_KHR.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY, VK_ERROR_DEVICE_LOST, VK_ERROR_OUT_OF_DATE_KHR, VK_ERROR_SURFACE_LOST_KHR.

VkResult vkAcquireNextImageKHR
    ( VkDevice device
    , VkSwapchainKHR swapchain
    , uint64_t timeout
    , VkSemaphore semaphore
    , VkFence fence
    , uint32_t* pImageIndex
    )

vkAcquireNextImageKHR registry at www.khronos.org

vkAcquireNextImageKHR Source #

Arguments

:: VkDevice

device

-> VkSwapchainKHR

swapchain

-> Word64

timeout

-> VkSemaphore

semaphore

-> VkFence

fence

-> Ptr Word32

pImageIndex

-> IO VkResult 

Success codes: VK_SUCCESS, VK_TIMEOUT, VK_NOT_READY, VK_SUBOPTIMAL_KHR.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY, VK_ERROR_DEVICE_LOST, VK_ERROR_OUT_OF_DATE_KHR, VK_ERROR_SURFACE_LOST_KHR.

VkResult vkAcquireNextImageKHR
    ( VkDevice device
    , VkSwapchainKHR swapchain
    , uint64_t timeout
    , VkSemaphore semaphore
    , VkFence fence
    , uint32_t* pImageIndex
    )

vkAcquireNextImageKHR registry at www.khronos.org

Note: When useNativeFFI-1-0 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myAcquireNextImageKHR <- vkGetDeviceProc @VkAcquireNextImageKHR vkDevice

or less efficient:

myAcquireNextImageKHR <- vkGetProc @VkAcquireNextImageKHR

Note: vkXxx and vkXxxSafe versions of the call refer to using unsafe of safe FFI respectively.

vkAcquireNextImageKHRSafe Source #

Arguments

:: VkDevice

device

-> VkSwapchainKHR

swapchain

-> Word64

timeout

-> VkSemaphore

semaphore

-> VkFence

fence

-> Ptr Word32

pImageIndex

-> IO VkResult 

Success codes: VK_SUCCESS, VK_TIMEOUT, VK_NOT_READY, VK_SUBOPTIMAL_KHR.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY, VK_ERROR_DEVICE_LOST, VK_ERROR_OUT_OF_DATE_KHR, VK_ERROR_SURFACE_LOST_KHR.

VkResult vkAcquireNextImageKHR
    ( VkDevice device
    , VkSwapchainKHR swapchain
    , uint64_t timeout
    , VkSemaphore semaphore
    , VkFence fence
    , uint32_t* pImageIndex
    )

vkAcquireNextImageKHR registry at www.khronos.org

Note: When useNativeFFI-1-0 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myAcquireNextImageKHR <- vkGetDeviceProc @VkAcquireNextImageKHR vkDevice

or less efficient:

myAcquireNextImageKHR <- vkGetProc @VkAcquireNextImageKHR

Note: vkXxx and vkXxxSafe versions of the call refer to using unsafe of safe FFI respectively.

type VkQueuePresentKHR = "vkQueuePresentKHR" Source #

type HS_vkQueuePresentKHR Source #

Arguments

 = VkQueue

queue

-> Ptr VkPresentInfoKHR

pPresentInfo

-> IO VkResult 

Success codes: VK_SUCCESS, VK_SUBOPTIMAL_KHR.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY, VK_ERROR_DEVICE_LOST, VK_ERROR_OUT_OF_DATE_KHR, VK_ERROR_SURFACE_LOST_KHR.

VkResult vkQueuePresentKHR
    ( VkQueue queue
    , const VkPresentInfoKHR* pPresentInfo
    )

vkQueuePresentKHR registry at www.khronos.org

vkQueuePresentKHR Source #

Arguments

:: VkQueue

queue

-> Ptr VkPresentInfoKHR

pPresentInfo

-> IO VkResult 

Success codes: VK_SUCCESS, VK_SUBOPTIMAL_KHR.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY, VK_ERROR_DEVICE_LOST, VK_ERROR_OUT_OF_DATE_KHR, VK_ERROR_SURFACE_LOST_KHR.

VkResult vkQueuePresentKHR
    ( VkQueue queue
    , const VkPresentInfoKHR* pPresentInfo
    )

vkQueuePresentKHR registry at www.khronos.org

Note: When useNativeFFI-1-0 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myQueuePresentKHR <- vkGetInstanceProc @VkQueuePresentKHR vkInstance

or less efficient:

myQueuePresentKHR <- vkGetProc @VkQueuePresentKHR

Note: vkXxx and vkXxxSafe versions of the call refer to using unsafe of safe FFI respectively.

vkQueuePresentKHRSafe Source #

Arguments

:: VkQueue

queue

-> Ptr VkPresentInfoKHR

pPresentInfo

-> IO VkResult 

Success codes: VK_SUCCESS, VK_SUBOPTIMAL_KHR.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY, VK_ERROR_DEVICE_LOST, VK_ERROR_OUT_OF_DATE_KHR, VK_ERROR_SURFACE_LOST_KHR.

VkResult vkQueuePresentKHR
    ( VkQueue queue
    , const VkPresentInfoKHR* pPresentInfo
    )

vkQueuePresentKHR registry at www.khronos.org

Note: When useNativeFFI-1-0 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myQueuePresentKHR <- vkGetInstanceProc @VkQueuePresentKHR vkInstance

or less efficient:

myQueuePresentKHR <- vkGetProc @VkQueuePresentKHR

Note: vkXxx and vkXxxSafe versions of the call refer to using unsafe of safe FFI respectively.

newtype VkBool32 Source #

Constructors

VkBool32 Word32 

Instances

Bounded VkBool32 Source # 
Enum VkBool32 Source # 
Eq VkBool32 Source # 
Integral VkBool32 Source # 
Data VkBool32 Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkBool32 -> c VkBool32 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkBool32 #

toConstr :: VkBool32 -> Constr #

dataTypeOf :: VkBool32 -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkBool32) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkBool32) #

gmapT :: (forall b. Data b => b -> b) -> VkBool32 -> VkBool32 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkBool32 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkBool32 -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkBool32 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkBool32 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkBool32 -> m VkBool32 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkBool32 -> m VkBool32 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkBool32 -> m VkBool32 #

Num VkBool32 Source # 
Ord VkBool32 Source # 
Read VkBool32 Source # 
Real VkBool32 Source # 
Show VkBool32 Source # 
Generic VkBool32 Source # 

Associated Types

type Rep VkBool32 :: * -> * #

Methods

from :: VkBool32 -> Rep VkBool32 x #

to :: Rep VkBool32 x -> VkBool32 #

Storable VkBool32 Source # 
Bits VkBool32 Source # 
FiniteBits VkBool32 Source # 
type Rep VkBool32 Source # 
type Rep VkBool32 = D1 (MetaData "VkBool32" "Graphics.Vulkan.Types.BaseTypes" "vulkan-api-1.1.2.1-GcVsfRwwhb24i5dsYq91EC" True) (C1 (MetaCons "VkBool32" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word32)))

newtype VkDeviceSize Source #

Constructors

VkDeviceSize Word64 

Instances

Bounded VkDeviceSize Source # 
Enum VkDeviceSize Source # 
Eq VkDeviceSize Source # 
Integral VkDeviceSize Source # 
Data VkDeviceSize Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkDeviceSize -> c VkDeviceSize #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkDeviceSize #

toConstr :: VkDeviceSize -> Constr #

dataTypeOf :: VkDeviceSize -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkDeviceSize) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkDeviceSize) #

gmapT :: (forall b. Data b => b -> b) -> VkDeviceSize -> VkDeviceSize #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkDeviceSize -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkDeviceSize -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkDeviceSize -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkDeviceSize -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkDeviceSize -> m VkDeviceSize #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkDeviceSize -> m VkDeviceSize #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkDeviceSize -> m VkDeviceSize #

Num VkDeviceSize Source # 
Ord VkDeviceSize Source # 
Read VkDeviceSize Source # 
Real VkDeviceSize Source # 
Show VkDeviceSize Source # 
Generic VkDeviceSize Source # 

Associated Types

type Rep VkDeviceSize :: * -> * #

Storable VkDeviceSize Source # 
Bits VkDeviceSize Source # 
FiniteBits VkDeviceSize Source # 
type Rep VkDeviceSize Source # 
type Rep VkDeviceSize = D1 (MetaData "VkDeviceSize" "Graphics.Vulkan.Types.BaseTypes" "vulkan-api-1.1.2.1-GcVsfRwwhb24i5dsYq91EC" True) (C1 (MetaCons "VkDeviceSize" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64)))

newtype VkFlags Source #

Constructors

VkFlags Word32 

Instances

Bounded VkFlags Source # 
Enum VkFlags Source # 
Eq VkFlags Source # 

Methods

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

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

Integral VkFlags Source # 
Data VkFlags Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkFlags -> c VkFlags #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkFlags #

toConstr :: VkFlags -> Constr #

dataTypeOf :: VkFlags -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkFlags) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkFlags) #

gmapT :: (forall b. Data b => b -> b) -> VkFlags -> VkFlags #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkFlags -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkFlags -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkFlags -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkFlags -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkFlags -> m VkFlags #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkFlags -> m VkFlags #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkFlags -> m VkFlags #

Num VkFlags Source # 
Ord VkFlags Source # 
Read VkFlags Source # 
Real VkFlags Source # 
Show VkFlags Source # 
Generic VkFlags Source # 

Associated Types

type Rep VkFlags :: * -> * #

Methods

from :: VkFlags -> Rep VkFlags x #

to :: Rep VkFlags x -> VkFlags #

Storable VkFlags Source # 
Bits VkFlags Source # 
FiniteBits VkFlags Source # 
type Rep VkFlags Source # 
type Rep VkFlags = D1 (MetaData "VkFlags" "Graphics.Vulkan.Types.BaseTypes" "vulkan-api-1.1.2.1-GcVsfRwwhb24i5dsYq91EC" True) (C1 (MetaCons "VkFlags" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word32)))

newtype VkSampleMask Source #

Constructors

VkSampleMask Word32 

Instances

Bounded VkSampleMask Source # 
Enum VkSampleMask Source # 
Eq VkSampleMask Source # 
Integral VkSampleMask Source # 
Data VkSampleMask Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkSampleMask -> c VkSampleMask #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkSampleMask #

toConstr :: VkSampleMask -> Constr #

dataTypeOf :: VkSampleMask -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkSampleMask) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkSampleMask) #

gmapT :: (forall b. Data b => b -> b) -> VkSampleMask -> VkSampleMask #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkSampleMask -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkSampleMask -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkSampleMask -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkSampleMask -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkSampleMask -> m VkSampleMask #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSampleMask -> m VkSampleMask #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSampleMask -> m VkSampleMask #

Num VkSampleMask Source # 
Ord VkSampleMask Source # 
Read VkSampleMask Source # 
Real VkSampleMask Source # 
Show VkSampleMask Source # 
Generic VkSampleMask Source # 

Associated Types

type Rep VkSampleMask :: * -> * #

Storable VkSampleMask Source # 
Bits VkSampleMask Source # 
FiniteBits VkSampleMask Source # 
type Rep VkSampleMask Source # 
type Rep VkSampleMask = D1 (MetaData "VkSampleMask" "Graphics.Vulkan.Types.BaseTypes" "vulkan-api-1.1.2.1-GcVsfRwwhb24i5dsYq91EC" True) (C1 (MetaCons "VkSampleMask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word32)))

newtype VkColorComponentBitmask a Source #

Instances

Bounded (VkColorComponentBitmask FlagMask) Source # 
Enum (VkColorComponentBitmask FlagMask) Source # 
Eq (VkColorComponentBitmask a) Source # 
Integral (VkColorComponentBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkColorComponentBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkColorComponentBitmask a -> c (VkColorComponentBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkColorComponentBitmask a) #

toConstr :: VkColorComponentBitmask a -> Constr #

dataTypeOf :: VkColorComponentBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkColorComponentBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkColorComponentBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkColorComponentBitmask a -> VkColorComponentBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkColorComponentBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkColorComponentBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkColorComponentBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkColorComponentBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkColorComponentBitmask a -> m (VkColorComponentBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkColorComponentBitmask a -> m (VkColorComponentBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkColorComponentBitmask a -> m (VkColorComponentBitmask a) #

Num (VkColorComponentBitmask FlagMask) Source # 
Ord (VkColorComponentBitmask a) Source # 
Read (VkColorComponentBitmask a) Source # 
Real (VkColorComponentBitmask FlagMask) Source # 
Show (VkColorComponentBitmask a) Source # 
Generic (VkColorComponentBitmask a) Source # 
Storable (VkColorComponentBitmask a) Source # 
Bits (VkColorComponentBitmask FlagMask) Source # 

Methods

(.&.) :: VkColorComponentBitmask FlagMask -> VkColorComponentBitmask FlagMask -> VkColorComponentBitmask FlagMask #

(.|.) :: VkColorComponentBitmask FlagMask -> VkColorComponentBitmask FlagMask -> VkColorComponentBitmask FlagMask #

xor :: VkColorComponentBitmask FlagMask -> VkColorComponentBitmask FlagMask -> VkColorComponentBitmask FlagMask #

complement :: VkColorComponentBitmask FlagMask -> VkColorComponentBitmask FlagMask #

shift :: VkColorComponentBitmask FlagMask -> Int -> VkColorComponentBitmask FlagMask #

rotate :: VkColorComponentBitmask FlagMask -> Int -> VkColorComponentBitmask FlagMask #

zeroBits :: VkColorComponentBitmask FlagMask #

bit :: Int -> VkColorComponentBitmask FlagMask #

setBit :: VkColorComponentBitmask FlagMask -> Int -> VkColorComponentBitmask FlagMask #

clearBit :: VkColorComponentBitmask FlagMask -> Int -> VkColorComponentBitmask FlagMask #

complementBit :: VkColorComponentBitmask FlagMask -> Int -> VkColorComponentBitmask FlagMask #

testBit :: VkColorComponentBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkColorComponentBitmask FlagMask -> Maybe Int #

bitSize :: VkColorComponentBitmask FlagMask -> Int #

isSigned :: VkColorComponentBitmask FlagMask -> Bool #

shiftL :: VkColorComponentBitmask FlagMask -> Int -> VkColorComponentBitmask FlagMask #

unsafeShiftL :: VkColorComponentBitmask FlagMask -> Int -> VkColorComponentBitmask FlagMask #

shiftR :: VkColorComponentBitmask FlagMask -> Int -> VkColorComponentBitmask FlagMask #

unsafeShiftR :: VkColorComponentBitmask FlagMask -> Int -> VkColorComponentBitmask FlagMask #

rotateL :: VkColorComponentBitmask FlagMask -> Int -> VkColorComponentBitmask FlagMask #

rotateR :: VkColorComponentBitmask FlagMask -> Int -> VkColorComponentBitmask FlagMask #

popCount :: VkColorComponentBitmask FlagMask -> Int #

FiniteBits (VkColorComponentBitmask FlagMask) Source # 
type Rep (VkColorComponentBitmask a) Source # 
type Rep (VkColorComponentBitmask a) = D1 (MetaData "VkColorComponentBitmask" "Graphics.Vulkan.Types.Enum.Color" "vulkan-api-1.1.2.1-GcVsfRwwhb24i5dsYq91EC" True) (C1 (MetaCons "VkColorComponentBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

pattern VK_COLOR_COMPONENT_R_BIT :: forall a. VkColorComponentBitmask a Source #

bitpos = 0

pattern VK_COLOR_COMPONENT_G_BIT :: forall a. VkColorComponentBitmask a Source #

bitpos = 1

pattern VK_COLOR_COMPONENT_B_BIT :: forall a. VkColorComponentBitmask a Source #

bitpos = 2

pattern VK_COLOR_COMPONENT_A_BIT :: forall a. VkColorComponentBitmask a Source #

bitpos = 3

newtype VkColorSpaceKHR Source #

Constructors

VkColorSpaceKHR Int32 

Instances

Bounded VkColorSpaceKHR Source # 
Enum VkColorSpaceKHR Source # 
Eq VkColorSpaceKHR Source # 
Data VkColorSpaceKHR Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkColorSpaceKHR -> c VkColorSpaceKHR #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkColorSpaceKHR #

toConstr :: VkColorSpaceKHR -> Constr #

dataTypeOf :: VkColorSpaceKHR -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkColorSpaceKHR) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkColorSpaceKHR) #

gmapT :: (forall b. Data b => b -> b) -> VkColorSpaceKHR -> VkColorSpaceKHR #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkColorSpaceKHR -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkColorSpaceKHR -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkColorSpaceKHR -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkColorSpaceKHR -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkColorSpaceKHR -> m VkColorSpaceKHR #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkColorSpaceKHR -> m VkColorSpaceKHR #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkColorSpaceKHR -> m VkColorSpaceKHR #

Num VkColorSpaceKHR Source # 
Ord VkColorSpaceKHR Source # 
Read VkColorSpaceKHR Source # 
Show VkColorSpaceKHR Source # 
Generic VkColorSpaceKHR Source # 
Storable VkColorSpaceKHR Source # 
type Rep VkColorSpaceKHR Source # 
type Rep VkColorSpaceKHR = D1 (MetaData "VkColorSpaceKHR" "Graphics.Vulkan.Types.Enum.Color" "vulkan-api-1.1.2.1-GcVsfRwwhb24i5dsYq91EC" True) (C1 (MetaCons "VkColorSpaceKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

newtype VkCompositeAlphaBitmaskKHR a Source #

Instances

Bounded (VkCompositeAlphaBitmaskKHR FlagMask) Source # 
Enum (VkCompositeAlphaBitmaskKHR FlagMask) Source # 
Eq (VkCompositeAlphaBitmaskKHR a) Source # 
Integral (VkCompositeAlphaBitmaskKHR FlagMask) Source # 
Typeable FlagType a => Data (VkCompositeAlphaBitmaskKHR a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkCompositeAlphaBitmaskKHR a -> c (VkCompositeAlphaBitmaskKHR a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkCompositeAlphaBitmaskKHR a) #

toConstr :: VkCompositeAlphaBitmaskKHR a -> Constr #

dataTypeOf :: VkCompositeAlphaBitmaskKHR a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkCompositeAlphaBitmaskKHR a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkCompositeAlphaBitmaskKHR a)) #

gmapT :: (forall b. Data b => b -> b) -> VkCompositeAlphaBitmaskKHR a -> VkCompositeAlphaBitmaskKHR a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkCompositeAlphaBitmaskKHR a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkCompositeAlphaBitmaskKHR a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkCompositeAlphaBitmaskKHR a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkCompositeAlphaBitmaskKHR a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkCompositeAlphaBitmaskKHR a -> m (VkCompositeAlphaBitmaskKHR a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkCompositeAlphaBitmaskKHR a -> m (VkCompositeAlphaBitmaskKHR a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkCompositeAlphaBitmaskKHR a -> m (VkCompositeAlphaBitmaskKHR a) #

Num (VkCompositeAlphaBitmaskKHR FlagMask) Source # 
Ord (VkCompositeAlphaBitmaskKHR a) Source # 
Read (VkCompositeAlphaBitmaskKHR a) Source # 
Real (VkCompositeAlphaBitmaskKHR FlagMask) Source # 
Show (VkCompositeAlphaBitmaskKHR a) Source # 
Generic (VkCompositeAlphaBitmaskKHR a) Source # 
Storable (VkCompositeAlphaBitmaskKHR a) Source # 
Bits (VkCompositeAlphaBitmaskKHR FlagMask) Source # 

Methods

(.&.) :: VkCompositeAlphaBitmaskKHR FlagMask -> VkCompositeAlphaBitmaskKHR FlagMask -> VkCompositeAlphaBitmaskKHR FlagMask #

(.|.) :: VkCompositeAlphaBitmaskKHR FlagMask -> VkCompositeAlphaBitmaskKHR FlagMask -> VkCompositeAlphaBitmaskKHR FlagMask #

xor :: VkCompositeAlphaBitmaskKHR FlagMask -> VkCompositeAlphaBitmaskKHR FlagMask -> VkCompositeAlphaBitmaskKHR FlagMask #

complement :: VkCompositeAlphaBitmaskKHR FlagMask -> VkCompositeAlphaBitmaskKHR FlagMask #

shift :: VkCompositeAlphaBitmaskKHR FlagMask -> Int -> VkCompositeAlphaBitmaskKHR FlagMask #

rotate :: VkCompositeAlphaBitmaskKHR FlagMask -> Int -> VkCompositeAlphaBitmaskKHR FlagMask #

zeroBits :: VkCompositeAlphaBitmaskKHR FlagMask #

bit :: Int -> VkCompositeAlphaBitmaskKHR FlagMask #

setBit :: VkCompositeAlphaBitmaskKHR FlagMask -> Int -> VkCompositeAlphaBitmaskKHR FlagMask #

clearBit :: VkCompositeAlphaBitmaskKHR FlagMask -> Int -> VkCompositeAlphaBitmaskKHR FlagMask #

complementBit :: VkCompositeAlphaBitmaskKHR FlagMask -> Int -> VkCompositeAlphaBitmaskKHR FlagMask #

testBit :: VkCompositeAlphaBitmaskKHR FlagMask -> Int -> Bool #

bitSizeMaybe :: VkCompositeAlphaBitmaskKHR FlagMask -> Maybe Int #

bitSize :: VkCompositeAlphaBitmaskKHR FlagMask -> Int #

isSigned :: VkCompositeAlphaBitmaskKHR FlagMask -> Bool #

shiftL :: VkCompositeAlphaBitmaskKHR FlagMask -> Int -> VkCompositeAlphaBitmaskKHR FlagMask #

unsafeShiftL :: VkCompositeAlphaBitmaskKHR FlagMask -> Int -> VkCompositeAlphaBitmaskKHR FlagMask #

shiftR :: VkCompositeAlphaBitmaskKHR FlagMask -> Int -> VkCompositeAlphaBitmaskKHR FlagMask #

unsafeShiftR :: VkCompositeAlphaBitmaskKHR FlagMask -> Int -> VkCompositeAlphaBitmaskKHR FlagMask #

rotateL :: VkCompositeAlphaBitmaskKHR FlagMask -> Int -> VkCompositeAlphaBitmaskKHR FlagMask #

rotateR :: VkCompositeAlphaBitmaskKHR FlagMask -> Int -> VkCompositeAlphaBitmaskKHR FlagMask #

popCount :: VkCompositeAlphaBitmaskKHR FlagMask -> Int #

FiniteBits (VkCompositeAlphaBitmaskKHR FlagMask) Source # 
type Rep (VkCompositeAlphaBitmaskKHR a) Source # 
type Rep (VkCompositeAlphaBitmaskKHR a) = D1 (MetaData "VkCompositeAlphaBitmaskKHR" "Graphics.Vulkan.Types.Enum.CompositeAlphaFlagsKHR" "vulkan-api-1.1.2.1-GcVsfRwwhb24i5dsYq91EC" True) (C1 (MetaCons "VkCompositeAlphaBitmaskKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkFormat Source #

Vulkan format definitions

type = enum

VkFormat registry at www.khronos.org

Constructors

VkFormat Int32 

Instances

Bounded VkFormat Source # 
Enum VkFormat Source # 
Eq VkFormat Source # 
Data VkFormat Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkFormat -> c VkFormat #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkFormat #

toConstr :: VkFormat -> Constr #

dataTypeOf :: VkFormat -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkFormat) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkFormat) #

gmapT :: (forall b. Data b => b -> b) -> VkFormat -> VkFormat #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkFormat -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkFormat -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkFormat -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkFormat -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkFormat -> m VkFormat #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkFormat -> m VkFormat #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkFormat -> m VkFormat #

Num VkFormat Source # 
Ord VkFormat Source # 
Read VkFormat Source # 
Show VkFormat Source # 
Generic VkFormat Source # 

Associated Types

type Rep VkFormat :: * -> * #

Methods

from :: VkFormat -> Rep VkFormat x #

to :: Rep VkFormat x -> VkFormat #

Storable VkFormat Source # 
type Rep VkFormat Source # 
type Rep VkFormat = D1 (MetaData "VkFormat" "Graphics.Vulkan.Types.Enum.Format" "vulkan-api-1.1.2.1-GcVsfRwwhb24i5dsYq91EC" True) (C1 (MetaCons "VkFormat" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

newtype VkFormatFeatureBitmask a Source #

Instances

Bounded (VkFormatFeatureBitmask FlagMask) Source # 
Enum (VkFormatFeatureBitmask FlagMask) Source # 
Eq (VkFormatFeatureBitmask a) Source # 
Integral (VkFormatFeatureBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkFormatFeatureBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkFormatFeatureBitmask a -> c (VkFormatFeatureBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkFormatFeatureBitmask a) #

toConstr :: VkFormatFeatureBitmask a -> Constr #

dataTypeOf :: VkFormatFeatureBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkFormatFeatureBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkFormatFeatureBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkFormatFeatureBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkFormatFeatureBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkFormatFeatureBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkFormatFeatureBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkFormatFeatureBitmask a -> m (VkFormatFeatureBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkFormatFeatureBitmask a -> m (VkFormatFeatureBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkFormatFeatureBitmask a -> m (VkFormatFeatureBitmask a) #

Num (VkFormatFeatureBitmask FlagMask) Source # 
Ord (VkFormatFeatureBitmask a) Source # 
Read (VkFormatFeatureBitmask a) Source # 
Real (VkFormatFeatureBitmask FlagMask) Source # 
Show (VkFormatFeatureBitmask a) Source # 
Generic (VkFormatFeatureBitmask a) Source # 
Storable (VkFormatFeatureBitmask a) Source # 
Bits (VkFormatFeatureBitmask FlagMask) Source # 

Methods

(.&.) :: VkFormatFeatureBitmask FlagMask -> VkFormatFeatureBitmask FlagMask -> VkFormatFeatureBitmask FlagMask #

(.|.) :: VkFormatFeatureBitmask FlagMask -> VkFormatFeatureBitmask FlagMask -> VkFormatFeatureBitmask FlagMask #

xor :: VkFormatFeatureBitmask FlagMask -> VkFormatFeatureBitmask FlagMask -> VkFormatFeatureBitmask FlagMask #

complement :: VkFormatFeatureBitmask FlagMask -> VkFormatFeatureBitmask FlagMask #

shift :: VkFormatFeatureBitmask FlagMask -> Int -> VkFormatFeatureBitmask FlagMask #

rotate :: VkFormatFeatureBitmask FlagMask -> Int -> VkFormatFeatureBitmask FlagMask #

zeroBits :: VkFormatFeatureBitmask FlagMask #

bit :: Int -> VkFormatFeatureBitmask FlagMask #

setBit :: VkFormatFeatureBitmask FlagMask -> Int -> VkFormatFeatureBitmask FlagMask #

clearBit :: VkFormatFeatureBitmask FlagMask -> Int -> VkFormatFeatureBitmask FlagMask #

complementBit :: VkFormatFeatureBitmask FlagMask -> Int -> VkFormatFeatureBitmask FlagMask #

testBit :: VkFormatFeatureBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkFormatFeatureBitmask FlagMask -> Maybe Int #

bitSize :: VkFormatFeatureBitmask FlagMask -> Int #

isSigned :: VkFormatFeatureBitmask FlagMask -> Bool #

shiftL :: VkFormatFeatureBitmask FlagMask -> Int -> VkFormatFeatureBitmask FlagMask #

unsafeShiftL :: VkFormatFeatureBitmask FlagMask -> Int -> VkFormatFeatureBitmask FlagMask #

shiftR :: VkFormatFeatureBitmask FlagMask -> Int -> VkFormatFeatureBitmask FlagMask #

unsafeShiftR :: VkFormatFeatureBitmask FlagMask -> Int -> VkFormatFeatureBitmask FlagMask #

rotateL :: VkFormatFeatureBitmask FlagMask -> Int -> VkFormatFeatureBitmask FlagMask #

rotateR :: VkFormatFeatureBitmask FlagMask -> Int -> VkFormatFeatureBitmask FlagMask #

popCount :: VkFormatFeatureBitmask FlagMask -> Int #

FiniteBits (VkFormatFeatureBitmask FlagMask) Source # 
type Rep (VkFormatFeatureBitmask a) Source # 
type Rep (VkFormatFeatureBitmask a) = D1 (MetaData "VkFormatFeatureBitmask" "Graphics.Vulkan.Types.Enum.Format" "vulkan-api-1.1.2.1-GcVsfRwwhb24i5dsYq91EC" True) (C1 (MetaCons "VkFormatFeatureBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

pattern VK_FORMAT_FEATURE_SAMPLED_IMAGE_BIT :: forall a. VkFormatFeatureBitmask a Source #

Format can be used for sampled images (SAMPLED_IMAGE and COMBINED_IMAGE_SAMPLER descriptor types)

bitpos = 0

pattern VK_FORMAT_FEATURE_STORAGE_IMAGE_BIT :: forall a. VkFormatFeatureBitmask a Source #

Format can be used for storage images (STORAGE_IMAGE descriptor type)

bitpos = 1

pattern VK_FORMAT_FEATURE_STORAGE_IMAGE_ATOMIC_BIT :: forall a. VkFormatFeatureBitmask a Source #

Format supports atomic operations in case it is used for storage images

bitpos = 2

pattern VK_FORMAT_FEATURE_UNIFORM_TEXEL_BUFFER_BIT :: forall a. VkFormatFeatureBitmask a Source #

Format can be used for uniform texel buffers (TBOs)

bitpos = 3

pattern VK_FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_BIT :: forall a. VkFormatFeatureBitmask a Source #

Format can be used for storage texel buffers (IBOs)

bitpos = 4

pattern VK_FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_ATOMIC_BIT :: forall a. VkFormatFeatureBitmask a Source #

Format supports atomic operations in case it is used for storage texel buffers

bitpos = 5

pattern VK_FORMAT_FEATURE_VERTEX_BUFFER_BIT :: forall a. VkFormatFeatureBitmask a Source #

Format can be used for vertex buffers (VBOs)

bitpos = 6

pattern VK_FORMAT_FEATURE_COLOR_ATTACHMENT_BIT :: forall a. VkFormatFeatureBitmask a Source #

Format can be used for color attachment images

bitpos = 7

pattern VK_FORMAT_FEATURE_COLOR_ATTACHMENT_BLEND_BIT :: forall a. VkFormatFeatureBitmask a Source #

Format supports blending in case it is used for color attachment images

bitpos = 8

pattern VK_FORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT :: forall a. VkFormatFeatureBitmask a Source #

Format can be used for depth/stencil attachment images

bitpos = 9

pattern VK_FORMAT_FEATURE_BLIT_SRC_BIT :: forall a. VkFormatFeatureBitmask a Source #

Format can be used as the source image of blits with vkCmdBlitImage

bitpos = 10

pattern VK_FORMAT_FEATURE_BLIT_DST_BIT :: forall a. VkFormatFeatureBitmask a Source #

Format can be used as the destination image of blits with vkCmdBlitImage

bitpos = 11

pattern VK_FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT :: forall a. VkFormatFeatureBitmask a Source #

Format can be filtered with VK_FILTER_LINEAR when being sampled

bitpos = 12

newtype VkImageAspectBitmask a Source #

Instances

Bounded (VkImageAspectBitmask FlagMask) Source # 
Enum (VkImageAspectBitmask FlagMask) Source # 
Eq (VkImageAspectBitmask a) Source # 
Integral (VkImageAspectBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkImageAspectBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkImageAspectBitmask a -> c (VkImageAspectBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkImageAspectBitmask a) #

toConstr :: VkImageAspectBitmask a -> Constr #

dataTypeOf :: VkImageAspectBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkImageAspectBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkImageAspectBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkImageAspectBitmask a -> VkImageAspectBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkImageAspectBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkImageAspectBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkImageAspectBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkImageAspectBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkImageAspectBitmask a -> m (VkImageAspectBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkImageAspectBitmask a -> m (VkImageAspectBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkImageAspectBitmask a -> m (VkImageAspectBitmask a) #

Num (VkImageAspectBitmask FlagMask) Source # 
Ord (VkImageAspectBitmask a) Source # 
Read (VkImageAspectBitmask a) Source # 
Real (VkImageAspectBitmask FlagMask) Source # 
Show (VkImageAspectBitmask a) Source # 
Generic (VkImageAspectBitmask a) Source # 
Storable (VkImageAspectBitmask a) Source # 
Bits (VkImageAspectBitmask FlagMask) Source # 

Methods

(.&.) :: VkImageAspectBitmask FlagMask -> VkImageAspectBitmask FlagMask -> VkImageAspectBitmask FlagMask #

(.|.) :: VkImageAspectBitmask FlagMask -> VkImageAspectBitmask FlagMask -> VkImageAspectBitmask FlagMask #

xor :: VkImageAspectBitmask FlagMask -> VkImageAspectBitmask FlagMask -> VkImageAspectBitmask FlagMask #

complement :: VkImageAspectBitmask FlagMask -> VkImageAspectBitmask FlagMask #

shift :: VkImageAspectBitmask FlagMask -> Int -> VkImageAspectBitmask FlagMask #

rotate :: VkImageAspectBitmask FlagMask -> Int -> VkImageAspectBitmask FlagMask #

zeroBits :: VkImageAspectBitmask FlagMask #

bit :: Int -> VkImageAspectBitmask FlagMask #

setBit :: VkImageAspectBitmask FlagMask -> Int -> VkImageAspectBitmask FlagMask #

clearBit :: VkImageAspectBitmask FlagMask -> Int -> VkImageAspectBitmask FlagMask #

complementBit :: VkImageAspectBitmask FlagMask -> Int -> VkImageAspectBitmask FlagMask #

testBit :: VkImageAspectBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkImageAspectBitmask FlagMask -> Maybe Int #

bitSize :: VkImageAspectBitmask FlagMask -> Int #

isSigned :: VkImageAspectBitmask FlagMask -> Bool #

shiftL :: VkImageAspectBitmask FlagMask -> Int -> VkImageAspectBitmask FlagMask #

unsafeShiftL :: VkImageAspectBitmask FlagMask -> Int -> VkImageAspectBitmask FlagMask #

shiftR :: VkImageAspectBitmask FlagMask -> Int -> VkImageAspectBitmask FlagMask #

unsafeShiftR :: VkImageAspectBitmask FlagMask -> Int -> VkImageAspectBitmask FlagMask #

rotateL :: VkImageAspectBitmask FlagMask -> Int -> VkImageAspectBitmask FlagMask #

rotateR :: VkImageAspectBitmask FlagMask -> Int -> VkImageAspectBitmask FlagMask #

popCount :: VkImageAspectBitmask FlagMask -> Int #

FiniteBits (VkImageAspectBitmask FlagMask) Source # 
type Rep (VkImageAspectBitmask a) Source # 
type Rep (VkImageAspectBitmask a) = D1 (MetaData "VkImageAspectBitmask" "Graphics.Vulkan.Types.Enum.Image" "vulkan-api-1.1.2.1-GcVsfRwwhb24i5dsYq91EC" True) (C1 (MetaCons "VkImageAspectBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

pattern VK_IMAGE_ASPECT_COLOR_BIT :: forall a. VkImageAspectBitmask a Source #

bitpos = 0

pattern VK_IMAGE_ASPECT_DEPTH_BIT :: forall a. VkImageAspectBitmask a Source #

bitpos = 1

pattern VK_IMAGE_ASPECT_STENCIL_BIT :: forall a. VkImageAspectBitmask a Source #

bitpos = 2

newtype VkImageCreateBitmask a Source #

Instances

Bounded (VkImageCreateBitmask FlagMask) Source # 
Enum (VkImageCreateBitmask FlagMask) Source # 
Eq (VkImageCreateBitmask a) Source # 
Integral (VkImageCreateBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkImageCreateBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkImageCreateBitmask a -> c (VkImageCreateBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkImageCreateBitmask a) #

toConstr :: VkImageCreateBitmask a -> Constr #

dataTypeOf :: VkImageCreateBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkImageCreateBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkImageCreateBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkImageCreateBitmask a -> VkImageCreateBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkImageCreateBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkImageCreateBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkImageCreateBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkImageCreateBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkImageCreateBitmask a -> m (VkImageCreateBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkImageCreateBitmask a -> m (VkImageCreateBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkImageCreateBitmask a -> m (VkImageCreateBitmask a) #

Num (VkImageCreateBitmask FlagMask) Source # 
Ord (VkImageCreateBitmask a) Source # 
Read (VkImageCreateBitmask a) Source # 
Real (VkImageCreateBitmask FlagMask) Source # 
Show (VkImageCreateBitmask a) Source # 
Generic (VkImageCreateBitmask a) Source # 
Storable (VkImageCreateBitmask a) Source # 
Bits (VkImageCreateBitmask FlagMask) Source # 

Methods

(.&.) :: VkImageCreateBitmask FlagMask -> VkImageCreateBitmask FlagMask -> VkImageCreateBitmask FlagMask #

(.|.) :: VkImageCreateBitmask FlagMask -> VkImageCreateBitmask FlagMask -> VkImageCreateBitmask FlagMask #

xor :: VkImageCreateBitmask FlagMask -> VkImageCreateBitmask FlagMask -> VkImageCreateBitmask FlagMask #

complement :: VkImageCreateBitmask FlagMask -> VkImageCreateBitmask FlagMask #

shift :: VkImageCreateBitmask FlagMask -> Int -> VkImageCreateBitmask FlagMask #

rotate :: VkImageCreateBitmask FlagMask -> Int -> VkImageCreateBitmask FlagMask #

zeroBits :: VkImageCreateBitmask FlagMask #

bit :: Int -> VkImageCreateBitmask FlagMask #

setBit :: VkImageCreateBitmask FlagMask -> Int -> VkImageCreateBitmask FlagMask #

clearBit :: VkImageCreateBitmask FlagMask -> Int -> VkImageCreateBitmask FlagMask #

complementBit :: VkImageCreateBitmask FlagMask -> Int -> VkImageCreateBitmask FlagMask #

testBit :: VkImageCreateBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkImageCreateBitmask FlagMask -> Maybe Int #

bitSize :: VkImageCreateBitmask FlagMask -> Int #

isSigned :: VkImageCreateBitmask FlagMask -> Bool #

shiftL :: VkImageCreateBitmask FlagMask -> Int -> VkImageCreateBitmask FlagMask #

unsafeShiftL :: VkImageCreateBitmask FlagMask -> Int -> VkImageCreateBitmask FlagMask #

shiftR :: VkImageCreateBitmask FlagMask -> Int -> VkImageCreateBitmask FlagMask #

unsafeShiftR :: VkImageCreateBitmask FlagMask -> Int -> VkImageCreateBitmask FlagMask #

rotateL :: VkImageCreateBitmask FlagMask -> Int -> VkImageCreateBitmask FlagMask #

rotateR :: VkImageCreateBitmask FlagMask -> Int -> VkImageCreateBitmask FlagMask #

popCount :: VkImageCreateBitmask FlagMask -> Int #

FiniteBits (VkImageCreateBitmask FlagMask) Source # 
type Rep (VkImageCreateBitmask a) Source # 
type Rep (VkImageCreateBitmask a) = D1 (MetaData "VkImageCreateBitmask" "Graphics.Vulkan.Types.Enum.Image" "vulkan-api-1.1.2.1-GcVsfRwwhb24i5dsYq91EC" True) (C1 (MetaCons "VkImageCreateBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

pattern VK_IMAGE_CREATE_SPARSE_BINDING_BIT :: forall a. VkImageCreateBitmask a Source #

Image should support sparse backing

bitpos = 0

pattern VK_IMAGE_CREATE_SPARSE_RESIDENCY_BIT :: forall a. VkImageCreateBitmask a Source #

Image should support sparse backing with partial residency

bitpos = 1

pattern VK_IMAGE_CREATE_SPARSE_ALIASED_BIT :: forall a. VkImageCreateBitmask a Source #

Image should support constent data access to physical memory ranges mapped into multiple locations of sparse images

bitpos = 2

pattern VK_IMAGE_CREATE_MUTABLE_FORMAT_BIT :: forall a. VkImageCreateBitmask a Source #

Allows image views to have different format than the base image

bitpos = 3

pattern VK_IMAGE_CREATE_CUBE_COMPATIBLE_BIT :: forall a. VkImageCreateBitmask a Source #

Allows creating image views with cube type from the created image

bitpos = 4

newtype VkImageLayout Source #

Constructors

VkImageLayout Int32 

Instances

Bounded VkImageLayout Source # 
Enum VkImageLayout Source # 
Eq VkImageLayout Source # 
Data VkImageLayout Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkImageLayout -> c VkImageLayout #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkImageLayout #

toConstr :: VkImageLayout -> Constr #

dataTypeOf :: VkImageLayout -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkImageLayout) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkImageLayout) #

gmapT :: (forall b. Data b => b -> b) -> VkImageLayout -> VkImageLayout #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkImageLayout -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkImageLayout -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkImageLayout -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkImageLayout -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkImageLayout -> m VkImageLayout #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkImageLayout -> m VkImageLayout #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkImageLayout -> m VkImageLayout #

Num VkImageLayout Source # 
Ord VkImageLayout Source # 
Read VkImageLayout Source # 
Show VkImageLayout Source # 
Generic VkImageLayout Source # 

Associated Types

type Rep VkImageLayout :: * -> * #

Storable VkImageLayout Source # 
type Rep VkImageLayout Source # 
type Rep VkImageLayout = D1 (MetaData "VkImageLayout" "Graphics.Vulkan.Types.Enum.Image" "vulkan-api-1.1.2.1-GcVsfRwwhb24i5dsYq91EC" True) (C1 (MetaCons "VkImageLayout" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

pattern VK_IMAGE_LAYOUT_UNDEFINED :: VkImageLayout Source #

Implicit layout an image is when its contents are undefined due to various reasons (e.g. right after creation)

pattern VK_IMAGE_LAYOUT_GENERAL :: VkImageLayout Source #

General layout when image can be used for any kind of access

pattern VK_IMAGE_LAYOUT_COLOR_ATTACHMENT_OPTIMAL :: VkImageLayout Source #

Optimal layout when image is only used for color attachment read/write

pattern VK_IMAGE_LAYOUT_DEPTH_STENCIL_ATTACHMENT_OPTIMAL :: VkImageLayout Source #

Optimal layout when image is only used for depthstencil attachment readwrite

pattern VK_IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL :: VkImageLayout Source #

Optimal layout when image is used for read only depth/stencil attachment and shader access

pattern VK_IMAGE_LAYOUT_SHADER_READ_ONLY_OPTIMAL :: VkImageLayout Source #

Optimal layout when image is used for read only shader access

pattern VK_IMAGE_LAYOUT_TRANSFER_SRC_OPTIMAL :: VkImageLayout Source #

Optimal layout when image is used only as source of transfer operations

pattern VK_IMAGE_LAYOUT_TRANSFER_DST_OPTIMAL :: VkImageLayout Source #

Optimal layout when image is used only as destination of transfer operations

pattern VK_IMAGE_LAYOUT_PREINITIALIZED :: VkImageLayout Source #

Initial layout used when the data is populated by the CPU

newtype VkImageTiling Source #

Constructors

VkImageTiling Int32 

Instances

Bounded VkImageTiling Source # 
Enum VkImageTiling Source # 
Eq VkImageTiling Source # 
Data VkImageTiling Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkImageTiling -> c VkImageTiling #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkImageTiling #

toConstr :: VkImageTiling -> Constr #

dataTypeOf :: VkImageTiling -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkImageTiling) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkImageTiling) #

gmapT :: (forall b. Data b => b -> b) -> VkImageTiling -> VkImageTiling #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkImageTiling -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkImageTiling -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkImageTiling -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkImageTiling -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkImageTiling -> m VkImageTiling #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkImageTiling -> m VkImageTiling #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkImageTiling -> m VkImageTiling #

Num VkImageTiling Source # 
Ord VkImageTiling Source # 
Read VkImageTiling Source # 
Show VkImageTiling Source # 
Generic VkImageTiling Source # 

Associated Types

type Rep VkImageTiling :: * -> * #

Storable VkImageTiling Source # 
type Rep VkImageTiling Source # 
type Rep VkImageTiling = D1 (MetaData "VkImageTiling" "Graphics.Vulkan.Types.Enum.Image" "vulkan-api-1.1.2.1-GcVsfRwwhb24i5dsYq91EC" True) (C1 (MetaCons "VkImageTiling" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

newtype VkImageType Source #

Constructors

VkImageType Int32 

Instances

Bounded VkImageType Source # 
Enum VkImageType Source # 
Eq VkImageType Source # 
Data VkImageType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkImageType -> c VkImageType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkImageType #

toConstr :: VkImageType -> Constr #

dataTypeOf :: VkImageType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkImageType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkImageType) #

gmapT :: (forall b. Data b => b -> b) -> VkImageType -> VkImageType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkImageType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkImageType -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkImageType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkImageType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkImageType -> m VkImageType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkImageType -> m VkImageType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkImageType -> m VkImageType #

Num VkImageType Source # 
Ord VkImageType Source # 
Read VkImageType Source # 
Show VkImageType Source # 
Generic VkImageType Source # 

Associated Types

type Rep VkImageType :: * -> * #

Storable VkImageType Source # 
type Rep VkImageType Source # 
type Rep VkImageType = D1 (MetaData "VkImageType" "Graphics.Vulkan.Types.Enum.Image" "vulkan-api-1.1.2.1-GcVsfRwwhb24i5dsYq91EC" True) (C1 (MetaCons "VkImageType" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

newtype VkImageUsageBitmask a Source #

Instances

Bounded (VkImageUsageBitmask FlagMask) Source # 
Enum (VkImageUsageBitmask FlagMask) Source # 
Eq (VkImageUsageBitmask a) Source # 
Integral (VkImageUsageBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkImageUsageBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkImageUsageBitmask a -> c (VkImageUsageBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkImageUsageBitmask a) #

toConstr :: VkImageUsageBitmask a -> Constr #

dataTypeOf :: VkImageUsageBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkImageUsageBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkImageUsageBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkImageUsageBitmask a -> VkImageUsageBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkImageUsageBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkImageUsageBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkImageUsageBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkImageUsageBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkImageUsageBitmask a -> m (VkImageUsageBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkImageUsageBitmask a -> m (VkImageUsageBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkImageUsageBitmask a -> m (VkImageUsageBitmask a) #

Num (VkImageUsageBitmask FlagMask) Source # 
Ord (VkImageUsageBitmask a) Source # 
Read (VkImageUsageBitmask a) Source # 
Real (VkImageUsageBitmask FlagMask) Source # 
Show (VkImageUsageBitmask a) Source # 
Generic (VkImageUsageBitmask a) Source # 

Associated Types

type Rep (VkImageUsageBitmask a) :: * -> * #

Storable (VkImageUsageBitmask a) Source # 
Bits (VkImageUsageBitmask FlagMask) Source # 

Methods

(.&.) :: VkImageUsageBitmask FlagMask -> VkImageUsageBitmask FlagMask -> VkImageUsageBitmask FlagMask #

(.|.) :: VkImageUsageBitmask FlagMask -> VkImageUsageBitmask FlagMask -> VkImageUsageBitmask FlagMask #

xor :: VkImageUsageBitmask FlagMask -> VkImageUsageBitmask FlagMask -> VkImageUsageBitmask FlagMask #

complement :: VkImageUsageBitmask FlagMask -> VkImageUsageBitmask FlagMask #

shift :: VkImageUsageBitmask FlagMask -> Int -> VkImageUsageBitmask FlagMask #

rotate :: VkImageUsageBitmask FlagMask -> Int -> VkImageUsageBitmask FlagMask #

zeroBits :: VkImageUsageBitmask FlagMask #

bit :: Int -> VkImageUsageBitmask FlagMask #

setBit :: VkImageUsageBitmask FlagMask -> Int -> VkImageUsageBitmask FlagMask #

clearBit :: VkImageUsageBitmask FlagMask -> Int -> VkImageUsageBitmask FlagMask #

complementBit :: VkImageUsageBitmask FlagMask -> Int -> VkImageUsageBitmask FlagMask #

testBit :: VkImageUsageBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkImageUsageBitmask FlagMask -> Maybe Int #

bitSize :: VkImageUsageBitmask FlagMask -> Int #

isSigned :: VkImageUsageBitmask FlagMask -> Bool #

shiftL :: VkImageUsageBitmask FlagMask -> Int -> VkImageUsageBitmask FlagMask #

unsafeShiftL :: VkImageUsageBitmask FlagMask -> Int -> VkImageUsageBitmask FlagMask #

shiftR :: VkImageUsageBitmask FlagMask -> Int -> VkImageUsageBitmask FlagMask #

unsafeShiftR :: VkImageUsageBitmask FlagMask -> Int -> VkImageUsageBitmask FlagMask #

rotateL :: VkImageUsageBitmask FlagMask -> Int -> VkImageUsageBitmask FlagMask #

rotateR :: VkImageUsageBitmask FlagMask -> Int -> VkImageUsageBitmask FlagMask #

popCount :: VkImageUsageBitmask FlagMask -> Int #

FiniteBits (VkImageUsageBitmask FlagMask) Source # 
type Rep (VkImageUsageBitmask a) Source # 
type Rep (VkImageUsageBitmask a) = D1 (MetaData "VkImageUsageBitmask" "Graphics.Vulkan.Types.Enum.Image" "vulkan-api-1.1.2.1-GcVsfRwwhb24i5dsYq91EC" True) (C1 (MetaCons "VkImageUsageBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

pattern VK_IMAGE_USAGE_TRANSFER_SRC_BIT :: forall a. VkImageUsageBitmask a Source #

Can be used as a source of transfer operations

bitpos = 0

pattern VK_IMAGE_USAGE_TRANSFER_DST_BIT :: forall a. VkImageUsageBitmask a Source #

Can be used as a destination of transfer operations

bitpos = 1

pattern VK_IMAGE_USAGE_SAMPLED_BIT :: forall a. VkImageUsageBitmask a Source #

Can be sampled from (SAMPLED_IMAGE and COMBINED_IMAGE_SAMPLER descriptor types)

bitpos = 2

pattern VK_IMAGE_USAGE_STORAGE_BIT :: forall a. VkImageUsageBitmask a Source #

Can be used as storage image (STORAGE_IMAGE descriptor type)

bitpos = 3

pattern VK_IMAGE_USAGE_COLOR_ATTACHMENT_BIT :: forall a. VkImageUsageBitmask a Source #

Can be used as framebuffer color attachment

bitpos = 4

pattern VK_IMAGE_USAGE_DEPTH_STENCIL_ATTACHMENT_BIT :: forall a. VkImageUsageBitmask a Source #

Can be used as framebuffer depth/stencil attachment

bitpos = 5

pattern VK_IMAGE_USAGE_TRANSIENT_ATTACHMENT_BIT :: forall a. VkImageUsageBitmask a Source #

Image data not needed outside of rendering

bitpos = 6

pattern VK_IMAGE_USAGE_INPUT_ATTACHMENT_BIT :: forall a. VkImageUsageBitmask a Source #

Can be used as framebuffer input attachment

bitpos = 7

newtype VkImageViewType Source #

Constructors

VkImageViewType Int32 

Instances

Bounded VkImageViewType Source # 
Enum VkImageViewType Source # 
Eq VkImageViewType Source # 
Data VkImageViewType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkImageViewType -> c VkImageViewType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkImageViewType #

toConstr :: VkImageViewType -> Constr #

dataTypeOf :: VkImageViewType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkImageViewType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkImageViewType) #

gmapT :: (forall b. Data b => b -> b) -> VkImageViewType -> VkImageViewType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkImageViewType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkImageViewType -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkImageViewType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkImageViewType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkImageViewType -> m VkImageViewType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkImageViewType -> m VkImageViewType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkImageViewType -> m VkImageViewType #

Num VkImageViewType Source # 
Ord VkImageViewType Source # 
Read VkImageViewType Source # 
Show VkImageViewType Source # 
Generic VkImageViewType Source # 
Storable VkImageViewType Source # 
type Rep VkImageViewType Source # 
type Rep VkImageViewType = D1 (MetaData "VkImageViewType" "Graphics.Vulkan.Types.Enum.Image" "vulkan-api-1.1.2.1-GcVsfRwwhb24i5dsYq91EC" True) (C1 (MetaCons "VkImageViewType" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

newtype VkInternalAllocationType Source #

Instances

Bounded VkInternalAllocationType Source # 
Enum VkInternalAllocationType Source # 
Eq VkInternalAllocationType Source # 
Data VkInternalAllocationType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkInternalAllocationType -> c VkInternalAllocationType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkInternalAllocationType #

toConstr :: VkInternalAllocationType -> Constr #

dataTypeOf :: VkInternalAllocationType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkInternalAllocationType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkInternalAllocationType) #

gmapT :: (forall b. Data b => b -> b) -> VkInternalAllocationType -> VkInternalAllocationType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkInternalAllocationType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkInternalAllocationType -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkInternalAllocationType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkInternalAllocationType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkInternalAllocationType -> m VkInternalAllocationType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkInternalAllocationType -> m VkInternalAllocationType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkInternalAllocationType -> m VkInternalAllocationType #

Num VkInternalAllocationType Source # 
Ord VkInternalAllocationType Source # 
Read VkInternalAllocationType Source # 
Show VkInternalAllocationType Source # 
Generic VkInternalAllocationType Source # 
Storable VkInternalAllocationType Source # 
type Rep VkInternalAllocationType Source # 
type Rep VkInternalAllocationType = D1 (MetaData "VkInternalAllocationType" "Graphics.Vulkan.Types.Enum.InternalAllocationType" "vulkan-api-1.1.2.1-GcVsfRwwhb24i5dsYq91EC" True) (C1 (MetaCons "VkInternalAllocationType" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

newtype VkPresentModeKHR Source #

Constructors

VkPresentModeKHR Int32 

Instances

Bounded VkPresentModeKHR Source # 
Enum VkPresentModeKHR Source # 
Eq VkPresentModeKHR Source # 
Data VkPresentModeKHR Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkPresentModeKHR -> c VkPresentModeKHR #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkPresentModeKHR #

toConstr :: VkPresentModeKHR -> Constr #

dataTypeOf :: VkPresentModeKHR -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkPresentModeKHR) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkPresentModeKHR) #

gmapT :: (forall b. Data b => b -> b) -> VkPresentModeKHR -> VkPresentModeKHR #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkPresentModeKHR -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkPresentModeKHR -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkPresentModeKHR -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkPresentModeKHR -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkPresentModeKHR -> m VkPresentModeKHR #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPresentModeKHR -> m VkPresentModeKHR #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPresentModeKHR -> m VkPresentModeKHR #

Num VkPresentModeKHR Source # 
Ord VkPresentModeKHR Source # 
Read VkPresentModeKHR Source # 
Show VkPresentModeKHR Source # 
Generic VkPresentModeKHR Source # 
Storable VkPresentModeKHR Source # 
type Rep VkPresentModeKHR Source # 
type Rep VkPresentModeKHR = D1 (MetaData "VkPresentModeKHR" "Graphics.Vulkan.Types.Enum.PresentModeKHR" "vulkan-api-1.1.2.1-GcVsfRwwhb24i5dsYq91EC" True) (C1 (MetaCons "VkPresentModeKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

newtype VkResult Source #

API result codes

type = enum

VkResult registry at www.khronos.org

Constructors

VkResult Int32 

Instances

Bounded VkResult Source # 
Enum VkResult Source # 
Eq VkResult Source # 
Data VkResult Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkResult -> c VkResult #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkResult #

toConstr :: VkResult -> Constr #

dataTypeOf :: VkResult -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkResult) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkResult) #

gmapT :: (forall b. Data b => b -> b) -> VkResult -> VkResult #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkResult -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkResult -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkResult -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkResult -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkResult -> m VkResult #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkResult -> m VkResult #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkResult -> m VkResult #

Num VkResult Source # 
Ord VkResult Source # 
Read VkResult Source # 
Show VkResult Source # 
Generic VkResult Source # 

Associated Types

type Rep VkResult :: * -> * #

Methods

from :: VkResult -> Rep VkResult x #

to :: Rep VkResult x -> VkResult #

Storable VkResult Source # 
type Rep VkResult Source # 
type Rep VkResult = D1 (MetaData "VkResult" "Graphics.Vulkan.Types.Enum.Result" "vulkan-api-1.1.2.1-GcVsfRwwhb24i5dsYq91EC" True) (C1 (MetaCons "VkResult" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

pattern VK_SUCCESS :: VkResult Source #

Command completed successfully

pattern VK_NOT_READY :: VkResult Source #

A fence or query has not yet completed

pattern VK_TIMEOUT :: VkResult Source #

A wait operation has not completed in the specified time

pattern VK_EVENT_SET :: VkResult Source #

An event is signaled

pattern VK_EVENT_RESET :: VkResult Source #

An event is unsignaled

pattern VK_INCOMPLETE :: VkResult Source #

A return array was too small for the result

pattern VK_ERROR_OUT_OF_HOST_MEMORY :: VkResult Source #

A host memory allocation has failed

pattern VK_ERROR_OUT_OF_DEVICE_MEMORY :: VkResult Source #

A device memory allocation has failed

pattern VK_ERROR_INITIALIZATION_FAILED :: VkResult Source #

Initialization of a object has failed

pattern VK_ERROR_DEVICE_LOST :: VkResult Source #

The logical device has been lost. See

pattern VK_ERROR_MEMORY_MAP_FAILED :: VkResult Source #

Mapping of a memory object has failed

pattern VK_ERROR_LAYER_NOT_PRESENT :: VkResult Source #

Layer specified does not exist

pattern VK_ERROR_EXTENSION_NOT_PRESENT :: VkResult Source #

Extension specified does not exist

pattern VK_ERROR_FEATURE_NOT_PRESENT :: VkResult Source #

Requested feature is not available on this device

pattern VK_ERROR_INCOMPATIBLE_DRIVER :: VkResult Source #

Unable to find a Vulkan driver

pattern VK_ERROR_TOO_MANY_OBJECTS :: VkResult Source #

Too many objects of the type have already been created

pattern VK_ERROR_FORMAT_NOT_SUPPORTED :: VkResult Source #

Requested format is not supported on this device

pattern VK_ERROR_FRAGMENTED_POOL :: VkResult Source #

A requested pool allocation has failed due to fragmentation of the pool's memory

newtype VkSharingMode Source #

Constructors

VkSharingMode Int32 

Instances

Bounded VkSharingMode Source # 
Enum VkSharingMode Source # 
Eq VkSharingMode Source # 
Data VkSharingMode Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkSharingMode -> c VkSharingMode #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkSharingMode #

toConstr :: VkSharingMode -> Constr #

dataTypeOf :: VkSharingMode -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkSharingMode) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkSharingMode) #

gmapT :: (forall b. Data b => b -> b) -> VkSharingMode -> VkSharingMode #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkSharingMode -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkSharingMode -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkSharingMode -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkSharingMode -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkSharingMode -> m VkSharingMode #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSharingMode -> m VkSharingMode #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSharingMode -> m VkSharingMode #

Num VkSharingMode Source # 
Ord VkSharingMode Source # 
Read VkSharingMode Source # 
Show VkSharingMode Source # 
Generic VkSharingMode Source # 

Associated Types

type Rep VkSharingMode :: * -> * #

Storable VkSharingMode Source # 
type Rep VkSharingMode Source # 
type Rep VkSharingMode = D1 (MetaData "VkSharingMode" "Graphics.Vulkan.Types.Enum.SharingMode" "vulkan-api-1.1.2.1-GcVsfRwwhb24i5dsYq91EC" True) (C1 (MetaCons "VkSharingMode" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

newtype VkStructureType Source #

Structure type enumerant

type = enum

VkStructureType registry at www.khronos.org

Constructors

VkStructureType Int32 

Instances

Bounded VkStructureType Source # 
Enum VkStructureType Source # 
Eq VkStructureType Source # 
Data VkStructureType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkStructureType -> c VkStructureType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkStructureType #

toConstr :: VkStructureType -> Constr #

dataTypeOf :: VkStructureType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkStructureType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkStructureType) #

gmapT :: (forall b. Data b => b -> b) -> VkStructureType -> VkStructureType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkStructureType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkStructureType -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkStructureType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkStructureType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkStructureType -> m VkStructureType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkStructureType -> m VkStructureType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkStructureType -> m VkStructureType #

Num VkStructureType Source # 
Ord VkStructureType Source # 
Read VkStructureType Source # 
Show VkStructureType Source # 
Generic VkStructureType Source # 
Storable VkStructureType Source # 
type Rep VkStructureType Source # 
type Rep VkStructureType = D1 (MetaData "VkStructureType" "Graphics.Vulkan.Types.Enum.StructureType" "vulkan-api-1.1.2.1-GcVsfRwwhb24i5dsYq91EC" True) (C1 (MetaCons "VkStructureType" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

pattern VK_STRUCTURE_TYPE_LOADER_INSTANCE_CREATE_INFO :: VkStructureType Source #

Reserved for internal use by the loader, layers, and ICDs

pattern VK_STRUCTURE_TYPE_LOADER_DEVICE_CREATE_INFO :: VkStructureType Source #

Reserved for internal use by the loader, layers, and ICDs

newtype VkSurfaceCounterBitmaskEXT a Source #

Instances

Bounded (VkSurfaceCounterBitmaskEXT FlagMask) Source # 
Enum (VkSurfaceCounterBitmaskEXT FlagMask) Source # 
Eq (VkSurfaceCounterBitmaskEXT a) Source # 
Integral (VkSurfaceCounterBitmaskEXT FlagMask) Source # 
Typeable FlagType a => Data (VkSurfaceCounterBitmaskEXT a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkSurfaceCounterBitmaskEXT a -> c (VkSurfaceCounterBitmaskEXT a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkSurfaceCounterBitmaskEXT a) #

toConstr :: VkSurfaceCounterBitmaskEXT a -> Constr #

dataTypeOf :: VkSurfaceCounterBitmaskEXT a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkSurfaceCounterBitmaskEXT a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkSurfaceCounterBitmaskEXT a)) #

gmapT :: (forall b. Data b => b -> b) -> VkSurfaceCounterBitmaskEXT a -> VkSurfaceCounterBitmaskEXT a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkSurfaceCounterBitmaskEXT a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkSurfaceCounterBitmaskEXT a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkSurfaceCounterBitmaskEXT a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkSurfaceCounterBitmaskEXT a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkSurfaceCounterBitmaskEXT a -> m (VkSurfaceCounterBitmaskEXT a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSurfaceCounterBitmaskEXT a -> m (VkSurfaceCounterBitmaskEXT a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSurfaceCounterBitmaskEXT a -> m (VkSurfaceCounterBitmaskEXT a) #

Num (VkSurfaceCounterBitmaskEXT FlagMask) Source # 
Ord (VkSurfaceCounterBitmaskEXT a) Source # 
Read (VkSurfaceCounterBitmaskEXT a) Source # 
Real (VkSurfaceCounterBitmaskEXT FlagMask) Source # 
Show (VkSurfaceCounterBitmaskEXT a) Source # 
Generic (VkSurfaceCounterBitmaskEXT a) Source # 
Storable (VkSurfaceCounterBitmaskEXT a) Source # 
Bits (VkSurfaceCounterBitmaskEXT FlagMask) Source # 

Methods

(.&.) :: VkSurfaceCounterBitmaskEXT FlagMask -> VkSurfaceCounterBitmaskEXT FlagMask -> VkSurfaceCounterBitmaskEXT FlagMask #

(.|.) :: VkSurfaceCounterBitmaskEXT FlagMask -> VkSurfaceCounterBitmaskEXT FlagMask -> VkSurfaceCounterBitmaskEXT FlagMask #

xor :: VkSurfaceCounterBitmaskEXT FlagMask -> VkSurfaceCounterBitmaskEXT FlagMask -> VkSurfaceCounterBitmaskEXT FlagMask #

complement :: VkSurfaceCounterBitmaskEXT FlagMask -> VkSurfaceCounterBitmaskEXT FlagMask #

shift :: VkSurfaceCounterBitmaskEXT FlagMask -> Int -> VkSurfaceCounterBitmaskEXT FlagMask #

rotate :: VkSurfaceCounterBitmaskEXT FlagMask -> Int -> VkSurfaceCounterBitmaskEXT FlagMask #

zeroBits :: VkSurfaceCounterBitmaskEXT FlagMask #

bit :: Int -> VkSurfaceCounterBitmaskEXT FlagMask #

setBit :: VkSurfaceCounterBitmaskEXT FlagMask -> Int -> VkSurfaceCounterBitmaskEXT FlagMask #

clearBit :: VkSurfaceCounterBitmaskEXT FlagMask -> Int -> VkSurfaceCounterBitmaskEXT FlagMask #

complementBit :: VkSurfaceCounterBitmaskEXT FlagMask -> Int -> VkSurfaceCounterBitmaskEXT FlagMask #

testBit :: VkSurfaceCounterBitmaskEXT FlagMask -> Int -> Bool #

bitSizeMaybe :: VkSurfaceCounterBitmaskEXT FlagMask -> Maybe Int #

bitSize :: VkSurfaceCounterBitmaskEXT FlagMask -> Int #

isSigned :: VkSurfaceCounterBitmaskEXT FlagMask -> Bool #

shiftL :: VkSurfaceCounterBitmaskEXT FlagMask -> Int -> VkSurfaceCounterBitmaskEXT FlagMask #

unsafeShiftL :: VkSurfaceCounterBitmaskEXT FlagMask -> Int -> VkSurfaceCounterBitmaskEXT FlagMask #

shiftR :: VkSurfaceCounterBitmaskEXT FlagMask -> Int -> VkSurfaceCounterBitmaskEXT FlagMask #

unsafeShiftR :: VkSurfaceCounterBitmaskEXT FlagMask -> Int -> VkSurfaceCounterBitmaskEXT FlagMask #

rotateL :: VkSurfaceCounterBitmaskEXT FlagMask -> Int -> VkSurfaceCounterBitmaskEXT FlagMask #

rotateR :: VkSurfaceCounterBitmaskEXT FlagMask -> Int -> VkSurfaceCounterBitmaskEXT FlagMask #

popCount :: VkSurfaceCounterBitmaskEXT FlagMask -> Int #

FiniteBits (VkSurfaceCounterBitmaskEXT FlagMask) Source # 
type Rep (VkSurfaceCounterBitmaskEXT a) Source # 
type Rep (VkSurfaceCounterBitmaskEXT a) = D1 (MetaData "VkSurfaceCounterBitmaskEXT" "Graphics.Vulkan.Types.Enum.Surface" "vulkan-api-1.1.2.1-GcVsfRwwhb24i5dsYq91EC" True) (C1 (MetaCons "VkSurfaceCounterBitmaskEXT" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkSurfaceTransformBitmaskKHR a Source #

Instances

Bounded (VkSurfaceTransformBitmaskKHR FlagMask) Source # 
Enum (VkSurfaceTransformBitmaskKHR FlagMask) Source # 
Eq (VkSurfaceTransformBitmaskKHR a) Source # 
Integral (VkSurfaceTransformBitmaskKHR FlagMask) Source # 
Typeable FlagType a => Data (VkSurfaceTransformBitmaskKHR a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkSurfaceTransformBitmaskKHR a -> c (VkSurfaceTransformBitmaskKHR a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkSurfaceTransformBitmaskKHR a) #

toConstr :: VkSurfaceTransformBitmaskKHR a -> Constr #

dataTypeOf :: VkSurfaceTransformBitmaskKHR a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkSurfaceTransformBitmaskKHR a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkSurfaceTransformBitmaskKHR a)) #

gmapT :: (forall b. Data b => b -> b) -> VkSurfaceTransformBitmaskKHR a -> VkSurfaceTransformBitmaskKHR a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkSurfaceTransformBitmaskKHR a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkSurfaceTransformBitmaskKHR a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkSurfaceTransformBitmaskKHR a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkSurfaceTransformBitmaskKHR a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkSurfaceTransformBitmaskKHR a -> m (VkSurfaceTransformBitmaskKHR a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSurfaceTransformBitmaskKHR a -> m (VkSurfaceTransformBitmaskKHR a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSurfaceTransformBitmaskKHR a -> m (VkSurfaceTransformBitmaskKHR a) #

Num (VkSurfaceTransformBitmaskKHR FlagMask) Source # 
Ord (VkSurfaceTransformBitmaskKHR a) Source # 
Read (VkSurfaceTransformBitmaskKHR a) Source # 
Real (VkSurfaceTransformBitmaskKHR FlagMask) Source # 
Show (VkSurfaceTransformBitmaskKHR a) Source # 
Generic (VkSurfaceTransformBitmaskKHR a) Source # 
Storable (VkSurfaceTransformBitmaskKHR a) Source # 
Bits (VkSurfaceTransformBitmaskKHR FlagMask) Source # 

Methods

(.&.) :: VkSurfaceTransformBitmaskKHR FlagMask -> VkSurfaceTransformBitmaskKHR FlagMask -> VkSurfaceTransformBitmaskKHR FlagMask #

(.|.) :: VkSurfaceTransformBitmaskKHR FlagMask -> VkSurfaceTransformBitmaskKHR FlagMask -> VkSurfaceTransformBitmaskKHR FlagMask #

xor :: VkSurfaceTransformBitmaskKHR FlagMask -> VkSurfaceTransformBitmaskKHR FlagMask -> VkSurfaceTransformBitmaskKHR FlagMask #

complement :: VkSurfaceTransformBitmaskKHR FlagMask -> VkSurfaceTransformBitmaskKHR FlagMask #

shift :: VkSurfaceTransformBitmaskKHR FlagMask -> Int -> VkSurfaceTransformBitmaskKHR FlagMask #

rotate :: VkSurfaceTransformBitmaskKHR FlagMask -> Int -> VkSurfaceTransformBitmaskKHR FlagMask #

zeroBits :: VkSurfaceTransformBitmaskKHR FlagMask #

bit :: Int -> VkSurfaceTransformBitmaskKHR FlagMask #

setBit :: VkSurfaceTransformBitmaskKHR FlagMask -> Int -> VkSurfaceTransformBitmaskKHR FlagMask #

clearBit :: VkSurfaceTransformBitmaskKHR FlagMask -> Int -> VkSurfaceTransformBitmaskKHR FlagMask #

complementBit :: VkSurfaceTransformBitmaskKHR FlagMask -> Int -> VkSurfaceTransformBitmaskKHR FlagMask #

testBit :: VkSurfaceTransformBitmaskKHR FlagMask -> Int -> Bool #

bitSizeMaybe :: VkSurfaceTransformBitmaskKHR FlagMask -> Maybe Int #

bitSize :: VkSurfaceTransformBitmaskKHR FlagMask -> Int #

isSigned :: VkSurfaceTransformBitmaskKHR FlagMask -> Bool #

shiftL :: VkSurfaceTransformBitmaskKHR FlagMask -> Int -> VkSurfaceTransformBitmaskKHR FlagMask #

unsafeShiftL :: VkSurfaceTransformBitmaskKHR FlagMask -> Int -> VkSurfaceTransformBitmaskKHR FlagMask #

shiftR :: VkSurfaceTransformBitmaskKHR FlagMask -> Int -> VkSurfaceTransformBitmaskKHR FlagMask #

unsafeShiftR :: VkSurfaceTransformBitmaskKHR FlagMask -> Int -> VkSurfaceTransformBitmaskKHR FlagMask #

rotateL :: VkSurfaceTransformBitmaskKHR FlagMask -> Int -> VkSurfaceTransformBitmaskKHR FlagMask #

rotateR :: VkSurfaceTransformBitmaskKHR FlagMask -> Int -> VkSurfaceTransformBitmaskKHR FlagMask #

popCount :: VkSurfaceTransformBitmaskKHR FlagMask -> Int #

FiniteBits (VkSurfaceTransformBitmaskKHR FlagMask) Source # 
type Rep (VkSurfaceTransformBitmaskKHR a) Source # 
type Rep (VkSurfaceTransformBitmaskKHR a) = D1 (MetaData "VkSurfaceTransformBitmaskKHR" "Graphics.Vulkan.Types.Enum.Surface" "vulkan-api-1.1.2.1-GcVsfRwwhb24i5dsYq91EC" True) (C1 (MetaCons "VkSurfaceTransformBitmaskKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkSwapchainCreateBitmaskKHR a Source #

Instances

Bounded (VkSwapchainCreateBitmaskKHR FlagMask) Source # 
Enum (VkSwapchainCreateBitmaskKHR FlagMask) Source # 
Eq (VkSwapchainCreateBitmaskKHR a) Source # 
Integral (VkSwapchainCreateBitmaskKHR FlagMask) Source # 
Typeable FlagType a => Data (VkSwapchainCreateBitmaskKHR a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkSwapchainCreateBitmaskKHR a -> c (VkSwapchainCreateBitmaskKHR a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkSwapchainCreateBitmaskKHR a) #

toConstr :: VkSwapchainCreateBitmaskKHR a -> Constr #

dataTypeOf :: VkSwapchainCreateBitmaskKHR a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkSwapchainCreateBitmaskKHR a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkSwapchainCreateBitmaskKHR a)) #

gmapT :: (forall b. Data b => b -> b) -> VkSwapchainCreateBitmaskKHR a -> VkSwapchainCreateBitmaskKHR a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkSwapchainCreateBitmaskKHR a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkSwapchainCreateBitmaskKHR a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkSwapchainCreateBitmaskKHR a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkSwapchainCreateBitmaskKHR a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkSwapchainCreateBitmaskKHR a -> m (VkSwapchainCreateBitmaskKHR a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSwapchainCreateBitmaskKHR a -> m (VkSwapchainCreateBitmaskKHR a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSwapchainCreateBitmaskKHR a -> m (VkSwapchainCreateBitmaskKHR a) #

Num (VkSwapchainCreateBitmaskKHR FlagMask) Source # 
Ord (VkSwapchainCreateBitmaskKHR a) Source # 
Read (VkSwapchainCreateBitmaskKHR a) Source # 
Real (VkSwapchainCreateBitmaskKHR FlagMask) Source # 
Show (VkSwapchainCreateBitmaskKHR a) Source # 
Generic (VkSwapchainCreateBitmaskKHR a) Source # 
Storable (VkSwapchainCreateBitmaskKHR a) Source # 
Bits (VkSwapchainCreateBitmaskKHR FlagMask) Source # 

Methods

(.&.) :: VkSwapchainCreateBitmaskKHR FlagMask -> VkSwapchainCreateBitmaskKHR FlagMask -> VkSwapchainCreateBitmaskKHR FlagMask #

(.|.) :: VkSwapchainCreateBitmaskKHR FlagMask -> VkSwapchainCreateBitmaskKHR FlagMask -> VkSwapchainCreateBitmaskKHR FlagMask #

xor :: VkSwapchainCreateBitmaskKHR FlagMask -> VkSwapchainCreateBitmaskKHR FlagMask -> VkSwapchainCreateBitmaskKHR FlagMask #

complement :: VkSwapchainCreateBitmaskKHR FlagMask -> VkSwapchainCreateBitmaskKHR FlagMask #

shift :: VkSwapchainCreateBitmaskKHR FlagMask -> Int -> VkSwapchainCreateBitmaskKHR FlagMask #

rotate :: VkSwapchainCreateBitmaskKHR FlagMask -> Int -> VkSwapchainCreateBitmaskKHR FlagMask #

zeroBits :: VkSwapchainCreateBitmaskKHR FlagMask #

bit :: Int -> VkSwapchainCreateBitmaskKHR FlagMask #

setBit :: VkSwapchainCreateBitmaskKHR FlagMask -> Int -> VkSwapchainCreateBitmaskKHR FlagMask #

clearBit :: VkSwapchainCreateBitmaskKHR FlagMask -> Int -> VkSwapchainCreateBitmaskKHR FlagMask #

complementBit :: VkSwapchainCreateBitmaskKHR FlagMask -> Int -> VkSwapchainCreateBitmaskKHR FlagMask #

testBit :: VkSwapchainCreateBitmaskKHR FlagMask -> Int -> Bool #

bitSizeMaybe :: VkSwapchainCreateBitmaskKHR FlagMask -> Maybe Int #

bitSize :: VkSwapchainCreateBitmaskKHR FlagMask -> Int #

isSigned :: VkSwapchainCreateBitmaskKHR FlagMask -> Bool #

shiftL :: VkSwapchainCreateBitmaskKHR FlagMask -> Int -> VkSwapchainCreateBitmaskKHR FlagMask #

unsafeShiftL :: VkSwapchainCreateBitmaskKHR FlagMask -> Int -> VkSwapchainCreateBitmaskKHR FlagMask #

shiftR :: VkSwapchainCreateBitmaskKHR FlagMask -> Int -> VkSwapchainCreateBitmaskKHR FlagMask #

unsafeShiftR :: VkSwapchainCreateBitmaskKHR FlagMask -> Int -> VkSwapchainCreateBitmaskKHR FlagMask #

rotateL :: VkSwapchainCreateBitmaskKHR FlagMask -> Int -> VkSwapchainCreateBitmaskKHR FlagMask #

rotateR :: VkSwapchainCreateBitmaskKHR FlagMask -> Int -> VkSwapchainCreateBitmaskKHR FlagMask #

popCount :: VkSwapchainCreateBitmaskKHR FlagMask -> Int #

FiniteBits (VkSwapchainCreateBitmaskKHR FlagMask) Source # 
type Rep (VkSwapchainCreateBitmaskKHR a) Source # 
type Rep (VkSwapchainCreateBitmaskKHR a) = D1 (MetaData "VkSwapchainCreateBitmaskKHR" "Graphics.Vulkan.Types.Enum.SwapchainCreateFlagsKHR" "vulkan-api-1.1.2.1-GcVsfRwwhb24i5dsYq91EC" True) (C1 (MetaCons "VkSwapchainCreateBitmaskKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkSystemAllocationScope Source #

Instances

Bounded VkSystemAllocationScope Source # 
Enum VkSystemAllocationScope Source # 
Eq VkSystemAllocationScope Source # 
Data VkSystemAllocationScope Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkSystemAllocationScope -> c VkSystemAllocationScope #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkSystemAllocationScope #

toConstr :: VkSystemAllocationScope -> Constr #

dataTypeOf :: VkSystemAllocationScope -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkSystemAllocationScope) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkSystemAllocationScope) #

gmapT :: (forall b. Data b => b -> b) -> VkSystemAllocationScope -> VkSystemAllocationScope #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkSystemAllocationScope -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkSystemAllocationScope -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkSystemAllocationScope -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkSystemAllocationScope -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkSystemAllocationScope -> m VkSystemAllocationScope #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSystemAllocationScope -> m VkSystemAllocationScope #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSystemAllocationScope -> m VkSystemAllocationScope #

Num VkSystemAllocationScope Source # 
Ord VkSystemAllocationScope Source # 
Read VkSystemAllocationScope Source # 
Show VkSystemAllocationScope Source # 
Generic VkSystemAllocationScope Source # 
Storable VkSystemAllocationScope Source # 
type Rep VkSystemAllocationScope Source # 
type Rep VkSystemAllocationScope = D1 (MetaData "VkSystemAllocationScope" "Graphics.Vulkan.Types.Enum.SystemAllocationScope" "vulkan-api-1.1.2.1-GcVsfRwwhb24i5dsYq91EC" True) (C1 (MetaCons "VkSystemAllocationScope" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

type PFN_vkAllocationFunction = FunPtr HS_vkAllocationFunction Source #

typedef void* (VKAPI_PTR *PFN_vkAllocationFunction)(
    void*                                       pUserData,
    size_t                                      size,
    size_t                                      alignment,
    VkSystemAllocationScope                     allocationScope);

newVkAllocationFunction :: HS_vkAllocationFunction -> IO PFN_vkAllocationFunction Source #

Wrap haskell function into C-callable FunPtr. Note, you need to free resources after using it.

type PFN_vkDebugReportCallbackEXT = FunPtr HS_vkDebugReportCallbackEXT Source #

typedef VkBool32 (VKAPI_PTR *PFN_vkDebugReportCallbackEXT)(
    VkDebugReportFlagsEXT                       flags,
    VkDebugReportObjectTypeEXT                  objectType,
    uint64_t                                    object,
    size_t                                      location,
    int32_t                                     messageCode,
    const char*                                 pLayerPrefix,
    const char*                                 pMessage,
    void*                                       pUserData);

newVkDebugReportCallbackEXT :: HS_vkDebugReportCallbackEXT -> IO PFN_vkDebugReportCallbackEXT Source #

Wrap haskell function into C-callable FunPtr. Note, you need to free resources after using it.

type PFN_vkDebugUtilsMessengerCallbackEXT = FunPtr HS_vkDebugUtilsMessengerCallbackEXT Source #

typedef VkBool32 (VKAPI_PTR *PFN_vkDebugUtilsMessengerCallbackEXT)(
    VkDebugUtilsMessageSeverityFlagBitsEXT           messageSeverity,
    VkDebugUtilsMessageTypeFlagsEXT                  messageType,
    const VkDebugUtilsMessengerCallbackDataEXT*      pCallbackData,
    void*                                            pUserData);

newVkDebugUtilsMessengerCallbackEXT :: HS_vkDebugUtilsMessengerCallbackEXT -> IO PFN_vkDebugUtilsMessengerCallbackEXT Source #

Wrap haskell function into C-callable FunPtr. Note, you need to free resources after using it.

type PFN_vkFreeFunction = FunPtr HS_vkFreeFunction Source #

typedef void (VKAPI_PTR *PFN_vkFreeFunction)(
    void*                                       pUserData,
    void*                                       pMemory);

newVkFreeFunction :: HS_vkFreeFunction -> IO PFN_vkFreeFunction Source #

Wrap haskell function into C-callable FunPtr. Note, you need to free resources after using it.

type PFN_vkInternalAllocationNotification = FunPtr HS_vkInternalAllocationNotification Source #

typedef void (VKAPI_PTR *PFN_vkInternalAllocationNotification)(
    void*                                       pUserData,
    size_t                                      size,
    VkInternalAllocationType                    allocationType,
    VkSystemAllocationScope                     allocationScope);

newVkInternalAllocationNotification :: HS_vkInternalAllocationNotification -> IO PFN_vkInternalAllocationNotification Source #

Wrap haskell function into C-callable FunPtr. Note, you need to free resources after using it.

type PFN_vkInternalFreeNotification = FunPtr HS_vkInternalFreeNotification Source #

typedef void (VKAPI_PTR *PFN_vkInternalFreeNotification)(
    void*                                       pUserData,
    size_t                                      size,
    VkInternalAllocationType                    allocationType,
    VkSystemAllocationScope                     allocationScope);

newVkInternalFreeNotification :: HS_vkInternalFreeNotification -> IO PFN_vkInternalFreeNotification Source #

Wrap haskell function into C-callable FunPtr. Note, you need to free resources after using it.

type PFN_vkReallocationFunction = FunPtr HS_vkReallocationFunction Source #

typedef void* (VKAPI_PTR *PFN_vkReallocationFunction)(
    void*                                       pUserData,
    void*                                       pOriginal,
    size_t                                      size,
    size_t                                      alignment,
    VkSystemAllocationScope                     allocationScope);

newVkReallocationFunction :: HS_vkReallocationFunction -> IO PFN_vkReallocationFunction Source #

Wrap haskell function into C-callable FunPtr. Note, you need to free resources after using it.

type PFN_vkVoidFunction = FunPtr HS_vkVoidFunction Source #

typedef void (VKAPI_PTR *PFN_vkVoidFunction)(void);

newVkVoidFunction :: HS_vkVoidFunction -> IO PFN_vkVoidFunction Source #

Wrap haskell function into C-callable FunPtr. Note, you need to free resources after using it.

data VkBuffer_T Source #

Opaque data type referenced by VkBuffer

data VkBufferView_T Source #

Opaque data type referenced by VkBufferView

data VkCommandBuffer_T Source #

Opaque data type referenced by VkCommandBuffer

data VkCommandPool_T Source #

Opaque data type referenced by VkCommandPool

data VkDebugReportCallbackEXT_T Source #

Opaque data type referenced by VkDebugReportCallbackEXT

data VkDebugUtilsMessengerEXT_T Source #

Opaque data type referenced by VkDebugUtilsMessengerEXT

data VkDescriptorPool_T Source #

Opaque data type referenced by VkDescriptorPool

data VkDescriptorSet_T Source #

Opaque data type referenced by VkDescriptorSet

data VkDescriptorSetLayout_T Source #

Opaque data type referenced by VkDescriptorSetLayout

data VkDescriptorUpdateTemplate_T Source #

Opaque data type referenced by VkDescriptorUpdateTemplate

data VkDescriptorUpdateTemplateKHR_T Source #

Opaque data type referenced by VkDescriptorUpdateTemplateKHR

data VkDevice_T Source #

Opaque data type referenced by VkDevice

data VkDeviceMemory_T Source #

Opaque data type referenced by VkDeviceMemory

data VkDisplayKHR_T Source #

Opaque data type referenced by VkDisplayKHR

data VkDisplayModeKHR_T Source #

Opaque data type referenced by VkDisplayModeKHR

data VkEvent_T Source #

Opaque data type referenced by VkEvent

data VkFence_T Source #

Opaque data type referenced by VkFence

data VkFramebuffer_T Source #

Opaque data type referenced by VkFramebuffer

data VkImage_T Source #

Opaque data type referenced by VkImage

data VkImageView_T Source #

Opaque data type referenced by VkImageView

data VkIndirectCommandsLayoutNVX_T Source #

Opaque data type referenced by VkIndirectCommandsLayoutNVX

data VkInstance_T Source #

Opaque data type referenced by VkInstance

data VkObjectTableNVX_T Source #

Opaque data type referenced by VkObjectTableNVX

data VkPhysicalDevice_T Source #

Opaque data type referenced by VkPhysicalDevice

data VkPipeline_T Source #

Opaque data type referenced by VkPipeline

data VkPipelineCache_T Source #

Opaque data type referenced by VkPipelineCache

data VkPipelineLayout_T Source #

Opaque data type referenced by VkPipelineLayout

data VkQueryPool_T Source #

Opaque data type referenced by VkQueryPool

data VkQueue_T Source #

Opaque data type referenced by VkQueue

data VkRenderPass_T Source #

Opaque data type referenced by VkRenderPass

data VkSampler_T Source #

Opaque data type referenced by VkSampler

data VkSamplerYcbcrConversion_T Source #

Opaque data type referenced by VkSamplerYcbcrConversion

data VkSamplerYcbcrConversionKHR_T Source #

Opaque data type referenced by VkSamplerYcbcrConversionKHR

data VkSemaphore_T Source #

Opaque data type referenced by VkSemaphore

data VkShaderModule_T Source #

Opaque data type referenced by VkShaderModule

data VkSurfaceKHR_T Source #

Opaque data type referenced by VkSurfaceKHR

data VkSwapchainKHR_T Source #

Opaque data type referenced by VkSwapchainKHR

data VkValidationCacheEXT_T Source #

Opaque data type referenced by VkValidationCacheEXT

data VkAllocationCallbacks Source #

typedef struct VkAllocationCallbacks {
    void*           pUserData;
    PFN_vkAllocationFunction   pfnAllocation;
    PFN_vkReallocationFunction pfnReallocation;
    PFN_vkFreeFunction    pfnFree;
    PFN_vkInternalAllocationNotification pfnInternalAllocation;
    PFN_vkInternalFreeNotification pfnInternalFree;
} VkAllocationCallbacks;

VkAllocationCallbacks registry at www.khronos.org

Instances

Eq VkAllocationCallbacks Source # 
Ord VkAllocationCallbacks Source # 
Show VkAllocationCallbacks Source # 
Storable VkAllocationCallbacks Source # 
VulkanMarshalPrim VkAllocationCallbacks Source # 
VulkanMarshal VkAllocationCallbacks Source # 
CanWriteField "pUserData" VkAllocationCallbacks Source # 
CanWriteField "pfnAllocation" VkAllocationCallbacks Source # 
CanWriteField "pfnFree" VkAllocationCallbacks Source # 
CanWriteField "pfnInternalAllocation" VkAllocationCallbacks Source # 

Methods

writeField :: Ptr VkAllocationCallbacks -> FieldType "pfnInternalAllocation" VkAllocationCallbacks -> IO () Source #

CanWriteField "pfnInternalFree" VkAllocationCallbacks Source # 
CanWriteField "pfnReallocation" VkAllocationCallbacks Source # 
CanReadField "pUserData" VkAllocationCallbacks Source # 
CanReadField "pfnAllocation" VkAllocationCallbacks Source # 
CanReadField "pfnFree" VkAllocationCallbacks Source # 
CanReadField "pfnInternalAllocation" VkAllocationCallbacks Source # 
CanReadField "pfnInternalFree" VkAllocationCallbacks Source # 
CanReadField "pfnReallocation" VkAllocationCallbacks Source # 
HasField "pUserData" VkAllocationCallbacks Source # 
HasField "pfnAllocation" VkAllocationCallbacks Source # 

Associated Types

type FieldType ("pfnAllocation" :: Symbol) VkAllocationCallbacks :: Type Source #

type FieldOptional ("pfnAllocation" :: Symbol) VkAllocationCallbacks :: Bool Source #

type FieldOffset ("pfnAllocation" :: Symbol) VkAllocationCallbacks :: Nat Source #

type FieldIsArray ("pfnAllocation" :: Symbol) VkAllocationCallbacks :: Bool Source #

HasField "pfnFree" VkAllocationCallbacks Source # 
HasField "pfnInternalAllocation" VkAllocationCallbacks Source # 

Associated Types

type FieldType ("pfnInternalAllocation" :: Symbol) VkAllocationCallbacks :: Type Source #

type FieldOptional ("pfnInternalAllocation" :: Symbol) VkAllocationCallbacks :: Bool Source #

type FieldOffset ("pfnInternalAllocation" :: Symbol) VkAllocationCallbacks :: Nat Source #

type FieldIsArray ("pfnInternalAllocation" :: Symbol) VkAllocationCallbacks :: Bool Source #

HasField "pfnInternalFree" VkAllocationCallbacks Source # 

Associated Types

type FieldType ("pfnInternalFree" :: Symbol) VkAllocationCallbacks :: Type Source #

type FieldOptional ("pfnInternalFree" :: Symbol) VkAllocationCallbacks :: Bool Source #

type FieldOffset ("pfnInternalFree" :: Symbol) VkAllocationCallbacks :: Nat Source #

type FieldIsArray ("pfnInternalFree" :: Symbol) VkAllocationCallbacks :: Bool Source #

HasField "pfnReallocation" VkAllocationCallbacks Source # 

Associated Types

type FieldType ("pfnReallocation" :: Symbol) VkAllocationCallbacks :: Type Source #

type FieldOptional ("pfnReallocation" :: Symbol) VkAllocationCallbacks :: Bool Source #

type FieldOffset ("pfnReallocation" :: Symbol) VkAllocationCallbacks :: Nat Source #

type FieldIsArray ("pfnReallocation" :: Symbol) VkAllocationCallbacks :: Bool Source #

type StructFields VkAllocationCallbacks Source # 
type StructFields VkAllocationCallbacks = (:) Symbol "pUserData" ((:) Symbol "pfnAllocation" ((:) Symbol "pfnReallocation" ((:) Symbol "pfnFree" ((:) Symbol "pfnInternalAllocation" ((:) Symbol "pfnInternalFree" ([] Symbol))))))
type CUnionType VkAllocationCallbacks Source # 
type ReturnedOnly VkAllocationCallbacks Source # 
type StructExtends VkAllocationCallbacks Source # 
type FieldType "pUserData" VkAllocationCallbacks Source # 
type FieldType "pfnAllocation" VkAllocationCallbacks Source # 
type FieldType "pfnFree" VkAllocationCallbacks Source # 
type FieldType "pfnInternalAllocation" VkAllocationCallbacks Source # 
type FieldType "pfnInternalFree" VkAllocationCallbacks Source # 
type FieldType "pfnReallocation" VkAllocationCallbacks Source # 
type FieldOptional "pUserData" VkAllocationCallbacks Source # 
type FieldOptional "pfnAllocation" VkAllocationCallbacks Source # 
type FieldOptional "pfnFree" VkAllocationCallbacks Source # 
type FieldOptional "pfnInternalAllocation" VkAllocationCallbacks Source # 
type FieldOptional "pfnInternalAllocation" VkAllocationCallbacks = True
type FieldOptional "pfnInternalFree" VkAllocationCallbacks Source # 
type FieldOptional "pfnInternalFree" VkAllocationCallbacks = True
type FieldOptional "pfnReallocation" VkAllocationCallbacks Source # 
type FieldOptional "pfnReallocation" VkAllocationCallbacks = False
type FieldOffset "pUserData" VkAllocationCallbacks Source # 
type FieldOffset "pUserData" VkAllocationCallbacks = 0
type FieldOffset "pfnAllocation" VkAllocationCallbacks Source # 
type FieldOffset "pfnAllocation" VkAllocationCallbacks = 8
type FieldOffset "pfnFree" VkAllocationCallbacks Source # 
type FieldOffset "pfnInternalAllocation" VkAllocationCallbacks Source # 
type FieldOffset "pfnInternalAllocation" VkAllocationCallbacks = 32
type FieldOffset "pfnInternalFree" VkAllocationCallbacks Source # 
type FieldOffset "pfnInternalFree" VkAllocationCallbacks = 40
type FieldOffset "pfnReallocation" VkAllocationCallbacks Source # 
type FieldOffset "pfnReallocation" VkAllocationCallbacks = 16
type FieldIsArray "pUserData" VkAllocationCallbacks Source # 
type FieldIsArray "pfnAllocation" VkAllocationCallbacks Source # 
type FieldIsArray "pfnFree" VkAllocationCallbacks Source # 
type FieldIsArray "pfnInternalAllocation" VkAllocationCallbacks Source # 
type FieldIsArray "pfnInternalAllocation" VkAllocationCallbacks = False
type FieldIsArray "pfnInternalFree" VkAllocationCallbacks Source # 
type FieldIsArray "pfnInternalFree" VkAllocationCallbacks = False
type FieldIsArray "pfnReallocation" VkAllocationCallbacks Source # 
type FieldIsArray "pfnReallocation" VkAllocationCallbacks = False

data VkExtent2D Source #

typedef struct VkExtent2D {
    uint32_t        width;
    uint32_t        height;
} VkExtent2D;

VkExtent2D registry at www.khronos.org

Instances

Eq VkExtent2D Source # 
Ord VkExtent2D Source # 
Show VkExtent2D Source # 
Storable VkExtent2D Source # 
VulkanMarshalPrim VkExtent2D Source # 
VulkanMarshal VkExtent2D Source # 
CanWriteField "height" VkExtent2D Source # 

Methods

writeField :: Ptr VkExtent2D -> FieldType "height" VkExtent2D -> IO () Source #

CanWriteField "width" VkExtent2D Source # 

Methods

writeField :: Ptr VkExtent2D -> FieldType "width" VkExtent2D -> IO () Source #

CanReadField "height" VkExtent2D Source # 
CanReadField "width" VkExtent2D Source # 
HasField "height" VkExtent2D Source # 

Associated Types

type FieldType ("height" :: Symbol) VkExtent2D :: Type Source #

type FieldOptional ("height" :: Symbol) VkExtent2D :: Bool Source #

type FieldOffset ("height" :: Symbol) VkExtent2D :: Nat Source #

type FieldIsArray ("height" :: Symbol) VkExtent2D :: Bool Source #

HasField "width" VkExtent2D Source # 

Associated Types

type FieldType ("width" :: Symbol) VkExtent2D :: Type Source #

type FieldOptional ("width" :: Symbol) VkExtent2D :: Bool Source #

type FieldOffset ("width" :: Symbol) VkExtent2D :: Nat Source #

type FieldIsArray ("width" :: Symbol) VkExtent2D :: Bool Source #

type StructFields VkExtent2D Source # 
type StructFields VkExtent2D = (:) Symbol "width" ((:) Symbol "height" ([] Symbol))
type CUnionType VkExtent2D Source # 
type ReturnedOnly VkExtent2D Source # 
type StructExtends VkExtent2D Source # 
type FieldType "height" VkExtent2D Source # 
type FieldType "height" VkExtent2D = Word32
type FieldType "width" VkExtent2D Source # 
type FieldType "width" VkExtent2D = Word32
type FieldOptional "height" VkExtent2D Source # 
type FieldOptional "width" VkExtent2D Source # 
type FieldOffset "height" VkExtent2D Source # 
type FieldOffset "height" VkExtent2D = 4
type FieldOffset "width" VkExtent2D Source # 
type FieldOffset "width" VkExtent2D = 0
type FieldIsArray "height" VkExtent2D Source # 
type FieldIsArray "height" VkExtent2D = False
type FieldIsArray "width" VkExtent2D Source # 

data VkExtent3D Source #

typedef struct VkExtent3D {
    uint32_t        width;
    uint32_t        height;
    uint32_t        depth;
} VkExtent3D;

VkExtent3D registry at www.khronos.org

Instances

Eq VkExtent3D Source # 
Ord VkExtent3D Source # 
Show VkExtent3D Source # 
Storable VkExtent3D Source # 
VulkanMarshalPrim VkExtent3D Source # 
VulkanMarshal VkExtent3D Source # 
CanWriteField "depth" VkExtent3D Source # 

Methods

writeField :: Ptr VkExtent3D -> FieldType "depth" VkExtent3D -> IO () Source #

CanWriteField "height" VkExtent3D Source # 

Methods

writeField :: Ptr VkExtent3D -> FieldType "height" VkExtent3D -> IO () Source #

CanWriteField "width" VkExtent3D Source # 

Methods

writeField :: Ptr VkExtent3D -> FieldType "width" VkExtent3D -> IO () Source #

CanReadField "depth" VkExtent3D Source # 
CanReadField "height" VkExtent3D Source # 
CanReadField "width" VkExtent3D Source # 
HasField "depth" VkExtent3D Source # 

Associated Types

type FieldType ("depth" :: Symbol) VkExtent3D :: Type Source #

type FieldOptional ("depth" :: Symbol) VkExtent3D :: Bool Source #

type FieldOffset ("depth" :: Symbol) VkExtent3D :: Nat Source #

type FieldIsArray ("depth" :: Symbol) VkExtent3D :: Bool Source #

HasField "height" VkExtent3D Source # 

Associated Types

type FieldType ("height" :: Symbol) VkExtent3D :: Type Source #

type FieldOptional ("height" :: Symbol) VkExtent3D :: Bool Source #

type FieldOffset ("height" :: Symbol) VkExtent3D :: Nat Source #

type FieldIsArray ("height" :: Symbol) VkExtent3D :: Bool Source #

HasField "width" VkExtent3D Source # 

Associated Types

type FieldType ("width" :: Symbol) VkExtent3D :: Type Source #

type FieldOptional ("width" :: Symbol) VkExtent3D :: Bool Source #

type FieldOffset ("width" :: Symbol) VkExtent3D :: Nat Source #

type FieldIsArray ("width" :: Symbol) VkExtent3D :: Bool Source #

type StructFields VkExtent3D Source # 
type StructFields VkExtent3D = (:) Symbol "width" ((:) Symbol "height" ((:) Symbol "depth" ([] Symbol)))
type CUnionType VkExtent3D Source # 
type ReturnedOnly VkExtent3D Source # 
type StructExtends VkExtent3D Source # 
type FieldType "depth" VkExtent3D Source # 
type FieldType "depth" VkExtent3D = Word32
type FieldType "height" VkExtent3D Source # 
type FieldType "height" VkExtent3D = Word32
type FieldType "width" VkExtent3D Source # 
type FieldType "width" VkExtent3D = Word32
type FieldOptional "depth" VkExtent3D Source # 
type FieldOptional "height" VkExtent3D Source # 
type FieldOptional "width" VkExtent3D Source # 
type FieldOffset "depth" VkExtent3D Source # 
type FieldOffset "depth" VkExtent3D = 8
type FieldOffset "height" VkExtent3D Source # 
type FieldOffset "height" VkExtent3D = 4
type FieldOffset "width" VkExtent3D Source # 
type FieldOffset "width" VkExtent3D = 0
type FieldIsArray "depth" VkExtent3D Source # 
type FieldIsArray "height" VkExtent3D Source # 
type FieldIsArray "height" VkExtent3D = False
type FieldIsArray "width" VkExtent3D Source # 

data VkPresentInfoKHR Source #

typedef struct VkPresentInfoKHR {
    VkStructureType sType;
    const void*  pNext;
    uint32_t         waitSemaphoreCount;
    const VkSemaphore* pWaitSemaphores;
    uint32_t                         swapchainCount;
    const VkSwapchainKHR* pSwapchains;
    const uint32_t* pImageIndices;
    VkResult* pResults;
} VkPresentInfoKHR;

VkPresentInfoKHR registry at www.khronos.org

Instances

Eq VkPresentInfoKHR Source # 
Ord VkPresentInfoKHR Source # 
Show VkPresentInfoKHR Source # 
Storable VkPresentInfoKHR Source # 
VulkanMarshalPrim VkPresentInfoKHR Source # 
VulkanMarshal VkPresentInfoKHR Source # 
CanWriteField "pImageIndices" VkPresentInfoKHR Source # 

Methods

writeField :: Ptr VkPresentInfoKHR -> FieldType "pImageIndices" VkPresentInfoKHR -> IO () Source #

CanWriteField "pNext" VkPresentInfoKHR Source # 
CanWriteField "pResults" VkPresentInfoKHR Source # 
CanWriteField "pSwapchains" VkPresentInfoKHR Source # 
CanWriteField "pWaitSemaphores" VkPresentInfoKHR Source # 

Methods

writeField :: Ptr VkPresentInfoKHR -> FieldType "pWaitSemaphores" VkPresentInfoKHR -> IO () Source #

CanWriteField "sType" VkPresentInfoKHR Source # 
CanWriteField "swapchainCount" VkPresentInfoKHR Source # 

Methods

writeField :: Ptr VkPresentInfoKHR -> FieldType "swapchainCount" VkPresentInfoKHR -> IO () Source #

CanWriteField "waitSemaphoreCount" VkPresentInfoKHR Source # 

Methods

writeField :: Ptr VkPresentInfoKHR -> FieldType "waitSemaphoreCount" VkPresentInfoKHR -> IO () Source #

CanReadField "pImageIndices" VkPresentInfoKHR Source # 
CanReadField "pNext" VkPresentInfoKHR Source # 
CanReadField "pResults" VkPresentInfoKHR Source # 
CanReadField "pSwapchains" VkPresentInfoKHR Source # 
CanReadField "pWaitSemaphores" VkPresentInfoKHR Source # 
CanReadField "sType" VkPresentInfoKHR Source # 
CanReadField "swapchainCount" VkPresentInfoKHR Source # 
CanReadField "waitSemaphoreCount" VkPresentInfoKHR Source # 
HasField "pImageIndices" VkPresentInfoKHR Source # 

Associated Types

type FieldType ("pImageIndices" :: Symbol) VkPresentInfoKHR :: Type Source #

type FieldOptional ("pImageIndices" :: Symbol) VkPresentInfoKHR :: Bool Source #

type FieldOffset ("pImageIndices" :: Symbol) VkPresentInfoKHR :: Nat Source #

type FieldIsArray ("pImageIndices" :: Symbol) VkPresentInfoKHR :: Bool Source #

HasField "pNext" VkPresentInfoKHR Source # 
HasField "pResults" VkPresentInfoKHR Source # 

Associated Types

type FieldType ("pResults" :: Symbol) VkPresentInfoKHR :: Type Source #

type FieldOptional ("pResults" :: Symbol) VkPresentInfoKHR :: Bool Source #

type FieldOffset ("pResults" :: Symbol) VkPresentInfoKHR :: Nat Source #

type FieldIsArray ("pResults" :: Symbol) VkPresentInfoKHR :: Bool Source #

HasField "pSwapchains" VkPresentInfoKHR Source # 

Associated Types

type FieldType ("pSwapchains" :: Symbol) VkPresentInfoKHR :: Type Source #

type FieldOptional ("pSwapchains" :: Symbol) VkPresentInfoKHR :: Bool Source #

type FieldOffset ("pSwapchains" :: Symbol) VkPresentInfoKHR :: Nat Source #

type FieldIsArray ("pSwapchains" :: Symbol) VkPresentInfoKHR :: Bool Source #

HasField "pWaitSemaphores" VkPresentInfoKHR Source # 

Associated Types

type FieldType ("pWaitSemaphores" :: Symbol) VkPresentInfoKHR :: Type Source #

type FieldOptional ("pWaitSemaphores" :: Symbol) VkPresentInfoKHR :: Bool Source #

type FieldOffset ("pWaitSemaphores" :: Symbol) VkPresentInfoKHR :: Nat Source #

type FieldIsArray ("pWaitSemaphores" :: Symbol) VkPresentInfoKHR :: Bool Source #

HasField "sType" VkPresentInfoKHR Source # 
HasField "swapchainCount" VkPresentInfoKHR Source # 

Associated Types

type FieldType ("swapchainCount" :: Symbol) VkPresentInfoKHR :: Type Source #

type FieldOptional ("swapchainCount" :: Symbol) VkPresentInfoKHR :: Bool Source #

type FieldOffset ("swapchainCount" :: Symbol) VkPresentInfoKHR :: Nat Source #

type FieldIsArray ("swapchainCount" :: Symbol) VkPresentInfoKHR :: Bool Source #

HasField "waitSemaphoreCount" VkPresentInfoKHR Source # 

Associated Types

type FieldType ("waitSemaphoreCount" :: Symbol) VkPresentInfoKHR :: Type Source #

type FieldOptional ("waitSemaphoreCount" :: Symbol) VkPresentInfoKHR :: Bool Source #

type FieldOffset ("waitSemaphoreCount" :: Symbol) VkPresentInfoKHR :: Nat Source #

type FieldIsArray ("waitSemaphoreCount" :: Symbol) VkPresentInfoKHR :: Bool Source #

type StructFields VkPresentInfoKHR Source # 
type StructFields VkPresentInfoKHR = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "waitSemaphoreCount" ((:) Symbol "pWaitSemaphores" ((:) Symbol "swapchainCount" ((:) Symbol "pSwapchains" ((:) Symbol "pImageIndices" ((:) Symbol "pResults" ([] Symbol))))))))
type CUnionType VkPresentInfoKHR Source # 
type ReturnedOnly VkPresentInfoKHR Source # 
type StructExtends VkPresentInfoKHR Source # 
type FieldType "pImageIndices" VkPresentInfoKHR Source # 
type FieldType "pImageIndices" VkPresentInfoKHR = Ptr Word32
type FieldType "pNext" VkPresentInfoKHR Source # 
type FieldType "pResults" VkPresentInfoKHR Source # 
type FieldType "pSwapchains" VkPresentInfoKHR Source # 
type FieldType "pWaitSemaphores" VkPresentInfoKHR Source # 
type FieldType "pWaitSemaphores" VkPresentInfoKHR = Ptr VkSemaphore
type FieldType "sType" VkPresentInfoKHR Source # 
type FieldType "swapchainCount" VkPresentInfoKHR Source # 
type FieldType "swapchainCount" VkPresentInfoKHR = Word32
type FieldType "waitSemaphoreCount" VkPresentInfoKHR Source # 
type FieldType "waitSemaphoreCount" VkPresentInfoKHR = Word32
type FieldOptional "pImageIndices" VkPresentInfoKHR Source # 
type FieldOptional "pImageIndices" VkPresentInfoKHR = False
type FieldOptional "pNext" VkPresentInfoKHR Source # 
type FieldOptional "pResults" VkPresentInfoKHR Source # 
type FieldOptional "pSwapchains" VkPresentInfoKHR Source # 
type FieldOptional "pSwapchains" VkPresentInfoKHR = False
type FieldOptional "pWaitSemaphores" VkPresentInfoKHR Source # 
type FieldOptional "pWaitSemaphores" VkPresentInfoKHR = False
type FieldOptional "sType" VkPresentInfoKHR Source # 
type FieldOptional "swapchainCount" VkPresentInfoKHR Source # 
type FieldOptional "swapchainCount" VkPresentInfoKHR = False
type FieldOptional "waitSemaphoreCount" VkPresentInfoKHR Source # 
type FieldOptional "waitSemaphoreCount" VkPresentInfoKHR = True
type FieldOffset "pImageIndices" VkPresentInfoKHR Source # 
type FieldOffset "pImageIndices" VkPresentInfoKHR = 48
type FieldOffset "pNext" VkPresentInfoKHR Source # 
type FieldOffset "pNext" VkPresentInfoKHR = 8
type FieldOffset "pResults" VkPresentInfoKHR Source # 
type FieldOffset "pResults" VkPresentInfoKHR = 56
type FieldOffset "pSwapchains" VkPresentInfoKHR Source # 
type FieldOffset "pSwapchains" VkPresentInfoKHR = 40
type FieldOffset "pWaitSemaphores" VkPresentInfoKHR Source # 
type FieldOffset "pWaitSemaphores" VkPresentInfoKHR = 24
type FieldOffset "sType" VkPresentInfoKHR Source # 
type FieldOffset "sType" VkPresentInfoKHR = 0
type FieldOffset "swapchainCount" VkPresentInfoKHR Source # 
type FieldOffset "swapchainCount" VkPresentInfoKHR = 32
type FieldOffset "waitSemaphoreCount" VkPresentInfoKHR Source # 
type FieldOffset "waitSemaphoreCount" VkPresentInfoKHR = 16
type FieldIsArray "pImageIndices" VkPresentInfoKHR Source # 
type FieldIsArray "pImageIndices" VkPresentInfoKHR = False
type FieldIsArray "pNext" VkPresentInfoKHR Source # 
type FieldIsArray "pResults" VkPresentInfoKHR Source # 
type FieldIsArray "pSwapchains" VkPresentInfoKHR Source # 
type FieldIsArray "pSwapchains" VkPresentInfoKHR = False
type FieldIsArray "pWaitSemaphores" VkPresentInfoKHR Source # 
type FieldIsArray "pWaitSemaphores" VkPresentInfoKHR = False
type FieldIsArray "sType" VkPresentInfoKHR Source # 
type FieldIsArray "swapchainCount" VkPresentInfoKHR Source # 
type FieldIsArray "swapchainCount" VkPresentInfoKHR = False
type FieldIsArray "waitSemaphoreCount" VkPresentInfoKHR Source # 
type FieldIsArray "waitSemaphoreCount" VkPresentInfoKHR = False

data VkPresentRegionKHR Source #

typedef struct VkPresentRegionKHR {
    uint32_t         rectangleCount;
    const VkRectLayerKHR*   pRectangles;
} VkPresentRegionKHR;

VkPresentRegionKHR registry at www.khronos.org

Instances

Eq VkPresentRegionKHR Source # 
Ord VkPresentRegionKHR Source # 
Show VkPresentRegionKHR Source # 
Storable VkPresentRegionKHR Source # 
VulkanMarshalPrim VkPresentRegionKHR Source # 
VulkanMarshal VkPresentRegionKHR Source # 
CanWriteField "pRectangles" VkPresentRegionKHR Source # 
CanWriteField "rectangleCount" VkPresentRegionKHR Source # 
CanReadField "pRectangles" VkPresentRegionKHR Source # 
CanReadField "rectangleCount" VkPresentRegionKHR Source # 
HasField "pRectangles" VkPresentRegionKHR Source # 

Associated Types

type FieldType ("pRectangles" :: Symbol) VkPresentRegionKHR :: Type Source #

type FieldOptional ("pRectangles" :: Symbol) VkPresentRegionKHR :: Bool Source #

type FieldOffset ("pRectangles" :: Symbol) VkPresentRegionKHR :: Nat Source #

type FieldIsArray ("pRectangles" :: Symbol) VkPresentRegionKHR :: Bool Source #

HasField "rectangleCount" VkPresentRegionKHR Source # 

Associated Types

type FieldType ("rectangleCount" :: Symbol) VkPresentRegionKHR :: Type Source #

type FieldOptional ("rectangleCount" :: Symbol) VkPresentRegionKHR :: Bool Source #

type FieldOffset ("rectangleCount" :: Symbol) VkPresentRegionKHR :: Nat Source #

type FieldIsArray ("rectangleCount" :: Symbol) VkPresentRegionKHR :: Bool Source #

type StructFields VkPresentRegionKHR Source # 
type StructFields VkPresentRegionKHR = (:) Symbol "rectangleCount" ((:) Symbol "pRectangles" ([] Symbol))
type CUnionType VkPresentRegionKHR Source # 
type ReturnedOnly VkPresentRegionKHR Source # 
type StructExtends VkPresentRegionKHR Source # 
type FieldType "pRectangles" VkPresentRegionKHR Source # 
type FieldType "rectangleCount" VkPresentRegionKHR Source # 
type FieldType "rectangleCount" VkPresentRegionKHR = Word32
type FieldOptional "pRectangles" VkPresentRegionKHR Source # 
type FieldOptional "rectangleCount" VkPresentRegionKHR Source # 
type FieldOptional "rectangleCount" VkPresentRegionKHR = True
type FieldOffset "pRectangles" VkPresentRegionKHR Source # 
type FieldOffset "pRectangles" VkPresentRegionKHR = 8
type FieldOffset "rectangleCount" VkPresentRegionKHR Source # 
type FieldOffset "rectangleCount" VkPresentRegionKHR = 0
type FieldIsArray "pRectangles" VkPresentRegionKHR Source # 
type FieldIsArray "rectangleCount" VkPresentRegionKHR Source # 
type FieldIsArray "rectangleCount" VkPresentRegionKHR = False

data VkPresentRegionsKHR Source #

typedef struct VkPresentRegionsKHR {
    VkStructureType sType;
    const void*                      pNext;
    uint32_t                         swapchainCount;
    const VkPresentRegionKHR*   pRegions;
} VkPresentRegionsKHR;

VkPresentRegionsKHR registry at www.khronos.org

Instances

Eq VkPresentRegionsKHR Source # 
Ord VkPresentRegionsKHR Source # 
Show VkPresentRegionsKHR Source # 
Storable VkPresentRegionsKHR Source # 
VulkanMarshalPrim VkPresentRegionsKHR Source # 
VulkanMarshal VkPresentRegionsKHR Source # 
CanWriteField "pNext" VkPresentRegionsKHR Source # 
CanWriteField "pRegions" VkPresentRegionsKHR Source # 
CanWriteField "sType" VkPresentRegionsKHR Source # 
CanWriteField "swapchainCount" VkPresentRegionsKHR Source # 
CanReadField "pNext" VkPresentRegionsKHR Source # 
CanReadField "pRegions" VkPresentRegionsKHR Source # 
CanReadField "sType" VkPresentRegionsKHR Source # 
CanReadField "swapchainCount" VkPresentRegionsKHR Source # 
HasField "pNext" VkPresentRegionsKHR Source # 
HasField "pRegions" VkPresentRegionsKHR Source # 
HasField "sType" VkPresentRegionsKHR Source # 
HasField "swapchainCount" VkPresentRegionsKHR Source # 

Associated Types

type FieldType ("swapchainCount" :: Symbol) VkPresentRegionsKHR :: Type Source #

type FieldOptional ("swapchainCount" :: Symbol) VkPresentRegionsKHR :: Bool Source #

type FieldOffset ("swapchainCount" :: Symbol) VkPresentRegionsKHR :: Nat Source #

type FieldIsArray ("swapchainCount" :: Symbol) VkPresentRegionsKHR :: Bool Source #

type StructFields VkPresentRegionsKHR Source # 
type StructFields VkPresentRegionsKHR = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "swapchainCount" ((:) Symbol "pRegions" ([] Symbol))))
type CUnionType VkPresentRegionsKHR Source # 
type ReturnedOnly VkPresentRegionsKHR Source # 
type StructExtends VkPresentRegionsKHR Source # 
type FieldType "pNext" VkPresentRegionsKHR Source # 
type FieldType "pRegions" VkPresentRegionsKHR Source # 
type FieldType "sType" VkPresentRegionsKHR Source # 
type FieldType "swapchainCount" VkPresentRegionsKHR Source # 
type FieldType "swapchainCount" VkPresentRegionsKHR = Word32
type FieldOptional "pNext" VkPresentRegionsKHR Source # 
type FieldOptional "pRegions" VkPresentRegionsKHR Source # 
type FieldOptional "sType" VkPresentRegionsKHR Source # 
type FieldOptional "swapchainCount" VkPresentRegionsKHR Source # 
type FieldOptional "swapchainCount" VkPresentRegionsKHR = False
type FieldOffset "pNext" VkPresentRegionsKHR Source # 
type FieldOffset "pRegions" VkPresentRegionsKHR Source # 
type FieldOffset "pRegions" VkPresentRegionsKHR = 24
type FieldOffset "sType" VkPresentRegionsKHR Source # 
type FieldOffset "swapchainCount" VkPresentRegionsKHR Source # 
type FieldOffset "swapchainCount" VkPresentRegionsKHR = 16
type FieldIsArray "pNext" VkPresentRegionsKHR Source # 
type FieldIsArray "pRegions" VkPresentRegionsKHR Source # 
type FieldIsArray "sType" VkPresentRegionsKHR Source # 
type FieldIsArray "swapchainCount" VkPresentRegionsKHR Source # 
type FieldIsArray "swapchainCount" VkPresentRegionsKHR = False

data VkPresentTimeGOOGLE Source #

typedef struct VkPresentTimeGOOGLE {
    uint32_t                         presentID;
    uint64_t                         desiredPresentTime;
} VkPresentTimeGOOGLE;

VkPresentTimeGOOGLE registry at www.khronos.org

Instances

Eq VkPresentTimeGOOGLE Source # 
Ord VkPresentTimeGOOGLE Source # 
Show VkPresentTimeGOOGLE Source # 
Storable VkPresentTimeGOOGLE Source # 
VulkanMarshalPrim VkPresentTimeGOOGLE Source # 
VulkanMarshal VkPresentTimeGOOGLE Source # 
CanWriteField "desiredPresentTime" VkPresentTimeGOOGLE Source # 

Methods

writeField :: Ptr VkPresentTimeGOOGLE -> FieldType "desiredPresentTime" VkPresentTimeGOOGLE -> IO () Source #

CanWriteField "presentID" VkPresentTimeGOOGLE Source # 
CanReadField "desiredPresentTime" VkPresentTimeGOOGLE Source # 
CanReadField "presentID" VkPresentTimeGOOGLE Source # 
HasField "desiredPresentTime" VkPresentTimeGOOGLE Source # 

Associated Types

type FieldType ("desiredPresentTime" :: Symbol) VkPresentTimeGOOGLE :: Type Source #

type FieldOptional ("desiredPresentTime" :: Symbol) VkPresentTimeGOOGLE :: Bool Source #

type FieldOffset ("desiredPresentTime" :: Symbol) VkPresentTimeGOOGLE :: Nat Source #

type FieldIsArray ("desiredPresentTime" :: Symbol) VkPresentTimeGOOGLE :: Bool Source #

HasField "presentID" VkPresentTimeGOOGLE Source # 

Associated Types

type FieldType ("presentID" :: Symbol) VkPresentTimeGOOGLE :: Type Source #

type FieldOptional ("presentID" :: Symbol) VkPresentTimeGOOGLE :: Bool Source #

type FieldOffset ("presentID" :: Symbol) VkPresentTimeGOOGLE :: Nat Source #

type FieldIsArray ("presentID" :: Symbol) VkPresentTimeGOOGLE :: Bool Source #

type StructFields VkPresentTimeGOOGLE Source # 
type StructFields VkPresentTimeGOOGLE = (:) Symbol "presentID" ((:) Symbol "desiredPresentTime" ([] Symbol))
type CUnionType VkPresentTimeGOOGLE Source # 
type ReturnedOnly VkPresentTimeGOOGLE Source # 
type StructExtends VkPresentTimeGOOGLE Source # 
type FieldType "desiredPresentTime" VkPresentTimeGOOGLE Source # 
type FieldType "desiredPresentTime" VkPresentTimeGOOGLE = Word64
type FieldType "presentID" VkPresentTimeGOOGLE Source # 
type FieldOptional "desiredPresentTime" VkPresentTimeGOOGLE Source # 
type FieldOptional "desiredPresentTime" VkPresentTimeGOOGLE = False
type FieldOptional "presentID" VkPresentTimeGOOGLE Source # 
type FieldOffset "desiredPresentTime" VkPresentTimeGOOGLE Source # 
type FieldOffset "desiredPresentTime" VkPresentTimeGOOGLE = 8
type FieldOffset "presentID" VkPresentTimeGOOGLE Source # 
type FieldOffset "presentID" VkPresentTimeGOOGLE = 0
type FieldIsArray "desiredPresentTime" VkPresentTimeGOOGLE Source # 
type FieldIsArray "desiredPresentTime" VkPresentTimeGOOGLE = False
type FieldIsArray "presentID" VkPresentTimeGOOGLE Source # 

data VkPresentTimesInfoGOOGLE Source #

typedef struct VkPresentTimesInfoGOOGLE {
    VkStructureType sType;
    const void*                      pNext;
    uint32_t                         swapchainCount;
    const VkPresentTimeGOOGLE*   pTimes;
} VkPresentTimesInfoGOOGLE;

VkPresentTimesInfoGOOGLE registry at www.khronos.org

Instances

Eq VkPresentTimesInfoGOOGLE Source # 
Ord VkPresentTimesInfoGOOGLE Source # 
Show VkPresentTimesInfoGOOGLE Source # 
Storable VkPresentTimesInfoGOOGLE Source # 
VulkanMarshalPrim VkPresentTimesInfoGOOGLE Source # 
VulkanMarshal VkPresentTimesInfoGOOGLE Source # 
CanWriteField "pNext" VkPresentTimesInfoGOOGLE Source # 
CanWriteField "pTimes" VkPresentTimesInfoGOOGLE Source # 
CanWriteField "sType" VkPresentTimesInfoGOOGLE Source # 
CanWriteField "swapchainCount" VkPresentTimesInfoGOOGLE Source # 
CanReadField "pNext" VkPresentTimesInfoGOOGLE Source # 
CanReadField "pTimes" VkPresentTimesInfoGOOGLE Source # 
CanReadField "sType" VkPresentTimesInfoGOOGLE Source # 
CanReadField "swapchainCount" VkPresentTimesInfoGOOGLE Source # 
HasField "pNext" VkPresentTimesInfoGOOGLE Source # 
HasField "pTimes" VkPresentTimesInfoGOOGLE Source # 
HasField "sType" VkPresentTimesInfoGOOGLE Source # 
HasField "swapchainCount" VkPresentTimesInfoGOOGLE Source # 

Associated Types

type FieldType ("swapchainCount" :: Symbol) VkPresentTimesInfoGOOGLE :: Type Source #

type FieldOptional ("swapchainCount" :: Symbol) VkPresentTimesInfoGOOGLE :: Bool Source #

type FieldOffset ("swapchainCount" :: Symbol) VkPresentTimesInfoGOOGLE :: Nat Source #

type FieldIsArray ("swapchainCount" :: Symbol) VkPresentTimesInfoGOOGLE :: Bool Source #

type StructFields VkPresentTimesInfoGOOGLE Source # 
type StructFields VkPresentTimesInfoGOOGLE = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "swapchainCount" ((:) Symbol "pTimes" ([] Symbol))))
type CUnionType VkPresentTimesInfoGOOGLE Source # 
type ReturnedOnly VkPresentTimesInfoGOOGLE Source # 
type StructExtends VkPresentTimesInfoGOOGLE Source # 
type FieldType "pNext" VkPresentTimesInfoGOOGLE Source # 
type FieldType "pTimes" VkPresentTimesInfoGOOGLE Source # 
type FieldType "sType" VkPresentTimesInfoGOOGLE Source # 
type FieldType "swapchainCount" VkPresentTimesInfoGOOGLE Source # 
type FieldType "swapchainCount" VkPresentTimesInfoGOOGLE = Word32
type FieldOptional "pNext" VkPresentTimesInfoGOOGLE Source # 
type FieldOptional "pTimes" VkPresentTimesInfoGOOGLE Source # 
type FieldOptional "sType" VkPresentTimesInfoGOOGLE Source # 
type FieldOptional "swapchainCount" VkPresentTimesInfoGOOGLE Source # 
type FieldOffset "pNext" VkPresentTimesInfoGOOGLE Source # 
type FieldOffset "pTimes" VkPresentTimesInfoGOOGLE Source # 
type FieldOffset "sType" VkPresentTimesInfoGOOGLE Source # 
type FieldOffset "swapchainCount" VkPresentTimesInfoGOOGLE Source # 
type FieldOffset "swapchainCount" VkPresentTimesInfoGOOGLE = 16
type FieldIsArray "pNext" VkPresentTimesInfoGOOGLE Source # 
type FieldIsArray "pTimes" VkPresentTimesInfoGOOGLE Source # 
type FieldIsArray "sType" VkPresentTimesInfoGOOGLE Source # 
type FieldIsArray "swapchainCount" VkPresentTimesInfoGOOGLE Source # 

data VkSwapchainCounterCreateInfoEXT Source #

typedef struct VkSwapchainCounterCreateInfoEXT {
    VkStructureType sType;
    const void*                      pNext;
    VkSurfaceCounterFlagsEXT         surfaceCounters;
} VkSwapchainCounterCreateInfoEXT;

VkSwapchainCounterCreateInfoEXT registry at www.khronos.org

Instances

Eq VkSwapchainCounterCreateInfoEXT Source # 
Ord VkSwapchainCounterCreateInfoEXT Source # 
Show VkSwapchainCounterCreateInfoEXT Source # 
Storable VkSwapchainCounterCreateInfoEXT Source # 
VulkanMarshalPrim VkSwapchainCounterCreateInfoEXT Source # 
VulkanMarshal VkSwapchainCounterCreateInfoEXT Source # 
CanWriteField "pNext" VkSwapchainCounterCreateInfoEXT Source # 
CanWriteField "sType" VkSwapchainCounterCreateInfoEXT Source # 
CanWriteField "surfaceCounters" VkSwapchainCounterCreateInfoEXT Source # 
CanReadField "pNext" VkSwapchainCounterCreateInfoEXT Source # 
CanReadField "sType" VkSwapchainCounterCreateInfoEXT Source # 
CanReadField "surfaceCounters" VkSwapchainCounterCreateInfoEXT Source # 
HasField "pNext" VkSwapchainCounterCreateInfoEXT Source # 
HasField "sType" VkSwapchainCounterCreateInfoEXT Source # 
HasField "surfaceCounters" VkSwapchainCounterCreateInfoEXT Source # 
type StructFields VkSwapchainCounterCreateInfoEXT Source # 
type StructFields VkSwapchainCounterCreateInfoEXT = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "surfaceCounters" ([] Symbol)))
type CUnionType VkSwapchainCounterCreateInfoEXT Source # 
type ReturnedOnly VkSwapchainCounterCreateInfoEXT Source # 
type StructExtends VkSwapchainCounterCreateInfoEXT Source # 
type FieldType "pNext" VkSwapchainCounterCreateInfoEXT Source # 
type FieldType "sType" VkSwapchainCounterCreateInfoEXT Source # 
type FieldType "surfaceCounters" VkSwapchainCounterCreateInfoEXT Source # 
type FieldOptional "pNext" VkSwapchainCounterCreateInfoEXT Source # 
type FieldOptional "sType" VkSwapchainCounterCreateInfoEXT Source # 
type FieldOptional "surfaceCounters" VkSwapchainCounterCreateInfoEXT Source # 
type FieldOffset "pNext" VkSwapchainCounterCreateInfoEXT Source # 
type FieldOffset "sType" VkSwapchainCounterCreateInfoEXT Source # 
type FieldOffset "surfaceCounters" VkSwapchainCounterCreateInfoEXT Source # 
type FieldOffset "surfaceCounters" VkSwapchainCounterCreateInfoEXT = 16
type FieldIsArray "pNext" VkSwapchainCounterCreateInfoEXT Source # 
type FieldIsArray "sType" VkSwapchainCounterCreateInfoEXT Source # 
type FieldIsArray "surfaceCounters" VkSwapchainCounterCreateInfoEXT Source # 

data VkSwapchainCreateInfoKHR Source #

typedef struct VkSwapchainCreateInfoKHR {
    VkStructureType sType;
    const void*                      pNext;
    VkSwapchainCreateFlagsKHR        flags;
    VkSurfaceKHR                     surface;
    uint32_t                         minImageCount;
    VkFormat                         imageFormat;
    VkColorSpaceKHR                  imageColorSpace;
    VkExtent2D                       imageExtent;
    uint32_t                         imageArrayLayers;
    VkImageUsageFlags                imageUsage;
    VkSharingMode                    imageSharingMode;
    uint32_t         queueFamilyIndexCount;
    const uint32_t*                  pQueueFamilyIndices;
    VkSurfaceTransformFlagBitsKHR    preTransform;
    VkCompositeAlphaFlagBitsKHR      compositeAlpha;
    VkPresentModeKHR                 presentMode;
    VkBool32                         clipped;
    VkSwapchainKHR   oldSwapchain;
} VkSwapchainCreateInfoKHR;

VkSwapchainCreateInfoKHR registry at www.khronos.org

Instances

Eq VkSwapchainCreateInfoKHR Source # 
Ord VkSwapchainCreateInfoKHR Source # 
Show VkSwapchainCreateInfoKHR Source # 
Storable VkSwapchainCreateInfoKHR Source # 
VulkanMarshalPrim VkSwapchainCreateInfoKHR Source # 
VulkanMarshal VkSwapchainCreateInfoKHR Source # 
CanWriteField "clipped" VkSwapchainCreateInfoKHR Source # 
CanWriteField "compositeAlpha" VkSwapchainCreateInfoKHR Source # 
CanWriteField "flags" VkSwapchainCreateInfoKHR Source # 
CanWriteField "imageArrayLayers" VkSwapchainCreateInfoKHR Source # 
CanWriteField "imageColorSpace" VkSwapchainCreateInfoKHR Source # 
CanWriteField "imageExtent" VkSwapchainCreateInfoKHR Source # 
CanWriteField "imageFormat" VkSwapchainCreateInfoKHR Source # 
CanWriteField "imageSharingMode" VkSwapchainCreateInfoKHR Source # 
CanWriteField "imageUsage" VkSwapchainCreateInfoKHR Source # 
CanWriteField "minImageCount" VkSwapchainCreateInfoKHR Source # 
CanWriteField "oldSwapchain" VkSwapchainCreateInfoKHR Source # 
CanWriteField "pNext" VkSwapchainCreateInfoKHR Source # 
CanWriteField "pQueueFamilyIndices" VkSwapchainCreateInfoKHR Source # 
CanWriteField "preTransform" VkSwapchainCreateInfoKHR Source # 
CanWriteField "presentMode" VkSwapchainCreateInfoKHR Source # 
CanWriteField "queueFamilyIndexCount" VkSwapchainCreateInfoKHR Source # 
CanWriteField "sType" VkSwapchainCreateInfoKHR Source # 
CanWriteField "surface" VkSwapchainCreateInfoKHR Source # 
CanReadField "clipped" VkSwapchainCreateInfoKHR Source # 
CanReadField "compositeAlpha" VkSwapchainCreateInfoKHR Source # 
CanReadField "flags" VkSwapchainCreateInfoKHR Source # 
CanReadField "imageArrayLayers" VkSwapchainCreateInfoKHR Source # 
CanReadField "imageColorSpace" VkSwapchainCreateInfoKHR Source # 
CanReadField "imageExtent" VkSwapchainCreateInfoKHR Source # 
CanReadField "imageFormat" VkSwapchainCreateInfoKHR Source # 
CanReadField "imageSharingMode" VkSwapchainCreateInfoKHR Source # 
CanReadField "imageUsage" VkSwapchainCreateInfoKHR Source # 
CanReadField "minImageCount" VkSwapchainCreateInfoKHR Source # 
CanReadField "oldSwapchain" VkSwapchainCreateInfoKHR Source # 
CanReadField "pNext" VkSwapchainCreateInfoKHR Source # 
CanReadField "pQueueFamilyIndices" VkSwapchainCreateInfoKHR Source # 
CanReadField "preTransform" VkSwapchainCreateInfoKHR Source # 
CanReadField "presentMode" VkSwapchainCreateInfoKHR Source # 
CanReadField "queueFamilyIndexCount" VkSwapchainCreateInfoKHR Source # 
CanReadField "sType" VkSwapchainCreateInfoKHR Source # 
CanReadField "surface" VkSwapchainCreateInfoKHR Source # 
HasField "clipped" VkSwapchainCreateInfoKHR Source # 
HasField "compositeAlpha" VkSwapchainCreateInfoKHR Source # 

Associated Types

type FieldType ("compositeAlpha" :: Symbol) VkSwapchainCreateInfoKHR :: Type Source #

type FieldOptional ("compositeAlpha" :: Symbol) VkSwapchainCreateInfoKHR :: Bool Source #

type FieldOffset ("compositeAlpha" :: Symbol) VkSwapchainCreateInfoKHR :: Nat Source #

type FieldIsArray ("compositeAlpha" :: Symbol) VkSwapchainCreateInfoKHR :: Bool Source #

HasField "flags" VkSwapchainCreateInfoKHR Source # 
HasField "imageArrayLayers" VkSwapchainCreateInfoKHR Source # 

Associated Types

type FieldType ("imageArrayLayers" :: Symbol) VkSwapchainCreateInfoKHR :: Type Source #

type FieldOptional ("imageArrayLayers" :: Symbol) VkSwapchainCreateInfoKHR :: Bool Source #

type FieldOffset ("imageArrayLayers" :: Symbol) VkSwapchainCreateInfoKHR :: Nat Source #

type FieldIsArray ("imageArrayLayers" :: Symbol) VkSwapchainCreateInfoKHR :: Bool Source #

HasField "imageColorSpace" VkSwapchainCreateInfoKHR Source # 

Associated Types

type FieldType ("imageColorSpace" :: Symbol) VkSwapchainCreateInfoKHR :: Type Source #

type FieldOptional ("imageColorSpace" :: Symbol) VkSwapchainCreateInfoKHR :: Bool Source #

type FieldOffset ("imageColorSpace" :: Symbol) VkSwapchainCreateInfoKHR :: Nat Source #

type FieldIsArray ("imageColorSpace" :: Symbol) VkSwapchainCreateInfoKHR :: Bool Source #

HasField "imageExtent" VkSwapchainCreateInfoKHR Source # 
HasField "imageFormat" VkSwapchainCreateInfoKHR Source # 
HasField "imageSharingMode" VkSwapchainCreateInfoKHR Source # 

Associated Types

type FieldType ("imageSharingMode" :: Symbol) VkSwapchainCreateInfoKHR :: Type Source #

type FieldOptional ("imageSharingMode" :: Symbol) VkSwapchainCreateInfoKHR :: Bool Source #

type FieldOffset ("imageSharingMode" :: Symbol) VkSwapchainCreateInfoKHR :: Nat Source #

type FieldIsArray ("imageSharingMode" :: Symbol) VkSwapchainCreateInfoKHR :: Bool Source #

HasField "imageUsage" VkSwapchainCreateInfoKHR Source # 
HasField "minImageCount" VkSwapchainCreateInfoKHR Source # 

Associated Types

type FieldType ("minImageCount" :: Symbol) VkSwapchainCreateInfoKHR :: Type Source #

type FieldOptional ("minImageCount" :: Symbol) VkSwapchainCreateInfoKHR :: Bool Source #

type FieldOffset ("minImageCount" :: Symbol) VkSwapchainCreateInfoKHR :: Nat Source #

type FieldIsArray ("minImageCount" :: Symbol) VkSwapchainCreateInfoKHR :: Bool Source #

HasField "oldSwapchain" VkSwapchainCreateInfoKHR Source # 
HasField "pNext" VkSwapchainCreateInfoKHR Source # 
HasField "pQueueFamilyIndices" VkSwapchainCreateInfoKHR Source # 

Associated Types

type FieldType ("pQueueFamilyIndices" :: Symbol) VkSwapchainCreateInfoKHR :: Type Source #

type FieldOptional ("pQueueFamilyIndices" :: Symbol) VkSwapchainCreateInfoKHR :: Bool Source #

type FieldOffset ("pQueueFamilyIndices" :: Symbol) VkSwapchainCreateInfoKHR :: Nat Source #

type FieldIsArray ("pQueueFamilyIndices" :: Symbol) VkSwapchainCreateInfoKHR :: Bool Source #

HasField "preTransform" VkSwapchainCreateInfoKHR Source # 
HasField "presentMode" VkSwapchainCreateInfoKHR Source # 
HasField "queueFamilyIndexCount" VkSwapchainCreateInfoKHR Source # 

Associated Types

type FieldType ("queueFamilyIndexCount" :: Symbol) VkSwapchainCreateInfoKHR :: Type Source #

type FieldOptional ("queueFamilyIndexCount" :: Symbol) VkSwapchainCreateInfoKHR :: Bool Source #

type FieldOffset ("queueFamilyIndexCount" :: Symbol) VkSwapchainCreateInfoKHR :: Nat Source #

type FieldIsArray ("queueFamilyIndexCount" :: Symbol) VkSwapchainCreateInfoKHR :: Bool Source #

HasField "sType" VkSwapchainCreateInfoKHR Source # 
HasField "surface" VkSwapchainCreateInfoKHR Source # 
type StructFields VkSwapchainCreateInfoKHR Source # 
type StructFields VkSwapchainCreateInfoKHR = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "surface" ((:) Symbol "minImageCount" ((:) Symbol "imageFormat" ((:) Symbol "imageColorSpace" ((:) Symbol "imageExtent" ((:) Symbol "imageArrayLayers" ((:) Symbol "imageUsage" ((:) Symbol "imageSharingMode" ((:) Symbol "queueFamilyIndexCount" ((:) Symbol "pQueueFamilyIndices" ((:) Symbol "preTransform" ((:) Symbol "compositeAlpha" ((:) Symbol "presentMode" ((:) Symbol "clipped" ((:) Symbol "oldSwapchain" ([] Symbol))))))))))))))))))
type CUnionType VkSwapchainCreateInfoKHR Source # 
type ReturnedOnly VkSwapchainCreateInfoKHR Source # 
type StructExtends VkSwapchainCreateInfoKHR Source # 
type FieldType "clipped" VkSwapchainCreateInfoKHR Source # 
type FieldType "compositeAlpha" VkSwapchainCreateInfoKHR Source # 
type FieldType "flags" VkSwapchainCreateInfoKHR Source # 
type FieldType "imageArrayLayers" VkSwapchainCreateInfoKHR Source # 
type FieldType "imageArrayLayers" VkSwapchainCreateInfoKHR = Word32
type FieldType "imageColorSpace" VkSwapchainCreateInfoKHR Source # 
type FieldType "imageExtent" VkSwapchainCreateInfoKHR Source # 
type FieldType "imageFormat" VkSwapchainCreateInfoKHR Source # 
type FieldType "imageSharingMode" VkSwapchainCreateInfoKHR Source # 
type FieldType "imageUsage" VkSwapchainCreateInfoKHR Source # 
type FieldType "minImageCount" VkSwapchainCreateInfoKHR Source # 
type FieldType "oldSwapchain" VkSwapchainCreateInfoKHR Source # 
type FieldType "pNext" VkSwapchainCreateInfoKHR Source # 
type FieldType "pQueueFamilyIndices" VkSwapchainCreateInfoKHR Source # 
type FieldType "pQueueFamilyIndices" VkSwapchainCreateInfoKHR = Ptr Word32
type FieldType "preTransform" VkSwapchainCreateInfoKHR Source # 
type FieldType "presentMode" VkSwapchainCreateInfoKHR Source # 
type FieldType "queueFamilyIndexCount" VkSwapchainCreateInfoKHR Source # 
type FieldType "queueFamilyIndexCount" VkSwapchainCreateInfoKHR = Word32
type FieldType "sType" VkSwapchainCreateInfoKHR Source # 
type FieldType "surface" VkSwapchainCreateInfoKHR Source # 
type FieldOptional "clipped" VkSwapchainCreateInfoKHR Source # 
type FieldOptional "compositeAlpha" VkSwapchainCreateInfoKHR Source # 
type FieldOptional "flags" VkSwapchainCreateInfoKHR Source # 
type FieldOptional "imageArrayLayers" VkSwapchainCreateInfoKHR Source # 
type FieldOptional "imageArrayLayers" VkSwapchainCreateInfoKHR = False
type FieldOptional "imageColorSpace" VkSwapchainCreateInfoKHR Source # 
type FieldOptional "imageExtent" VkSwapchainCreateInfoKHR Source # 
type FieldOptional "imageFormat" VkSwapchainCreateInfoKHR Source # 
type FieldOptional "imageSharingMode" VkSwapchainCreateInfoKHR Source # 
type FieldOptional "imageSharingMode" VkSwapchainCreateInfoKHR = False
type FieldOptional "imageUsage" VkSwapchainCreateInfoKHR Source # 
type FieldOptional "minImageCount" VkSwapchainCreateInfoKHR Source # 
type FieldOptional "oldSwapchain" VkSwapchainCreateInfoKHR Source # 
type FieldOptional "pNext" VkSwapchainCreateInfoKHR Source # 
type FieldOptional "pQueueFamilyIndices" VkSwapchainCreateInfoKHR Source # 
type FieldOptional "pQueueFamilyIndices" VkSwapchainCreateInfoKHR = False
type FieldOptional "preTransform" VkSwapchainCreateInfoKHR Source # 
type FieldOptional "presentMode" VkSwapchainCreateInfoKHR Source # 
type FieldOptional "queueFamilyIndexCount" VkSwapchainCreateInfoKHR Source # 
type FieldOptional "queueFamilyIndexCount" VkSwapchainCreateInfoKHR = True
type FieldOptional "sType" VkSwapchainCreateInfoKHR Source # 
type FieldOptional "surface" VkSwapchainCreateInfoKHR Source # 
type FieldOffset "clipped" VkSwapchainCreateInfoKHR Source # 
type FieldOffset "compositeAlpha" VkSwapchainCreateInfoKHR Source # 
type FieldOffset "compositeAlpha" VkSwapchainCreateInfoKHR = 84
type FieldOffset "flags" VkSwapchainCreateInfoKHR Source # 
type FieldOffset "imageArrayLayers" VkSwapchainCreateInfoKHR Source # 
type FieldOffset "imageArrayLayers" VkSwapchainCreateInfoKHR = 52
type FieldOffset "imageColorSpace" VkSwapchainCreateInfoKHR Source # 
type FieldOffset "imageColorSpace" VkSwapchainCreateInfoKHR = 40
type FieldOffset "imageExtent" VkSwapchainCreateInfoKHR Source # 
type FieldOffset "imageExtent" VkSwapchainCreateInfoKHR = 44
type FieldOffset "imageFormat" VkSwapchainCreateInfoKHR Source # 
type FieldOffset "imageFormat" VkSwapchainCreateInfoKHR = 36
type FieldOffset "imageSharingMode" VkSwapchainCreateInfoKHR Source # 
type FieldOffset "imageSharingMode" VkSwapchainCreateInfoKHR = 60
type FieldOffset "imageUsage" VkSwapchainCreateInfoKHR Source # 
type FieldOffset "imageUsage" VkSwapchainCreateInfoKHR = 56
type FieldOffset "minImageCount" VkSwapchainCreateInfoKHR Source # 
type FieldOffset "minImageCount" VkSwapchainCreateInfoKHR = 32
type FieldOffset "oldSwapchain" VkSwapchainCreateInfoKHR Source # 
type FieldOffset "oldSwapchain" VkSwapchainCreateInfoKHR = 96
type FieldOffset "pNext" VkSwapchainCreateInfoKHR Source # 
type FieldOffset "pQueueFamilyIndices" VkSwapchainCreateInfoKHR Source # 
type FieldOffset "pQueueFamilyIndices" VkSwapchainCreateInfoKHR = 72
type FieldOffset "preTransform" VkSwapchainCreateInfoKHR Source # 
type FieldOffset "preTransform" VkSwapchainCreateInfoKHR = 80
type FieldOffset "presentMode" VkSwapchainCreateInfoKHR Source # 
type FieldOffset "presentMode" VkSwapchainCreateInfoKHR = 88
type FieldOffset "queueFamilyIndexCount" VkSwapchainCreateInfoKHR Source # 
type FieldOffset "queueFamilyIndexCount" VkSwapchainCreateInfoKHR = 64
type FieldOffset "sType" VkSwapchainCreateInfoKHR Source # 
type FieldOffset "surface" VkSwapchainCreateInfoKHR Source # 
type FieldIsArray "clipped" VkSwapchainCreateInfoKHR Source # 
type FieldIsArray "compositeAlpha" VkSwapchainCreateInfoKHR Source # 
type FieldIsArray "flags" VkSwapchainCreateInfoKHR Source # 
type FieldIsArray "imageArrayLayers" VkSwapchainCreateInfoKHR Source # 
type FieldIsArray "imageArrayLayers" VkSwapchainCreateInfoKHR = False
type FieldIsArray "imageColorSpace" VkSwapchainCreateInfoKHR Source # 
type FieldIsArray "imageExtent" VkSwapchainCreateInfoKHR Source # 
type FieldIsArray "imageFormat" VkSwapchainCreateInfoKHR Source # 
type FieldIsArray "imageSharingMode" VkSwapchainCreateInfoKHR Source # 
type FieldIsArray "imageSharingMode" VkSwapchainCreateInfoKHR = False
type FieldIsArray "imageUsage" VkSwapchainCreateInfoKHR Source # 
type FieldIsArray "minImageCount" VkSwapchainCreateInfoKHR Source # 
type FieldIsArray "oldSwapchain" VkSwapchainCreateInfoKHR Source # 
type FieldIsArray "pNext" VkSwapchainCreateInfoKHR Source # 
type FieldIsArray "pQueueFamilyIndices" VkSwapchainCreateInfoKHR Source # 
type FieldIsArray "pQueueFamilyIndices" VkSwapchainCreateInfoKHR = False
type FieldIsArray "preTransform" VkSwapchainCreateInfoKHR Source # 
type FieldIsArray "presentMode" VkSwapchainCreateInfoKHR Source # 
type FieldIsArray "queueFamilyIndexCount" VkSwapchainCreateInfoKHR Source # 
type FieldIsArray "queueFamilyIndexCount" VkSwapchainCreateInfoKHR = False
type FieldIsArray "sType" VkSwapchainCreateInfoKHR Source # 
type FieldIsArray "surface" VkSwapchainCreateInfoKHR Source # 

pattern VK_KHR_SWAPCHAIN_SPEC_VERSION :: forall a. (Num a, Eq a) => a Source #

type VK_KHR_SWAPCHAIN_EXTENSION_NAME = "VK_KHR_swapchain" Source #

Required extensions: VK_KHR_surface.

data VkAcquireNextImageInfoKHR Source #

typedef struct VkAcquireNextImageInfoKHR {
    VkStructureType sType;
    const void*                      pNext;
    VkSwapchainKHR swapchain;
    uint64_t                         timeout;
    VkSemaphore semaphore;
    VkFence fence;
    uint32_t                         deviceMask;
} VkAcquireNextImageInfoKHR;

VkAcquireNextImageInfoKHR registry at www.khronos.org

Instances

Eq VkAcquireNextImageInfoKHR Source # 
Ord VkAcquireNextImageInfoKHR Source # 
Show VkAcquireNextImageInfoKHR Source # 
Storable VkAcquireNextImageInfoKHR Source # 
VulkanMarshalPrim VkAcquireNextImageInfoKHR Source # 
VulkanMarshal VkAcquireNextImageInfoKHR Source # 
CanWriteField "deviceMask" VkAcquireNextImageInfoKHR Source # 
CanWriteField "fence" VkAcquireNextImageInfoKHR Source # 
CanWriteField "pNext" VkAcquireNextImageInfoKHR Source # 
CanWriteField "sType" VkAcquireNextImageInfoKHR Source # 
CanWriteField "semaphore" VkAcquireNextImageInfoKHR Source # 
CanWriteField "swapchain" VkAcquireNextImageInfoKHR Source # 
CanWriteField "timeout" VkAcquireNextImageInfoKHR Source # 
CanReadField "deviceMask" VkAcquireNextImageInfoKHR Source # 
CanReadField "fence" VkAcquireNextImageInfoKHR Source # 
CanReadField "pNext" VkAcquireNextImageInfoKHR Source # 
CanReadField "sType" VkAcquireNextImageInfoKHR Source # 
CanReadField "semaphore" VkAcquireNextImageInfoKHR Source # 
CanReadField "swapchain" VkAcquireNextImageInfoKHR Source # 
CanReadField "timeout" VkAcquireNextImageInfoKHR Source # 
HasField "deviceMask" VkAcquireNextImageInfoKHR Source # 
HasField "fence" VkAcquireNextImageInfoKHR Source # 
HasField "pNext" VkAcquireNextImageInfoKHR Source # 
HasField "sType" VkAcquireNextImageInfoKHR Source # 
HasField "semaphore" VkAcquireNextImageInfoKHR Source # 
HasField "swapchain" VkAcquireNextImageInfoKHR Source # 
HasField "timeout" VkAcquireNextImageInfoKHR Source # 
type StructFields VkAcquireNextImageInfoKHR Source # 
type StructFields VkAcquireNextImageInfoKHR = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "swapchain" ((:) Symbol "timeout" ((:) Symbol "semaphore" ((:) Symbol "fence" ((:) Symbol "deviceMask" ([] Symbol)))))))
type CUnionType VkAcquireNextImageInfoKHR Source # 
type ReturnedOnly VkAcquireNextImageInfoKHR Source # 
type StructExtends VkAcquireNextImageInfoKHR Source # 
type FieldType "deviceMask" VkAcquireNextImageInfoKHR Source # 
type FieldType "fence" VkAcquireNextImageInfoKHR Source # 
type FieldType "pNext" VkAcquireNextImageInfoKHR Source # 
type FieldType "sType" VkAcquireNextImageInfoKHR Source # 
type FieldType "semaphore" VkAcquireNextImageInfoKHR Source # 
type FieldType "swapchain" VkAcquireNextImageInfoKHR Source # 
type FieldType "timeout" VkAcquireNextImageInfoKHR Source # 
type FieldOptional "deviceMask" VkAcquireNextImageInfoKHR Source # 
type FieldOptional "fence" VkAcquireNextImageInfoKHR Source # 
type FieldOptional "pNext" VkAcquireNextImageInfoKHR Source # 
type FieldOptional "sType" VkAcquireNextImageInfoKHR Source # 
type FieldOptional "semaphore" VkAcquireNextImageInfoKHR Source # 
type FieldOptional "swapchain" VkAcquireNextImageInfoKHR Source # 
type FieldOptional "timeout" VkAcquireNextImageInfoKHR Source # 
type FieldOffset "deviceMask" VkAcquireNextImageInfoKHR Source # 
type FieldOffset "deviceMask" VkAcquireNextImageInfoKHR = 48
type FieldOffset "fence" VkAcquireNextImageInfoKHR Source # 
type FieldOffset "pNext" VkAcquireNextImageInfoKHR Source # 
type FieldOffset "sType" VkAcquireNextImageInfoKHR Source # 
type FieldOffset "semaphore" VkAcquireNextImageInfoKHR Source # 
type FieldOffset "swapchain" VkAcquireNextImageInfoKHR Source # 
type FieldOffset "timeout" VkAcquireNextImageInfoKHR Source # 
type FieldIsArray "deviceMask" VkAcquireNextImageInfoKHR Source # 
type FieldIsArray "fence" VkAcquireNextImageInfoKHR Source # 
type FieldIsArray "pNext" VkAcquireNextImageInfoKHR Source # 
type FieldIsArray "sType" VkAcquireNextImageInfoKHR Source # 
type FieldIsArray "semaphore" VkAcquireNextImageInfoKHR Source # 
type FieldIsArray "swapchain" VkAcquireNextImageInfoKHR Source # 
type FieldIsArray "timeout" VkAcquireNextImageInfoKHR Source # 

data VkBindBufferMemoryDeviceGroupInfo Source #

typedef struct VkBindBufferMemoryDeviceGroupInfo {
    VkStructureType sType;
    const void*                      pNext;
    uint32_t         deviceIndexCount;
    const uint32_t*  pDeviceIndices;
} VkBindBufferMemoryDeviceGroupInfo;

VkBindBufferMemoryDeviceGroupInfo registry at www.khronos.org

Instances

Eq VkBindBufferMemoryDeviceGroupInfo Source # 
Ord VkBindBufferMemoryDeviceGroupInfo Source # 
Show VkBindBufferMemoryDeviceGroupInfo Source # 
Storable VkBindBufferMemoryDeviceGroupInfo Source # 
VulkanMarshalPrim VkBindBufferMemoryDeviceGroupInfo Source # 
VulkanMarshal VkBindBufferMemoryDeviceGroupInfo Source # 
CanWriteField "deviceIndexCount" VkBindBufferMemoryDeviceGroupInfo Source # 
CanWriteField "pDeviceIndices" VkBindBufferMemoryDeviceGroupInfo Source # 
CanWriteField "pNext" VkBindBufferMemoryDeviceGroupInfo Source # 
CanWriteField "sType" VkBindBufferMemoryDeviceGroupInfo Source # 
CanReadField "deviceIndexCount" VkBindBufferMemoryDeviceGroupInfo Source # 
CanReadField "pDeviceIndices" VkBindBufferMemoryDeviceGroupInfo Source # 
CanReadField "pNext" VkBindBufferMemoryDeviceGroupInfo Source # 
CanReadField "sType" VkBindBufferMemoryDeviceGroupInfo Source # 
HasField "deviceIndexCount" VkBindBufferMemoryDeviceGroupInfo Source # 
HasField "pDeviceIndices" VkBindBufferMemoryDeviceGroupInfo Source # 
HasField "pNext" VkBindBufferMemoryDeviceGroupInfo Source # 
HasField "sType" VkBindBufferMemoryDeviceGroupInfo Source # 
type StructFields VkBindBufferMemoryDeviceGroupInfo Source # 
type StructFields VkBindBufferMemoryDeviceGroupInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "deviceIndexCount" ((:) Symbol "pDeviceIndices" ([] Symbol))))
type CUnionType VkBindBufferMemoryDeviceGroupInfo Source # 
type ReturnedOnly VkBindBufferMemoryDeviceGroupInfo Source # 
type StructExtends VkBindBufferMemoryDeviceGroupInfo Source # 
type FieldType "deviceIndexCount" VkBindBufferMemoryDeviceGroupInfo Source # 
type FieldType "pDeviceIndices" VkBindBufferMemoryDeviceGroupInfo Source # 
type FieldType "pNext" VkBindBufferMemoryDeviceGroupInfo Source # 
type FieldType "sType" VkBindBufferMemoryDeviceGroupInfo Source # 
type FieldOptional "deviceIndexCount" VkBindBufferMemoryDeviceGroupInfo Source # 
type FieldOptional "pDeviceIndices" VkBindBufferMemoryDeviceGroupInfo Source # 
type FieldOptional "pNext" VkBindBufferMemoryDeviceGroupInfo Source # 
type FieldOptional "sType" VkBindBufferMemoryDeviceGroupInfo Source # 
type FieldOffset "deviceIndexCount" VkBindBufferMemoryDeviceGroupInfo Source # 
type FieldOffset "deviceIndexCount" VkBindBufferMemoryDeviceGroupInfo = 16
type FieldOffset "pDeviceIndices" VkBindBufferMemoryDeviceGroupInfo Source # 
type FieldOffset "pNext" VkBindBufferMemoryDeviceGroupInfo Source # 
type FieldOffset "sType" VkBindBufferMemoryDeviceGroupInfo Source # 
type FieldIsArray "deviceIndexCount" VkBindBufferMemoryDeviceGroupInfo Source # 
type FieldIsArray "pDeviceIndices" VkBindBufferMemoryDeviceGroupInfo Source # 
type FieldIsArray "pNext" VkBindBufferMemoryDeviceGroupInfo Source # 
type FieldIsArray "sType" VkBindBufferMemoryDeviceGroupInfo Source # 

data VkBindBufferMemoryInfo Source #

typedef struct VkBindBufferMemoryInfo {
    VkStructureType sType;
    const void*                      pNext;
    VkBuffer                         buffer;
    VkDeviceMemory                   memory;
    VkDeviceSize                     memoryOffset;
} VkBindBufferMemoryInfo;

VkBindBufferMemoryInfo registry at www.khronos.org

Instances

Eq VkBindBufferMemoryInfo Source # 
Ord VkBindBufferMemoryInfo Source # 
Show VkBindBufferMemoryInfo Source # 
Storable VkBindBufferMemoryInfo Source # 
VulkanMarshalPrim VkBindBufferMemoryInfo Source # 
VulkanMarshal VkBindBufferMemoryInfo Source # 
CanWriteField "buffer" VkBindBufferMemoryInfo Source # 
CanWriteField "memory" VkBindBufferMemoryInfo Source # 
CanWriteField "memoryOffset" VkBindBufferMemoryInfo Source # 
CanWriteField "pNext" VkBindBufferMemoryInfo Source # 
CanWriteField "sType" VkBindBufferMemoryInfo Source # 
CanReadField "buffer" VkBindBufferMemoryInfo Source # 
CanReadField "memory" VkBindBufferMemoryInfo Source # 
CanReadField "memoryOffset" VkBindBufferMemoryInfo Source # 
CanReadField "pNext" VkBindBufferMemoryInfo Source # 
CanReadField "sType" VkBindBufferMemoryInfo Source # 
HasField "buffer" VkBindBufferMemoryInfo Source # 
HasField "memory" VkBindBufferMemoryInfo Source # 
HasField "memoryOffset" VkBindBufferMemoryInfo Source # 

Associated Types

type FieldType ("memoryOffset" :: Symbol) VkBindBufferMemoryInfo :: Type Source #

type FieldOptional ("memoryOffset" :: Symbol) VkBindBufferMemoryInfo :: Bool Source #

type FieldOffset ("memoryOffset" :: Symbol) VkBindBufferMemoryInfo :: Nat Source #

type FieldIsArray ("memoryOffset" :: Symbol) VkBindBufferMemoryInfo :: Bool Source #

HasField "pNext" VkBindBufferMemoryInfo Source # 
HasField "sType" VkBindBufferMemoryInfo Source # 
type StructFields VkBindBufferMemoryInfo Source # 
type StructFields VkBindBufferMemoryInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "buffer" ((:) Symbol "memory" ((:) Symbol "memoryOffset" ([] Symbol)))))
type CUnionType VkBindBufferMemoryInfo Source # 
type ReturnedOnly VkBindBufferMemoryInfo Source # 
type StructExtends VkBindBufferMemoryInfo Source # 
type FieldType "buffer" VkBindBufferMemoryInfo Source # 
type FieldType "memory" VkBindBufferMemoryInfo Source # 
type FieldType "memoryOffset" VkBindBufferMemoryInfo Source # 
type FieldType "pNext" VkBindBufferMemoryInfo Source # 
type FieldType "sType" VkBindBufferMemoryInfo Source # 
type FieldOptional "buffer" VkBindBufferMemoryInfo Source # 
type FieldOptional "memory" VkBindBufferMemoryInfo Source # 
type FieldOptional "memoryOffset" VkBindBufferMemoryInfo Source # 
type FieldOptional "pNext" VkBindBufferMemoryInfo Source # 
type FieldOptional "sType" VkBindBufferMemoryInfo Source # 
type FieldOffset "buffer" VkBindBufferMemoryInfo Source # 
type FieldOffset "memory" VkBindBufferMemoryInfo Source # 
type FieldOffset "memoryOffset" VkBindBufferMemoryInfo Source # 
type FieldOffset "memoryOffset" VkBindBufferMemoryInfo = 32
type FieldOffset "pNext" VkBindBufferMemoryInfo Source # 
type FieldOffset "sType" VkBindBufferMemoryInfo Source # 
type FieldIsArray "buffer" VkBindBufferMemoryInfo Source # 
type FieldIsArray "memory" VkBindBufferMemoryInfo Source # 
type FieldIsArray "memoryOffset" VkBindBufferMemoryInfo Source # 
type FieldIsArray "pNext" VkBindBufferMemoryInfo Source # 
type FieldIsArray "sType" VkBindBufferMemoryInfo Source # 

data VkBindImageMemoryDeviceGroupInfo Source #

typedef struct VkBindImageMemoryDeviceGroupInfo {
    VkStructureType sType;
    const void*                      pNext;
    uint32_t         deviceIndexCount;
    const uint32_t*  pDeviceIndices;
    uint32_t         splitInstanceBindRegionCount;
    const VkRect2D*  pSplitInstanceBindRegions;
} VkBindImageMemoryDeviceGroupInfo;

VkBindImageMemoryDeviceGroupInfo registry at www.khronos.org

Instances

Eq VkBindImageMemoryDeviceGroupInfo Source # 
Ord VkBindImageMemoryDeviceGroupInfo Source # 
Show VkBindImageMemoryDeviceGroupInfo Source # 
Storable VkBindImageMemoryDeviceGroupInfo Source # 
VulkanMarshalPrim VkBindImageMemoryDeviceGroupInfo Source # 
VulkanMarshal VkBindImageMemoryDeviceGroupInfo Source # 
CanWriteField "deviceIndexCount" VkBindImageMemoryDeviceGroupInfo Source # 
CanWriteField "pDeviceIndices" VkBindImageMemoryDeviceGroupInfo Source # 
CanWriteField "pNext" VkBindImageMemoryDeviceGroupInfo Source # 
CanWriteField "pSplitInstanceBindRegions" VkBindImageMemoryDeviceGroupInfo Source # 
CanWriteField "sType" VkBindImageMemoryDeviceGroupInfo Source # 
CanWriteField "splitInstanceBindRegionCount" VkBindImageMemoryDeviceGroupInfo Source # 
CanReadField "deviceIndexCount" VkBindImageMemoryDeviceGroupInfo Source # 
CanReadField "pDeviceIndices" VkBindImageMemoryDeviceGroupInfo Source # 
CanReadField "pNext" VkBindImageMemoryDeviceGroupInfo Source # 
CanReadField "pSplitInstanceBindRegions" VkBindImageMemoryDeviceGroupInfo Source # 
CanReadField "sType" VkBindImageMemoryDeviceGroupInfo Source # 
CanReadField "splitInstanceBindRegionCount" VkBindImageMemoryDeviceGroupInfo Source # 
HasField "deviceIndexCount" VkBindImageMemoryDeviceGroupInfo Source # 
HasField "pDeviceIndices" VkBindImageMemoryDeviceGroupInfo Source # 
HasField "pNext" VkBindImageMemoryDeviceGroupInfo Source # 
HasField "pSplitInstanceBindRegions" VkBindImageMemoryDeviceGroupInfo Source # 

Associated Types

type FieldType ("pSplitInstanceBindRegions" :: Symbol) VkBindImageMemoryDeviceGroupInfo :: Type Source #

type FieldOptional ("pSplitInstanceBindRegions" :: Symbol) VkBindImageMemoryDeviceGroupInfo :: Bool Source #

type FieldOffset ("pSplitInstanceBindRegions" :: Symbol) VkBindImageMemoryDeviceGroupInfo :: Nat Source #

type FieldIsArray ("pSplitInstanceBindRegions" :: Symbol) VkBindImageMemoryDeviceGroupInfo :: Bool Source #

HasField "sType" VkBindImageMemoryDeviceGroupInfo Source # 
HasField "splitInstanceBindRegionCount" VkBindImageMemoryDeviceGroupInfo Source # 

Associated Types

type FieldType ("splitInstanceBindRegionCount" :: Symbol) VkBindImageMemoryDeviceGroupInfo :: Type Source #

type FieldOptional ("splitInstanceBindRegionCount" :: Symbol) VkBindImageMemoryDeviceGroupInfo :: Bool Source #

type FieldOffset ("splitInstanceBindRegionCount" :: Symbol) VkBindImageMemoryDeviceGroupInfo :: Nat Source #

type FieldIsArray ("splitInstanceBindRegionCount" :: Symbol) VkBindImageMemoryDeviceGroupInfo :: Bool Source #

type StructFields VkBindImageMemoryDeviceGroupInfo Source # 
type StructFields VkBindImageMemoryDeviceGroupInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "deviceIndexCount" ((:) Symbol "pDeviceIndices" ((:) Symbol "splitInstanceBindRegionCount" ((:) Symbol "pSplitInstanceBindRegions" ([] Symbol))))))
type CUnionType VkBindImageMemoryDeviceGroupInfo Source # 
type ReturnedOnly VkBindImageMemoryDeviceGroupInfo Source # 
type StructExtends VkBindImageMemoryDeviceGroupInfo Source # 
type FieldType "deviceIndexCount" VkBindImageMemoryDeviceGroupInfo Source # 
type FieldType "pDeviceIndices" VkBindImageMemoryDeviceGroupInfo Source # 
type FieldType "pNext" VkBindImageMemoryDeviceGroupInfo Source # 
type FieldType "pSplitInstanceBindRegions" VkBindImageMemoryDeviceGroupInfo Source # 
type FieldType "pSplitInstanceBindRegions" VkBindImageMemoryDeviceGroupInfo = Ptr VkRect2D
type FieldType "sType" VkBindImageMemoryDeviceGroupInfo Source # 
type FieldType "splitInstanceBindRegionCount" VkBindImageMemoryDeviceGroupInfo Source # 
type FieldType "splitInstanceBindRegionCount" VkBindImageMemoryDeviceGroupInfo = Word32
type FieldOptional "deviceIndexCount" VkBindImageMemoryDeviceGroupInfo Source # 
type FieldOptional "pDeviceIndices" VkBindImageMemoryDeviceGroupInfo Source # 
type FieldOptional "pNext" VkBindImageMemoryDeviceGroupInfo Source # 
type FieldOptional "pSplitInstanceBindRegions" VkBindImageMemoryDeviceGroupInfo Source # 
type FieldOptional "pSplitInstanceBindRegions" VkBindImageMemoryDeviceGroupInfo = False
type FieldOptional "sType" VkBindImageMemoryDeviceGroupInfo Source # 
type FieldOptional "splitInstanceBindRegionCount" VkBindImageMemoryDeviceGroupInfo Source # 
type FieldOptional "splitInstanceBindRegionCount" VkBindImageMemoryDeviceGroupInfo = True
type FieldOffset "deviceIndexCount" VkBindImageMemoryDeviceGroupInfo Source # 
type FieldOffset "deviceIndexCount" VkBindImageMemoryDeviceGroupInfo = 16
type FieldOffset "pDeviceIndices" VkBindImageMemoryDeviceGroupInfo Source # 
type FieldOffset "pNext" VkBindImageMemoryDeviceGroupInfo Source # 
type FieldOffset "pSplitInstanceBindRegions" VkBindImageMemoryDeviceGroupInfo Source # 
type FieldOffset "pSplitInstanceBindRegions" VkBindImageMemoryDeviceGroupInfo = 40
type FieldOffset "sType" VkBindImageMemoryDeviceGroupInfo Source # 
type FieldOffset "splitInstanceBindRegionCount" VkBindImageMemoryDeviceGroupInfo Source # 
type FieldOffset "splitInstanceBindRegionCount" VkBindImageMemoryDeviceGroupInfo = 32
type FieldIsArray "deviceIndexCount" VkBindImageMemoryDeviceGroupInfo Source # 
type FieldIsArray "pDeviceIndices" VkBindImageMemoryDeviceGroupInfo Source # 
type FieldIsArray "pNext" VkBindImageMemoryDeviceGroupInfo Source # 
type FieldIsArray "pSplitInstanceBindRegions" VkBindImageMemoryDeviceGroupInfo Source # 
type FieldIsArray "pSplitInstanceBindRegions" VkBindImageMemoryDeviceGroupInfo = False
type FieldIsArray "sType" VkBindImageMemoryDeviceGroupInfo Source # 
type FieldIsArray "splitInstanceBindRegionCount" VkBindImageMemoryDeviceGroupInfo Source # 
type FieldIsArray "splitInstanceBindRegionCount" VkBindImageMemoryDeviceGroupInfo = False

data VkBindImageMemoryInfo Source #

typedef struct VkBindImageMemoryInfo {
    VkStructureType sType;
    const void*                      pNext;
    VkImage                          image;
    VkDeviceMemory                   memory;
    VkDeviceSize                     memoryOffset;
} VkBindImageMemoryInfo;

VkBindImageMemoryInfo registry at www.khronos.org

Instances

Eq VkBindImageMemoryInfo Source # 
Ord VkBindImageMemoryInfo Source # 
Show VkBindImageMemoryInfo Source # 
Storable VkBindImageMemoryInfo Source # 
VulkanMarshalPrim VkBindImageMemoryInfo Source # 
VulkanMarshal VkBindImageMemoryInfo Source # 
CanWriteField "image" VkBindImageMemoryInfo Source # 
CanWriteField "memory" VkBindImageMemoryInfo Source # 
CanWriteField "memoryOffset" VkBindImageMemoryInfo Source # 
CanWriteField "pNext" VkBindImageMemoryInfo Source # 
CanWriteField "sType" VkBindImageMemoryInfo Source # 
CanReadField "image" VkBindImageMemoryInfo Source # 
CanReadField "memory" VkBindImageMemoryInfo Source # 
CanReadField "memoryOffset" VkBindImageMemoryInfo Source # 
CanReadField "pNext" VkBindImageMemoryInfo Source # 
CanReadField "sType" VkBindImageMemoryInfo Source # 
HasField "image" VkBindImageMemoryInfo Source # 
HasField "memory" VkBindImageMemoryInfo Source # 
HasField "memoryOffset" VkBindImageMemoryInfo Source # 

Associated Types

type FieldType ("memoryOffset" :: Symbol) VkBindImageMemoryInfo :: Type Source #

type FieldOptional ("memoryOffset" :: Symbol) VkBindImageMemoryInfo :: Bool Source #

type FieldOffset ("memoryOffset" :: Symbol) VkBindImageMemoryInfo :: Nat Source #

type FieldIsArray ("memoryOffset" :: Symbol) VkBindImageMemoryInfo :: Bool Source #

HasField "pNext" VkBindImageMemoryInfo Source # 
HasField "sType" VkBindImageMemoryInfo Source # 
type StructFields VkBindImageMemoryInfo Source # 
type StructFields VkBindImageMemoryInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "image" ((:) Symbol "memory" ((:) Symbol "memoryOffset" ([] Symbol)))))
type CUnionType VkBindImageMemoryInfo Source # 
type ReturnedOnly VkBindImageMemoryInfo Source # 
type StructExtends VkBindImageMemoryInfo Source # 
type FieldType "image" VkBindImageMemoryInfo Source # 
type FieldType "memory" VkBindImageMemoryInfo Source # 
type FieldType "memoryOffset" VkBindImageMemoryInfo Source # 
type FieldType "pNext" VkBindImageMemoryInfo Source # 
type FieldType "sType" VkBindImageMemoryInfo Source # 
type FieldOptional "image" VkBindImageMemoryInfo Source # 
type FieldOptional "memory" VkBindImageMemoryInfo Source # 
type FieldOptional "memoryOffset" VkBindImageMemoryInfo Source # 
type FieldOptional "pNext" VkBindImageMemoryInfo Source # 
type FieldOptional "sType" VkBindImageMemoryInfo Source # 
type FieldOffset "image" VkBindImageMemoryInfo Source # 
type FieldOffset "memory" VkBindImageMemoryInfo Source # 
type FieldOffset "memoryOffset" VkBindImageMemoryInfo Source # 
type FieldOffset "memoryOffset" VkBindImageMemoryInfo = 32
type FieldOffset "pNext" VkBindImageMemoryInfo Source # 
type FieldOffset "sType" VkBindImageMemoryInfo Source # 
type FieldIsArray "image" VkBindImageMemoryInfo Source # 
type FieldIsArray "memory" VkBindImageMemoryInfo Source # 
type FieldIsArray "memoryOffset" VkBindImageMemoryInfo Source # 
type FieldIsArray "pNext" VkBindImageMemoryInfo Source # 
type FieldIsArray "sType" VkBindImageMemoryInfo Source # 

data VkBindImageMemorySwapchainInfoKHR Source #

typedef struct VkBindImageMemorySwapchainInfoKHR {
    VkStructureType sType;
    const void*                      pNext;
    VkSwapchainKHR swapchain;
    uint32_t                         imageIndex;
} VkBindImageMemorySwapchainInfoKHR;

VkBindImageMemorySwapchainInfoKHR registry at www.khronos.org

Instances

Eq VkBindImageMemorySwapchainInfoKHR Source # 
Ord VkBindImageMemorySwapchainInfoKHR Source # 
Show VkBindImageMemorySwapchainInfoKHR Source # 
Storable VkBindImageMemorySwapchainInfoKHR Source # 
VulkanMarshalPrim VkBindImageMemorySwapchainInfoKHR Source # 
VulkanMarshal VkBindImageMemorySwapchainInfoKHR Source # 
CanWriteField "imageIndex" VkBindImageMemorySwapchainInfoKHR Source # 
CanWriteField "pNext" VkBindImageMemorySwapchainInfoKHR Source # 
CanWriteField "sType" VkBindImageMemorySwapchainInfoKHR Source # 
CanWriteField "swapchain" VkBindImageMemorySwapchainInfoKHR Source # 
CanReadField "imageIndex" VkBindImageMemorySwapchainInfoKHR Source # 
CanReadField "pNext" VkBindImageMemorySwapchainInfoKHR Source # 
CanReadField "sType" VkBindImageMemorySwapchainInfoKHR Source # 
CanReadField "swapchain" VkBindImageMemorySwapchainInfoKHR Source # 
HasField "imageIndex" VkBindImageMemorySwapchainInfoKHR Source # 
HasField "pNext" VkBindImageMemorySwapchainInfoKHR Source # 
HasField "sType" VkBindImageMemorySwapchainInfoKHR Source # 
HasField "swapchain" VkBindImageMemorySwapchainInfoKHR Source # 
type StructFields VkBindImageMemorySwapchainInfoKHR Source # 
type StructFields VkBindImageMemorySwapchainInfoKHR = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "swapchain" ((:) Symbol "imageIndex" ([] Symbol))))
type CUnionType VkBindImageMemorySwapchainInfoKHR Source # 
type ReturnedOnly VkBindImageMemorySwapchainInfoKHR Source # 
type StructExtends VkBindImageMemorySwapchainInfoKHR Source # 
type FieldType "imageIndex" VkBindImageMemorySwapchainInfoKHR Source # 
type FieldType "pNext" VkBindImageMemorySwapchainInfoKHR Source # 
type FieldType "sType" VkBindImageMemorySwapchainInfoKHR Source # 
type FieldType "swapchain" VkBindImageMemorySwapchainInfoKHR Source # 
type FieldOptional "imageIndex" VkBindImageMemorySwapchainInfoKHR Source # 
type FieldOptional "pNext" VkBindImageMemorySwapchainInfoKHR Source # 
type FieldOptional "sType" VkBindImageMemorySwapchainInfoKHR Source # 
type FieldOptional "swapchain" VkBindImageMemorySwapchainInfoKHR Source # 
type FieldOffset "imageIndex" VkBindImageMemorySwapchainInfoKHR Source # 
type FieldOffset "pNext" VkBindImageMemorySwapchainInfoKHR Source # 
type FieldOffset "sType" VkBindImageMemorySwapchainInfoKHR Source # 
type FieldOffset "swapchain" VkBindImageMemorySwapchainInfoKHR Source # 
type FieldIsArray "imageIndex" VkBindImageMemorySwapchainInfoKHR Source # 
type FieldIsArray "pNext" VkBindImageMemorySwapchainInfoKHR Source # 
type FieldIsArray "sType" VkBindImageMemorySwapchainInfoKHR Source # 
type FieldIsArray "swapchain" VkBindImageMemorySwapchainInfoKHR Source # 

data VkBindImagePlaneMemoryInfo Source #

typedef struct VkBindImagePlaneMemoryInfo {
    VkStructureType sType;
    const void*                      pNext;
    VkImageAspectFlagBits            planeAspect;
} VkBindImagePlaneMemoryInfo;

VkBindImagePlaneMemoryInfo registry at www.khronos.org

Instances

Eq VkBindImagePlaneMemoryInfo Source # 
Ord VkBindImagePlaneMemoryInfo Source # 
Show VkBindImagePlaneMemoryInfo Source # 
Storable VkBindImagePlaneMemoryInfo Source # 
VulkanMarshalPrim VkBindImagePlaneMemoryInfo Source # 
VulkanMarshal VkBindImagePlaneMemoryInfo Source # 
CanWriteField "pNext" VkBindImagePlaneMemoryInfo Source # 
CanWriteField "planeAspect" VkBindImagePlaneMemoryInfo Source # 
CanWriteField "sType" VkBindImagePlaneMemoryInfo Source # 
CanReadField "pNext" VkBindImagePlaneMemoryInfo Source # 
CanReadField "planeAspect" VkBindImagePlaneMemoryInfo Source # 
CanReadField "sType" VkBindImagePlaneMemoryInfo Source # 
HasField "pNext" VkBindImagePlaneMemoryInfo Source # 
HasField "planeAspect" VkBindImagePlaneMemoryInfo Source # 
HasField "sType" VkBindImagePlaneMemoryInfo Source # 
type StructFields VkBindImagePlaneMemoryInfo Source # 
type StructFields VkBindImagePlaneMemoryInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "planeAspect" ([] Symbol)))
type CUnionType VkBindImagePlaneMemoryInfo Source # 
type ReturnedOnly VkBindImagePlaneMemoryInfo Source # 
type StructExtends VkBindImagePlaneMemoryInfo Source # 
type FieldType "pNext" VkBindImagePlaneMemoryInfo Source # 
type FieldType "planeAspect" VkBindImagePlaneMemoryInfo Source # 
type FieldType "sType" VkBindImagePlaneMemoryInfo Source # 
type FieldOptional "pNext" VkBindImagePlaneMemoryInfo Source # 
type FieldOptional "planeAspect" VkBindImagePlaneMemoryInfo Source # 
type FieldOptional "sType" VkBindImagePlaneMemoryInfo Source # 
type FieldOffset "pNext" VkBindImagePlaneMemoryInfo Source # 
type FieldOffset "planeAspect" VkBindImagePlaneMemoryInfo Source # 
type FieldOffset "planeAspect" VkBindImagePlaneMemoryInfo = 16
type FieldOffset "sType" VkBindImagePlaneMemoryInfo Source # 
type FieldIsArray "pNext" VkBindImagePlaneMemoryInfo Source # 
type FieldIsArray "planeAspect" VkBindImagePlaneMemoryInfo Source # 
type FieldIsArray "sType" VkBindImagePlaneMemoryInfo Source # 

data VkBindSparseInfo Source #

typedef struct VkBindSparseInfo {
    VkStructureType sType;
    const void*            pNext;
    uint32_t               waitSemaphoreCount;
    const VkSemaphore*     pWaitSemaphores;
    uint32_t               bufferBindCount;
    const VkSparseBufferMemoryBindInfo* pBufferBinds;
    uint32_t               imageOpaqueBindCount;
    const VkSparseImageOpaqueMemoryBindInfo* pImageOpaqueBinds;
    uint32_t               imageBindCount;
    const VkSparseImageMemoryBindInfo* pImageBinds;
    uint32_t               signalSemaphoreCount;
    const VkSemaphore*     pSignalSemaphores;
} VkBindSparseInfo;

VkBindSparseInfo registry at www.khronos.org

Instances

Eq VkBindSparseInfo Source # 
Ord VkBindSparseInfo Source # 
Show VkBindSparseInfo Source # 
Storable VkBindSparseInfo Source # 
VulkanMarshalPrim VkBindSparseInfo Source # 
VulkanMarshal VkBindSparseInfo Source # 
CanWriteField "bufferBindCount" VkBindSparseInfo Source # 

Methods

writeField :: Ptr VkBindSparseInfo -> FieldType "bufferBindCount" VkBindSparseInfo -> IO () Source #

CanWriteField "imageBindCount" VkBindSparseInfo Source # 

Methods

writeField :: Ptr VkBindSparseInfo -> FieldType "imageBindCount" VkBindSparseInfo -> IO () Source #

CanWriteField "imageOpaqueBindCount" VkBindSparseInfo Source # 

Methods

writeField :: Ptr VkBindSparseInfo -> FieldType "imageOpaqueBindCount" VkBindSparseInfo -> IO () Source #

CanWriteField "pBufferBinds" VkBindSparseInfo Source # 
CanWriteField "pImageBinds" VkBindSparseInfo Source # 
CanWriteField "pImageOpaqueBinds" VkBindSparseInfo Source # 

Methods

writeField :: Ptr VkBindSparseInfo -> FieldType "pImageOpaqueBinds" VkBindSparseInfo -> IO () Source #

CanWriteField "pNext" VkBindSparseInfo Source # 
CanWriteField "pSignalSemaphores" VkBindSparseInfo Source # 

Methods

writeField :: Ptr VkBindSparseInfo -> FieldType "pSignalSemaphores" VkBindSparseInfo -> IO () Source #

CanWriteField "pWaitSemaphores" VkBindSparseInfo Source # 

Methods

writeField :: Ptr VkBindSparseInfo -> FieldType "pWaitSemaphores" VkBindSparseInfo -> IO () Source #

CanWriteField "sType" VkBindSparseInfo Source # 
CanWriteField "signalSemaphoreCount" VkBindSparseInfo Source # 

Methods

writeField :: Ptr VkBindSparseInfo -> FieldType "signalSemaphoreCount" VkBindSparseInfo -> IO () Source #

CanWriteField "waitSemaphoreCount" VkBindSparseInfo Source # 

Methods

writeField :: Ptr VkBindSparseInfo -> FieldType "waitSemaphoreCount" VkBindSparseInfo -> IO () Source #

CanReadField "bufferBindCount" VkBindSparseInfo Source # 
CanReadField "imageBindCount" VkBindSparseInfo Source # 
CanReadField "imageOpaqueBindCount" VkBindSparseInfo Source # 

Methods

getField :: VkBindSparseInfo -> FieldType "imageOpaqueBindCount" VkBindSparseInfo Source #

readField :: Ptr VkBindSparseInfo -> IO (FieldType "imageOpaqueBindCount" VkBindSparseInfo) Source #

CanReadField "pBufferBinds" VkBindSparseInfo Source # 
CanReadField "pImageBinds" VkBindSparseInfo Source # 
CanReadField "pImageOpaqueBinds" VkBindSparseInfo Source # 
CanReadField "pNext" VkBindSparseInfo Source # 
CanReadField "pSignalSemaphores" VkBindSparseInfo Source # 
CanReadField "pWaitSemaphores" VkBindSparseInfo Source # 
CanReadField "sType" VkBindSparseInfo Source # 
CanReadField "signalSemaphoreCount" VkBindSparseInfo Source # 

Methods

getField :: VkBindSparseInfo -> FieldType "signalSemaphoreCount" VkBindSparseInfo Source #

readField :: Ptr VkBindSparseInfo -> IO (FieldType "signalSemaphoreCount" VkBindSparseInfo) Source #

CanReadField "waitSemaphoreCount" VkBindSparseInfo Source # 
HasField "bufferBindCount" VkBindSparseInfo Source # 

Associated Types

type FieldType ("bufferBindCount" :: Symbol) VkBindSparseInfo :: Type Source #

type FieldOptional ("bufferBindCount" :: Symbol) VkBindSparseInfo :: Bool Source #

type FieldOffset ("bufferBindCount" :: Symbol) VkBindSparseInfo :: Nat Source #

type FieldIsArray ("bufferBindCount" :: Symbol) VkBindSparseInfo :: Bool Source #

HasField "imageBindCount" VkBindSparseInfo Source # 

Associated Types

type FieldType ("imageBindCount" :: Symbol) VkBindSparseInfo :: Type Source #

type FieldOptional ("imageBindCount" :: Symbol) VkBindSparseInfo :: Bool Source #

type FieldOffset ("imageBindCount" :: Symbol) VkBindSparseInfo :: Nat Source #

type FieldIsArray ("imageBindCount" :: Symbol) VkBindSparseInfo :: Bool Source #

HasField "imageOpaqueBindCount" VkBindSparseInfo Source # 

Associated Types

type FieldType ("imageOpaqueBindCount" :: Symbol) VkBindSparseInfo :: Type Source #

type FieldOptional ("imageOpaqueBindCount" :: Symbol) VkBindSparseInfo :: Bool Source #

type FieldOffset ("imageOpaqueBindCount" :: Symbol) VkBindSparseInfo :: Nat Source #

type FieldIsArray ("imageOpaqueBindCount" :: Symbol) VkBindSparseInfo :: Bool Source #

HasField "pBufferBinds" VkBindSparseInfo Source # 

Associated Types

type FieldType ("pBufferBinds" :: Symbol) VkBindSparseInfo :: Type Source #

type FieldOptional ("pBufferBinds" :: Symbol) VkBindSparseInfo :: Bool Source #

type FieldOffset ("pBufferBinds" :: Symbol) VkBindSparseInfo :: Nat Source #

type FieldIsArray ("pBufferBinds" :: Symbol) VkBindSparseInfo :: Bool Source #

HasField "pImageBinds" VkBindSparseInfo Source # 

Associated Types

type FieldType ("pImageBinds" :: Symbol) VkBindSparseInfo :: Type Source #

type FieldOptional ("pImageBinds" :: Symbol) VkBindSparseInfo :: Bool Source #

type FieldOffset ("pImageBinds" :: Symbol) VkBindSparseInfo :: Nat Source #

type FieldIsArray ("pImageBinds" :: Symbol) VkBindSparseInfo :: Bool Source #

HasField "pImageOpaqueBinds" VkBindSparseInfo Source # 

Associated Types

type FieldType ("pImageOpaqueBinds" :: Symbol) VkBindSparseInfo :: Type Source #

type FieldOptional ("pImageOpaqueBinds" :: Symbol) VkBindSparseInfo :: Bool Source #

type FieldOffset ("pImageOpaqueBinds" :: Symbol) VkBindSparseInfo :: Nat Source #

type FieldIsArray ("pImageOpaqueBinds" :: Symbol) VkBindSparseInfo :: Bool Source #

HasField "pNext" VkBindSparseInfo Source # 
HasField "pSignalSemaphores" VkBindSparseInfo Source # 

Associated Types

type FieldType ("pSignalSemaphores" :: Symbol) VkBindSparseInfo :: Type Source #

type FieldOptional ("pSignalSemaphores" :: Symbol) VkBindSparseInfo :: Bool Source #

type FieldOffset ("pSignalSemaphores" :: Symbol) VkBindSparseInfo :: Nat Source #

type FieldIsArray ("pSignalSemaphores" :: Symbol) VkBindSparseInfo :: Bool Source #

HasField "pWaitSemaphores" VkBindSparseInfo Source # 

Associated Types

type FieldType ("pWaitSemaphores" :: Symbol) VkBindSparseInfo :: Type Source #

type FieldOptional ("pWaitSemaphores" :: Symbol) VkBindSparseInfo :: Bool Source #

type FieldOffset ("pWaitSemaphores" :: Symbol) VkBindSparseInfo :: Nat Source #

type FieldIsArray ("pWaitSemaphores" :: Symbol) VkBindSparseInfo :: Bool Source #

HasField "sType" VkBindSparseInfo Source # 
HasField "signalSemaphoreCount" VkBindSparseInfo Source # 

Associated Types

type FieldType ("signalSemaphoreCount" :: Symbol) VkBindSparseInfo :: Type Source #

type FieldOptional ("signalSemaphoreCount" :: Symbol) VkBindSparseInfo :: Bool Source #

type FieldOffset ("signalSemaphoreCount" :: Symbol) VkBindSparseInfo :: Nat Source #

type FieldIsArray ("signalSemaphoreCount" :: Symbol) VkBindSparseInfo :: Bool Source #

HasField "waitSemaphoreCount" VkBindSparseInfo Source # 

Associated Types

type FieldType ("waitSemaphoreCount" :: Symbol) VkBindSparseInfo :: Type Source #

type FieldOptional ("waitSemaphoreCount" :: Symbol) VkBindSparseInfo :: Bool Source #

type FieldOffset ("waitSemaphoreCount" :: Symbol) VkBindSparseInfo :: Nat Source #

type FieldIsArray ("waitSemaphoreCount" :: Symbol) VkBindSparseInfo :: Bool Source #

type StructFields VkBindSparseInfo Source # 
type StructFields VkBindSparseInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "waitSemaphoreCount" ((:) Symbol "pWaitSemaphores" ((:) Symbol "bufferBindCount" ((:) Symbol "pBufferBinds" ((:) Symbol "imageOpaqueBindCount" ((:) Symbol "pImageOpaqueBinds" ((:) Symbol "imageBindCount" ((:) Symbol "pImageBinds" ((:) Symbol "signalSemaphoreCount" ((:) Symbol "pSignalSemaphores" ([] Symbol))))))))))))
type CUnionType VkBindSparseInfo Source # 
type ReturnedOnly VkBindSparseInfo Source # 
type StructExtends VkBindSparseInfo Source # 
type FieldType "bufferBindCount" VkBindSparseInfo Source # 
type FieldType "bufferBindCount" VkBindSparseInfo = Word32
type FieldType "imageBindCount" VkBindSparseInfo Source # 
type FieldType "imageBindCount" VkBindSparseInfo = Word32
type FieldType "imageOpaqueBindCount" VkBindSparseInfo Source # 
type FieldType "imageOpaqueBindCount" VkBindSparseInfo = Word32
type FieldType "pBufferBinds" VkBindSparseInfo Source # 
type FieldType "pImageBinds" VkBindSparseInfo Source # 
type FieldType "pImageOpaqueBinds" VkBindSparseInfo Source # 
type FieldType "pNext" VkBindSparseInfo Source # 
type FieldType "pSignalSemaphores" VkBindSparseInfo Source # 
type FieldType "pSignalSemaphores" VkBindSparseInfo = Ptr VkSemaphore
type FieldType "pWaitSemaphores" VkBindSparseInfo Source # 
type FieldType "pWaitSemaphores" VkBindSparseInfo = Ptr VkSemaphore
type FieldType "sType" VkBindSparseInfo Source # 
type FieldType "signalSemaphoreCount" VkBindSparseInfo Source # 
type FieldType "signalSemaphoreCount" VkBindSparseInfo = Word32
type FieldType "waitSemaphoreCount" VkBindSparseInfo Source # 
type FieldType "waitSemaphoreCount" VkBindSparseInfo = Word32
type FieldOptional "bufferBindCount" VkBindSparseInfo Source # 
type FieldOptional "bufferBindCount" VkBindSparseInfo = True
type FieldOptional "imageBindCount" VkBindSparseInfo Source # 
type FieldOptional "imageBindCount" VkBindSparseInfo = True
type FieldOptional "imageOpaqueBindCount" VkBindSparseInfo Source # 
type FieldOptional "imageOpaqueBindCount" VkBindSparseInfo = True
type FieldOptional "pBufferBinds" VkBindSparseInfo Source # 
type FieldOptional "pBufferBinds" VkBindSparseInfo = False
type FieldOptional "pImageBinds" VkBindSparseInfo Source # 
type FieldOptional "pImageBinds" VkBindSparseInfo = False
type FieldOptional "pImageOpaqueBinds" VkBindSparseInfo Source # 
type FieldOptional "pImageOpaqueBinds" VkBindSparseInfo = False
type FieldOptional "pNext" VkBindSparseInfo Source # 
type FieldOptional "pSignalSemaphores" VkBindSparseInfo Source # 
type FieldOptional "pSignalSemaphores" VkBindSparseInfo = False
type FieldOptional "pWaitSemaphores" VkBindSparseInfo Source # 
type FieldOptional "pWaitSemaphores" VkBindSparseInfo = False
type FieldOptional "sType" VkBindSparseInfo Source # 
type FieldOptional "signalSemaphoreCount" VkBindSparseInfo Source # 
type FieldOptional "signalSemaphoreCount" VkBindSparseInfo = True
type FieldOptional "waitSemaphoreCount" VkBindSparseInfo Source # 
type FieldOptional "waitSemaphoreCount" VkBindSparseInfo = True
type FieldOffset "bufferBindCount" VkBindSparseInfo Source # 
type FieldOffset "bufferBindCount" VkBindSparseInfo = 32
type FieldOffset "imageBindCount" VkBindSparseInfo Source # 
type FieldOffset "imageBindCount" VkBindSparseInfo = 64
type FieldOffset "imageOpaqueBindCount" VkBindSparseInfo Source # 
type FieldOffset "imageOpaqueBindCount" VkBindSparseInfo = 48
type FieldOffset "pBufferBinds" VkBindSparseInfo Source # 
type FieldOffset "pBufferBinds" VkBindSparseInfo = 40
type FieldOffset "pImageBinds" VkBindSparseInfo Source # 
type FieldOffset "pImageBinds" VkBindSparseInfo = 72
type FieldOffset "pImageOpaqueBinds" VkBindSparseInfo Source # 
type FieldOffset "pImageOpaqueBinds" VkBindSparseInfo = 56
type FieldOffset "pNext" VkBindSparseInfo Source # 
type FieldOffset "pNext" VkBindSparseInfo = 8
type FieldOffset "pSignalSemaphores" VkBindSparseInfo Source # 
type FieldOffset "pSignalSemaphores" VkBindSparseInfo = 88
type FieldOffset "pWaitSemaphores" VkBindSparseInfo Source # 
type FieldOffset "pWaitSemaphores" VkBindSparseInfo = 24
type FieldOffset "sType" VkBindSparseInfo Source # 
type FieldOffset "sType" VkBindSparseInfo = 0
type FieldOffset "signalSemaphoreCount" VkBindSparseInfo Source # 
type FieldOffset "signalSemaphoreCount" VkBindSparseInfo = 80
type FieldOffset "waitSemaphoreCount" VkBindSparseInfo Source # 
type FieldOffset "waitSemaphoreCount" VkBindSparseInfo = 16
type FieldIsArray "bufferBindCount" VkBindSparseInfo Source # 
type FieldIsArray "bufferBindCount" VkBindSparseInfo = False
type FieldIsArray "imageBindCount" VkBindSparseInfo Source # 
type FieldIsArray "imageBindCount" VkBindSparseInfo = False
type FieldIsArray "imageOpaqueBindCount" VkBindSparseInfo Source # 
type FieldIsArray "imageOpaqueBindCount" VkBindSparseInfo = False
type FieldIsArray "pBufferBinds" VkBindSparseInfo Source # 
type FieldIsArray "pBufferBinds" VkBindSparseInfo = False
type FieldIsArray "pImageBinds" VkBindSparseInfo Source # 
type FieldIsArray "pImageBinds" VkBindSparseInfo = False
type FieldIsArray "pImageOpaqueBinds" VkBindSparseInfo Source # 
type FieldIsArray "pImageOpaqueBinds" VkBindSparseInfo = False
type FieldIsArray "pNext" VkBindSparseInfo Source # 
type FieldIsArray "pSignalSemaphores" VkBindSparseInfo Source # 
type FieldIsArray "pSignalSemaphores" VkBindSparseInfo = False
type FieldIsArray "pWaitSemaphores" VkBindSparseInfo Source # 
type FieldIsArray "pWaitSemaphores" VkBindSparseInfo = False
type FieldIsArray "sType" VkBindSparseInfo Source # 
type FieldIsArray "signalSemaphoreCount" VkBindSparseInfo Source # 
type FieldIsArray "signalSemaphoreCount" VkBindSparseInfo = False
type FieldIsArray "waitSemaphoreCount" VkBindSparseInfo Source # 
type FieldIsArray "waitSemaphoreCount" VkBindSparseInfo = False

data VkDeviceCreateInfo Source #

typedef struct VkDeviceCreateInfo {
    VkStructureType sType;
    const void*     pNext;
    VkDeviceCreateFlags    flags;
    uint32_t        queueCreateInfoCount;
    const VkDeviceQueueCreateInfo* pQueueCreateInfos;
    uint32_t               enabledLayerCount;
    const char* const*      ppEnabledLayerNames;
    uint32_t               enabledExtensionCount;
    const char* const*      ppEnabledExtensionNames;
    const VkPhysicalDeviceFeatures* pEnabledFeatures;
} VkDeviceCreateInfo;

VkDeviceCreateInfo registry at www.khronos.org

Instances

Eq VkDeviceCreateInfo Source # 
Ord VkDeviceCreateInfo Source # 
Show VkDeviceCreateInfo Source # 
Storable VkDeviceCreateInfo Source # 
VulkanMarshalPrim VkDeviceCreateInfo Source # 
VulkanMarshal VkDeviceCreateInfo Source # 
CanWriteField "enabledExtensionCount" VkDeviceCreateInfo Source # 

Methods

writeField :: Ptr VkDeviceCreateInfo -> FieldType "enabledExtensionCount" VkDeviceCreateInfo -> IO () Source #

CanWriteField "enabledLayerCount" VkDeviceCreateInfo Source # 

Methods

writeField :: Ptr VkDeviceCreateInfo -> FieldType "enabledLayerCount" VkDeviceCreateInfo -> IO () Source #

CanWriteField "flags" VkDeviceCreateInfo Source # 
CanWriteField "pEnabledFeatures" VkDeviceCreateInfo Source # 

Methods

writeField :: Ptr VkDeviceCreateInfo -> FieldType "pEnabledFeatures" VkDeviceCreateInfo -> IO () Source #

CanWriteField "pNext" VkDeviceCreateInfo Source # 
CanWriteField "pQueueCreateInfos" VkDeviceCreateInfo Source # 

Methods

writeField :: Ptr VkDeviceCreateInfo -> FieldType "pQueueCreateInfos" VkDeviceCreateInfo -> IO () Source #

CanWriteField "ppEnabledExtensionNames" VkDeviceCreateInfo Source # 

Methods

writeField :: Ptr VkDeviceCreateInfo -> FieldType "ppEnabledExtensionNames" VkDeviceCreateInfo -> IO () Source #

CanWriteField "ppEnabledLayerNames" VkDeviceCreateInfo Source # 

Methods

writeField :: Ptr VkDeviceCreateInfo -> FieldType "ppEnabledLayerNames" VkDeviceCreateInfo -> IO () Source #

CanWriteField "queueCreateInfoCount" VkDeviceCreateInfo Source # 

Methods

writeField :: Ptr VkDeviceCreateInfo -> FieldType "queueCreateInfoCount" VkDeviceCreateInfo -> IO () Source #

CanWriteField "sType" VkDeviceCreateInfo Source # 
CanReadField "enabledExtensionCount" VkDeviceCreateInfo Source # 
CanReadField "enabledLayerCount" VkDeviceCreateInfo Source # 
CanReadField "flags" VkDeviceCreateInfo Source # 
CanReadField "pEnabledFeatures" VkDeviceCreateInfo Source # 
CanReadField "pNext" VkDeviceCreateInfo Source # 
CanReadField "pQueueCreateInfos" VkDeviceCreateInfo Source # 
CanReadField "ppEnabledExtensionNames" VkDeviceCreateInfo Source # 

Methods

getField :: VkDeviceCreateInfo -> FieldType "ppEnabledExtensionNames" VkDeviceCreateInfo Source #

readField :: Ptr VkDeviceCreateInfo -> IO (FieldType "ppEnabledExtensionNames" VkDeviceCreateInfo) Source #

CanReadField "ppEnabledLayerNames" VkDeviceCreateInfo Source # 
CanReadField "queueCreateInfoCount" VkDeviceCreateInfo Source # 
CanReadField "sType" VkDeviceCreateInfo Source # 
HasField "enabledExtensionCount" VkDeviceCreateInfo Source # 

Associated Types

type FieldType ("enabledExtensionCount" :: Symbol) VkDeviceCreateInfo :: Type Source #

type FieldOptional ("enabledExtensionCount" :: Symbol) VkDeviceCreateInfo :: Bool Source #

type FieldOffset ("enabledExtensionCount" :: Symbol) VkDeviceCreateInfo :: Nat Source #

type FieldIsArray ("enabledExtensionCount" :: Symbol) VkDeviceCreateInfo :: Bool Source #

HasField "enabledLayerCount" VkDeviceCreateInfo Source # 

Associated Types

type FieldType ("enabledLayerCount" :: Symbol) VkDeviceCreateInfo :: Type Source #

type FieldOptional ("enabledLayerCount" :: Symbol) VkDeviceCreateInfo :: Bool Source #

type FieldOffset ("enabledLayerCount" :: Symbol) VkDeviceCreateInfo :: Nat Source #

type FieldIsArray ("enabledLayerCount" :: Symbol) VkDeviceCreateInfo :: Bool Source #

HasField "flags" VkDeviceCreateInfo Source # 
HasField "pEnabledFeatures" VkDeviceCreateInfo Source # 

Associated Types

type FieldType ("pEnabledFeatures" :: Symbol) VkDeviceCreateInfo :: Type Source #

type FieldOptional ("pEnabledFeatures" :: Symbol) VkDeviceCreateInfo :: Bool Source #

type FieldOffset ("pEnabledFeatures" :: Symbol) VkDeviceCreateInfo :: Nat Source #

type FieldIsArray ("pEnabledFeatures" :: Symbol) VkDeviceCreateInfo :: Bool Source #

HasField "pNext" VkDeviceCreateInfo Source # 
HasField "pQueueCreateInfos" VkDeviceCreateInfo Source # 

Associated Types

type FieldType ("pQueueCreateInfos" :: Symbol) VkDeviceCreateInfo :: Type Source #

type FieldOptional ("pQueueCreateInfos" :: Symbol) VkDeviceCreateInfo :: Bool Source #

type FieldOffset ("pQueueCreateInfos" :: Symbol) VkDeviceCreateInfo :: Nat Source #

type FieldIsArray ("pQueueCreateInfos" :: Symbol) VkDeviceCreateInfo :: Bool Source #

HasField "ppEnabledExtensionNames" VkDeviceCreateInfo Source # 

Associated Types

type FieldType ("ppEnabledExtensionNames" :: Symbol) VkDeviceCreateInfo :: Type Source #

type FieldOptional ("ppEnabledExtensionNames" :: Symbol) VkDeviceCreateInfo :: Bool Source #

type FieldOffset ("ppEnabledExtensionNames" :: Symbol) VkDeviceCreateInfo :: Nat Source #

type FieldIsArray ("ppEnabledExtensionNames" :: Symbol) VkDeviceCreateInfo :: Bool Source #

HasField "ppEnabledLayerNames" VkDeviceCreateInfo Source # 

Associated Types

type FieldType ("ppEnabledLayerNames" :: Symbol) VkDeviceCreateInfo :: Type Source #

type FieldOptional ("ppEnabledLayerNames" :: Symbol) VkDeviceCreateInfo :: Bool Source #

type FieldOffset ("ppEnabledLayerNames" :: Symbol) VkDeviceCreateInfo :: Nat Source #

type FieldIsArray ("ppEnabledLayerNames" :: Symbol) VkDeviceCreateInfo :: Bool Source #

HasField "queueCreateInfoCount" VkDeviceCreateInfo Source # 

Associated Types

type FieldType ("queueCreateInfoCount" :: Symbol) VkDeviceCreateInfo :: Type Source #

type FieldOptional ("queueCreateInfoCount" :: Symbol) VkDeviceCreateInfo :: Bool Source #

type FieldOffset ("queueCreateInfoCount" :: Symbol) VkDeviceCreateInfo :: Nat Source #

type FieldIsArray ("queueCreateInfoCount" :: Symbol) VkDeviceCreateInfo :: Bool Source #

HasField "sType" VkDeviceCreateInfo Source # 
type StructFields VkDeviceCreateInfo Source # 
type StructFields VkDeviceCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "queueCreateInfoCount" ((:) Symbol "pQueueCreateInfos" ((:) Symbol "enabledLayerCount" ((:) Symbol "ppEnabledLayerNames" ((:) Symbol "enabledExtensionCount" ((:) Symbol "ppEnabledExtensionNames" ((:) Symbol "pEnabledFeatures" ([] Symbol))))))))))
type CUnionType VkDeviceCreateInfo Source # 
type ReturnedOnly VkDeviceCreateInfo Source # 
type StructExtends VkDeviceCreateInfo Source # 
type FieldType "enabledExtensionCount" VkDeviceCreateInfo Source # 
type FieldType "enabledExtensionCount" VkDeviceCreateInfo = Word32
type FieldType "enabledLayerCount" VkDeviceCreateInfo Source # 
type FieldType "enabledLayerCount" VkDeviceCreateInfo = Word32
type FieldType "flags" VkDeviceCreateInfo Source # 
type FieldType "pEnabledFeatures" VkDeviceCreateInfo Source # 
type FieldType "pNext" VkDeviceCreateInfo Source # 
type FieldType "pQueueCreateInfos" VkDeviceCreateInfo Source # 
type FieldType "ppEnabledExtensionNames" VkDeviceCreateInfo Source # 
type FieldType "ppEnabledExtensionNames" VkDeviceCreateInfo = Ptr CString
type FieldType "ppEnabledLayerNames" VkDeviceCreateInfo Source # 
type FieldType "ppEnabledLayerNames" VkDeviceCreateInfo = Ptr CString
type FieldType "queueCreateInfoCount" VkDeviceCreateInfo Source # 
type FieldType "queueCreateInfoCount" VkDeviceCreateInfo = Word32
type FieldType "sType" VkDeviceCreateInfo Source # 
type FieldOptional "enabledExtensionCount" VkDeviceCreateInfo Source # 
type FieldOptional "enabledExtensionCount" VkDeviceCreateInfo = True
type FieldOptional "enabledLayerCount" VkDeviceCreateInfo Source # 
type FieldOptional "enabledLayerCount" VkDeviceCreateInfo = True
type FieldOptional "flags" VkDeviceCreateInfo Source # 
type FieldOptional "pEnabledFeatures" VkDeviceCreateInfo Source # 
type FieldOptional "pEnabledFeatures" VkDeviceCreateInfo = True
type FieldOptional "pNext" VkDeviceCreateInfo Source # 
type FieldOptional "pQueueCreateInfos" VkDeviceCreateInfo Source # 
type FieldOptional "pQueueCreateInfos" VkDeviceCreateInfo = False
type FieldOptional "ppEnabledExtensionNames" VkDeviceCreateInfo Source # 
type FieldOptional "ppEnabledExtensionNames" VkDeviceCreateInfo = False
type FieldOptional "ppEnabledLayerNames" VkDeviceCreateInfo Source # 
type FieldOptional "ppEnabledLayerNames" VkDeviceCreateInfo = False
type FieldOptional "queueCreateInfoCount" VkDeviceCreateInfo Source # 
type FieldOptional "queueCreateInfoCount" VkDeviceCreateInfo = False
type FieldOptional "sType" VkDeviceCreateInfo Source # 
type FieldOffset "enabledExtensionCount" VkDeviceCreateInfo Source # 
type FieldOffset "enabledExtensionCount" VkDeviceCreateInfo = 48
type FieldOffset "enabledLayerCount" VkDeviceCreateInfo Source # 
type FieldOffset "enabledLayerCount" VkDeviceCreateInfo = 32
type FieldOffset "flags" VkDeviceCreateInfo Source # 
type FieldOffset "pEnabledFeatures" VkDeviceCreateInfo Source # 
type FieldOffset "pEnabledFeatures" VkDeviceCreateInfo = 64
type FieldOffset "pNext" VkDeviceCreateInfo Source # 
type FieldOffset "pQueueCreateInfos" VkDeviceCreateInfo Source # 
type FieldOffset "pQueueCreateInfos" VkDeviceCreateInfo = 24
type FieldOffset "ppEnabledExtensionNames" VkDeviceCreateInfo Source # 
type FieldOffset "ppEnabledExtensionNames" VkDeviceCreateInfo = 56
type FieldOffset "ppEnabledLayerNames" VkDeviceCreateInfo Source # 
type FieldOffset "ppEnabledLayerNames" VkDeviceCreateInfo = 40
type FieldOffset "queueCreateInfoCount" VkDeviceCreateInfo Source # 
type FieldOffset "queueCreateInfoCount" VkDeviceCreateInfo = 20
type FieldOffset "sType" VkDeviceCreateInfo Source # 
type FieldIsArray "enabledExtensionCount" VkDeviceCreateInfo Source # 
type FieldIsArray "enabledExtensionCount" VkDeviceCreateInfo = False
type FieldIsArray "enabledLayerCount" VkDeviceCreateInfo Source # 
type FieldIsArray "enabledLayerCount" VkDeviceCreateInfo = False
type FieldIsArray "flags" VkDeviceCreateInfo Source # 
type FieldIsArray "pEnabledFeatures" VkDeviceCreateInfo Source # 
type FieldIsArray "pEnabledFeatures" VkDeviceCreateInfo = False
type FieldIsArray "pNext" VkDeviceCreateInfo Source # 
type FieldIsArray "pQueueCreateInfos" VkDeviceCreateInfo Source # 
type FieldIsArray "pQueueCreateInfos" VkDeviceCreateInfo = False
type FieldIsArray "ppEnabledExtensionNames" VkDeviceCreateInfo Source # 
type FieldIsArray "ppEnabledExtensionNames" VkDeviceCreateInfo = False
type FieldIsArray "ppEnabledLayerNames" VkDeviceCreateInfo Source # 
type FieldIsArray "ppEnabledLayerNames" VkDeviceCreateInfo = False
type FieldIsArray "queueCreateInfoCount" VkDeviceCreateInfo Source # 
type FieldIsArray "queueCreateInfoCount" VkDeviceCreateInfo = False
type FieldIsArray "sType" VkDeviceCreateInfo Source # 

data VkDeviceEventInfoEXT Source #

typedef struct VkDeviceEventInfoEXT {
    VkStructureType sType;
    const void*                      pNext;
    VkDeviceEventTypeEXT             deviceEvent;
} VkDeviceEventInfoEXT;

VkDeviceEventInfoEXT registry at www.khronos.org

Instances

Eq VkDeviceEventInfoEXT Source # 
Ord VkDeviceEventInfoEXT Source # 
Show VkDeviceEventInfoEXT Source # 
Storable VkDeviceEventInfoEXT Source # 
VulkanMarshalPrim VkDeviceEventInfoEXT Source # 
VulkanMarshal VkDeviceEventInfoEXT Source # 
CanWriteField "deviceEvent" VkDeviceEventInfoEXT Source # 
CanWriteField "pNext" VkDeviceEventInfoEXT Source # 
CanWriteField "sType" VkDeviceEventInfoEXT Source # 
CanReadField "deviceEvent" VkDeviceEventInfoEXT Source # 
CanReadField "pNext" VkDeviceEventInfoEXT Source # 
CanReadField "sType" VkDeviceEventInfoEXT Source # 
HasField "deviceEvent" VkDeviceEventInfoEXT Source # 

Associated Types

type FieldType ("deviceEvent" :: Symbol) VkDeviceEventInfoEXT :: Type Source #

type FieldOptional ("deviceEvent" :: Symbol) VkDeviceEventInfoEXT :: Bool Source #

type FieldOffset ("deviceEvent" :: Symbol) VkDeviceEventInfoEXT :: Nat Source #

type FieldIsArray ("deviceEvent" :: Symbol) VkDeviceEventInfoEXT :: Bool Source #

HasField "pNext" VkDeviceEventInfoEXT Source # 
HasField "sType" VkDeviceEventInfoEXT Source # 
type StructFields VkDeviceEventInfoEXT Source # 
type StructFields VkDeviceEventInfoEXT = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "deviceEvent" ([] Symbol)))
type CUnionType VkDeviceEventInfoEXT Source # 
type ReturnedOnly VkDeviceEventInfoEXT Source # 
type StructExtends VkDeviceEventInfoEXT Source # 
type FieldType "deviceEvent" VkDeviceEventInfoEXT Source # 
type FieldType "pNext" VkDeviceEventInfoEXT Source # 
type FieldType "sType" VkDeviceEventInfoEXT Source # 
type FieldOptional "deviceEvent" VkDeviceEventInfoEXT Source # 
type FieldOptional "pNext" VkDeviceEventInfoEXT Source # 
type FieldOptional "sType" VkDeviceEventInfoEXT Source # 
type FieldOffset "deviceEvent" VkDeviceEventInfoEXT Source # 
type FieldOffset "deviceEvent" VkDeviceEventInfoEXT = 16
type FieldOffset "pNext" VkDeviceEventInfoEXT Source # 
type FieldOffset "sType" VkDeviceEventInfoEXT Source # 
type FieldIsArray "deviceEvent" VkDeviceEventInfoEXT Source # 
type FieldIsArray "pNext" VkDeviceEventInfoEXT Source # 
type FieldIsArray "sType" VkDeviceEventInfoEXT Source # 

data VkDeviceGeneratedCommandsFeaturesNVX Source #

typedef struct VkDeviceGeneratedCommandsFeaturesNVX {
    VkStructureType sType;
    const void*                      pNext;
    VkBool32                         computeBindingPointSupport;
} VkDeviceGeneratedCommandsFeaturesNVX;

VkDeviceGeneratedCommandsFeaturesNVX registry at www.khronos.org

Instances

Eq VkDeviceGeneratedCommandsFeaturesNVX Source # 
Ord VkDeviceGeneratedCommandsFeaturesNVX Source # 
Show VkDeviceGeneratedCommandsFeaturesNVX Source # 
Storable VkDeviceGeneratedCommandsFeaturesNVX Source # 
VulkanMarshalPrim VkDeviceGeneratedCommandsFeaturesNVX Source # 
VulkanMarshal VkDeviceGeneratedCommandsFeaturesNVX Source # 
CanWriteField "computeBindingPointSupport" VkDeviceGeneratedCommandsFeaturesNVX Source # 
CanWriteField "pNext" VkDeviceGeneratedCommandsFeaturesNVX Source # 
CanWriteField "sType" VkDeviceGeneratedCommandsFeaturesNVX Source # 
CanReadField "computeBindingPointSupport" VkDeviceGeneratedCommandsFeaturesNVX Source # 
CanReadField "pNext" VkDeviceGeneratedCommandsFeaturesNVX Source # 
CanReadField "sType" VkDeviceGeneratedCommandsFeaturesNVX Source # 
HasField "computeBindingPointSupport" VkDeviceGeneratedCommandsFeaturesNVX Source # 

Associated Types

type FieldType ("computeBindingPointSupport" :: Symbol) VkDeviceGeneratedCommandsFeaturesNVX :: Type Source #

type FieldOptional ("computeBindingPointSupport" :: Symbol) VkDeviceGeneratedCommandsFeaturesNVX :: Bool Source #

type FieldOffset ("computeBindingPointSupport" :: Symbol) VkDeviceGeneratedCommandsFeaturesNVX :: Nat Source #

type FieldIsArray ("computeBindingPointSupport" :: Symbol) VkDeviceGeneratedCommandsFeaturesNVX :: Bool Source #

HasField "pNext" VkDeviceGeneratedCommandsFeaturesNVX Source # 
HasField "sType" VkDeviceGeneratedCommandsFeaturesNVX Source # 
type StructFields VkDeviceGeneratedCommandsFeaturesNVX Source # 
type StructFields VkDeviceGeneratedCommandsFeaturesNVX = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "computeBindingPointSupport" ([] Symbol)))
type CUnionType VkDeviceGeneratedCommandsFeaturesNVX Source # 
type ReturnedOnly VkDeviceGeneratedCommandsFeaturesNVX Source # 
type StructExtends VkDeviceGeneratedCommandsFeaturesNVX Source # 
type FieldType "computeBindingPointSupport" VkDeviceGeneratedCommandsFeaturesNVX Source # 
type FieldType "computeBindingPointSupport" VkDeviceGeneratedCommandsFeaturesNVX = VkBool32
type FieldType "pNext" VkDeviceGeneratedCommandsFeaturesNVX Source # 
type FieldType "sType" VkDeviceGeneratedCommandsFeaturesNVX Source # 
type FieldOptional "computeBindingPointSupport" VkDeviceGeneratedCommandsFeaturesNVX Source # 
type FieldOptional "computeBindingPointSupport" VkDeviceGeneratedCommandsFeaturesNVX = False
type FieldOptional "pNext" VkDeviceGeneratedCommandsFeaturesNVX Source # 
type FieldOptional "sType" VkDeviceGeneratedCommandsFeaturesNVX Source # 
type FieldOffset "computeBindingPointSupport" VkDeviceGeneratedCommandsFeaturesNVX Source # 
type FieldOffset "computeBindingPointSupport" VkDeviceGeneratedCommandsFeaturesNVX = 16
type FieldOffset "pNext" VkDeviceGeneratedCommandsFeaturesNVX Source # 
type FieldOffset "sType" VkDeviceGeneratedCommandsFeaturesNVX Source # 
type FieldIsArray "computeBindingPointSupport" VkDeviceGeneratedCommandsFeaturesNVX Source # 
type FieldIsArray "computeBindingPointSupport" VkDeviceGeneratedCommandsFeaturesNVX = False
type FieldIsArray "pNext" VkDeviceGeneratedCommandsFeaturesNVX Source # 
type FieldIsArray "sType" VkDeviceGeneratedCommandsFeaturesNVX Source # 

data VkDeviceGeneratedCommandsLimitsNVX Source #

typedef struct VkDeviceGeneratedCommandsLimitsNVX {
    VkStructureType sType;
    const void*                      pNext;
    uint32_t                         maxIndirectCommandsLayoutTokenCount;
    uint32_t                         maxObjectEntryCounts;
    uint32_t                         minSequenceCountBufferOffsetAlignment;
    uint32_t                         minSequenceIndexBufferOffsetAlignment;
    uint32_t                         minCommandsTokenBufferOffsetAlignment;
} VkDeviceGeneratedCommandsLimitsNVX;

VkDeviceGeneratedCommandsLimitsNVX registry at www.khronos.org

Instances

Eq VkDeviceGeneratedCommandsLimitsNVX Source # 
Ord VkDeviceGeneratedCommandsLimitsNVX Source # 
Show VkDeviceGeneratedCommandsLimitsNVX Source # 
Storable VkDeviceGeneratedCommandsLimitsNVX Source # 
VulkanMarshalPrim VkDeviceGeneratedCommandsLimitsNVX Source # 
VulkanMarshal VkDeviceGeneratedCommandsLimitsNVX Source # 
CanWriteField "maxIndirectCommandsLayoutTokenCount" VkDeviceGeneratedCommandsLimitsNVX Source # 
CanWriteField "maxObjectEntryCounts" VkDeviceGeneratedCommandsLimitsNVX Source # 
CanWriteField "minCommandsTokenBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 

Methods

writeField :: Ptr VkDeviceGeneratedCommandsLimitsNVX -> FieldType "minCommandsTokenBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX -> IO () Source #

CanWriteField "minSequenceCountBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 

Methods

writeField :: Ptr VkDeviceGeneratedCommandsLimitsNVX -> FieldType "minSequenceCountBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX -> IO () Source #

CanWriteField "minSequenceIndexBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 

Methods

writeField :: Ptr VkDeviceGeneratedCommandsLimitsNVX -> FieldType "minSequenceIndexBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX -> IO () Source #

CanWriteField "pNext" VkDeviceGeneratedCommandsLimitsNVX Source # 
CanWriteField "sType" VkDeviceGeneratedCommandsLimitsNVX Source # 
CanReadField "maxIndirectCommandsLayoutTokenCount" VkDeviceGeneratedCommandsLimitsNVX Source # 
CanReadField "maxObjectEntryCounts" VkDeviceGeneratedCommandsLimitsNVX Source # 
CanReadField "minCommandsTokenBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 
CanReadField "minSequenceCountBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 
CanReadField "minSequenceIndexBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 
CanReadField "pNext" VkDeviceGeneratedCommandsLimitsNVX Source # 
CanReadField "sType" VkDeviceGeneratedCommandsLimitsNVX Source # 
HasField "maxIndirectCommandsLayoutTokenCount" VkDeviceGeneratedCommandsLimitsNVX Source # 

Associated Types

type FieldType ("maxIndirectCommandsLayoutTokenCount" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Type Source #

type FieldOptional ("maxIndirectCommandsLayoutTokenCount" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Bool Source #

type FieldOffset ("maxIndirectCommandsLayoutTokenCount" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Nat Source #

type FieldIsArray ("maxIndirectCommandsLayoutTokenCount" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Bool Source #

HasField "maxObjectEntryCounts" VkDeviceGeneratedCommandsLimitsNVX Source # 

Associated Types

type FieldType ("maxObjectEntryCounts" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Type Source #

type FieldOptional ("maxObjectEntryCounts" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Bool Source #

type FieldOffset ("maxObjectEntryCounts" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Nat Source #

type FieldIsArray ("maxObjectEntryCounts" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Bool Source #

HasField "minCommandsTokenBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 

Associated Types

type FieldType ("minCommandsTokenBufferOffsetAlignment" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Type Source #

type FieldOptional ("minCommandsTokenBufferOffsetAlignment" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Bool Source #

type FieldOffset ("minCommandsTokenBufferOffsetAlignment" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Nat Source #

type FieldIsArray ("minCommandsTokenBufferOffsetAlignment" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Bool Source #

HasField "minSequenceCountBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 

Associated Types

type FieldType ("minSequenceCountBufferOffsetAlignment" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Type Source #

type FieldOptional ("minSequenceCountBufferOffsetAlignment" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Bool Source #

type FieldOffset ("minSequenceCountBufferOffsetAlignment" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Nat Source #

type FieldIsArray ("minSequenceCountBufferOffsetAlignment" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Bool Source #

HasField "minSequenceIndexBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 

Associated Types

type FieldType ("minSequenceIndexBufferOffsetAlignment" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Type Source #

type FieldOptional ("minSequenceIndexBufferOffsetAlignment" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Bool Source #

type FieldOffset ("minSequenceIndexBufferOffsetAlignment" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Nat Source #

type FieldIsArray ("minSequenceIndexBufferOffsetAlignment" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Bool Source #

HasField "pNext" VkDeviceGeneratedCommandsLimitsNVX Source # 
HasField "sType" VkDeviceGeneratedCommandsLimitsNVX Source # 
type StructFields VkDeviceGeneratedCommandsLimitsNVX Source # 
type StructFields VkDeviceGeneratedCommandsLimitsNVX = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "maxIndirectCommandsLayoutTokenCount" ((:) Symbol "maxObjectEntryCounts" ((:) Symbol "minSequenceCountBufferOffsetAlignment" ((:) Symbol "minSequenceIndexBufferOffsetAlignment" ((:) Symbol "minCommandsTokenBufferOffsetAlignment" ([] Symbol)))))))
type CUnionType VkDeviceGeneratedCommandsLimitsNVX Source # 
type ReturnedOnly VkDeviceGeneratedCommandsLimitsNVX Source # 
type StructExtends VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldType "maxIndirectCommandsLayoutTokenCount" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldType "maxIndirectCommandsLayoutTokenCount" VkDeviceGeneratedCommandsLimitsNVX = Word32
type FieldType "maxObjectEntryCounts" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldType "minCommandsTokenBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldType "minCommandsTokenBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX = Word32
type FieldType "minSequenceCountBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldType "minSequenceCountBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX = Word32
type FieldType "minSequenceIndexBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldType "minSequenceIndexBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX = Word32
type FieldType "pNext" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldType "sType" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldOptional "maxIndirectCommandsLayoutTokenCount" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldOptional "maxIndirectCommandsLayoutTokenCount" VkDeviceGeneratedCommandsLimitsNVX = False
type FieldOptional "maxObjectEntryCounts" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldOptional "minCommandsTokenBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldOptional "minCommandsTokenBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX = False
type FieldOptional "minSequenceCountBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldOptional "minSequenceCountBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX = False
type FieldOptional "minSequenceIndexBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldOptional "minSequenceIndexBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX = False
type FieldOptional "pNext" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldOptional "sType" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldOffset "maxIndirectCommandsLayoutTokenCount" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldOffset "maxIndirectCommandsLayoutTokenCount" VkDeviceGeneratedCommandsLimitsNVX = 16
type FieldOffset "maxObjectEntryCounts" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldOffset "maxObjectEntryCounts" VkDeviceGeneratedCommandsLimitsNVX = 20
type FieldOffset "minCommandsTokenBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldOffset "minCommandsTokenBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX = 32
type FieldOffset "minSequenceCountBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldOffset "minSequenceCountBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX = 24
type FieldOffset "minSequenceIndexBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldOffset "minSequenceIndexBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX = 28
type FieldOffset "pNext" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldOffset "sType" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldIsArray "maxIndirectCommandsLayoutTokenCount" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldIsArray "maxIndirectCommandsLayoutTokenCount" VkDeviceGeneratedCommandsLimitsNVX = False
type FieldIsArray "maxObjectEntryCounts" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldIsArray "minCommandsTokenBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldIsArray "minCommandsTokenBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX = False
type FieldIsArray "minSequenceCountBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldIsArray "minSequenceCountBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX = False
type FieldIsArray "minSequenceIndexBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldIsArray "minSequenceIndexBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX = False
type FieldIsArray "pNext" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldIsArray "sType" VkDeviceGeneratedCommandsLimitsNVX Source # 

data VkDeviceGroupBindSparseInfo Source #

typedef struct VkDeviceGroupBindSparseInfo {
    VkStructureType sType;
    const void*                      pNext;
    uint32_t                         resourceDeviceIndex;
    uint32_t                         memoryDeviceIndex;
} VkDeviceGroupBindSparseInfo;

VkDeviceGroupBindSparseInfo registry at www.khronos.org

Instances

Eq VkDeviceGroupBindSparseInfo Source # 
Ord VkDeviceGroupBindSparseInfo Source # 
Show VkDeviceGroupBindSparseInfo Source # 
Storable VkDeviceGroupBindSparseInfo Source # 
VulkanMarshalPrim VkDeviceGroupBindSparseInfo Source # 
VulkanMarshal VkDeviceGroupBindSparseInfo Source # 
CanWriteField "memoryDeviceIndex" VkDeviceGroupBindSparseInfo Source # 
CanWriteField "pNext" VkDeviceGroupBindSparseInfo Source # 
CanWriteField "resourceDeviceIndex" VkDeviceGroupBindSparseInfo Source # 
CanWriteField "sType" VkDeviceGroupBindSparseInfo Source # 
CanReadField "memoryDeviceIndex" VkDeviceGroupBindSparseInfo Source # 
CanReadField "pNext" VkDeviceGroupBindSparseInfo Source # 
CanReadField "resourceDeviceIndex" VkDeviceGroupBindSparseInfo Source # 
CanReadField "sType" VkDeviceGroupBindSparseInfo Source # 
HasField "memoryDeviceIndex" VkDeviceGroupBindSparseInfo Source # 

Associated Types

type FieldType ("memoryDeviceIndex" :: Symbol) VkDeviceGroupBindSparseInfo :: Type Source #

type FieldOptional ("memoryDeviceIndex" :: Symbol) VkDeviceGroupBindSparseInfo :: Bool Source #

type FieldOffset ("memoryDeviceIndex" :: Symbol) VkDeviceGroupBindSparseInfo :: Nat Source #

type FieldIsArray ("memoryDeviceIndex" :: Symbol) VkDeviceGroupBindSparseInfo :: Bool Source #

HasField "pNext" VkDeviceGroupBindSparseInfo Source # 
HasField "resourceDeviceIndex" VkDeviceGroupBindSparseInfo Source # 

Associated Types

type FieldType ("resourceDeviceIndex" :: Symbol) VkDeviceGroupBindSparseInfo :: Type Source #

type FieldOptional ("resourceDeviceIndex" :: Symbol) VkDeviceGroupBindSparseInfo :: Bool Source #

type FieldOffset ("resourceDeviceIndex" :: Symbol) VkDeviceGroupBindSparseInfo :: Nat Source #

type FieldIsArray ("resourceDeviceIndex" :: Symbol) VkDeviceGroupBindSparseInfo :: Bool Source #

HasField "sType" VkDeviceGroupBindSparseInfo Source # 
type StructFields VkDeviceGroupBindSparseInfo Source # 
type StructFields VkDeviceGroupBindSparseInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "resourceDeviceIndex" ((:) Symbol "memoryDeviceIndex" ([] Symbol))))
type CUnionType VkDeviceGroupBindSparseInfo Source # 
type ReturnedOnly VkDeviceGroupBindSparseInfo Source # 
type StructExtends VkDeviceGroupBindSparseInfo Source # 
type FieldType "memoryDeviceIndex" VkDeviceGroupBindSparseInfo Source # 
type FieldType "memoryDeviceIndex" VkDeviceGroupBindSparseInfo = Word32
type FieldType "pNext" VkDeviceGroupBindSparseInfo Source # 
type FieldType "resourceDeviceIndex" VkDeviceGroupBindSparseInfo Source # 
type FieldType "resourceDeviceIndex" VkDeviceGroupBindSparseInfo = Word32
type FieldType "sType" VkDeviceGroupBindSparseInfo Source # 
type FieldOptional "memoryDeviceIndex" VkDeviceGroupBindSparseInfo Source # 
type FieldOptional "pNext" VkDeviceGroupBindSparseInfo Source # 
type FieldOptional "resourceDeviceIndex" VkDeviceGroupBindSparseInfo Source # 
type FieldOptional "resourceDeviceIndex" VkDeviceGroupBindSparseInfo = False
type FieldOptional "sType" VkDeviceGroupBindSparseInfo Source # 
type FieldOffset "memoryDeviceIndex" VkDeviceGroupBindSparseInfo Source # 
type FieldOffset "memoryDeviceIndex" VkDeviceGroupBindSparseInfo = 20
type FieldOffset "pNext" VkDeviceGroupBindSparseInfo Source # 
type FieldOffset "resourceDeviceIndex" VkDeviceGroupBindSparseInfo Source # 
type FieldOffset "resourceDeviceIndex" VkDeviceGroupBindSparseInfo = 16
type FieldOffset "sType" VkDeviceGroupBindSparseInfo Source # 
type FieldIsArray "memoryDeviceIndex" VkDeviceGroupBindSparseInfo Source # 
type FieldIsArray "pNext" VkDeviceGroupBindSparseInfo Source # 
type FieldIsArray "resourceDeviceIndex" VkDeviceGroupBindSparseInfo Source # 
type FieldIsArray "resourceDeviceIndex" VkDeviceGroupBindSparseInfo = False
type FieldIsArray "sType" VkDeviceGroupBindSparseInfo Source # 

data VkDeviceGroupCommandBufferBeginInfo Source #

typedef struct VkDeviceGroupCommandBufferBeginInfo {
    VkStructureType sType;
    const void*                      pNext;
    uint32_t                         deviceMask;
} VkDeviceGroupCommandBufferBeginInfo;

VkDeviceGroupCommandBufferBeginInfo registry at www.khronos.org

Instances

Eq VkDeviceGroupCommandBufferBeginInfo Source # 
Ord VkDeviceGroupCommandBufferBeginInfo Source # 
Show VkDeviceGroupCommandBufferBeginInfo Source # 
Storable VkDeviceGroupCommandBufferBeginInfo Source # 
VulkanMarshalPrim VkDeviceGroupCommandBufferBeginInfo Source # 
VulkanMarshal VkDeviceGroupCommandBufferBeginInfo Source # 
CanWriteField "deviceMask" VkDeviceGroupCommandBufferBeginInfo Source # 
CanWriteField "pNext" VkDeviceGroupCommandBufferBeginInfo Source # 
CanWriteField "sType" VkDeviceGroupCommandBufferBeginInfo Source # 
CanReadField "deviceMask" VkDeviceGroupCommandBufferBeginInfo Source # 
CanReadField "pNext" VkDeviceGroupCommandBufferBeginInfo Source # 
CanReadField "sType" VkDeviceGroupCommandBufferBeginInfo Source # 
HasField "deviceMask" VkDeviceGroupCommandBufferBeginInfo Source # 
HasField "pNext" VkDeviceGroupCommandBufferBeginInfo Source # 
HasField "sType" VkDeviceGroupCommandBufferBeginInfo Source # 
type StructFields VkDeviceGroupCommandBufferBeginInfo Source # 
type StructFields VkDeviceGroupCommandBufferBeginInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "deviceMask" ([] Symbol)))
type CUnionType VkDeviceGroupCommandBufferBeginInfo Source # 
type ReturnedOnly VkDeviceGroupCommandBufferBeginInfo Source # 
type StructExtends VkDeviceGroupCommandBufferBeginInfo Source # 
type FieldType "deviceMask" VkDeviceGroupCommandBufferBeginInfo Source # 
type FieldType "pNext" VkDeviceGroupCommandBufferBeginInfo Source # 
type FieldType "sType" VkDeviceGroupCommandBufferBeginInfo Source # 
type FieldOptional "deviceMask" VkDeviceGroupCommandBufferBeginInfo Source # 
type FieldOptional "pNext" VkDeviceGroupCommandBufferBeginInfo Source # 
type FieldOptional "sType" VkDeviceGroupCommandBufferBeginInfo Source # 
type FieldOffset "deviceMask" VkDeviceGroupCommandBufferBeginInfo Source # 
type FieldOffset "pNext" VkDeviceGroupCommandBufferBeginInfo Source # 
type FieldOffset "sType" VkDeviceGroupCommandBufferBeginInfo Source # 
type FieldIsArray "deviceMask" VkDeviceGroupCommandBufferBeginInfo Source # 
type FieldIsArray "pNext" VkDeviceGroupCommandBufferBeginInfo Source # 
type FieldIsArray "sType" VkDeviceGroupCommandBufferBeginInfo Source # 

data VkDeviceGroupDeviceCreateInfo Source #

typedef struct VkDeviceGroupDeviceCreateInfo {
    VkStructureType sType;
    const void*                      pNext;
    uint32_t                         physicalDeviceCount;
    const VkPhysicalDevice*  pPhysicalDevices;
} VkDeviceGroupDeviceCreateInfo;

VkDeviceGroupDeviceCreateInfo registry at www.khronos.org

Instances

Eq VkDeviceGroupDeviceCreateInfo Source # 
Ord VkDeviceGroupDeviceCreateInfo Source # 
Show VkDeviceGroupDeviceCreateInfo Source # 
Storable VkDeviceGroupDeviceCreateInfo Source # 
VulkanMarshalPrim VkDeviceGroupDeviceCreateInfo Source # 
VulkanMarshal VkDeviceGroupDeviceCreateInfo Source # 
CanWriteField "pNext" VkDeviceGroupDeviceCreateInfo Source # 
CanWriteField "pPhysicalDevices" VkDeviceGroupDeviceCreateInfo Source # 
CanWriteField "physicalDeviceCount" VkDeviceGroupDeviceCreateInfo Source # 
CanWriteField "sType" VkDeviceGroupDeviceCreateInfo Source # 
CanReadField "pNext" VkDeviceGroupDeviceCreateInfo Source # 
CanReadField "pPhysicalDevices" VkDeviceGroupDeviceCreateInfo Source # 
CanReadField "physicalDeviceCount" VkDeviceGroupDeviceCreateInfo Source # 
CanReadField "sType" VkDeviceGroupDeviceCreateInfo Source # 
HasField "pNext" VkDeviceGroupDeviceCreateInfo Source # 
HasField "pPhysicalDevices" VkDeviceGroupDeviceCreateInfo Source # 

Associated Types

type FieldType ("pPhysicalDevices" :: Symbol) VkDeviceGroupDeviceCreateInfo :: Type Source #

type FieldOptional ("pPhysicalDevices" :: Symbol) VkDeviceGroupDeviceCreateInfo :: Bool Source #

type FieldOffset ("pPhysicalDevices" :: Symbol) VkDeviceGroupDeviceCreateInfo :: Nat Source #

type FieldIsArray ("pPhysicalDevices" :: Symbol) VkDeviceGroupDeviceCreateInfo :: Bool Source #

HasField "physicalDeviceCount" VkDeviceGroupDeviceCreateInfo Source # 

Associated Types

type FieldType ("physicalDeviceCount" :: Symbol) VkDeviceGroupDeviceCreateInfo :: Type Source #

type FieldOptional ("physicalDeviceCount" :: Symbol) VkDeviceGroupDeviceCreateInfo :: Bool Source #

type FieldOffset ("physicalDeviceCount" :: Symbol) VkDeviceGroupDeviceCreateInfo :: Nat Source #

type FieldIsArray ("physicalDeviceCount" :: Symbol) VkDeviceGroupDeviceCreateInfo :: Bool Source #

HasField "sType" VkDeviceGroupDeviceCreateInfo Source # 
type StructFields VkDeviceGroupDeviceCreateInfo Source # 
type StructFields VkDeviceGroupDeviceCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "physicalDeviceCount" ((:) Symbol "pPhysicalDevices" ([] Symbol))))
type CUnionType VkDeviceGroupDeviceCreateInfo Source # 
type ReturnedOnly VkDeviceGroupDeviceCreateInfo Source # 
type StructExtends VkDeviceGroupDeviceCreateInfo Source # 
type FieldType "pNext" VkDeviceGroupDeviceCreateInfo Source # 
type FieldType "pPhysicalDevices" VkDeviceGroupDeviceCreateInfo Source # 
type FieldType "physicalDeviceCount" VkDeviceGroupDeviceCreateInfo Source # 
type FieldType "physicalDeviceCount" VkDeviceGroupDeviceCreateInfo = Word32
type FieldType "sType" VkDeviceGroupDeviceCreateInfo Source # 
type FieldOptional "pNext" VkDeviceGroupDeviceCreateInfo Source # 
type FieldOptional "pPhysicalDevices" VkDeviceGroupDeviceCreateInfo Source # 
type FieldOptional "physicalDeviceCount" VkDeviceGroupDeviceCreateInfo Source # 
type FieldOptional "physicalDeviceCount" VkDeviceGroupDeviceCreateInfo = True
type FieldOptional "sType" VkDeviceGroupDeviceCreateInfo Source # 
type FieldOffset "pNext" VkDeviceGroupDeviceCreateInfo Source # 
type FieldOffset "pPhysicalDevices" VkDeviceGroupDeviceCreateInfo Source # 
type FieldOffset "pPhysicalDevices" VkDeviceGroupDeviceCreateInfo = 24
type FieldOffset "physicalDeviceCount" VkDeviceGroupDeviceCreateInfo Source # 
type FieldOffset "physicalDeviceCount" VkDeviceGroupDeviceCreateInfo = 16
type FieldOffset "sType" VkDeviceGroupDeviceCreateInfo Source # 
type FieldIsArray "pNext" VkDeviceGroupDeviceCreateInfo Source # 
type FieldIsArray "pPhysicalDevices" VkDeviceGroupDeviceCreateInfo Source # 
type FieldIsArray "physicalDeviceCount" VkDeviceGroupDeviceCreateInfo Source # 
type FieldIsArray "physicalDeviceCount" VkDeviceGroupDeviceCreateInfo = False
type FieldIsArray "sType" VkDeviceGroupDeviceCreateInfo Source # 

data VkDeviceGroupPresentCapabilitiesKHR Source #

typedef struct VkDeviceGroupPresentCapabilitiesKHR {
    VkStructureType sType;
    const void*                      pNext;
    uint32_t                         presentMask[VK_MAX_DEVICE_GROUP_SIZE];
    VkDeviceGroupPresentModeFlagsKHR modes;
} VkDeviceGroupPresentCapabilitiesKHR;

VkDeviceGroupPresentCapabilitiesKHR registry at www.khronos.org

Instances

Eq VkDeviceGroupPresentCapabilitiesKHR Source # 
Ord VkDeviceGroupPresentCapabilitiesKHR Source # 
Show VkDeviceGroupPresentCapabilitiesKHR Source # 
Storable VkDeviceGroupPresentCapabilitiesKHR Source # 
VulkanMarshalPrim VkDeviceGroupPresentCapabilitiesKHR Source # 
VulkanMarshal VkDeviceGroupPresentCapabilitiesKHR Source # 
CanWriteField "modes" VkDeviceGroupPresentCapabilitiesKHR Source # 
CanWriteField "pNext" VkDeviceGroupPresentCapabilitiesKHR Source # 
CanWriteField "sType" VkDeviceGroupPresentCapabilitiesKHR Source # 
CanReadField "modes" VkDeviceGroupPresentCapabilitiesKHR Source # 
CanReadField "pNext" VkDeviceGroupPresentCapabilitiesKHR Source # 
CanReadField "sType" VkDeviceGroupPresentCapabilitiesKHR Source # 
HasField "modes" VkDeviceGroupPresentCapabilitiesKHR Source # 
HasField "pNext" VkDeviceGroupPresentCapabilitiesKHR Source # 
HasField "presentMask" VkDeviceGroupPresentCapabilitiesKHR Source # 
HasField "sType" VkDeviceGroupPresentCapabilitiesKHR Source # 
(KnownNat idx, IndexInBounds "presentMask" idx VkDeviceGroupPresentCapabilitiesKHR) => CanWriteFieldArray "presentMask" idx VkDeviceGroupPresentCapabilitiesKHR Source # 
(KnownNat idx, IndexInBounds "presentMask" idx VkDeviceGroupPresentCapabilitiesKHR) => CanReadFieldArray "presentMask" idx VkDeviceGroupPresentCapabilitiesKHR Source # 
type StructFields VkDeviceGroupPresentCapabilitiesKHR Source # 
type StructFields VkDeviceGroupPresentCapabilitiesKHR = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "presentMask" ((:) Symbol "modes" ([] Symbol))))
type CUnionType VkDeviceGroupPresentCapabilitiesKHR Source # 
type ReturnedOnly VkDeviceGroupPresentCapabilitiesKHR Source # 
type StructExtends VkDeviceGroupPresentCapabilitiesKHR Source # 
type FieldArrayLength "presentMask" VkDeviceGroupPresentCapabilitiesKHR Source # 
type FieldType "modes" VkDeviceGroupPresentCapabilitiesKHR Source # 
type FieldType "pNext" VkDeviceGroupPresentCapabilitiesKHR Source # 
type FieldType "presentMask" VkDeviceGroupPresentCapabilitiesKHR Source # 
type FieldType "sType" VkDeviceGroupPresentCapabilitiesKHR Source # 
type FieldOptional "modes" VkDeviceGroupPresentCapabilitiesKHR Source # 
type FieldOptional "pNext" VkDeviceGroupPresentCapabilitiesKHR Source # 
type FieldOptional "presentMask" VkDeviceGroupPresentCapabilitiesKHR Source # 
type FieldOptional "sType" VkDeviceGroupPresentCapabilitiesKHR Source # 
type FieldOffset "modes" VkDeviceGroupPresentCapabilitiesKHR Source # 
type FieldOffset "pNext" VkDeviceGroupPresentCapabilitiesKHR Source # 
type FieldOffset "presentMask" VkDeviceGroupPresentCapabilitiesKHR Source # 
type FieldOffset "sType" VkDeviceGroupPresentCapabilitiesKHR Source # 
type FieldIsArray "modes" VkDeviceGroupPresentCapabilitiesKHR Source # 
type FieldIsArray "pNext" VkDeviceGroupPresentCapabilitiesKHR Source # 
type FieldIsArray "presentMask" VkDeviceGroupPresentCapabilitiesKHR Source # 
type FieldIsArray "sType" VkDeviceGroupPresentCapabilitiesKHR Source # 

data VkDeviceGroupPresentInfoKHR Source #

typedef struct VkDeviceGroupPresentInfoKHR {
    VkStructureType sType;
    const void*                      pNext;
    uint32_t         swapchainCount;
    const uint32_t* pDeviceMasks;
    VkDeviceGroupPresentModeFlagBitsKHR mode;
} VkDeviceGroupPresentInfoKHR;

VkDeviceGroupPresentInfoKHR registry at www.khronos.org

Instances

Eq VkDeviceGroupPresentInfoKHR Source # 
Ord VkDeviceGroupPresentInfoKHR Source # 
Show VkDeviceGroupPresentInfoKHR Source # 
Storable VkDeviceGroupPresentInfoKHR Source # 
VulkanMarshalPrim VkDeviceGroupPresentInfoKHR Source # 
VulkanMarshal VkDeviceGroupPresentInfoKHR Source # 
CanWriteField "mode" VkDeviceGroupPresentInfoKHR Source # 
CanWriteField "pDeviceMasks" VkDeviceGroupPresentInfoKHR Source # 
CanWriteField "pNext" VkDeviceGroupPresentInfoKHR Source # 
CanWriteField "sType" VkDeviceGroupPresentInfoKHR Source # 
CanWriteField "swapchainCount" VkDeviceGroupPresentInfoKHR Source # 
CanReadField "mode" VkDeviceGroupPresentInfoKHR Source # 
CanReadField "pDeviceMasks" VkDeviceGroupPresentInfoKHR Source # 
CanReadField "pNext" VkDeviceGroupPresentInfoKHR Source # 
CanReadField "sType" VkDeviceGroupPresentInfoKHR Source # 
CanReadField "swapchainCount" VkDeviceGroupPresentInfoKHR Source # 
HasField "mode" VkDeviceGroupPresentInfoKHR Source # 
HasField "pDeviceMasks" VkDeviceGroupPresentInfoKHR Source # 
HasField "pNext" VkDeviceGroupPresentInfoKHR Source # 
HasField "sType" VkDeviceGroupPresentInfoKHR Source # 
HasField "swapchainCount" VkDeviceGroupPresentInfoKHR Source # 
type StructFields VkDeviceGroupPresentInfoKHR Source # 
type StructFields VkDeviceGroupPresentInfoKHR = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "swapchainCount" ((:) Symbol "pDeviceMasks" ((:) Symbol "mode" ([] Symbol)))))
type CUnionType VkDeviceGroupPresentInfoKHR Source # 
type ReturnedOnly VkDeviceGroupPresentInfoKHR Source # 
type StructExtends VkDeviceGroupPresentInfoKHR Source # 
type FieldType "mode" VkDeviceGroupPresentInfoKHR Source # 
type FieldType "pDeviceMasks" VkDeviceGroupPresentInfoKHR Source # 
type FieldType "pNext" VkDeviceGroupPresentInfoKHR Source # 
type FieldType "sType" VkDeviceGroupPresentInfoKHR Source # 
type FieldType "swapchainCount" VkDeviceGroupPresentInfoKHR Source # 
type FieldOptional "mode" VkDeviceGroupPresentInfoKHR Source # 
type FieldOptional "pDeviceMasks" VkDeviceGroupPresentInfoKHR Source # 
type FieldOptional "pNext" VkDeviceGroupPresentInfoKHR Source # 
type FieldOptional "sType" VkDeviceGroupPresentInfoKHR Source # 
type FieldOptional "swapchainCount" VkDeviceGroupPresentInfoKHR Source # 
type FieldOffset "mode" VkDeviceGroupPresentInfoKHR Source # 
type FieldOffset "pDeviceMasks" VkDeviceGroupPresentInfoKHR Source # 
type FieldOffset "pDeviceMasks" VkDeviceGroupPresentInfoKHR = 24
type FieldOffset "pNext" VkDeviceGroupPresentInfoKHR Source # 
type FieldOffset "sType" VkDeviceGroupPresentInfoKHR Source # 
type FieldOffset "swapchainCount" VkDeviceGroupPresentInfoKHR Source # 
type FieldOffset "swapchainCount" VkDeviceGroupPresentInfoKHR = 16
type FieldIsArray "mode" VkDeviceGroupPresentInfoKHR Source # 
type FieldIsArray "pDeviceMasks" VkDeviceGroupPresentInfoKHR Source # 
type FieldIsArray "pNext" VkDeviceGroupPresentInfoKHR Source # 
type FieldIsArray "sType" VkDeviceGroupPresentInfoKHR Source # 
type FieldIsArray "swapchainCount" VkDeviceGroupPresentInfoKHR Source # 

data VkDeviceGroupRenderPassBeginInfo Source #

typedef struct VkDeviceGroupRenderPassBeginInfo {
    VkStructureType sType;
    const void*                      pNext;
    uint32_t                         deviceMask;
    uint32_t         deviceRenderAreaCount;
    const VkRect2D*  pDeviceRenderAreas;
} VkDeviceGroupRenderPassBeginInfo;

VkDeviceGroupRenderPassBeginInfo registry at www.khronos.org

Instances

Eq VkDeviceGroupRenderPassBeginInfo Source # 
Ord VkDeviceGroupRenderPassBeginInfo Source # 
Show VkDeviceGroupRenderPassBeginInfo Source # 
Storable VkDeviceGroupRenderPassBeginInfo Source # 
VulkanMarshalPrim VkDeviceGroupRenderPassBeginInfo Source # 
VulkanMarshal VkDeviceGroupRenderPassBeginInfo Source # 
CanWriteField "deviceMask" VkDeviceGroupRenderPassBeginInfo Source # 
CanWriteField "deviceRenderAreaCount" VkDeviceGroupRenderPassBeginInfo Source # 
CanWriteField "pDeviceRenderAreas" VkDeviceGroupRenderPassBeginInfo Source # 
CanWriteField "pNext" VkDeviceGroupRenderPassBeginInfo Source # 
CanWriteField "sType" VkDeviceGroupRenderPassBeginInfo Source # 
CanReadField "deviceMask" VkDeviceGroupRenderPassBeginInfo Source # 
CanReadField "deviceRenderAreaCount" VkDeviceGroupRenderPassBeginInfo Source # 
CanReadField "pDeviceRenderAreas" VkDeviceGroupRenderPassBeginInfo Source # 
CanReadField "pNext" VkDeviceGroupRenderPassBeginInfo Source # 
CanReadField "sType" VkDeviceGroupRenderPassBeginInfo Source # 
HasField "deviceMask" VkDeviceGroupRenderPassBeginInfo Source # 
HasField "deviceRenderAreaCount" VkDeviceGroupRenderPassBeginInfo Source # 

Associated Types

type FieldType ("deviceRenderAreaCount" :: Symbol) VkDeviceGroupRenderPassBeginInfo :: Type Source #

type FieldOptional ("deviceRenderAreaCount" :: Symbol) VkDeviceGroupRenderPassBeginInfo :: Bool Source #

type FieldOffset ("deviceRenderAreaCount" :: Symbol) VkDeviceGroupRenderPassBeginInfo :: Nat Source #

type FieldIsArray ("deviceRenderAreaCount" :: Symbol) VkDeviceGroupRenderPassBeginInfo :: Bool Source #

HasField "pDeviceRenderAreas" VkDeviceGroupRenderPassBeginInfo Source # 

Associated Types

type FieldType ("pDeviceRenderAreas" :: Symbol) VkDeviceGroupRenderPassBeginInfo :: Type Source #

type FieldOptional ("pDeviceRenderAreas" :: Symbol) VkDeviceGroupRenderPassBeginInfo :: Bool Source #

type FieldOffset ("pDeviceRenderAreas" :: Symbol) VkDeviceGroupRenderPassBeginInfo :: Nat Source #

type FieldIsArray ("pDeviceRenderAreas" :: Symbol) VkDeviceGroupRenderPassBeginInfo :: Bool Source #

HasField "pNext" VkDeviceGroupRenderPassBeginInfo Source # 
HasField "sType" VkDeviceGroupRenderPassBeginInfo Source # 
type StructFields VkDeviceGroupRenderPassBeginInfo Source # 
type StructFields VkDeviceGroupRenderPassBeginInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "deviceMask" ((:) Symbol "deviceRenderAreaCount" ((:) Symbol "pDeviceRenderAreas" ([] Symbol)))))
type CUnionType VkDeviceGroupRenderPassBeginInfo Source # 
type ReturnedOnly VkDeviceGroupRenderPassBeginInfo Source # 
type StructExtends VkDeviceGroupRenderPassBeginInfo Source # 
type FieldType "deviceMask" VkDeviceGroupRenderPassBeginInfo Source # 
type FieldType "deviceRenderAreaCount" VkDeviceGroupRenderPassBeginInfo Source # 
type FieldType "deviceRenderAreaCount" VkDeviceGroupRenderPassBeginInfo = Word32
type FieldType "pDeviceRenderAreas" VkDeviceGroupRenderPassBeginInfo Source # 
type FieldType "pNext" VkDeviceGroupRenderPassBeginInfo Source # 
type FieldType "sType" VkDeviceGroupRenderPassBeginInfo Source # 
type FieldOptional "deviceMask" VkDeviceGroupRenderPassBeginInfo Source # 
type FieldOptional "deviceRenderAreaCount" VkDeviceGroupRenderPassBeginInfo Source # 
type FieldOptional "deviceRenderAreaCount" VkDeviceGroupRenderPassBeginInfo = True
type FieldOptional "pDeviceRenderAreas" VkDeviceGroupRenderPassBeginInfo Source # 
type FieldOptional "pNext" VkDeviceGroupRenderPassBeginInfo Source # 
type FieldOptional "sType" VkDeviceGroupRenderPassBeginInfo Source # 
type FieldOffset "deviceMask" VkDeviceGroupRenderPassBeginInfo Source # 
type FieldOffset "deviceRenderAreaCount" VkDeviceGroupRenderPassBeginInfo Source # 
type FieldOffset "deviceRenderAreaCount" VkDeviceGroupRenderPassBeginInfo = 20
type FieldOffset "pDeviceRenderAreas" VkDeviceGroupRenderPassBeginInfo Source # 
type FieldOffset "pDeviceRenderAreas" VkDeviceGroupRenderPassBeginInfo = 24
type FieldOffset "pNext" VkDeviceGroupRenderPassBeginInfo Source # 
type FieldOffset "sType" VkDeviceGroupRenderPassBeginInfo Source # 
type FieldIsArray "deviceMask" VkDeviceGroupRenderPassBeginInfo Source # 
type FieldIsArray "deviceRenderAreaCount" VkDeviceGroupRenderPassBeginInfo Source # 
type FieldIsArray "deviceRenderAreaCount" VkDeviceGroupRenderPassBeginInfo = False
type FieldIsArray "pDeviceRenderAreas" VkDeviceGroupRenderPassBeginInfo Source # 
type FieldIsArray "pNext" VkDeviceGroupRenderPassBeginInfo Source # 
type FieldIsArray "sType" VkDeviceGroupRenderPassBeginInfo Source # 

data VkDeviceGroupSubmitInfo Source #

typedef struct VkDeviceGroupSubmitInfo {
    VkStructureType sType;
    const void*                      pNext;
    uint32_t         waitSemaphoreCount;
    const uint32_t*    pWaitSemaphoreDeviceIndices;
    uint32_t         commandBufferCount;
    const uint32_t*    pCommandBufferDeviceMasks;
    uint32_t         signalSemaphoreCount;
    const uint32_t*  pSignalSemaphoreDeviceIndices;
} VkDeviceGroupSubmitInfo;

VkDeviceGroupSubmitInfo registry at www.khronos.org

Instances

Eq VkDeviceGroupSubmitInfo Source # 
Ord VkDeviceGroupSubmitInfo Source # 
Show VkDeviceGroupSubmitInfo Source # 
Storable VkDeviceGroupSubmitInfo Source # 
VulkanMarshalPrim VkDeviceGroupSubmitInfo Source # 
VulkanMarshal VkDeviceGroupSubmitInfo Source # 
CanWriteField "commandBufferCount" VkDeviceGroupSubmitInfo Source # 
CanWriteField "pCommandBufferDeviceMasks" VkDeviceGroupSubmitInfo Source # 

Methods

writeField :: Ptr VkDeviceGroupSubmitInfo -> FieldType "pCommandBufferDeviceMasks" VkDeviceGroupSubmitInfo -> IO () Source #

CanWriteField "pNext" VkDeviceGroupSubmitInfo Source # 
CanWriteField "pSignalSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo Source # 

Methods

writeField :: Ptr VkDeviceGroupSubmitInfo -> FieldType "pSignalSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo -> IO () Source #

CanWriteField "pWaitSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo Source # 

Methods

writeField :: Ptr VkDeviceGroupSubmitInfo -> FieldType "pWaitSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo -> IO () Source #

CanWriteField "sType" VkDeviceGroupSubmitInfo Source # 
CanWriteField "signalSemaphoreCount" VkDeviceGroupSubmitInfo Source # 
CanWriteField "waitSemaphoreCount" VkDeviceGroupSubmitInfo Source # 
CanReadField "commandBufferCount" VkDeviceGroupSubmitInfo Source # 
CanReadField "pCommandBufferDeviceMasks" VkDeviceGroupSubmitInfo Source # 
CanReadField "pNext" VkDeviceGroupSubmitInfo Source # 
CanReadField "pSignalSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo Source # 
CanReadField "pWaitSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo Source # 
CanReadField "sType" VkDeviceGroupSubmitInfo Source # 
CanReadField "signalSemaphoreCount" VkDeviceGroupSubmitInfo Source # 
CanReadField "waitSemaphoreCount" VkDeviceGroupSubmitInfo Source # 
HasField "commandBufferCount" VkDeviceGroupSubmitInfo Source # 

Associated Types

type FieldType ("commandBufferCount" :: Symbol) VkDeviceGroupSubmitInfo :: Type Source #

type FieldOptional ("commandBufferCount" :: Symbol) VkDeviceGroupSubmitInfo :: Bool Source #

type FieldOffset ("commandBufferCount" :: Symbol) VkDeviceGroupSubmitInfo :: Nat Source #

type FieldIsArray ("commandBufferCount" :: Symbol) VkDeviceGroupSubmitInfo :: Bool Source #

HasField "pCommandBufferDeviceMasks" VkDeviceGroupSubmitInfo Source # 

Associated Types

type FieldType ("pCommandBufferDeviceMasks" :: Symbol) VkDeviceGroupSubmitInfo :: Type Source #

type FieldOptional ("pCommandBufferDeviceMasks" :: Symbol) VkDeviceGroupSubmitInfo :: Bool Source #

type FieldOffset ("pCommandBufferDeviceMasks" :: Symbol) VkDeviceGroupSubmitInfo :: Nat Source #

type FieldIsArray ("pCommandBufferDeviceMasks" :: Symbol) VkDeviceGroupSubmitInfo :: Bool Source #

HasField "pNext" VkDeviceGroupSubmitInfo Source # 
HasField "pSignalSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo Source # 

Associated Types

type FieldType ("pSignalSemaphoreDeviceIndices" :: Symbol) VkDeviceGroupSubmitInfo :: Type Source #

type FieldOptional ("pSignalSemaphoreDeviceIndices" :: Symbol) VkDeviceGroupSubmitInfo :: Bool Source #

type FieldOffset ("pSignalSemaphoreDeviceIndices" :: Symbol) VkDeviceGroupSubmitInfo :: Nat Source #

type FieldIsArray ("pSignalSemaphoreDeviceIndices" :: Symbol) VkDeviceGroupSubmitInfo :: Bool Source #

HasField "pWaitSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo Source # 

Associated Types

type FieldType ("pWaitSemaphoreDeviceIndices" :: Symbol) VkDeviceGroupSubmitInfo :: Type Source #

type FieldOptional ("pWaitSemaphoreDeviceIndices" :: Symbol) VkDeviceGroupSubmitInfo :: Bool Source #

type FieldOffset ("pWaitSemaphoreDeviceIndices" :: Symbol) VkDeviceGroupSubmitInfo :: Nat Source #

type FieldIsArray ("pWaitSemaphoreDeviceIndices" :: Symbol) VkDeviceGroupSubmitInfo :: Bool Source #

HasField "sType" VkDeviceGroupSubmitInfo Source # 
HasField "signalSemaphoreCount" VkDeviceGroupSubmitInfo Source # 

Associated Types

type FieldType ("signalSemaphoreCount" :: Symbol) VkDeviceGroupSubmitInfo :: Type Source #

type FieldOptional ("signalSemaphoreCount" :: Symbol) VkDeviceGroupSubmitInfo :: Bool Source #

type FieldOffset ("signalSemaphoreCount" :: Symbol) VkDeviceGroupSubmitInfo :: Nat Source #

type FieldIsArray ("signalSemaphoreCount" :: Symbol) VkDeviceGroupSubmitInfo :: Bool Source #

HasField "waitSemaphoreCount" VkDeviceGroupSubmitInfo Source # 

Associated Types

type FieldType ("waitSemaphoreCount" :: Symbol) VkDeviceGroupSubmitInfo :: Type Source #

type FieldOptional ("waitSemaphoreCount" :: Symbol) VkDeviceGroupSubmitInfo :: Bool Source #

type FieldOffset ("waitSemaphoreCount" :: Symbol) VkDeviceGroupSubmitInfo :: Nat Source #

type FieldIsArray ("waitSemaphoreCount" :: Symbol) VkDeviceGroupSubmitInfo :: Bool Source #

type StructFields VkDeviceGroupSubmitInfo Source # 
type StructFields VkDeviceGroupSubmitInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "waitSemaphoreCount" ((:) Symbol "pWaitSemaphoreDeviceIndices" ((:) Symbol "commandBufferCount" ((:) Symbol "pCommandBufferDeviceMasks" ((:) Symbol "signalSemaphoreCount" ((:) Symbol "pSignalSemaphoreDeviceIndices" ([] Symbol))))))))
type CUnionType VkDeviceGroupSubmitInfo Source # 
type ReturnedOnly VkDeviceGroupSubmitInfo Source # 
type StructExtends VkDeviceGroupSubmitInfo Source # 
type FieldType "commandBufferCount" VkDeviceGroupSubmitInfo Source # 
type FieldType "commandBufferCount" VkDeviceGroupSubmitInfo = Word32
type FieldType "pCommandBufferDeviceMasks" VkDeviceGroupSubmitInfo Source # 
type FieldType "pCommandBufferDeviceMasks" VkDeviceGroupSubmitInfo = Ptr Word32
type FieldType "pNext" VkDeviceGroupSubmitInfo Source # 
type FieldType "pSignalSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo Source # 
type FieldType "pSignalSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo = Ptr Word32
type FieldType "pWaitSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo Source # 
type FieldType "pWaitSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo = Ptr Word32
type FieldType "sType" VkDeviceGroupSubmitInfo Source # 
type FieldType "signalSemaphoreCount" VkDeviceGroupSubmitInfo Source # 
type FieldType "signalSemaphoreCount" VkDeviceGroupSubmitInfo = Word32
type FieldType "waitSemaphoreCount" VkDeviceGroupSubmitInfo Source # 
type FieldType "waitSemaphoreCount" VkDeviceGroupSubmitInfo = Word32
type FieldOptional "commandBufferCount" VkDeviceGroupSubmitInfo Source # 
type FieldOptional "commandBufferCount" VkDeviceGroupSubmitInfo = True
type FieldOptional "pCommandBufferDeviceMasks" VkDeviceGroupSubmitInfo Source # 
type FieldOptional "pCommandBufferDeviceMasks" VkDeviceGroupSubmitInfo = False
type FieldOptional "pNext" VkDeviceGroupSubmitInfo Source # 
type FieldOptional "pSignalSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo Source # 
type FieldOptional "pSignalSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo = False
type FieldOptional "pWaitSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo Source # 
type FieldOptional "pWaitSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo = False
type FieldOptional "sType" VkDeviceGroupSubmitInfo Source # 
type FieldOptional "signalSemaphoreCount" VkDeviceGroupSubmitInfo Source # 
type FieldOptional "signalSemaphoreCount" VkDeviceGroupSubmitInfo = True
type FieldOptional "waitSemaphoreCount" VkDeviceGroupSubmitInfo Source # 
type FieldOptional "waitSemaphoreCount" VkDeviceGroupSubmitInfo = True
type FieldOffset "commandBufferCount" VkDeviceGroupSubmitInfo Source # 
type FieldOffset "commandBufferCount" VkDeviceGroupSubmitInfo = 32
type FieldOffset "pCommandBufferDeviceMasks" VkDeviceGroupSubmitInfo Source # 
type FieldOffset "pCommandBufferDeviceMasks" VkDeviceGroupSubmitInfo = 40
type FieldOffset "pNext" VkDeviceGroupSubmitInfo Source # 
type FieldOffset "pSignalSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo Source # 
type FieldOffset "pSignalSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo = 56
type FieldOffset "pWaitSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo Source # 
type FieldOffset "pWaitSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo = 24
type FieldOffset "sType" VkDeviceGroupSubmitInfo Source # 
type FieldOffset "signalSemaphoreCount" VkDeviceGroupSubmitInfo Source # 
type FieldOffset "signalSemaphoreCount" VkDeviceGroupSubmitInfo = 48
type FieldOffset "waitSemaphoreCount" VkDeviceGroupSubmitInfo Source # 
type FieldOffset "waitSemaphoreCount" VkDeviceGroupSubmitInfo = 16
type FieldIsArray "commandBufferCount" VkDeviceGroupSubmitInfo Source # 
type FieldIsArray "commandBufferCount" VkDeviceGroupSubmitInfo = False
type FieldIsArray "pCommandBufferDeviceMasks" VkDeviceGroupSubmitInfo Source # 
type FieldIsArray "pCommandBufferDeviceMasks" VkDeviceGroupSubmitInfo = False
type FieldIsArray "pNext" VkDeviceGroupSubmitInfo Source # 
type FieldIsArray "pSignalSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo Source # 
type FieldIsArray "pSignalSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo = False
type FieldIsArray "pWaitSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo Source # 
type FieldIsArray "pWaitSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo = False
type FieldIsArray "sType" VkDeviceGroupSubmitInfo Source # 
type FieldIsArray "signalSemaphoreCount" VkDeviceGroupSubmitInfo Source # 
type FieldIsArray "signalSemaphoreCount" VkDeviceGroupSubmitInfo = False
type FieldIsArray "waitSemaphoreCount" VkDeviceGroupSubmitInfo Source # 
type FieldIsArray "waitSemaphoreCount" VkDeviceGroupSubmitInfo = False

data VkDeviceGroupSwapchainCreateInfoKHR Source #

typedef struct VkDeviceGroupSwapchainCreateInfoKHR {
    VkStructureType sType;
    const void*                      pNext;
    VkDeviceGroupPresentModeFlagsKHR                         modes;
} VkDeviceGroupSwapchainCreateInfoKHR;

VkDeviceGroupSwapchainCreateInfoKHR registry at www.khronos.org

Instances

Eq VkDeviceGroupSwapchainCreateInfoKHR Source # 
Ord VkDeviceGroupSwapchainCreateInfoKHR Source # 
Show VkDeviceGroupSwapchainCreateInfoKHR Source # 
Storable VkDeviceGroupSwapchainCreateInfoKHR Source # 
VulkanMarshalPrim VkDeviceGroupSwapchainCreateInfoKHR Source # 
VulkanMarshal VkDeviceGroupSwapchainCreateInfoKHR Source # 
CanWriteField "modes" VkDeviceGroupSwapchainCreateInfoKHR Source # 
CanWriteField "pNext" VkDeviceGroupSwapchainCreateInfoKHR Source # 
CanWriteField "sType" VkDeviceGroupSwapchainCreateInfoKHR Source # 
CanReadField "modes" VkDeviceGroupSwapchainCreateInfoKHR Source # 
CanReadField "pNext" VkDeviceGroupSwapchainCreateInfoKHR Source # 
CanReadField "sType" VkDeviceGroupSwapchainCreateInfoKHR Source # 
HasField "modes" VkDeviceGroupSwapchainCreateInfoKHR Source # 
HasField "pNext" VkDeviceGroupSwapchainCreateInfoKHR Source # 
HasField "sType" VkDeviceGroupSwapchainCreateInfoKHR Source # 
type StructFields VkDeviceGroupSwapchainCreateInfoKHR Source # 
type StructFields VkDeviceGroupSwapchainCreateInfoKHR = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "modes" ([] Symbol)))
type CUnionType VkDeviceGroupSwapchainCreateInfoKHR Source # 
type ReturnedOnly VkDeviceGroupSwapchainCreateInfoKHR Source # 
type StructExtends VkDeviceGroupSwapchainCreateInfoKHR Source # 
type FieldType "modes" VkDeviceGroupSwapchainCreateInfoKHR Source # 
type FieldType "pNext" VkDeviceGroupSwapchainCreateInfoKHR Source # 
type FieldType "sType" VkDeviceGroupSwapchainCreateInfoKHR Source # 
type FieldOptional "modes" VkDeviceGroupSwapchainCreateInfoKHR Source # 
type FieldOptional "pNext" VkDeviceGroupSwapchainCreateInfoKHR Source # 
type FieldOptional "sType" VkDeviceGroupSwapchainCreateInfoKHR Source # 
type FieldOffset "modes" VkDeviceGroupSwapchainCreateInfoKHR Source # 
type FieldOffset "pNext" VkDeviceGroupSwapchainCreateInfoKHR Source # 
type FieldOffset "sType" VkDeviceGroupSwapchainCreateInfoKHR Source # 
type FieldIsArray "modes" VkDeviceGroupSwapchainCreateInfoKHR Source # 
type FieldIsArray "pNext" VkDeviceGroupSwapchainCreateInfoKHR Source # 
type FieldIsArray "sType" VkDeviceGroupSwapchainCreateInfoKHR Source # 

data VkDeviceQueueCreateInfo Source #

typedef struct VkDeviceQueueCreateInfo {
    VkStructureType sType;
    const void*     pNext;
    VkDeviceQueueCreateFlags    flags;
    uint32_t        queueFamilyIndex;
    uint32_t        queueCount;
    const float*    pQueuePriorities;
} VkDeviceQueueCreateInfo;

VkDeviceQueueCreateInfo registry at www.khronos.org

Instances

Eq VkDeviceQueueCreateInfo Source # 
Ord VkDeviceQueueCreateInfo Source # 
Show VkDeviceQueueCreateInfo Source # 
Storable VkDeviceQueueCreateInfo Source # 
VulkanMarshalPrim VkDeviceQueueCreateInfo Source # 
VulkanMarshal VkDeviceQueueCreateInfo Source # 
CanWriteField "flags" VkDeviceQueueCreateInfo Source # 
CanWriteField "pNext" VkDeviceQueueCreateInfo Source # 
CanWriteField "pQueuePriorities" VkDeviceQueueCreateInfo Source # 
CanWriteField "queueCount" VkDeviceQueueCreateInfo Source # 
CanWriteField "queueFamilyIndex" VkDeviceQueueCreateInfo Source # 
CanWriteField "sType" VkDeviceQueueCreateInfo Source # 
CanReadField "flags" VkDeviceQueueCreateInfo Source # 
CanReadField "pNext" VkDeviceQueueCreateInfo Source # 
CanReadField "pQueuePriorities" VkDeviceQueueCreateInfo Source # 
CanReadField "queueCount" VkDeviceQueueCreateInfo Source # 
CanReadField "queueFamilyIndex" VkDeviceQueueCreateInfo Source # 
CanReadField "sType" VkDeviceQueueCreateInfo Source # 
HasField "flags" VkDeviceQueueCreateInfo Source # 
HasField "pNext" VkDeviceQueueCreateInfo Source # 
HasField "pQueuePriorities" VkDeviceQueueCreateInfo Source # 

Associated Types

type FieldType ("pQueuePriorities" :: Symbol) VkDeviceQueueCreateInfo :: Type Source #

type FieldOptional ("pQueuePriorities" :: Symbol) VkDeviceQueueCreateInfo :: Bool Source #

type FieldOffset ("pQueuePriorities" :: Symbol) VkDeviceQueueCreateInfo :: Nat Source #

type FieldIsArray ("pQueuePriorities" :: Symbol) VkDeviceQueueCreateInfo :: Bool Source #

HasField "queueCount" VkDeviceQueueCreateInfo Source # 
HasField "queueFamilyIndex" VkDeviceQueueCreateInfo Source # 

Associated Types

type FieldType ("queueFamilyIndex" :: Symbol) VkDeviceQueueCreateInfo :: Type Source #

type FieldOptional ("queueFamilyIndex" :: Symbol) VkDeviceQueueCreateInfo :: Bool Source #

type FieldOffset ("queueFamilyIndex" :: Symbol) VkDeviceQueueCreateInfo :: Nat Source #

type FieldIsArray ("queueFamilyIndex" :: Symbol) VkDeviceQueueCreateInfo :: Bool Source #

HasField "sType" VkDeviceQueueCreateInfo Source # 
type StructFields VkDeviceQueueCreateInfo Source # 
type StructFields VkDeviceQueueCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "queueFamilyIndex" ((:) Symbol "queueCount" ((:) Symbol "pQueuePriorities" ([] Symbol))))))
type CUnionType VkDeviceQueueCreateInfo Source # 
type ReturnedOnly VkDeviceQueueCreateInfo Source # 
type StructExtends VkDeviceQueueCreateInfo Source # 
type FieldType "flags" VkDeviceQueueCreateInfo Source # 
type FieldType "pNext" VkDeviceQueueCreateInfo Source # 
type FieldType "pQueuePriorities" VkDeviceQueueCreateInfo Source # 
type FieldType "pQueuePriorities" VkDeviceQueueCreateInfo = Ptr Float
type FieldType "queueCount" VkDeviceQueueCreateInfo Source # 
type FieldType "queueFamilyIndex" VkDeviceQueueCreateInfo Source # 
type FieldType "queueFamilyIndex" VkDeviceQueueCreateInfo = Word32
type FieldType "sType" VkDeviceQueueCreateInfo Source # 
type FieldOptional "flags" VkDeviceQueueCreateInfo Source # 
type FieldOptional "pNext" VkDeviceQueueCreateInfo Source # 
type FieldOptional "pQueuePriorities" VkDeviceQueueCreateInfo Source # 
type FieldOptional "pQueuePriorities" VkDeviceQueueCreateInfo = False
type FieldOptional "queueCount" VkDeviceQueueCreateInfo Source # 
type FieldOptional "queueFamilyIndex" VkDeviceQueueCreateInfo Source # 
type FieldOptional "queueFamilyIndex" VkDeviceQueueCreateInfo = False
type FieldOptional "sType" VkDeviceQueueCreateInfo Source # 
type FieldOffset "flags" VkDeviceQueueCreateInfo Source # 
type FieldOffset "pNext" VkDeviceQueueCreateInfo Source # 
type FieldOffset "pQueuePriorities" VkDeviceQueueCreateInfo Source # 
type FieldOffset "pQueuePriorities" VkDeviceQueueCreateInfo = 32
type FieldOffset "queueCount" VkDeviceQueueCreateInfo Source # 
type FieldOffset "queueCount" VkDeviceQueueCreateInfo = 24
type FieldOffset "queueFamilyIndex" VkDeviceQueueCreateInfo Source # 
type FieldOffset "queueFamilyIndex" VkDeviceQueueCreateInfo = 20
type FieldOffset "sType" VkDeviceQueueCreateInfo Source # 
type FieldIsArray "flags" VkDeviceQueueCreateInfo Source # 
type FieldIsArray "pNext" VkDeviceQueueCreateInfo Source # 
type FieldIsArray "pQueuePriorities" VkDeviceQueueCreateInfo Source # 
type FieldIsArray "pQueuePriorities" VkDeviceQueueCreateInfo = False
type FieldIsArray "queueCount" VkDeviceQueueCreateInfo Source # 
type FieldIsArray "queueFamilyIndex" VkDeviceQueueCreateInfo Source # 
type FieldIsArray "queueFamilyIndex" VkDeviceQueueCreateInfo = False
type FieldIsArray "sType" VkDeviceQueueCreateInfo Source # 

data VkDeviceQueueGlobalPriorityCreateInfoEXT Source #

typedef struct VkDeviceQueueGlobalPriorityCreateInfoEXT {
    VkStructureType sType;
    const void*                    pNext;
    VkQueueGlobalPriorityEXT       globalPriority;
} VkDeviceQueueGlobalPriorityCreateInfoEXT;

VkDeviceQueueGlobalPriorityCreateInfoEXT registry at www.khronos.org

Instances

Eq VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
Ord VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
Show VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
Storable VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
VulkanMarshalPrim VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
VulkanMarshal VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
CanWriteField "globalPriority" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
CanWriteField "pNext" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
CanWriteField "sType" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
CanReadField "globalPriority" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
CanReadField "pNext" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
CanReadField "sType" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
HasField "globalPriority" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
HasField "pNext" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
HasField "sType" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
type StructFields VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
type StructFields VkDeviceQueueGlobalPriorityCreateInfoEXT = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "globalPriority" ([] Symbol)))
type CUnionType VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
type ReturnedOnly VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
type StructExtends VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
type FieldType "globalPriority" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
type FieldType "pNext" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
type FieldType "sType" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
type FieldOptional "globalPriority" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
type FieldOptional "pNext" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
type FieldOptional "sType" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
type FieldOffset "globalPriority" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
type FieldOffset "pNext" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
type FieldOffset "sType" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
type FieldIsArray "globalPriority" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
type FieldIsArray "pNext" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
type FieldIsArray "sType" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 

data VkDeviceQueueInfo2 Source #

typedef struct VkDeviceQueueInfo2 {
    VkStructureType sType;
    const void*                         pNext;
    VkDeviceQueueCreateFlags            flags;
    uint32_t                            queueFamilyIndex;
    uint32_t                            queueIndex;
} VkDeviceQueueInfo2;

VkDeviceQueueInfo2 registry at www.khronos.org

Instances

Eq VkDeviceQueueInfo2 Source # 
Ord VkDeviceQueueInfo2 Source # 
Show VkDeviceQueueInfo2 Source # 
Storable VkDeviceQueueInfo2 Source # 
VulkanMarshalPrim VkDeviceQueueInfo2 Source # 
VulkanMarshal VkDeviceQueueInfo2 Source # 
CanWriteField "flags" VkDeviceQueueInfo2 Source # 
CanWriteField "pNext" VkDeviceQueueInfo2 Source # 
CanWriteField "queueFamilyIndex" VkDeviceQueueInfo2 Source # 

Methods

writeField :: Ptr VkDeviceQueueInfo2 -> FieldType "queueFamilyIndex" VkDeviceQueueInfo2 -> IO () Source #

CanWriteField "queueIndex" VkDeviceQueueInfo2 Source # 
CanWriteField "sType" VkDeviceQueueInfo2 Source # 
CanReadField "flags" VkDeviceQueueInfo2 Source # 
CanReadField "pNext" VkDeviceQueueInfo2 Source # 
CanReadField "queueFamilyIndex" VkDeviceQueueInfo2 Source # 
CanReadField "queueIndex" VkDeviceQueueInfo2 Source # 
CanReadField "sType" VkDeviceQueueInfo2 Source # 
HasField "flags" VkDeviceQueueInfo2 Source # 
HasField "pNext" VkDeviceQueueInfo2 Source # 
HasField "queueFamilyIndex" VkDeviceQueueInfo2 Source # 

Associated Types

type FieldType ("queueFamilyIndex" :: Symbol) VkDeviceQueueInfo2 :: Type Source #

type FieldOptional ("queueFamilyIndex" :: Symbol) VkDeviceQueueInfo2 :: Bool Source #

type FieldOffset ("queueFamilyIndex" :: Symbol) VkDeviceQueueInfo2 :: Nat Source #

type FieldIsArray ("queueFamilyIndex" :: Symbol) VkDeviceQueueInfo2 :: Bool Source #

HasField "queueIndex" VkDeviceQueueInfo2 Source # 

Associated Types

type FieldType ("queueIndex" :: Symbol) VkDeviceQueueInfo2 :: Type Source #

type FieldOptional ("queueIndex" :: Symbol) VkDeviceQueueInfo2 :: Bool Source #

type FieldOffset ("queueIndex" :: Symbol) VkDeviceQueueInfo2 :: Nat Source #

type FieldIsArray ("queueIndex" :: Symbol) VkDeviceQueueInfo2 :: Bool Source #

HasField "sType" VkDeviceQueueInfo2 Source # 
type StructFields VkDeviceQueueInfo2 Source # 
type StructFields VkDeviceQueueInfo2 = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "queueFamilyIndex" ((:) Symbol "queueIndex" ([] Symbol)))))
type CUnionType VkDeviceQueueInfo2 Source # 
type ReturnedOnly VkDeviceQueueInfo2 Source # 
type StructExtends VkDeviceQueueInfo2 Source # 
type FieldType "flags" VkDeviceQueueInfo2 Source # 
type FieldType "pNext" VkDeviceQueueInfo2 Source # 
type FieldType "queueFamilyIndex" VkDeviceQueueInfo2 Source # 
type FieldType "queueFamilyIndex" VkDeviceQueueInfo2 = Word32
type FieldType "queueIndex" VkDeviceQueueInfo2 Source # 
type FieldType "queueIndex" VkDeviceQueueInfo2 = Word32
type FieldType "sType" VkDeviceQueueInfo2 Source # 
type FieldOptional "flags" VkDeviceQueueInfo2 Source # 
type FieldOptional "pNext" VkDeviceQueueInfo2 Source # 
type FieldOptional "queueFamilyIndex" VkDeviceQueueInfo2 Source # 
type FieldOptional "queueFamilyIndex" VkDeviceQueueInfo2 = False
type FieldOptional "queueIndex" VkDeviceQueueInfo2 Source # 
type FieldOptional "sType" VkDeviceQueueInfo2 Source # 
type FieldOffset "flags" VkDeviceQueueInfo2 Source # 
type FieldOffset "pNext" VkDeviceQueueInfo2 Source # 
type FieldOffset "queueFamilyIndex" VkDeviceQueueInfo2 Source # 
type FieldOffset "queueFamilyIndex" VkDeviceQueueInfo2 = 20
type FieldOffset "queueIndex" VkDeviceQueueInfo2 Source # 
type FieldOffset "queueIndex" VkDeviceQueueInfo2 = 24
type FieldOffset "sType" VkDeviceQueueInfo2 Source # 
type FieldIsArray "flags" VkDeviceQueueInfo2 Source # 
type FieldIsArray "pNext" VkDeviceQueueInfo2 Source # 
type FieldIsArray "queueFamilyIndex" VkDeviceQueueInfo2 Source # 
type FieldIsArray "queueFamilyIndex" VkDeviceQueueInfo2 = False
type FieldIsArray "queueIndex" VkDeviceQueueInfo2 Source # 
type FieldIsArray "sType" VkDeviceQueueInfo2 Source # 

newtype VkDeviceCreateFlagBits Source #

Instances

Bounded VkDeviceCreateFlagBits Source # 
Enum VkDeviceCreateFlagBits Source # 
Eq VkDeviceCreateFlagBits Source # 
Integral VkDeviceCreateFlagBits Source # 
Data VkDeviceCreateFlagBits Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkDeviceCreateFlagBits -> c VkDeviceCreateFlagBits #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkDeviceCreateFlagBits #

toConstr :: VkDeviceCreateFlagBits -> Constr #

dataTypeOf :: VkDeviceCreateFlagBits -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkDeviceCreateFlagBits) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkDeviceCreateFlagBits) #

gmapT :: (forall b. Data b => b -> b) -> VkDeviceCreateFlagBits -> VkDeviceCreateFlagBits #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkDeviceCreateFlagBits -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkDeviceCreateFlagBits -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkDeviceCreateFlagBits -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkDeviceCreateFlagBits -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkDeviceCreateFlagBits -> m VkDeviceCreateFlagBits #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkDeviceCreateFlagBits -> m VkDeviceCreateFlagBits #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkDeviceCreateFlagBits -> m VkDeviceCreateFlagBits #

Num VkDeviceCreateFlagBits Source # 
Ord VkDeviceCreateFlagBits Source # 
Read VkDeviceCreateFlagBits Source # 
Real VkDeviceCreateFlagBits Source # 
Show VkDeviceCreateFlagBits Source # 
Generic VkDeviceCreateFlagBits Source # 
Storable VkDeviceCreateFlagBits Source # 
Bits VkDeviceCreateFlagBits Source # 
FiniteBits VkDeviceCreateFlagBits Source # 
type Rep VkDeviceCreateFlagBits Source # 
type Rep VkDeviceCreateFlagBits = D1 (MetaData "VkDeviceCreateFlagBits" "Graphics.Vulkan.Types.Enum.Device" "vulkan-api-1.1.2.1-GcVsfRwwhb24i5dsYq91EC" True) (C1 (MetaCons "VkDeviceCreateFlagBits" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkDeviceEventTypeEXT Source #

Instances

Bounded VkDeviceEventTypeEXT Source # 
Enum VkDeviceEventTypeEXT Source # 
Eq VkDeviceEventTypeEXT Source # 
Data VkDeviceEventTypeEXT Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkDeviceEventTypeEXT -> c VkDeviceEventTypeEXT #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkDeviceEventTypeEXT #

toConstr :: VkDeviceEventTypeEXT -> Constr #

dataTypeOf :: VkDeviceEventTypeEXT -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkDeviceEventTypeEXT) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkDeviceEventTypeEXT) #

gmapT :: (forall b. Data b => b -> b) -> VkDeviceEventTypeEXT -> VkDeviceEventTypeEXT #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkDeviceEventTypeEXT -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkDeviceEventTypeEXT -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkDeviceEventTypeEXT -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkDeviceEventTypeEXT -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkDeviceEventTypeEXT -> m VkDeviceEventTypeEXT #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkDeviceEventTypeEXT -> m VkDeviceEventTypeEXT #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkDeviceEventTypeEXT -> m VkDeviceEventTypeEXT #

Num VkDeviceEventTypeEXT Source # 
Ord VkDeviceEventTypeEXT Source # 
Read VkDeviceEventTypeEXT Source # 
Show VkDeviceEventTypeEXT Source # 
Generic VkDeviceEventTypeEXT Source # 
Storable VkDeviceEventTypeEXT Source # 
type Rep VkDeviceEventTypeEXT Source # 
type Rep VkDeviceEventTypeEXT = D1 (MetaData "VkDeviceEventTypeEXT" "Graphics.Vulkan.Types.Enum.Device" "vulkan-api-1.1.2.1-GcVsfRwwhb24i5dsYq91EC" True) (C1 (MetaCons "VkDeviceEventTypeEXT" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

newtype VkDeviceGroupPresentModeBitmaskKHR a Source #

Instances

Bounded (VkDeviceGroupPresentModeBitmaskKHR FlagMask) Source # 
Enum (VkDeviceGroupPresentModeBitmaskKHR FlagMask) Source # 
Eq (VkDeviceGroupPresentModeBitmaskKHR a) Source # 
Integral (VkDeviceGroupPresentModeBitmaskKHR FlagMask) Source # 
Typeable FlagType a => Data (VkDeviceGroupPresentModeBitmaskKHR a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkDeviceGroupPresentModeBitmaskKHR a -> c (VkDeviceGroupPresentModeBitmaskKHR a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkDeviceGroupPresentModeBitmaskKHR a) #

toConstr :: VkDeviceGroupPresentModeBitmaskKHR a -> Constr #

dataTypeOf :: VkDeviceGroupPresentModeBitmaskKHR a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkDeviceGroupPresentModeBitmaskKHR a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkDeviceGroupPresentModeBitmaskKHR a)) #

gmapT :: (forall b. Data b => b -> b) -> VkDeviceGroupPresentModeBitmaskKHR a -> VkDeviceGroupPresentModeBitmaskKHR a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkDeviceGroupPresentModeBitmaskKHR a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkDeviceGroupPresentModeBitmaskKHR a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkDeviceGroupPresentModeBitmaskKHR a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkDeviceGroupPresentModeBitmaskKHR a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkDeviceGroupPresentModeBitmaskKHR a -> m (VkDeviceGroupPresentModeBitmaskKHR a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkDeviceGroupPresentModeBitmaskKHR a -> m (VkDeviceGroupPresentModeBitmaskKHR a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkDeviceGroupPresentModeBitmaskKHR a -> m (VkDeviceGroupPresentModeBitmaskKHR a) #

Num (VkDeviceGroupPresentModeBitmaskKHR FlagMask) Source # 
Ord (VkDeviceGroupPresentModeBitmaskKHR a) Source # 
Read (VkDeviceGroupPresentModeBitmaskKHR a) Source # 
Real (VkDeviceGroupPresentModeBitmaskKHR FlagMask) Source # 
Show (VkDeviceGroupPresentModeBitmaskKHR a) Source # 
Generic (VkDeviceGroupPresentModeBitmaskKHR a) Source # 
Storable (VkDeviceGroupPresentModeBitmaskKHR a) Source # 
Bits (VkDeviceGroupPresentModeBitmaskKHR FlagMask) Source # 

Methods

(.&.) :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> VkDeviceGroupPresentModeBitmaskKHR FlagMask -> VkDeviceGroupPresentModeBitmaskKHR FlagMask #

(.|.) :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> VkDeviceGroupPresentModeBitmaskKHR FlagMask -> VkDeviceGroupPresentModeBitmaskKHR FlagMask #

xor :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> VkDeviceGroupPresentModeBitmaskKHR FlagMask -> VkDeviceGroupPresentModeBitmaskKHR FlagMask #

complement :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> VkDeviceGroupPresentModeBitmaskKHR FlagMask #

shift :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> Int -> VkDeviceGroupPresentModeBitmaskKHR FlagMask #

rotate :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> Int -> VkDeviceGroupPresentModeBitmaskKHR FlagMask #

zeroBits :: VkDeviceGroupPresentModeBitmaskKHR FlagMask #

bit :: Int -> VkDeviceGroupPresentModeBitmaskKHR FlagMask #

setBit :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> Int -> VkDeviceGroupPresentModeBitmaskKHR FlagMask #

clearBit :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> Int -> VkDeviceGroupPresentModeBitmaskKHR FlagMask #

complementBit :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> Int -> VkDeviceGroupPresentModeBitmaskKHR FlagMask #

testBit :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> Int -> Bool #

bitSizeMaybe :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> Maybe Int #

bitSize :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> Int #

isSigned :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> Bool #

shiftL :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> Int -> VkDeviceGroupPresentModeBitmaskKHR FlagMask #

unsafeShiftL :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> Int -> VkDeviceGroupPresentModeBitmaskKHR FlagMask #

shiftR :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> Int -> VkDeviceGroupPresentModeBitmaskKHR FlagMask #

unsafeShiftR :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> Int -> VkDeviceGroupPresentModeBitmaskKHR FlagMask #

rotateL :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> Int -> VkDeviceGroupPresentModeBitmaskKHR FlagMask #

rotateR :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> Int -> VkDeviceGroupPresentModeBitmaskKHR FlagMask #

popCount :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> Int #

FiniteBits (VkDeviceGroupPresentModeBitmaskKHR FlagMask) Source # 
type Rep (VkDeviceGroupPresentModeBitmaskKHR a) Source # 
type Rep (VkDeviceGroupPresentModeBitmaskKHR a) = D1 (MetaData "VkDeviceGroupPresentModeBitmaskKHR" "Graphics.Vulkan.Types.Enum.Device" "vulkan-api-1.1.2.1-GcVsfRwwhb24i5dsYq91EC" True) (C1 (MetaCons "VkDeviceGroupPresentModeBitmaskKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

pattern VK_DEVICE_GROUP_PRESENT_MODE_LOCAL_BIT_KHR :: forall a. VkDeviceGroupPresentModeBitmaskKHR a Source #

Present from local memory

bitpos = 0

pattern VK_DEVICE_GROUP_PRESENT_MODE_REMOTE_BIT_KHR :: forall a. VkDeviceGroupPresentModeBitmaskKHR a Source #

Present from remote memory

bitpos = 1

pattern VK_DEVICE_GROUP_PRESENT_MODE_SUM_BIT_KHR :: forall a. VkDeviceGroupPresentModeBitmaskKHR a Source #

Present sum of local and/or remote memory

bitpos = 2

pattern VK_DEVICE_GROUP_PRESENT_MODE_LOCAL_MULTI_DEVICE_BIT_KHR :: forall a. VkDeviceGroupPresentModeBitmaskKHR a Source #

Each physical device presents from local memory

bitpos = 3

newtype VkDeviceQueueCreateBitmask a Source #

Instances

Bounded (VkDeviceQueueCreateBitmask FlagMask) Source # 
Enum (VkDeviceQueueCreateBitmask FlagMask) Source # 
Eq (VkDeviceQueueCreateBitmask a) Source # 
Integral (VkDeviceQueueCreateBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkDeviceQueueCreateBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkDeviceQueueCreateBitmask a -> c (VkDeviceQueueCreateBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkDeviceQueueCreateBitmask a) #

toConstr :: VkDeviceQueueCreateBitmask a -> Constr #

dataTypeOf :: VkDeviceQueueCreateBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkDeviceQueueCreateBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkDeviceQueueCreateBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkDeviceQueueCreateBitmask a -> VkDeviceQueueCreateBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkDeviceQueueCreateBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkDeviceQueueCreateBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkDeviceQueueCreateBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkDeviceQueueCreateBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkDeviceQueueCreateBitmask a -> m (VkDeviceQueueCreateBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkDeviceQueueCreateBitmask a -> m (VkDeviceQueueCreateBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkDeviceQueueCreateBitmask a -> m (VkDeviceQueueCreateBitmask a) #

Num (VkDeviceQueueCreateBitmask FlagMask) Source # 
Ord (VkDeviceQueueCreateBitmask a) Source # 
Read (VkDeviceQueueCreateBitmask a) Source # 
Real (VkDeviceQueueCreateBitmask FlagMask) Source # 
Show (VkDeviceQueueCreateBitmask a) Source # 
Generic (VkDeviceQueueCreateBitmask a) Source # 
Storable (VkDeviceQueueCreateBitmask a) Source # 
Bits (VkDeviceQueueCreateBitmask FlagMask) Source # 

Methods

(.&.) :: VkDeviceQueueCreateBitmask FlagMask -> VkDeviceQueueCreateBitmask FlagMask -> VkDeviceQueueCreateBitmask FlagMask #

(.|.) :: VkDeviceQueueCreateBitmask FlagMask -> VkDeviceQueueCreateBitmask FlagMask -> VkDeviceQueueCreateBitmask FlagMask #

xor :: VkDeviceQueueCreateBitmask FlagMask -> VkDeviceQueueCreateBitmask FlagMask -> VkDeviceQueueCreateBitmask FlagMask #

complement :: VkDeviceQueueCreateBitmask FlagMask -> VkDeviceQueueCreateBitmask FlagMask #

shift :: VkDeviceQueueCreateBitmask FlagMask -> Int -> VkDeviceQueueCreateBitmask FlagMask #

rotate :: VkDeviceQueueCreateBitmask FlagMask -> Int -> VkDeviceQueueCreateBitmask FlagMask #

zeroBits :: VkDeviceQueueCreateBitmask FlagMask #

bit :: Int -> VkDeviceQueueCreateBitmask FlagMask #

setBit :: VkDeviceQueueCreateBitmask FlagMask -> Int -> VkDeviceQueueCreateBitmask FlagMask #

clearBit :: VkDeviceQueueCreateBitmask FlagMask -> Int -> VkDeviceQueueCreateBitmask FlagMask #

complementBit :: VkDeviceQueueCreateBitmask FlagMask -> Int -> VkDeviceQueueCreateBitmask FlagMask #

testBit :: VkDeviceQueueCreateBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkDeviceQueueCreateBitmask FlagMask -> Maybe Int #

bitSize :: VkDeviceQueueCreateBitmask FlagMask -> Int #

isSigned :: VkDeviceQueueCreateBitmask FlagMask -> Bool #

shiftL :: VkDeviceQueueCreateBitmask FlagMask -> Int -> VkDeviceQueueCreateBitmask FlagMask #

unsafeShiftL :: VkDeviceQueueCreateBitmask FlagMask -> Int -> VkDeviceQueueCreateBitmask FlagMask #

shiftR :: VkDeviceQueueCreateBitmask FlagMask -> Int -> VkDeviceQueueCreateBitmask FlagMask #

unsafeShiftR :: VkDeviceQueueCreateBitmask FlagMask -> Int -> VkDeviceQueueCreateBitmask FlagMask #

rotateL :: VkDeviceQueueCreateBitmask FlagMask -> Int -> VkDeviceQueueCreateBitmask FlagMask #

rotateR :: VkDeviceQueueCreateBitmask FlagMask -> Int -> VkDeviceQueueCreateBitmask FlagMask #

popCount :: VkDeviceQueueCreateBitmask FlagMask -> Int #

FiniteBits (VkDeviceQueueCreateBitmask FlagMask) Source # 
type Rep (VkDeviceQueueCreateBitmask a) Source # 
type Rep (VkDeviceQueueCreateBitmask a) = D1 (MetaData "VkDeviceQueueCreateBitmask" "Graphics.Vulkan.Types.Enum.Device" "vulkan-api-1.1.2.1-GcVsfRwwhb24i5dsYq91EC" True) (C1 (MetaCons "VkDeviceQueueCreateBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

data VkImageBlit Source #

typedef struct VkImageBlit {
    VkImageSubresourceLayers srcSubresource;
    VkOffset3D             srcOffsets[2];
    VkImageSubresourceLayers dstSubresource;
    VkOffset3D             dstOffsets[2];
} VkImageBlit;

VkImageBlit registry at www.khronos.org

Instances

Eq VkImageBlit Source # 
Ord VkImageBlit Source # 
Show VkImageBlit Source # 
Storable VkImageBlit Source # 
VulkanMarshalPrim VkImageBlit Source # 
VulkanMarshal VkImageBlit Source # 
CanWriteField "dstSubresource" VkImageBlit Source # 

Methods

writeField :: Ptr VkImageBlit -> FieldType "dstSubresource" VkImageBlit -> IO () Source #

CanWriteField "srcSubresource" VkImageBlit Source # 

Methods

writeField :: Ptr VkImageBlit -> FieldType "srcSubresource" VkImageBlit -> IO () Source #

CanReadField "dstSubresource" VkImageBlit Source # 

Methods

getField :: VkImageBlit -> FieldType "dstSubresource" VkImageBlit Source #

readField :: Ptr VkImageBlit -> IO (FieldType "dstSubresource" VkImageBlit) Source #

CanReadField "srcSubresource" VkImageBlit Source # 

Methods

getField :: VkImageBlit -> FieldType "srcSubresource" VkImageBlit Source #

readField :: Ptr VkImageBlit -> IO (FieldType "srcSubresource" VkImageBlit) Source #

HasField "dstOffsets" VkImageBlit Source # 

Associated Types

type FieldType ("dstOffsets" :: Symbol) VkImageBlit :: Type Source #

type FieldOptional ("dstOffsets" :: Symbol) VkImageBlit :: Bool Source #

type FieldOffset ("dstOffsets" :: Symbol) VkImageBlit :: Nat Source #

type FieldIsArray ("dstOffsets" :: Symbol) VkImageBlit :: Bool Source #

HasField "dstSubresource" VkImageBlit Source # 

Associated Types

type FieldType ("dstSubresource" :: Symbol) VkImageBlit :: Type Source #

type FieldOptional ("dstSubresource" :: Symbol) VkImageBlit :: Bool Source #

type FieldOffset ("dstSubresource" :: Symbol) VkImageBlit :: Nat Source #

type FieldIsArray ("dstSubresource" :: Symbol) VkImageBlit :: Bool Source #

HasField "srcOffsets" VkImageBlit Source # 

Associated Types

type FieldType ("srcOffsets" :: Symbol) VkImageBlit :: Type Source #

type FieldOptional ("srcOffsets" :: Symbol) VkImageBlit :: Bool Source #

type FieldOffset ("srcOffsets" :: Symbol) VkImageBlit :: Nat Source #

type FieldIsArray ("srcOffsets" :: Symbol) VkImageBlit :: Bool Source #

HasField "srcSubresource" VkImageBlit Source # 

Associated Types

type FieldType ("srcSubresource" :: Symbol) VkImageBlit :: Type Source #

type FieldOptional ("srcSubresource" :: Symbol) VkImageBlit :: Bool Source #

type FieldOffset ("srcSubresource" :: Symbol) VkImageBlit :: Nat Source #

type FieldIsArray ("srcSubresource" :: Symbol) VkImageBlit :: Bool Source #

(KnownNat idx, IndexInBounds "dstOffsets" idx VkImageBlit) => CanWriteFieldArray "dstOffsets" idx VkImageBlit Source # 

Methods

writeFieldArray :: Ptr VkImageBlit -> FieldType "dstOffsets" VkImageBlit -> IO () Source #

(KnownNat idx, IndexInBounds "srcOffsets" idx VkImageBlit) => CanWriteFieldArray "srcOffsets" idx VkImageBlit Source # 

Methods

writeFieldArray :: Ptr VkImageBlit -> FieldType "srcOffsets" VkImageBlit -> IO () Source #

(KnownNat idx, IndexInBounds "dstOffsets" idx VkImageBlit) => CanReadFieldArray "dstOffsets" idx VkImageBlit Source # 
(KnownNat idx, IndexInBounds "srcOffsets" idx VkImageBlit) => CanReadFieldArray "srcOffsets" idx VkImageBlit Source # 
type StructFields VkImageBlit Source # 
type StructFields VkImageBlit = (:) Symbol "srcSubresource" ((:) Symbol "srcOffsets" ((:) Symbol "dstSubresource" ((:) Symbol "dstOffsets" ([] Symbol))))
type CUnionType VkImageBlit Source # 
type ReturnedOnly VkImageBlit Source # 
type StructExtends VkImageBlit Source # 
type FieldArrayLength "dstOffsets" VkImageBlit Source # 
type FieldArrayLength "dstOffsets" VkImageBlit = 2
type FieldArrayLength "srcOffsets" VkImageBlit Source # 
type FieldArrayLength "srcOffsets" VkImageBlit = 2
type FieldType "dstOffsets" VkImageBlit Source # 
type FieldType "dstOffsets" VkImageBlit = VkOffset3D
type FieldType "dstSubresource" VkImageBlit Source # 
type FieldType "srcOffsets" VkImageBlit Source # 
type FieldType "srcOffsets" VkImageBlit = VkOffset3D
type FieldType "srcSubresource" VkImageBlit Source # 
type FieldOptional "dstOffsets" VkImageBlit Source # 
type FieldOptional "dstOffsets" VkImageBlit = False
type FieldOptional "dstSubresource" VkImageBlit Source # 
type FieldOptional "dstSubresource" VkImageBlit = False
type FieldOptional "srcOffsets" VkImageBlit Source # 
type FieldOptional "srcOffsets" VkImageBlit = False
type FieldOptional "srcSubresource" VkImageBlit Source # 
type FieldOptional "srcSubresource" VkImageBlit = False
type FieldOffset "dstOffsets" VkImageBlit Source # 
type FieldOffset "dstOffsets" VkImageBlit = 56
type FieldOffset "dstSubresource" VkImageBlit Source # 
type FieldOffset "dstSubresource" VkImageBlit = 40
type FieldOffset "srcOffsets" VkImageBlit Source # 
type FieldOffset "srcOffsets" VkImageBlit = 16
type FieldOffset "srcSubresource" VkImageBlit Source # 
type FieldOffset "srcSubresource" VkImageBlit = 0
type FieldIsArray "dstOffsets" VkImageBlit Source # 
type FieldIsArray "dstOffsets" VkImageBlit = True
type FieldIsArray "dstSubresource" VkImageBlit Source # 
type FieldIsArray "dstSubresource" VkImageBlit = False
type FieldIsArray "srcOffsets" VkImageBlit Source # 
type FieldIsArray "srcOffsets" VkImageBlit = True
type FieldIsArray "srcSubresource" VkImageBlit Source # 
type FieldIsArray "srcSubresource" VkImageBlit = False

data VkImageCopy Source #

typedef struct VkImageCopy {
    VkImageSubresourceLayers srcSubresource;
    VkOffset3D             srcOffset;
    VkImageSubresourceLayers dstSubresource;
    VkOffset3D             dstOffset;
    VkExtent3D             extent;
} VkImageCopy;

VkImageCopy registry at www.khronos.org

Instances

Eq VkImageCopy Source # 
Ord VkImageCopy Source # 
Show VkImageCopy Source # 
Storable VkImageCopy Source # 
VulkanMarshalPrim VkImageCopy Source # 
VulkanMarshal VkImageCopy Source # 
CanWriteField "dstOffset" VkImageCopy Source # 

Methods

writeField :: Ptr VkImageCopy -> FieldType "dstOffset" VkImageCopy -> IO () Source #

CanWriteField "dstSubresource" VkImageCopy Source # 

Methods

writeField :: Ptr VkImageCopy -> FieldType "dstSubresource" VkImageCopy -> IO () Source #

CanWriteField "extent" VkImageCopy Source # 
CanWriteField "srcOffset" VkImageCopy Source # 

Methods

writeField :: Ptr VkImageCopy -> FieldType "srcOffset" VkImageCopy -> IO () Source #

CanWriteField "srcSubresource" VkImageCopy Source # 

Methods

writeField :: Ptr VkImageCopy -> FieldType "srcSubresource" VkImageCopy -> IO () Source #

CanReadField "dstOffset" VkImageCopy Source # 
CanReadField "dstSubresource" VkImageCopy Source # 

Methods

getField :: VkImageCopy -> FieldType "dstSubresource" VkImageCopy Source #

readField :: Ptr VkImageCopy -> IO (FieldType "dstSubresource" VkImageCopy) Source #

CanReadField "extent" VkImageCopy Source # 
CanReadField "srcOffset" VkImageCopy Source # 
CanReadField "srcSubresource" VkImageCopy Source # 

Methods

getField :: VkImageCopy -> FieldType "srcSubresource" VkImageCopy Source #

readField :: Ptr VkImageCopy -> IO (FieldType "srcSubresource" VkImageCopy) Source #

HasField "dstOffset" VkImageCopy Source # 

Associated Types

type FieldType ("dstOffset" :: Symbol) VkImageCopy :: Type Source #

type FieldOptional ("dstOffset" :: Symbol) VkImageCopy :: Bool Source #

type FieldOffset ("dstOffset" :: Symbol) VkImageCopy :: Nat Source #

type FieldIsArray ("dstOffset" :: Symbol) VkImageCopy :: Bool Source #

HasField "dstSubresource" VkImageCopy Source # 

Associated Types

type FieldType ("dstSubresource" :: Symbol) VkImageCopy :: Type Source #

type FieldOptional ("dstSubresource" :: Symbol) VkImageCopy :: Bool Source #

type FieldOffset ("dstSubresource" :: Symbol) VkImageCopy :: Nat Source #

type FieldIsArray ("dstSubresource" :: Symbol) VkImageCopy :: Bool Source #

HasField "extent" VkImageCopy Source # 

Associated Types

type FieldType ("extent" :: Symbol) VkImageCopy :: Type Source #

type FieldOptional ("extent" :: Symbol) VkImageCopy :: Bool Source #

type FieldOffset ("extent" :: Symbol) VkImageCopy :: Nat Source #

type FieldIsArray ("extent" :: Symbol) VkImageCopy :: Bool Source #

HasField "srcOffset" VkImageCopy Source # 

Associated Types

type FieldType ("srcOffset" :: Symbol) VkImageCopy :: Type Source #

type FieldOptional ("srcOffset" :: Symbol) VkImageCopy :: Bool Source #

type FieldOffset ("srcOffset" :: Symbol) VkImageCopy :: Nat Source #

type FieldIsArray ("srcOffset" :: Symbol) VkImageCopy :: Bool Source #

HasField "srcSubresource" VkImageCopy Source # 

Associated Types

type FieldType ("srcSubresource" :: Symbol) VkImageCopy :: Type Source #

type FieldOptional ("srcSubresource" :: Symbol) VkImageCopy :: Bool Source #

type FieldOffset ("srcSubresource" :: Symbol) VkImageCopy :: Nat Source #

type FieldIsArray ("srcSubresource" :: Symbol) VkImageCopy :: Bool Source #

type StructFields VkImageCopy Source # 
type StructFields VkImageCopy = (:) Symbol "srcSubresource" ((:) Symbol "srcOffset" ((:) Symbol "dstSubresource" ((:) Symbol "dstOffset" ((:) Symbol "extent" ([] Symbol)))))
type CUnionType VkImageCopy Source # 
type ReturnedOnly VkImageCopy Source # 
type StructExtends VkImageCopy Source # 
type FieldType "dstOffset" VkImageCopy Source # 
type FieldType "dstOffset" VkImageCopy = VkOffset3D
type FieldType "dstSubresource" VkImageCopy Source # 
type FieldType "extent" VkImageCopy Source # 
type FieldType "srcOffset" VkImageCopy Source # 
type FieldType "srcOffset" VkImageCopy = VkOffset3D
type FieldType "srcSubresource" VkImageCopy Source # 
type FieldOptional "dstOffset" VkImageCopy Source # 
type FieldOptional "dstOffset" VkImageCopy = False
type FieldOptional "dstSubresource" VkImageCopy Source # 
type FieldOptional "dstSubresource" VkImageCopy = False
type FieldOptional "extent" VkImageCopy Source # 
type FieldOptional "srcOffset" VkImageCopy Source # 
type FieldOptional "srcOffset" VkImageCopy = False
type FieldOptional "srcSubresource" VkImageCopy Source # 
type FieldOptional "srcSubresource" VkImageCopy = False
type FieldOffset "dstOffset" VkImageCopy Source # 
type FieldOffset "dstOffset" VkImageCopy = 44
type FieldOffset "dstSubresource" VkImageCopy Source # 
type FieldOffset "dstSubresource" VkImageCopy = 28
type FieldOffset "extent" VkImageCopy Source # 
type FieldOffset "extent" VkImageCopy = 56
type FieldOffset "srcOffset" VkImageCopy Source # 
type FieldOffset "srcOffset" VkImageCopy = 16
type FieldOffset "srcSubresource" VkImageCopy Source # 
type FieldOffset "srcSubresource" VkImageCopy = 0
type FieldIsArray "dstOffset" VkImageCopy Source # 
type FieldIsArray "dstOffset" VkImageCopy = False
type FieldIsArray "dstSubresource" VkImageCopy Source # 
type FieldIsArray "dstSubresource" VkImageCopy = False
type FieldIsArray "extent" VkImageCopy Source # 
type FieldIsArray "srcOffset" VkImageCopy Source # 
type FieldIsArray "srcOffset" VkImageCopy = False
type FieldIsArray "srcSubresource" VkImageCopy Source # 
type FieldIsArray "srcSubresource" VkImageCopy = False

data VkImageCreateInfo Source #

typedef struct VkImageCreateInfo {
    VkStructureType sType;
    const void*            pNext;
    VkImageCreateFlags     flags;
    VkImageType            imageType;
    VkFormat               format;
    VkExtent3D             extent;
    uint32_t               mipLevels;
    uint32_t               arrayLayers;
    VkSampleCountFlagBits  samples;
    VkImageTiling          tiling;
    VkImageUsageFlags      usage;
    VkSharingMode          sharingMode;
    uint32_t               queueFamilyIndexCount;
    const uint32_t*        pQueueFamilyIndices;
    VkImageLayout          initialLayout;
} VkImageCreateInfo;

VkImageCreateInfo registry at www.khronos.org

Instances

Eq VkImageCreateInfo Source # 
Ord VkImageCreateInfo Source # 
Show VkImageCreateInfo Source # 
Storable VkImageCreateInfo Source # 
VulkanMarshalPrim VkImageCreateInfo Source # 
VulkanMarshal VkImageCreateInfo Source # 
CanWriteField "arrayLayers" VkImageCreateInfo Source # 
CanWriteField "extent" VkImageCreateInfo Source # 
CanWriteField "flags" VkImageCreateInfo Source # 
CanWriteField "format" VkImageCreateInfo Source # 
CanWriteField "imageType" VkImageCreateInfo Source # 
CanWriteField "initialLayout" VkImageCreateInfo Source # 
CanWriteField "mipLevels" VkImageCreateInfo Source # 
CanWriteField "pNext" VkImageCreateInfo Source # 
CanWriteField "pQueueFamilyIndices" VkImageCreateInfo Source # 

Methods

writeField :: Ptr VkImageCreateInfo -> FieldType "pQueueFamilyIndices" VkImageCreateInfo -> IO () Source #

CanWriteField "queueFamilyIndexCount" VkImageCreateInfo Source # 

Methods

writeField :: Ptr VkImageCreateInfo -> FieldType "queueFamilyIndexCount" VkImageCreateInfo -> IO () Source #

CanWriteField "sType" VkImageCreateInfo Source # 
CanWriteField "samples" VkImageCreateInfo Source # 
CanWriteField "sharingMode" VkImageCreateInfo Source # 
CanWriteField "tiling" VkImageCreateInfo Source # 
CanWriteField "usage" VkImageCreateInfo Source # 
CanReadField "arrayLayers" VkImageCreateInfo Source # 
CanReadField "extent" VkImageCreateInfo Source # 
CanReadField "flags" VkImageCreateInfo Source # 
CanReadField "format" VkImageCreateInfo Source # 
CanReadField "imageType" VkImageCreateInfo Source # 
CanReadField "initialLayout" VkImageCreateInfo Source # 
CanReadField "mipLevels" VkImageCreateInfo Source # 
CanReadField "pNext" VkImageCreateInfo Source # 
CanReadField "pQueueFamilyIndices" VkImageCreateInfo Source # 
CanReadField "queueFamilyIndexCount" VkImageCreateInfo Source # 
CanReadField "sType" VkImageCreateInfo Source # 
CanReadField "samples" VkImageCreateInfo Source # 
CanReadField "sharingMode" VkImageCreateInfo Source # 
CanReadField "tiling" VkImageCreateInfo Source # 
CanReadField "usage" VkImageCreateInfo Source # 
HasField "arrayLayers" VkImageCreateInfo Source # 

Associated Types

type FieldType ("arrayLayers" :: Symbol) VkImageCreateInfo :: Type Source #

type FieldOptional ("arrayLayers" :: Symbol) VkImageCreateInfo :: Bool Source #

type FieldOffset ("arrayLayers" :: Symbol) VkImageCreateInfo :: Nat Source #

type FieldIsArray ("arrayLayers" :: Symbol) VkImageCreateInfo :: Bool Source #

HasField "extent" VkImageCreateInfo Source # 
HasField "flags" VkImageCreateInfo Source # 
HasField "format" VkImageCreateInfo Source # 
HasField "imageType" VkImageCreateInfo Source # 

Associated Types

type FieldType ("imageType" :: Symbol) VkImageCreateInfo :: Type Source #

type FieldOptional ("imageType" :: Symbol) VkImageCreateInfo :: Bool Source #

type FieldOffset ("imageType" :: Symbol) VkImageCreateInfo :: Nat Source #

type FieldIsArray ("imageType" :: Symbol) VkImageCreateInfo :: Bool Source #

HasField "initialLayout" VkImageCreateInfo Source # 

Associated Types

type FieldType ("initialLayout" :: Symbol) VkImageCreateInfo :: Type Source #

type FieldOptional ("initialLayout" :: Symbol) VkImageCreateInfo :: Bool Source #

type FieldOffset ("initialLayout" :: Symbol) VkImageCreateInfo :: Nat Source #

type FieldIsArray ("initialLayout" :: Symbol) VkImageCreateInfo :: Bool Source #

HasField "mipLevels" VkImageCreateInfo Source # 

Associated Types

type FieldType ("mipLevels" :: Symbol) VkImageCreateInfo :: Type Source #

type FieldOptional ("mipLevels" :: Symbol) VkImageCreateInfo :: Bool Source #

type FieldOffset ("mipLevels" :: Symbol) VkImageCreateInfo :: Nat Source #

type FieldIsArray ("mipLevels" :: Symbol) VkImageCreateInfo :: Bool Source #

HasField "pNext" VkImageCreateInfo Source # 
HasField "pQueueFamilyIndices" VkImageCreateInfo Source # 

Associated Types

type FieldType ("pQueueFamilyIndices" :: Symbol) VkImageCreateInfo :: Type Source #

type FieldOptional ("pQueueFamilyIndices" :: Symbol) VkImageCreateInfo :: Bool Source #

type FieldOffset ("pQueueFamilyIndices" :: Symbol) VkImageCreateInfo :: Nat Source #

type FieldIsArray ("pQueueFamilyIndices" :: Symbol) VkImageCreateInfo :: Bool Source #

HasField "queueFamilyIndexCount" VkImageCreateInfo Source # 

Associated Types

type FieldType ("queueFamilyIndexCount" :: Symbol) VkImageCreateInfo :: Type Source #

type FieldOptional ("queueFamilyIndexCount" :: Symbol) VkImageCreateInfo :: Bool Source #

type FieldOffset ("queueFamilyIndexCount" :: Symbol) VkImageCreateInfo :: Nat Source #

type FieldIsArray ("queueFamilyIndexCount" :: Symbol) VkImageCreateInfo :: Bool Source #

HasField "sType" VkImageCreateInfo Source # 
HasField "samples" VkImageCreateInfo Source # 
HasField "sharingMode" VkImageCreateInfo Source # 

Associated Types

type FieldType ("sharingMode" :: Symbol) VkImageCreateInfo :: Type Source #

type FieldOptional ("sharingMode" :: Symbol) VkImageCreateInfo :: Bool Source #

type FieldOffset ("sharingMode" :: Symbol) VkImageCreateInfo :: Nat Source #

type FieldIsArray ("sharingMode" :: Symbol) VkImageCreateInfo :: Bool Source #

HasField "tiling" VkImageCreateInfo Source # 
HasField "usage" VkImageCreateInfo Source # 
type StructFields VkImageCreateInfo Source # 
type StructFields VkImageCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "imageType" ((:) Symbol "format" ((:) Symbol "extent" ((:) Symbol "mipLevels" ((:) Symbol "arrayLayers" ((:) Symbol "samples" ((:) Symbol "tiling" ((:) Symbol "usage" ((:) Symbol "sharingMode" ((:) Symbol "queueFamilyIndexCount" ((:) Symbol "pQueueFamilyIndices" ((:) Symbol "initialLayout" ([] Symbol)))))))))))))))
type CUnionType VkImageCreateInfo Source # 
type ReturnedOnly VkImageCreateInfo Source # 
type StructExtends VkImageCreateInfo Source # 
type FieldType "arrayLayers" VkImageCreateInfo Source # 
type FieldType "arrayLayers" VkImageCreateInfo = Word32
type FieldType "extent" VkImageCreateInfo Source # 
type FieldType "flags" VkImageCreateInfo Source # 
type FieldType "format" VkImageCreateInfo Source # 
type FieldType "imageType" VkImageCreateInfo Source # 
type FieldType "initialLayout" VkImageCreateInfo Source # 
type FieldType "mipLevels" VkImageCreateInfo Source # 
type FieldType "pNext" VkImageCreateInfo Source # 
type FieldType "pQueueFamilyIndices" VkImageCreateInfo Source # 
type FieldType "pQueueFamilyIndices" VkImageCreateInfo = Ptr Word32
type FieldType "queueFamilyIndexCount" VkImageCreateInfo Source # 
type FieldType "queueFamilyIndexCount" VkImageCreateInfo = Word32
type FieldType "sType" VkImageCreateInfo Source # 
type FieldType "samples" VkImageCreateInfo Source # 
type FieldType "sharingMode" VkImageCreateInfo Source # 
type FieldType "tiling" VkImageCreateInfo Source # 
type FieldType "usage" VkImageCreateInfo Source # 
type FieldOptional "arrayLayers" VkImageCreateInfo Source # 
type FieldOptional "extent" VkImageCreateInfo Source # 
type FieldOptional "flags" VkImageCreateInfo Source # 
type FieldOptional "format" VkImageCreateInfo Source # 
type FieldOptional "imageType" VkImageCreateInfo Source # 
type FieldOptional "initialLayout" VkImageCreateInfo Source # 
type FieldOptional "initialLayout" VkImageCreateInfo = False
type FieldOptional "mipLevels" VkImageCreateInfo Source # 
type FieldOptional "pNext" VkImageCreateInfo Source # 
type FieldOptional "pQueueFamilyIndices" VkImageCreateInfo Source # 
type FieldOptional "pQueueFamilyIndices" VkImageCreateInfo = False
type FieldOptional "queueFamilyIndexCount" VkImageCreateInfo Source # 
type FieldOptional "queueFamilyIndexCount" VkImageCreateInfo = True
type FieldOptional "sType" VkImageCreateInfo Source # 
type FieldOptional "samples" VkImageCreateInfo Source # 
type FieldOptional "sharingMode" VkImageCreateInfo Source # 
type FieldOptional "tiling" VkImageCreateInfo Source # 
type FieldOptional "usage" VkImageCreateInfo Source # 
type FieldOffset "arrayLayers" VkImageCreateInfo Source # 
type FieldOffset "arrayLayers" VkImageCreateInfo = 44
type FieldOffset "extent" VkImageCreateInfo Source # 
type FieldOffset "extent" VkImageCreateInfo = 28
type FieldOffset "flags" VkImageCreateInfo Source # 
type FieldOffset "flags" VkImageCreateInfo = 16
type FieldOffset "format" VkImageCreateInfo Source # 
type FieldOffset "format" VkImageCreateInfo = 24
type FieldOffset "imageType" VkImageCreateInfo Source # 
type FieldOffset "imageType" VkImageCreateInfo = 20
type FieldOffset "initialLayout" VkImageCreateInfo Source # 
type FieldOffset "initialLayout" VkImageCreateInfo = 80
type FieldOffset "mipLevels" VkImageCreateInfo Source # 
type FieldOffset "mipLevels" VkImageCreateInfo = 40
type FieldOffset "pNext" VkImageCreateInfo Source # 
type FieldOffset "pQueueFamilyIndices" VkImageCreateInfo Source # 
type FieldOffset "pQueueFamilyIndices" VkImageCreateInfo = 72
type FieldOffset "queueFamilyIndexCount" VkImageCreateInfo Source # 
type FieldOffset "queueFamilyIndexCount" VkImageCreateInfo = 64
type FieldOffset "sType" VkImageCreateInfo Source # 
type FieldOffset "samples" VkImageCreateInfo Source # 
type FieldOffset "samples" VkImageCreateInfo = 48
type FieldOffset "sharingMode" VkImageCreateInfo Source # 
type FieldOffset "sharingMode" VkImageCreateInfo = 60
type FieldOffset "tiling" VkImageCreateInfo Source # 
type FieldOffset "tiling" VkImageCreateInfo = 52
type FieldOffset "usage" VkImageCreateInfo Source # 
type FieldOffset "usage" VkImageCreateInfo = 56
type FieldIsArray "arrayLayers" VkImageCreateInfo Source # 
type FieldIsArray "arrayLayers" VkImageCreateInfo = False
type FieldIsArray "extent" VkImageCreateInfo Source # 
type FieldIsArray "flags" VkImageCreateInfo Source # 
type FieldIsArray "format" VkImageCreateInfo Source # 
type FieldIsArray "imageType" VkImageCreateInfo Source # 
type FieldIsArray "initialLayout" VkImageCreateInfo Source # 
type FieldIsArray "initialLayout" VkImageCreateInfo = False
type FieldIsArray "mipLevels" VkImageCreateInfo Source # 
type FieldIsArray "pNext" VkImageCreateInfo Source # 
type FieldIsArray "pQueueFamilyIndices" VkImageCreateInfo Source # 
type FieldIsArray "pQueueFamilyIndices" VkImageCreateInfo = False
type FieldIsArray "queueFamilyIndexCount" VkImageCreateInfo Source # 
type FieldIsArray "queueFamilyIndexCount" VkImageCreateInfo = False
type FieldIsArray "sType" VkImageCreateInfo Source # 
type FieldIsArray "samples" VkImageCreateInfo Source # 
type FieldIsArray "sharingMode" VkImageCreateInfo Source # 
type FieldIsArray "sharingMode" VkImageCreateInfo = False
type FieldIsArray "tiling" VkImageCreateInfo Source # 
type FieldIsArray "usage" VkImageCreateInfo Source # 

data VkImageFormatListCreateInfoKHR Source #

typedef struct VkImageFormatListCreateInfoKHR {
    VkStructureType sType;
    const void*            pNext;
    uint32_t               viewFormatCount;
    const VkFormat*      pViewFormats;
} VkImageFormatListCreateInfoKHR;

VkImageFormatListCreateInfoKHR registry at www.khronos.org

Instances

Eq VkImageFormatListCreateInfoKHR Source # 
Ord VkImageFormatListCreateInfoKHR Source # 
Show VkImageFormatListCreateInfoKHR Source # 
Storable VkImageFormatListCreateInfoKHR Source # 
VulkanMarshalPrim VkImageFormatListCreateInfoKHR Source # 
VulkanMarshal VkImageFormatListCreateInfoKHR Source # 
CanWriteField "pNext" VkImageFormatListCreateInfoKHR Source # 
CanWriteField "pViewFormats" VkImageFormatListCreateInfoKHR Source # 
CanWriteField "sType" VkImageFormatListCreateInfoKHR Source # 
CanWriteField "viewFormatCount" VkImageFormatListCreateInfoKHR Source # 
CanReadField "pNext" VkImageFormatListCreateInfoKHR Source # 
CanReadField "pViewFormats" VkImageFormatListCreateInfoKHR Source # 
CanReadField "sType" VkImageFormatListCreateInfoKHR Source # 
CanReadField "viewFormatCount" VkImageFormatListCreateInfoKHR Source # 
HasField "pNext" VkImageFormatListCreateInfoKHR Source # 
HasField "pViewFormats" VkImageFormatListCreateInfoKHR Source # 
HasField "sType" VkImageFormatListCreateInfoKHR Source # 
HasField "viewFormatCount" VkImageFormatListCreateInfoKHR Source # 
type StructFields VkImageFormatListCreateInfoKHR Source # 
type StructFields VkImageFormatListCreateInfoKHR = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "viewFormatCount" ((:) Symbol "pViewFormats" ([] Symbol))))
type CUnionType VkImageFormatListCreateInfoKHR Source # 
type ReturnedOnly VkImageFormatListCreateInfoKHR Source # 
type StructExtends VkImageFormatListCreateInfoKHR Source # 
type FieldType "pNext" VkImageFormatListCreateInfoKHR Source # 
type FieldType "pViewFormats" VkImageFormatListCreateInfoKHR Source # 
type FieldType "sType" VkImageFormatListCreateInfoKHR Source # 
type FieldType "viewFormatCount" VkImageFormatListCreateInfoKHR Source # 
type FieldOptional "pNext" VkImageFormatListCreateInfoKHR Source # 
type FieldOptional "pViewFormats" VkImageFormatListCreateInfoKHR Source # 
type FieldOptional "sType" VkImageFormatListCreateInfoKHR Source # 
type FieldOptional "viewFormatCount" VkImageFormatListCreateInfoKHR Source # 
type FieldOffset "pNext" VkImageFormatListCreateInfoKHR Source # 
type FieldOffset "pViewFormats" VkImageFormatListCreateInfoKHR Source # 
type FieldOffset "sType" VkImageFormatListCreateInfoKHR Source # 
type FieldOffset "viewFormatCount" VkImageFormatListCreateInfoKHR Source # 
type FieldOffset "viewFormatCount" VkImageFormatListCreateInfoKHR = 16
type FieldIsArray "pNext" VkImageFormatListCreateInfoKHR Source # 
type FieldIsArray "pViewFormats" VkImageFormatListCreateInfoKHR Source # 
type FieldIsArray "sType" VkImageFormatListCreateInfoKHR Source # 
type FieldIsArray "viewFormatCount" VkImageFormatListCreateInfoKHR Source # 

data VkImageFormatProperties Source #

typedef struct VkImageFormatProperties {
    VkExtent3D             maxExtent;
    uint32_t               maxMipLevels;
    uint32_t               maxArrayLayers;
    VkSampleCountFlags     sampleCounts;
    VkDeviceSize           maxResourceSize;
} VkImageFormatProperties;

VkImageFormatProperties registry at www.khronos.org

Instances

Eq VkImageFormatProperties Source # 
Ord VkImageFormatProperties Source # 
Show VkImageFormatProperties Source # 
Storable VkImageFormatProperties Source # 
VulkanMarshalPrim VkImageFormatProperties Source # 
VulkanMarshal VkImageFormatProperties Source # 
CanWriteField "maxArrayLayers" VkImageFormatProperties Source # 
CanWriteField "maxExtent" VkImageFormatProperties Source # 
CanWriteField "maxMipLevels" VkImageFormatProperties Source # 
CanWriteField "maxResourceSize" VkImageFormatProperties Source # 
CanWriteField "sampleCounts" VkImageFormatProperties Source # 
CanReadField "maxArrayLayers" VkImageFormatProperties Source # 
CanReadField "maxExtent" VkImageFormatProperties Source # 
CanReadField "maxMipLevels" VkImageFormatProperties Source # 
CanReadField "maxResourceSize" VkImageFormatProperties Source # 
CanReadField "sampleCounts" VkImageFormatProperties Source # 
HasField "maxArrayLayers" VkImageFormatProperties Source # 

Associated Types

type FieldType ("maxArrayLayers" :: Symbol) VkImageFormatProperties :: Type Source #

type FieldOptional ("maxArrayLayers" :: Symbol) VkImageFormatProperties :: Bool Source #

type FieldOffset ("maxArrayLayers" :: Symbol) VkImageFormatProperties :: Nat Source #

type FieldIsArray ("maxArrayLayers" :: Symbol) VkImageFormatProperties :: Bool Source #

HasField "maxExtent" VkImageFormatProperties Source # 
HasField "maxMipLevels" VkImageFormatProperties Source # 

Associated Types

type FieldType ("maxMipLevels" :: Symbol) VkImageFormatProperties :: Type Source #

type FieldOptional ("maxMipLevels" :: Symbol) VkImageFormatProperties :: Bool Source #

type FieldOffset ("maxMipLevels" :: Symbol) VkImageFormatProperties :: Nat Source #

type FieldIsArray ("maxMipLevels" :: Symbol) VkImageFormatProperties :: Bool Source #

HasField "maxResourceSize" VkImageFormatProperties Source # 

Associated Types

type FieldType ("maxResourceSize" :: Symbol) VkImageFormatProperties :: Type Source #

type FieldOptional ("maxResourceSize" :: Symbol) VkImageFormatProperties :: Bool Source #

type FieldOffset ("maxResourceSize" :: Symbol) VkImageFormatProperties :: Nat Source #

type FieldIsArray ("maxResourceSize" :: Symbol) VkImageFormatProperties :: Bool Source #

HasField "sampleCounts" VkImageFormatProperties Source # 

Associated Types

type FieldType ("sampleCounts" :: Symbol) VkImageFormatProperties :: Type Source #

type FieldOptional ("sampleCounts" :: Symbol) VkImageFormatProperties :: Bool Source #

type FieldOffset ("sampleCounts" :: Symbol) VkImageFormatProperties :: Nat Source #

type FieldIsArray ("sampleCounts" :: Symbol) VkImageFormatProperties :: Bool Source #

type StructFields VkImageFormatProperties Source # 
type StructFields VkImageFormatProperties = (:) Symbol "maxExtent" ((:) Symbol "maxMipLevels" ((:) Symbol "maxArrayLayers" ((:) Symbol "sampleCounts" ((:) Symbol "maxResourceSize" ([] Symbol)))))
type CUnionType VkImageFormatProperties Source # 
type ReturnedOnly VkImageFormatProperties Source # 
type StructExtends VkImageFormatProperties Source # 
type FieldType "maxArrayLayers" VkImageFormatProperties Source # 
type FieldType "maxArrayLayers" VkImageFormatProperties = Word32
type FieldType "maxExtent" VkImageFormatProperties Source # 
type FieldType "maxMipLevels" VkImageFormatProperties Source # 
type FieldType "maxResourceSize" VkImageFormatProperties Source # 
type FieldType "sampleCounts" VkImageFormatProperties Source # 
type FieldOptional "maxArrayLayers" VkImageFormatProperties Source # 
type FieldOptional "maxExtent" VkImageFormatProperties Source # 
type FieldOptional "maxMipLevels" VkImageFormatProperties Source # 
type FieldOptional "maxResourceSize" VkImageFormatProperties Source # 
type FieldOptional "sampleCounts" VkImageFormatProperties Source # 
type FieldOffset "maxArrayLayers" VkImageFormatProperties Source # 
type FieldOffset "maxArrayLayers" VkImageFormatProperties = 16
type FieldOffset "maxExtent" VkImageFormatProperties Source # 
type FieldOffset "maxMipLevels" VkImageFormatProperties Source # 
type FieldOffset "maxMipLevels" VkImageFormatProperties = 12
type FieldOffset "maxResourceSize" VkImageFormatProperties Source # 
type FieldOffset "maxResourceSize" VkImageFormatProperties = 24
type FieldOffset "sampleCounts" VkImageFormatProperties Source # 
type FieldOffset "sampleCounts" VkImageFormatProperties = 20
type FieldIsArray "maxArrayLayers" VkImageFormatProperties Source # 
type FieldIsArray "maxExtent" VkImageFormatProperties Source # 
type FieldIsArray "maxMipLevels" VkImageFormatProperties Source # 
type FieldIsArray "maxResourceSize" VkImageFormatProperties Source # 
type FieldIsArray "maxResourceSize" VkImageFormatProperties = False
type FieldIsArray "sampleCounts" VkImageFormatProperties Source # 

data VkImageFormatProperties2 Source #

typedef struct VkImageFormatProperties2 {
    VkStructureType sType;
    void* pNext;
    VkImageFormatProperties          imageFormatProperties;
} VkImageFormatProperties2;

VkImageFormatProperties2 registry at www.khronos.org

Instances

Eq VkImageFormatProperties2 Source # 
Ord VkImageFormatProperties2 Source # 
Show VkImageFormatProperties2 Source # 
Storable VkImageFormatProperties2 Source # 
VulkanMarshalPrim VkImageFormatProperties2 Source # 
VulkanMarshal VkImageFormatProperties2 Source # 
CanWriteField "imageFormatProperties" VkImageFormatProperties2 Source # 
CanWriteField "pNext" VkImageFormatProperties2 Source # 
CanWriteField "sType" VkImageFormatProperties2 Source # 
CanReadField "imageFormatProperties" VkImageFormatProperties2 Source # 
CanReadField "pNext" VkImageFormatProperties2 Source # 
CanReadField "sType" VkImageFormatProperties2 Source # 
HasField "imageFormatProperties" VkImageFormatProperties2 Source # 

Associated Types

type FieldType ("imageFormatProperties" :: Symbol) VkImageFormatProperties2 :: Type Source #

type FieldOptional ("imageFormatProperties" :: Symbol) VkImageFormatProperties2 :: Bool Source #

type FieldOffset ("imageFormatProperties" :: Symbol) VkImageFormatProperties2 :: Nat Source #

type FieldIsArray ("imageFormatProperties" :: Symbol) VkImageFormatProperties2 :: Bool Source #

HasField "pNext" VkImageFormatProperties2 Source # 
HasField "sType" VkImageFormatProperties2 Source # 
type StructFields VkImageFormatProperties2 Source # 
type StructFields VkImageFormatProperties2 = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "imageFormatProperties" ([] Symbol)))
type CUnionType VkImageFormatProperties2 Source # 
type ReturnedOnly VkImageFormatProperties2 Source # 
type StructExtends VkImageFormatProperties2 Source # 
type FieldType "imageFormatProperties" VkImageFormatProperties2 Source # 
type FieldType "pNext" VkImageFormatProperties2 Source # 
type FieldType "sType" VkImageFormatProperties2 Source # 
type FieldOptional "imageFormatProperties" VkImageFormatProperties2 Source # 
type FieldOptional "imageFormatProperties" VkImageFormatProperties2 = False
type FieldOptional "pNext" VkImageFormatProperties2 Source # 
type FieldOptional "sType" VkImageFormatProperties2 Source # 
type FieldOffset "imageFormatProperties" VkImageFormatProperties2 Source # 
type FieldOffset "imageFormatProperties" VkImageFormatProperties2 = 16
type FieldOffset "pNext" VkImageFormatProperties2 Source # 
type FieldOffset "sType" VkImageFormatProperties2 Source # 
type FieldIsArray "imageFormatProperties" VkImageFormatProperties2 Source # 
type FieldIsArray "imageFormatProperties" VkImageFormatProperties2 = False
type FieldIsArray "pNext" VkImageFormatProperties2 Source # 
type FieldIsArray "sType" VkImageFormatProperties2 Source # 

data VkImageMemoryBarrier Source #

typedef struct VkImageMemoryBarrier {
    VkStructureType sType;
    const void*            pNext;
    VkAccessFlags          srcAccessMask;
    VkAccessFlags          dstAccessMask;
    VkImageLayout          oldLayout;
    VkImageLayout          newLayout;
    uint32_t               srcQueueFamilyIndex;
    uint32_t               dstQueueFamilyIndex;
    VkImage                image;
    VkImageSubresourceRange subresourceRange;
} VkImageMemoryBarrier;

VkImageMemoryBarrier registry at www.khronos.org

Instances

Eq VkImageMemoryBarrier Source # 
Ord VkImageMemoryBarrier Source # 
Show VkImageMemoryBarrier Source # 
Storable VkImageMemoryBarrier Source # 
VulkanMarshalPrim VkImageMemoryBarrier Source # 
VulkanMarshal VkImageMemoryBarrier Source # 
CanWriteField "dstAccessMask" VkImageMemoryBarrier Source # 
CanWriteField "dstQueueFamilyIndex" VkImageMemoryBarrier Source # 

Methods

writeField :: Ptr VkImageMemoryBarrier -> FieldType "dstQueueFamilyIndex" VkImageMemoryBarrier -> IO () Source #

CanWriteField "image" VkImageMemoryBarrier Source # 
CanWriteField "newLayout" VkImageMemoryBarrier Source # 
CanWriteField "oldLayout" VkImageMemoryBarrier Source # 
CanWriteField "pNext" VkImageMemoryBarrier Source # 
CanWriteField "sType" VkImageMemoryBarrier Source # 
CanWriteField "srcAccessMask" VkImageMemoryBarrier Source # 
CanWriteField "srcQueueFamilyIndex" VkImageMemoryBarrier Source # 

Methods

writeField :: Ptr VkImageMemoryBarrier -> FieldType "srcQueueFamilyIndex" VkImageMemoryBarrier -> IO () Source #

CanWriteField "subresourceRange" VkImageMemoryBarrier Source # 
CanReadField "dstAccessMask" VkImageMemoryBarrier Source # 
CanReadField "dstQueueFamilyIndex" VkImageMemoryBarrier Source # 
CanReadField "image" VkImageMemoryBarrier Source # 
CanReadField "newLayout" VkImageMemoryBarrier Source # 
CanReadField "oldLayout" VkImageMemoryBarrier Source # 
CanReadField "pNext" VkImageMemoryBarrier Source # 
CanReadField "sType" VkImageMemoryBarrier Source # 
CanReadField "srcAccessMask" VkImageMemoryBarrier Source # 
CanReadField "srcQueueFamilyIndex" VkImageMemoryBarrier Source # 
CanReadField "subresourceRange" VkImageMemoryBarrier Source # 
HasField "dstAccessMask" VkImageMemoryBarrier Source # 

Associated Types

type FieldType ("dstAccessMask" :: Symbol) VkImageMemoryBarrier :: Type Source #

type FieldOptional ("dstAccessMask" :: Symbol) VkImageMemoryBarrier :: Bool Source #

type FieldOffset ("dstAccessMask" :: Symbol) VkImageMemoryBarrier :: Nat Source #

type FieldIsArray ("dstAccessMask" :: Symbol) VkImageMemoryBarrier :: Bool Source #

HasField "dstQueueFamilyIndex" VkImageMemoryBarrier Source # 

Associated Types

type FieldType ("dstQueueFamilyIndex" :: Symbol) VkImageMemoryBarrier :: Type Source #

type FieldOptional ("dstQueueFamilyIndex" :: Symbol) VkImageMemoryBarrier :: Bool Source #

type FieldOffset ("dstQueueFamilyIndex" :: Symbol) VkImageMemoryBarrier :: Nat Source #

type FieldIsArray ("dstQueueFamilyIndex" :: Symbol) VkImageMemoryBarrier :: Bool Source #

HasField "image" VkImageMemoryBarrier Source # 
HasField "newLayout" VkImageMemoryBarrier Source # 
HasField "oldLayout" VkImageMemoryBarrier Source # 
HasField "pNext" VkImageMemoryBarrier Source # 
HasField "sType" VkImageMemoryBarrier Source # 
HasField "srcAccessMask" VkImageMemoryBarrier Source # 

Associated Types

type FieldType ("srcAccessMask" :: Symbol) VkImageMemoryBarrier :: Type Source #

type FieldOptional ("srcAccessMask" :: Symbol) VkImageMemoryBarrier :: Bool Source #

type FieldOffset ("srcAccessMask" :: Symbol) VkImageMemoryBarrier :: Nat Source #

type FieldIsArray ("srcAccessMask" :: Symbol) VkImageMemoryBarrier :: Bool Source #

HasField "srcQueueFamilyIndex" VkImageMemoryBarrier Source # 

Associated Types

type FieldType ("srcQueueFamilyIndex" :: Symbol) VkImageMemoryBarrier :: Type Source #

type FieldOptional ("srcQueueFamilyIndex" :: Symbol) VkImageMemoryBarrier :: Bool Source #

type FieldOffset ("srcQueueFamilyIndex" :: Symbol) VkImageMemoryBarrier :: Nat Source #

type FieldIsArray ("srcQueueFamilyIndex" :: Symbol) VkImageMemoryBarrier :: Bool Source #

HasField "subresourceRange" VkImageMemoryBarrier Source # 

Associated Types

type FieldType ("subresourceRange" :: Symbol) VkImageMemoryBarrier :: Type Source #

type FieldOptional ("subresourceRange" :: Symbol) VkImageMemoryBarrier :: Bool Source #

type FieldOffset ("subresourceRange" :: Symbol) VkImageMemoryBarrier :: Nat Source #

type FieldIsArray ("subresourceRange" :: Symbol) VkImageMemoryBarrier :: Bool Source #

type StructFields VkImageMemoryBarrier Source # 
type StructFields VkImageMemoryBarrier = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "srcAccessMask" ((:) Symbol "dstAccessMask" ((:) Symbol "oldLayout" ((:) Symbol "newLayout" ((:) Symbol "srcQueueFamilyIndex" ((:) Symbol "dstQueueFamilyIndex" ((:) Symbol "image" ((:) Symbol "subresourceRange" ([] Symbol))))))))))
type CUnionType VkImageMemoryBarrier Source # 
type ReturnedOnly VkImageMemoryBarrier Source # 
type StructExtends VkImageMemoryBarrier Source # 
type FieldType "dstAccessMask" VkImageMemoryBarrier Source # 
type FieldType "dstQueueFamilyIndex" VkImageMemoryBarrier Source # 
type FieldType "dstQueueFamilyIndex" VkImageMemoryBarrier = Word32
type FieldType "image" VkImageMemoryBarrier Source # 
type FieldType "newLayout" VkImageMemoryBarrier Source # 
type FieldType "oldLayout" VkImageMemoryBarrier Source # 
type FieldType "pNext" VkImageMemoryBarrier Source # 
type FieldType "sType" VkImageMemoryBarrier Source # 
type FieldType "srcAccessMask" VkImageMemoryBarrier Source # 
type FieldType "srcQueueFamilyIndex" VkImageMemoryBarrier Source # 
type FieldType "srcQueueFamilyIndex" VkImageMemoryBarrier = Word32
type FieldType "subresourceRange" VkImageMemoryBarrier Source # 
type FieldOptional "dstAccessMask" VkImageMemoryBarrier Source # 
type FieldOptional "dstAccessMask" VkImageMemoryBarrier = True
type FieldOptional "dstQueueFamilyIndex" VkImageMemoryBarrier Source # 
type FieldOptional "dstQueueFamilyIndex" VkImageMemoryBarrier = False
type FieldOptional "image" VkImageMemoryBarrier Source # 
type FieldOptional "newLayout" VkImageMemoryBarrier Source # 
type FieldOptional "oldLayout" VkImageMemoryBarrier Source # 
type FieldOptional "pNext" VkImageMemoryBarrier Source # 
type FieldOptional "sType" VkImageMemoryBarrier Source # 
type FieldOptional "srcAccessMask" VkImageMemoryBarrier Source # 
type FieldOptional "srcAccessMask" VkImageMemoryBarrier = True
type FieldOptional "srcQueueFamilyIndex" VkImageMemoryBarrier Source # 
type FieldOptional "srcQueueFamilyIndex" VkImageMemoryBarrier = False
type FieldOptional "subresourceRange" VkImageMemoryBarrier Source # 
type FieldOptional "subresourceRange" VkImageMemoryBarrier = False
type FieldOffset "dstAccessMask" VkImageMemoryBarrier Source # 
type FieldOffset "dstAccessMask" VkImageMemoryBarrier = 20
type FieldOffset "dstQueueFamilyIndex" VkImageMemoryBarrier Source # 
type FieldOffset "dstQueueFamilyIndex" VkImageMemoryBarrier = 36
type FieldOffset "image" VkImageMemoryBarrier Source # 
type FieldOffset "newLayout" VkImageMemoryBarrier Source # 
type FieldOffset "newLayout" VkImageMemoryBarrier = 28
type FieldOffset "oldLayout" VkImageMemoryBarrier Source # 
type FieldOffset "oldLayout" VkImageMemoryBarrier = 24
type FieldOffset "pNext" VkImageMemoryBarrier Source # 
type FieldOffset "sType" VkImageMemoryBarrier Source # 
type FieldOffset "srcAccessMask" VkImageMemoryBarrier Source # 
type FieldOffset "srcAccessMask" VkImageMemoryBarrier = 16
type FieldOffset "srcQueueFamilyIndex" VkImageMemoryBarrier Source # 
type FieldOffset "srcQueueFamilyIndex" VkImageMemoryBarrier = 32
type FieldOffset "subresourceRange" VkImageMemoryBarrier Source # 
type FieldOffset "subresourceRange" VkImageMemoryBarrier = 48
type FieldIsArray "dstAccessMask" VkImageMemoryBarrier Source # 
type FieldIsArray "dstAccessMask" VkImageMemoryBarrier = False
type FieldIsArray "dstQueueFamilyIndex" VkImageMemoryBarrier Source # 
type FieldIsArray "dstQueueFamilyIndex" VkImageMemoryBarrier = False
type FieldIsArray "image" VkImageMemoryBarrier Source # 
type FieldIsArray "newLayout" VkImageMemoryBarrier Source # 
type FieldIsArray "oldLayout" VkImageMemoryBarrier Source # 
type FieldIsArray "pNext" VkImageMemoryBarrier Source # 
type FieldIsArray "sType" VkImageMemoryBarrier Source # 
type FieldIsArray "srcAccessMask" VkImageMemoryBarrier Source # 
type FieldIsArray "srcAccessMask" VkImageMemoryBarrier = False
type FieldIsArray "srcQueueFamilyIndex" VkImageMemoryBarrier Source # 
type FieldIsArray "srcQueueFamilyIndex" VkImageMemoryBarrier = False
type FieldIsArray "subresourceRange" VkImageMemoryBarrier Source # 
type FieldIsArray "subresourceRange" VkImageMemoryBarrier = False

data VkImageMemoryRequirementsInfo2 Source #

typedef struct VkImageMemoryRequirementsInfo2 {
    VkStructureType sType;
    const void*                                                          pNext;
    VkImage                                                              image;
} VkImageMemoryRequirementsInfo2;

VkImageMemoryRequirementsInfo2 registry at www.khronos.org

Instances

Eq VkImageMemoryRequirementsInfo2 Source # 
Ord VkImageMemoryRequirementsInfo2 Source # 
Show VkImageMemoryRequirementsInfo2 Source # 
Storable VkImageMemoryRequirementsInfo2 Source # 
VulkanMarshalPrim VkImageMemoryRequirementsInfo2 Source # 
VulkanMarshal VkImageMemoryRequirementsInfo2 Source # 
CanWriteField "image" VkImageMemoryRequirementsInfo2 Source # 
CanWriteField "pNext" VkImageMemoryRequirementsInfo2 Source # 
CanWriteField "sType" VkImageMemoryRequirementsInfo2 Source # 
CanReadField "image" VkImageMemoryRequirementsInfo2 Source # 
CanReadField "pNext" VkImageMemoryRequirementsInfo2 Source # 
CanReadField "sType" VkImageMemoryRequirementsInfo2 Source # 
HasField "image" VkImageMemoryRequirementsInfo2 Source # 
HasField "pNext" VkImageMemoryRequirementsInfo2 Source # 
HasField "sType" VkImageMemoryRequirementsInfo2 Source # 
type StructFields VkImageMemoryRequirementsInfo2 Source # 
type StructFields VkImageMemoryRequirementsInfo2 = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "image" ([] Symbol)))
type CUnionType VkImageMemoryRequirementsInfo2 Source # 
type ReturnedOnly VkImageMemoryRequirementsInfo2 Source # 
type StructExtends VkImageMemoryRequirementsInfo2 Source # 
type FieldType "image" VkImageMemoryRequirementsInfo2 Source # 
type FieldType "pNext" VkImageMemoryRequirementsInfo2 Source # 
type FieldType "sType" VkImageMemoryRequirementsInfo2 Source # 
type FieldOptional "image" VkImageMemoryRequirementsInfo2 Source # 
type FieldOptional "pNext" VkImageMemoryRequirementsInfo2 Source # 
type FieldOptional "sType" VkImageMemoryRequirementsInfo2 Source # 
type FieldOffset "image" VkImageMemoryRequirementsInfo2 Source # 
type FieldOffset "pNext" VkImageMemoryRequirementsInfo2 Source # 
type FieldOffset "sType" VkImageMemoryRequirementsInfo2 Source # 
type FieldIsArray "image" VkImageMemoryRequirementsInfo2 Source # 
type FieldIsArray "pNext" VkImageMemoryRequirementsInfo2 Source # 
type FieldIsArray "sType" VkImageMemoryRequirementsInfo2 Source # 

data VkImagePlaneMemoryRequirementsInfo Source #

typedef struct VkImagePlaneMemoryRequirementsInfo {
    VkStructureType sType;
    const void*                      pNext;
    VkImageAspectFlagBits            planeAspect;
} VkImagePlaneMemoryRequirementsInfo;

VkImagePlaneMemoryRequirementsInfo registry at www.khronos.org

Instances

Eq VkImagePlaneMemoryRequirementsInfo Source # 
Ord VkImagePlaneMemoryRequirementsInfo Source # 
Show VkImagePlaneMemoryRequirementsInfo Source # 
Storable VkImagePlaneMemoryRequirementsInfo Source # 
VulkanMarshalPrim VkImagePlaneMemoryRequirementsInfo Source # 
VulkanMarshal VkImagePlaneMemoryRequirementsInfo Source # 
CanWriteField "pNext" VkImagePlaneMemoryRequirementsInfo Source # 
CanWriteField "planeAspect" VkImagePlaneMemoryRequirementsInfo Source # 
CanWriteField "sType" VkImagePlaneMemoryRequirementsInfo Source # 
CanReadField "pNext" VkImagePlaneMemoryRequirementsInfo Source # 
CanReadField "planeAspect" VkImagePlaneMemoryRequirementsInfo Source # 
CanReadField "sType" VkImagePlaneMemoryRequirementsInfo Source # 
HasField "pNext" VkImagePlaneMemoryRequirementsInfo Source # 
HasField "planeAspect" VkImagePlaneMemoryRequirementsInfo Source # 
HasField "sType" VkImagePlaneMemoryRequirementsInfo Source # 
type StructFields VkImagePlaneMemoryRequirementsInfo Source # 
type StructFields VkImagePlaneMemoryRequirementsInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "planeAspect" ([] Symbol)))
type CUnionType VkImagePlaneMemoryRequirementsInfo Source # 
type ReturnedOnly VkImagePlaneMemoryRequirementsInfo Source # 
type StructExtends VkImagePlaneMemoryRequirementsInfo Source # 
type FieldType "pNext" VkImagePlaneMemoryRequirementsInfo Source # 
type FieldType "planeAspect" VkImagePlaneMemoryRequirementsInfo Source # 
type FieldType "sType" VkImagePlaneMemoryRequirementsInfo Source # 
type FieldOptional "pNext" VkImagePlaneMemoryRequirementsInfo Source # 
type FieldOptional "planeAspect" VkImagePlaneMemoryRequirementsInfo Source # 
type FieldOptional "sType" VkImagePlaneMemoryRequirementsInfo Source # 
type FieldOffset "pNext" VkImagePlaneMemoryRequirementsInfo Source # 
type FieldOffset "planeAspect" VkImagePlaneMemoryRequirementsInfo Source # 
type FieldOffset "sType" VkImagePlaneMemoryRequirementsInfo Source # 
type FieldIsArray "pNext" VkImagePlaneMemoryRequirementsInfo Source # 
type FieldIsArray "planeAspect" VkImagePlaneMemoryRequirementsInfo Source # 
type FieldIsArray "sType" VkImagePlaneMemoryRequirementsInfo Source # 

data VkImageResolve Source #

typedef struct VkImageResolve {
    VkImageSubresourceLayers srcSubresource;
    VkOffset3D             srcOffset;
    VkImageSubresourceLayers dstSubresource;
    VkOffset3D             dstOffset;
    VkExtent3D             extent;
} VkImageResolve;

VkImageResolve registry at www.khronos.org

Instances

Eq VkImageResolve Source # 
Ord VkImageResolve Source # 
Show VkImageResolve Source # 
Storable VkImageResolve Source # 
VulkanMarshalPrim VkImageResolve Source # 
VulkanMarshal VkImageResolve Source # 
CanWriteField "dstOffset" VkImageResolve Source # 
CanWriteField "dstSubresource" VkImageResolve Source # 

Methods

writeField :: Ptr VkImageResolve -> FieldType "dstSubresource" VkImageResolve -> IO () Source #

CanWriteField "extent" VkImageResolve Source # 
CanWriteField "srcOffset" VkImageResolve Source # 
CanWriteField "srcSubresource" VkImageResolve Source # 

Methods

writeField :: Ptr VkImageResolve -> FieldType "srcSubresource" VkImageResolve -> IO () Source #

CanReadField "dstOffset" VkImageResolve Source # 
CanReadField "dstSubresource" VkImageResolve Source # 
CanReadField "extent" VkImageResolve Source # 
CanReadField "srcOffset" VkImageResolve Source # 
CanReadField "srcSubresource" VkImageResolve Source # 
HasField "dstOffset" VkImageResolve Source # 

Associated Types

type FieldType ("dstOffset" :: Symbol) VkImageResolve :: Type Source #

type FieldOptional ("dstOffset" :: Symbol) VkImageResolve :: Bool Source #

type FieldOffset ("dstOffset" :: Symbol) VkImageResolve :: Nat Source #

type FieldIsArray ("dstOffset" :: Symbol) VkImageResolve :: Bool Source #

HasField "dstSubresource" VkImageResolve Source # 

Associated Types

type FieldType ("dstSubresource" :: Symbol) VkImageResolve :: Type Source #

type FieldOptional ("dstSubresource" :: Symbol) VkImageResolve :: Bool Source #

type FieldOffset ("dstSubresource" :: Symbol) VkImageResolve :: Nat Source #

type FieldIsArray ("dstSubresource" :: Symbol) VkImageResolve :: Bool Source #

HasField "extent" VkImageResolve Source # 

Associated Types

type FieldType ("extent" :: Symbol) VkImageResolve :: Type Source #

type FieldOptional ("extent" :: Symbol) VkImageResolve :: Bool Source #

type FieldOffset ("extent" :: Symbol) VkImageResolve :: Nat Source #

type FieldIsArray ("extent" :: Symbol) VkImageResolve :: Bool Source #

HasField "srcOffset" VkImageResolve Source # 

Associated Types

type FieldType ("srcOffset" :: Symbol) VkImageResolve :: Type Source #

type FieldOptional ("srcOffset" :: Symbol) VkImageResolve :: Bool Source #

type FieldOffset ("srcOffset" :: Symbol) VkImageResolve :: Nat Source #

type FieldIsArray ("srcOffset" :: Symbol) VkImageResolve :: Bool Source #

HasField "srcSubresource" VkImageResolve Source # 

Associated Types

type FieldType ("srcSubresource" :: Symbol) VkImageResolve :: Type Source #

type FieldOptional ("srcSubresource" :: Symbol) VkImageResolve :: Bool Source #

type FieldOffset ("srcSubresource" :: Symbol) VkImageResolve :: Nat Source #

type FieldIsArray ("srcSubresource" :: Symbol) VkImageResolve :: Bool Source #

type StructFields VkImageResolve Source # 
type StructFields VkImageResolve = (:) Symbol "srcSubresource" ((:) Symbol "srcOffset" ((:) Symbol "dstSubresource" ((:) Symbol "dstOffset" ((:) Symbol "extent" ([] Symbol)))))
type CUnionType VkImageResolve Source # 
type ReturnedOnly VkImageResolve Source # 
type StructExtends VkImageResolve Source # 
type FieldType "dstOffset" VkImageResolve Source # 
type FieldType "dstSubresource" VkImageResolve Source # 
type FieldType "extent" VkImageResolve Source # 
type FieldType "srcOffset" VkImageResolve Source # 
type FieldType "srcSubresource" VkImageResolve Source # 
type FieldOptional "dstOffset" VkImageResolve Source # 
type FieldOptional "dstSubresource" VkImageResolve Source # 
type FieldOptional "dstSubresource" VkImageResolve = False
type FieldOptional "extent" VkImageResolve Source # 
type FieldOptional "srcOffset" VkImageResolve Source # 
type FieldOptional "srcSubresource" VkImageResolve Source # 
type FieldOptional "srcSubresource" VkImageResolve = False
type FieldOffset "dstOffset" VkImageResolve Source # 
type FieldOffset "dstOffset" VkImageResolve = 44
type FieldOffset "dstSubresource" VkImageResolve Source # 
type FieldOffset "dstSubresource" VkImageResolve = 28
type FieldOffset "extent" VkImageResolve Source # 
type FieldOffset "extent" VkImageResolve = 56
type FieldOffset "srcOffset" VkImageResolve Source # 
type FieldOffset "srcOffset" VkImageResolve = 16
type FieldOffset "srcSubresource" VkImageResolve Source # 
type FieldOffset "srcSubresource" VkImageResolve = 0
type FieldIsArray "dstOffset" VkImageResolve Source # 
type FieldIsArray "dstOffset" VkImageResolve = False
type FieldIsArray "dstSubresource" VkImageResolve Source # 
type FieldIsArray "dstSubresource" VkImageResolve = False
type FieldIsArray "extent" VkImageResolve Source # 
type FieldIsArray "srcOffset" VkImageResolve Source # 
type FieldIsArray "srcOffset" VkImageResolve = False
type FieldIsArray "srcSubresource" VkImageResolve Source # 
type FieldIsArray "srcSubresource" VkImageResolve = False

data VkImageSparseMemoryRequirementsInfo2 Source #

typedef struct VkImageSparseMemoryRequirementsInfo2 {
    VkStructureType sType;
    const void*                                                          pNext;
    VkImage                                                              image;
} VkImageSparseMemoryRequirementsInfo2;

VkImageSparseMemoryRequirementsInfo2 registry at www.khronos.org

Instances

Eq VkImageSparseMemoryRequirementsInfo2 Source # 
Ord VkImageSparseMemoryRequirementsInfo2 Source # 
Show VkImageSparseMemoryRequirementsInfo2 Source # 
Storable VkImageSparseMemoryRequirementsInfo2 Source # 
VulkanMarshalPrim VkImageSparseMemoryRequirementsInfo2 Source # 
VulkanMarshal VkImageSparseMemoryRequirementsInfo2 Source # 
CanWriteField "image" VkImageSparseMemoryRequirementsInfo2 Source # 
CanWriteField "pNext" VkImageSparseMemoryRequirementsInfo2 Source # 
CanWriteField "sType" VkImageSparseMemoryRequirementsInfo2 Source # 
CanReadField "image" VkImageSparseMemoryRequirementsInfo2 Source # 
CanReadField "pNext" VkImageSparseMemoryRequirementsInfo2 Source # 
CanReadField "sType" VkImageSparseMemoryRequirementsInfo2 Source # 
HasField "image" VkImageSparseMemoryRequirementsInfo2 Source # 
HasField "pNext" VkImageSparseMemoryRequirementsInfo2 Source # 
HasField "sType" VkImageSparseMemoryRequirementsInfo2 Source # 
type StructFields VkImageSparseMemoryRequirementsInfo2 Source # 
type StructFields VkImageSparseMemoryRequirementsInfo2 = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "image" ([] Symbol)))
type CUnionType VkImageSparseMemoryRequirementsInfo2 Source # 
type ReturnedOnly VkImageSparseMemoryRequirementsInfo2 Source # 
type StructExtends VkImageSparseMemoryRequirementsInfo2 Source # 
type FieldType "image" VkImageSparseMemoryRequirementsInfo2 Source # 
type FieldType "pNext" VkImageSparseMemoryRequirementsInfo2 Source # 
type FieldType "sType" VkImageSparseMemoryRequirementsInfo2 Source # 
type FieldOptional "image" VkImageSparseMemoryRequirementsInfo2 Source # 
type FieldOptional "pNext" VkImageSparseMemoryRequirementsInfo2 Source # 
type FieldOptional "sType" VkImageSparseMemoryRequirementsInfo2 Source # 
type FieldOffset "image" VkImageSparseMemoryRequirementsInfo2 Source # 
type FieldOffset "pNext" VkImageSparseMemoryRequirementsInfo2 Source # 
type FieldOffset "sType" VkImageSparseMemoryRequirementsInfo2 Source # 
type FieldIsArray "image" VkImageSparseMemoryRequirementsInfo2 Source # 
type FieldIsArray "pNext" VkImageSparseMemoryRequirementsInfo2 Source # 
type FieldIsArray "sType" VkImageSparseMemoryRequirementsInfo2 Source # 

data VkImageSubresource Source #

typedef struct VkImageSubresource {
    VkImageAspectFlags     aspectMask;
    uint32_t               mipLevel;
    uint32_t               arrayLayer;
} VkImageSubresource;

VkImageSubresource registry at www.khronos.org

Instances

Eq VkImageSubresource Source # 
Ord VkImageSubresource Source # 
Show VkImageSubresource Source # 
Storable VkImageSubresource Source # 
VulkanMarshalPrim VkImageSubresource Source # 
VulkanMarshal VkImageSubresource Source # 
CanWriteField "arrayLayer" VkImageSubresource Source # 
CanWriteField "aspectMask" VkImageSubresource Source # 
CanWriteField "mipLevel" VkImageSubresource Source # 
CanReadField "arrayLayer" VkImageSubresource Source # 
CanReadField "aspectMask" VkImageSubresource Source # 
CanReadField "mipLevel" VkImageSubresource Source # 
HasField "arrayLayer" VkImageSubresource Source # 

Associated Types

type FieldType ("arrayLayer" :: Symbol) VkImageSubresource :: Type Source #

type FieldOptional ("arrayLayer" :: Symbol) VkImageSubresource :: Bool Source #

type FieldOffset ("arrayLayer" :: Symbol) VkImageSubresource :: Nat Source #

type FieldIsArray ("arrayLayer" :: Symbol) VkImageSubresource :: Bool Source #

HasField "aspectMask" VkImageSubresource Source # 

Associated Types

type FieldType ("aspectMask" :: Symbol) VkImageSubresource :: Type Source #

type FieldOptional ("aspectMask" :: Symbol) VkImageSubresource :: Bool Source #

type FieldOffset ("aspectMask" :: Symbol) VkImageSubresource :: Nat Source #

type FieldIsArray ("aspectMask" :: Symbol) VkImageSubresource :: Bool Source #

HasField "mipLevel" VkImageSubresource Source # 
type StructFields VkImageSubresource Source # 
type StructFields VkImageSubresource = (:) Symbol "aspectMask" ((:) Symbol "mipLevel" ((:) Symbol "arrayLayer" ([] Symbol)))
type CUnionType VkImageSubresource Source # 
type ReturnedOnly VkImageSubresource Source # 
type StructExtends VkImageSubresource Source # 
type FieldType "arrayLayer" VkImageSubresource Source # 
type FieldType "arrayLayer" VkImageSubresource = Word32
type FieldType "aspectMask" VkImageSubresource Source # 
type FieldType "mipLevel" VkImageSubresource Source # 
type FieldOptional "arrayLayer" VkImageSubresource Source # 
type FieldOptional "aspectMask" VkImageSubresource Source # 
type FieldOptional "mipLevel" VkImageSubresource Source # 
type FieldOffset "arrayLayer" VkImageSubresource Source # 
type FieldOffset "arrayLayer" VkImageSubresource = 8
type FieldOffset "aspectMask" VkImageSubresource Source # 
type FieldOffset "aspectMask" VkImageSubresource = 0
type FieldOffset "mipLevel" VkImageSubresource Source # 
type FieldOffset "mipLevel" VkImageSubresource = 4
type FieldIsArray "arrayLayer" VkImageSubresource Source # 
type FieldIsArray "aspectMask" VkImageSubresource Source # 
type FieldIsArray "mipLevel" VkImageSubresource Source # 

data VkImageSubresourceLayers Source #

typedef struct VkImageSubresourceLayers {
    VkImageAspectFlags     aspectMask;
    uint32_t               mipLevel;
    uint32_t               baseArrayLayer;
    uint32_t               layerCount;
} VkImageSubresourceLayers;

VkImageSubresourceLayers registry at www.khronos.org

Instances

Eq VkImageSubresourceLayers Source # 
Ord VkImageSubresourceLayers Source # 
Show VkImageSubresourceLayers Source # 
Storable VkImageSubresourceLayers Source # 
VulkanMarshalPrim VkImageSubresourceLayers Source # 
VulkanMarshal VkImageSubresourceLayers Source # 
CanWriteField "aspectMask" VkImageSubresourceLayers Source # 
CanWriteField "baseArrayLayer" VkImageSubresourceLayers Source # 
CanWriteField "layerCount" VkImageSubresourceLayers Source # 
CanWriteField "mipLevel" VkImageSubresourceLayers Source # 
CanReadField "aspectMask" VkImageSubresourceLayers Source # 
CanReadField "baseArrayLayer" VkImageSubresourceLayers Source # 
CanReadField "layerCount" VkImageSubresourceLayers Source # 
CanReadField "mipLevel" VkImageSubresourceLayers Source # 
HasField "aspectMask" VkImageSubresourceLayers Source # 
HasField "baseArrayLayer" VkImageSubresourceLayers Source # 

Associated Types

type FieldType ("baseArrayLayer" :: Symbol) VkImageSubresourceLayers :: Type Source #

type FieldOptional ("baseArrayLayer" :: Symbol) VkImageSubresourceLayers :: Bool Source #

type FieldOffset ("baseArrayLayer" :: Symbol) VkImageSubresourceLayers :: Nat Source #

type FieldIsArray ("baseArrayLayer" :: Symbol) VkImageSubresourceLayers :: Bool Source #

HasField "layerCount" VkImageSubresourceLayers Source # 
HasField "mipLevel" VkImageSubresourceLayers Source # 
type StructFields VkImageSubresourceLayers Source # 
type StructFields VkImageSubresourceLayers = (:) Symbol "aspectMask" ((:) Symbol "mipLevel" ((:) Symbol "baseArrayLayer" ((:) Symbol "layerCount" ([] Symbol))))
type CUnionType VkImageSubresourceLayers Source # 
type ReturnedOnly VkImageSubresourceLayers Source # 
type StructExtends VkImageSubresourceLayers Source # 
type FieldType "aspectMask" VkImageSubresourceLayers Source # 
type FieldType "baseArrayLayer" VkImageSubresourceLayers Source # 
type FieldType "baseArrayLayer" VkImageSubresourceLayers = Word32
type FieldType "layerCount" VkImageSubresourceLayers Source # 
type FieldType "mipLevel" VkImageSubresourceLayers Source # 
type FieldOptional "aspectMask" VkImageSubresourceLayers Source # 
type FieldOptional "baseArrayLayer" VkImageSubresourceLayers Source # 
type FieldOptional "layerCount" VkImageSubresourceLayers Source # 
type FieldOptional "mipLevel" VkImageSubresourceLayers Source # 
type FieldOffset "aspectMask" VkImageSubresourceLayers Source # 
type FieldOffset "baseArrayLayer" VkImageSubresourceLayers Source # 
type FieldOffset "baseArrayLayer" VkImageSubresourceLayers = 8
type FieldOffset "layerCount" VkImageSubresourceLayers Source # 
type FieldOffset "layerCount" VkImageSubresourceLayers = 12
type FieldOffset "mipLevel" VkImageSubresourceLayers Source # 
type FieldIsArray "aspectMask" VkImageSubresourceLayers Source # 
type FieldIsArray "baseArrayLayer" VkImageSubresourceLayers Source # 
type FieldIsArray "layerCount" VkImageSubresourceLayers Source # 
type FieldIsArray "mipLevel" VkImageSubresourceLayers Source # 

data VkImageSubresourceRange Source #

typedef struct VkImageSubresourceRange {
    VkImageAspectFlags     aspectMask;
    uint32_t               baseMipLevel;
    uint32_t               levelCount;
    uint32_t               baseArrayLayer;
    uint32_t               layerCount;
} VkImageSubresourceRange;

VkImageSubresourceRange registry at www.khronos.org

Instances

Eq VkImageSubresourceRange Source # 
Ord VkImageSubresourceRange Source # 
Show VkImageSubresourceRange Source # 
Storable VkImageSubresourceRange Source # 
VulkanMarshalPrim VkImageSubresourceRange Source # 
VulkanMarshal VkImageSubresourceRange Source # 
CanWriteField "aspectMask" VkImageSubresourceRange Source # 
CanWriteField "baseArrayLayer" VkImageSubresourceRange Source # 
CanWriteField "baseMipLevel" VkImageSubresourceRange Source # 
CanWriteField "layerCount" VkImageSubresourceRange Source # 
CanWriteField "levelCount" VkImageSubresourceRange Source # 
CanReadField "aspectMask" VkImageSubresourceRange Source # 
CanReadField "baseArrayLayer" VkImageSubresourceRange Source # 
CanReadField "baseMipLevel" VkImageSubresourceRange Source # 
CanReadField "layerCount" VkImageSubresourceRange Source # 
CanReadField "levelCount" VkImageSubresourceRange Source # 
HasField "aspectMask" VkImageSubresourceRange Source # 
HasField "baseArrayLayer" VkImageSubresourceRange Source # 

Associated Types

type FieldType ("baseArrayLayer" :: Symbol) VkImageSubresourceRange :: Type Source #

type FieldOptional ("baseArrayLayer" :: Symbol) VkImageSubresourceRange :: Bool Source #

type FieldOffset ("baseArrayLayer" :: Symbol) VkImageSubresourceRange :: Nat Source #

type FieldIsArray ("baseArrayLayer" :: Symbol) VkImageSubresourceRange :: Bool Source #

HasField "baseMipLevel" VkImageSubresourceRange Source # 

Associated Types

type FieldType ("baseMipLevel" :: Symbol) VkImageSubresourceRange :: Type Source #

type FieldOptional ("baseMipLevel" :: Symbol) VkImageSubresourceRange :: Bool Source #

type FieldOffset ("baseMipLevel" :: Symbol) VkImageSubresourceRange :: Nat Source #

type FieldIsArray ("baseMipLevel" :: Symbol) VkImageSubresourceRange :: Bool Source #

HasField "layerCount" VkImageSubresourceRange Source # 
HasField "levelCount" VkImageSubresourceRange Source # 
type StructFields VkImageSubresourceRange Source # 
type StructFields VkImageSubresourceRange = (:) Symbol "aspectMask" ((:) Symbol "baseMipLevel" ((:) Symbol "levelCount" ((:) Symbol "baseArrayLayer" ((:) Symbol "layerCount" ([] Symbol)))))
type CUnionType VkImageSubresourceRange Source # 
type ReturnedOnly VkImageSubresourceRange Source # 
type StructExtends VkImageSubresourceRange Source # 
type FieldType "aspectMask" VkImageSubresourceRange Source # 
type FieldType "baseArrayLayer" VkImageSubresourceRange Source # 
type FieldType "baseArrayLayer" VkImageSubresourceRange = Word32
type FieldType "baseMipLevel" VkImageSubresourceRange Source # 
type FieldType "layerCount" VkImageSubresourceRange Source # 
type FieldType "levelCount" VkImageSubresourceRange Source # 
type FieldOptional "aspectMask" VkImageSubresourceRange Source # 
type FieldOptional "baseArrayLayer" VkImageSubresourceRange Source # 
type FieldOptional "baseMipLevel" VkImageSubresourceRange Source # 
type FieldOptional "layerCount" VkImageSubresourceRange Source # 
type FieldOptional "levelCount" VkImageSubresourceRange Source # 
type FieldOffset "aspectMask" VkImageSubresourceRange Source # 
type FieldOffset "aspectMask" VkImageSubresourceRange = 0
type FieldOffset "baseArrayLayer" VkImageSubresourceRange Source # 
type FieldOffset "baseArrayLayer" VkImageSubresourceRange = 12
type FieldOffset "baseMipLevel" VkImageSubresourceRange Source # 
type FieldOffset "baseMipLevel" VkImageSubresourceRange = 4
type FieldOffset "layerCount" VkImageSubresourceRange Source # 
type FieldOffset "layerCount" VkImageSubresourceRange = 16
type FieldOffset "levelCount" VkImageSubresourceRange Source # 
type FieldOffset "levelCount" VkImageSubresourceRange = 8
type FieldIsArray "aspectMask" VkImageSubresourceRange Source # 
type FieldIsArray "baseArrayLayer" VkImageSubresourceRange Source # 
type FieldIsArray "baseMipLevel" VkImageSubresourceRange Source # 
type FieldIsArray "layerCount" VkImageSubresourceRange Source # 
type FieldIsArray "levelCount" VkImageSubresourceRange Source # 

data VkImageSwapchainCreateInfoKHR Source #

typedef struct VkImageSwapchainCreateInfoKHR {
    VkStructureType sType;
    const void*                      pNext;
    VkSwapchainKHR   swapchain;
} VkImageSwapchainCreateInfoKHR;

VkImageSwapchainCreateInfoKHR registry at www.khronos.org

Instances

Eq VkImageSwapchainCreateInfoKHR Source # 
Ord VkImageSwapchainCreateInfoKHR Source # 
Show VkImageSwapchainCreateInfoKHR Source # 
Storable VkImageSwapchainCreateInfoKHR Source # 
VulkanMarshalPrim VkImageSwapchainCreateInfoKHR Source # 
VulkanMarshal VkImageSwapchainCreateInfoKHR Source # 
CanWriteField "pNext" VkImageSwapchainCreateInfoKHR Source # 
CanWriteField "sType" VkImageSwapchainCreateInfoKHR Source # 
CanWriteField "swapchain" VkImageSwapchainCreateInfoKHR Source # 
CanReadField "pNext" VkImageSwapchainCreateInfoKHR Source # 
CanReadField "sType" VkImageSwapchainCreateInfoKHR Source # 
CanReadField "swapchain" VkImageSwapchainCreateInfoKHR Source # 
HasField "pNext" VkImageSwapchainCreateInfoKHR Source # 
HasField "sType" VkImageSwapchainCreateInfoKHR Source # 
HasField "swapchain" VkImageSwapchainCreateInfoKHR Source # 
type StructFields VkImageSwapchainCreateInfoKHR Source # 
type StructFields VkImageSwapchainCreateInfoKHR = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "swapchain" ([] Symbol)))
type CUnionType VkImageSwapchainCreateInfoKHR Source # 
type ReturnedOnly VkImageSwapchainCreateInfoKHR Source # 
type StructExtends VkImageSwapchainCreateInfoKHR Source # 
type FieldType "pNext" VkImageSwapchainCreateInfoKHR Source # 
type FieldType "sType" VkImageSwapchainCreateInfoKHR Source # 
type FieldType "swapchain" VkImageSwapchainCreateInfoKHR Source # 
type FieldOptional "pNext" VkImageSwapchainCreateInfoKHR Source # 
type FieldOptional "sType" VkImageSwapchainCreateInfoKHR Source # 
type FieldOptional "swapchain" VkImageSwapchainCreateInfoKHR Source # 
type FieldOffset "pNext" VkImageSwapchainCreateInfoKHR Source # 
type FieldOffset "sType" VkImageSwapchainCreateInfoKHR Source # 
type FieldOffset "swapchain" VkImageSwapchainCreateInfoKHR Source # 
type FieldIsArray "pNext" VkImageSwapchainCreateInfoKHR Source # 
type FieldIsArray "sType" VkImageSwapchainCreateInfoKHR Source # 
type FieldIsArray "swapchain" VkImageSwapchainCreateInfoKHR Source # 

data VkImageViewCreateInfo Source #

typedef struct VkImageViewCreateInfo {
    VkStructureType sType;
    const void*            pNext;
    VkImageViewCreateFlags flags;
    VkImage                image;
    VkImageViewType        viewType;
    VkFormat               format;
    VkComponentMapping     components;
    VkImageSubresourceRange subresourceRange;
} VkImageViewCreateInfo;

VkImageViewCreateInfo registry at www.khronos.org

Instances

Eq VkImageViewCreateInfo Source # 
Ord VkImageViewCreateInfo Source # 
Show VkImageViewCreateInfo Source # 
Storable VkImageViewCreateInfo Source # 
VulkanMarshalPrim VkImageViewCreateInfo Source # 
VulkanMarshal VkImageViewCreateInfo Source # 
CanWriteField "components" VkImageViewCreateInfo Source # 
CanWriteField "flags" VkImageViewCreateInfo Source # 
CanWriteField "format" VkImageViewCreateInfo Source # 
CanWriteField "image" VkImageViewCreateInfo Source # 
CanWriteField "pNext" VkImageViewCreateInfo Source # 
CanWriteField "sType" VkImageViewCreateInfo Source # 
CanWriteField "subresourceRange" VkImageViewCreateInfo Source # 
CanWriteField "viewType" VkImageViewCreateInfo Source # 
CanReadField "components" VkImageViewCreateInfo Source # 
CanReadField "flags" VkImageViewCreateInfo Source # 
CanReadField "format" VkImageViewCreateInfo Source # 
CanReadField "image" VkImageViewCreateInfo Source # 
CanReadField "pNext" VkImageViewCreateInfo Source # 
CanReadField "sType" VkImageViewCreateInfo Source # 
CanReadField "subresourceRange" VkImageViewCreateInfo Source # 
CanReadField "viewType" VkImageViewCreateInfo Source # 
HasField "components" VkImageViewCreateInfo Source # 
HasField "flags" VkImageViewCreateInfo Source # 
HasField "format" VkImageViewCreateInfo Source # 
HasField "image" VkImageViewCreateInfo Source # 
HasField "pNext" VkImageViewCreateInfo Source # 
HasField "sType" VkImageViewCreateInfo Source # 
HasField "subresourceRange" VkImageViewCreateInfo Source # 

Associated Types

type FieldType ("subresourceRange" :: Symbol) VkImageViewCreateInfo :: Type Source #

type FieldOptional ("subresourceRange" :: Symbol) VkImageViewCreateInfo :: Bool Source #

type FieldOffset ("subresourceRange" :: Symbol) VkImageViewCreateInfo :: Nat Source #

type FieldIsArray ("subresourceRange" :: Symbol) VkImageViewCreateInfo :: Bool Source #

HasField "viewType" VkImageViewCreateInfo Source # 
type StructFields VkImageViewCreateInfo Source # 
type StructFields VkImageViewCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "image" ((:) Symbol "viewType" ((:) Symbol "format" ((:) Symbol "components" ((:) Symbol "subresourceRange" ([] Symbol))))))))
type CUnionType VkImageViewCreateInfo Source # 
type ReturnedOnly VkImageViewCreateInfo Source # 
type StructExtends VkImageViewCreateInfo Source # 
type FieldType "components" VkImageViewCreateInfo Source # 
type FieldType "flags" VkImageViewCreateInfo Source # 
type FieldType "format" VkImageViewCreateInfo Source # 
type FieldType "image" VkImageViewCreateInfo Source # 
type FieldType "pNext" VkImageViewCreateInfo Source # 
type FieldType "sType" VkImageViewCreateInfo Source # 
type FieldType "subresourceRange" VkImageViewCreateInfo Source # 
type FieldType "viewType" VkImageViewCreateInfo Source # 
type FieldOptional "components" VkImageViewCreateInfo Source # 
type FieldOptional "flags" VkImageViewCreateInfo Source # 
type FieldOptional "format" VkImageViewCreateInfo Source # 
type FieldOptional "image" VkImageViewCreateInfo Source # 
type FieldOptional "pNext" VkImageViewCreateInfo Source # 
type FieldOptional "sType" VkImageViewCreateInfo Source # 
type FieldOptional "subresourceRange" VkImageViewCreateInfo Source # 
type FieldOptional "subresourceRange" VkImageViewCreateInfo = False
type FieldOptional "viewType" VkImageViewCreateInfo Source # 
type FieldOffset "components" VkImageViewCreateInfo Source # 
type FieldOffset "components" VkImageViewCreateInfo = 40
type FieldOffset "flags" VkImageViewCreateInfo Source # 
type FieldOffset "format" VkImageViewCreateInfo Source # 
type FieldOffset "image" VkImageViewCreateInfo Source # 
type FieldOffset "pNext" VkImageViewCreateInfo Source # 
type FieldOffset "sType" VkImageViewCreateInfo Source # 
type FieldOffset "subresourceRange" VkImageViewCreateInfo Source # 
type FieldOffset "subresourceRange" VkImageViewCreateInfo = 56
type FieldOffset "viewType" VkImageViewCreateInfo Source # 
type FieldOffset "viewType" VkImageViewCreateInfo = 32
type FieldIsArray "components" VkImageViewCreateInfo Source # 
type FieldIsArray "flags" VkImageViewCreateInfo Source # 
type FieldIsArray "format" VkImageViewCreateInfo Source # 
type FieldIsArray "image" VkImageViewCreateInfo Source # 
type FieldIsArray "pNext" VkImageViewCreateInfo Source # 
type FieldIsArray "sType" VkImageViewCreateInfo Source # 
type FieldIsArray "subresourceRange" VkImageViewCreateInfo Source # 
type FieldIsArray "subresourceRange" VkImageViewCreateInfo = False
type FieldIsArray "viewType" VkImageViewCreateInfo Source # 

data VkImageViewUsageCreateInfo Source #

typedef struct VkImageViewUsageCreateInfo {
    VkStructureType sType;
    const void* pNext;
    VkImageUsageFlags usage;
} VkImageViewUsageCreateInfo;

VkImageViewUsageCreateInfo registry at www.khronos.org

Instances

Eq VkImageViewUsageCreateInfo Source # 
Ord VkImageViewUsageCreateInfo Source # 
Show VkImageViewUsageCreateInfo Source # 
Storable VkImageViewUsageCreateInfo Source # 
VulkanMarshalPrim VkImageViewUsageCreateInfo Source # 
VulkanMarshal VkImageViewUsageCreateInfo Source # 
CanWriteField "pNext" VkImageViewUsageCreateInfo Source # 
CanWriteField "sType" VkImageViewUsageCreateInfo Source # 
CanWriteField "usage" VkImageViewUsageCreateInfo Source # 
CanReadField "pNext" VkImageViewUsageCreateInfo Source # 
CanReadField "sType" VkImageViewUsageCreateInfo Source # 
CanReadField "usage" VkImageViewUsageCreateInfo Source # 
HasField "pNext" VkImageViewUsageCreateInfo Source # 
HasField "sType" VkImageViewUsageCreateInfo Source # 
HasField "usage" VkImageViewUsageCreateInfo Source # 
type StructFields VkImageViewUsageCreateInfo Source # 
type StructFields VkImageViewUsageCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "usage" ([] Symbol)))
type CUnionType VkImageViewUsageCreateInfo Source # 
type ReturnedOnly VkImageViewUsageCreateInfo Source # 
type StructExtends VkImageViewUsageCreateInfo Source # 
type FieldType "pNext" VkImageViewUsageCreateInfo Source # 
type FieldType "sType" VkImageViewUsageCreateInfo Source # 
type FieldType "usage" VkImageViewUsageCreateInfo Source # 
type FieldOptional "pNext" VkImageViewUsageCreateInfo Source # 
type FieldOptional "sType" VkImageViewUsageCreateInfo Source # 
type FieldOptional "usage" VkImageViewUsageCreateInfo Source # 
type FieldOffset "pNext" VkImageViewUsageCreateInfo Source # 
type FieldOffset "sType" VkImageViewUsageCreateInfo Source # 
type FieldOffset "usage" VkImageViewUsageCreateInfo Source # 
type FieldIsArray "pNext" VkImageViewUsageCreateInfo Source # 
type FieldIsArray "sType" VkImageViewUsageCreateInfo Source # 
type FieldIsArray "usage" VkImageViewUsageCreateInfo Source # 

newtype VkSampleCountBitmask a Source #

Instances

Bounded (VkSampleCountBitmask FlagMask) Source # 
Enum (VkSampleCountBitmask FlagMask) Source # 
Eq (VkSampleCountBitmask a) Source # 
Integral (VkSampleCountBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkSampleCountBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkSampleCountBitmask a -> c (VkSampleCountBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkSampleCountBitmask a) #

toConstr :: VkSampleCountBitmask a -> Constr #

dataTypeOf :: VkSampleCountBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkSampleCountBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkSampleCountBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkSampleCountBitmask a -> VkSampleCountBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkSampleCountBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkSampleCountBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkSampleCountBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkSampleCountBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkSampleCountBitmask a -> m (VkSampleCountBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSampleCountBitmask a -> m (VkSampleCountBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSampleCountBitmask a -> m (VkSampleCountBitmask a) #

Num (VkSampleCountBitmask FlagMask) Source # 
Ord (VkSampleCountBitmask a) Source # 
Read (VkSampleCountBitmask a) Source # 
Real (VkSampleCountBitmask FlagMask) Source # 
Show (VkSampleCountBitmask a) Source # 
Generic (VkSampleCountBitmask a) Source # 
Storable (VkSampleCountBitmask a) Source # 
Bits (VkSampleCountBitmask FlagMask) Source # 

Methods

(.&.) :: VkSampleCountBitmask FlagMask -> VkSampleCountBitmask FlagMask -> VkSampleCountBitmask FlagMask #

(.|.) :: VkSampleCountBitmask FlagMask -> VkSampleCountBitmask FlagMask -> VkSampleCountBitmask FlagMask #

xor :: VkSampleCountBitmask FlagMask -> VkSampleCountBitmask FlagMask -> VkSampleCountBitmask FlagMask #

complement :: VkSampleCountBitmask FlagMask -> VkSampleCountBitmask FlagMask #

shift :: VkSampleCountBitmask FlagMask -> Int -> VkSampleCountBitmask FlagMask #

rotate :: VkSampleCountBitmask FlagMask -> Int -> VkSampleCountBitmask FlagMask #

zeroBits :: VkSampleCountBitmask FlagMask #

bit :: Int -> VkSampleCountBitmask FlagMask #

setBit :: VkSampleCountBitmask FlagMask -> Int -> VkSampleCountBitmask FlagMask #

clearBit :: VkSampleCountBitmask FlagMask -> Int -> VkSampleCountBitmask FlagMask #

complementBit :: VkSampleCountBitmask FlagMask -> Int -> VkSampleCountBitmask FlagMask #

testBit :: VkSampleCountBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkSampleCountBitmask FlagMask -> Maybe Int #

bitSize :: VkSampleCountBitmask FlagMask -> Int #

isSigned :: VkSampleCountBitmask FlagMask -> Bool #

shiftL :: VkSampleCountBitmask FlagMask -> Int -> VkSampleCountBitmask FlagMask #

unsafeShiftL :: VkSampleCountBitmask FlagMask -> Int -> VkSampleCountBitmask FlagMask #

shiftR :: VkSampleCountBitmask FlagMask -> Int -> VkSampleCountBitmask FlagMask #

unsafeShiftR :: VkSampleCountBitmask FlagMask -> Int -> VkSampleCountBitmask FlagMask #

rotateL :: VkSampleCountBitmask FlagMask -> Int -> VkSampleCountBitmask FlagMask #

rotateR :: VkSampleCountBitmask FlagMask -> Int -> VkSampleCountBitmask FlagMask #

popCount :: VkSampleCountBitmask FlagMask -> Int #

FiniteBits (VkSampleCountBitmask FlagMask) Source # 
type Rep (VkSampleCountBitmask a) Source # 
type Rep (VkSampleCountBitmask a) = D1 (MetaData "VkSampleCountBitmask" "Graphics.Vulkan.Types.Enum.SampleCountFlags" "vulkan-api-1.1.2.1-GcVsfRwwhb24i5dsYq91EC" True) (C1 (MetaCons "VkSampleCountBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

pattern VK_SAMPLE_COUNT_1_BIT :: forall a. VkSampleCountBitmask a Source #

Sample count 1 supported

bitpos = 0

pattern VK_SAMPLE_COUNT_2_BIT :: forall a. VkSampleCountBitmask a Source #

Sample count 2 supported

bitpos = 1

pattern VK_SAMPLE_COUNT_4_BIT :: forall a. VkSampleCountBitmask a Source #

Sample count 4 supported

bitpos = 2

pattern VK_SAMPLE_COUNT_8_BIT :: forall a. VkSampleCountBitmask a Source #

Sample count 8 supported

bitpos = 3

pattern VK_SAMPLE_COUNT_16_BIT :: forall a. VkSampleCountBitmask a Source #

Sample count 16 supported

bitpos = 4

pattern VK_SAMPLE_COUNT_32_BIT :: forall a. VkSampleCountBitmask a Source #

Sample count 32 supported

bitpos = 5

pattern VK_SAMPLE_COUNT_64_BIT :: forall a. VkSampleCountBitmask a Source #

Sample count 64 supported

bitpos = 6

type VkGetDeviceGroupPresentCapabilitiesKHR = "vkGetDeviceGroupPresentCapabilitiesKHR" Source #

type HS_vkGetDeviceGroupPresentCapabilitiesKHR Source #

Arguments

 = VkDevice

device

-> Ptr VkDeviceGroupPresentCapabilitiesKHR

pDeviceGroupPresentCapabilities

-> IO VkResult 

Success codes: VK_SUCCESS.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY.

VkResult vkGetDeviceGroupPresentCapabilitiesKHR
    ( VkDevice device
    , VkDeviceGroupPresentCapabilitiesKHR* pDeviceGroupPresentCapabilities
    )

vkGetDeviceGroupPresentCapabilitiesKHR registry at www.khronos.org

vkGetDeviceGroupPresentCapabilitiesKHR Source #

Arguments

:: VkDevice

device

-> Ptr VkDeviceGroupPresentCapabilitiesKHR

pDeviceGroupPresentCapabilities

-> IO VkResult 

Success codes: VK_SUCCESS.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY.

VkResult vkGetDeviceGroupPresentCapabilitiesKHR
    ( VkDevice device
    , VkDeviceGroupPresentCapabilitiesKHR* pDeviceGroupPresentCapabilities
    )

vkGetDeviceGroupPresentCapabilitiesKHR registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetDeviceGroupPresentCapabilitiesKHR <- vkGetDeviceProc @VkGetDeviceGroupPresentCapabilitiesKHR vkDevice

or less efficient:

myGetDeviceGroupPresentCapabilitiesKHR <- vkGetProc @VkGetDeviceGroupPresentCapabilitiesKHR

Note: vkXxx and vkXxxSafe versions of the call refer to using unsafe of safe FFI respectively.

vkGetDeviceGroupPresentCapabilitiesKHRSafe Source #

Arguments

:: VkDevice

device

-> Ptr VkDeviceGroupPresentCapabilitiesKHR

pDeviceGroupPresentCapabilities

-> IO VkResult 

Success codes: VK_SUCCESS.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY.

VkResult vkGetDeviceGroupPresentCapabilitiesKHR
    ( VkDevice device
    , VkDeviceGroupPresentCapabilitiesKHR* pDeviceGroupPresentCapabilities
    )

vkGetDeviceGroupPresentCapabilitiesKHR registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetDeviceGroupPresentCapabilitiesKHR <- vkGetDeviceProc @VkGetDeviceGroupPresentCapabilitiesKHR vkDevice

or less efficient:

myGetDeviceGroupPresentCapabilitiesKHR <- vkGetProc @VkGetDeviceGroupPresentCapabilitiesKHR

Note: vkXxx and vkXxxSafe versions of the call refer to using unsafe of safe FFI respectively.

type VkGetDeviceGroupSurfacePresentModesKHR = "vkGetDeviceGroupSurfacePresentModesKHR" Source #

type HS_vkGetDeviceGroupSurfacePresentModesKHR Source #

Arguments

 = VkDevice

device

-> VkSurfaceKHR

surface

-> Ptr VkDeviceGroupPresentModeFlagsKHR

pModes

-> IO VkResult 

Success codes: VK_SUCCESS.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY, VK_ERROR_SURFACE_LOST_KHR.

VkResult vkGetDeviceGroupSurfacePresentModesKHR
    ( VkDevice device
    , VkSurfaceKHR surface
    , VkDeviceGroupPresentModeFlagsKHR* pModes
    )

vkGetDeviceGroupSurfacePresentModesKHR registry at www.khronos.org

vkGetDeviceGroupSurfacePresentModesKHR Source #

Arguments

:: VkDevice

device

-> VkSurfaceKHR

surface

-> Ptr VkDeviceGroupPresentModeFlagsKHR

pModes

-> IO VkResult 

Success codes: VK_SUCCESS.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY, VK_ERROR_SURFACE_LOST_KHR.

VkResult vkGetDeviceGroupSurfacePresentModesKHR
    ( VkDevice device
    , VkSurfaceKHR surface
    , VkDeviceGroupPresentModeFlagsKHR* pModes
    )

vkGetDeviceGroupSurfacePresentModesKHR registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetDeviceGroupSurfacePresentModesKHR <- vkGetDeviceProc @VkGetDeviceGroupSurfacePresentModesKHR vkDevice

or less efficient:

myGetDeviceGroupSurfacePresentModesKHR <- vkGetProc @VkGetDeviceGroupSurfacePresentModesKHR

Note: vkXxx and vkXxxSafe versions of the call refer to using unsafe of safe FFI respectively.

vkGetDeviceGroupSurfacePresentModesKHRSafe Source #

Arguments

:: VkDevice

device

-> VkSurfaceKHR

surface

-> Ptr VkDeviceGroupPresentModeFlagsKHR

pModes

-> IO VkResult 

Success codes: VK_SUCCESS.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY, VK_ERROR_SURFACE_LOST_KHR.

VkResult vkGetDeviceGroupSurfacePresentModesKHR
    ( VkDevice device
    , VkSurfaceKHR surface
    , VkDeviceGroupPresentModeFlagsKHR* pModes
    )

vkGetDeviceGroupSurfacePresentModesKHR registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetDeviceGroupSurfacePresentModesKHR <- vkGetDeviceProc @VkGetDeviceGroupSurfacePresentModesKHR vkDevice

or less efficient:

myGetDeviceGroupSurfacePresentModesKHR <- vkGetProc @VkGetDeviceGroupSurfacePresentModesKHR

Note: vkXxx and vkXxxSafe versions of the call refer to using unsafe of safe FFI respectively.

type VkGetPhysicalDevicePresentRectanglesKHR = "vkGetPhysicalDevicePresentRectanglesKHR" Source #

type HS_vkGetPhysicalDevicePresentRectanglesKHR Source #

Arguments

 = VkPhysicalDevice

physicalDevice

-> VkSurfaceKHR

surface

-> Ptr Word32

pRectCount

-> Ptr VkRect2D

pRects

-> IO VkResult 

Success codes: VK_SUCCESS, VK_INCOMPLETE.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY.

VkResult vkGetPhysicalDevicePresentRectanglesKHR
    ( VkPhysicalDevice physicalDevice
    , VkSurfaceKHR surface
    , uint32_t* pRectCount
    , VkRect2D* pRects
    )

vkGetPhysicalDevicePresentRectanglesKHR registry at www.khronos.org

vkGetPhysicalDevicePresentRectanglesKHR Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> VkSurfaceKHR

surface

-> Ptr Word32

pRectCount

-> Ptr VkRect2D

pRects

-> IO VkResult 

Success codes: VK_SUCCESS, VK_INCOMPLETE.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY.

VkResult vkGetPhysicalDevicePresentRectanglesKHR
    ( VkPhysicalDevice physicalDevice
    , VkSurfaceKHR surface
    , uint32_t* pRectCount
    , VkRect2D* pRects
    )

vkGetPhysicalDevicePresentRectanglesKHR registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetPhysicalDevicePresentRectanglesKHR <- vkGetInstanceProc @VkGetPhysicalDevicePresentRectanglesKHR vkInstance

or less efficient:

myGetPhysicalDevicePresentRectanglesKHR <- vkGetProc @VkGetPhysicalDevicePresentRectanglesKHR

Note: vkXxx and vkXxxSafe versions of the call refer to using unsafe of safe FFI respectively.

vkGetPhysicalDevicePresentRectanglesKHRSafe Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> VkSurfaceKHR

surface

-> Ptr Word32

pRectCount

-> Ptr VkRect2D

pRects

-> IO VkResult 

Success codes: VK_SUCCESS, VK_INCOMPLETE.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY.

VkResult vkGetPhysicalDevicePresentRectanglesKHR
    ( VkPhysicalDevice physicalDevice
    , VkSurfaceKHR surface
    , uint32_t* pRectCount
    , VkRect2D* pRects
    )

vkGetPhysicalDevicePresentRectanglesKHR registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetPhysicalDevicePresentRectanglesKHR <- vkGetInstanceProc @VkGetPhysicalDevicePresentRectanglesKHR vkInstance

or less efficient:

myGetPhysicalDevicePresentRectanglesKHR <- vkGetProc @VkGetPhysicalDevicePresentRectanglesKHR

Note: vkXxx and vkXxxSafe versions of the call refer to using unsafe of safe FFI respectively.

type VkAcquireNextImage2KHR = "vkAcquireNextImage2KHR" Source #

type HS_vkAcquireNextImage2KHR Source #

Arguments

 = VkDevice

device

-> Ptr VkAcquireNextImageInfoKHR

pAcquireInfo

-> Ptr Word32

pImageIndex

-> IO VkResult 

Success codes: VK_SUCCESS, VK_TIMEOUT, VK_NOT_READY, VK_SUBOPTIMAL_KHR.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY, VK_ERROR_DEVICE_LOST, VK_ERROR_OUT_OF_DATE_KHR, VK_ERROR_SURFACE_LOST_KHR.

VkResult vkAcquireNextImage2KHR
    ( VkDevice device
    , const VkAcquireNextImageInfoKHR* pAcquireInfo
    , uint32_t* pImageIndex
    )

vkAcquireNextImage2KHR registry at www.khronos.org

vkAcquireNextImage2KHR Source #

Arguments

:: VkDevice

device

-> Ptr VkAcquireNextImageInfoKHR

pAcquireInfo

-> Ptr Word32

pImageIndex

-> IO VkResult 

Success codes: VK_SUCCESS, VK_TIMEOUT, VK_NOT_READY, VK_SUBOPTIMAL_KHR.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY, VK_ERROR_DEVICE_LOST, VK_ERROR_OUT_OF_DATE_KHR, VK_ERROR_SURFACE_LOST_KHR.

VkResult vkAcquireNextImage2KHR
    ( VkDevice device
    , const VkAcquireNextImageInfoKHR* pAcquireInfo
    , uint32_t* pImageIndex
    )

vkAcquireNextImage2KHR registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myAcquireNextImage2KHR <- vkGetDeviceProc @VkAcquireNextImage2KHR vkDevice

or less efficient:

myAcquireNextImage2KHR <- vkGetProc @VkAcquireNextImage2KHR

Note: vkXxx and vkXxxSafe versions of the call refer to using unsafe of safe FFI respectively.

vkAcquireNextImage2KHRSafe Source #

Arguments

:: VkDevice

device

-> Ptr VkAcquireNextImageInfoKHR

pAcquireInfo

-> Ptr Word32

pImageIndex

-> IO VkResult 

Success codes: VK_SUCCESS, VK_TIMEOUT, VK_NOT_READY, VK_SUBOPTIMAL_KHR.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY, VK_ERROR_DEVICE_LOST, VK_ERROR_OUT_OF_DATE_KHR, VK_ERROR_SURFACE_LOST_KHR.

VkResult vkAcquireNextImage2KHR
    ( VkDevice device
    , const VkAcquireNextImageInfoKHR* pAcquireInfo
    , uint32_t* pImageIndex
    )

vkAcquireNextImage2KHR registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myAcquireNextImage2KHR <- vkGetDeviceProc @VkAcquireNextImage2KHR vkDevice

or less efficient:

myAcquireNextImage2KHR <- vkGetProc @VkAcquireNextImage2KHR

Note: vkXxx and vkXxxSafe versions of the call refer to using unsafe of safe FFI respectively.

data VkOffset2D Source #

typedef struct VkOffset2D {
    int32_t        x;
    int32_t        y;
} VkOffset2D;

VkOffset2D registry at www.khronos.org

Instances

Eq VkOffset2D Source # 
Ord VkOffset2D Source # 
Show VkOffset2D Source # 
Storable VkOffset2D Source # 
VulkanMarshalPrim VkOffset2D Source # 
VulkanMarshal VkOffset2D Source # 
CanWriteField "x" VkOffset2D Source # 
CanWriteField "y" VkOffset2D Source # 
CanReadField "x" VkOffset2D Source # 
CanReadField "y" VkOffset2D Source # 
HasField "x" VkOffset2D Source # 
HasField "y" VkOffset2D Source # 
type StructFields VkOffset2D Source # 
type StructFields VkOffset2D = (:) Symbol "x" ((:) Symbol "y" ([] Symbol))
type CUnionType VkOffset2D Source # 
type ReturnedOnly VkOffset2D Source # 
type StructExtends VkOffset2D Source # 
type FieldType "x" VkOffset2D Source # 
type FieldType "y" VkOffset2D Source # 
type FieldOptional "x" VkOffset2D Source # 
type FieldOptional "y" VkOffset2D Source # 
type FieldOffset "x" VkOffset2D Source # 
type FieldOffset "x" VkOffset2D = 0
type FieldOffset "y" VkOffset2D Source # 
type FieldOffset "y" VkOffset2D = 4
type FieldIsArray "x" VkOffset2D Source # 
type FieldIsArray "y" VkOffset2D Source # 

data VkOffset3D Source #

typedef struct VkOffset3D {
    int32_t        x;
    int32_t        y;
    int32_t        z;
} VkOffset3D;

VkOffset3D registry at www.khronos.org

Instances

Eq VkOffset3D Source # 
Ord VkOffset3D Source # 
Show VkOffset3D Source # 
Storable VkOffset3D Source # 
VulkanMarshalPrim VkOffset3D Source # 
VulkanMarshal VkOffset3D Source # 
CanWriteField "x" VkOffset3D Source # 
CanWriteField "y" VkOffset3D Source # 
CanWriteField "z" VkOffset3D Source # 
CanReadField "x" VkOffset3D Source # 
CanReadField "y" VkOffset3D Source # 
CanReadField "z" VkOffset3D Source # 
HasField "x" VkOffset3D Source # 
HasField "y" VkOffset3D Source # 
HasField "z" VkOffset3D Source # 
type StructFields VkOffset3D Source # 
type StructFields VkOffset3D = (:) Symbol "x" ((:) Symbol "y" ((:) Symbol "z" ([] Symbol)))
type CUnionType VkOffset3D Source # 
type ReturnedOnly VkOffset3D Source # 
type StructExtends VkOffset3D Source # 
type FieldType "x" VkOffset3D Source # 
type FieldType "y" VkOffset3D Source # 
type FieldType "z" VkOffset3D Source # 
type FieldOptional "x" VkOffset3D Source # 
type FieldOptional "y" VkOffset3D Source # 
type FieldOptional "z" VkOffset3D Source # 
type FieldOffset "x" VkOffset3D Source # 
type FieldOffset "x" VkOffset3D = 0
type FieldOffset "y" VkOffset3D Source # 
type FieldOffset "y" VkOffset3D = 4
type FieldOffset "z" VkOffset3D Source # 
type FieldOffset "z" VkOffset3D = 8
type FieldIsArray "x" VkOffset3D Source # 
type FieldIsArray "y" VkOffset3D Source # 
type FieldIsArray "z" VkOffset3D Source # 

data VkRect2D Source #

typedef struct VkRect2D {
    VkOffset2D     offset;
    VkExtent2D     extent;
} VkRect2D;

VkRect2D registry at www.khronos.org

Constructors

VkRect2D# Addr# ByteArray# 

Instances

Eq VkRect2D Source # 
Ord VkRect2D Source # 
Show VkRect2D Source # 
Storable VkRect2D Source # 
VulkanMarshalPrim VkRect2D Source # 
VulkanMarshal VkRect2D Source # 
CanWriteField "extent" VkRect2D Source # 

Methods

writeField :: Ptr VkRect2D -> FieldType "extent" VkRect2D -> IO () Source #

CanWriteField "offset" VkRect2D Source # 

Methods

writeField :: Ptr VkRect2D -> FieldType "offset" VkRect2D -> IO () Source #

CanReadField "extent" VkRect2D Source # 
CanReadField "offset" VkRect2D Source # 
HasField "extent" VkRect2D Source # 

Associated Types

type FieldType ("extent" :: Symbol) VkRect2D :: Type Source #

type FieldOptional ("extent" :: Symbol) VkRect2D :: Bool Source #

type FieldOffset ("extent" :: Symbol) VkRect2D :: Nat Source #

type FieldIsArray ("extent" :: Symbol) VkRect2D :: Bool Source #

HasField "offset" VkRect2D Source # 

Associated Types

type FieldType ("offset" :: Symbol) VkRect2D :: Type Source #

type FieldOptional ("offset" :: Symbol) VkRect2D :: Bool Source #

type FieldOffset ("offset" :: Symbol) VkRect2D :: Nat Source #

type FieldIsArray ("offset" :: Symbol) VkRect2D :: Bool Source #

type StructFields VkRect2D Source # 
type StructFields VkRect2D = (:) Symbol "offset" ((:) Symbol "extent" ([] Symbol))
type CUnionType VkRect2D Source # 
type ReturnedOnly VkRect2D Source # 
type StructExtends VkRect2D Source # 
type FieldType "extent" VkRect2D Source # 
type FieldType "extent" VkRect2D = VkExtent2D
type FieldType "offset" VkRect2D Source # 
type FieldType "offset" VkRect2D = VkOffset2D
type FieldOptional "extent" VkRect2D Source # 
type FieldOptional "extent" VkRect2D = False
type FieldOptional "offset" VkRect2D Source # 
type FieldOptional "offset" VkRect2D = False
type FieldOffset "extent" VkRect2D Source # 
type FieldOffset "extent" VkRect2D = 8
type FieldOffset "offset" VkRect2D Source # 
type FieldOffset "offset" VkRect2D = 0
type FieldIsArray "extent" VkRect2D Source # 
type FieldIsArray "extent" VkRect2D = False
type FieldIsArray "offset" VkRect2D Source # 
type FieldIsArray "offset" VkRect2D = False

data VkRectLayerKHR Source #

typedef struct VkRectLayerKHR {
    VkOffset2D                       offset;
    VkExtent2D                       extent;
    uint32_t                         layer;
} VkRectLayerKHR;

VkRectLayerKHR registry at www.khronos.org

Instances

Eq VkRectLayerKHR Source # 
Ord VkRectLayerKHR Source # 
Show VkRectLayerKHR Source # 
Storable VkRectLayerKHR Source # 
VulkanMarshalPrim VkRectLayerKHR Source # 
VulkanMarshal VkRectLayerKHR Source # 
CanWriteField "extent" VkRectLayerKHR Source # 
CanWriteField "layer" VkRectLayerKHR Source # 
CanWriteField "offset" VkRectLayerKHR Source # 
CanReadField "extent" VkRectLayerKHR Source # 
CanReadField "layer" VkRectLayerKHR Source # 
CanReadField "offset" VkRectLayerKHR Source # 
HasField "extent" VkRectLayerKHR Source # 

Associated Types

type FieldType ("extent" :: Symbol) VkRectLayerKHR :: Type Source #

type FieldOptional ("extent" :: Symbol) VkRectLayerKHR :: Bool Source #

type FieldOffset ("extent" :: Symbol) VkRectLayerKHR :: Nat Source #

type FieldIsArray ("extent" :: Symbol) VkRectLayerKHR :: Bool Source #

HasField "layer" VkRectLayerKHR Source # 
HasField "offset" VkRectLayerKHR Source # 

Associated Types

type FieldType ("offset" :: Symbol) VkRectLayerKHR :: Type Source #

type FieldOptional ("offset" :: Symbol) VkRectLayerKHR :: Bool Source #

type FieldOffset ("offset" :: Symbol) VkRectLayerKHR :: Nat Source #

type FieldIsArray ("offset" :: Symbol) VkRectLayerKHR :: Bool Source #

type StructFields VkRectLayerKHR Source # 
type StructFields VkRectLayerKHR = (:) Symbol "offset" ((:) Symbol "extent" ((:) Symbol "layer" ([] Symbol)))
type CUnionType VkRectLayerKHR Source # 
type ReturnedOnly VkRectLayerKHR Source # 
type StructExtends VkRectLayerKHR Source # 
type FieldType "extent" VkRectLayerKHR Source # 
type FieldType "layer" VkRectLayerKHR Source # 
type FieldType "offset" VkRectLayerKHR Source # 
type FieldOptional "extent" VkRectLayerKHR Source # 
type FieldOptional "layer" VkRectLayerKHR Source # 
type FieldOptional "offset" VkRectLayerKHR Source # 
type FieldOffset "extent" VkRectLayerKHR Source # 
type FieldOffset "extent" VkRectLayerKHR = 8
type FieldOffset "layer" VkRectLayerKHR Source # 
type FieldOffset "layer" VkRectLayerKHR = 16
type FieldOffset "offset" VkRectLayerKHR Source # 
type FieldOffset "offset" VkRectLayerKHR = 0
type FieldIsArray "extent" VkRectLayerKHR Source # 
type FieldIsArray "layer" VkRectLayerKHR Source # 
type FieldIsArray "offset" VkRectLayerKHR Source # 

pattern VK_SWAPCHAIN_CREATE_SPLIT_INSTANCE_BIND_REGIONS_BIT_KHR :: VkSwapchainCreateFlagBitsKHR Source #

Allow images with VK_IMAGE_CREATE_SPLIT_INSTANCE_BIND_REGIONS_BIT

bitpos = 0

Orphan instances

VulkanProc "vkAcquireNextImage2KHR" Source # 

Associated Types

type VkProcType ("vkAcquireNextImage2KHR" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtr :: FunPtr (VkProcType "vkAcquireNextImage2KHR") -> VkProcType "vkAcquireNextImage2KHR" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkAcquireNextImage2KHR") -> VkProcType "vkAcquireNextImage2KHR" Source #

VulkanProc "vkAcquireNextImageKHR" Source # 

Associated Types

type VkProcType ("vkAcquireNextImageKHR" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtr :: FunPtr (VkProcType "vkAcquireNextImageKHR") -> VkProcType "vkAcquireNextImageKHR" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkAcquireNextImageKHR") -> VkProcType "vkAcquireNextImageKHR" Source #

VulkanProc "vkCreateSwapchainKHR" Source # 

Associated Types

type VkProcType ("vkCreateSwapchainKHR" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtr :: FunPtr (VkProcType "vkCreateSwapchainKHR") -> VkProcType "vkCreateSwapchainKHR" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkCreateSwapchainKHR") -> VkProcType "vkCreateSwapchainKHR" Source #

VulkanProc "vkDestroySwapchainKHR" Source # 

Associated Types

type VkProcType ("vkDestroySwapchainKHR" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtr :: FunPtr (VkProcType "vkDestroySwapchainKHR") -> VkProcType "vkDestroySwapchainKHR" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkDestroySwapchainKHR") -> VkProcType "vkDestroySwapchainKHR" Source #

VulkanProc "vkGetDeviceGroupPresentCapabilitiesKHR" Source # 

Associated Types

type VkProcType ("vkGetDeviceGroupPresentCapabilitiesKHR" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtr :: FunPtr (VkProcType "vkGetDeviceGroupPresentCapabilitiesKHR") -> VkProcType "vkGetDeviceGroupPresentCapabilitiesKHR" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkGetDeviceGroupPresentCapabilitiesKHR") -> VkProcType "vkGetDeviceGroupPresentCapabilitiesKHR" Source #

VulkanProc "vkGetDeviceGroupSurfacePresentModesKHR" Source # 

Associated Types

type VkProcType ("vkGetDeviceGroupSurfacePresentModesKHR" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtr :: FunPtr (VkProcType "vkGetDeviceGroupSurfacePresentModesKHR") -> VkProcType "vkGetDeviceGroupSurfacePresentModesKHR" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkGetDeviceGroupSurfacePresentModesKHR") -> VkProcType "vkGetDeviceGroupSurfacePresentModesKHR" Source #

VulkanProc "vkGetPhysicalDevicePresentRectanglesKHR" Source # 

Associated Types

type VkProcType ("vkGetPhysicalDevicePresentRectanglesKHR" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtr :: FunPtr (VkProcType "vkGetPhysicalDevicePresentRectanglesKHR") -> VkProcType "vkGetPhysicalDevicePresentRectanglesKHR" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkGetPhysicalDevicePresentRectanglesKHR") -> VkProcType "vkGetPhysicalDevicePresentRectanglesKHR" Source #

VulkanProc "vkGetSwapchainImagesKHR" Source # 

Associated Types

type VkProcType ("vkGetSwapchainImagesKHR" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtr :: FunPtr (VkProcType "vkGetSwapchainImagesKHR") -> VkProcType "vkGetSwapchainImagesKHR" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkGetSwapchainImagesKHR") -> VkProcType "vkGetSwapchainImagesKHR" Source #

VulkanProc "vkQueuePresentKHR" Source # 

Associated Types

type VkProcType ("vkQueuePresentKHR" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtr :: FunPtr (VkProcType "vkQueuePresentKHR") -> VkProcType "vkQueuePresentKHR" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkQueuePresentKHR") -> VkProcType "vkQueuePresentKHR" Source #