vulkan-api-1.1.1.0: Low-level low-overhead vulkan api bindings
Safe HaskellNone
LanguageHaskell2010

Graphics.Vulkan.Ext.VK_KHR_surface

Synopsis

Vulkan extension: VK_KHR_surface

supported: vulkan

contact: James Jones cubanismo,Ian Elliott ianelliottgoogle.com

author: KHR

type: instance

Extension number: 1

type VkDestroySurfaceKHR = "vkDestroySurfaceKHR" Source #

type HS_vkDestroySurfaceKHR Source #

Arguments

 = VkInstance

instance

-> VkSurfaceKHR

surface

-> Ptr VkAllocationCallbacks

pAllocator

-> IO () 
void vkDestroySurfaceKHR
    ( VkInstance instance
    , VkSurfaceKHR surface
    , const VkAllocationCallbacks* pAllocator
    )

vkDestroySurfaceKHR registry at www.khronos.org

vkDestroySurfaceKHR Source #

Arguments

:: VkInstance

instance

-> VkSurfaceKHR

surface

-> Ptr VkAllocationCallbacks

pAllocator

-> IO () 
void vkDestroySurfaceKHR
    ( VkInstance instance
    , VkSurfaceKHR surface
    , const VkAllocationCallbacks* pAllocator
    )

vkDestroySurfaceKHR registry at www.khronos.org

Note: flag useNativeFFI-1-0 is disabled, so this function is looked up dynamically at runtime; vkDestroySurfaceKHRSafe and vkDestroySurfaceKHR are synonyms.

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

myDestroySurfaceKHR <- vkGetInstanceProc @VkDestroySurfaceKHR vkInstance

or less efficient:

myDestroySurfaceKHR <- vkGetProc @VkDestroySurfaceKHR

vkDestroySurfaceKHRSafe Source #

Arguments

:: VkInstance

instance

-> VkSurfaceKHR

surface

-> Ptr VkAllocationCallbacks

pAllocator

-> IO () 
void vkDestroySurfaceKHR
    ( VkInstance instance
    , VkSurfaceKHR surface
    , const VkAllocationCallbacks* pAllocator
    )

vkDestroySurfaceKHR registry at www.khronos.org

Note: flag useNativeFFI-1-0 is disabled, so this function is looked up dynamically at runtime; vkDestroySurfaceKHRSafe and vkDestroySurfaceKHR are synonyms.

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

myDestroySurfaceKHR <- vkGetInstanceProc @VkDestroySurfaceKHR vkInstance

or less efficient:

myDestroySurfaceKHR <- vkGetProc @VkDestroySurfaceKHR

type VkGetPhysicalDeviceSurfaceSupportKHR = "vkGetPhysicalDeviceSurfaceSupportKHR" Source #

type HS_vkGetPhysicalDeviceSurfaceSupportKHR Source #

Arguments

 = VkPhysicalDevice

physicalDevice

-> Word32

queueFamilyIndex

-> VkSurfaceKHR

surface

-> Ptr VkBool32

pSupported

-> 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 vkGetPhysicalDeviceSurfaceSupportKHR
    ( VkPhysicalDevice physicalDevice
    , uint32_t queueFamilyIndex
    , VkSurfaceKHR surface
    , VkBool32* pSupported
    )

vkGetPhysicalDeviceSurfaceSupportKHR registry at www.khronos.org

vkGetPhysicalDeviceSurfaceSupportKHR Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> Word32

queueFamilyIndex

-> VkSurfaceKHR

surface

-> Ptr VkBool32

pSupported

-> 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 vkGetPhysicalDeviceSurfaceSupportKHR
    ( VkPhysicalDevice physicalDevice
    , uint32_t queueFamilyIndex
    , VkSurfaceKHR surface
    , VkBool32* pSupported
    )

vkGetPhysicalDeviceSurfaceSupportKHR registry at www.khronos.org

Note: flag useNativeFFI-1-0 is disabled, so this function is looked up dynamically at runtime; vkGetPhysicalDeviceSurfaceSupportKHRSafe and vkGetPhysicalDeviceSurfaceSupportKHR are synonyms.

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

myGetPhysicalDeviceSurfaceSupportKHR <- vkGetInstanceProc @VkGetPhysicalDeviceSurfaceSupportKHR vkInstance

or less efficient:

myGetPhysicalDeviceSurfaceSupportKHR <- vkGetProc @VkGetPhysicalDeviceSurfaceSupportKHR

vkGetPhysicalDeviceSurfaceSupportKHRSafe Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> Word32

queueFamilyIndex

-> VkSurfaceKHR

surface

-> Ptr VkBool32

pSupported

-> 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 vkGetPhysicalDeviceSurfaceSupportKHR
    ( VkPhysicalDevice physicalDevice
    , uint32_t queueFamilyIndex
    , VkSurfaceKHR surface
    , VkBool32* pSupported
    )

vkGetPhysicalDeviceSurfaceSupportKHR registry at www.khronos.org

Note: flag useNativeFFI-1-0 is disabled, so this function is looked up dynamically at runtime; vkGetPhysicalDeviceSurfaceSupportKHRSafe and vkGetPhysicalDeviceSurfaceSupportKHR are synonyms.

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

myGetPhysicalDeviceSurfaceSupportKHR <- vkGetInstanceProc @VkGetPhysicalDeviceSurfaceSupportKHR vkInstance

or less efficient:

myGetPhysicalDeviceSurfaceSupportKHR <- vkGetProc @VkGetPhysicalDeviceSurfaceSupportKHR

type VkGetPhysicalDeviceSurfaceCapabilitiesKHR = "vkGetPhysicalDeviceSurfaceCapabilitiesKHR" Source #

type HS_vkGetPhysicalDeviceSurfaceCapabilitiesKHR Source #

Arguments

 = VkPhysicalDevice

physicalDevice

-> VkSurfaceKHR

surface

-> Ptr VkSurfaceCapabilitiesKHR

pSurfaceCapabilities

-> 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 vkGetPhysicalDeviceSurfaceCapabilitiesKHR
    ( VkPhysicalDevice physicalDevice
    , VkSurfaceKHR surface
    , VkSurfaceCapabilitiesKHR* pSurfaceCapabilities
    )

vkGetPhysicalDeviceSurfaceCapabilitiesKHR registry at www.khronos.org

vkGetPhysicalDeviceSurfaceCapabilitiesKHR Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> VkSurfaceKHR

surface

-> Ptr VkSurfaceCapabilitiesKHR

pSurfaceCapabilities

-> 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 vkGetPhysicalDeviceSurfaceCapabilitiesKHR
    ( VkPhysicalDevice physicalDevice
    , VkSurfaceKHR surface
    , VkSurfaceCapabilitiesKHR* pSurfaceCapabilities
    )

vkGetPhysicalDeviceSurfaceCapabilitiesKHR registry at www.khronos.org

Note: flag useNativeFFI-1-0 is disabled, so this function is looked up dynamically at runtime; vkGetPhysicalDeviceSurfaceCapabilitiesKHRSafe and vkGetPhysicalDeviceSurfaceCapabilitiesKHR are synonyms.

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

myGetPhysicalDeviceSurfaceCapabilitiesKHR <- vkGetInstanceProc @VkGetPhysicalDeviceSurfaceCapabilitiesKHR vkInstance

or less efficient:

myGetPhysicalDeviceSurfaceCapabilitiesKHR <- vkGetProc @VkGetPhysicalDeviceSurfaceCapabilitiesKHR

vkGetPhysicalDeviceSurfaceCapabilitiesKHRSafe Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> VkSurfaceKHR

surface

-> Ptr VkSurfaceCapabilitiesKHR

pSurfaceCapabilities

-> 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 vkGetPhysicalDeviceSurfaceCapabilitiesKHR
    ( VkPhysicalDevice physicalDevice
    , VkSurfaceKHR surface
    , VkSurfaceCapabilitiesKHR* pSurfaceCapabilities
    )

vkGetPhysicalDeviceSurfaceCapabilitiesKHR registry at www.khronos.org

Note: flag useNativeFFI-1-0 is disabled, so this function is looked up dynamically at runtime; vkGetPhysicalDeviceSurfaceCapabilitiesKHRSafe and vkGetPhysicalDeviceSurfaceCapabilitiesKHR are synonyms.

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

myGetPhysicalDeviceSurfaceCapabilitiesKHR <- vkGetInstanceProc @VkGetPhysicalDeviceSurfaceCapabilitiesKHR vkInstance

or less efficient:

myGetPhysicalDeviceSurfaceCapabilitiesKHR <- vkGetProc @VkGetPhysicalDeviceSurfaceCapabilitiesKHR

type VkGetPhysicalDeviceSurfaceFormatsKHR = "vkGetPhysicalDeviceSurfaceFormatsKHR" Source #

type HS_vkGetPhysicalDeviceSurfaceFormatsKHR Source #

Arguments

 = VkPhysicalDevice

physicalDevice

-> VkSurfaceKHR

surface

-> Ptr Word32

pSurfaceFormatCount

-> Ptr VkSurfaceFormatKHR

pSurfaceFormats

-> IO VkResult 

Success codes: VK_SUCCESS, VK_INCOMPLETE.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY, VK_ERROR_SURFACE_LOST_KHR.

VkResult vkGetPhysicalDeviceSurfaceFormatsKHR
    ( VkPhysicalDevice physicalDevice
    , VkSurfaceKHR surface
    , uint32_t* pSurfaceFormatCount
    , VkSurfaceFormatKHR* pSurfaceFormats
    )

vkGetPhysicalDeviceSurfaceFormatsKHR registry at www.khronos.org

vkGetPhysicalDeviceSurfaceFormatsKHR Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> VkSurfaceKHR

surface

-> Ptr Word32

pSurfaceFormatCount

-> Ptr VkSurfaceFormatKHR

pSurfaceFormats

-> IO VkResult 

Success codes: VK_SUCCESS, VK_INCOMPLETE.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY, VK_ERROR_SURFACE_LOST_KHR.

VkResult vkGetPhysicalDeviceSurfaceFormatsKHR
    ( VkPhysicalDevice physicalDevice
    , VkSurfaceKHR surface
    , uint32_t* pSurfaceFormatCount
    , VkSurfaceFormatKHR* pSurfaceFormats
    )

vkGetPhysicalDeviceSurfaceFormatsKHR registry at www.khronos.org

Note: flag useNativeFFI-1-0 is disabled, so this function is looked up dynamically at runtime; vkGetPhysicalDeviceSurfaceFormatsKHRSafe and vkGetPhysicalDeviceSurfaceFormatsKHR are synonyms.

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

myGetPhysicalDeviceSurfaceFormatsKHR <- vkGetInstanceProc @VkGetPhysicalDeviceSurfaceFormatsKHR vkInstance

or less efficient:

myGetPhysicalDeviceSurfaceFormatsKHR <- vkGetProc @VkGetPhysicalDeviceSurfaceFormatsKHR

vkGetPhysicalDeviceSurfaceFormatsKHRSafe Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> VkSurfaceKHR

surface

-> Ptr Word32

pSurfaceFormatCount

-> Ptr VkSurfaceFormatKHR

pSurfaceFormats

-> IO VkResult 

Success codes: VK_SUCCESS, VK_INCOMPLETE.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY, VK_ERROR_SURFACE_LOST_KHR.

VkResult vkGetPhysicalDeviceSurfaceFormatsKHR
    ( VkPhysicalDevice physicalDevice
    , VkSurfaceKHR surface
    , uint32_t* pSurfaceFormatCount
    , VkSurfaceFormatKHR* pSurfaceFormats
    )

vkGetPhysicalDeviceSurfaceFormatsKHR registry at www.khronos.org

Note: flag useNativeFFI-1-0 is disabled, so this function is looked up dynamically at runtime; vkGetPhysicalDeviceSurfaceFormatsKHRSafe and vkGetPhysicalDeviceSurfaceFormatsKHR are synonyms.

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

myGetPhysicalDeviceSurfaceFormatsKHR <- vkGetInstanceProc @VkGetPhysicalDeviceSurfaceFormatsKHR vkInstance

or less efficient:

myGetPhysicalDeviceSurfaceFormatsKHR <- vkGetProc @VkGetPhysicalDeviceSurfaceFormatsKHR

type VkGetPhysicalDeviceSurfacePresentModesKHR = "vkGetPhysicalDeviceSurfacePresentModesKHR" Source #

type HS_vkGetPhysicalDeviceSurfacePresentModesKHR Source #

Arguments

 = VkPhysicalDevice

physicalDevice

-> VkSurfaceKHR

surface

-> Ptr Word32

pPresentModeCount

-> Ptr VkPresentModeKHR

pPresentModes

-> IO VkResult 

Success codes: VK_SUCCESS, VK_INCOMPLETE.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY, VK_ERROR_SURFACE_LOST_KHR.

VkResult vkGetPhysicalDeviceSurfacePresentModesKHR
    ( VkPhysicalDevice physicalDevice
    , VkSurfaceKHR surface
    , uint32_t* pPresentModeCount
    , VkPresentModeKHR* pPresentModes
    )

vkGetPhysicalDeviceSurfacePresentModesKHR registry at www.khronos.org

vkGetPhysicalDeviceSurfacePresentModesKHR Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> VkSurfaceKHR

surface

-> Ptr Word32

pPresentModeCount

-> Ptr VkPresentModeKHR

pPresentModes

-> IO VkResult 

Success codes: VK_SUCCESS, VK_INCOMPLETE.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY, VK_ERROR_SURFACE_LOST_KHR.

VkResult vkGetPhysicalDeviceSurfacePresentModesKHR
    ( VkPhysicalDevice physicalDevice
    , VkSurfaceKHR surface
    , uint32_t* pPresentModeCount
    , VkPresentModeKHR* pPresentModes
    )

vkGetPhysicalDeviceSurfacePresentModesKHR registry at www.khronos.org

Note: flag useNativeFFI-1-0 is disabled, so this function is looked up dynamically at runtime; vkGetPhysicalDeviceSurfacePresentModesKHRSafe and vkGetPhysicalDeviceSurfacePresentModesKHR are synonyms.

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

myGetPhysicalDeviceSurfacePresentModesKHR <- vkGetInstanceProc @VkGetPhysicalDeviceSurfacePresentModesKHR vkInstance

or less efficient:

myGetPhysicalDeviceSurfacePresentModesKHR <- vkGetProc @VkGetPhysicalDeviceSurfacePresentModesKHR

vkGetPhysicalDeviceSurfacePresentModesKHRSafe Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> VkSurfaceKHR

surface

-> Ptr Word32

pPresentModeCount

-> Ptr VkPresentModeKHR

pPresentModes

-> IO VkResult 

Success codes: VK_SUCCESS, VK_INCOMPLETE.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY, VK_ERROR_SURFACE_LOST_KHR.

VkResult vkGetPhysicalDeviceSurfacePresentModesKHR
    ( VkPhysicalDevice physicalDevice
    , VkSurfaceKHR surface
    , uint32_t* pPresentModeCount
    , VkPresentModeKHR* pPresentModes
    )

vkGetPhysicalDeviceSurfacePresentModesKHR registry at www.khronos.org

Note: flag useNativeFFI-1-0 is disabled, so this function is looked up dynamically at runtime; vkGetPhysicalDeviceSurfacePresentModesKHRSafe and vkGetPhysicalDeviceSurfacePresentModesKHR are synonyms.

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

myGetPhysicalDeviceSurfacePresentModesKHR <- vkGetInstanceProc @VkGetPhysicalDeviceSurfacePresentModesKHR vkInstance

or less efficient:

myGetPhysicalDeviceSurfacePresentModesKHR <- vkGetProc @VkGetPhysicalDeviceSurfacePresentModesKHR

newtype VkBool32 Source #

Constructors

VkBool32 Word32 

Instances

Instances details
Bounded VkBool32 Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Enum VkBool32 Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Eq VkBool32 Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Integral VkBool32 Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Data VkBool32 Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

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 :: forall r r'. (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 # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Ord VkBool32 Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Read VkBool32 Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Real VkBool32 Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Show VkBool32 Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Generic VkBool32 Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Associated Types

type Rep VkBool32 :: Type -> Type #

Methods

from :: VkBool32 -> Rep VkBool32 x #

to :: Rep VkBool32 x -> VkBool32 #

Storable VkBool32 Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Bits VkBool32 Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

FiniteBits VkBool32 Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

type Rep VkBool32 Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

type Rep VkBool32 = D1 ('MetaData "VkBool32" "Graphics.Vulkan.Types.BaseTypes" "vulkan-api-1.1.1.0-LBmI6dMSRRRGKEhmYXhCF0" 'True) (C1 ('MetaCons "VkBool32" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32)))

newtype VkDeviceSize Source #

Constructors

VkDeviceSize Word64 

Instances

Instances details
Bounded VkDeviceSize Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Enum VkDeviceSize Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Eq VkDeviceSize Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Integral VkDeviceSize Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Data VkDeviceSize Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

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 :: forall r r'. (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 # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Ord VkDeviceSize Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Read VkDeviceSize Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Real VkDeviceSize Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Show VkDeviceSize Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Generic VkDeviceSize Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Associated Types

type Rep VkDeviceSize :: Type -> Type #

Storable VkDeviceSize Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Bits VkDeviceSize Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

FiniteBits VkDeviceSize Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

type Rep VkDeviceSize Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

type Rep VkDeviceSize = D1 ('MetaData "VkDeviceSize" "Graphics.Vulkan.Types.BaseTypes" "vulkan-api-1.1.1.0-LBmI6dMSRRRGKEhmYXhCF0" 'True) (C1 ('MetaCons "VkDeviceSize" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)))

newtype VkFlags Source #

Constructors

VkFlags Word32 

Instances

Instances details
Bounded VkFlags Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Enum VkFlags Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Eq VkFlags Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Methods

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

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

Integral VkFlags Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Data VkFlags Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

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 :: forall r r'. (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 # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Ord VkFlags Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Read VkFlags Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Real VkFlags Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Show VkFlags Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Generic VkFlags Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Associated Types

type Rep VkFlags :: Type -> Type #

Methods

from :: VkFlags -> Rep VkFlags x #

to :: Rep VkFlags x -> VkFlags #

Storable VkFlags Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Bits VkFlags Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

FiniteBits VkFlags Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

type Rep VkFlags Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

type Rep VkFlags = D1 ('MetaData "VkFlags" "Graphics.Vulkan.Types.BaseTypes" "vulkan-api-1.1.1.0-LBmI6dMSRRRGKEhmYXhCF0" 'True) (C1 ('MetaCons "VkFlags" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32)))

newtype VkSampleMask Source #

Constructors

VkSampleMask Word32 

Instances

Instances details
Bounded VkSampleMask Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Enum VkSampleMask Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Eq VkSampleMask Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Integral VkSampleMask Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Data VkSampleMask Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

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 :: forall r r'. (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 # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Ord VkSampleMask Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Read VkSampleMask Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Real VkSampleMask Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Show VkSampleMask Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Generic VkSampleMask Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Associated Types

type Rep VkSampleMask :: Type -> Type #

Storable VkSampleMask Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

Bits VkSampleMask Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

FiniteBits VkSampleMask Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

type Rep VkSampleMask Source # 
Instance details

Defined in Graphics.Vulkan.Types.BaseTypes

type Rep VkSampleMask = D1 ('MetaData "VkSampleMask" "Graphics.Vulkan.Types.BaseTypes" "vulkan-api-1.1.1.0-LBmI6dMSRRRGKEhmYXhCF0" 'True) (C1 ('MetaCons "VkSampleMask" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32)))

newtype VkColorComponentBitmask (a :: FlagType) Source #

Instances

Instances details
Bounded (VkColorComponentBitmask FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Color

Enum (VkColorComponentBitmask FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Color

Eq (VkColorComponentBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Color

Integral (VkColorComponentBitmask FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Color

Typeable a => Data (VkColorComponentBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Color

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 :: forall r r'. (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 # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Color

Ord (VkColorComponentBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Color

Read (VkColorComponentBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Color

Real (VkColorComponentBitmask FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Color

Show (VkColorComponentBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Color

Generic (VkColorComponentBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Color

Associated Types

type Rep (VkColorComponentBitmask a) :: Type -> Type #

Storable (VkColorComponentBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Color

Bits (VkColorComponentBitmask FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Color

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 # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Color

type Rep (VkColorComponentBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Color

type Rep (VkColorComponentBitmask a) = D1 ('MetaData "VkColorComponentBitmask" "Graphics.Vulkan.Types.Enum.Color" "vulkan-api-1.1.1.0-LBmI6dMSRRRGKEhmYXhCF0" 'True) (C1 ('MetaCons "VkColorComponentBitmask" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VkFlags)))

newtype VkColorSpaceKHR Source #

Constructors

VkColorSpaceKHR Int32 

Instances

Instances details
Bounded VkColorSpaceKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Color

Enum VkColorSpaceKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Color

Eq VkColorSpaceKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Color

Data VkColorSpaceKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Color

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 :: forall r r'. (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 # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Color

Ord VkColorSpaceKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Color

Read VkColorSpaceKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Color

Show VkColorSpaceKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Color

Generic VkColorSpaceKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Color

Associated Types

type Rep VkColorSpaceKHR :: Type -> Type #

Storable VkColorSpaceKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Color

type Rep VkColorSpaceKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Color

type Rep VkColorSpaceKHR = D1 ('MetaData "VkColorSpaceKHR" "Graphics.Vulkan.Types.Enum.Color" "vulkan-api-1.1.1.0-LBmI6dMSRRRGKEhmYXhCF0" 'True) (C1 ('MetaCons "VkColorSpaceKHR" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int32)))

newtype VkCompositeAlphaBitmaskKHR (a :: FlagType) Source #

Instances

Instances details
Bounded (VkCompositeAlphaBitmaskKHR FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.CompositeAlphaFlagsKHR

Enum (VkCompositeAlphaBitmaskKHR FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.CompositeAlphaFlagsKHR

Eq (VkCompositeAlphaBitmaskKHR a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.CompositeAlphaFlagsKHR

Integral (VkCompositeAlphaBitmaskKHR FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.CompositeAlphaFlagsKHR

Typeable a => Data (VkCompositeAlphaBitmaskKHR a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.CompositeAlphaFlagsKHR

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 :: forall r r'. (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 # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.CompositeAlphaFlagsKHR

Ord (VkCompositeAlphaBitmaskKHR a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.CompositeAlphaFlagsKHR

Read (VkCompositeAlphaBitmaskKHR a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.CompositeAlphaFlagsKHR

Real (VkCompositeAlphaBitmaskKHR FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.CompositeAlphaFlagsKHR

Show (VkCompositeAlphaBitmaskKHR a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.CompositeAlphaFlagsKHR

Generic (VkCompositeAlphaBitmaskKHR a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.CompositeAlphaFlagsKHR

Associated Types

type Rep (VkCompositeAlphaBitmaskKHR a) :: Type -> Type #

Storable (VkCompositeAlphaBitmaskKHR a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.CompositeAlphaFlagsKHR

Bits (VkCompositeAlphaBitmaskKHR FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.CompositeAlphaFlagsKHR

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 # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.CompositeAlphaFlagsKHR

type Rep (VkCompositeAlphaBitmaskKHR a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.CompositeAlphaFlagsKHR

type Rep (VkCompositeAlphaBitmaskKHR a) = D1 ('MetaData "VkCompositeAlphaBitmaskKHR" "Graphics.Vulkan.Types.Enum.CompositeAlphaFlagsKHR" "vulkan-api-1.1.1.0-LBmI6dMSRRRGKEhmYXhCF0" 'True) (C1 ('MetaCons "VkCompositeAlphaBitmaskKHR" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VkFlags)))

newtype VkFormat Source #

Vulkan format definitions

type = enum

VkFormat registry at www.khronos.org

Constructors

VkFormat Int32 

Instances

Instances details
Bounded VkFormat Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Format

Enum VkFormat Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Format

Eq VkFormat Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Format

Data VkFormat Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Format

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 :: forall r r'. (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 # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Format

Ord VkFormat Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Format

Read VkFormat Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Format

Show VkFormat Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Format

Generic VkFormat Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Format

Associated Types

type Rep VkFormat :: Type -> Type #

Methods

from :: VkFormat -> Rep VkFormat x #

to :: Rep VkFormat x -> VkFormat #

Storable VkFormat Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Format

type Rep VkFormat Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Format

type Rep VkFormat = D1 ('MetaData "VkFormat" "Graphics.Vulkan.Types.Enum.Format" "vulkan-api-1.1.1.0-LBmI6dMSRRRGKEhmYXhCF0" 'True) (C1 ('MetaCons "VkFormat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int32)))

newtype VkFormatFeatureBitmask (a :: FlagType) Source #

Instances

Instances details
Bounded (VkFormatFeatureBitmask FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Format

Enum (VkFormatFeatureBitmask FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Format

Eq (VkFormatFeatureBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Format

Integral (VkFormatFeatureBitmask FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Format

Typeable a => Data (VkFormatFeatureBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Format

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 :: forall r r'. (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 # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Format

Ord (VkFormatFeatureBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Format

Read (VkFormatFeatureBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Format

Real (VkFormatFeatureBitmask FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Format

Show (VkFormatFeatureBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Format

Generic (VkFormatFeatureBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Format

Associated Types

type Rep (VkFormatFeatureBitmask a) :: Type -> Type #

Storable (VkFormatFeatureBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Format

Bits (VkFormatFeatureBitmask FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Format

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 # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Format

type Rep (VkFormatFeatureBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Format

type Rep (VkFormatFeatureBitmask a) = D1 ('MetaData "VkFormatFeatureBitmask" "Graphics.Vulkan.Types.Enum.Format" "vulkan-api-1.1.1.0-LBmI6dMSRRRGKEhmYXhCF0" 'True) (C1 ('MetaCons "VkFormatFeatureBitmask" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VkFlags)))

pattern VK_FORMAT_FEATURE_SAMPLED_IMAGE_BIT :: 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 :: VkFormatFeatureBitmask a Source #

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

bitpos = 1

pattern VK_FORMAT_FEATURE_STORAGE_IMAGE_ATOMIC_BIT :: 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 :: VkFormatFeatureBitmask a Source #

Format can be used for uniform texel buffers (TBOs)

bitpos = 3

pattern VK_FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_BIT :: VkFormatFeatureBitmask a Source #

Format can be used for storage texel buffers (IBOs)

bitpos = 4

pattern VK_FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_ATOMIC_BIT :: 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 :: VkFormatFeatureBitmask a Source #

Format can be used for vertex buffers (VBOs)

bitpos = 6

pattern VK_FORMAT_FEATURE_COLOR_ATTACHMENT_BIT :: VkFormatFeatureBitmask a Source #

Format can be used for color attachment images

bitpos = 7

pattern VK_FORMAT_FEATURE_COLOR_ATTACHMENT_BLEND_BIT :: 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 :: VkFormatFeatureBitmask a Source #

Format can be used for depth/stencil attachment images

bitpos = 9

pattern VK_FORMAT_FEATURE_BLIT_SRC_BIT :: VkFormatFeatureBitmask a Source #

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

bitpos = 10

pattern VK_FORMAT_FEATURE_BLIT_DST_BIT :: 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 :: VkFormatFeatureBitmask a Source #

Format can be filtered with VK_FILTER_LINEAR when being sampled

bitpos = 12

newtype VkImageAspectBitmask (a :: FlagType) Source #

Instances

Instances details
Bounded (VkImageAspectBitmask FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Enum (VkImageAspectBitmask FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Eq (VkImageAspectBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Integral (VkImageAspectBitmask FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Typeable a => Data (VkImageAspectBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

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 :: forall r r'. (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 # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Ord (VkImageAspectBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Read (VkImageAspectBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Real (VkImageAspectBitmask FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Show (VkImageAspectBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Generic (VkImageAspectBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Associated Types

type Rep (VkImageAspectBitmask a) :: Type -> Type #

Storable (VkImageAspectBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Bits (VkImageAspectBitmask FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

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 # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

type Rep (VkImageAspectBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

type Rep (VkImageAspectBitmask a) = D1 ('MetaData "VkImageAspectBitmask" "Graphics.Vulkan.Types.Enum.Image" "vulkan-api-1.1.1.0-LBmI6dMSRRRGKEhmYXhCF0" 'True) (C1 ('MetaCons "VkImageAspectBitmask" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VkFlags)))

newtype VkImageCreateBitmask (a :: FlagType) Source #

Instances

Instances details
Bounded (VkImageCreateBitmask FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Enum (VkImageCreateBitmask FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Eq (VkImageCreateBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Integral (VkImageCreateBitmask FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Typeable a => Data (VkImageCreateBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

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 :: forall r r'. (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 # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Ord (VkImageCreateBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Read (VkImageCreateBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Real (VkImageCreateBitmask FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Show (VkImageCreateBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Generic (VkImageCreateBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Associated Types

type Rep (VkImageCreateBitmask a) :: Type -> Type #

Storable (VkImageCreateBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Bits (VkImageCreateBitmask FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

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 # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

type Rep (VkImageCreateBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

type Rep (VkImageCreateBitmask a) = D1 ('MetaData "VkImageCreateBitmask" "Graphics.Vulkan.Types.Enum.Image" "vulkan-api-1.1.1.0-LBmI6dMSRRRGKEhmYXhCF0" 'True) (C1 ('MetaCons "VkImageCreateBitmask" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VkFlags)))

pattern VK_IMAGE_CREATE_SPARSE_BINDING_BIT :: VkImageCreateBitmask a Source #

Image should support sparse backing

bitpos = 0

pattern VK_IMAGE_CREATE_SPARSE_RESIDENCY_BIT :: VkImageCreateBitmask a Source #

Image should support sparse backing with partial residency

bitpos = 1

pattern VK_IMAGE_CREATE_SPARSE_ALIASED_BIT :: 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 :: VkImageCreateBitmask a Source #

Allows image views to have different format than the base image

bitpos = 3

pattern VK_IMAGE_CREATE_CUBE_COMPATIBLE_BIT :: VkImageCreateBitmask a Source #

Allows creating image views with cube type from the created image

bitpos = 4

newtype VkImageLayout Source #

Constructors

VkImageLayout Int32 

Instances

Instances details
Bounded VkImageLayout Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Enum VkImageLayout Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Eq VkImageLayout Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Data VkImageLayout Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

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 :: forall r r'. (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 # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Ord VkImageLayout Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Read VkImageLayout Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Show VkImageLayout Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Generic VkImageLayout Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Associated Types

type Rep VkImageLayout :: Type -> Type #

Storable VkImageLayout Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

type Rep VkImageLayout Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

type Rep VkImageLayout = D1 ('MetaData "VkImageLayout" "Graphics.Vulkan.Types.Enum.Image" "vulkan-api-1.1.1.0-LBmI6dMSRRRGKEhmYXhCF0" 'True) (C1 ('MetaCons "VkImageLayout" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe 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

Instances details
Bounded VkImageTiling Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Enum VkImageTiling Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Eq VkImageTiling Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Data VkImageTiling Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

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 :: forall r r'. (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 # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Ord VkImageTiling Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Read VkImageTiling Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Show VkImageTiling Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Generic VkImageTiling Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Associated Types

type Rep VkImageTiling :: Type -> Type #

Storable VkImageTiling Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

type Rep VkImageTiling Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

type Rep VkImageTiling = D1 ('MetaData "VkImageTiling" "Graphics.Vulkan.Types.Enum.Image" "vulkan-api-1.1.1.0-LBmI6dMSRRRGKEhmYXhCF0" 'True) (C1 ('MetaCons "VkImageTiling" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int32)))

newtype VkImageType Source #

Constructors

VkImageType Int32 

Instances

Instances details
Bounded VkImageType Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Enum VkImageType Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Eq VkImageType Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Data VkImageType Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

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 :: forall r r'. (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 # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Ord VkImageType Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Read VkImageType Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Show VkImageType Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Generic VkImageType Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Associated Types

type Rep VkImageType :: Type -> Type #

Storable VkImageType Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

type Rep VkImageType Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

type Rep VkImageType = D1 ('MetaData "VkImageType" "Graphics.Vulkan.Types.Enum.Image" "vulkan-api-1.1.1.0-LBmI6dMSRRRGKEhmYXhCF0" 'True) (C1 ('MetaCons "VkImageType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int32)))

newtype VkImageUsageBitmask (a :: FlagType) Source #

Instances

Instances details
Bounded (VkImageUsageBitmask FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Enum (VkImageUsageBitmask FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Eq (VkImageUsageBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Integral (VkImageUsageBitmask FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Typeable a => Data (VkImageUsageBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

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 :: forall r r'. (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 # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Ord (VkImageUsageBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Read (VkImageUsageBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Real (VkImageUsageBitmask FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Show (VkImageUsageBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Generic (VkImageUsageBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Associated Types

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

Storable (VkImageUsageBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Bits (VkImageUsageBitmask FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

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 # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

type Rep (VkImageUsageBitmask a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

type Rep (VkImageUsageBitmask a) = D1 ('MetaData "VkImageUsageBitmask" "Graphics.Vulkan.Types.Enum.Image" "vulkan-api-1.1.1.0-LBmI6dMSRRRGKEhmYXhCF0" 'True) (C1 ('MetaCons "VkImageUsageBitmask" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VkFlags)))

pattern VK_IMAGE_USAGE_TRANSFER_SRC_BIT :: VkImageUsageBitmask a Source #

Can be used as a source of transfer operations

bitpos = 0

pattern VK_IMAGE_USAGE_TRANSFER_DST_BIT :: VkImageUsageBitmask a Source #

Can be used as a destination of transfer operations

bitpos = 1

pattern VK_IMAGE_USAGE_SAMPLED_BIT :: VkImageUsageBitmask a Source #

Can be sampled from (SAMPLED_IMAGE and COMBINED_IMAGE_SAMPLER descriptor types)

bitpos = 2

pattern VK_IMAGE_USAGE_STORAGE_BIT :: VkImageUsageBitmask a Source #

Can be used as storage image (STORAGE_IMAGE descriptor type)

bitpos = 3

pattern VK_IMAGE_USAGE_COLOR_ATTACHMENT_BIT :: VkImageUsageBitmask a Source #

Can be used as framebuffer color attachment

bitpos = 4

pattern VK_IMAGE_USAGE_DEPTH_STENCIL_ATTACHMENT_BIT :: VkImageUsageBitmask a Source #

Can be used as framebuffer depth/stencil attachment

bitpos = 5

pattern VK_IMAGE_USAGE_TRANSIENT_ATTACHMENT_BIT :: VkImageUsageBitmask a Source #

Image data not needed outside of rendering

bitpos = 6

pattern VK_IMAGE_USAGE_INPUT_ATTACHMENT_BIT :: VkImageUsageBitmask a Source #

Can be used as framebuffer input attachment

bitpos = 7

newtype VkImageViewType Source #

Constructors

VkImageViewType Int32 

Instances

Instances details
Bounded VkImageViewType Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Enum VkImageViewType Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Eq VkImageViewType Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Data VkImageViewType Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

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 :: forall r r'. (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 # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Ord VkImageViewType Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Read VkImageViewType Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Show VkImageViewType Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Generic VkImageViewType Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

Associated Types

type Rep VkImageViewType :: Type -> Type #

Storable VkImageViewType Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

type Rep VkImageViewType Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Image

type Rep VkImageViewType = D1 ('MetaData "VkImageViewType" "Graphics.Vulkan.Types.Enum.Image" "vulkan-api-1.1.1.0-LBmI6dMSRRRGKEhmYXhCF0" 'True) (C1 ('MetaCons "VkImageViewType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int32)))

newtype VkInternalAllocationType Source #

Instances

Instances details
Bounded VkInternalAllocationType Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.InternalAllocationType

Enum VkInternalAllocationType Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.InternalAllocationType

Eq VkInternalAllocationType Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.InternalAllocationType

Data VkInternalAllocationType Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.InternalAllocationType

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 :: forall r r'. (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 # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.InternalAllocationType

Ord VkInternalAllocationType Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.InternalAllocationType

Read VkInternalAllocationType Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.InternalAllocationType

Show VkInternalAllocationType Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.InternalAllocationType

Generic VkInternalAllocationType Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.InternalAllocationType

Associated Types

type Rep VkInternalAllocationType :: Type -> Type #

Storable VkInternalAllocationType Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.InternalAllocationType

type Rep VkInternalAllocationType Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.InternalAllocationType

type Rep VkInternalAllocationType = D1 ('MetaData "VkInternalAllocationType" "Graphics.Vulkan.Types.Enum.InternalAllocationType" "vulkan-api-1.1.1.0-LBmI6dMSRRRGKEhmYXhCF0" 'True) (C1 ('MetaCons "VkInternalAllocationType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int32)))

newtype VkPresentModeKHR Source #

Constructors

VkPresentModeKHR Int32 

Instances

Instances details
Bounded VkPresentModeKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.PresentModeKHR

Enum VkPresentModeKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.PresentModeKHR

Eq VkPresentModeKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.PresentModeKHR

Data VkPresentModeKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.PresentModeKHR

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 :: forall r r'. (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 # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.PresentModeKHR

Ord VkPresentModeKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.PresentModeKHR

Read VkPresentModeKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.PresentModeKHR

Show VkPresentModeKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.PresentModeKHR

Generic VkPresentModeKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.PresentModeKHR

Associated Types

type Rep VkPresentModeKHR :: Type -> Type #

Storable VkPresentModeKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.PresentModeKHR

type Rep VkPresentModeKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.PresentModeKHR

type Rep VkPresentModeKHR = D1 ('MetaData "VkPresentModeKHR" "Graphics.Vulkan.Types.Enum.PresentModeKHR" "vulkan-api-1.1.1.0-LBmI6dMSRRRGKEhmYXhCF0" 'True) (C1 ('MetaCons "VkPresentModeKHR" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int32)))

newtype VkResult Source #

API result codes

type = enum

VkResult registry at www.khronos.org

Constructors

VkResult Int32 

Instances

Instances details
Bounded VkResult Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Result

Enum VkResult Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Result

Eq VkResult Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Result

Data VkResult Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Result

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 :: forall r r'. (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 # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Result

Ord VkResult Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Result

Read VkResult Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Result

Show VkResult Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Result

Generic VkResult Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Result

Associated Types

type Rep VkResult :: Type -> Type #

Methods

from :: VkResult -> Rep VkResult x #

to :: Rep VkResult x -> VkResult #

Storable VkResult Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Result

type Rep VkResult Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Result

type Rep VkResult = D1 ('MetaData "VkResult" "Graphics.Vulkan.Types.Enum.Result" "vulkan-api-1.1.1.0-LBmI6dMSRRRGKEhmYXhCF0" 'True) (C1 ('MetaCons "VkResult" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe 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 VkSurfaceCounterBitmaskEXT (a :: FlagType) Source #

Instances

Instances details
Bounded (VkSurfaceCounterBitmaskEXT FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Surface

Enum (VkSurfaceCounterBitmaskEXT FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Surface

Eq (VkSurfaceCounterBitmaskEXT a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Surface

Integral (VkSurfaceCounterBitmaskEXT FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Surface

Typeable a => Data (VkSurfaceCounterBitmaskEXT a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Surface

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 :: forall r r'. (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 # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Surface

Ord (VkSurfaceCounterBitmaskEXT a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Surface

Read (VkSurfaceCounterBitmaskEXT a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Surface

Real (VkSurfaceCounterBitmaskEXT FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Surface

Show (VkSurfaceCounterBitmaskEXT a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Surface

Generic (VkSurfaceCounterBitmaskEXT a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Surface

Associated Types

type Rep (VkSurfaceCounterBitmaskEXT a) :: Type -> Type #

Storable (VkSurfaceCounterBitmaskEXT a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Surface

Bits (VkSurfaceCounterBitmaskEXT FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Surface

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 # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Surface

type Rep (VkSurfaceCounterBitmaskEXT a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Surface

type Rep (VkSurfaceCounterBitmaskEXT a) = D1 ('MetaData "VkSurfaceCounterBitmaskEXT" "Graphics.Vulkan.Types.Enum.Surface" "vulkan-api-1.1.1.0-LBmI6dMSRRRGKEhmYXhCF0" 'True) (C1 ('MetaCons "VkSurfaceCounterBitmaskEXT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VkFlags)))

newtype VkSurfaceTransformBitmaskKHR (a :: FlagType) Source #

Instances

Instances details
Bounded (VkSurfaceTransformBitmaskKHR FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Surface

Enum (VkSurfaceTransformBitmaskKHR FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Surface

Eq (VkSurfaceTransformBitmaskKHR a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Surface

Integral (VkSurfaceTransformBitmaskKHR FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Surface

Typeable a => Data (VkSurfaceTransformBitmaskKHR a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Surface

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 :: forall r r'. (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 # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Surface

Ord (VkSurfaceTransformBitmaskKHR a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Surface

Read (VkSurfaceTransformBitmaskKHR a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Surface

Real (VkSurfaceTransformBitmaskKHR FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Surface

Show (VkSurfaceTransformBitmaskKHR a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Surface

Generic (VkSurfaceTransformBitmaskKHR a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Surface

Associated Types

type Rep (VkSurfaceTransformBitmaskKHR a) :: Type -> Type #

Storable (VkSurfaceTransformBitmaskKHR a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Surface

Bits (VkSurfaceTransformBitmaskKHR FlagMask) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Surface

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 # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Surface

type Rep (VkSurfaceTransformBitmaskKHR a) Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.Surface

type Rep (VkSurfaceTransformBitmaskKHR a) = D1 ('MetaData "VkSurfaceTransformBitmaskKHR" "Graphics.Vulkan.Types.Enum.Surface" "vulkan-api-1.1.1.0-LBmI6dMSRRRGKEhmYXhCF0" 'True) (C1 ('MetaCons "VkSurfaceTransformBitmaskKHR" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VkFlags)))

newtype VkSystemAllocationScope Source #

Instances

Instances details
Bounded VkSystemAllocationScope Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.SystemAllocationScope

Enum VkSystemAllocationScope Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.SystemAllocationScope

Eq VkSystemAllocationScope Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.SystemAllocationScope

Data VkSystemAllocationScope Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.SystemAllocationScope

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 :: forall r r'. (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 # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.SystemAllocationScope

Ord VkSystemAllocationScope Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.SystemAllocationScope

Read VkSystemAllocationScope Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.SystemAllocationScope

Show VkSystemAllocationScope Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.SystemAllocationScope

Generic VkSystemAllocationScope Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.SystemAllocationScope

Associated Types

type Rep VkSystemAllocationScope :: Type -> Type #

Storable VkSystemAllocationScope Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.SystemAllocationScope

type Rep VkSystemAllocationScope Source # 
Instance details

Defined in Graphics.Vulkan.Types.Enum.SystemAllocationScope

type Rep VkSystemAllocationScope = D1 ('MetaData "VkSystemAllocationScope" "Graphics.Vulkan.Types.Enum.SystemAllocationScope" "vulkan-api-1.1.1.0-LBmI6dMSRRRGKEhmYXhCF0" 'True) (C1 ('MetaCons "VkSystemAllocationScope" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe 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

Instances details
Eq VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

Ord VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

Show VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

Storable VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

VulkanMarshalPrim VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

VulkanMarshal VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

CanWriteField "pUserData" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

CanWriteField "pfnAllocation" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

CanWriteField "pfnFree" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

CanWriteField "pfnInternalAllocation" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

Methods

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

CanWriteField "pfnInternalFree" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

CanWriteField "pfnReallocation" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

CanReadField "pUserData" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

CanReadField "pfnAllocation" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

CanReadField "pfnFree" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

CanReadField "pfnInternalAllocation" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

CanReadField "pfnInternalFree" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

CanReadField "pfnReallocation" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

HasField "pUserData" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

HasField "pfnAllocation" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

Associated Types

type FieldType "pfnAllocation" VkAllocationCallbacks Source #

type FieldOptional "pfnAllocation" VkAllocationCallbacks :: Bool Source #

type FieldOffset "pfnAllocation" VkAllocationCallbacks :: Nat Source #

type FieldIsArray "pfnAllocation" VkAllocationCallbacks :: Bool Source #

HasField "pfnFree" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

HasField "pfnInternalAllocation" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

Associated Types

type FieldType "pfnInternalAllocation" VkAllocationCallbacks Source #

type FieldOptional "pfnInternalAllocation" VkAllocationCallbacks :: Bool Source #

type FieldOffset "pfnInternalAllocation" VkAllocationCallbacks :: Nat Source #

type FieldIsArray "pfnInternalAllocation" VkAllocationCallbacks :: Bool Source #

HasField "pfnInternalFree" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

Associated Types

type FieldType "pfnInternalFree" VkAllocationCallbacks Source #

type FieldOptional "pfnInternalFree" VkAllocationCallbacks :: Bool Source #

type FieldOffset "pfnInternalFree" VkAllocationCallbacks :: Nat Source #

type FieldIsArray "pfnInternalFree" VkAllocationCallbacks :: Bool Source #

HasField "pfnReallocation" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

Associated Types

type FieldType "pfnReallocation" VkAllocationCallbacks Source #

type FieldOptional "pfnReallocation" VkAllocationCallbacks :: Bool Source #

type FieldOffset "pfnReallocation" VkAllocationCallbacks :: Nat Source #

type FieldIsArray "pfnReallocation" VkAllocationCallbacks :: Bool Source #

type StructFields VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

type StructFields VkAllocationCallbacks = '["pUserData", "pfnAllocation", "pfnReallocation", "pfnFree", "pfnInternalAllocation", "pfnInternalFree"]
type CUnionType VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

type ReturnedOnly VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

type StructExtends VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

type FieldType "pUserData" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

type FieldType "pfnAllocation" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

type FieldType "pfnFree" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

type FieldType "pfnInternalAllocation" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

type FieldType "pfnInternalFree" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

type FieldType "pfnReallocation" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

type FieldOptional "pUserData" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

type FieldOptional "pfnAllocation" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

type FieldOptional "pfnAllocation" VkAllocationCallbacks = 'False
type FieldOptional "pfnFree" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

type FieldOptional "pfnInternalAllocation" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

type FieldOptional "pfnInternalAllocation" VkAllocationCallbacks = 'True
type FieldOptional "pfnInternalFree" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

type FieldOptional "pfnInternalFree" VkAllocationCallbacks = 'True
type FieldOptional "pfnReallocation" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

type FieldOptional "pfnReallocation" VkAllocationCallbacks = 'False
type FieldOffset "pUserData" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

type FieldOffset "pUserData" VkAllocationCallbacks = 0
type FieldOffset "pfnAllocation" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

type FieldOffset "pfnAllocation" VkAllocationCallbacks = 8
type FieldOffset "pfnFree" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

type FieldOffset "pfnInternalAllocation" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

type FieldOffset "pfnInternalAllocation" VkAllocationCallbacks = 32
type FieldOffset "pfnInternalFree" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

type FieldOffset "pfnInternalFree" VkAllocationCallbacks = 40
type FieldOffset "pfnReallocation" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

type FieldOffset "pfnReallocation" VkAllocationCallbacks = 16
type FieldIsArray "pUserData" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

type FieldIsArray "pfnAllocation" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

type FieldIsArray "pfnAllocation" VkAllocationCallbacks = 'False
type FieldIsArray "pfnFree" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

type FieldIsArray "pfnInternalAllocation" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

type FieldIsArray "pfnInternalAllocation" VkAllocationCallbacks = 'False
type FieldIsArray "pfnInternalFree" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

type FieldIsArray "pfnInternalFree" VkAllocationCallbacks = 'False
type FieldIsArray "pfnReallocation" VkAllocationCallbacks Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.AllocationCallbacks

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

Instances details
Eq VkExtent2D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

Ord VkExtent2D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

Show VkExtent2D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

Storable VkExtent2D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

VulkanMarshalPrim VkExtent2D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

VulkanMarshal VkExtent2D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

CanWriteField "height" VkExtent2D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

Methods

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

CanWriteField "width" VkExtent2D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

Methods

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

CanReadField "height" VkExtent2D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

CanReadField "width" VkExtent2D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

HasField "height" VkExtent2D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

Associated Types

type FieldType "height" VkExtent2D Source #

type FieldOptional "height" VkExtent2D :: Bool Source #

type FieldOffset "height" VkExtent2D :: Nat Source #

type FieldIsArray "height" VkExtent2D :: Bool Source #

HasField "width" VkExtent2D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

Associated Types

type FieldType "width" VkExtent2D Source #

type FieldOptional "width" VkExtent2D :: Bool Source #

type FieldOffset "width" VkExtent2D :: Nat Source #

type FieldIsArray "width" VkExtent2D :: Bool Source #

type StructFields VkExtent2D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

type StructFields VkExtent2D = '["width", "height"]
type CUnionType VkExtent2D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

type ReturnedOnly VkExtent2D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

type StructExtends VkExtent2D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

type StructExtends VkExtent2D = '[] :: [Type]
type FieldType "height" VkExtent2D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

type FieldType "height" VkExtent2D = Word32
type FieldType "width" VkExtent2D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

type FieldType "width" VkExtent2D = Word32
type FieldOptional "height" VkExtent2D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

type FieldOptional "height" VkExtent2D = 'False
type FieldOptional "width" VkExtent2D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

type FieldOffset "height" VkExtent2D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

type FieldOffset "height" VkExtent2D = 4
type FieldOffset "width" VkExtent2D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

type FieldOffset "width" VkExtent2D = 0
type FieldIsArray "height" VkExtent2D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

type FieldIsArray "height" VkExtent2D = 'False
type FieldIsArray "width" VkExtent2D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

type FieldIsArray "width" VkExtent2D = 'False

data VkExtent3D Source #

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

VkExtent3D registry at www.khronos.org

Instances

Instances details
Eq VkExtent3D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

Ord VkExtent3D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

Show VkExtent3D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

Storable VkExtent3D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

VulkanMarshalPrim VkExtent3D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

VulkanMarshal VkExtent3D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

CanWriteField "depth" VkExtent3D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

Methods

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

CanWriteField "height" VkExtent3D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

Methods

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

CanWriteField "width" VkExtent3D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

Methods

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

CanReadField "depth" VkExtent3D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

CanReadField "height" VkExtent3D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

CanReadField "width" VkExtent3D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

HasField "depth" VkExtent3D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

Associated Types

type FieldType "depth" VkExtent3D Source #

type FieldOptional "depth" VkExtent3D :: Bool Source #

type FieldOffset "depth" VkExtent3D :: Nat Source #

type FieldIsArray "depth" VkExtent3D :: Bool Source #

HasField "height" VkExtent3D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

Associated Types

type FieldType "height" VkExtent3D Source #

type FieldOptional "height" VkExtent3D :: Bool Source #

type FieldOffset "height" VkExtent3D :: Nat Source #

type FieldIsArray "height" VkExtent3D :: Bool Source #

HasField "width" VkExtent3D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

Associated Types

type FieldType "width" VkExtent3D Source #

type FieldOptional "width" VkExtent3D :: Bool Source #

type FieldOffset "width" VkExtent3D :: Nat Source #

type FieldIsArray "width" VkExtent3D :: Bool Source #

type StructFields VkExtent3D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

type StructFields VkExtent3D = '["width", "height", "depth"]
type CUnionType VkExtent3D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

type ReturnedOnly VkExtent3D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

type StructExtends VkExtent3D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

type StructExtends VkExtent3D = '[] :: [Type]
type FieldType "depth" VkExtent3D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

type FieldType "depth" VkExtent3D = Word32
type FieldType "height" VkExtent3D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

type FieldType "height" VkExtent3D = Word32
type FieldType "width" VkExtent3D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

type FieldType "width" VkExtent3D = Word32
type FieldOptional "depth" VkExtent3D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

type FieldOptional "height" VkExtent3D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

type FieldOptional "height" VkExtent3D = 'False
type FieldOptional "width" VkExtent3D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

type FieldOffset "depth" VkExtent3D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

type FieldOffset "depth" VkExtent3D = 8
type FieldOffset "height" VkExtent3D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

type FieldOffset "height" VkExtent3D = 4
type FieldOffset "width" VkExtent3D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

type FieldOffset "width" VkExtent3D = 0
type FieldIsArray "depth" VkExtent3D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

type FieldIsArray "depth" VkExtent3D = 'False
type FieldIsArray "height" VkExtent3D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

type FieldIsArray "height" VkExtent3D = 'False
type FieldIsArray "width" VkExtent3D Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Extent

type FieldIsArray "width" VkExtent3D = 'False

data VkSurfaceCapabilities2EXT Source #

typedef struct VkSurfaceCapabilities2EXT {
    VkStructureType sType;
    void*                            pNext;
    uint32_t                         minImageCount;
    uint32_t                         maxImageCount;
    VkExtent2D                       currentExtent;
    VkExtent2D                       minImageExtent;
    VkExtent2D                       maxImageExtent;
    uint32_t                         maxImageArrayLayers;
    VkSurfaceTransformFlagsKHR       supportedTransforms;
    VkSurfaceTransformFlagBitsKHR    currentTransform;
    VkCompositeAlphaFlagsKHR         supportedCompositeAlpha;
    VkImageUsageFlags                supportedUsageFlags;
    VkSurfaceCounterFlagsEXT supportedSurfaceCounters;
} VkSurfaceCapabilities2EXT;

VkSurfaceCapabilities2EXT registry at www.khronos.org

Instances

Instances details
Eq VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

Ord VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

Show VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

Storable VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

VulkanMarshalPrim VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

VulkanMarshal VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanWriteField "currentExtent" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanWriteField "currentTransform" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanWriteField "maxImageArrayLayers" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanWriteField "maxImageCount" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanWriteField "maxImageExtent" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanWriteField "minImageCount" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanWriteField "minImageExtent" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanWriteField "pNext" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanWriteField "sType" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanWriteField "supportedCompositeAlpha" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanWriteField "supportedSurfaceCounters" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanWriteField "supportedTransforms" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanWriteField "supportedUsageFlags" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanReadField "currentExtent" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanReadField "currentTransform" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanReadField "maxImageArrayLayers" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanReadField "maxImageCount" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanReadField "maxImageExtent" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanReadField "minImageCount" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanReadField "minImageExtent" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanReadField "pNext" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanReadField "sType" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanReadField "supportedCompositeAlpha" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanReadField "supportedSurfaceCounters" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanReadField "supportedTransforms" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanReadField "supportedUsageFlags" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

HasField "currentExtent" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

Associated Types

type FieldType "currentExtent" VkSurfaceCapabilities2EXT Source #

type FieldOptional "currentExtent" VkSurfaceCapabilities2EXT :: Bool Source #

type FieldOffset "currentExtent" VkSurfaceCapabilities2EXT :: Nat Source #

type FieldIsArray "currentExtent" VkSurfaceCapabilities2EXT :: Bool Source #

HasField "currentTransform" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

Associated Types

type FieldType "currentTransform" VkSurfaceCapabilities2EXT Source #

type FieldOptional "currentTransform" VkSurfaceCapabilities2EXT :: Bool Source #

type FieldOffset "currentTransform" VkSurfaceCapabilities2EXT :: Nat Source #

type FieldIsArray "currentTransform" VkSurfaceCapabilities2EXT :: Bool Source #

HasField "maxImageArrayLayers" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

Associated Types

type FieldType "maxImageArrayLayers" VkSurfaceCapabilities2EXT Source #

type FieldOptional "maxImageArrayLayers" VkSurfaceCapabilities2EXT :: Bool Source #

type FieldOffset "maxImageArrayLayers" VkSurfaceCapabilities2EXT :: Nat Source #

type FieldIsArray "maxImageArrayLayers" VkSurfaceCapabilities2EXT :: Bool Source #

HasField "maxImageCount" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

Associated Types

type FieldType "maxImageCount" VkSurfaceCapabilities2EXT Source #

type FieldOptional "maxImageCount" VkSurfaceCapabilities2EXT :: Bool Source #

type FieldOffset "maxImageCount" VkSurfaceCapabilities2EXT :: Nat Source #

type FieldIsArray "maxImageCount" VkSurfaceCapabilities2EXT :: Bool Source #

HasField "maxImageExtent" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

Associated Types

type FieldType "maxImageExtent" VkSurfaceCapabilities2EXT Source #

type FieldOptional "maxImageExtent" VkSurfaceCapabilities2EXT :: Bool Source #

type FieldOffset "maxImageExtent" VkSurfaceCapabilities2EXT :: Nat Source #

type FieldIsArray "maxImageExtent" VkSurfaceCapabilities2EXT :: Bool Source #

HasField "minImageCount" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

Associated Types

type FieldType "minImageCount" VkSurfaceCapabilities2EXT Source #

type FieldOptional "minImageCount" VkSurfaceCapabilities2EXT :: Bool Source #

type FieldOffset "minImageCount" VkSurfaceCapabilities2EXT :: Nat Source #

type FieldIsArray "minImageCount" VkSurfaceCapabilities2EXT :: Bool Source #

HasField "minImageExtent" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

Associated Types

type FieldType "minImageExtent" VkSurfaceCapabilities2EXT Source #

type FieldOptional "minImageExtent" VkSurfaceCapabilities2EXT :: Bool Source #

type FieldOffset "minImageExtent" VkSurfaceCapabilities2EXT :: Nat Source #

type FieldIsArray "minImageExtent" VkSurfaceCapabilities2EXT :: Bool Source #

HasField "pNext" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

HasField "sType" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

HasField "supportedCompositeAlpha" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

Associated Types

type FieldType "supportedCompositeAlpha" VkSurfaceCapabilities2EXT Source #

type FieldOptional "supportedCompositeAlpha" VkSurfaceCapabilities2EXT :: Bool Source #

type FieldOffset "supportedCompositeAlpha" VkSurfaceCapabilities2EXT :: Nat Source #

type FieldIsArray "supportedCompositeAlpha" VkSurfaceCapabilities2EXT :: Bool Source #

HasField "supportedSurfaceCounters" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

Associated Types

type FieldType "supportedSurfaceCounters" VkSurfaceCapabilities2EXT Source #

type FieldOptional "supportedSurfaceCounters" VkSurfaceCapabilities2EXT :: Bool Source #

type FieldOffset "supportedSurfaceCounters" VkSurfaceCapabilities2EXT :: Nat Source #

type FieldIsArray "supportedSurfaceCounters" VkSurfaceCapabilities2EXT :: Bool Source #

HasField "supportedTransforms" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

Associated Types

type FieldType "supportedTransforms" VkSurfaceCapabilities2EXT Source #

type FieldOptional "supportedTransforms" VkSurfaceCapabilities2EXT :: Bool Source #

type FieldOffset "supportedTransforms" VkSurfaceCapabilities2EXT :: Nat Source #

type FieldIsArray "supportedTransforms" VkSurfaceCapabilities2EXT :: Bool Source #

HasField "supportedUsageFlags" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

Associated Types

type FieldType "supportedUsageFlags" VkSurfaceCapabilities2EXT Source #

type FieldOptional "supportedUsageFlags" VkSurfaceCapabilities2EXT :: Bool Source #

type FieldOffset "supportedUsageFlags" VkSurfaceCapabilities2EXT :: Nat Source #

type FieldIsArray "supportedUsageFlags" VkSurfaceCapabilities2EXT :: Bool Source #

type StructFields VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type StructFields VkSurfaceCapabilities2EXT = '["sType", "pNext", "minImageCount", "maxImageCount", "currentExtent", "minImageExtent", "maxImageExtent", "maxImageArrayLayers", "supportedTransforms", "currentTransform", "supportedCompositeAlpha", "supportedUsageFlags", "supportedSurfaceCounters"]
type CUnionType VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type ReturnedOnly VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type StructExtends VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldType "currentExtent" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldType "currentTransform" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldType "maxImageArrayLayers" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldType "maxImageArrayLayers" VkSurfaceCapabilities2EXT = Word32
type FieldType "maxImageCount" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldType "maxImageExtent" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldType "minImageCount" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldType "minImageExtent" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldType "pNext" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldType "sType" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldType "supportedCompositeAlpha" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldType "supportedSurfaceCounters" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldType "supportedTransforms" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldType "supportedUsageFlags" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOptional "currentExtent" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOptional "currentTransform" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOptional "currentTransform" VkSurfaceCapabilities2EXT = 'False
type FieldOptional "maxImageArrayLayers" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOptional "maxImageArrayLayers" VkSurfaceCapabilities2EXT = 'False
type FieldOptional "maxImageCount" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOptional "maxImageExtent" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOptional "minImageCount" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOptional "minImageExtent" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOptional "pNext" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOptional "sType" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOptional "supportedCompositeAlpha" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOptional "supportedCompositeAlpha" VkSurfaceCapabilities2EXT = 'True
type FieldOptional "supportedSurfaceCounters" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOptional "supportedSurfaceCounters" VkSurfaceCapabilities2EXT = 'True
type FieldOptional "supportedTransforms" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOptional "supportedTransforms" VkSurfaceCapabilities2EXT = 'True
type FieldOptional "supportedUsageFlags" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOptional "supportedUsageFlags" VkSurfaceCapabilities2EXT = 'True
type FieldOffset "currentExtent" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOffset "currentExtent" VkSurfaceCapabilities2EXT = 24
type FieldOffset "currentTransform" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOffset "currentTransform" VkSurfaceCapabilities2EXT = 56
type FieldOffset "maxImageArrayLayers" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOffset "maxImageArrayLayers" VkSurfaceCapabilities2EXT = 48
type FieldOffset "maxImageCount" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOffset "maxImageCount" VkSurfaceCapabilities2EXT = 20
type FieldOffset "maxImageExtent" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOffset "maxImageExtent" VkSurfaceCapabilities2EXT = 40
type FieldOffset "minImageCount" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOffset "minImageCount" VkSurfaceCapabilities2EXT = 16
type FieldOffset "minImageExtent" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOffset "minImageExtent" VkSurfaceCapabilities2EXT = 32
type FieldOffset "pNext" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOffset "sType" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOffset "supportedCompositeAlpha" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOffset "supportedCompositeAlpha" VkSurfaceCapabilities2EXT = 60
type FieldOffset "supportedSurfaceCounters" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOffset "supportedSurfaceCounters" VkSurfaceCapabilities2EXT = 68
type FieldOffset "supportedTransforms" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOffset "supportedTransforms" VkSurfaceCapabilities2EXT = 52
type FieldOffset "supportedUsageFlags" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOffset "supportedUsageFlags" VkSurfaceCapabilities2EXT = 64
type FieldIsArray "currentExtent" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldIsArray "currentTransform" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldIsArray "currentTransform" VkSurfaceCapabilities2EXT = 'False
type FieldIsArray "maxImageArrayLayers" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldIsArray "maxImageArrayLayers" VkSurfaceCapabilities2EXT = 'False
type FieldIsArray "maxImageCount" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldIsArray "maxImageExtent" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldIsArray "minImageCount" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldIsArray "minImageExtent" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldIsArray "pNext" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldIsArray "sType" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldIsArray "supportedCompositeAlpha" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldIsArray "supportedCompositeAlpha" VkSurfaceCapabilities2EXT = 'False
type FieldIsArray "supportedSurfaceCounters" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldIsArray "supportedSurfaceCounters" VkSurfaceCapabilities2EXT = 'False
type FieldIsArray "supportedTransforms" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldIsArray "supportedTransforms" VkSurfaceCapabilities2EXT = 'False
type FieldIsArray "supportedUsageFlags" VkSurfaceCapabilities2EXT Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldIsArray "supportedUsageFlags" VkSurfaceCapabilities2EXT = 'False

data VkSurfaceCapabilities2KHR Source #

typedef struct VkSurfaceCapabilities2KHR {
    VkStructureType sType;
    void*   pNext;
    VkSurfaceCapabilitiesKHR surfaceCapabilities;
} VkSurfaceCapabilities2KHR;

VkSurfaceCapabilities2KHR registry at www.khronos.org

Instances

Instances details
Eq VkSurfaceCapabilities2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

Ord VkSurfaceCapabilities2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

Show VkSurfaceCapabilities2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

Storable VkSurfaceCapabilities2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

VulkanMarshalPrim VkSurfaceCapabilities2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

VulkanMarshal VkSurfaceCapabilities2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanWriteField "pNext" VkSurfaceCapabilities2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanWriteField "sType" VkSurfaceCapabilities2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanWriteField "surfaceCapabilities" VkSurfaceCapabilities2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanReadField "pNext" VkSurfaceCapabilities2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanReadField "sType" VkSurfaceCapabilities2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanReadField "surfaceCapabilities" VkSurfaceCapabilities2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

HasField "pNext" VkSurfaceCapabilities2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

HasField "sType" VkSurfaceCapabilities2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

HasField "surfaceCapabilities" VkSurfaceCapabilities2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

Associated Types

type FieldType "surfaceCapabilities" VkSurfaceCapabilities2KHR Source #

type FieldOptional "surfaceCapabilities" VkSurfaceCapabilities2KHR :: Bool Source #

type FieldOffset "surfaceCapabilities" VkSurfaceCapabilities2KHR :: Nat Source #

type FieldIsArray "surfaceCapabilities" VkSurfaceCapabilities2KHR :: Bool Source #

type StructFields VkSurfaceCapabilities2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type StructFields VkSurfaceCapabilities2KHR = '["sType", "pNext", "surfaceCapabilities"]
type CUnionType VkSurfaceCapabilities2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type ReturnedOnly VkSurfaceCapabilities2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type StructExtends VkSurfaceCapabilities2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldType "pNext" VkSurfaceCapabilities2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldType "sType" VkSurfaceCapabilities2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldType "surfaceCapabilities" VkSurfaceCapabilities2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOptional "pNext" VkSurfaceCapabilities2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOptional "sType" VkSurfaceCapabilities2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOptional "surfaceCapabilities" VkSurfaceCapabilities2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOptional "surfaceCapabilities" VkSurfaceCapabilities2KHR = 'False
type FieldOffset "pNext" VkSurfaceCapabilities2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOffset "sType" VkSurfaceCapabilities2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOffset "surfaceCapabilities" VkSurfaceCapabilities2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOffset "surfaceCapabilities" VkSurfaceCapabilities2KHR = 16
type FieldIsArray "pNext" VkSurfaceCapabilities2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldIsArray "sType" VkSurfaceCapabilities2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldIsArray "surfaceCapabilities" VkSurfaceCapabilities2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldIsArray "surfaceCapabilities" VkSurfaceCapabilities2KHR = 'False

data VkSurfaceCapabilitiesKHR Source #

typedef struct VkSurfaceCapabilitiesKHR {
    uint32_t                         minImageCount;
    uint32_t                         maxImageCount;
    VkExtent2D                       currentExtent;
    VkExtent2D                       minImageExtent;
    VkExtent2D                       maxImageExtent;
    uint32_t                         maxImageArrayLayers;
    VkSurfaceTransformFlagsKHR       supportedTransforms;
    VkSurfaceTransformFlagBitsKHR    currentTransform;
    VkCompositeAlphaFlagsKHR         supportedCompositeAlpha;
    VkImageUsageFlags                supportedUsageFlags;
} VkSurfaceCapabilitiesKHR;

VkSurfaceCapabilitiesKHR registry at www.khronos.org

Instances

Instances details
Eq VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

Ord VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

Show VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

Storable VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

VulkanMarshalPrim VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

VulkanMarshal VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanWriteField "currentExtent" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanWriteField "currentTransform" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanWriteField "maxImageArrayLayers" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanWriteField "maxImageCount" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanWriteField "maxImageExtent" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanWriteField "minImageCount" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanWriteField "minImageExtent" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanWriteField "supportedCompositeAlpha" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanWriteField "supportedTransforms" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanWriteField "supportedUsageFlags" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanReadField "currentExtent" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanReadField "currentTransform" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanReadField "maxImageArrayLayers" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanReadField "maxImageCount" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanReadField "maxImageExtent" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanReadField "minImageCount" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanReadField "minImageExtent" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanReadField "supportedCompositeAlpha" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanReadField "supportedTransforms" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanReadField "supportedUsageFlags" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

HasField "currentExtent" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

Associated Types

type FieldType "currentExtent" VkSurfaceCapabilitiesKHR Source #

type FieldOptional "currentExtent" VkSurfaceCapabilitiesKHR :: Bool Source #

type FieldOffset "currentExtent" VkSurfaceCapabilitiesKHR :: Nat Source #

type FieldIsArray "currentExtent" VkSurfaceCapabilitiesKHR :: Bool Source #

HasField "currentTransform" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

Associated Types

type FieldType "currentTransform" VkSurfaceCapabilitiesKHR Source #

type FieldOptional "currentTransform" VkSurfaceCapabilitiesKHR :: Bool Source #

type FieldOffset "currentTransform" VkSurfaceCapabilitiesKHR :: Nat Source #

type FieldIsArray "currentTransform" VkSurfaceCapabilitiesKHR :: Bool Source #

HasField "maxImageArrayLayers" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

Associated Types

type FieldType "maxImageArrayLayers" VkSurfaceCapabilitiesKHR Source #

type FieldOptional "maxImageArrayLayers" VkSurfaceCapabilitiesKHR :: Bool Source #

type FieldOffset "maxImageArrayLayers" VkSurfaceCapabilitiesKHR :: Nat Source #

type FieldIsArray "maxImageArrayLayers" VkSurfaceCapabilitiesKHR :: Bool Source #

HasField "maxImageCount" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

Associated Types

type FieldType "maxImageCount" VkSurfaceCapabilitiesKHR Source #

type FieldOptional "maxImageCount" VkSurfaceCapabilitiesKHR :: Bool Source #

type FieldOffset "maxImageCount" VkSurfaceCapabilitiesKHR :: Nat Source #

type FieldIsArray "maxImageCount" VkSurfaceCapabilitiesKHR :: Bool Source #

HasField "maxImageExtent" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

Associated Types

type FieldType "maxImageExtent" VkSurfaceCapabilitiesKHR Source #

type FieldOptional "maxImageExtent" VkSurfaceCapabilitiesKHR :: Bool Source #

type FieldOffset "maxImageExtent" VkSurfaceCapabilitiesKHR :: Nat Source #

type FieldIsArray "maxImageExtent" VkSurfaceCapabilitiesKHR :: Bool Source #

HasField "minImageCount" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

Associated Types

type FieldType "minImageCount" VkSurfaceCapabilitiesKHR Source #

type FieldOptional "minImageCount" VkSurfaceCapabilitiesKHR :: Bool Source #

type FieldOffset "minImageCount" VkSurfaceCapabilitiesKHR :: Nat Source #

type FieldIsArray "minImageCount" VkSurfaceCapabilitiesKHR :: Bool Source #

HasField "minImageExtent" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

Associated Types

type FieldType "minImageExtent" VkSurfaceCapabilitiesKHR Source #

type FieldOptional "minImageExtent" VkSurfaceCapabilitiesKHR :: Bool Source #

type FieldOffset "minImageExtent" VkSurfaceCapabilitiesKHR :: Nat Source #

type FieldIsArray "minImageExtent" VkSurfaceCapabilitiesKHR :: Bool Source #

HasField "supportedCompositeAlpha" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

Associated Types

type FieldType "supportedCompositeAlpha" VkSurfaceCapabilitiesKHR Source #

type FieldOptional "supportedCompositeAlpha" VkSurfaceCapabilitiesKHR :: Bool Source #

type FieldOffset "supportedCompositeAlpha" VkSurfaceCapabilitiesKHR :: Nat Source #

type FieldIsArray "supportedCompositeAlpha" VkSurfaceCapabilitiesKHR :: Bool Source #

HasField "supportedTransforms" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

Associated Types

type FieldType "supportedTransforms" VkSurfaceCapabilitiesKHR Source #

type FieldOptional "supportedTransforms" VkSurfaceCapabilitiesKHR :: Bool Source #

type FieldOffset "supportedTransforms" VkSurfaceCapabilitiesKHR :: Nat Source #

type FieldIsArray "supportedTransforms" VkSurfaceCapabilitiesKHR :: Bool Source #

HasField "supportedUsageFlags" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

Associated Types

type FieldType "supportedUsageFlags" VkSurfaceCapabilitiesKHR Source #

type FieldOptional "supportedUsageFlags" VkSurfaceCapabilitiesKHR :: Bool Source #

type FieldOffset "supportedUsageFlags" VkSurfaceCapabilitiesKHR :: Nat Source #

type FieldIsArray "supportedUsageFlags" VkSurfaceCapabilitiesKHR :: Bool Source #

type StructFields VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type StructFields VkSurfaceCapabilitiesKHR = '["minImageCount", "maxImageCount", "currentExtent", "minImageExtent", "maxImageExtent", "maxImageArrayLayers", "supportedTransforms", "currentTransform", "supportedCompositeAlpha", "supportedUsageFlags"]
type CUnionType VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type ReturnedOnly VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type StructExtends VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldType "currentExtent" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldType "currentTransform" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldType "maxImageArrayLayers" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldType "maxImageArrayLayers" VkSurfaceCapabilitiesKHR = Word32
type FieldType "maxImageCount" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldType "maxImageExtent" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldType "minImageCount" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldType "minImageExtent" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldType "supportedCompositeAlpha" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldType "supportedTransforms" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldType "supportedUsageFlags" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOptional "currentExtent" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOptional "currentTransform" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOptional "currentTransform" VkSurfaceCapabilitiesKHR = 'False
type FieldOptional "maxImageArrayLayers" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOptional "maxImageArrayLayers" VkSurfaceCapabilitiesKHR = 'False
type FieldOptional "maxImageCount" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOptional "maxImageExtent" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOptional "minImageCount" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOptional "minImageExtent" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOptional "supportedCompositeAlpha" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOptional "supportedCompositeAlpha" VkSurfaceCapabilitiesKHR = 'True
type FieldOptional "supportedTransforms" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOptional "supportedTransforms" VkSurfaceCapabilitiesKHR = 'True
type FieldOptional "supportedUsageFlags" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOptional "supportedUsageFlags" VkSurfaceCapabilitiesKHR = 'True
type FieldOffset "currentExtent" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOffset "currentExtent" VkSurfaceCapabilitiesKHR = 8
type FieldOffset "currentTransform" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOffset "currentTransform" VkSurfaceCapabilitiesKHR = 40
type FieldOffset "maxImageArrayLayers" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOffset "maxImageArrayLayers" VkSurfaceCapabilitiesKHR = 32
type FieldOffset "maxImageCount" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOffset "maxImageCount" VkSurfaceCapabilitiesKHR = 4
type FieldOffset "maxImageExtent" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOffset "maxImageExtent" VkSurfaceCapabilitiesKHR = 24
type FieldOffset "minImageCount" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOffset "minImageCount" VkSurfaceCapabilitiesKHR = 0
type FieldOffset "minImageExtent" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOffset "minImageExtent" VkSurfaceCapabilitiesKHR = 16
type FieldOffset "supportedCompositeAlpha" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOffset "supportedCompositeAlpha" VkSurfaceCapabilitiesKHR = 44
type FieldOffset "supportedTransforms" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOffset "supportedTransforms" VkSurfaceCapabilitiesKHR = 36
type FieldOffset "supportedUsageFlags" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOffset "supportedUsageFlags" VkSurfaceCapabilitiesKHR = 48
type FieldIsArray "currentExtent" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldIsArray "currentTransform" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldIsArray "currentTransform" VkSurfaceCapabilitiesKHR = 'False
type FieldIsArray "maxImageArrayLayers" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldIsArray "maxImageArrayLayers" VkSurfaceCapabilitiesKHR = 'False
type FieldIsArray "maxImageCount" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldIsArray "maxImageExtent" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldIsArray "minImageCount" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldIsArray "minImageExtent" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldIsArray "supportedCompositeAlpha" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldIsArray "supportedCompositeAlpha" VkSurfaceCapabilitiesKHR = 'False
type FieldIsArray "supportedTransforms" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldIsArray "supportedTransforms" VkSurfaceCapabilitiesKHR = 'False
type FieldIsArray "supportedUsageFlags" VkSurfaceCapabilitiesKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldIsArray "supportedUsageFlags" VkSurfaceCapabilitiesKHR = 'False

data VkSurfaceFormat2KHR Source #

typedef struct VkSurfaceFormat2KHR {
    VkStructureType sType;
    void* pNext;
    VkSurfaceFormatKHR surfaceFormat;
} VkSurfaceFormat2KHR;

VkSurfaceFormat2KHR registry at www.khronos.org

Instances

Instances details
Eq VkSurfaceFormat2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

Ord VkSurfaceFormat2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

Show VkSurfaceFormat2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

Storable VkSurfaceFormat2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

VulkanMarshalPrim VkSurfaceFormat2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

VulkanMarshal VkSurfaceFormat2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanWriteField "pNext" VkSurfaceFormat2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanWriteField "sType" VkSurfaceFormat2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanWriteField "surfaceFormat" VkSurfaceFormat2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanReadField "pNext" VkSurfaceFormat2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanReadField "sType" VkSurfaceFormat2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanReadField "surfaceFormat" VkSurfaceFormat2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

HasField "pNext" VkSurfaceFormat2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

HasField "sType" VkSurfaceFormat2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

HasField "surfaceFormat" VkSurfaceFormat2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

Associated Types

type FieldType "surfaceFormat" VkSurfaceFormat2KHR Source #

type FieldOptional "surfaceFormat" VkSurfaceFormat2KHR :: Bool Source #

type FieldOffset "surfaceFormat" VkSurfaceFormat2KHR :: Nat Source #

type FieldIsArray "surfaceFormat" VkSurfaceFormat2KHR :: Bool Source #

type StructFields VkSurfaceFormat2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type StructFields VkSurfaceFormat2KHR = '["sType", "pNext", "surfaceFormat"]
type CUnionType VkSurfaceFormat2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type ReturnedOnly VkSurfaceFormat2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type StructExtends VkSurfaceFormat2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldType "pNext" VkSurfaceFormat2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldType "sType" VkSurfaceFormat2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldType "surfaceFormat" VkSurfaceFormat2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOptional "pNext" VkSurfaceFormat2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOptional "sType" VkSurfaceFormat2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOptional "surfaceFormat" VkSurfaceFormat2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOptional "surfaceFormat" VkSurfaceFormat2KHR = 'False
type FieldOffset "pNext" VkSurfaceFormat2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOffset "sType" VkSurfaceFormat2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOffset "surfaceFormat" VkSurfaceFormat2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOffset "surfaceFormat" VkSurfaceFormat2KHR = 16
type FieldIsArray "pNext" VkSurfaceFormat2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldIsArray "sType" VkSurfaceFormat2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldIsArray "surfaceFormat" VkSurfaceFormat2KHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldIsArray "surfaceFormat" VkSurfaceFormat2KHR = 'False

data VkSurfaceFormatKHR Source #

typedef struct VkSurfaceFormatKHR {
    VkFormat                         format;
    VkColorSpaceKHR                  colorSpace;
} VkSurfaceFormatKHR;

VkSurfaceFormatKHR registry at www.khronos.org

Instances

Instances details
Eq VkSurfaceFormatKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

Ord VkSurfaceFormatKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

Show VkSurfaceFormatKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

Storable VkSurfaceFormatKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

VulkanMarshalPrim VkSurfaceFormatKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

VulkanMarshal VkSurfaceFormatKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanWriteField "colorSpace" VkSurfaceFormatKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanWriteField "format" VkSurfaceFormatKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanReadField "colorSpace" VkSurfaceFormatKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

CanReadField "format" VkSurfaceFormatKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

HasField "colorSpace" VkSurfaceFormatKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

Associated Types

type FieldType "colorSpace" VkSurfaceFormatKHR Source #

type FieldOptional "colorSpace" VkSurfaceFormatKHR :: Bool Source #

type FieldOffset "colorSpace" VkSurfaceFormatKHR :: Nat Source #

type FieldIsArray "colorSpace" VkSurfaceFormatKHR :: Bool Source #

HasField "format" VkSurfaceFormatKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type StructFields VkSurfaceFormatKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type StructFields VkSurfaceFormatKHR = '["format", "colorSpace"]
type CUnionType VkSurfaceFormatKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type ReturnedOnly VkSurfaceFormatKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type StructExtends VkSurfaceFormatKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldType "colorSpace" VkSurfaceFormatKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldType "format" VkSurfaceFormatKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOptional "colorSpace" VkSurfaceFormatKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOptional "format" VkSurfaceFormatKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOffset "colorSpace" VkSurfaceFormatKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldOffset "colorSpace" VkSurfaceFormatKHR = 4
type FieldOffset "format" VkSurfaceFormatKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldIsArray "colorSpace" VkSurfaceFormatKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

type FieldIsArray "format" VkSurfaceFormatKHR Source # 
Instance details

Defined in Graphics.Vulkan.Types.Struct.Surface

pattern VK_KHR_SURFACE_SPEC_VERSION :: (Num a, Eq a) => a Source #

type VK_KHR_SURFACE_EXTENSION_NAME = "VK_KHR_surface" Source #

Orphan instances

VulkanProc "vkDestroySurfaceKHR" Source # 
Instance details

Associated Types

type VkProcType "vkDestroySurfaceKHR" Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtr :: FunPtr (VkProcType "vkDestroySurfaceKHR") -> VkProcType "vkDestroySurfaceKHR" Source #

VulkanProc "vkGetPhysicalDeviceSurfaceCapabilitiesKHR" Source # 
Instance details

Associated Types

type VkProcType "vkGetPhysicalDeviceSurfaceCapabilitiesKHR" Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtr :: FunPtr (VkProcType "vkGetPhysicalDeviceSurfaceCapabilitiesKHR") -> VkProcType "vkGetPhysicalDeviceSurfaceCapabilitiesKHR" Source #

VulkanProc "vkGetPhysicalDeviceSurfaceFormatsKHR" Source # 
Instance details

Associated Types

type VkProcType "vkGetPhysicalDeviceSurfaceFormatsKHR" Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtr :: FunPtr (VkProcType "vkGetPhysicalDeviceSurfaceFormatsKHR") -> VkProcType "vkGetPhysicalDeviceSurfaceFormatsKHR" Source #

VulkanProc "vkGetPhysicalDeviceSurfacePresentModesKHR" Source # 
Instance details

Associated Types

type VkProcType "vkGetPhysicalDeviceSurfacePresentModesKHR" Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtr :: FunPtr (VkProcType "vkGetPhysicalDeviceSurfacePresentModesKHR") -> VkProcType "vkGetPhysicalDeviceSurfacePresentModesKHR" Source #

VulkanProc "vkGetPhysicalDeviceSurfaceSupportKHR" Source # 
Instance details

Associated Types

type VkProcType "vkGetPhysicalDeviceSurfaceSupportKHR" Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtr :: FunPtr (VkProcType "vkGetPhysicalDeviceSurfaceSupportKHR") -> VkProcType "vkGetPhysicalDeviceSurfaceSupportKHR" Source #