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

Safe HaskellNone
LanguageHaskell2010

Graphics.Vulkan.Core_1_1

Contents

Synopsis

Vulkan 1.1 core API interface definitions.

api = vulkan
name = VK_VERSION_1_1
number = 1.1

Device Initialization

type VkEnumerateInstanceVersion = "vkEnumerateInstanceVersion" Source #

type HS_vkEnumerateInstanceVersion Source #

Arguments

 = Ptr Word32

pApiVersion

-> IO VkResult 

Success codes: VK_SUCCESS.

VkResult vkEnumerateInstanceVersion
    ( uint32_t* pApiVersion
    )

vkEnumerateInstanceVersion registry at www.khronos.org

vkEnumerateInstanceVersion Source #

Arguments

:: Ptr Word32

pApiVersion

-> IO VkResult 

Success codes: VK_SUCCESS.

VkResult vkEnumerateInstanceVersion
    ( uint32_t* pApiVersion
    )

vkEnumerateInstanceVersion registry at www.khronos.org

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

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

myEnumerateInstanceVersion <- vkGetInstanceProc @VkEnumerateInstanceVersion vkInstance

or less efficient:

myEnumerateInstanceVersion <- vkGetProc @VkEnumerateInstanceVersion

Note: vkEnumerateInstanceVersionUnsafe and vkEnumerateInstanceVersionSafe are the unsafe and safe FFI imports of this function, respectively. vkEnumerateInstanceVersion is an alias of vkEnumerateInstanceVersionUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkEnumerateInstanceVersionSafe.

vkEnumerateInstanceVersionUnsafe Source #

Arguments

:: Ptr Word32

pApiVersion

-> IO VkResult 

Success codes: VK_SUCCESS.

VkResult vkEnumerateInstanceVersion
    ( uint32_t* pApiVersion
    )

vkEnumerateInstanceVersion registry at www.khronos.org

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

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

myEnumerateInstanceVersion <- vkGetInstanceProc @VkEnumerateInstanceVersion vkInstance

or less efficient:

myEnumerateInstanceVersion <- vkGetProc @VkEnumerateInstanceVersion

Note: vkEnumerateInstanceVersionUnsafe and vkEnumerateInstanceVersionSafe are the unsafe and safe FFI imports of this function, respectively. vkEnumerateInstanceVersion is an alias of vkEnumerateInstanceVersionUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkEnumerateInstanceVersionSafe.

vkEnumerateInstanceVersionSafe Source #

Arguments

:: Ptr Word32

pApiVersion

-> IO VkResult 

Success codes: VK_SUCCESS.

VkResult vkEnumerateInstanceVersion
    ( uint32_t* pApiVersion
    )

vkEnumerateInstanceVersion registry at www.khronos.org

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

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

myEnumerateInstanceVersion <- vkGetInstanceProc @VkEnumerateInstanceVersion vkInstance

or less efficient:

myEnumerateInstanceVersion <- vkGetProc @VkEnumerateInstanceVersion

Note: vkEnumerateInstanceVersionUnsafe and vkEnumerateInstanceVersionSafe are the unsafe and safe FFI imports of this function, respectively. vkEnumerateInstanceVersion is an alias of vkEnumerateInstanceVersionUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkEnumerateInstanceVersionSafe.

newtype VkResult Source #

API result codes

type = enum

VkResult registry at www.khronos.org

Constructors

VkResult Int32 

Instances

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

Methods

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

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

toConstr :: VkResult -> Constr #

dataTypeOf :: VkResult -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Associated Types

type Rep VkResult :: * -> * #

Methods

from :: VkResult -> Rep VkResult x #

to :: Rep VkResult x -> VkResult #

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

pattern VK_SUCCESS :: VkResult Source #

Command completed successfully

pattern VK_NOT_READY :: VkResult Source #

A fence or query has not yet completed

pattern VK_TIMEOUT :: VkResult Source #

A wait operation has not completed in the specified time

pattern VK_EVENT_SET :: VkResult Source #

An event is signaled

pattern VK_EVENT_RESET :: VkResult Source #

An event is unsignaled

pattern VK_INCOMPLETE :: VkResult Source #

A return array was too small for the result

pattern VK_ERROR_OUT_OF_HOST_MEMORY :: VkResult Source #

A host memory allocation has failed

pattern VK_ERROR_OUT_OF_DEVICE_MEMORY :: VkResult Source #

A device memory allocation has failed

pattern VK_ERROR_INITIALIZATION_FAILED :: VkResult Source #

Initialization of a object has failed

pattern VK_ERROR_DEVICE_LOST :: VkResult Source #

The logical device has been lost. See

pattern VK_ERROR_MEMORY_MAP_FAILED :: VkResult Source #

Mapping of a memory object has failed

pattern VK_ERROR_LAYER_NOT_PRESENT :: VkResult Source #

Layer specified does not exist

pattern VK_ERROR_EXTENSION_NOT_PRESENT :: VkResult Source #

Extension specified does not exist

pattern VK_ERROR_FEATURE_NOT_PRESENT :: VkResult Source #

Requested feature is not available on this device

pattern VK_ERROR_INCOMPATIBLE_DRIVER :: VkResult Source #

Unable to find a Vulkan driver

pattern VK_ERROR_TOO_MANY_OBJECTS :: VkResult Source #

Too many objects of the type have already been created

pattern VK_ERROR_FORMAT_NOT_SUPPORTED :: VkResult Source #

Requested format is not supported on this device

pattern VK_ERROR_FRAGMENTED_POOL :: VkResult Source #

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

Promoted from VK_KHR_relaxed_block_layout, which has no API

Promoted from VK_KHR_storage_buffer_storage_class, which has no API

Originally based on VK_KHR_subgroup (extension 94), but the actual enum block used was, incorrectly, that of extension 95

newtype VkBool32 Source #

Constructors

VkBool32 Word32 

Instances

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

Methods

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

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

toConstr :: VkBool32 -> Constr #

dataTypeOf :: VkBool32 -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Associated Types

type Rep VkBool32 :: * -> * #

Methods

from :: VkBool32 -> Rep VkBool32 x #

to :: Rep VkBool32 x -> VkBool32 #

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

newtype VkDeviceSize Source #

Constructors

VkDeviceSize Word64 

Instances

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

Methods

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

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

toConstr :: VkDeviceSize -> Constr #

dataTypeOf :: VkDeviceSize -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Associated Types

type Rep VkDeviceSize :: * -> * #

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

newtype VkFlags Source #

Constructors

VkFlags Word32 

Instances

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

Methods

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

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

Integral VkFlags Source # 
Data VkFlags Source # 

Methods

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

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

toConstr :: VkFlags -> Constr #

dataTypeOf :: VkFlags -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Associated Types

type Rep VkFlags :: * -> * #

Methods

from :: VkFlags -> Rep VkFlags x #

to :: Rep VkFlags x -> VkFlags #

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

newtype VkSampleMask Source #

Constructors

VkSampleMask Word32 

Instances

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

Methods

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

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

toConstr :: VkSampleMask -> Constr #

dataTypeOf :: VkSampleMask -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Associated Types

type Rep VkSampleMask :: * -> * #

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

data VkPhysicalDevice16BitStorageFeatures Source #

typedef struct VkPhysicalDevice16BitStorageFeatures {
    VkStructureType sType;
    void*      pNext;
    VkBool32                         storageBuffer16BitAccess;
    VkBool32                         uniformAndStorageBuffer16BitAccess;
    VkBool32                         storagePushConstant16;
    VkBool32                         storageInputOutput16;
} VkPhysicalDevice16BitStorageFeatures;

VkPhysicalDevice16BitStorageFeatures registry at www.khronos.org

Instances

Eq VkPhysicalDevice16BitStorageFeatures Source # 
Ord VkPhysicalDevice16BitStorageFeatures Source # 
Show VkPhysicalDevice16BitStorageFeatures Source # 
Storable VkPhysicalDevice16BitStorageFeatures Source # 
VulkanMarshalPrim VkPhysicalDevice16BitStorageFeatures Source # 
VulkanMarshal VkPhysicalDevice16BitStorageFeatures Source # 
CanWriteField "pNext" VkPhysicalDevice16BitStorageFeatures Source # 
CanWriteField "sType" VkPhysicalDevice16BitStorageFeatures Source # 
CanWriteField "storageBuffer16BitAccess" VkPhysicalDevice16BitStorageFeatures Source # 
CanWriteField "storageInputOutput16" VkPhysicalDevice16BitStorageFeatures Source # 
CanWriteField "storagePushConstant16" VkPhysicalDevice16BitStorageFeatures Source # 
CanWriteField "uniformAndStorageBuffer16BitAccess" VkPhysicalDevice16BitStorageFeatures Source # 
CanReadField "pNext" VkPhysicalDevice16BitStorageFeatures Source # 
CanReadField "sType" VkPhysicalDevice16BitStorageFeatures Source # 
CanReadField "storageBuffer16BitAccess" VkPhysicalDevice16BitStorageFeatures Source # 
CanReadField "storageInputOutput16" VkPhysicalDevice16BitStorageFeatures Source # 
CanReadField "storagePushConstant16" VkPhysicalDevice16BitStorageFeatures Source # 
CanReadField "uniformAndStorageBuffer16BitAccess" VkPhysicalDevice16BitStorageFeatures Source # 
HasField "pNext" VkPhysicalDevice16BitStorageFeatures Source # 
HasField "sType" VkPhysicalDevice16BitStorageFeatures Source # 
HasField "storageBuffer16BitAccess" VkPhysicalDevice16BitStorageFeatures Source # 

Associated Types

type FieldType ("storageBuffer16BitAccess" :: Symbol) VkPhysicalDevice16BitStorageFeatures :: Type Source #

type FieldOptional ("storageBuffer16BitAccess" :: Symbol) VkPhysicalDevice16BitStorageFeatures :: Bool Source #

type FieldOffset ("storageBuffer16BitAccess" :: Symbol) VkPhysicalDevice16BitStorageFeatures :: Nat Source #

type FieldIsArray ("storageBuffer16BitAccess" :: Symbol) VkPhysicalDevice16BitStorageFeatures :: Bool Source #

HasField "storageInputOutput16" VkPhysicalDevice16BitStorageFeatures Source # 
HasField "storagePushConstant16" VkPhysicalDevice16BitStorageFeatures Source # 

Associated Types

type FieldType ("storagePushConstant16" :: Symbol) VkPhysicalDevice16BitStorageFeatures :: Type Source #

type FieldOptional ("storagePushConstant16" :: Symbol) VkPhysicalDevice16BitStorageFeatures :: Bool Source #

type FieldOffset ("storagePushConstant16" :: Symbol) VkPhysicalDevice16BitStorageFeatures :: Nat Source #

type FieldIsArray ("storagePushConstant16" :: Symbol) VkPhysicalDevice16BitStorageFeatures :: Bool Source #

HasField "uniformAndStorageBuffer16BitAccess" VkPhysicalDevice16BitStorageFeatures Source # 

Associated Types

type FieldType ("uniformAndStorageBuffer16BitAccess" :: Symbol) VkPhysicalDevice16BitStorageFeatures :: Type Source #

type FieldOptional ("uniformAndStorageBuffer16BitAccess" :: Symbol) VkPhysicalDevice16BitStorageFeatures :: Bool Source #

type FieldOffset ("uniformAndStorageBuffer16BitAccess" :: Symbol) VkPhysicalDevice16BitStorageFeatures :: Nat Source #

type FieldIsArray ("uniformAndStorageBuffer16BitAccess" :: Symbol) VkPhysicalDevice16BitStorageFeatures :: Bool Source #

type StructFields VkPhysicalDevice16BitStorageFeatures Source # 
type StructFields VkPhysicalDevice16BitStorageFeatures = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "storageBuffer16BitAccess" ((:) Symbol "uniformAndStorageBuffer16BitAccess" ((:) Symbol "storagePushConstant16" ((:) Symbol "storageInputOutput16" ([] Symbol))))))
type CUnionType VkPhysicalDevice16BitStorageFeatures Source # 
type ReturnedOnly VkPhysicalDevice16BitStorageFeatures Source # 
type StructExtends VkPhysicalDevice16BitStorageFeatures Source # 
type FieldType "pNext" VkPhysicalDevice16BitStorageFeatures Source # 
type FieldType "sType" VkPhysicalDevice16BitStorageFeatures Source # 
type FieldType "storageBuffer16BitAccess" VkPhysicalDevice16BitStorageFeatures Source # 
type FieldType "storageBuffer16BitAccess" VkPhysicalDevice16BitStorageFeatures = VkBool32
type FieldType "storageInputOutput16" VkPhysicalDevice16BitStorageFeatures Source # 
type FieldType "storagePushConstant16" VkPhysicalDevice16BitStorageFeatures Source # 
type FieldType "uniformAndStorageBuffer16BitAccess" VkPhysicalDevice16BitStorageFeatures Source # 
type FieldType "uniformAndStorageBuffer16BitAccess" VkPhysicalDevice16BitStorageFeatures = VkBool32
type FieldOptional "pNext" VkPhysicalDevice16BitStorageFeatures Source # 
type FieldOptional "sType" VkPhysicalDevice16BitStorageFeatures Source # 
type FieldOptional "storageBuffer16BitAccess" VkPhysicalDevice16BitStorageFeatures Source # 
type FieldOptional "storageBuffer16BitAccess" VkPhysicalDevice16BitStorageFeatures = False
type FieldOptional "storageInputOutput16" VkPhysicalDevice16BitStorageFeatures Source # 
type FieldOptional "storagePushConstant16" VkPhysicalDevice16BitStorageFeatures Source # 
type FieldOptional "uniformAndStorageBuffer16BitAccess" VkPhysicalDevice16BitStorageFeatures Source # 
type FieldOptional "uniformAndStorageBuffer16BitAccess" VkPhysicalDevice16BitStorageFeatures = False
type FieldOffset "pNext" VkPhysicalDevice16BitStorageFeatures Source # 
type FieldOffset "sType" VkPhysicalDevice16BitStorageFeatures Source # 
type FieldOffset "storageBuffer16BitAccess" VkPhysicalDevice16BitStorageFeatures Source # 
type FieldOffset "storageBuffer16BitAccess" VkPhysicalDevice16BitStorageFeatures = 16
type FieldOffset "storageInputOutput16" VkPhysicalDevice16BitStorageFeatures Source # 
type FieldOffset "storageInputOutput16" VkPhysicalDevice16BitStorageFeatures = 28
type FieldOffset "storagePushConstant16" VkPhysicalDevice16BitStorageFeatures Source # 
type FieldOffset "storagePushConstant16" VkPhysicalDevice16BitStorageFeatures = 24
type FieldOffset "uniformAndStorageBuffer16BitAccess" VkPhysicalDevice16BitStorageFeatures Source # 
type FieldOffset "uniformAndStorageBuffer16BitAccess" VkPhysicalDevice16BitStorageFeatures = 20
type FieldIsArray "pNext" VkPhysicalDevice16BitStorageFeatures Source # 
type FieldIsArray "sType" VkPhysicalDevice16BitStorageFeatures Source # 
type FieldIsArray "storageBuffer16BitAccess" VkPhysicalDevice16BitStorageFeatures Source # 
type FieldIsArray "storageBuffer16BitAccess" VkPhysicalDevice16BitStorageFeatures = False
type FieldIsArray "storageInputOutput16" VkPhysicalDevice16BitStorageFeatures Source # 
type FieldIsArray "storagePushConstant16" VkPhysicalDevice16BitStorageFeatures Source # 
type FieldIsArray "uniformAndStorageBuffer16BitAccess" VkPhysicalDevice16BitStorageFeatures Source # 
type FieldIsArray "uniformAndStorageBuffer16BitAccess" VkPhysicalDevice16BitStorageFeatures = False

data VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT Source #

typedef struct VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT {
    VkStructureType sType;
    void*                            pNext;
    VkBool32                         advancedBlendCoherentOperations;
} VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT;

VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT registry at www.khronos.org

Instances

Eq VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT Source # 
Ord VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT Source # 
Show VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT Source # 
Storable VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT Source # 
VulkanMarshalPrim VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT Source # 
VulkanMarshal VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT Source # 
CanWriteField "advancedBlendCoherentOperations" VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT Source # 
CanWriteField "pNext" VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT Source # 
CanWriteField "sType" VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT Source # 
CanReadField "advancedBlendCoherentOperations" VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT Source # 
CanReadField "pNext" VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT Source # 
CanReadField "sType" VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT Source # 
HasField "advancedBlendCoherentOperations" VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT Source # 

Associated Types

type FieldType ("advancedBlendCoherentOperations" :: Symbol) VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT :: Type Source #

type FieldOptional ("advancedBlendCoherentOperations" :: Symbol) VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT :: Bool Source #

type FieldOffset ("advancedBlendCoherentOperations" :: Symbol) VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT :: Nat Source #

type FieldIsArray ("advancedBlendCoherentOperations" :: Symbol) VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT :: Bool Source #

HasField "pNext" VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT Source # 
HasField "sType" VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT Source # 
type StructFields VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT Source # 
type StructFields VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "advancedBlendCoherentOperations" ([] Symbol)))
type CUnionType VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT Source # 
type ReturnedOnly VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT Source # 
type StructExtends VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT Source # 
type FieldType "advancedBlendCoherentOperations" VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT Source # 
type FieldType "pNext" VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT Source # 
type FieldType "sType" VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT Source # 
type FieldOptional "advancedBlendCoherentOperations" VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT Source # 
type FieldOptional "pNext" VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT Source # 
type FieldOptional "sType" VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT Source # 
type FieldOffset "advancedBlendCoherentOperations" VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT Source # 
type FieldOffset "advancedBlendCoherentOperations" VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT = 16
type FieldOffset "pNext" VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT Source # 
type FieldOffset "sType" VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT Source # 
type FieldIsArray "advancedBlendCoherentOperations" VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT Source # 
type FieldIsArray "pNext" VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT Source # 
type FieldIsArray "sType" VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT Source # 

data VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source #

typedef struct VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT {
    VkStructureType sType;
    void*                            pNext;
    uint32_t                         advancedBlendMaxColorAttachments;
    VkBool32                         advancedBlendIndependentBlend;
    VkBool32                         advancedBlendNonPremultipliedSrcColor;
    VkBool32                         advancedBlendNonPremultipliedDstColor;
    VkBool32                         advancedBlendCorrelatedOverlap;
    VkBool32                         advancedBlendAllOperations;
} VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT;

VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT registry at www.khronos.org

Instances

Eq VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
Ord VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
Show VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
Storable VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
VulkanMarshalPrim VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
VulkanMarshal VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
CanWriteField "advancedBlendAllOperations" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
CanWriteField "advancedBlendCorrelatedOverlap" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
CanWriteField "advancedBlendIndependentBlend" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
CanWriteField "advancedBlendMaxColorAttachments" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
CanWriteField "advancedBlendNonPremultipliedDstColor" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
CanWriteField "advancedBlendNonPremultipliedSrcColor" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
CanWriteField "pNext" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
CanWriteField "sType" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
CanReadField "advancedBlendAllOperations" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
CanReadField "advancedBlendCorrelatedOverlap" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
CanReadField "advancedBlendIndependentBlend" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
CanReadField "advancedBlendMaxColorAttachments" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
CanReadField "advancedBlendNonPremultipliedDstColor" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
CanReadField "advancedBlendNonPremultipliedSrcColor" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
CanReadField "pNext" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
CanReadField "sType" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
HasField "advancedBlendAllOperations" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
HasField "advancedBlendCorrelatedOverlap" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
HasField "advancedBlendIndependentBlend" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
HasField "advancedBlendMaxColorAttachments" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 

Associated Types

type FieldType ("advancedBlendMaxColorAttachments" :: Symbol) VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT :: Type Source #

type FieldOptional ("advancedBlendMaxColorAttachments" :: Symbol) VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT :: Bool Source #

type FieldOffset ("advancedBlendMaxColorAttachments" :: Symbol) VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT :: Nat Source #

type FieldIsArray ("advancedBlendMaxColorAttachments" :: Symbol) VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT :: Bool Source #

HasField "advancedBlendNonPremultipliedDstColor" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 

Associated Types

type FieldType ("advancedBlendNonPremultipliedDstColor" :: Symbol) VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT :: Type Source #

type FieldOptional ("advancedBlendNonPremultipliedDstColor" :: Symbol) VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT :: Bool Source #

type FieldOffset ("advancedBlendNonPremultipliedDstColor" :: Symbol) VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT :: Nat Source #

type FieldIsArray ("advancedBlendNonPremultipliedDstColor" :: Symbol) VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT :: Bool Source #

HasField "advancedBlendNonPremultipliedSrcColor" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 

Associated Types

type FieldType ("advancedBlendNonPremultipliedSrcColor" :: Symbol) VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT :: Type Source #

type FieldOptional ("advancedBlendNonPremultipliedSrcColor" :: Symbol) VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT :: Bool Source #

type FieldOffset ("advancedBlendNonPremultipliedSrcColor" :: Symbol) VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT :: Nat Source #

type FieldIsArray ("advancedBlendNonPremultipliedSrcColor" :: Symbol) VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT :: Bool Source #

HasField "pNext" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
HasField "sType" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
type StructFields VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
type StructFields VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "advancedBlendMaxColorAttachments" ((:) Symbol "advancedBlendIndependentBlend" ((:) Symbol "advancedBlendNonPremultipliedSrcColor" ((:) Symbol "advancedBlendNonPremultipliedDstColor" ((:) Symbol "advancedBlendCorrelatedOverlap" ((:) Symbol "advancedBlendAllOperations" ([] Symbol))))))))
type CUnionType VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
type ReturnedOnly VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
type StructExtends VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
type FieldType "advancedBlendAllOperations" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
type FieldType "advancedBlendCorrelatedOverlap" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
type FieldType "advancedBlendIndependentBlend" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
type FieldType "advancedBlendMaxColorAttachments" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
type FieldType "advancedBlendMaxColorAttachments" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT = Word32
type FieldType "advancedBlendNonPremultipliedDstColor" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
type FieldType "advancedBlendNonPremultipliedDstColor" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT = VkBool32
type FieldType "advancedBlendNonPremultipliedSrcColor" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
type FieldType "advancedBlendNonPremultipliedSrcColor" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT = VkBool32
type FieldType "pNext" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
type FieldType "sType" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
type FieldOptional "advancedBlendAllOperations" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
type FieldOptional "advancedBlendCorrelatedOverlap" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
type FieldOptional "advancedBlendIndependentBlend" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
type FieldOptional "advancedBlendMaxColorAttachments" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
type FieldOptional "advancedBlendNonPremultipliedDstColor" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
type FieldOptional "advancedBlendNonPremultipliedDstColor" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT = False
type FieldOptional "advancedBlendNonPremultipliedSrcColor" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
type FieldOptional "advancedBlendNonPremultipliedSrcColor" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT = False
type FieldOptional "pNext" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
type FieldOptional "sType" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
type FieldOffset "advancedBlendAllOperations" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
type FieldOffset "advancedBlendCorrelatedOverlap" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
type FieldOffset "advancedBlendCorrelatedOverlap" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT = 32
type FieldOffset "advancedBlendIndependentBlend" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
type FieldOffset "advancedBlendIndependentBlend" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT = 20
type FieldOffset "advancedBlendMaxColorAttachments" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
type FieldOffset "advancedBlendMaxColorAttachments" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT = 16
type FieldOffset "advancedBlendNonPremultipliedDstColor" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
type FieldOffset "advancedBlendNonPremultipliedDstColor" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT = 28
type FieldOffset "advancedBlendNonPremultipliedSrcColor" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
type FieldOffset "advancedBlendNonPremultipliedSrcColor" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT = 24
type FieldOffset "pNext" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
type FieldOffset "sType" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
type FieldIsArray "advancedBlendAllOperations" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
type FieldIsArray "advancedBlendCorrelatedOverlap" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
type FieldIsArray "advancedBlendIndependentBlend" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
type FieldIsArray "advancedBlendMaxColorAttachments" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
type FieldIsArray "advancedBlendNonPremultipliedDstColor" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
type FieldIsArray "advancedBlendNonPremultipliedDstColor" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT = False
type FieldIsArray "advancedBlendNonPremultipliedSrcColor" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
type FieldIsArray "advancedBlendNonPremultipliedSrcColor" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT = False
type FieldIsArray "pNext" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 
type FieldIsArray "sType" VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT Source # 

data VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source #

typedef struct VkPhysicalDeviceConservativeRasterizationPropertiesEXT {
    VkStructureType sType;
    void*                  pNext;
    float                  primitiveOverestimationSize;
    float                  maxExtraPrimitiveOverestimationSize;
    float                  extraPrimitiveOverestimationSizeGranularity;
    VkBool32               primitiveUnderestimation;
    VkBool32               conservativePointAndLineRasterization;
    VkBool32               degenerateTrianglesRasterized;
    VkBool32               degenerateLinesRasterized;
    VkBool32               fullyCoveredFragmentShaderInputVariable;
    VkBool32               conservativeRasterizationPostDepthCoverage;
} VkPhysicalDeviceConservativeRasterizationPropertiesEXT;

VkPhysicalDeviceConservativeRasterizationPropertiesEXT registry at www.khronos.org

Instances

Eq VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
Ord VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
Show VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
Storable VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
VulkanMarshalPrim VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
VulkanMarshal VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
CanWriteField "conservativePointAndLineRasterization" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
CanWriteField "conservativeRasterizationPostDepthCoverage" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
CanWriteField "degenerateLinesRasterized" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
CanWriteField "degenerateTrianglesRasterized" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
CanWriteField "extraPrimitiveOverestimationSizeGranularity" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
CanWriteField "fullyCoveredFragmentShaderInputVariable" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
CanWriteField "maxExtraPrimitiveOverestimationSize" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
CanWriteField "pNext" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
CanWriteField "primitiveOverestimationSize" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
CanWriteField "primitiveUnderestimation" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
CanWriteField "sType" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
CanReadField "conservativePointAndLineRasterization" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
CanReadField "conservativeRasterizationPostDepthCoverage" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
CanReadField "degenerateLinesRasterized" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
CanReadField "degenerateTrianglesRasterized" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
CanReadField "extraPrimitiveOverestimationSizeGranularity" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
CanReadField "fullyCoveredFragmentShaderInputVariable" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
CanReadField "maxExtraPrimitiveOverestimationSize" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
CanReadField "pNext" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
CanReadField "primitiveOverestimationSize" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
CanReadField "primitiveUnderestimation" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
CanReadField "sType" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
HasField "conservativePointAndLineRasterization" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 

Associated Types

type FieldType ("conservativePointAndLineRasterization" :: Symbol) VkPhysicalDeviceConservativeRasterizationPropertiesEXT :: Type Source #

type FieldOptional ("conservativePointAndLineRasterization" :: Symbol) VkPhysicalDeviceConservativeRasterizationPropertiesEXT :: Bool Source #

type FieldOffset ("conservativePointAndLineRasterization" :: Symbol) VkPhysicalDeviceConservativeRasterizationPropertiesEXT :: Nat Source #

type FieldIsArray ("conservativePointAndLineRasterization" :: Symbol) VkPhysicalDeviceConservativeRasterizationPropertiesEXT :: Bool Source #

HasField "conservativeRasterizationPostDepthCoverage" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 

Associated Types

type FieldType ("conservativeRasterizationPostDepthCoverage" :: Symbol) VkPhysicalDeviceConservativeRasterizationPropertiesEXT :: Type Source #

type FieldOptional ("conservativeRasterizationPostDepthCoverage" :: Symbol) VkPhysicalDeviceConservativeRasterizationPropertiesEXT :: Bool Source #

type FieldOffset ("conservativeRasterizationPostDepthCoverage" :: Symbol) VkPhysicalDeviceConservativeRasterizationPropertiesEXT :: Nat Source #

type FieldIsArray ("conservativeRasterizationPostDepthCoverage" :: Symbol) VkPhysicalDeviceConservativeRasterizationPropertiesEXT :: Bool Source #

HasField "degenerateLinesRasterized" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
HasField "degenerateTrianglesRasterized" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
HasField "extraPrimitiveOverestimationSizeGranularity" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 

Associated Types

type FieldType ("extraPrimitiveOverestimationSizeGranularity" :: Symbol) VkPhysicalDeviceConservativeRasterizationPropertiesEXT :: Type Source #

type FieldOptional ("extraPrimitiveOverestimationSizeGranularity" :: Symbol) VkPhysicalDeviceConservativeRasterizationPropertiesEXT :: Bool Source #

type FieldOffset ("extraPrimitiveOverestimationSizeGranularity" :: Symbol) VkPhysicalDeviceConservativeRasterizationPropertiesEXT :: Nat Source #

type FieldIsArray ("extraPrimitiveOverestimationSizeGranularity" :: Symbol) VkPhysicalDeviceConservativeRasterizationPropertiesEXT :: Bool Source #

HasField "fullyCoveredFragmentShaderInputVariable" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 

Associated Types

type FieldType ("fullyCoveredFragmentShaderInputVariable" :: Symbol) VkPhysicalDeviceConservativeRasterizationPropertiesEXT :: Type Source #

type FieldOptional ("fullyCoveredFragmentShaderInputVariable" :: Symbol) VkPhysicalDeviceConservativeRasterizationPropertiesEXT :: Bool Source #

type FieldOffset ("fullyCoveredFragmentShaderInputVariable" :: Symbol) VkPhysicalDeviceConservativeRasterizationPropertiesEXT :: Nat Source #

type FieldIsArray ("fullyCoveredFragmentShaderInputVariable" :: Symbol) VkPhysicalDeviceConservativeRasterizationPropertiesEXT :: Bool Source #

HasField "maxExtraPrimitiveOverestimationSize" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 

Associated Types

type FieldType ("maxExtraPrimitiveOverestimationSize" :: Symbol) VkPhysicalDeviceConservativeRasterizationPropertiesEXT :: Type Source #

type FieldOptional ("maxExtraPrimitiveOverestimationSize" :: Symbol) VkPhysicalDeviceConservativeRasterizationPropertiesEXT :: Bool Source #

type FieldOffset ("maxExtraPrimitiveOverestimationSize" :: Symbol) VkPhysicalDeviceConservativeRasterizationPropertiesEXT :: Nat Source #

type FieldIsArray ("maxExtraPrimitiveOverestimationSize" :: Symbol) VkPhysicalDeviceConservativeRasterizationPropertiesEXT :: Bool Source #

HasField "pNext" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
HasField "primitiveOverestimationSize" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
HasField "primitiveUnderestimation" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
HasField "sType" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type StructFields VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type StructFields VkPhysicalDeviceConservativeRasterizationPropertiesEXT = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "primitiveOverestimationSize" ((:) Symbol "maxExtraPrimitiveOverestimationSize" ((:) Symbol "extraPrimitiveOverestimationSizeGranularity" ((:) Symbol "primitiveUnderestimation" ((:) Symbol "conservativePointAndLineRasterization" ((:) Symbol "degenerateTrianglesRasterized" ((:) Symbol "degenerateLinesRasterized" ((:) Symbol "fullyCoveredFragmentShaderInputVariable" ((:) Symbol "conservativeRasterizationPostDepthCoverage" ([] Symbol)))))))))))
type CUnionType VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type ReturnedOnly VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type StructExtends VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldType "conservativePointAndLineRasterization" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldType "conservativePointAndLineRasterization" VkPhysicalDeviceConservativeRasterizationPropertiesEXT = VkBool32
type FieldType "conservativeRasterizationPostDepthCoverage" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldType "conservativeRasterizationPostDepthCoverage" VkPhysicalDeviceConservativeRasterizationPropertiesEXT = VkBool32
type FieldType "degenerateLinesRasterized" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldType "degenerateTrianglesRasterized" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldType "extraPrimitiveOverestimationSizeGranularity" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldType "extraPrimitiveOverestimationSizeGranularity" VkPhysicalDeviceConservativeRasterizationPropertiesEXT = Float
type FieldType "fullyCoveredFragmentShaderInputVariable" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldType "fullyCoveredFragmentShaderInputVariable" VkPhysicalDeviceConservativeRasterizationPropertiesEXT = VkBool32
type FieldType "maxExtraPrimitiveOverestimationSize" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldType "maxExtraPrimitiveOverestimationSize" VkPhysicalDeviceConservativeRasterizationPropertiesEXT = Float
type FieldType "pNext" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldType "primitiveOverestimationSize" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldType "primitiveUnderestimation" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldType "sType" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldOptional "conservativePointAndLineRasterization" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldOptional "conservativePointAndLineRasterization" VkPhysicalDeviceConservativeRasterizationPropertiesEXT = False
type FieldOptional "conservativeRasterizationPostDepthCoverage" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldOptional "conservativeRasterizationPostDepthCoverage" VkPhysicalDeviceConservativeRasterizationPropertiesEXT = False
type FieldOptional "degenerateLinesRasterized" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldOptional "degenerateTrianglesRasterized" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldOptional "extraPrimitiveOverestimationSizeGranularity" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldOptional "extraPrimitiveOverestimationSizeGranularity" VkPhysicalDeviceConservativeRasterizationPropertiesEXT = False
type FieldOptional "fullyCoveredFragmentShaderInputVariable" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldOptional "fullyCoveredFragmentShaderInputVariable" VkPhysicalDeviceConservativeRasterizationPropertiesEXT = False
type FieldOptional "maxExtraPrimitiveOverestimationSize" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldOptional "pNext" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldOptional "primitiveOverestimationSize" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldOptional "primitiveUnderestimation" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldOptional "sType" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldOffset "conservativePointAndLineRasterization" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldOffset "conservativePointAndLineRasterization" VkPhysicalDeviceConservativeRasterizationPropertiesEXT = 32
type FieldOffset "conservativeRasterizationPostDepthCoverage" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldOffset "conservativeRasterizationPostDepthCoverage" VkPhysicalDeviceConservativeRasterizationPropertiesEXT = 48
type FieldOffset "degenerateLinesRasterized" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldOffset "degenerateTrianglesRasterized" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldOffset "extraPrimitiveOverestimationSizeGranularity" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldOffset "extraPrimitiveOverestimationSizeGranularity" VkPhysicalDeviceConservativeRasterizationPropertiesEXT = 24
type FieldOffset "fullyCoveredFragmentShaderInputVariable" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldOffset "fullyCoveredFragmentShaderInputVariable" VkPhysicalDeviceConservativeRasterizationPropertiesEXT = 44
type FieldOffset "maxExtraPrimitiveOverestimationSize" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldOffset "maxExtraPrimitiveOverestimationSize" VkPhysicalDeviceConservativeRasterizationPropertiesEXT = 20
type FieldOffset "pNext" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldOffset "primitiveOverestimationSize" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldOffset "primitiveUnderestimation" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldOffset "sType" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldIsArray "conservativePointAndLineRasterization" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldIsArray "conservativePointAndLineRasterization" VkPhysicalDeviceConservativeRasterizationPropertiesEXT = False
type FieldIsArray "conservativeRasterizationPostDepthCoverage" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldIsArray "conservativeRasterizationPostDepthCoverage" VkPhysicalDeviceConservativeRasterizationPropertiesEXT = False
type FieldIsArray "degenerateLinesRasterized" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldIsArray "degenerateTrianglesRasterized" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldIsArray "extraPrimitiveOverestimationSizeGranularity" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldIsArray "extraPrimitiveOverestimationSizeGranularity" VkPhysicalDeviceConservativeRasterizationPropertiesEXT = False
type FieldIsArray "fullyCoveredFragmentShaderInputVariable" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldIsArray "fullyCoveredFragmentShaderInputVariable" VkPhysicalDeviceConservativeRasterizationPropertiesEXT = False
type FieldIsArray "maxExtraPrimitiveOverestimationSize" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldIsArray "pNext" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldIsArray "primitiveOverestimationSize" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldIsArray "primitiveUnderestimation" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 
type FieldIsArray "sType" VkPhysicalDeviceConservativeRasterizationPropertiesEXT Source # 

data VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source #

typedef struct VkPhysicalDeviceDescriptorIndexingFeaturesEXT {
    VkStructureType sType;
    void*                            pNext;
    VkBool32               shaderInputAttachmentArrayDynamicIndexing;
    VkBool32               shaderUniformTexelBufferArrayDynamicIndexing;
    VkBool32               shaderStorageTexelBufferArrayDynamicIndexing;
    VkBool32               shaderUniformBufferArrayNonUniformIndexing;
    VkBool32               shaderSampledImageArrayNonUniformIndexing;
    VkBool32               shaderStorageBufferArrayNonUniformIndexing;
    VkBool32               shaderStorageImageArrayNonUniformIndexing;
    VkBool32               shaderInputAttachmentArrayNonUniformIndexing;
    VkBool32               shaderUniformTexelBufferArrayNonUniformIndexing;
    VkBool32               shaderStorageTexelBufferArrayNonUniformIndexing;
    VkBool32               descriptorBindingUniformBufferUpdateAfterBind;
    VkBool32               descriptorBindingSampledImageUpdateAfterBind;
    VkBool32               descriptorBindingStorageImageUpdateAfterBind;
    VkBool32               descriptorBindingStorageBufferUpdateAfterBind;
    VkBool32               descriptorBindingUniformTexelBufferUpdateAfterBind;
    VkBool32               descriptorBindingStorageTexelBufferUpdateAfterBind;
    VkBool32               descriptorBindingUpdateUnusedWhilePending;
    VkBool32               descriptorBindingPartiallyBound;
    VkBool32               descriptorBindingVariableDescriptorCount;
    VkBool32               runtimeDescriptorArray;
} VkPhysicalDeviceDescriptorIndexingFeaturesEXT;

VkPhysicalDeviceDescriptorIndexingFeaturesEXT registry at www.khronos.org

Instances

Eq VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
Ord VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
Show VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
Storable VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
VulkanMarshalPrim VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
VulkanMarshal VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanWriteField "descriptorBindingPartiallyBound" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanWriteField "descriptorBindingSampledImageUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanWriteField "descriptorBindingStorageBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanWriteField "descriptorBindingStorageImageUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanWriteField "descriptorBindingStorageTexelBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanWriteField "descriptorBindingUniformBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanWriteField "descriptorBindingUniformTexelBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanWriteField "descriptorBindingUpdateUnusedWhilePending" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanWriteField "descriptorBindingVariableDescriptorCount" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanWriteField "pNext" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanWriteField "runtimeDescriptorArray" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanWriteField "sType" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanWriteField "shaderInputAttachmentArrayDynamicIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanWriteField "shaderInputAttachmentArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanWriteField "shaderSampledImageArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanWriteField "shaderStorageBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanWriteField "shaderStorageImageArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanWriteField "shaderStorageTexelBufferArrayDynamicIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanWriteField "shaderStorageTexelBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanWriteField "shaderUniformBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanWriteField "shaderUniformTexelBufferArrayDynamicIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanWriteField "shaderUniformTexelBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanReadField "descriptorBindingPartiallyBound" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanReadField "descriptorBindingSampledImageUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanReadField "descriptorBindingStorageBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanReadField "descriptorBindingStorageImageUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanReadField "descriptorBindingStorageTexelBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanReadField "descriptorBindingUniformBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanReadField "descriptorBindingUniformTexelBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanReadField "descriptorBindingUpdateUnusedWhilePending" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanReadField "descriptorBindingVariableDescriptorCount" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanReadField "pNext" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanReadField "runtimeDescriptorArray" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanReadField "sType" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanReadField "shaderInputAttachmentArrayDynamicIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanReadField "shaderInputAttachmentArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanReadField "shaderSampledImageArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanReadField "shaderStorageBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanReadField "shaderStorageImageArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanReadField "shaderStorageTexelBufferArrayDynamicIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanReadField "shaderStorageTexelBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanReadField "shaderUniformBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanReadField "shaderUniformTexelBufferArrayDynamicIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
CanReadField "shaderUniformTexelBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
HasField "descriptorBindingPartiallyBound" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 

Associated Types

type FieldType ("descriptorBindingPartiallyBound" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Type Source #

type FieldOptional ("descriptorBindingPartiallyBound" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Bool Source #

type FieldOffset ("descriptorBindingPartiallyBound" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Nat Source #

type FieldIsArray ("descriptorBindingPartiallyBound" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Bool Source #

HasField "descriptorBindingSampledImageUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 

Associated Types

type FieldType ("descriptorBindingSampledImageUpdateAfterBind" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Type Source #

type FieldOptional ("descriptorBindingSampledImageUpdateAfterBind" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Bool Source #

type FieldOffset ("descriptorBindingSampledImageUpdateAfterBind" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Nat Source #

type FieldIsArray ("descriptorBindingSampledImageUpdateAfterBind" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Bool Source #

HasField "descriptorBindingStorageBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 

Associated Types

type FieldType ("descriptorBindingStorageBufferUpdateAfterBind" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Type Source #

type FieldOptional ("descriptorBindingStorageBufferUpdateAfterBind" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Bool Source #

type FieldOffset ("descriptorBindingStorageBufferUpdateAfterBind" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Nat Source #

type FieldIsArray ("descriptorBindingStorageBufferUpdateAfterBind" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Bool Source #

HasField "descriptorBindingStorageImageUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 

Associated Types

type FieldType ("descriptorBindingStorageImageUpdateAfterBind" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Type Source #

type FieldOptional ("descriptorBindingStorageImageUpdateAfterBind" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Bool Source #

type FieldOffset ("descriptorBindingStorageImageUpdateAfterBind" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Nat Source #

type FieldIsArray ("descriptorBindingStorageImageUpdateAfterBind" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Bool Source #

HasField "descriptorBindingStorageTexelBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 

Associated Types

type FieldType ("descriptorBindingStorageTexelBufferUpdateAfterBind" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Type Source #

type FieldOptional ("descriptorBindingStorageTexelBufferUpdateAfterBind" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Bool Source #

type FieldOffset ("descriptorBindingStorageTexelBufferUpdateAfterBind" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Nat Source #

type FieldIsArray ("descriptorBindingStorageTexelBufferUpdateAfterBind" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Bool Source #

HasField "descriptorBindingUniformBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 

Associated Types

type FieldType ("descriptorBindingUniformBufferUpdateAfterBind" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Type Source #

type FieldOptional ("descriptorBindingUniformBufferUpdateAfterBind" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Bool Source #

type FieldOffset ("descriptorBindingUniformBufferUpdateAfterBind" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Nat Source #

type FieldIsArray ("descriptorBindingUniformBufferUpdateAfterBind" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Bool Source #

HasField "descriptorBindingUniformTexelBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 

Associated Types

type FieldType ("descriptorBindingUniformTexelBufferUpdateAfterBind" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Type Source #

type FieldOptional ("descriptorBindingUniformTexelBufferUpdateAfterBind" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Bool Source #

type FieldOffset ("descriptorBindingUniformTexelBufferUpdateAfterBind" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Nat Source #

type FieldIsArray ("descriptorBindingUniformTexelBufferUpdateAfterBind" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Bool Source #

HasField "descriptorBindingUpdateUnusedWhilePending" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 

Associated Types

type FieldType ("descriptorBindingUpdateUnusedWhilePending" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Type Source #

type FieldOptional ("descriptorBindingUpdateUnusedWhilePending" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Bool Source #

type FieldOffset ("descriptorBindingUpdateUnusedWhilePending" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Nat Source #

type FieldIsArray ("descriptorBindingUpdateUnusedWhilePending" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Bool Source #

HasField "descriptorBindingVariableDescriptorCount" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 

Associated Types

type FieldType ("descriptorBindingVariableDescriptorCount" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Type Source #

type FieldOptional ("descriptorBindingVariableDescriptorCount" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Bool Source #

type FieldOffset ("descriptorBindingVariableDescriptorCount" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Nat Source #

type FieldIsArray ("descriptorBindingVariableDescriptorCount" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Bool Source #

HasField "pNext" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
HasField "runtimeDescriptorArray" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
HasField "sType" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
HasField "shaderInputAttachmentArrayDynamicIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 

Associated Types

type FieldType ("shaderInputAttachmentArrayDynamicIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Type Source #

type FieldOptional ("shaderInputAttachmentArrayDynamicIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Bool Source #

type FieldOffset ("shaderInputAttachmentArrayDynamicIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Nat Source #

type FieldIsArray ("shaderInputAttachmentArrayDynamicIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Bool Source #

HasField "shaderInputAttachmentArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 

Associated Types

type FieldType ("shaderInputAttachmentArrayNonUniformIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Type Source #

type FieldOptional ("shaderInputAttachmentArrayNonUniformIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Bool Source #

type FieldOffset ("shaderInputAttachmentArrayNonUniformIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Nat Source #

type FieldIsArray ("shaderInputAttachmentArrayNonUniformIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Bool Source #

HasField "shaderSampledImageArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 

Associated Types

type FieldType ("shaderSampledImageArrayNonUniformIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Type Source #

type FieldOptional ("shaderSampledImageArrayNonUniformIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Bool Source #

type FieldOffset ("shaderSampledImageArrayNonUniformIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Nat Source #

type FieldIsArray ("shaderSampledImageArrayNonUniformIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Bool Source #

HasField "shaderStorageBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 

Associated Types

type FieldType ("shaderStorageBufferArrayNonUniformIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Type Source #

type FieldOptional ("shaderStorageBufferArrayNonUniformIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Bool Source #

type FieldOffset ("shaderStorageBufferArrayNonUniformIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Nat Source #

type FieldIsArray ("shaderStorageBufferArrayNonUniformIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Bool Source #

HasField "shaderStorageImageArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 

Associated Types

type FieldType ("shaderStorageImageArrayNonUniformIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Type Source #

type FieldOptional ("shaderStorageImageArrayNonUniformIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Bool Source #

type FieldOffset ("shaderStorageImageArrayNonUniformIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Nat Source #

type FieldIsArray ("shaderStorageImageArrayNonUniformIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Bool Source #

HasField "shaderStorageTexelBufferArrayDynamicIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 

Associated Types

type FieldType ("shaderStorageTexelBufferArrayDynamicIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Type Source #

type FieldOptional ("shaderStorageTexelBufferArrayDynamicIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Bool Source #

type FieldOffset ("shaderStorageTexelBufferArrayDynamicIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Nat Source #

type FieldIsArray ("shaderStorageTexelBufferArrayDynamicIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Bool Source #

HasField "shaderStorageTexelBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 

Associated Types

type FieldType ("shaderStorageTexelBufferArrayNonUniformIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Type Source #

type FieldOptional ("shaderStorageTexelBufferArrayNonUniformIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Bool Source #

type FieldOffset ("shaderStorageTexelBufferArrayNonUniformIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Nat Source #

type FieldIsArray ("shaderStorageTexelBufferArrayNonUniformIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Bool Source #

HasField "shaderUniformBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 

Associated Types

type FieldType ("shaderUniformBufferArrayNonUniformIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Type Source #

type FieldOptional ("shaderUniformBufferArrayNonUniformIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Bool Source #

type FieldOffset ("shaderUniformBufferArrayNonUniformIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Nat Source #

type FieldIsArray ("shaderUniformBufferArrayNonUniformIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Bool Source #

HasField "shaderUniformTexelBufferArrayDynamicIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 

Associated Types

type FieldType ("shaderUniformTexelBufferArrayDynamicIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Type Source #

type FieldOptional ("shaderUniformTexelBufferArrayDynamicIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Bool Source #

type FieldOffset ("shaderUniformTexelBufferArrayDynamicIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Nat Source #

type FieldIsArray ("shaderUniformTexelBufferArrayDynamicIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Bool Source #

HasField "shaderUniformTexelBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 

Associated Types

type FieldType ("shaderUniformTexelBufferArrayNonUniformIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Type Source #

type FieldOptional ("shaderUniformTexelBufferArrayNonUniformIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Bool Source #

type FieldOffset ("shaderUniformTexelBufferArrayNonUniformIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Nat Source #

type FieldIsArray ("shaderUniformTexelBufferArrayNonUniformIndexing" :: Symbol) VkPhysicalDeviceDescriptorIndexingFeaturesEXT :: Bool Source #

type StructFields VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type StructFields VkPhysicalDeviceDescriptorIndexingFeaturesEXT = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "shaderInputAttachmentArrayDynamicIndexing" ((:) Symbol "shaderUniformTexelBufferArrayDynamicIndexing" ((:) Symbol "shaderStorageTexelBufferArrayDynamicIndexing" ((:) Symbol "shaderUniformBufferArrayNonUniformIndexing" ((:) Symbol "shaderSampledImageArrayNonUniformIndexing" ((:) Symbol "shaderStorageBufferArrayNonUniformIndexing" ((:) Symbol "shaderStorageImageArrayNonUniformIndexing" ((:) Symbol "shaderInputAttachmentArrayNonUniformIndexing" ((:) Symbol "shaderUniformTexelBufferArrayNonUniformIndexing" ((:) Symbol "shaderStorageTexelBufferArrayNonUniformIndexing" ((:) Symbol "descriptorBindingUniformBufferUpdateAfterBind" ((:) Symbol "descriptorBindingSampledImageUpdateAfterBind" ((:) Symbol "descriptorBindingStorageImageUpdateAfterBind" ((:) Symbol "descriptorBindingStorageBufferUpdateAfterBind" ((:) Symbol "descriptorBindingUniformTexelBufferUpdateAfterBind" ((:) Symbol "descriptorBindingStorageTexelBufferUpdateAfterBind" ((:) Symbol "descriptorBindingUpdateUnusedWhilePending" ((:) Symbol "descriptorBindingPartiallyBound" ((:) Symbol "descriptorBindingVariableDescriptorCount" ((:) Symbol "runtimeDescriptorArray" ([] Symbol))))))))))))))))))))))
type CUnionType VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type ReturnedOnly VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type StructExtends VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldType "descriptorBindingPartiallyBound" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldType "descriptorBindingPartiallyBound" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = VkBool32
type FieldType "descriptorBindingSampledImageUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldType "descriptorBindingSampledImageUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = VkBool32
type FieldType "descriptorBindingStorageBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldType "descriptorBindingStorageBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = VkBool32
type FieldType "descriptorBindingStorageImageUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldType "descriptorBindingStorageImageUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = VkBool32
type FieldType "descriptorBindingStorageTexelBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldType "descriptorBindingStorageTexelBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = VkBool32
type FieldType "descriptorBindingUniformBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldType "descriptorBindingUniformBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = VkBool32
type FieldType "descriptorBindingUniformTexelBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldType "descriptorBindingUniformTexelBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = VkBool32
type FieldType "descriptorBindingUpdateUnusedWhilePending" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldType "descriptorBindingUpdateUnusedWhilePending" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = VkBool32
type FieldType "descriptorBindingVariableDescriptorCount" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldType "descriptorBindingVariableDescriptorCount" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = VkBool32
type FieldType "pNext" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldType "runtimeDescriptorArray" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldType "sType" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldType "shaderInputAttachmentArrayDynamicIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldType "shaderInputAttachmentArrayDynamicIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = VkBool32
type FieldType "shaderInputAttachmentArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldType "shaderInputAttachmentArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = VkBool32
type FieldType "shaderSampledImageArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldType "shaderSampledImageArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = VkBool32
type FieldType "shaderStorageBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldType "shaderStorageBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = VkBool32
type FieldType "shaderStorageImageArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldType "shaderStorageImageArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = VkBool32
type FieldType "shaderStorageTexelBufferArrayDynamicIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldType "shaderStorageTexelBufferArrayDynamicIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = VkBool32
type FieldType "shaderStorageTexelBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldType "shaderStorageTexelBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = VkBool32
type FieldType "shaderUniformBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldType "shaderUniformBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = VkBool32
type FieldType "shaderUniformTexelBufferArrayDynamicIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldType "shaderUniformTexelBufferArrayDynamicIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = VkBool32
type FieldType "shaderUniformTexelBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldType "shaderUniformTexelBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = VkBool32
type FieldOptional "descriptorBindingPartiallyBound" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOptional "descriptorBindingPartiallyBound" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = False
type FieldOptional "descriptorBindingSampledImageUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOptional "descriptorBindingSampledImageUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = False
type FieldOptional "descriptorBindingStorageBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOptional "descriptorBindingStorageBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = False
type FieldOptional "descriptorBindingStorageImageUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOptional "descriptorBindingStorageImageUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = False
type FieldOptional "descriptorBindingStorageTexelBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOptional "descriptorBindingStorageTexelBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = False
type FieldOptional "descriptorBindingUniformBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOptional "descriptorBindingUniformBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = False
type FieldOptional "descriptorBindingUniformTexelBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOptional "descriptorBindingUniformTexelBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = False
type FieldOptional "descriptorBindingUpdateUnusedWhilePending" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOptional "descriptorBindingUpdateUnusedWhilePending" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = False
type FieldOptional "descriptorBindingVariableDescriptorCount" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOptional "descriptorBindingVariableDescriptorCount" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = False
type FieldOptional "pNext" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOptional "runtimeDescriptorArray" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOptional "sType" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOptional "shaderInputAttachmentArrayDynamicIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOptional "shaderInputAttachmentArrayDynamicIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = False
type FieldOptional "shaderInputAttachmentArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOptional "shaderInputAttachmentArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = False
type FieldOptional "shaderSampledImageArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOptional "shaderSampledImageArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = False
type FieldOptional "shaderStorageBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOptional "shaderStorageBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = False
type FieldOptional "shaderStorageImageArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOptional "shaderStorageImageArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = False
type FieldOptional "shaderStorageTexelBufferArrayDynamicIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOptional "shaderStorageTexelBufferArrayDynamicIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = False
type FieldOptional "shaderStorageTexelBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOptional "shaderStorageTexelBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = False
type FieldOptional "shaderUniformBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOptional "shaderUniformBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = False
type FieldOptional "shaderUniformTexelBufferArrayDynamicIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOptional "shaderUniformTexelBufferArrayDynamicIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = False
type FieldOptional "shaderUniformTexelBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOptional "shaderUniformTexelBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = False
type FieldOffset "descriptorBindingPartiallyBound" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOffset "descriptorBindingPartiallyBound" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = 84
type FieldOffset "descriptorBindingSampledImageUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOffset "descriptorBindingSampledImageUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = 60
type FieldOffset "descriptorBindingStorageBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOffset "descriptorBindingStorageBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = 68
type FieldOffset "descriptorBindingStorageImageUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOffset "descriptorBindingStorageImageUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = 64
type FieldOffset "descriptorBindingStorageTexelBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOffset "descriptorBindingStorageTexelBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = 76
type FieldOffset "descriptorBindingUniformBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOffset "descriptorBindingUniformBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = 56
type FieldOffset "descriptorBindingUniformTexelBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOffset "descriptorBindingUniformTexelBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = 72
type FieldOffset "descriptorBindingUpdateUnusedWhilePending" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOffset "descriptorBindingUpdateUnusedWhilePending" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = 80
type FieldOffset "descriptorBindingVariableDescriptorCount" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOffset "descriptorBindingVariableDescriptorCount" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = 88
type FieldOffset "pNext" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOffset "runtimeDescriptorArray" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOffset "sType" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOffset "shaderInputAttachmentArrayDynamicIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOffset "shaderInputAttachmentArrayDynamicIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = 16
type FieldOffset "shaderInputAttachmentArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOffset "shaderInputAttachmentArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = 44
type FieldOffset "shaderSampledImageArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOffset "shaderSampledImageArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = 32
type FieldOffset "shaderStorageBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOffset "shaderStorageBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = 36
type FieldOffset "shaderStorageImageArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOffset "shaderStorageImageArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = 40
type FieldOffset "shaderStorageTexelBufferArrayDynamicIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOffset "shaderStorageTexelBufferArrayDynamicIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = 24
type FieldOffset "shaderStorageTexelBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOffset "shaderStorageTexelBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = 52
type FieldOffset "shaderUniformBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOffset "shaderUniformBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = 28
type FieldOffset "shaderUniformTexelBufferArrayDynamicIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOffset "shaderUniformTexelBufferArrayDynamicIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = 20
type FieldOffset "shaderUniformTexelBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldOffset "shaderUniformTexelBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = 48
type FieldIsArray "descriptorBindingPartiallyBound" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldIsArray "descriptorBindingPartiallyBound" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = False
type FieldIsArray "descriptorBindingSampledImageUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldIsArray "descriptorBindingSampledImageUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = False
type FieldIsArray "descriptorBindingStorageBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldIsArray "descriptorBindingStorageBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = False
type FieldIsArray "descriptorBindingStorageImageUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldIsArray "descriptorBindingStorageImageUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = False
type FieldIsArray "descriptorBindingStorageTexelBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldIsArray "descriptorBindingStorageTexelBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = False
type FieldIsArray "descriptorBindingUniformBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldIsArray "descriptorBindingUniformBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = False
type FieldIsArray "descriptorBindingUniformTexelBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldIsArray "descriptorBindingUniformTexelBufferUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = False
type FieldIsArray "descriptorBindingUpdateUnusedWhilePending" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldIsArray "descriptorBindingUpdateUnusedWhilePending" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = False
type FieldIsArray "descriptorBindingVariableDescriptorCount" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldIsArray "descriptorBindingVariableDescriptorCount" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = False
type FieldIsArray "pNext" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldIsArray "runtimeDescriptorArray" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldIsArray "sType" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldIsArray "shaderInputAttachmentArrayDynamicIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldIsArray "shaderInputAttachmentArrayDynamicIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = False
type FieldIsArray "shaderInputAttachmentArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldIsArray "shaderInputAttachmentArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = False
type FieldIsArray "shaderSampledImageArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldIsArray "shaderSampledImageArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = False
type FieldIsArray "shaderStorageBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldIsArray "shaderStorageBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = False
type FieldIsArray "shaderStorageImageArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldIsArray "shaderStorageImageArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = False
type FieldIsArray "shaderStorageTexelBufferArrayDynamicIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldIsArray "shaderStorageTexelBufferArrayDynamicIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = False
type FieldIsArray "shaderStorageTexelBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldIsArray "shaderStorageTexelBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = False
type FieldIsArray "shaderUniformBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldIsArray "shaderUniformBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = False
type FieldIsArray "shaderUniformTexelBufferArrayDynamicIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldIsArray "shaderUniformTexelBufferArrayDynamicIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = False
type FieldIsArray "shaderUniformTexelBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT Source # 
type FieldIsArray "shaderUniformTexelBufferArrayNonUniformIndexing" VkPhysicalDeviceDescriptorIndexingFeaturesEXT = False

data VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source #

typedef struct VkPhysicalDeviceDescriptorIndexingPropertiesEXT {
    VkStructureType sType;
    void*                            pNext;
    uint32_t               maxUpdateAfterBindDescriptorsInAllPools;
    VkBool32               shaderUniformBufferArrayNonUniformIndexingNative;
    VkBool32               shaderSampledImageArrayNonUniformIndexingNative;
    VkBool32               shaderStorageBufferArrayNonUniformIndexingNative;
    VkBool32               shaderStorageImageArrayNonUniformIndexingNative;
    VkBool32               shaderInputAttachmentArrayNonUniformIndexingNative;
    VkBool32               robustBufferAccessUpdateAfterBind;
    VkBool32               quadDivergentImplicitLod;
    uint32_t               maxPerStageDescriptorUpdateAfterBindSamplers;
    uint32_t               maxPerStageDescriptorUpdateAfterBindUniformBuffers;
    uint32_t               maxPerStageDescriptorUpdateAfterBindStorageBuffers;
    uint32_t               maxPerStageDescriptorUpdateAfterBindSampledImages;
    uint32_t               maxPerStageDescriptorUpdateAfterBindStorageImages;
    uint32_t               maxPerStageDescriptorUpdateAfterBindInputAttachments;
    uint32_t               maxPerStageUpdateAfterBindResources;
    uint32_t               maxDescriptorSetUpdateAfterBindSamplers;
    uint32_t               maxDescriptorSetUpdateAfterBindUniformBuffers;
    uint32_t               maxDescriptorSetUpdateAfterBindUniformBuffersDynamic;
    uint32_t               maxDescriptorSetUpdateAfterBindStorageBuffers;
    uint32_t               maxDescriptorSetUpdateAfterBindStorageBuffersDynamic;
    uint32_t               maxDescriptorSetUpdateAfterBindSampledImages;
    uint32_t               maxDescriptorSetUpdateAfterBindStorageImages;
    uint32_t               maxDescriptorSetUpdateAfterBindInputAttachments;
} VkPhysicalDeviceDescriptorIndexingPropertiesEXT;

VkPhysicalDeviceDescriptorIndexingPropertiesEXT registry at www.khronos.org

Instances

Eq VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
Ord VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
Show VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
Storable VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
VulkanMarshalPrim VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
VulkanMarshal VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanWriteField "maxDescriptorSetUpdateAfterBindInputAttachments" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanWriteField "maxDescriptorSetUpdateAfterBindSampledImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanWriteField "maxDescriptorSetUpdateAfterBindSamplers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanWriteField "maxDescriptorSetUpdateAfterBindStorageBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanWriteField "maxDescriptorSetUpdateAfterBindStorageBuffersDynamic" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanWriteField "maxDescriptorSetUpdateAfterBindStorageImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanWriteField "maxDescriptorSetUpdateAfterBindUniformBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanWriteField "maxDescriptorSetUpdateAfterBindUniformBuffersDynamic" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanWriteField "maxPerStageDescriptorUpdateAfterBindInputAttachments" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanWriteField "maxPerStageDescriptorUpdateAfterBindSampledImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanWriteField "maxPerStageDescriptorUpdateAfterBindSamplers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanWriteField "maxPerStageDescriptorUpdateAfterBindStorageBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanWriteField "maxPerStageDescriptorUpdateAfterBindStorageImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanWriteField "maxPerStageDescriptorUpdateAfterBindUniformBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanWriteField "maxPerStageUpdateAfterBindResources" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanWriteField "maxUpdateAfterBindDescriptorsInAllPools" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanWriteField "pNext" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanWriteField "quadDivergentImplicitLod" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanWriteField "robustBufferAccessUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanWriteField "sType" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanWriteField "shaderInputAttachmentArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanWriteField "shaderSampledImageArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanWriteField "shaderStorageBufferArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanWriteField "shaderStorageImageArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanWriteField "shaderUniformBufferArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanReadField "maxDescriptorSetUpdateAfterBindInputAttachments" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanReadField "maxDescriptorSetUpdateAfterBindSampledImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanReadField "maxDescriptorSetUpdateAfterBindSamplers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanReadField "maxDescriptorSetUpdateAfterBindStorageBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanReadField "maxDescriptorSetUpdateAfterBindStorageBuffersDynamic" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanReadField "maxDescriptorSetUpdateAfterBindStorageImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanReadField "maxDescriptorSetUpdateAfterBindUniformBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanReadField "maxDescriptorSetUpdateAfterBindUniformBuffersDynamic" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanReadField "maxPerStageDescriptorUpdateAfterBindInputAttachments" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanReadField "maxPerStageDescriptorUpdateAfterBindSampledImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanReadField "maxPerStageDescriptorUpdateAfterBindSamplers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanReadField "maxPerStageDescriptorUpdateAfterBindStorageBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanReadField "maxPerStageDescriptorUpdateAfterBindStorageImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanReadField "maxPerStageDescriptorUpdateAfterBindUniformBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanReadField "maxPerStageUpdateAfterBindResources" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanReadField "maxUpdateAfterBindDescriptorsInAllPools" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanReadField "pNext" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanReadField "quadDivergentImplicitLod" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanReadField "robustBufferAccessUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanReadField "sType" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanReadField "shaderInputAttachmentArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanReadField "shaderSampledImageArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanReadField "shaderStorageBufferArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanReadField "shaderStorageImageArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
CanReadField "shaderUniformBufferArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
HasField "maxDescriptorSetUpdateAfterBindInputAttachments" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 

Associated Types

type FieldType ("maxDescriptorSetUpdateAfterBindInputAttachments" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Type Source #

type FieldOptional ("maxDescriptorSetUpdateAfterBindInputAttachments" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

type FieldOffset ("maxDescriptorSetUpdateAfterBindInputAttachments" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Nat Source #

type FieldIsArray ("maxDescriptorSetUpdateAfterBindInputAttachments" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

HasField "maxDescriptorSetUpdateAfterBindSampledImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 

Associated Types

type FieldType ("maxDescriptorSetUpdateAfterBindSampledImages" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Type Source #

type FieldOptional ("maxDescriptorSetUpdateAfterBindSampledImages" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

type FieldOffset ("maxDescriptorSetUpdateAfterBindSampledImages" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Nat Source #

type FieldIsArray ("maxDescriptorSetUpdateAfterBindSampledImages" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

HasField "maxDescriptorSetUpdateAfterBindSamplers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 

Associated Types

type FieldType ("maxDescriptorSetUpdateAfterBindSamplers" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Type Source #

type FieldOptional ("maxDescriptorSetUpdateAfterBindSamplers" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

type FieldOffset ("maxDescriptorSetUpdateAfterBindSamplers" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Nat Source #

type FieldIsArray ("maxDescriptorSetUpdateAfterBindSamplers" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

HasField "maxDescriptorSetUpdateAfterBindStorageBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 

Associated Types

type FieldType ("maxDescriptorSetUpdateAfterBindStorageBuffers" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Type Source #

type FieldOptional ("maxDescriptorSetUpdateAfterBindStorageBuffers" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

type FieldOffset ("maxDescriptorSetUpdateAfterBindStorageBuffers" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Nat Source #

type FieldIsArray ("maxDescriptorSetUpdateAfterBindStorageBuffers" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

HasField "maxDescriptorSetUpdateAfterBindStorageBuffersDynamic" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 

Associated Types

type FieldType ("maxDescriptorSetUpdateAfterBindStorageBuffersDynamic" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Type Source #

type FieldOptional ("maxDescriptorSetUpdateAfterBindStorageBuffersDynamic" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

type FieldOffset ("maxDescriptorSetUpdateAfterBindStorageBuffersDynamic" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Nat Source #

type FieldIsArray ("maxDescriptorSetUpdateAfterBindStorageBuffersDynamic" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

HasField "maxDescriptorSetUpdateAfterBindStorageImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 

Associated Types

type FieldType ("maxDescriptorSetUpdateAfterBindStorageImages" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Type Source #

type FieldOptional ("maxDescriptorSetUpdateAfterBindStorageImages" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

type FieldOffset ("maxDescriptorSetUpdateAfterBindStorageImages" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Nat Source #

type FieldIsArray ("maxDescriptorSetUpdateAfterBindStorageImages" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

HasField "maxDescriptorSetUpdateAfterBindUniformBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 

Associated Types

type FieldType ("maxDescriptorSetUpdateAfterBindUniformBuffers" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Type Source #

type FieldOptional ("maxDescriptorSetUpdateAfterBindUniformBuffers" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

type FieldOffset ("maxDescriptorSetUpdateAfterBindUniformBuffers" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Nat Source #

type FieldIsArray ("maxDescriptorSetUpdateAfterBindUniformBuffers" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

HasField "maxDescriptorSetUpdateAfterBindUniformBuffersDynamic" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 

Associated Types

type FieldType ("maxDescriptorSetUpdateAfterBindUniformBuffersDynamic" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Type Source #

type FieldOptional ("maxDescriptorSetUpdateAfterBindUniformBuffersDynamic" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

type FieldOffset ("maxDescriptorSetUpdateAfterBindUniformBuffersDynamic" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Nat Source #

type FieldIsArray ("maxDescriptorSetUpdateAfterBindUniformBuffersDynamic" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

HasField "maxPerStageDescriptorUpdateAfterBindInputAttachments" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 

Associated Types

type FieldType ("maxPerStageDescriptorUpdateAfterBindInputAttachments" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Type Source #

type FieldOptional ("maxPerStageDescriptorUpdateAfterBindInputAttachments" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

type FieldOffset ("maxPerStageDescriptorUpdateAfterBindInputAttachments" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Nat Source #

type FieldIsArray ("maxPerStageDescriptorUpdateAfterBindInputAttachments" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

HasField "maxPerStageDescriptorUpdateAfterBindSampledImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 

Associated Types

type FieldType ("maxPerStageDescriptorUpdateAfterBindSampledImages" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Type Source #

type FieldOptional ("maxPerStageDescriptorUpdateAfterBindSampledImages" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

type FieldOffset ("maxPerStageDescriptorUpdateAfterBindSampledImages" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Nat Source #

type FieldIsArray ("maxPerStageDescriptorUpdateAfterBindSampledImages" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

HasField "maxPerStageDescriptorUpdateAfterBindSamplers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 

Associated Types

type FieldType ("maxPerStageDescriptorUpdateAfterBindSamplers" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Type Source #

type FieldOptional ("maxPerStageDescriptorUpdateAfterBindSamplers" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

type FieldOffset ("maxPerStageDescriptorUpdateAfterBindSamplers" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Nat Source #

type FieldIsArray ("maxPerStageDescriptorUpdateAfterBindSamplers" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

HasField "maxPerStageDescriptorUpdateAfterBindStorageBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 

Associated Types

type FieldType ("maxPerStageDescriptorUpdateAfterBindStorageBuffers" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Type Source #

type FieldOptional ("maxPerStageDescriptorUpdateAfterBindStorageBuffers" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

type FieldOffset ("maxPerStageDescriptorUpdateAfterBindStorageBuffers" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Nat Source #

type FieldIsArray ("maxPerStageDescriptorUpdateAfterBindStorageBuffers" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

HasField "maxPerStageDescriptorUpdateAfterBindStorageImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 

Associated Types

type FieldType ("maxPerStageDescriptorUpdateAfterBindStorageImages" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Type Source #

type FieldOptional ("maxPerStageDescriptorUpdateAfterBindStorageImages" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

type FieldOffset ("maxPerStageDescriptorUpdateAfterBindStorageImages" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Nat Source #

type FieldIsArray ("maxPerStageDescriptorUpdateAfterBindStorageImages" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

HasField "maxPerStageDescriptorUpdateAfterBindUniformBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 

Associated Types

type FieldType ("maxPerStageDescriptorUpdateAfterBindUniformBuffers" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Type Source #

type FieldOptional ("maxPerStageDescriptorUpdateAfterBindUniformBuffers" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

type FieldOffset ("maxPerStageDescriptorUpdateAfterBindUniformBuffers" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Nat Source #

type FieldIsArray ("maxPerStageDescriptorUpdateAfterBindUniformBuffers" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

HasField "maxPerStageUpdateAfterBindResources" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 

Associated Types

type FieldType ("maxPerStageUpdateAfterBindResources" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Type Source #

type FieldOptional ("maxPerStageUpdateAfterBindResources" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

type FieldOffset ("maxPerStageUpdateAfterBindResources" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Nat Source #

type FieldIsArray ("maxPerStageUpdateAfterBindResources" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

HasField "maxUpdateAfterBindDescriptorsInAllPools" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 

Associated Types

type FieldType ("maxUpdateAfterBindDescriptorsInAllPools" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Type Source #

type FieldOptional ("maxUpdateAfterBindDescriptorsInAllPools" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

type FieldOffset ("maxUpdateAfterBindDescriptorsInAllPools" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Nat Source #

type FieldIsArray ("maxUpdateAfterBindDescriptorsInAllPools" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

HasField "pNext" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
HasField "quadDivergentImplicitLod" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
HasField "robustBufferAccessUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 

Associated Types

type FieldType ("robustBufferAccessUpdateAfterBind" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Type Source #

type FieldOptional ("robustBufferAccessUpdateAfterBind" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

type FieldOffset ("robustBufferAccessUpdateAfterBind" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Nat Source #

type FieldIsArray ("robustBufferAccessUpdateAfterBind" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

HasField "sType" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
HasField "shaderInputAttachmentArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 

Associated Types

type FieldType ("shaderInputAttachmentArrayNonUniformIndexingNative" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Type Source #

type FieldOptional ("shaderInputAttachmentArrayNonUniformIndexingNative" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

type FieldOffset ("shaderInputAttachmentArrayNonUniformIndexingNative" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Nat Source #

type FieldIsArray ("shaderInputAttachmentArrayNonUniformIndexingNative" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

HasField "shaderSampledImageArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 

Associated Types

type FieldType ("shaderSampledImageArrayNonUniformIndexingNative" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Type Source #

type FieldOptional ("shaderSampledImageArrayNonUniformIndexingNative" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

type FieldOffset ("shaderSampledImageArrayNonUniformIndexingNative" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Nat Source #

type FieldIsArray ("shaderSampledImageArrayNonUniformIndexingNative" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

HasField "shaderStorageBufferArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 

Associated Types

type FieldType ("shaderStorageBufferArrayNonUniformIndexingNative" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Type Source #

type FieldOptional ("shaderStorageBufferArrayNonUniformIndexingNative" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

type FieldOffset ("shaderStorageBufferArrayNonUniformIndexingNative" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Nat Source #

type FieldIsArray ("shaderStorageBufferArrayNonUniformIndexingNative" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

HasField "shaderStorageImageArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 

Associated Types

type FieldType ("shaderStorageImageArrayNonUniformIndexingNative" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Type Source #

type FieldOptional ("shaderStorageImageArrayNonUniformIndexingNative" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

type FieldOffset ("shaderStorageImageArrayNonUniformIndexingNative" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Nat Source #

type FieldIsArray ("shaderStorageImageArrayNonUniformIndexingNative" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

HasField "shaderUniformBufferArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 

Associated Types

type FieldType ("shaderUniformBufferArrayNonUniformIndexingNative" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Type Source #

type FieldOptional ("shaderUniformBufferArrayNonUniformIndexingNative" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

type FieldOffset ("shaderUniformBufferArrayNonUniformIndexingNative" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Nat Source #

type FieldIsArray ("shaderUniformBufferArrayNonUniformIndexingNative" :: Symbol) VkPhysicalDeviceDescriptorIndexingPropertiesEXT :: Bool Source #

type StructFields VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type StructFields VkPhysicalDeviceDescriptorIndexingPropertiesEXT = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "maxUpdateAfterBindDescriptorsInAllPools" ((:) Symbol "shaderUniformBufferArrayNonUniformIndexingNative" ((:) Symbol "shaderSampledImageArrayNonUniformIndexingNative" ((:) Symbol "shaderStorageBufferArrayNonUniformIndexingNative" ((:) Symbol "shaderStorageImageArrayNonUniformIndexingNative" ((:) Symbol "shaderInputAttachmentArrayNonUniformIndexingNative" ((:) Symbol "robustBufferAccessUpdateAfterBind" ((:) Symbol "quadDivergentImplicitLod" ((:) Symbol "maxPerStageDescriptorUpdateAfterBindSamplers" ((:) Symbol "maxPerStageDescriptorUpdateAfterBindUniformBuffers" ((:) Symbol "maxPerStageDescriptorUpdateAfterBindStorageBuffers" ((:) Symbol "maxPerStageDescriptorUpdateAfterBindSampledImages" ((:) Symbol "maxPerStageDescriptorUpdateAfterBindStorageImages" ((:) Symbol "maxPerStageDescriptorUpdateAfterBindInputAttachments" ((:) Symbol "maxPerStageUpdateAfterBindResources" ((:) Symbol "maxDescriptorSetUpdateAfterBindSamplers" ((:) Symbol "maxDescriptorSetUpdateAfterBindUniformBuffers" ((:) Symbol "maxDescriptorSetUpdateAfterBindUniformBuffersDynamic" ((:) Symbol "maxDescriptorSetUpdateAfterBindStorageBuffers" ((:) Symbol "maxDescriptorSetUpdateAfterBindStorageBuffersDynamic" ((:) Symbol "maxDescriptorSetUpdateAfterBindSampledImages" ((:) Symbol "maxDescriptorSetUpdateAfterBindStorageImages" ((:) Symbol "maxDescriptorSetUpdateAfterBindInputAttachments" ([] Symbol)))))))))))))))))))))))))
type CUnionType VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type ReturnedOnly VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type StructExtends VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldType "maxDescriptorSetUpdateAfterBindInputAttachments" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldType "maxDescriptorSetUpdateAfterBindInputAttachments" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = Word32
type FieldType "maxDescriptorSetUpdateAfterBindSampledImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldType "maxDescriptorSetUpdateAfterBindSampledImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = Word32
type FieldType "maxDescriptorSetUpdateAfterBindSamplers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldType "maxDescriptorSetUpdateAfterBindSamplers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = Word32
type FieldType "maxDescriptorSetUpdateAfterBindStorageBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldType "maxDescriptorSetUpdateAfterBindStorageBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = Word32
type FieldType "maxDescriptorSetUpdateAfterBindStorageBuffersDynamic" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldType "maxDescriptorSetUpdateAfterBindStorageBuffersDynamic" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = Word32
type FieldType "maxDescriptorSetUpdateAfterBindStorageImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldType "maxDescriptorSetUpdateAfterBindStorageImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = Word32
type FieldType "maxDescriptorSetUpdateAfterBindUniformBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldType "maxDescriptorSetUpdateAfterBindUniformBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = Word32
type FieldType "maxDescriptorSetUpdateAfterBindUniformBuffersDynamic" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldType "maxDescriptorSetUpdateAfterBindUniformBuffersDynamic" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = Word32
type FieldType "maxPerStageDescriptorUpdateAfterBindInputAttachments" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldType "maxPerStageDescriptorUpdateAfterBindInputAttachments" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = Word32
type FieldType "maxPerStageDescriptorUpdateAfterBindSampledImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldType "maxPerStageDescriptorUpdateAfterBindSampledImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = Word32
type FieldType "maxPerStageDescriptorUpdateAfterBindSamplers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldType "maxPerStageDescriptorUpdateAfterBindSamplers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = Word32
type FieldType "maxPerStageDescriptorUpdateAfterBindStorageBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldType "maxPerStageDescriptorUpdateAfterBindStorageBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = Word32
type FieldType "maxPerStageDescriptorUpdateAfterBindStorageImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldType "maxPerStageDescriptorUpdateAfterBindStorageImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = Word32
type FieldType "maxPerStageDescriptorUpdateAfterBindUniformBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldType "maxPerStageDescriptorUpdateAfterBindUniformBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = Word32
type FieldType "maxPerStageUpdateAfterBindResources" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldType "maxPerStageUpdateAfterBindResources" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = Word32
type FieldType "maxUpdateAfterBindDescriptorsInAllPools" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldType "maxUpdateAfterBindDescriptorsInAllPools" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = Word32
type FieldType "pNext" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldType "quadDivergentImplicitLod" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldType "robustBufferAccessUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldType "robustBufferAccessUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = VkBool32
type FieldType "sType" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldType "shaderInputAttachmentArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldType "shaderInputAttachmentArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = VkBool32
type FieldType "shaderSampledImageArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldType "shaderSampledImageArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = VkBool32
type FieldType "shaderStorageBufferArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldType "shaderStorageBufferArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = VkBool32
type FieldType "shaderStorageImageArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldType "shaderStorageImageArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = VkBool32
type FieldType "shaderUniformBufferArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldType "shaderUniformBufferArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = VkBool32
type FieldOptional "maxDescriptorSetUpdateAfterBindInputAttachments" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOptional "maxDescriptorSetUpdateAfterBindInputAttachments" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldOptional "maxDescriptorSetUpdateAfterBindSampledImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOptional "maxDescriptorSetUpdateAfterBindSampledImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldOptional "maxDescriptorSetUpdateAfterBindSamplers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOptional "maxDescriptorSetUpdateAfterBindSamplers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldOptional "maxDescriptorSetUpdateAfterBindStorageBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOptional "maxDescriptorSetUpdateAfterBindStorageBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldOptional "maxDescriptorSetUpdateAfterBindStorageBuffersDynamic" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOptional "maxDescriptorSetUpdateAfterBindStorageBuffersDynamic" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldOptional "maxDescriptorSetUpdateAfterBindStorageImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOptional "maxDescriptorSetUpdateAfterBindStorageImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldOptional "maxDescriptorSetUpdateAfterBindUniformBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOptional "maxDescriptorSetUpdateAfterBindUniformBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldOptional "maxDescriptorSetUpdateAfterBindUniformBuffersDynamic" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOptional "maxDescriptorSetUpdateAfterBindUniformBuffersDynamic" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldOptional "maxPerStageDescriptorUpdateAfterBindInputAttachments" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOptional "maxPerStageDescriptorUpdateAfterBindInputAttachments" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldOptional "maxPerStageDescriptorUpdateAfterBindSampledImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOptional "maxPerStageDescriptorUpdateAfterBindSampledImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldOptional "maxPerStageDescriptorUpdateAfterBindSamplers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOptional "maxPerStageDescriptorUpdateAfterBindSamplers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldOptional "maxPerStageDescriptorUpdateAfterBindStorageBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOptional "maxPerStageDescriptorUpdateAfterBindStorageBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldOptional "maxPerStageDescriptorUpdateAfterBindStorageImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOptional "maxPerStageDescriptorUpdateAfterBindStorageImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldOptional "maxPerStageDescriptorUpdateAfterBindUniformBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOptional "maxPerStageDescriptorUpdateAfterBindUniformBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldOptional "maxPerStageUpdateAfterBindResources" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOptional "maxPerStageUpdateAfterBindResources" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldOptional "maxUpdateAfterBindDescriptorsInAllPools" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOptional "maxUpdateAfterBindDescriptorsInAllPools" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldOptional "pNext" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOptional "quadDivergentImplicitLod" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOptional "robustBufferAccessUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOptional "robustBufferAccessUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldOptional "sType" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOptional "shaderInputAttachmentArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOptional "shaderInputAttachmentArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldOptional "shaderSampledImageArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOptional "shaderSampledImageArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldOptional "shaderStorageBufferArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOptional "shaderStorageBufferArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldOptional "shaderStorageImageArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOptional "shaderStorageImageArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldOptional "shaderUniformBufferArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOptional "shaderUniformBufferArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldOffset "maxDescriptorSetUpdateAfterBindInputAttachments" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOffset "maxDescriptorSetUpdateAfterBindInputAttachments" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = 104
type FieldOffset "maxDescriptorSetUpdateAfterBindSampledImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOffset "maxDescriptorSetUpdateAfterBindSampledImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = 96
type FieldOffset "maxDescriptorSetUpdateAfterBindSamplers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOffset "maxDescriptorSetUpdateAfterBindSamplers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = 76
type FieldOffset "maxDescriptorSetUpdateAfterBindStorageBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOffset "maxDescriptorSetUpdateAfterBindStorageBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = 88
type FieldOffset "maxDescriptorSetUpdateAfterBindStorageBuffersDynamic" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOffset "maxDescriptorSetUpdateAfterBindStorageBuffersDynamic" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = 92
type FieldOffset "maxDescriptorSetUpdateAfterBindStorageImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOffset "maxDescriptorSetUpdateAfterBindStorageImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = 100
type FieldOffset "maxDescriptorSetUpdateAfterBindUniformBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOffset "maxDescriptorSetUpdateAfterBindUniformBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = 80
type FieldOffset "maxDescriptorSetUpdateAfterBindUniformBuffersDynamic" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOffset "maxDescriptorSetUpdateAfterBindUniformBuffersDynamic" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = 84
type FieldOffset "maxPerStageDescriptorUpdateAfterBindInputAttachments" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOffset "maxPerStageDescriptorUpdateAfterBindInputAttachments" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = 68
type FieldOffset "maxPerStageDescriptorUpdateAfterBindSampledImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOffset "maxPerStageDescriptorUpdateAfterBindSampledImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = 60
type FieldOffset "maxPerStageDescriptorUpdateAfterBindSamplers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOffset "maxPerStageDescriptorUpdateAfterBindSamplers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = 48
type FieldOffset "maxPerStageDescriptorUpdateAfterBindStorageBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOffset "maxPerStageDescriptorUpdateAfterBindStorageBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = 56
type FieldOffset "maxPerStageDescriptorUpdateAfterBindStorageImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOffset "maxPerStageDescriptorUpdateAfterBindStorageImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = 64
type FieldOffset "maxPerStageDescriptorUpdateAfterBindUniformBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOffset "maxPerStageDescriptorUpdateAfterBindUniformBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = 52
type FieldOffset "maxPerStageUpdateAfterBindResources" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOffset "maxPerStageUpdateAfterBindResources" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = 72
type FieldOffset "maxUpdateAfterBindDescriptorsInAllPools" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOffset "maxUpdateAfterBindDescriptorsInAllPools" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = 16
type FieldOffset "pNext" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOffset "quadDivergentImplicitLod" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOffset "robustBufferAccessUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOffset "robustBufferAccessUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = 40
type FieldOffset "sType" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOffset "shaderInputAttachmentArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOffset "shaderInputAttachmentArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = 36
type FieldOffset "shaderSampledImageArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOffset "shaderSampledImageArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = 24
type FieldOffset "shaderStorageBufferArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOffset "shaderStorageBufferArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = 28
type FieldOffset "shaderStorageImageArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOffset "shaderStorageImageArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = 32
type FieldOffset "shaderUniformBufferArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldOffset "shaderUniformBufferArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = 20
type FieldIsArray "maxDescriptorSetUpdateAfterBindInputAttachments" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldIsArray "maxDescriptorSetUpdateAfterBindInputAttachments" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldIsArray "maxDescriptorSetUpdateAfterBindSampledImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldIsArray "maxDescriptorSetUpdateAfterBindSampledImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldIsArray "maxDescriptorSetUpdateAfterBindSamplers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldIsArray "maxDescriptorSetUpdateAfterBindSamplers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldIsArray "maxDescriptorSetUpdateAfterBindStorageBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldIsArray "maxDescriptorSetUpdateAfterBindStorageBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldIsArray "maxDescriptorSetUpdateAfterBindStorageBuffersDynamic" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldIsArray "maxDescriptorSetUpdateAfterBindStorageBuffersDynamic" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldIsArray "maxDescriptorSetUpdateAfterBindStorageImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldIsArray "maxDescriptorSetUpdateAfterBindStorageImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldIsArray "maxDescriptorSetUpdateAfterBindUniformBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldIsArray "maxDescriptorSetUpdateAfterBindUniformBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldIsArray "maxDescriptorSetUpdateAfterBindUniformBuffersDynamic" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldIsArray "maxDescriptorSetUpdateAfterBindUniformBuffersDynamic" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldIsArray "maxPerStageDescriptorUpdateAfterBindInputAttachments" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldIsArray "maxPerStageDescriptorUpdateAfterBindInputAttachments" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldIsArray "maxPerStageDescriptorUpdateAfterBindSampledImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldIsArray "maxPerStageDescriptorUpdateAfterBindSampledImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldIsArray "maxPerStageDescriptorUpdateAfterBindSamplers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldIsArray "maxPerStageDescriptorUpdateAfterBindSamplers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldIsArray "maxPerStageDescriptorUpdateAfterBindStorageBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldIsArray "maxPerStageDescriptorUpdateAfterBindStorageBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldIsArray "maxPerStageDescriptorUpdateAfterBindStorageImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldIsArray "maxPerStageDescriptorUpdateAfterBindStorageImages" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldIsArray "maxPerStageDescriptorUpdateAfterBindUniformBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldIsArray "maxPerStageDescriptorUpdateAfterBindUniformBuffers" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldIsArray "maxPerStageUpdateAfterBindResources" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldIsArray "maxPerStageUpdateAfterBindResources" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldIsArray "maxUpdateAfterBindDescriptorsInAllPools" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldIsArray "maxUpdateAfterBindDescriptorsInAllPools" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldIsArray "pNext" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldIsArray "quadDivergentImplicitLod" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldIsArray "robustBufferAccessUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldIsArray "robustBufferAccessUpdateAfterBind" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldIsArray "sType" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldIsArray "shaderInputAttachmentArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldIsArray "shaderInputAttachmentArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldIsArray "shaderSampledImageArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldIsArray "shaderSampledImageArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldIsArray "shaderStorageBufferArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldIsArray "shaderStorageBufferArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldIsArray "shaderStorageImageArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldIsArray "shaderStorageImageArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False
type FieldIsArray "shaderUniformBufferArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT Source # 
type FieldIsArray "shaderUniformBufferArrayNonUniformIndexingNative" VkPhysicalDeviceDescriptorIndexingPropertiesEXT = False

data VkPhysicalDeviceDiscardRectanglePropertiesEXT Source #

typedef struct VkPhysicalDeviceDiscardRectanglePropertiesEXT {
    VkStructureType sType;
    void*                  pNext;
    uint32_t               maxDiscardRectangles;
} VkPhysicalDeviceDiscardRectanglePropertiesEXT;

VkPhysicalDeviceDiscardRectanglePropertiesEXT registry at www.khronos.org

Instances

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

data VkPhysicalDeviceExternalBufferInfo Source #

typedef struct VkPhysicalDeviceExternalBufferInfo {
    VkStructureType sType;
    const void*                      pNext;
    VkBufferCreateFlags flags;
    VkBufferUsageFlags               usage;
    VkExternalMemoryHandleTypeFlagBits handleType;
} VkPhysicalDeviceExternalBufferInfo;

VkPhysicalDeviceExternalBufferInfo registry at www.khronos.org

Instances

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

data VkPhysicalDeviceExternalFenceInfo Source #

typedef struct VkPhysicalDeviceExternalFenceInfo {
    VkStructureType sType;
    const void*                      pNext;
    VkExternalFenceHandleTypeFlagBits handleType;
} VkPhysicalDeviceExternalFenceInfo;

VkPhysicalDeviceExternalFenceInfo registry at www.khronos.org

Instances

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

data VkPhysicalDeviceExternalImageFormatInfo Source #

typedef struct VkPhysicalDeviceExternalImageFormatInfo {
    VkStructureType sType;
    const void*                      pNext;
    VkExternalMemoryHandleTypeFlagBits handleType;
} VkPhysicalDeviceExternalImageFormatInfo;

VkPhysicalDeviceExternalImageFormatInfo registry at www.khronos.org

Instances

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

data VkPhysicalDeviceExternalMemoryHostPropertiesEXT Source #

typedef struct VkPhysicalDeviceExternalMemoryHostPropertiesEXT {
    VkStructureType sType;
    void* pNext;
    VkDeviceSize minImportedHostPointerAlignment;
} VkPhysicalDeviceExternalMemoryHostPropertiesEXT;

VkPhysicalDeviceExternalMemoryHostPropertiesEXT registry at www.khronos.org

Instances

Eq VkPhysicalDeviceExternalMemoryHostPropertiesEXT Source # 
Ord VkPhysicalDeviceExternalMemoryHostPropertiesEXT Source # 
Show VkPhysicalDeviceExternalMemoryHostPropertiesEXT Source # 
Storable VkPhysicalDeviceExternalMemoryHostPropertiesEXT Source # 
VulkanMarshalPrim VkPhysicalDeviceExternalMemoryHostPropertiesEXT Source # 
VulkanMarshal VkPhysicalDeviceExternalMemoryHostPropertiesEXT Source # 
CanWriteField "minImportedHostPointerAlignment" VkPhysicalDeviceExternalMemoryHostPropertiesEXT Source # 
CanWriteField "pNext" VkPhysicalDeviceExternalMemoryHostPropertiesEXT Source # 
CanWriteField "sType" VkPhysicalDeviceExternalMemoryHostPropertiesEXT Source # 
CanReadField "minImportedHostPointerAlignment" VkPhysicalDeviceExternalMemoryHostPropertiesEXT Source # 
CanReadField "pNext" VkPhysicalDeviceExternalMemoryHostPropertiesEXT Source # 
CanReadField "sType" VkPhysicalDeviceExternalMemoryHostPropertiesEXT Source # 
HasField "minImportedHostPointerAlignment" VkPhysicalDeviceExternalMemoryHostPropertiesEXT Source # 

Associated Types

type FieldType ("minImportedHostPointerAlignment" :: Symbol) VkPhysicalDeviceExternalMemoryHostPropertiesEXT :: Type Source #

type FieldOptional ("minImportedHostPointerAlignment" :: Symbol) VkPhysicalDeviceExternalMemoryHostPropertiesEXT :: Bool Source #

type FieldOffset ("minImportedHostPointerAlignment" :: Symbol) VkPhysicalDeviceExternalMemoryHostPropertiesEXT :: Nat Source #

type FieldIsArray ("minImportedHostPointerAlignment" :: Symbol) VkPhysicalDeviceExternalMemoryHostPropertiesEXT :: Bool Source #

HasField "pNext" VkPhysicalDeviceExternalMemoryHostPropertiesEXT Source # 
HasField "sType" VkPhysicalDeviceExternalMemoryHostPropertiesEXT Source # 
type StructFields VkPhysicalDeviceExternalMemoryHostPropertiesEXT Source # 
type StructFields VkPhysicalDeviceExternalMemoryHostPropertiesEXT = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "minImportedHostPointerAlignment" ([] Symbol)))
type CUnionType VkPhysicalDeviceExternalMemoryHostPropertiesEXT Source # 
type ReturnedOnly VkPhysicalDeviceExternalMemoryHostPropertiesEXT Source # 
type StructExtends VkPhysicalDeviceExternalMemoryHostPropertiesEXT Source # 
type FieldType "minImportedHostPointerAlignment" VkPhysicalDeviceExternalMemoryHostPropertiesEXT Source # 
type FieldType "pNext" VkPhysicalDeviceExternalMemoryHostPropertiesEXT Source # 
type FieldType "sType" VkPhysicalDeviceExternalMemoryHostPropertiesEXT Source # 
type FieldOptional "minImportedHostPointerAlignment" VkPhysicalDeviceExternalMemoryHostPropertiesEXT Source # 
type FieldOptional "pNext" VkPhysicalDeviceExternalMemoryHostPropertiesEXT Source # 
type FieldOptional "sType" VkPhysicalDeviceExternalMemoryHostPropertiesEXT Source # 
type FieldOffset "minImportedHostPointerAlignment" VkPhysicalDeviceExternalMemoryHostPropertiesEXT Source # 
type FieldOffset "minImportedHostPointerAlignment" VkPhysicalDeviceExternalMemoryHostPropertiesEXT = 16
type FieldOffset "pNext" VkPhysicalDeviceExternalMemoryHostPropertiesEXT Source # 
type FieldOffset "sType" VkPhysicalDeviceExternalMemoryHostPropertiesEXT Source # 
type FieldIsArray "minImportedHostPointerAlignment" VkPhysicalDeviceExternalMemoryHostPropertiesEXT Source # 
type FieldIsArray "minImportedHostPointerAlignment" VkPhysicalDeviceExternalMemoryHostPropertiesEXT = False
type FieldIsArray "pNext" VkPhysicalDeviceExternalMemoryHostPropertiesEXT Source # 
type FieldIsArray "sType" VkPhysicalDeviceExternalMemoryHostPropertiesEXT Source # 

data VkPhysicalDeviceExternalSemaphoreInfo Source #

typedef struct VkPhysicalDeviceExternalSemaphoreInfo {
    VkStructureType sType;
    const void*                      pNext;
    VkExternalSemaphoreHandleTypeFlagBits handleType;
} VkPhysicalDeviceExternalSemaphoreInfo;

VkPhysicalDeviceExternalSemaphoreInfo registry at www.khronos.org

Instances

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

data VkPhysicalDeviceFeatures2 Source #

typedef struct VkPhysicalDeviceFeatures2 {
    VkStructureType sType;
    void*                            pNext;
    VkPhysicalDeviceFeatures         features;
} VkPhysicalDeviceFeatures2;

VkPhysicalDeviceFeatures2 registry at www.khronos.org

Instances

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

data VkPhysicalDeviceGroupProperties Source #

typedef struct VkPhysicalDeviceGroupProperties {
    VkStructureType sType;
    void*                            pNext;
    uint32_t                         physicalDeviceCount;
    VkPhysicalDevice                 physicalDevices[VK_MAX_DEVICE_GROUP_SIZE];
    VkBool32                         subsetAllocation;
} VkPhysicalDeviceGroupProperties;

VkPhysicalDeviceGroupProperties registry at www.khronos.org

Instances

Eq VkPhysicalDeviceGroupProperties Source # 
Ord VkPhysicalDeviceGroupProperties Source # 
Show VkPhysicalDeviceGroupProperties Source # 
Storable VkPhysicalDeviceGroupProperties Source # 
VulkanMarshalPrim VkPhysicalDeviceGroupProperties Source # 
VulkanMarshal VkPhysicalDeviceGroupProperties Source # 
CanWriteField "pNext" VkPhysicalDeviceGroupProperties Source # 
CanWriteField "physicalDeviceCount" VkPhysicalDeviceGroupProperties Source # 
CanWriteField "sType" VkPhysicalDeviceGroupProperties Source # 
CanWriteField "subsetAllocation" VkPhysicalDeviceGroupProperties Source # 
CanReadField "pNext" VkPhysicalDeviceGroupProperties Source # 
CanReadField "physicalDeviceCount" VkPhysicalDeviceGroupProperties Source # 
CanReadField "sType" VkPhysicalDeviceGroupProperties Source # 
CanReadField "subsetAllocation" VkPhysicalDeviceGroupProperties Source # 
HasField "pNext" VkPhysicalDeviceGroupProperties Source # 
HasField "physicalDeviceCount" VkPhysicalDeviceGroupProperties Source # 

Associated Types

type FieldType ("physicalDeviceCount" :: Symbol) VkPhysicalDeviceGroupProperties :: Type Source #

type FieldOptional ("physicalDeviceCount" :: Symbol) VkPhysicalDeviceGroupProperties :: Bool Source #

type FieldOffset ("physicalDeviceCount" :: Symbol) VkPhysicalDeviceGroupProperties :: Nat Source #

type FieldIsArray ("physicalDeviceCount" :: Symbol) VkPhysicalDeviceGroupProperties :: Bool Source #

HasField "physicalDevices" VkPhysicalDeviceGroupProperties Source # 
HasField "sType" VkPhysicalDeviceGroupProperties Source # 
HasField "subsetAllocation" VkPhysicalDeviceGroupProperties Source # 
(KnownNat idx, IndexInBounds "physicalDevices" idx VkPhysicalDeviceGroupProperties) => CanWriteFieldArray "physicalDevices" idx VkPhysicalDeviceGroupProperties Source # 
(KnownNat idx, IndexInBounds "physicalDevices" idx VkPhysicalDeviceGroupProperties) => CanReadFieldArray "physicalDevices" idx VkPhysicalDeviceGroupProperties Source # 
type StructFields VkPhysicalDeviceGroupProperties Source # 
type StructFields VkPhysicalDeviceGroupProperties = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "physicalDeviceCount" ((:) Symbol "physicalDevices" ((:) Symbol "subsetAllocation" ([] Symbol)))))
type CUnionType VkPhysicalDeviceGroupProperties Source # 
type ReturnedOnly VkPhysicalDeviceGroupProperties Source # 
type StructExtends VkPhysicalDeviceGroupProperties Source # 
type FieldArrayLength "physicalDevices" VkPhysicalDeviceGroupProperties Source # 
type FieldType "pNext" VkPhysicalDeviceGroupProperties Source # 
type FieldType "physicalDeviceCount" VkPhysicalDeviceGroupProperties Source # 
type FieldType "physicalDeviceCount" VkPhysicalDeviceGroupProperties = Word32
type FieldType "physicalDevices" VkPhysicalDeviceGroupProperties Source # 
type FieldType "sType" VkPhysicalDeviceGroupProperties Source # 
type FieldType "subsetAllocation" VkPhysicalDeviceGroupProperties Source # 
type FieldOptional "pNext" VkPhysicalDeviceGroupProperties Source # 
type FieldOptional "physicalDeviceCount" VkPhysicalDeviceGroupProperties Source # 
type FieldOptional "physicalDevices" VkPhysicalDeviceGroupProperties Source # 
type FieldOptional "sType" VkPhysicalDeviceGroupProperties Source # 
type FieldOptional "subsetAllocation" VkPhysicalDeviceGroupProperties Source # 
type FieldOffset "pNext" VkPhysicalDeviceGroupProperties Source # 
type FieldOffset "physicalDeviceCount" VkPhysicalDeviceGroupProperties Source # 
type FieldOffset "physicalDeviceCount" VkPhysicalDeviceGroupProperties = 16
type FieldOffset "physicalDevices" VkPhysicalDeviceGroupProperties Source # 
type FieldOffset "physicalDevices" VkPhysicalDeviceGroupProperties = 24
type FieldOffset "sType" VkPhysicalDeviceGroupProperties Source # 
type FieldOffset "subsetAllocation" VkPhysicalDeviceGroupProperties Source # 
type FieldOffset "subsetAllocation" VkPhysicalDeviceGroupProperties = 280
type FieldIsArray "pNext" VkPhysicalDeviceGroupProperties Source # 
type FieldIsArray "physicalDeviceCount" VkPhysicalDeviceGroupProperties Source # 
type FieldIsArray "physicalDevices" VkPhysicalDeviceGroupProperties Source # 
type FieldIsArray "sType" VkPhysicalDeviceGroupProperties Source # 
type FieldIsArray "subsetAllocation" VkPhysicalDeviceGroupProperties Source # 

data VkPhysicalDeviceIDProperties Source #

typedef struct VkPhysicalDeviceIDProperties {
    VkStructureType sType;
    void*                            pNext;
    uint8_t                          deviceUUID[VK_UUID_SIZE];
    uint8_t                          driverUUID[VK_UUID_SIZE];
    uint8_t                          deviceLUID[VK_LUID_SIZE];
    uint32_t                         deviceNodeMask;
    VkBool32                         deviceLUIDValid;
} VkPhysicalDeviceIDProperties;

VkPhysicalDeviceIDProperties registry at www.khronos.org

Instances

Eq VkPhysicalDeviceIDProperties Source # 
Ord VkPhysicalDeviceIDProperties Source # 
Show VkPhysicalDeviceIDProperties Source # 
Storable VkPhysicalDeviceIDProperties Source # 
VulkanMarshalPrim VkPhysicalDeviceIDProperties Source # 
VulkanMarshal VkPhysicalDeviceIDProperties Source # 
CanWriteField "deviceLUIDValid" VkPhysicalDeviceIDProperties Source # 
CanWriteField "deviceNodeMask" VkPhysicalDeviceIDProperties Source # 
CanWriteField "pNext" VkPhysicalDeviceIDProperties Source # 
CanWriteField "sType" VkPhysicalDeviceIDProperties Source # 
CanReadField "deviceLUIDValid" VkPhysicalDeviceIDProperties Source # 
CanReadField "deviceNodeMask" VkPhysicalDeviceIDProperties Source # 
CanReadField "pNext" VkPhysicalDeviceIDProperties Source # 
CanReadField "sType" VkPhysicalDeviceIDProperties Source # 
HasField "deviceLUID" VkPhysicalDeviceIDProperties Source # 
HasField "deviceLUIDValid" VkPhysicalDeviceIDProperties Source # 

Associated Types

type FieldType ("deviceLUIDValid" :: Symbol) VkPhysicalDeviceIDProperties :: Type Source #

type FieldOptional ("deviceLUIDValid" :: Symbol) VkPhysicalDeviceIDProperties :: Bool Source #

type FieldOffset ("deviceLUIDValid" :: Symbol) VkPhysicalDeviceIDProperties :: Nat Source #

type FieldIsArray ("deviceLUIDValid" :: Symbol) VkPhysicalDeviceIDProperties :: Bool Source #

HasField "deviceNodeMask" VkPhysicalDeviceIDProperties Source # 
HasField "deviceUUID" VkPhysicalDeviceIDProperties Source # 
HasField "driverUUID" VkPhysicalDeviceIDProperties Source # 
HasField "pNext" VkPhysicalDeviceIDProperties Source # 
HasField "sType" VkPhysicalDeviceIDProperties Source # 
(KnownNat idx, IndexInBounds "deviceLUID" idx VkPhysicalDeviceIDProperties) => CanWriteFieldArray "deviceLUID" idx VkPhysicalDeviceIDProperties Source # 
(KnownNat idx, IndexInBounds "deviceUUID" idx VkPhysicalDeviceIDProperties) => CanWriteFieldArray "deviceUUID" idx VkPhysicalDeviceIDProperties Source # 
(KnownNat idx, IndexInBounds "driverUUID" idx VkPhysicalDeviceIDProperties) => CanWriteFieldArray "driverUUID" idx VkPhysicalDeviceIDProperties Source # 
(KnownNat idx, IndexInBounds "deviceLUID" idx VkPhysicalDeviceIDProperties) => CanReadFieldArray "deviceLUID" idx VkPhysicalDeviceIDProperties Source # 
(KnownNat idx, IndexInBounds "deviceUUID" idx VkPhysicalDeviceIDProperties) => CanReadFieldArray "deviceUUID" idx VkPhysicalDeviceIDProperties Source # 
(KnownNat idx, IndexInBounds "driverUUID" idx VkPhysicalDeviceIDProperties) => CanReadFieldArray "driverUUID" idx VkPhysicalDeviceIDProperties Source # 
type StructFields VkPhysicalDeviceIDProperties Source # 
type StructFields VkPhysicalDeviceIDProperties = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "deviceUUID" ((:) Symbol "driverUUID" ((:) Symbol "deviceLUID" ((:) Symbol "deviceNodeMask" ((:) Symbol "deviceLUIDValid" ([] Symbol)))))))
type CUnionType VkPhysicalDeviceIDProperties Source # 
type ReturnedOnly VkPhysicalDeviceIDProperties Source # 
type StructExtends VkPhysicalDeviceIDProperties Source # 
type FieldArrayLength "deviceLUID" VkPhysicalDeviceIDProperties Source # 
type FieldArrayLength "deviceUUID" VkPhysicalDeviceIDProperties Source # 
type FieldArrayLength "driverUUID" VkPhysicalDeviceIDProperties Source # 
type FieldType "deviceLUID" VkPhysicalDeviceIDProperties Source # 
type FieldType "deviceLUIDValid" VkPhysicalDeviceIDProperties Source # 
type FieldType "deviceNodeMask" VkPhysicalDeviceIDProperties Source # 
type FieldType "deviceUUID" VkPhysicalDeviceIDProperties Source # 
type FieldType "driverUUID" VkPhysicalDeviceIDProperties Source # 
type FieldType "pNext" VkPhysicalDeviceIDProperties Source # 
type FieldType "sType" VkPhysicalDeviceIDProperties Source # 
type FieldOptional "deviceLUID" VkPhysicalDeviceIDProperties Source # 
type FieldOptional "deviceLUIDValid" VkPhysicalDeviceIDProperties Source # 
type FieldOptional "deviceNodeMask" VkPhysicalDeviceIDProperties Source # 
type FieldOptional "deviceUUID" VkPhysicalDeviceIDProperties Source # 
type FieldOptional "driverUUID" VkPhysicalDeviceIDProperties Source # 
type FieldOptional "pNext" VkPhysicalDeviceIDProperties Source # 
type FieldOptional "sType" VkPhysicalDeviceIDProperties Source # 
type FieldOffset "deviceLUID" VkPhysicalDeviceIDProperties Source # 
type FieldOffset "deviceLUIDValid" VkPhysicalDeviceIDProperties Source # 
type FieldOffset "deviceLUIDValid" VkPhysicalDeviceIDProperties = 60
type FieldOffset "deviceNodeMask" VkPhysicalDeviceIDProperties Source # 
type FieldOffset "deviceNodeMask" VkPhysicalDeviceIDProperties = 56
type FieldOffset "deviceUUID" VkPhysicalDeviceIDProperties Source # 
type FieldOffset "driverUUID" VkPhysicalDeviceIDProperties Source # 
type FieldOffset "pNext" VkPhysicalDeviceIDProperties Source # 
type FieldOffset "sType" VkPhysicalDeviceIDProperties Source # 
type FieldIsArray "deviceLUID" VkPhysicalDeviceIDProperties Source # 
type FieldIsArray "deviceLUIDValid" VkPhysicalDeviceIDProperties Source # 
type FieldIsArray "deviceNodeMask" VkPhysicalDeviceIDProperties Source # 
type FieldIsArray "deviceUUID" VkPhysicalDeviceIDProperties Source # 
type FieldIsArray "driverUUID" VkPhysicalDeviceIDProperties Source # 
type FieldIsArray "pNext" VkPhysicalDeviceIDProperties Source # 
type FieldIsArray "sType" VkPhysicalDeviceIDProperties Source # 

data VkPhysicalDeviceImageFormatInfo2 Source #

typedef struct VkPhysicalDeviceImageFormatInfo2 {
    VkStructureType sType;
    const void* pNext;
    VkFormat                         format;
    VkImageType                      type;
    VkImageTiling                    tiling;
    VkImageUsageFlags                usage;
    VkImageCreateFlags flags;
} VkPhysicalDeviceImageFormatInfo2;

VkPhysicalDeviceImageFormatInfo2 registry at www.khronos.org

Instances

Eq VkPhysicalDeviceImageFormatInfo2 Source # 
Ord VkPhysicalDeviceImageFormatInfo2 Source # 
Show VkPhysicalDeviceImageFormatInfo2 Source # 
Storable VkPhysicalDeviceImageFormatInfo2 Source # 
VulkanMarshalPrim VkPhysicalDeviceImageFormatInfo2 Source # 
VulkanMarshal VkPhysicalDeviceImageFormatInfo2 Source # 
CanWriteField "flags" VkPhysicalDeviceImageFormatInfo2 Source # 
CanWriteField "format" VkPhysicalDeviceImageFormatInfo2 Source # 
CanWriteField "pNext" VkPhysicalDeviceImageFormatInfo2 Source # 
CanWriteField "sType" VkPhysicalDeviceImageFormatInfo2 Source # 
CanWriteField "tiling" VkPhysicalDeviceImageFormatInfo2 Source # 
CanWriteField "type" VkPhysicalDeviceImageFormatInfo2 Source # 
CanWriteField "usage" VkPhysicalDeviceImageFormatInfo2 Source # 
CanReadField "flags" VkPhysicalDeviceImageFormatInfo2 Source # 
CanReadField "format" VkPhysicalDeviceImageFormatInfo2 Source # 
CanReadField "pNext" VkPhysicalDeviceImageFormatInfo2 Source # 
CanReadField "sType" VkPhysicalDeviceImageFormatInfo2 Source # 
CanReadField "tiling" VkPhysicalDeviceImageFormatInfo2 Source # 
CanReadField "type" VkPhysicalDeviceImageFormatInfo2 Source # 
CanReadField "usage" VkPhysicalDeviceImageFormatInfo2 Source # 
HasField "flags" VkPhysicalDeviceImageFormatInfo2 Source # 
HasField "format" VkPhysicalDeviceImageFormatInfo2 Source # 
HasField "pNext" VkPhysicalDeviceImageFormatInfo2 Source # 
HasField "sType" VkPhysicalDeviceImageFormatInfo2 Source # 
HasField "tiling" VkPhysicalDeviceImageFormatInfo2 Source # 
HasField "type" VkPhysicalDeviceImageFormatInfo2 Source # 
HasField "usage" VkPhysicalDeviceImageFormatInfo2 Source # 
type StructFields VkPhysicalDeviceImageFormatInfo2 Source # 
type StructFields VkPhysicalDeviceImageFormatInfo2 = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "format" ((:) Symbol "type" ((:) Symbol "tiling" ((:) Symbol "usage" ((:) Symbol "flags" ([] Symbol)))))))
type CUnionType VkPhysicalDeviceImageFormatInfo2 Source # 
type ReturnedOnly VkPhysicalDeviceImageFormatInfo2 Source # 
type StructExtends VkPhysicalDeviceImageFormatInfo2 Source # 
type FieldType "flags" VkPhysicalDeviceImageFormatInfo2 Source # 
type FieldType "format" VkPhysicalDeviceImageFormatInfo2 Source # 
type FieldType "pNext" VkPhysicalDeviceImageFormatInfo2 Source # 
type FieldType "sType" VkPhysicalDeviceImageFormatInfo2 Source # 
type FieldType "tiling" VkPhysicalDeviceImageFormatInfo2 Source # 
type FieldType "type" VkPhysicalDeviceImageFormatInfo2 Source # 
type FieldType "usage" VkPhysicalDeviceImageFormatInfo2 Source # 
type FieldOptional "flags" VkPhysicalDeviceImageFormatInfo2 Source # 
type FieldOptional "format" VkPhysicalDeviceImageFormatInfo2 Source # 
type FieldOptional "pNext" VkPhysicalDeviceImageFormatInfo2 Source # 
type FieldOptional "sType" VkPhysicalDeviceImageFormatInfo2 Source # 
type FieldOptional "tiling" VkPhysicalDeviceImageFormatInfo2 Source # 
type FieldOptional "type" VkPhysicalDeviceImageFormatInfo2 Source # 
type FieldOptional "usage" VkPhysicalDeviceImageFormatInfo2 Source # 
type FieldOffset "flags" VkPhysicalDeviceImageFormatInfo2 Source # 
type FieldOffset "format" VkPhysicalDeviceImageFormatInfo2 Source # 
type FieldOffset "pNext" VkPhysicalDeviceImageFormatInfo2 Source # 
type FieldOffset "sType" VkPhysicalDeviceImageFormatInfo2 Source # 
type FieldOffset "tiling" VkPhysicalDeviceImageFormatInfo2 Source # 
type FieldOffset "type" VkPhysicalDeviceImageFormatInfo2 Source # 
type FieldOffset "usage" VkPhysicalDeviceImageFormatInfo2 Source # 
type FieldIsArray "flags" VkPhysicalDeviceImageFormatInfo2 Source # 
type FieldIsArray "format" VkPhysicalDeviceImageFormatInfo2 Source # 
type FieldIsArray "pNext" VkPhysicalDeviceImageFormatInfo2 Source # 
type FieldIsArray "sType" VkPhysicalDeviceImageFormatInfo2 Source # 
type FieldIsArray "tiling" VkPhysicalDeviceImageFormatInfo2 Source # 
type FieldIsArray "type" VkPhysicalDeviceImageFormatInfo2 Source # 
type FieldIsArray "usage" VkPhysicalDeviceImageFormatInfo2 Source # 

data VkPhysicalDeviceLimits Source #

typedef struct VkPhysicalDeviceLimits {
    uint32_t               maxImageDimension1D;
    uint32_t               maxImageDimension2D;
    uint32_t               maxImageDimension3D;
    uint32_t               maxImageDimensionCube;
    uint32_t               maxImageArrayLayers;
    uint32_t               maxTexelBufferElements;
    uint32_t               maxUniformBufferRange;
    uint32_t               maxStorageBufferRange;
    uint32_t               maxPushConstantsSize;
    uint32_t               maxMemoryAllocationCount;
    uint32_t               maxSamplerAllocationCount;
    VkDeviceSize           bufferImageGranularity;
    VkDeviceSize           sparseAddressSpaceSize;
    uint32_t               maxBoundDescriptorSets;
    uint32_t               maxPerStageDescriptorSamplers;
    uint32_t               maxPerStageDescriptorUniformBuffers;
    uint32_t               maxPerStageDescriptorStorageBuffers;
    uint32_t               maxPerStageDescriptorSampledImages;
    uint32_t               maxPerStageDescriptorStorageImages;
    uint32_t               maxPerStageDescriptorInputAttachments;
    uint32_t               maxPerStageResources;
    uint32_t               maxDescriptorSetSamplers;
    uint32_t               maxDescriptorSetUniformBuffers;
    uint32_t               maxDescriptorSetUniformBuffersDynamic;
    uint32_t               maxDescriptorSetStorageBuffers;
    uint32_t               maxDescriptorSetStorageBuffersDynamic;
    uint32_t               maxDescriptorSetSampledImages;
    uint32_t               maxDescriptorSetStorageImages;
    uint32_t               maxDescriptorSetInputAttachments;
    uint32_t               maxVertexInputAttributes;
    uint32_t               maxVertexInputBindings;
    uint32_t               maxVertexInputAttributeOffset;
    uint32_t               maxVertexInputBindingStride;
    uint32_t               maxVertexOutputComponents;
    uint32_t               maxTessellationGenerationLevel;
    uint32_t               maxTessellationPatchSize;
    uint32_t               maxTessellationControlPerVertexInputComponents;
    uint32_t               maxTessellationControlPerVertexOutputComponents;
    uint32_t               maxTessellationControlPerPatchOutputComponents;
    uint32_t               maxTessellationControlTotalOutputComponents;
    uint32_t               maxTessellationEvaluationInputComponents;
    uint32_t               maxTessellationEvaluationOutputComponents;
    uint32_t               maxGeometryShaderInvocations;
    uint32_t               maxGeometryInputComponents;
    uint32_t               maxGeometryOutputComponents;
    uint32_t               maxGeometryOutputVertices;
    uint32_t               maxGeometryTotalOutputComponents;
    uint32_t               maxFragmentInputComponents;
    uint32_t               maxFragmentOutputAttachments;
    uint32_t               maxFragmentDualSrcAttachments;
    uint32_t               maxFragmentCombinedOutputResources;
    uint32_t               maxComputeSharedMemorySize;
    uint32_t               maxComputeWorkGroupCount[3];
    uint32_t               maxComputeWorkGroupInvocations;
    uint32_t               maxComputeWorkGroupSize[3];
    uint32_t               subPixelPrecisionBits;
    uint32_t               subTexelPrecisionBits;
    uint32_t               mipmapPrecisionBits;
    uint32_t               maxDrawIndexedIndexValue;
    uint32_t               maxDrawIndirectCount;
    float                  maxSamplerLodBias;
    float                  maxSamplerAnisotropy;
    uint32_t               maxViewports;
    uint32_t               maxViewportDimensions[2];
    float                  viewportBoundsRange[2];
    uint32_t               viewportSubPixelBits;
    size_t                 minMemoryMapAlignment;
    VkDeviceSize           minTexelBufferOffsetAlignment;
    VkDeviceSize           minUniformBufferOffsetAlignment;
    VkDeviceSize           minStorageBufferOffsetAlignment;
    int32_t                minTexelOffset;
    uint32_t               maxTexelOffset;
    int32_t                minTexelGatherOffset;
    uint32_t               maxTexelGatherOffset;
    float                  minInterpolationOffset;
    float                  maxInterpolationOffset;
    uint32_t               subPixelInterpolationOffsetBits;
    uint32_t               maxFramebufferWidth;
    uint32_t               maxFramebufferHeight;
    uint32_t               maxFramebufferLayers;
    VkSampleCountFlags     framebufferColorSampleCounts;
    VkSampleCountFlags     framebufferDepthSampleCounts;
    VkSampleCountFlags     framebufferStencilSampleCounts;
    VkSampleCountFlags     framebufferNoAttachmentsSampleCounts;
    uint32_t               maxColorAttachments;
    VkSampleCountFlags     sampledImageColorSampleCounts;
    VkSampleCountFlags     sampledImageIntegerSampleCounts;
    VkSampleCountFlags     sampledImageDepthSampleCounts;
    VkSampleCountFlags     sampledImageStencilSampleCounts;
    VkSampleCountFlags     storageImageSampleCounts;
    uint32_t               maxSampleMaskWords;
    VkBool32               timestampComputeAndGraphics;
    float                  timestampPeriod;
    uint32_t               maxClipDistances;
    uint32_t               maxCullDistances;
    uint32_t               maxCombinedClipAndCullDistances;
    uint32_t               discreteQueuePriorities;
    float                  pointSizeRange[2];
    float                  lineWidthRange[2];
    float                  pointSizeGranularity;
    float                  lineWidthGranularity;
    VkBool32               strictLines;
    VkBool32               standardSampleLocations;
    VkDeviceSize           optimalBufferCopyOffsetAlignment;
    VkDeviceSize           optimalBufferCopyRowPitchAlignment;
    VkDeviceSize           nonCoherentAtomSize;
} VkPhysicalDeviceLimits;

VkPhysicalDeviceLimits registry at www.khronos.org

Instances

Eq VkPhysicalDeviceLimits Source # 
Ord VkPhysicalDeviceLimits Source # 
Show VkPhysicalDeviceLimits Source # 
Storable VkPhysicalDeviceLimits Source # 
VulkanMarshalPrim VkPhysicalDeviceLimits Source # 
VulkanMarshal VkPhysicalDeviceLimits Source # 
CanWriteField "bufferImageGranularity" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "bufferImageGranularity" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "discreteQueuePriorities" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "discreteQueuePriorities" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "framebufferColorSampleCounts" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "framebufferColorSampleCounts" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "framebufferDepthSampleCounts" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "framebufferDepthSampleCounts" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "framebufferNoAttachmentsSampleCounts" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "framebufferNoAttachmentsSampleCounts" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "framebufferStencilSampleCounts" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "framebufferStencilSampleCounts" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "lineWidthGranularity" VkPhysicalDeviceLimits Source # 
CanWriteField "maxBoundDescriptorSets" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxBoundDescriptorSets" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxClipDistances" VkPhysicalDeviceLimits Source # 
CanWriteField "maxColorAttachments" VkPhysicalDeviceLimits Source # 
CanWriteField "maxCombinedClipAndCullDistances" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxCombinedClipAndCullDistances" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxComputeSharedMemorySize" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxComputeSharedMemorySize" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxComputeWorkGroupInvocations" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxComputeWorkGroupInvocations" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxCullDistances" VkPhysicalDeviceLimits Source # 
CanWriteField "maxDescriptorSetInputAttachments" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxDescriptorSetInputAttachments" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxDescriptorSetSampledImages" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxDescriptorSetSampledImages" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxDescriptorSetSamplers" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxDescriptorSetSamplers" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxDescriptorSetStorageBuffers" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxDescriptorSetStorageBuffers" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxDescriptorSetStorageBuffersDynamic" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxDescriptorSetStorageBuffersDynamic" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxDescriptorSetStorageImages" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxDescriptorSetStorageImages" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxDescriptorSetUniformBuffers" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxDescriptorSetUniformBuffers" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxDescriptorSetUniformBuffersDynamic" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxDescriptorSetUniformBuffersDynamic" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxDrawIndexedIndexValue" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxDrawIndexedIndexValue" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxDrawIndirectCount" VkPhysicalDeviceLimits Source # 
CanWriteField "maxFragmentCombinedOutputResources" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxFragmentCombinedOutputResources" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxFragmentDualSrcAttachments" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxFragmentDualSrcAttachments" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxFragmentInputComponents" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxFragmentInputComponents" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxFragmentOutputAttachments" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxFragmentOutputAttachments" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxFramebufferHeight" VkPhysicalDeviceLimits Source # 
CanWriteField "maxFramebufferLayers" VkPhysicalDeviceLimits Source # 
CanWriteField "maxFramebufferWidth" VkPhysicalDeviceLimits Source # 
CanWriteField "maxGeometryInputComponents" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxGeometryInputComponents" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxGeometryOutputComponents" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxGeometryOutputComponents" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxGeometryOutputVertices" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxGeometryOutputVertices" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxGeometryShaderInvocations" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxGeometryShaderInvocations" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxGeometryTotalOutputComponents" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxGeometryTotalOutputComponents" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxImageArrayLayers" VkPhysicalDeviceLimits Source # 
CanWriteField "maxImageDimension1D" VkPhysicalDeviceLimits Source # 
CanWriteField "maxImageDimension2D" VkPhysicalDeviceLimits Source # 
CanWriteField "maxImageDimension3D" VkPhysicalDeviceLimits Source # 
CanWriteField "maxImageDimensionCube" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxImageDimensionCube" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxInterpolationOffset" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxInterpolationOffset" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxMemoryAllocationCount" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxMemoryAllocationCount" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxPerStageDescriptorInputAttachments" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxPerStageDescriptorInputAttachments" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxPerStageDescriptorSampledImages" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxPerStageDescriptorSampledImages" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxPerStageDescriptorSamplers" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxPerStageDescriptorSamplers" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxPerStageDescriptorStorageBuffers" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxPerStageDescriptorStorageBuffers" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxPerStageDescriptorStorageImages" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxPerStageDescriptorStorageImages" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxPerStageDescriptorUniformBuffers" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxPerStageDescriptorUniformBuffers" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxPerStageResources" VkPhysicalDeviceLimits Source # 
CanWriteField "maxPushConstantsSize" VkPhysicalDeviceLimits Source # 
CanWriteField "maxSampleMaskWords" VkPhysicalDeviceLimits Source # 
CanWriteField "maxSamplerAllocationCount" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxSamplerAllocationCount" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxSamplerAnisotropy" VkPhysicalDeviceLimits Source # 
CanWriteField "maxSamplerLodBias" VkPhysicalDeviceLimits Source # 
CanWriteField "maxStorageBufferRange" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxStorageBufferRange" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxTessellationControlPerPatchOutputComponents" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxTessellationControlPerPatchOutputComponents" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxTessellationControlPerVertexInputComponents" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxTessellationControlPerVertexInputComponents" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxTessellationControlPerVertexOutputComponents" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxTessellationControlPerVertexOutputComponents" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxTessellationControlTotalOutputComponents" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxTessellationControlTotalOutputComponents" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxTessellationEvaluationInputComponents" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxTessellationEvaluationInputComponents" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxTessellationEvaluationOutputComponents" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxTessellationEvaluationOutputComponents" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxTessellationGenerationLevel" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxTessellationGenerationLevel" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxTessellationPatchSize" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxTessellationPatchSize" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxTexelBufferElements" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxTexelBufferElements" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxTexelGatherOffset" VkPhysicalDeviceLimits Source # 
CanWriteField "maxTexelOffset" VkPhysicalDeviceLimits Source # 
CanWriteField "maxUniformBufferRange" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxUniformBufferRange" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxVertexInputAttributeOffset" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxVertexInputAttributeOffset" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxVertexInputAttributes" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxVertexInputAttributes" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxVertexInputBindingStride" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxVertexInputBindingStride" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxVertexInputBindings" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxVertexInputBindings" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxVertexOutputComponents" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "maxVertexOutputComponents" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "maxViewports" VkPhysicalDeviceLimits Source # 
CanWriteField "minInterpolationOffset" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "minInterpolationOffset" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "minMemoryMapAlignment" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "minMemoryMapAlignment" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "minStorageBufferOffsetAlignment" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "minStorageBufferOffsetAlignment" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "minTexelBufferOffsetAlignment" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "minTexelBufferOffsetAlignment" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "minTexelGatherOffset" VkPhysicalDeviceLimits Source # 
CanWriteField "minTexelOffset" VkPhysicalDeviceLimits Source # 
CanWriteField "minUniformBufferOffsetAlignment" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "minUniformBufferOffsetAlignment" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "mipmapPrecisionBits" VkPhysicalDeviceLimits Source # 
CanWriteField "nonCoherentAtomSize" VkPhysicalDeviceLimits Source # 
CanWriteField "optimalBufferCopyOffsetAlignment" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "optimalBufferCopyOffsetAlignment" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "optimalBufferCopyRowPitchAlignment" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "optimalBufferCopyRowPitchAlignment" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "pointSizeGranularity" VkPhysicalDeviceLimits Source # 
CanWriteField "sampledImageColorSampleCounts" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "sampledImageColorSampleCounts" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "sampledImageDepthSampleCounts" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "sampledImageDepthSampleCounts" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "sampledImageIntegerSampleCounts" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "sampledImageIntegerSampleCounts" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "sampledImageStencilSampleCounts" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "sampledImageStencilSampleCounts" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "sparseAddressSpaceSize" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "sparseAddressSpaceSize" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "standardSampleLocations" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "standardSampleLocations" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "storageImageSampleCounts" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "storageImageSampleCounts" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "strictLines" VkPhysicalDeviceLimits Source # 
CanWriteField "subPixelInterpolationOffsetBits" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "subPixelInterpolationOffsetBits" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "subPixelPrecisionBits" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "subPixelPrecisionBits" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "subTexelPrecisionBits" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "subTexelPrecisionBits" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "timestampComputeAndGraphics" VkPhysicalDeviceLimits Source # 

Methods

writeField :: Ptr VkPhysicalDeviceLimits -> FieldType "timestampComputeAndGraphics" VkPhysicalDeviceLimits -> IO () Source #

CanWriteField "timestampPeriod" VkPhysicalDeviceLimits Source # 
CanWriteField "viewportSubPixelBits" VkPhysicalDeviceLimits Source # 
CanReadField "bufferImageGranularity" VkPhysicalDeviceLimits Source # 
CanReadField "discreteQueuePriorities" VkPhysicalDeviceLimits Source # 
CanReadField "framebufferColorSampleCounts" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "framebufferColorSampleCounts" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "framebufferColorSampleCounts" VkPhysicalDeviceLimits) Source #

CanReadField "framebufferDepthSampleCounts" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "framebufferDepthSampleCounts" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "framebufferDepthSampleCounts" VkPhysicalDeviceLimits) Source #

CanReadField "framebufferNoAttachmentsSampleCounts" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "framebufferNoAttachmentsSampleCounts" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "framebufferNoAttachmentsSampleCounts" VkPhysicalDeviceLimits) Source #

CanReadField "framebufferStencilSampleCounts" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "framebufferStencilSampleCounts" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "framebufferStencilSampleCounts" VkPhysicalDeviceLimits) Source #

CanReadField "lineWidthGranularity" VkPhysicalDeviceLimits Source # 
CanReadField "maxBoundDescriptorSets" VkPhysicalDeviceLimits Source # 
CanReadField "maxClipDistances" VkPhysicalDeviceLimits Source # 
CanReadField "maxColorAttachments" VkPhysicalDeviceLimits Source # 
CanReadField "maxCombinedClipAndCullDistances" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "maxCombinedClipAndCullDistances" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "maxCombinedClipAndCullDistances" VkPhysicalDeviceLimits) Source #

CanReadField "maxComputeSharedMemorySize" VkPhysicalDeviceLimits Source # 
CanReadField "maxComputeWorkGroupInvocations" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "maxComputeWorkGroupInvocations" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "maxComputeWorkGroupInvocations" VkPhysicalDeviceLimits) Source #

CanReadField "maxCullDistances" VkPhysicalDeviceLimits Source # 
CanReadField "maxDescriptorSetInputAttachments" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "maxDescriptorSetInputAttachments" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "maxDescriptorSetInputAttachments" VkPhysicalDeviceLimits) Source #

CanReadField "maxDescriptorSetSampledImages" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "maxDescriptorSetSampledImages" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "maxDescriptorSetSampledImages" VkPhysicalDeviceLimits) Source #

CanReadField "maxDescriptorSetSamplers" VkPhysicalDeviceLimits Source # 
CanReadField "maxDescriptorSetStorageBuffers" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "maxDescriptorSetStorageBuffers" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "maxDescriptorSetStorageBuffers" VkPhysicalDeviceLimits) Source #

CanReadField "maxDescriptorSetStorageBuffersDynamic" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "maxDescriptorSetStorageBuffersDynamic" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "maxDescriptorSetStorageBuffersDynamic" VkPhysicalDeviceLimits) Source #

CanReadField "maxDescriptorSetStorageImages" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "maxDescriptorSetStorageImages" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "maxDescriptorSetStorageImages" VkPhysicalDeviceLimits) Source #

CanReadField "maxDescriptorSetUniformBuffers" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "maxDescriptorSetUniformBuffers" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "maxDescriptorSetUniformBuffers" VkPhysicalDeviceLimits) Source #

CanReadField "maxDescriptorSetUniformBuffersDynamic" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "maxDescriptorSetUniformBuffersDynamic" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "maxDescriptorSetUniformBuffersDynamic" VkPhysicalDeviceLimits) Source #

CanReadField "maxDrawIndexedIndexValue" VkPhysicalDeviceLimits Source # 
CanReadField "maxDrawIndirectCount" VkPhysicalDeviceLimits Source # 
CanReadField "maxFragmentCombinedOutputResources" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "maxFragmentCombinedOutputResources" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "maxFragmentCombinedOutputResources" VkPhysicalDeviceLimits) Source #

CanReadField "maxFragmentDualSrcAttachments" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "maxFragmentDualSrcAttachments" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "maxFragmentDualSrcAttachments" VkPhysicalDeviceLimits) Source #

CanReadField "maxFragmentInputComponents" VkPhysicalDeviceLimits Source # 
CanReadField "maxFragmentOutputAttachments" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "maxFragmentOutputAttachments" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "maxFragmentOutputAttachments" VkPhysicalDeviceLimits) Source #

CanReadField "maxFramebufferHeight" VkPhysicalDeviceLimits Source # 
CanReadField "maxFramebufferLayers" VkPhysicalDeviceLimits Source # 
CanReadField "maxFramebufferWidth" VkPhysicalDeviceLimits Source # 
CanReadField "maxGeometryInputComponents" VkPhysicalDeviceLimits Source # 
CanReadField "maxGeometryOutputComponents" VkPhysicalDeviceLimits Source # 
CanReadField "maxGeometryOutputVertices" VkPhysicalDeviceLimits Source # 
CanReadField "maxGeometryShaderInvocations" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "maxGeometryShaderInvocations" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "maxGeometryShaderInvocations" VkPhysicalDeviceLimits) Source #

CanReadField "maxGeometryTotalOutputComponents" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "maxGeometryTotalOutputComponents" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "maxGeometryTotalOutputComponents" VkPhysicalDeviceLimits) Source #

CanReadField "maxImageArrayLayers" VkPhysicalDeviceLimits Source # 
CanReadField "maxImageDimension1D" VkPhysicalDeviceLimits Source # 
CanReadField "maxImageDimension2D" VkPhysicalDeviceLimits Source # 
CanReadField "maxImageDimension3D" VkPhysicalDeviceLimits Source # 
CanReadField "maxImageDimensionCube" VkPhysicalDeviceLimits Source # 
CanReadField "maxInterpolationOffset" VkPhysicalDeviceLimits Source # 
CanReadField "maxMemoryAllocationCount" VkPhysicalDeviceLimits Source # 
CanReadField "maxPerStageDescriptorInputAttachments" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "maxPerStageDescriptorInputAttachments" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "maxPerStageDescriptorInputAttachments" VkPhysicalDeviceLimits) Source #

CanReadField "maxPerStageDescriptorSampledImages" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "maxPerStageDescriptorSampledImages" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "maxPerStageDescriptorSampledImages" VkPhysicalDeviceLimits) Source #

CanReadField "maxPerStageDescriptorSamplers" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "maxPerStageDescriptorSamplers" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "maxPerStageDescriptorSamplers" VkPhysicalDeviceLimits) Source #

CanReadField "maxPerStageDescriptorStorageBuffers" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "maxPerStageDescriptorStorageBuffers" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "maxPerStageDescriptorStorageBuffers" VkPhysicalDeviceLimits) Source #

CanReadField "maxPerStageDescriptorStorageImages" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "maxPerStageDescriptorStorageImages" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "maxPerStageDescriptorStorageImages" VkPhysicalDeviceLimits) Source #

CanReadField "maxPerStageDescriptorUniformBuffers" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "maxPerStageDescriptorUniformBuffers" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "maxPerStageDescriptorUniformBuffers" VkPhysicalDeviceLimits) Source #

CanReadField "maxPerStageResources" VkPhysicalDeviceLimits Source # 
CanReadField "maxPushConstantsSize" VkPhysicalDeviceLimits Source # 
CanReadField "maxSampleMaskWords" VkPhysicalDeviceLimits Source # 
CanReadField "maxSamplerAllocationCount" VkPhysicalDeviceLimits Source # 
CanReadField "maxSamplerAnisotropy" VkPhysicalDeviceLimits Source # 
CanReadField "maxSamplerLodBias" VkPhysicalDeviceLimits Source # 
CanReadField "maxStorageBufferRange" VkPhysicalDeviceLimits Source # 
CanReadField "maxTessellationControlPerPatchOutputComponents" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "maxTessellationControlPerPatchOutputComponents" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "maxTessellationControlPerPatchOutputComponents" VkPhysicalDeviceLimits) Source #

CanReadField "maxTessellationControlPerVertexInputComponents" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "maxTessellationControlPerVertexInputComponents" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "maxTessellationControlPerVertexInputComponents" VkPhysicalDeviceLimits) Source #

CanReadField "maxTessellationControlPerVertexOutputComponents" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "maxTessellationControlPerVertexOutputComponents" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "maxTessellationControlPerVertexOutputComponents" VkPhysicalDeviceLimits) Source #

CanReadField "maxTessellationControlTotalOutputComponents" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "maxTessellationControlTotalOutputComponents" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "maxTessellationControlTotalOutputComponents" VkPhysicalDeviceLimits) Source #

CanReadField "maxTessellationEvaluationInputComponents" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "maxTessellationEvaluationInputComponents" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "maxTessellationEvaluationInputComponents" VkPhysicalDeviceLimits) Source #

CanReadField "maxTessellationEvaluationOutputComponents" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "maxTessellationEvaluationOutputComponents" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "maxTessellationEvaluationOutputComponents" VkPhysicalDeviceLimits) Source #

CanReadField "maxTessellationGenerationLevel" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "maxTessellationGenerationLevel" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "maxTessellationGenerationLevel" VkPhysicalDeviceLimits) Source #

CanReadField "maxTessellationPatchSize" VkPhysicalDeviceLimits Source # 
CanReadField "maxTexelBufferElements" VkPhysicalDeviceLimits Source # 
CanReadField "maxTexelGatherOffset" VkPhysicalDeviceLimits Source # 
CanReadField "maxTexelOffset" VkPhysicalDeviceLimits Source # 
CanReadField "maxUniformBufferRange" VkPhysicalDeviceLimits Source # 
CanReadField "maxVertexInputAttributeOffset" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "maxVertexInputAttributeOffset" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "maxVertexInputAttributeOffset" VkPhysicalDeviceLimits) Source #

CanReadField "maxVertexInputAttributes" VkPhysicalDeviceLimits Source # 
CanReadField "maxVertexInputBindingStride" VkPhysicalDeviceLimits Source # 
CanReadField "maxVertexInputBindings" VkPhysicalDeviceLimits Source # 
CanReadField "maxVertexOutputComponents" VkPhysicalDeviceLimits Source # 
CanReadField "maxViewports" VkPhysicalDeviceLimits Source # 
CanReadField "minInterpolationOffset" VkPhysicalDeviceLimits Source # 
CanReadField "minMemoryMapAlignment" VkPhysicalDeviceLimits Source # 
CanReadField "minStorageBufferOffsetAlignment" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "minStorageBufferOffsetAlignment" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "minStorageBufferOffsetAlignment" VkPhysicalDeviceLimits) Source #

CanReadField "minTexelBufferOffsetAlignment" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "minTexelBufferOffsetAlignment" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "minTexelBufferOffsetAlignment" VkPhysicalDeviceLimits) Source #

CanReadField "minTexelGatherOffset" VkPhysicalDeviceLimits Source # 
CanReadField "minTexelOffset" VkPhysicalDeviceLimits Source # 
CanReadField "minUniformBufferOffsetAlignment" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "minUniformBufferOffsetAlignment" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "minUniformBufferOffsetAlignment" VkPhysicalDeviceLimits) Source #

CanReadField "mipmapPrecisionBits" VkPhysicalDeviceLimits Source # 
CanReadField "nonCoherentAtomSize" VkPhysicalDeviceLimits Source # 
CanReadField "optimalBufferCopyOffsetAlignment" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "optimalBufferCopyOffsetAlignment" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "optimalBufferCopyOffsetAlignment" VkPhysicalDeviceLimits) Source #

CanReadField "optimalBufferCopyRowPitchAlignment" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "optimalBufferCopyRowPitchAlignment" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "optimalBufferCopyRowPitchAlignment" VkPhysicalDeviceLimits) Source #

CanReadField "pointSizeGranularity" VkPhysicalDeviceLimits Source # 
CanReadField "sampledImageColorSampleCounts" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "sampledImageColorSampleCounts" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "sampledImageColorSampleCounts" VkPhysicalDeviceLimits) Source #

CanReadField "sampledImageDepthSampleCounts" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "sampledImageDepthSampleCounts" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "sampledImageDepthSampleCounts" VkPhysicalDeviceLimits) Source #

CanReadField "sampledImageIntegerSampleCounts" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "sampledImageIntegerSampleCounts" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "sampledImageIntegerSampleCounts" VkPhysicalDeviceLimits) Source #

CanReadField "sampledImageStencilSampleCounts" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "sampledImageStencilSampleCounts" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "sampledImageStencilSampleCounts" VkPhysicalDeviceLimits) Source #

CanReadField "sparseAddressSpaceSize" VkPhysicalDeviceLimits Source # 
CanReadField "standardSampleLocations" VkPhysicalDeviceLimits Source # 
CanReadField "storageImageSampleCounts" VkPhysicalDeviceLimits Source # 
CanReadField "strictLines" VkPhysicalDeviceLimits Source # 
CanReadField "subPixelInterpolationOffsetBits" VkPhysicalDeviceLimits Source # 

Methods

getField :: VkPhysicalDeviceLimits -> FieldType "subPixelInterpolationOffsetBits" VkPhysicalDeviceLimits Source #

readField :: Ptr VkPhysicalDeviceLimits -> IO (FieldType "subPixelInterpolationOffsetBits" VkPhysicalDeviceLimits) Source #

CanReadField "subPixelPrecisionBits" VkPhysicalDeviceLimits Source # 
CanReadField "subTexelPrecisionBits" VkPhysicalDeviceLimits Source # 
CanReadField "timestampComputeAndGraphics" VkPhysicalDeviceLimits Source # 
CanReadField "timestampPeriod" VkPhysicalDeviceLimits Source # 
CanReadField "viewportSubPixelBits" VkPhysicalDeviceLimits Source # 
HasField "bufferImageGranularity" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("bufferImageGranularity" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("bufferImageGranularity" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("bufferImageGranularity" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("bufferImageGranularity" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "discreteQueuePriorities" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("discreteQueuePriorities" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("discreteQueuePriorities" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("discreteQueuePriorities" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("discreteQueuePriorities" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "framebufferColorSampleCounts" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("framebufferColorSampleCounts" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("framebufferColorSampleCounts" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("framebufferColorSampleCounts" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("framebufferColorSampleCounts" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "framebufferDepthSampleCounts" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("framebufferDepthSampleCounts" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("framebufferDepthSampleCounts" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("framebufferDepthSampleCounts" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("framebufferDepthSampleCounts" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "framebufferNoAttachmentsSampleCounts" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("framebufferNoAttachmentsSampleCounts" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("framebufferNoAttachmentsSampleCounts" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("framebufferNoAttachmentsSampleCounts" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("framebufferNoAttachmentsSampleCounts" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "framebufferStencilSampleCounts" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("framebufferStencilSampleCounts" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("framebufferStencilSampleCounts" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("framebufferStencilSampleCounts" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("framebufferStencilSampleCounts" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "lineWidthGranularity" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("lineWidthGranularity" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("lineWidthGranularity" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("lineWidthGranularity" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("lineWidthGranularity" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "lineWidthRange" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("lineWidthRange" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("lineWidthRange" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("lineWidthRange" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("lineWidthRange" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxBoundDescriptorSets" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxBoundDescriptorSets" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxBoundDescriptorSets" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxBoundDescriptorSets" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxBoundDescriptorSets" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxClipDistances" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxClipDistances" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxClipDistances" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxClipDistances" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxClipDistances" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxColorAttachments" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxColorAttachments" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxColorAttachments" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxColorAttachments" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxColorAttachments" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxCombinedClipAndCullDistances" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxCombinedClipAndCullDistances" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxCombinedClipAndCullDistances" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxCombinedClipAndCullDistances" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxCombinedClipAndCullDistances" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxComputeSharedMemorySize" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxComputeSharedMemorySize" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxComputeSharedMemorySize" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxComputeSharedMemorySize" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxComputeSharedMemorySize" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxComputeWorkGroupCount" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxComputeWorkGroupCount" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxComputeWorkGroupCount" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxComputeWorkGroupCount" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxComputeWorkGroupCount" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxComputeWorkGroupInvocations" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxComputeWorkGroupInvocations" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxComputeWorkGroupInvocations" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxComputeWorkGroupInvocations" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxComputeWorkGroupInvocations" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxComputeWorkGroupSize" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxComputeWorkGroupSize" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxComputeWorkGroupSize" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxComputeWorkGroupSize" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxComputeWorkGroupSize" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxCullDistances" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxCullDistances" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxCullDistances" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxCullDistances" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxCullDistances" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxDescriptorSetInputAttachments" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxDescriptorSetInputAttachments" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxDescriptorSetInputAttachments" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxDescriptorSetInputAttachments" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxDescriptorSetInputAttachments" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxDescriptorSetSampledImages" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxDescriptorSetSampledImages" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxDescriptorSetSampledImages" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxDescriptorSetSampledImages" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxDescriptorSetSampledImages" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxDescriptorSetSamplers" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxDescriptorSetSamplers" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxDescriptorSetSamplers" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxDescriptorSetSamplers" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxDescriptorSetSamplers" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxDescriptorSetStorageBuffers" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxDescriptorSetStorageBuffers" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxDescriptorSetStorageBuffers" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxDescriptorSetStorageBuffers" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxDescriptorSetStorageBuffers" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxDescriptorSetStorageBuffersDynamic" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxDescriptorSetStorageBuffersDynamic" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxDescriptorSetStorageBuffersDynamic" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxDescriptorSetStorageBuffersDynamic" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxDescriptorSetStorageBuffersDynamic" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxDescriptorSetStorageImages" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxDescriptorSetStorageImages" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxDescriptorSetStorageImages" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxDescriptorSetStorageImages" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxDescriptorSetStorageImages" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxDescriptorSetUniformBuffers" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxDescriptorSetUniformBuffers" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxDescriptorSetUniformBuffers" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxDescriptorSetUniformBuffers" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxDescriptorSetUniformBuffers" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxDescriptorSetUniformBuffersDynamic" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxDescriptorSetUniformBuffersDynamic" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxDescriptorSetUniformBuffersDynamic" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxDescriptorSetUniformBuffersDynamic" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxDescriptorSetUniformBuffersDynamic" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxDrawIndexedIndexValue" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxDrawIndexedIndexValue" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxDrawIndexedIndexValue" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxDrawIndexedIndexValue" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxDrawIndexedIndexValue" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxDrawIndirectCount" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxDrawIndirectCount" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxDrawIndirectCount" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxDrawIndirectCount" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxDrawIndirectCount" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxFragmentCombinedOutputResources" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxFragmentCombinedOutputResources" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxFragmentCombinedOutputResources" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxFragmentCombinedOutputResources" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxFragmentCombinedOutputResources" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxFragmentDualSrcAttachments" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxFragmentDualSrcAttachments" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxFragmentDualSrcAttachments" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxFragmentDualSrcAttachments" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxFragmentDualSrcAttachments" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxFragmentInputComponents" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxFragmentInputComponents" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxFragmentInputComponents" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxFragmentInputComponents" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxFragmentInputComponents" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxFragmentOutputAttachments" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxFragmentOutputAttachments" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxFragmentOutputAttachments" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxFragmentOutputAttachments" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxFragmentOutputAttachments" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxFramebufferHeight" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxFramebufferHeight" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxFramebufferHeight" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxFramebufferHeight" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxFramebufferHeight" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxFramebufferLayers" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxFramebufferLayers" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxFramebufferLayers" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxFramebufferLayers" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxFramebufferLayers" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxFramebufferWidth" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxFramebufferWidth" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxFramebufferWidth" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxFramebufferWidth" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxFramebufferWidth" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxGeometryInputComponents" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxGeometryInputComponents" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxGeometryInputComponents" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxGeometryInputComponents" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxGeometryInputComponents" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxGeometryOutputComponents" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxGeometryOutputComponents" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxGeometryOutputComponents" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxGeometryOutputComponents" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxGeometryOutputComponents" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxGeometryOutputVertices" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxGeometryOutputVertices" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxGeometryOutputVertices" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxGeometryOutputVertices" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxGeometryOutputVertices" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxGeometryShaderInvocations" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxGeometryShaderInvocations" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxGeometryShaderInvocations" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxGeometryShaderInvocations" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxGeometryShaderInvocations" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxGeometryTotalOutputComponents" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxGeometryTotalOutputComponents" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxGeometryTotalOutputComponents" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxGeometryTotalOutputComponents" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxGeometryTotalOutputComponents" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxImageArrayLayers" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxImageArrayLayers" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxImageArrayLayers" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxImageArrayLayers" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxImageArrayLayers" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxImageDimension1D" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxImageDimension1D" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxImageDimension1D" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxImageDimension1D" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxImageDimension1D" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxImageDimension2D" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxImageDimension2D" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxImageDimension2D" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxImageDimension2D" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxImageDimension2D" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxImageDimension3D" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxImageDimension3D" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxImageDimension3D" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxImageDimension3D" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxImageDimension3D" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxImageDimensionCube" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxImageDimensionCube" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxImageDimensionCube" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxImageDimensionCube" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxImageDimensionCube" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxInterpolationOffset" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxInterpolationOffset" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxInterpolationOffset" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxInterpolationOffset" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxInterpolationOffset" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxMemoryAllocationCount" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxMemoryAllocationCount" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxMemoryAllocationCount" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxMemoryAllocationCount" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxMemoryAllocationCount" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxPerStageDescriptorInputAttachments" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxPerStageDescriptorInputAttachments" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxPerStageDescriptorInputAttachments" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxPerStageDescriptorInputAttachments" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxPerStageDescriptorInputAttachments" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxPerStageDescriptorSampledImages" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxPerStageDescriptorSampledImages" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxPerStageDescriptorSampledImages" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxPerStageDescriptorSampledImages" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxPerStageDescriptorSampledImages" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxPerStageDescriptorSamplers" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxPerStageDescriptorSamplers" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxPerStageDescriptorSamplers" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxPerStageDescriptorSamplers" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxPerStageDescriptorSamplers" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxPerStageDescriptorStorageBuffers" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxPerStageDescriptorStorageBuffers" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxPerStageDescriptorStorageBuffers" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxPerStageDescriptorStorageBuffers" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxPerStageDescriptorStorageBuffers" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxPerStageDescriptorStorageImages" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxPerStageDescriptorStorageImages" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxPerStageDescriptorStorageImages" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxPerStageDescriptorStorageImages" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxPerStageDescriptorStorageImages" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxPerStageDescriptorUniformBuffers" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxPerStageDescriptorUniformBuffers" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxPerStageDescriptorUniformBuffers" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxPerStageDescriptorUniformBuffers" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxPerStageDescriptorUniformBuffers" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxPerStageResources" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxPerStageResources" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxPerStageResources" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxPerStageResources" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxPerStageResources" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxPushConstantsSize" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxPushConstantsSize" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxPushConstantsSize" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxPushConstantsSize" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxPushConstantsSize" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxSampleMaskWords" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxSampleMaskWords" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxSampleMaskWords" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxSampleMaskWords" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxSampleMaskWords" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxSamplerAllocationCount" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxSamplerAllocationCount" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxSamplerAllocationCount" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxSamplerAllocationCount" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxSamplerAllocationCount" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxSamplerAnisotropy" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxSamplerAnisotropy" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxSamplerAnisotropy" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxSamplerAnisotropy" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxSamplerAnisotropy" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxSamplerLodBias" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxSamplerLodBias" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxSamplerLodBias" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxSamplerLodBias" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxSamplerLodBias" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxStorageBufferRange" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxStorageBufferRange" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxStorageBufferRange" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxStorageBufferRange" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxStorageBufferRange" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxTessellationControlPerPatchOutputComponents" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxTessellationControlPerPatchOutputComponents" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxTessellationControlPerPatchOutputComponents" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxTessellationControlPerPatchOutputComponents" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxTessellationControlPerPatchOutputComponents" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxTessellationControlPerVertexInputComponents" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxTessellationControlPerVertexInputComponents" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxTessellationControlPerVertexInputComponents" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxTessellationControlPerVertexInputComponents" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxTessellationControlPerVertexInputComponents" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxTessellationControlPerVertexOutputComponents" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxTessellationControlPerVertexOutputComponents" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxTessellationControlPerVertexOutputComponents" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxTessellationControlPerVertexOutputComponents" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxTessellationControlPerVertexOutputComponents" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxTessellationControlTotalOutputComponents" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxTessellationControlTotalOutputComponents" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxTessellationControlTotalOutputComponents" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxTessellationControlTotalOutputComponents" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxTessellationControlTotalOutputComponents" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxTessellationEvaluationInputComponents" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxTessellationEvaluationInputComponents" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxTessellationEvaluationInputComponents" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxTessellationEvaluationInputComponents" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxTessellationEvaluationInputComponents" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxTessellationEvaluationOutputComponents" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxTessellationEvaluationOutputComponents" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxTessellationEvaluationOutputComponents" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxTessellationEvaluationOutputComponents" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxTessellationEvaluationOutputComponents" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxTessellationGenerationLevel" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxTessellationGenerationLevel" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxTessellationGenerationLevel" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxTessellationGenerationLevel" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxTessellationGenerationLevel" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxTessellationPatchSize" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxTessellationPatchSize" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxTessellationPatchSize" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxTessellationPatchSize" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxTessellationPatchSize" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxTexelBufferElements" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxTexelBufferElements" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxTexelBufferElements" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxTexelBufferElements" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxTexelBufferElements" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxTexelGatherOffset" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxTexelGatherOffset" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxTexelGatherOffset" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxTexelGatherOffset" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxTexelGatherOffset" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxTexelOffset" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxTexelOffset" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxTexelOffset" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxTexelOffset" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxTexelOffset" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxUniformBufferRange" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxUniformBufferRange" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxUniformBufferRange" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxUniformBufferRange" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxUniformBufferRange" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxVertexInputAttributeOffset" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxVertexInputAttributeOffset" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxVertexInputAttributeOffset" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxVertexInputAttributeOffset" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxVertexInputAttributeOffset" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxVertexInputAttributes" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxVertexInputAttributes" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxVertexInputAttributes" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxVertexInputAttributes" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxVertexInputAttributes" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxVertexInputBindingStride" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxVertexInputBindingStride" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxVertexInputBindingStride" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxVertexInputBindingStride" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxVertexInputBindingStride" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxVertexInputBindings" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxVertexInputBindings" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxVertexInputBindings" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxVertexInputBindings" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxVertexInputBindings" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxVertexOutputComponents" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxVertexOutputComponents" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxVertexOutputComponents" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxVertexOutputComponents" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxVertexOutputComponents" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxViewportDimensions" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxViewportDimensions" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxViewportDimensions" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxViewportDimensions" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxViewportDimensions" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "maxViewports" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("maxViewports" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("maxViewports" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("maxViewports" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("maxViewports" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "minInterpolationOffset" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("minInterpolationOffset" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("minInterpolationOffset" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("minInterpolationOffset" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("minInterpolationOffset" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "minMemoryMapAlignment" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("minMemoryMapAlignment" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("minMemoryMapAlignment" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("minMemoryMapAlignment" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("minMemoryMapAlignment" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "minStorageBufferOffsetAlignment" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("minStorageBufferOffsetAlignment" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("minStorageBufferOffsetAlignment" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("minStorageBufferOffsetAlignment" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("minStorageBufferOffsetAlignment" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "minTexelBufferOffsetAlignment" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("minTexelBufferOffsetAlignment" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("minTexelBufferOffsetAlignment" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("minTexelBufferOffsetAlignment" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("minTexelBufferOffsetAlignment" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "minTexelGatherOffset" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("minTexelGatherOffset" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("minTexelGatherOffset" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("minTexelGatherOffset" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("minTexelGatherOffset" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "minTexelOffset" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("minTexelOffset" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("minTexelOffset" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("minTexelOffset" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("minTexelOffset" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "minUniformBufferOffsetAlignment" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("minUniformBufferOffsetAlignment" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("minUniformBufferOffsetAlignment" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("minUniformBufferOffsetAlignment" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("minUniformBufferOffsetAlignment" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "mipmapPrecisionBits" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("mipmapPrecisionBits" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("mipmapPrecisionBits" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("mipmapPrecisionBits" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("mipmapPrecisionBits" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "nonCoherentAtomSize" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("nonCoherentAtomSize" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("nonCoherentAtomSize" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("nonCoherentAtomSize" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("nonCoherentAtomSize" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "optimalBufferCopyOffsetAlignment" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("optimalBufferCopyOffsetAlignment" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("optimalBufferCopyOffsetAlignment" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("optimalBufferCopyOffsetAlignment" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("optimalBufferCopyOffsetAlignment" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "optimalBufferCopyRowPitchAlignment" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("optimalBufferCopyRowPitchAlignment" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("optimalBufferCopyRowPitchAlignment" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("optimalBufferCopyRowPitchAlignment" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("optimalBufferCopyRowPitchAlignment" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "pointSizeGranularity" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("pointSizeGranularity" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("pointSizeGranularity" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("pointSizeGranularity" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("pointSizeGranularity" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "pointSizeRange" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("pointSizeRange" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("pointSizeRange" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("pointSizeRange" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("pointSizeRange" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "sampledImageColorSampleCounts" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("sampledImageColorSampleCounts" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("sampledImageColorSampleCounts" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("sampledImageColorSampleCounts" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("sampledImageColorSampleCounts" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "sampledImageDepthSampleCounts" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("sampledImageDepthSampleCounts" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("sampledImageDepthSampleCounts" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("sampledImageDepthSampleCounts" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("sampledImageDepthSampleCounts" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "sampledImageIntegerSampleCounts" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("sampledImageIntegerSampleCounts" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("sampledImageIntegerSampleCounts" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("sampledImageIntegerSampleCounts" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("sampledImageIntegerSampleCounts" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "sampledImageStencilSampleCounts" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("sampledImageStencilSampleCounts" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("sampledImageStencilSampleCounts" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("sampledImageStencilSampleCounts" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("sampledImageStencilSampleCounts" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "sparseAddressSpaceSize" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("sparseAddressSpaceSize" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("sparseAddressSpaceSize" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("sparseAddressSpaceSize" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("sparseAddressSpaceSize" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "standardSampleLocations" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("standardSampleLocations" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("standardSampleLocations" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("standardSampleLocations" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("standardSampleLocations" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "storageImageSampleCounts" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("storageImageSampleCounts" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("storageImageSampleCounts" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("storageImageSampleCounts" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("storageImageSampleCounts" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "strictLines" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("strictLines" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("strictLines" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("strictLines" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("strictLines" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "subPixelInterpolationOffsetBits" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("subPixelInterpolationOffsetBits" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("subPixelInterpolationOffsetBits" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("subPixelInterpolationOffsetBits" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("subPixelInterpolationOffsetBits" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "subPixelPrecisionBits" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("subPixelPrecisionBits" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("subPixelPrecisionBits" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("subPixelPrecisionBits" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("subPixelPrecisionBits" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "subTexelPrecisionBits" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("subTexelPrecisionBits" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("subTexelPrecisionBits" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("subTexelPrecisionBits" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("subTexelPrecisionBits" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "timestampComputeAndGraphics" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("timestampComputeAndGraphics" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("timestampComputeAndGraphics" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("timestampComputeAndGraphics" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("timestampComputeAndGraphics" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "timestampPeriod" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("timestampPeriod" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("timestampPeriod" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("timestampPeriod" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("timestampPeriod" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "viewportBoundsRange" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("viewportBoundsRange" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("viewportBoundsRange" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("viewportBoundsRange" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("viewportBoundsRange" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

HasField "viewportSubPixelBits" VkPhysicalDeviceLimits Source # 

Associated Types

type FieldType ("viewportSubPixelBits" :: Symbol) VkPhysicalDeviceLimits :: Type Source #

type FieldOptional ("viewportSubPixelBits" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

type FieldOffset ("viewportSubPixelBits" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

type FieldIsArray ("viewportSubPixelBits" :: Symbol) VkPhysicalDeviceLimits :: Bool Source #

(KnownNat idx, IndexInBounds "lineWidthRange" idx VkPhysicalDeviceLimits) => CanWriteFieldArray "lineWidthRange" idx VkPhysicalDeviceLimits Source # 
(KnownNat idx, IndexInBounds "maxComputeWorkGroupCount" idx VkPhysicalDeviceLimits) => CanWriteFieldArray "maxComputeWorkGroupCount" idx VkPhysicalDeviceLimits Source # 
(KnownNat idx, IndexInBounds "maxComputeWorkGroupSize" idx VkPhysicalDeviceLimits) => CanWriteFieldArray "maxComputeWorkGroupSize" idx VkPhysicalDeviceLimits Source # 
(KnownNat idx, IndexInBounds "maxViewportDimensions" idx VkPhysicalDeviceLimits) => CanWriteFieldArray "maxViewportDimensions" idx VkPhysicalDeviceLimits Source # 
(KnownNat idx, IndexInBounds "pointSizeRange" idx VkPhysicalDeviceLimits) => CanWriteFieldArray "pointSizeRange" idx VkPhysicalDeviceLimits Source # 
(KnownNat idx, IndexInBounds "viewportBoundsRange" idx VkPhysicalDeviceLimits) => CanWriteFieldArray "viewportBoundsRange" idx VkPhysicalDeviceLimits Source # 
(KnownNat idx, IndexInBounds "lineWidthRange" idx VkPhysicalDeviceLimits) => CanReadFieldArray "lineWidthRange" idx VkPhysicalDeviceLimits Source # 
(KnownNat idx, IndexInBounds "maxComputeWorkGroupCount" idx VkPhysicalDeviceLimits) => CanReadFieldArray "maxComputeWorkGroupCount" idx VkPhysicalDeviceLimits Source # 

Associated Types

type FieldArrayLength ("maxComputeWorkGroupCount" :: Symbol) VkPhysicalDeviceLimits :: Nat Source #

(KnownNat idx, IndexInBounds "maxComputeWorkGroupSize" idx VkPhysicalDeviceLimits) => CanReadFieldArray "maxComputeWorkGroupSize" idx VkPhysicalDeviceLimits Source # 
(KnownNat idx, IndexInBounds "maxViewportDimensions" idx VkPhysicalDeviceLimits) => CanReadFieldArray "maxViewportDimensions" idx VkPhysicalDeviceLimits Source # 
(KnownNat idx, IndexInBounds "pointSizeRange" idx VkPhysicalDeviceLimits) => CanReadFieldArray "pointSizeRange" idx VkPhysicalDeviceLimits Source # 
(KnownNat idx, IndexInBounds "viewportBoundsRange" idx VkPhysicalDeviceLimits) => CanReadFieldArray "viewportBoundsRange" idx VkPhysicalDeviceLimits Source # 
type StructFields VkPhysicalDeviceLimits Source # 
type StructFields VkPhysicalDeviceLimits = (:) Symbol "maxImageDimension1D" ((:) Symbol "maxImageDimension2D" ((:) Symbol "maxImageDimension3D" ((:) Symbol "maxImageDimensionCube" ((:) Symbol "maxImageArrayLayers" ((:) Symbol "maxTexelBufferElements" ((:) Symbol "maxUniformBufferRange" ((:) Symbol "maxStorageBufferRange" ((:) Symbol "maxPushConstantsSize" ((:) Symbol "maxMemoryAllocationCount" ((:) Symbol "maxSamplerAllocationCount" ((:) Symbol "bufferImageGranularity" ((:) Symbol "sparseAddressSpaceSize" ((:) Symbol "maxBoundDescriptorSets" ((:) Symbol "maxPerStageDescriptorSamplers" ((:) Symbol "maxPerStageDescriptorUniformBuffers" ((:) Symbol "maxPerStageDescriptorStorageBuffers" ((:) Symbol "maxPerStageDescriptorSampledImages" ((:) Symbol "maxPerStageDescriptorStorageImages" ((:) Symbol "maxPerStageDescriptorInputAttachments" ((:) Symbol "maxPerStageResources" ((:) Symbol "maxDescriptorSetSamplers" ((:) Symbol "maxDescriptorSetUniformBuffers" ((:) Symbol "maxDescriptorSetUniformBuffersDynamic" ((:) Symbol "maxDescriptorSetStorageBuffers" ((:) Symbol "maxDescriptorSetStorageBuffersDynamic" ((:) Symbol "maxDescriptorSetSampledImages" ((:) Symbol "maxDescriptorSetStorageImages" ((:) Symbol "maxDescriptorSetInputAttachments" ((:) Symbol "maxVertexInputAttributes" ((:) Symbol "maxVertexInputBindings" ((:) Symbol "maxVertexInputAttributeOffset" ((:) Symbol "maxVertexInputBindingStride" ((:) Symbol "maxVertexOutputComponents" ((:) Symbol "maxTessellationGenerationLevel" ((:) Symbol "maxTessellationPatchSize" ((:) Symbol "maxTessellationControlPerVertexInputComponents" ((:) Symbol "maxTessellationControlPerVertexOutputComponents" ((:) Symbol "maxTessellationControlPerPatchOutputComponents" ((:) Symbol "maxTessellationControlTotalOutputComponents" ((:) Symbol "maxTessellationEvaluationInputComponents" ((:) Symbol "maxTessellationEvaluationOutputComponents" ((:) Symbol "maxGeometryShaderInvocations" ((:) Symbol "maxGeometryInputComponents" ((:) Symbol "maxGeometryOutputComponents" ((:) Symbol "maxGeometryOutputVertices" ((:) Symbol "maxGeometryTotalOutputComponents" ((:) Symbol "maxFragmentInputComponents" ((:) Symbol "maxFragmentOutputAttachments" ((:) Symbol "maxFragmentDualSrcAttachments" ((:) Symbol "maxFragmentCombinedOutputResources" ((:) Symbol "maxComputeSharedMemorySize" ((:) Symbol "maxComputeWorkGroupCount" ((:) Symbol "maxComputeWorkGroupInvocations" ((:) Symbol "maxComputeWorkGroupSize" ((:) Symbol "subPixelPrecisionBits" ((:) Symbol "subTexelPrecisionBits" ((:) Symbol "mipmapPrecisionBits" ((:) Symbol "maxDrawIndexedIndexValue" ((:) Symbol "maxDrawIndirectCount" ((:) Symbol "maxSamplerLodBias" ((:) Symbol "maxSamplerAnisotropy" ((:) Symbol "maxViewports" ((:) Symbol "maxViewportDimensions" ((:) Symbol "viewportBoundsRange" ((:) Symbol "viewportSubPixelBits" ((:) Symbol "minMemoryMapAlignment" ((:) Symbol "minTexelBufferOffsetAlignment" ((:) Symbol "minUniformBufferOffsetAlignment" ((:) Symbol "minStorageBufferOffsetAlignment" ((:) Symbol "minTexelOffset" ((:) Symbol "maxTexelOffset" ((:) Symbol "minTexelGatherOffset" ((:) Symbol "maxTexelGatherOffset" ((:) Symbol "minInterpolationOffset" ((:) Symbol "maxInterpolationOffset" ((:) Symbol "subPixelInterpolationOffsetBits" ((:) Symbol "maxFramebufferWidth" ((:) Symbol "maxFramebufferHeight" ((:) Symbol "maxFramebufferLayers" ((:) Symbol "framebufferColorSampleCounts" ((:) Symbol "framebufferDepthSampleCounts" ((:) Symbol "framebufferStencilSampleCounts" ((:) Symbol "framebufferNoAttachmentsSampleCounts" ((:) Symbol "maxColorAttachments" ((:) Symbol "sampledImageColorSampleCounts" ((:) Symbol "sampledImageIntegerSampleCounts" ((:) Symbol "sampledImageDepthSampleCounts" ((:) Symbol "sampledImageStencilSampleCounts" ((:) Symbol "storageImageSampleCounts" ((:) Symbol "maxSampleMaskWords" ((:) Symbol "timestampComputeAndGraphics" ((:) Symbol "timestampPeriod" ((:) Symbol "maxClipDistances" ((:) Symbol "maxCullDistances" ((:) Symbol "maxCombinedClipAndCullDistances" ((:) Symbol "discreteQueuePriorities" ((:) Symbol "pointSizeRange" ((:) Symbol "lineWidthRange" ((:) Symbol "pointSizeGranularity" ((:) Symbol "lineWidthGranularity" ((:) Symbol "strictLines" ((:) Symbol "standardSampleLocations" ((:) Symbol "optimalBufferCopyOffsetAlignment" ((:) Symbol "optimalBufferCopyRowPitchAlignment" ((:) Symbol "nonCoherentAtomSize" ([] Symbol))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
type CUnionType VkPhysicalDeviceLimits Source # 
type ReturnedOnly VkPhysicalDeviceLimits Source # 
type StructExtends VkPhysicalDeviceLimits Source # 
type FieldArrayLength "lineWidthRange" VkPhysicalDeviceLimits Source # 
type FieldArrayLength "lineWidthRange" VkPhysicalDeviceLimits = 2
type FieldArrayLength "maxComputeWorkGroupCount" VkPhysicalDeviceLimits Source # 
type FieldArrayLength "maxComputeWorkGroupCount" VkPhysicalDeviceLimits = 3
type FieldArrayLength "maxComputeWorkGroupSize" VkPhysicalDeviceLimits Source # 
type FieldArrayLength "maxComputeWorkGroupSize" VkPhysicalDeviceLimits = 3
type FieldArrayLength "maxViewportDimensions" VkPhysicalDeviceLimits Source # 
type FieldArrayLength "maxViewportDimensions" VkPhysicalDeviceLimits = 2
type FieldArrayLength "pointSizeRange" VkPhysicalDeviceLimits Source # 
type FieldArrayLength "pointSizeRange" VkPhysicalDeviceLimits = 2
type FieldArrayLength "viewportBoundsRange" VkPhysicalDeviceLimits Source # 
type FieldArrayLength "viewportBoundsRange" VkPhysicalDeviceLimits = 2
type FieldType "bufferImageGranularity" VkPhysicalDeviceLimits Source # 
type FieldType "bufferImageGranularity" VkPhysicalDeviceLimits = VkDeviceSize
type FieldType "discreteQueuePriorities" VkPhysicalDeviceLimits Source # 
type FieldType "discreteQueuePriorities" VkPhysicalDeviceLimits = Word32
type FieldType "framebufferColorSampleCounts" VkPhysicalDeviceLimits Source # 
type FieldType "framebufferColorSampleCounts" VkPhysicalDeviceLimits = VkSampleCountFlags
type FieldType "framebufferDepthSampleCounts" VkPhysicalDeviceLimits Source # 
type FieldType "framebufferDepthSampleCounts" VkPhysicalDeviceLimits = VkSampleCountFlags
type FieldType "framebufferNoAttachmentsSampleCounts" VkPhysicalDeviceLimits Source # 
type FieldType "framebufferNoAttachmentsSampleCounts" VkPhysicalDeviceLimits = VkSampleCountFlags
type FieldType "framebufferStencilSampleCounts" VkPhysicalDeviceLimits Source # 
type FieldType "framebufferStencilSampleCounts" VkPhysicalDeviceLimits = VkSampleCountFlags
type FieldType "lineWidthGranularity" VkPhysicalDeviceLimits Source # 
type FieldType "lineWidthGranularity" VkPhysicalDeviceLimits = Float
type FieldType "lineWidthRange" VkPhysicalDeviceLimits Source # 
type FieldType "lineWidthRange" VkPhysicalDeviceLimits = Float
type FieldType "maxBoundDescriptorSets" VkPhysicalDeviceLimits Source # 
type FieldType "maxBoundDescriptorSets" VkPhysicalDeviceLimits = Word32
type FieldType "maxClipDistances" VkPhysicalDeviceLimits Source # 
type FieldType "maxClipDistances" VkPhysicalDeviceLimits = Word32
type FieldType "maxColorAttachments" VkPhysicalDeviceLimits Source # 
type FieldType "maxColorAttachments" VkPhysicalDeviceLimits = Word32
type FieldType "maxCombinedClipAndCullDistances" VkPhysicalDeviceLimits Source # 
type FieldType "maxCombinedClipAndCullDistances" VkPhysicalDeviceLimits = Word32
type FieldType "maxComputeSharedMemorySize" VkPhysicalDeviceLimits Source # 
type FieldType "maxComputeSharedMemorySize" VkPhysicalDeviceLimits = Word32
type FieldType "maxComputeWorkGroupCount" VkPhysicalDeviceLimits Source # 
type FieldType "maxComputeWorkGroupCount" VkPhysicalDeviceLimits = Word32
type FieldType "maxComputeWorkGroupInvocations" VkPhysicalDeviceLimits Source # 
type FieldType "maxComputeWorkGroupInvocations" VkPhysicalDeviceLimits = Word32
type FieldType "maxComputeWorkGroupSize" VkPhysicalDeviceLimits Source # 
type FieldType "maxComputeWorkGroupSize" VkPhysicalDeviceLimits = Word32
type FieldType "maxCullDistances" VkPhysicalDeviceLimits Source # 
type FieldType "maxCullDistances" VkPhysicalDeviceLimits = Word32
type FieldType "maxDescriptorSetInputAttachments" VkPhysicalDeviceLimits Source # 
type FieldType "maxDescriptorSetInputAttachments" VkPhysicalDeviceLimits = Word32
type FieldType "maxDescriptorSetSampledImages" VkPhysicalDeviceLimits Source # 
type FieldType "maxDescriptorSetSampledImages" VkPhysicalDeviceLimits = Word32
type FieldType "maxDescriptorSetSamplers" VkPhysicalDeviceLimits Source # 
type FieldType "maxDescriptorSetSamplers" VkPhysicalDeviceLimits = Word32
type FieldType "maxDescriptorSetStorageBuffers" VkPhysicalDeviceLimits Source # 
type FieldType "maxDescriptorSetStorageBuffers" VkPhysicalDeviceLimits = Word32
type FieldType "maxDescriptorSetStorageBuffersDynamic" VkPhysicalDeviceLimits Source # 
type FieldType "maxDescriptorSetStorageBuffersDynamic" VkPhysicalDeviceLimits = Word32
type FieldType "maxDescriptorSetStorageImages" VkPhysicalDeviceLimits Source # 
type FieldType "maxDescriptorSetStorageImages" VkPhysicalDeviceLimits = Word32
type FieldType "maxDescriptorSetUniformBuffers" VkPhysicalDeviceLimits Source # 
type FieldType "maxDescriptorSetUniformBuffers" VkPhysicalDeviceLimits = Word32
type FieldType "maxDescriptorSetUniformBuffersDynamic" VkPhysicalDeviceLimits Source # 
type FieldType "maxDescriptorSetUniformBuffersDynamic" VkPhysicalDeviceLimits = Word32
type FieldType "maxDrawIndexedIndexValue" VkPhysicalDeviceLimits Source # 
type FieldType "maxDrawIndexedIndexValue" VkPhysicalDeviceLimits = Word32
type FieldType "maxDrawIndirectCount" VkPhysicalDeviceLimits Source # 
type FieldType "maxDrawIndirectCount" VkPhysicalDeviceLimits = Word32
type FieldType "maxFragmentCombinedOutputResources" VkPhysicalDeviceLimits Source # 
type FieldType "maxFragmentCombinedOutputResources" VkPhysicalDeviceLimits = Word32
type FieldType "maxFragmentDualSrcAttachments" VkPhysicalDeviceLimits Source # 
type FieldType "maxFragmentDualSrcAttachments" VkPhysicalDeviceLimits = Word32
type FieldType "maxFragmentInputComponents" VkPhysicalDeviceLimits Source # 
type FieldType "maxFragmentInputComponents" VkPhysicalDeviceLimits = Word32
type FieldType "maxFragmentOutputAttachments" VkPhysicalDeviceLimits Source # 
type FieldType "maxFragmentOutputAttachments" VkPhysicalDeviceLimits = Word32
type FieldType "maxFramebufferHeight" VkPhysicalDeviceLimits Source # 
type FieldType "maxFramebufferHeight" VkPhysicalDeviceLimits = Word32
type FieldType "maxFramebufferLayers" VkPhysicalDeviceLimits Source # 
type FieldType "maxFramebufferLayers" VkPhysicalDeviceLimits = Word32
type FieldType "maxFramebufferWidth" VkPhysicalDeviceLimits Source # 
type FieldType "maxFramebufferWidth" VkPhysicalDeviceLimits = Word32
type FieldType "maxGeometryInputComponents" VkPhysicalDeviceLimits Source # 
type FieldType "maxGeometryInputComponents" VkPhysicalDeviceLimits = Word32
type FieldType "maxGeometryOutputComponents" VkPhysicalDeviceLimits Source # 
type FieldType "maxGeometryOutputComponents" VkPhysicalDeviceLimits = Word32
type FieldType "maxGeometryOutputVertices" VkPhysicalDeviceLimits Source # 
type FieldType "maxGeometryOutputVertices" VkPhysicalDeviceLimits = Word32
type FieldType "maxGeometryShaderInvocations" VkPhysicalDeviceLimits Source # 
type FieldType "maxGeometryShaderInvocations" VkPhysicalDeviceLimits = Word32
type FieldType "maxGeometryTotalOutputComponents" VkPhysicalDeviceLimits Source # 
type FieldType "maxGeometryTotalOutputComponents" VkPhysicalDeviceLimits = Word32
type FieldType "maxImageArrayLayers" VkPhysicalDeviceLimits Source # 
type FieldType "maxImageArrayLayers" VkPhysicalDeviceLimits = Word32
type FieldType "maxImageDimension1D" VkPhysicalDeviceLimits Source # 
type FieldType "maxImageDimension1D" VkPhysicalDeviceLimits = Word32
type FieldType "maxImageDimension2D" VkPhysicalDeviceLimits Source # 
type FieldType "maxImageDimension2D" VkPhysicalDeviceLimits = Word32
type FieldType "maxImageDimension3D" VkPhysicalDeviceLimits Source # 
type FieldType "maxImageDimension3D" VkPhysicalDeviceLimits = Word32
type FieldType "maxImageDimensionCube" VkPhysicalDeviceLimits Source # 
type FieldType "maxImageDimensionCube" VkPhysicalDeviceLimits = Word32
type FieldType "maxInterpolationOffset" VkPhysicalDeviceLimits Source # 
type FieldType "maxInterpolationOffset" VkPhysicalDeviceLimits = Float
type FieldType "maxMemoryAllocationCount" VkPhysicalDeviceLimits Source # 
type FieldType "maxMemoryAllocationCount" VkPhysicalDeviceLimits = Word32
type FieldType "maxPerStageDescriptorInputAttachments" VkPhysicalDeviceLimits Source # 
type FieldType "maxPerStageDescriptorInputAttachments" VkPhysicalDeviceLimits = Word32
type FieldType "maxPerStageDescriptorSampledImages" VkPhysicalDeviceLimits Source # 
type FieldType "maxPerStageDescriptorSampledImages" VkPhysicalDeviceLimits = Word32
type FieldType "maxPerStageDescriptorSamplers" VkPhysicalDeviceLimits Source # 
type FieldType "maxPerStageDescriptorSamplers" VkPhysicalDeviceLimits = Word32
type FieldType "maxPerStageDescriptorStorageBuffers" VkPhysicalDeviceLimits Source # 
type FieldType "maxPerStageDescriptorStorageBuffers" VkPhysicalDeviceLimits = Word32
type FieldType "maxPerStageDescriptorStorageImages" VkPhysicalDeviceLimits Source # 
type FieldType "maxPerStageDescriptorStorageImages" VkPhysicalDeviceLimits = Word32
type FieldType "maxPerStageDescriptorUniformBuffers" VkPhysicalDeviceLimits Source # 
type FieldType "maxPerStageDescriptorUniformBuffers" VkPhysicalDeviceLimits = Word32
type FieldType "maxPerStageResources" VkPhysicalDeviceLimits Source # 
type FieldType "maxPerStageResources" VkPhysicalDeviceLimits = Word32
type FieldType "maxPushConstantsSize" VkPhysicalDeviceLimits Source # 
type FieldType "maxPushConstantsSize" VkPhysicalDeviceLimits = Word32
type FieldType "maxSampleMaskWords" VkPhysicalDeviceLimits Source # 
type FieldType "maxSampleMaskWords" VkPhysicalDeviceLimits = Word32
type FieldType "maxSamplerAllocationCount" VkPhysicalDeviceLimits Source # 
type FieldType "maxSamplerAllocationCount" VkPhysicalDeviceLimits = Word32
type FieldType "maxSamplerAnisotropy" VkPhysicalDeviceLimits Source # 
type FieldType "maxSamplerAnisotropy" VkPhysicalDeviceLimits = Float
type FieldType "maxSamplerLodBias" VkPhysicalDeviceLimits Source # 
type FieldType "maxSamplerLodBias" VkPhysicalDeviceLimits = Float
type FieldType "maxStorageBufferRange" VkPhysicalDeviceLimits Source # 
type FieldType "maxStorageBufferRange" VkPhysicalDeviceLimits = Word32
type FieldType "maxTessellationControlPerPatchOutputComponents" VkPhysicalDeviceLimits Source # 
type FieldType "maxTessellationControlPerPatchOutputComponents" VkPhysicalDeviceLimits = Word32
type FieldType "maxTessellationControlPerVertexInputComponents" VkPhysicalDeviceLimits Source # 
type FieldType "maxTessellationControlPerVertexInputComponents" VkPhysicalDeviceLimits = Word32
type FieldType "maxTessellationControlPerVertexOutputComponents" VkPhysicalDeviceLimits Source # 
type FieldType "maxTessellationControlPerVertexOutputComponents" VkPhysicalDeviceLimits = Word32
type FieldType "maxTessellationControlTotalOutputComponents" VkPhysicalDeviceLimits Source # 
type FieldType "maxTessellationControlTotalOutputComponents" VkPhysicalDeviceLimits = Word32
type FieldType "maxTessellationEvaluationInputComponents" VkPhysicalDeviceLimits Source # 
type FieldType "maxTessellationEvaluationInputComponents" VkPhysicalDeviceLimits = Word32
type FieldType "maxTessellationEvaluationOutputComponents" VkPhysicalDeviceLimits Source # 
type FieldType "maxTessellationEvaluationOutputComponents" VkPhysicalDeviceLimits = Word32
type FieldType "maxTessellationGenerationLevel" VkPhysicalDeviceLimits Source # 
type FieldType "maxTessellationGenerationLevel" VkPhysicalDeviceLimits = Word32
type FieldType "maxTessellationPatchSize" VkPhysicalDeviceLimits Source # 
type FieldType "maxTessellationPatchSize" VkPhysicalDeviceLimits = Word32
type FieldType "maxTexelBufferElements" VkPhysicalDeviceLimits Source # 
type FieldType "maxTexelBufferElements" VkPhysicalDeviceLimits = Word32
type FieldType "maxTexelGatherOffset" VkPhysicalDeviceLimits Source # 
type FieldType "maxTexelGatherOffset" VkPhysicalDeviceLimits = Word32
type FieldType "maxTexelOffset" VkPhysicalDeviceLimits Source # 
type FieldType "maxTexelOffset" VkPhysicalDeviceLimits = Word32
type FieldType "maxUniformBufferRange" VkPhysicalDeviceLimits Source # 
type FieldType "maxUniformBufferRange" VkPhysicalDeviceLimits = Word32
type FieldType "maxVertexInputAttributeOffset" VkPhysicalDeviceLimits Source # 
type FieldType "maxVertexInputAttributeOffset" VkPhysicalDeviceLimits = Word32
type FieldType "maxVertexInputAttributes" VkPhysicalDeviceLimits Source # 
type FieldType "maxVertexInputAttributes" VkPhysicalDeviceLimits = Word32
type FieldType "maxVertexInputBindingStride" VkPhysicalDeviceLimits Source # 
type FieldType "maxVertexInputBindingStride" VkPhysicalDeviceLimits = Word32
type FieldType "maxVertexInputBindings" VkPhysicalDeviceLimits Source # 
type FieldType "maxVertexInputBindings" VkPhysicalDeviceLimits = Word32
type FieldType "maxVertexOutputComponents" VkPhysicalDeviceLimits Source # 
type FieldType "maxVertexOutputComponents" VkPhysicalDeviceLimits = Word32
type FieldType "maxViewportDimensions" VkPhysicalDeviceLimits Source # 
type FieldType "maxViewportDimensions" VkPhysicalDeviceLimits = Word32
type FieldType "maxViewports" VkPhysicalDeviceLimits Source # 
type FieldType "minInterpolationOffset" VkPhysicalDeviceLimits Source # 
type FieldType "minInterpolationOffset" VkPhysicalDeviceLimits = Float
type FieldType "minMemoryMapAlignment" VkPhysicalDeviceLimits Source # 
type FieldType "minMemoryMapAlignment" VkPhysicalDeviceLimits = CSize
type FieldType "minStorageBufferOffsetAlignment" VkPhysicalDeviceLimits Source # 
type FieldType "minStorageBufferOffsetAlignment" VkPhysicalDeviceLimits = VkDeviceSize
type FieldType "minTexelBufferOffsetAlignment" VkPhysicalDeviceLimits Source # 
type FieldType "minTexelBufferOffsetAlignment" VkPhysicalDeviceLimits = VkDeviceSize
type FieldType "minTexelGatherOffset" VkPhysicalDeviceLimits Source # 
type FieldType "minTexelGatherOffset" VkPhysicalDeviceLimits = Int32
type FieldType "minTexelOffset" VkPhysicalDeviceLimits Source # 
type FieldType "minTexelOffset" VkPhysicalDeviceLimits = Int32
type FieldType "minUniformBufferOffsetAlignment" VkPhysicalDeviceLimits Source # 
type FieldType "minUniformBufferOffsetAlignment" VkPhysicalDeviceLimits = VkDeviceSize
type FieldType "mipmapPrecisionBits" VkPhysicalDeviceLimits Source # 
type FieldType "mipmapPrecisionBits" VkPhysicalDeviceLimits = Word32
type FieldType "nonCoherentAtomSize" VkPhysicalDeviceLimits Source # 
type FieldType "nonCoherentAtomSize" VkPhysicalDeviceLimits = VkDeviceSize
type FieldType "optimalBufferCopyOffsetAlignment" VkPhysicalDeviceLimits Source # 
type FieldType "optimalBufferCopyOffsetAlignment" VkPhysicalDeviceLimits = VkDeviceSize
type FieldType "optimalBufferCopyRowPitchAlignment" VkPhysicalDeviceLimits Source # 
type FieldType "optimalBufferCopyRowPitchAlignment" VkPhysicalDeviceLimits = VkDeviceSize
type FieldType "pointSizeGranularity" VkPhysicalDeviceLimits Source # 
type FieldType "pointSizeGranularity" VkPhysicalDeviceLimits = Float
type FieldType "pointSizeRange" VkPhysicalDeviceLimits Source # 
type FieldType "pointSizeRange" VkPhysicalDeviceLimits = Float
type FieldType "sampledImageColorSampleCounts" VkPhysicalDeviceLimits Source # 
type FieldType "sampledImageColorSampleCounts" VkPhysicalDeviceLimits = VkSampleCountFlags
type FieldType "sampledImageDepthSampleCounts" VkPhysicalDeviceLimits Source # 
type FieldType "sampledImageDepthSampleCounts" VkPhysicalDeviceLimits = VkSampleCountFlags
type FieldType "sampledImageIntegerSampleCounts" VkPhysicalDeviceLimits Source # 
type FieldType "sampledImageIntegerSampleCounts" VkPhysicalDeviceLimits = VkSampleCountFlags
type FieldType "sampledImageStencilSampleCounts" VkPhysicalDeviceLimits Source # 
type FieldType "sampledImageStencilSampleCounts" VkPhysicalDeviceLimits = VkSampleCountFlags
type FieldType "sparseAddressSpaceSize" VkPhysicalDeviceLimits Source # 
type FieldType "sparseAddressSpaceSize" VkPhysicalDeviceLimits = VkDeviceSize
type FieldType "standardSampleLocations" VkPhysicalDeviceLimits Source # 
type FieldType "standardSampleLocations" VkPhysicalDeviceLimits = VkBool32
type FieldType "storageImageSampleCounts" VkPhysicalDeviceLimits Source # 
type FieldType "storageImageSampleCounts" VkPhysicalDeviceLimits = VkSampleCountFlags
type FieldType "strictLines" VkPhysicalDeviceLimits Source # 
type FieldType "subPixelInterpolationOffsetBits" VkPhysicalDeviceLimits Source # 
type FieldType "subPixelInterpolationOffsetBits" VkPhysicalDeviceLimits = Word32
type FieldType "subPixelPrecisionBits" VkPhysicalDeviceLimits Source # 
type FieldType "subPixelPrecisionBits" VkPhysicalDeviceLimits = Word32
type FieldType "subTexelPrecisionBits" VkPhysicalDeviceLimits Source # 
type FieldType "subTexelPrecisionBits" VkPhysicalDeviceLimits = Word32
type FieldType "timestampComputeAndGraphics" VkPhysicalDeviceLimits Source # 
type FieldType "timestampComputeAndGraphics" VkPhysicalDeviceLimits = VkBool32
type FieldType "timestampPeriod" VkPhysicalDeviceLimits Source # 
type FieldType "timestampPeriod" VkPhysicalDeviceLimits = Float
type FieldType "viewportBoundsRange" VkPhysicalDeviceLimits Source # 
type FieldType "viewportBoundsRange" VkPhysicalDeviceLimits = Float
type FieldType "viewportSubPixelBits" VkPhysicalDeviceLimits Source # 
type FieldType "viewportSubPixelBits" VkPhysicalDeviceLimits = Word32
type FieldOptional "bufferImageGranularity" VkPhysicalDeviceLimits Source # 
type FieldOptional "bufferImageGranularity" VkPhysicalDeviceLimits = False
type FieldOptional "discreteQueuePriorities" VkPhysicalDeviceLimits Source # 
type FieldOptional "discreteQueuePriorities" VkPhysicalDeviceLimits = False
type FieldOptional "framebufferColorSampleCounts" VkPhysicalDeviceLimits Source # 
type FieldOptional "framebufferColorSampleCounts" VkPhysicalDeviceLimits = True
type FieldOptional "framebufferDepthSampleCounts" VkPhysicalDeviceLimits Source # 
type FieldOptional "framebufferDepthSampleCounts" VkPhysicalDeviceLimits = True
type FieldOptional "framebufferNoAttachmentsSampleCounts" VkPhysicalDeviceLimits Source # 
type FieldOptional "framebufferNoAttachmentsSampleCounts" VkPhysicalDeviceLimits = True
type FieldOptional "framebufferStencilSampleCounts" VkPhysicalDeviceLimits Source # 
type FieldOptional "framebufferStencilSampleCounts" VkPhysicalDeviceLimits = True
type FieldOptional "lineWidthGranularity" VkPhysicalDeviceLimits Source # 
type FieldOptional "lineWidthGranularity" VkPhysicalDeviceLimits = False
type FieldOptional "lineWidthRange" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxBoundDescriptorSets" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxBoundDescriptorSets" VkPhysicalDeviceLimits = False
type FieldOptional "maxClipDistances" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxClipDistances" VkPhysicalDeviceLimits = False
type FieldOptional "maxColorAttachments" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxColorAttachments" VkPhysicalDeviceLimits = False
type FieldOptional "maxCombinedClipAndCullDistances" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxCombinedClipAndCullDistances" VkPhysicalDeviceLimits = False
type FieldOptional "maxComputeSharedMemorySize" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxComputeSharedMemorySize" VkPhysicalDeviceLimits = False
type FieldOptional "maxComputeWorkGroupCount" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxComputeWorkGroupCount" VkPhysicalDeviceLimits = False
type FieldOptional "maxComputeWorkGroupInvocations" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxComputeWorkGroupInvocations" VkPhysicalDeviceLimits = False
type FieldOptional "maxComputeWorkGroupSize" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxComputeWorkGroupSize" VkPhysicalDeviceLimits = False
type FieldOptional "maxCullDistances" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxCullDistances" VkPhysicalDeviceLimits = False
type FieldOptional "maxDescriptorSetInputAttachments" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxDescriptorSetInputAttachments" VkPhysicalDeviceLimits = False
type FieldOptional "maxDescriptorSetSampledImages" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxDescriptorSetSampledImages" VkPhysicalDeviceLimits = False
type FieldOptional "maxDescriptorSetSamplers" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxDescriptorSetSamplers" VkPhysicalDeviceLimits = False
type FieldOptional "maxDescriptorSetStorageBuffers" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxDescriptorSetStorageBuffers" VkPhysicalDeviceLimits = False
type FieldOptional "maxDescriptorSetStorageBuffersDynamic" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxDescriptorSetStorageBuffersDynamic" VkPhysicalDeviceLimits = False
type FieldOptional "maxDescriptorSetStorageImages" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxDescriptorSetStorageImages" VkPhysicalDeviceLimits = False
type FieldOptional "maxDescriptorSetUniformBuffers" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxDescriptorSetUniformBuffers" VkPhysicalDeviceLimits = False
type FieldOptional "maxDescriptorSetUniformBuffersDynamic" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxDescriptorSetUniformBuffersDynamic" VkPhysicalDeviceLimits = False
type FieldOptional "maxDrawIndexedIndexValue" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxDrawIndexedIndexValue" VkPhysicalDeviceLimits = False
type FieldOptional "maxDrawIndirectCount" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxDrawIndirectCount" VkPhysicalDeviceLimits = False
type FieldOptional "maxFragmentCombinedOutputResources" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxFragmentCombinedOutputResources" VkPhysicalDeviceLimits = False
type FieldOptional "maxFragmentDualSrcAttachments" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxFragmentDualSrcAttachments" VkPhysicalDeviceLimits = False
type FieldOptional "maxFragmentInputComponents" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxFragmentInputComponents" VkPhysicalDeviceLimits = False
type FieldOptional "maxFragmentOutputAttachments" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxFragmentOutputAttachments" VkPhysicalDeviceLimits = False
type FieldOptional "maxFramebufferHeight" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxFramebufferHeight" VkPhysicalDeviceLimits = False
type FieldOptional "maxFramebufferLayers" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxFramebufferLayers" VkPhysicalDeviceLimits = False
type FieldOptional "maxFramebufferWidth" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxFramebufferWidth" VkPhysicalDeviceLimits = False
type FieldOptional "maxGeometryInputComponents" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxGeometryInputComponents" VkPhysicalDeviceLimits = False
type FieldOptional "maxGeometryOutputComponents" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxGeometryOutputComponents" VkPhysicalDeviceLimits = False
type FieldOptional "maxGeometryOutputVertices" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxGeometryOutputVertices" VkPhysicalDeviceLimits = False
type FieldOptional "maxGeometryShaderInvocations" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxGeometryShaderInvocations" VkPhysicalDeviceLimits = False
type FieldOptional "maxGeometryTotalOutputComponents" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxGeometryTotalOutputComponents" VkPhysicalDeviceLimits = False
type FieldOptional "maxImageArrayLayers" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxImageArrayLayers" VkPhysicalDeviceLimits = False
type FieldOptional "maxImageDimension1D" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxImageDimension1D" VkPhysicalDeviceLimits = False
type FieldOptional "maxImageDimension2D" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxImageDimension2D" VkPhysicalDeviceLimits = False
type FieldOptional "maxImageDimension3D" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxImageDimension3D" VkPhysicalDeviceLimits = False
type FieldOptional "maxImageDimensionCube" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxImageDimensionCube" VkPhysicalDeviceLimits = False
type FieldOptional "maxInterpolationOffset" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxInterpolationOffset" VkPhysicalDeviceLimits = False
type FieldOptional "maxMemoryAllocationCount" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxMemoryAllocationCount" VkPhysicalDeviceLimits = False
type FieldOptional "maxPerStageDescriptorInputAttachments" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxPerStageDescriptorInputAttachments" VkPhysicalDeviceLimits = False
type FieldOptional "maxPerStageDescriptorSampledImages" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxPerStageDescriptorSampledImages" VkPhysicalDeviceLimits = False
type FieldOptional "maxPerStageDescriptorSamplers" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxPerStageDescriptorSamplers" VkPhysicalDeviceLimits = False
type FieldOptional "maxPerStageDescriptorStorageBuffers" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxPerStageDescriptorStorageBuffers" VkPhysicalDeviceLimits = False
type FieldOptional "maxPerStageDescriptorStorageImages" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxPerStageDescriptorStorageImages" VkPhysicalDeviceLimits = False
type FieldOptional "maxPerStageDescriptorUniformBuffers" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxPerStageDescriptorUniformBuffers" VkPhysicalDeviceLimits = False
type FieldOptional "maxPerStageResources" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxPerStageResources" VkPhysicalDeviceLimits = False
type FieldOptional "maxPushConstantsSize" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxPushConstantsSize" VkPhysicalDeviceLimits = False
type FieldOptional "maxSampleMaskWords" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxSampleMaskWords" VkPhysicalDeviceLimits = False
type FieldOptional "maxSamplerAllocationCount" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxSamplerAllocationCount" VkPhysicalDeviceLimits = False
type FieldOptional "maxSamplerAnisotropy" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxSamplerAnisotropy" VkPhysicalDeviceLimits = False
type FieldOptional "maxSamplerLodBias" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxSamplerLodBias" VkPhysicalDeviceLimits = False
type FieldOptional "maxStorageBufferRange" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxStorageBufferRange" VkPhysicalDeviceLimits = False
type FieldOptional "maxTessellationControlPerPatchOutputComponents" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxTessellationControlPerPatchOutputComponents" VkPhysicalDeviceLimits = False
type FieldOptional "maxTessellationControlPerVertexInputComponents" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxTessellationControlPerVertexInputComponents" VkPhysicalDeviceLimits = False
type FieldOptional "maxTessellationControlPerVertexOutputComponents" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxTessellationControlPerVertexOutputComponents" VkPhysicalDeviceLimits = False
type FieldOptional "maxTessellationControlTotalOutputComponents" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxTessellationControlTotalOutputComponents" VkPhysicalDeviceLimits = False
type FieldOptional "maxTessellationEvaluationInputComponents" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxTessellationEvaluationInputComponents" VkPhysicalDeviceLimits = False
type FieldOptional "maxTessellationEvaluationOutputComponents" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxTessellationEvaluationOutputComponents" VkPhysicalDeviceLimits = False
type FieldOptional "maxTessellationGenerationLevel" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxTessellationGenerationLevel" VkPhysicalDeviceLimits = False
type FieldOptional "maxTessellationPatchSize" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxTessellationPatchSize" VkPhysicalDeviceLimits = False
type FieldOptional "maxTexelBufferElements" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxTexelBufferElements" VkPhysicalDeviceLimits = False
type FieldOptional "maxTexelGatherOffset" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxTexelGatherOffset" VkPhysicalDeviceLimits = False
type FieldOptional "maxTexelOffset" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxUniformBufferRange" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxUniformBufferRange" VkPhysicalDeviceLimits = False
type FieldOptional "maxVertexInputAttributeOffset" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxVertexInputAttributeOffset" VkPhysicalDeviceLimits = False
type FieldOptional "maxVertexInputAttributes" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxVertexInputAttributes" VkPhysicalDeviceLimits = False
type FieldOptional "maxVertexInputBindingStride" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxVertexInputBindingStride" VkPhysicalDeviceLimits = False
type FieldOptional "maxVertexInputBindings" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxVertexInputBindings" VkPhysicalDeviceLimits = False
type FieldOptional "maxVertexOutputComponents" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxVertexOutputComponents" VkPhysicalDeviceLimits = False
type FieldOptional "maxViewportDimensions" VkPhysicalDeviceLimits Source # 
type FieldOptional "maxViewportDimensions" VkPhysicalDeviceLimits = False
type FieldOptional "maxViewports" VkPhysicalDeviceLimits Source # 
type FieldOptional "minInterpolationOffset" VkPhysicalDeviceLimits Source # 
type FieldOptional "minInterpolationOffset" VkPhysicalDeviceLimits = False
type FieldOptional "minMemoryMapAlignment" VkPhysicalDeviceLimits Source # 
type FieldOptional "minMemoryMapAlignment" VkPhysicalDeviceLimits = False
type FieldOptional "minStorageBufferOffsetAlignment" VkPhysicalDeviceLimits Source # 
type FieldOptional "minStorageBufferOffsetAlignment" VkPhysicalDeviceLimits = False
type FieldOptional "minTexelBufferOffsetAlignment" VkPhysicalDeviceLimits Source # 
type FieldOptional "minTexelBufferOffsetAlignment" VkPhysicalDeviceLimits = False
type FieldOptional "minTexelGatherOffset" VkPhysicalDeviceLimits Source # 
type FieldOptional "minTexelGatherOffset" VkPhysicalDeviceLimits = False
type FieldOptional "minTexelOffset" VkPhysicalDeviceLimits Source # 
type FieldOptional "minUniformBufferOffsetAlignment" VkPhysicalDeviceLimits Source # 
type FieldOptional "minUniformBufferOffsetAlignment" VkPhysicalDeviceLimits = False
type FieldOptional "mipmapPrecisionBits" VkPhysicalDeviceLimits Source # 
type FieldOptional "mipmapPrecisionBits" VkPhysicalDeviceLimits = False
type FieldOptional "nonCoherentAtomSize" VkPhysicalDeviceLimits Source # 
type FieldOptional "nonCoherentAtomSize" VkPhysicalDeviceLimits = False
type FieldOptional "optimalBufferCopyOffsetAlignment" VkPhysicalDeviceLimits Source # 
type FieldOptional "optimalBufferCopyOffsetAlignment" VkPhysicalDeviceLimits = False
type FieldOptional "optimalBufferCopyRowPitchAlignment" VkPhysicalDeviceLimits Source # 
type FieldOptional "optimalBufferCopyRowPitchAlignment" VkPhysicalDeviceLimits = False
type FieldOptional "pointSizeGranularity" VkPhysicalDeviceLimits Source # 
type FieldOptional "pointSizeGranularity" VkPhysicalDeviceLimits = False
type FieldOptional "pointSizeRange" VkPhysicalDeviceLimits Source # 
type FieldOptional "sampledImageColorSampleCounts" VkPhysicalDeviceLimits Source # 
type FieldOptional "sampledImageColorSampleCounts" VkPhysicalDeviceLimits = True
type FieldOptional "sampledImageDepthSampleCounts" VkPhysicalDeviceLimits Source # 
type FieldOptional "sampledImageDepthSampleCounts" VkPhysicalDeviceLimits = True
type FieldOptional "sampledImageIntegerSampleCounts" VkPhysicalDeviceLimits Source # 
type FieldOptional "sampledImageIntegerSampleCounts" VkPhysicalDeviceLimits = True
type FieldOptional "sampledImageStencilSampleCounts" VkPhysicalDeviceLimits Source # 
type FieldOptional "sampledImageStencilSampleCounts" VkPhysicalDeviceLimits = True
type FieldOptional "sparseAddressSpaceSize" VkPhysicalDeviceLimits Source # 
type FieldOptional "sparseAddressSpaceSize" VkPhysicalDeviceLimits = False
type FieldOptional "standardSampleLocations" VkPhysicalDeviceLimits Source # 
type FieldOptional "standardSampleLocations" VkPhysicalDeviceLimits = False
type FieldOptional "storageImageSampleCounts" VkPhysicalDeviceLimits Source # 
type FieldOptional "storageImageSampleCounts" VkPhysicalDeviceLimits = True
type FieldOptional "strictLines" VkPhysicalDeviceLimits Source # 
type FieldOptional "subPixelInterpolationOffsetBits" VkPhysicalDeviceLimits Source # 
type FieldOptional "subPixelInterpolationOffsetBits" VkPhysicalDeviceLimits = False
type FieldOptional "subPixelPrecisionBits" VkPhysicalDeviceLimits Source # 
type FieldOptional "subPixelPrecisionBits" VkPhysicalDeviceLimits = False
type FieldOptional "subTexelPrecisionBits" VkPhysicalDeviceLimits Source # 
type FieldOptional "subTexelPrecisionBits" VkPhysicalDeviceLimits = False
type FieldOptional "timestampComputeAndGraphics" VkPhysicalDeviceLimits Source # 
type FieldOptional "timestampComputeAndGraphics" VkPhysicalDeviceLimits = False
type FieldOptional "timestampPeriod" VkPhysicalDeviceLimits Source # 
type FieldOptional "timestampPeriod" VkPhysicalDeviceLimits = False
type FieldOptional "viewportBoundsRange" VkPhysicalDeviceLimits Source # 
type FieldOptional "viewportBoundsRange" VkPhysicalDeviceLimits = False
type FieldOptional "viewportSubPixelBits" VkPhysicalDeviceLimits Source # 
type FieldOptional "viewportSubPixelBits" VkPhysicalDeviceLimits = False
type FieldOffset "bufferImageGranularity" VkPhysicalDeviceLimits Source # 
type FieldOffset "bufferImageGranularity" VkPhysicalDeviceLimits = 48
type FieldOffset "discreteQueuePriorities" VkPhysicalDeviceLimits Source # 
type FieldOffset "discreteQueuePriorities" VkPhysicalDeviceLimits = 440
type FieldOffset "framebufferColorSampleCounts" VkPhysicalDeviceLimits Source # 
type FieldOffset "framebufferColorSampleCounts" VkPhysicalDeviceLimits = 376
type FieldOffset "framebufferDepthSampleCounts" VkPhysicalDeviceLimits Source # 
type FieldOffset "framebufferDepthSampleCounts" VkPhysicalDeviceLimits = 380
type FieldOffset "framebufferNoAttachmentsSampleCounts" VkPhysicalDeviceLimits Source # 
type FieldOffset "framebufferNoAttachmentsSampleCounts" VkPhysicalDeviceLimits = 388
type FieldOffset "framebufferStencilSampleCounts" VkPhysicalDeviceLimits Source # 
type FieldOffset "framebufferStencilSampleCounts" VkPhysicalDeviceLimits = 384
type FieldOffset "lineWidthGranularity" VkPhysicalDeviceLimits Source # 
type FieldOffset "lineWidthGranularity" VkPhysicalDeviceLimits = 464
type FieldOffset "lineWidthRange" VkPhysicalDeviceLimits Source # 
type FieldOffset "lineWidthRange" VkPhysicalDeviceLimits = 452
type FieldOffset "maxBoundDescriptorSets" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxBoundDescriptorSets" VkPhysicalDeviceLimits = 64
type FieldOffset "maxClipDistances" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxClipDistances" VkPhysicalDeviceLimits = 428
type FieldOffset "maxColorAttachments" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxColorAttachments" VkPhysicalDeviceLimits = 392
type FieldOffset "maxCombinedClipAndCullDistances" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxCombinedClipAndCullDistances" VkPhysicalDeviceLimits = 436
type FieldOffset "maxComputeSharedMemorySize" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxComputeSharedMemorySize" VkPhysicalDeviceLimits = 216
type FieldOffset "maxComputeWorkGroupCount" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxComputeWorkGroupCount" VkPhysicalDeviceLimits = 220
type FieldOffset "maxComputeWorkGroupInvocations" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxComputeWorkGroupInvocations" VkPhysicalDeviceLimits = 232
type FieldOffset "maxComputeWorkGroupSize" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxComputeWorkGroupSize" VkPhysicalDeviceLimits = 236
type FieldOffset "maxCullDistances" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxCullDistances" VkPhysicalDeviceLimits = 432
type FieldOffset "maxDescriptorSetInputAttachments" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxDescriptorSetInputAttachments" VkPhysicalDeviceLimits = 124
type FieldOffset "maxDescriptorSetSampledImages" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxDescriptorSetSampledImages" VkPhysicalDeviceLimits = 116
type FieldOffset "maxDescriptorSetSamplers" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxDescriptorSetSamplers" VkPhysicalDeviceLimits = 96
type FieldOffset "maxDescriptorSetStorageBuffers" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxDescriptorSetStorageBuffers" VkPhysicalDeviceLimits = 108
type FieldOffset "maxDescriptorSetStorageBuffersDynamic" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxDescriptorSetStorageBuffersDynamic" VkPhysicalDeviceLimits = 112
type FieldOffset "maxDescriptorSetStorageImages" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxDescriptorSetStorageImages" VkPhysicalDeviceLimits = 120
type FieldOffset "maxDescriptorSetUniformBuffers" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxDescriptorSetUniformBuffers" VkPhysicalDeviceLimits = 100
type FieldOffset "maxDescriptorSetUniformBuffersDynamic" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxDescriptorSetUniformBuffersDynamic" VkPhysicalDeviceLimits = 104
type FieldOffset "maxDrawIndexedIndexValue" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxDrawIndexedIndexValue" VkPhysicalDeviceLimits = 260
type FieldOffset "maxDrawIndirectCount" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxDrawIndirectCount" VkPhysicalDeviceLimits = 264
type FieldOffset "maxFragmentCombinedOutputResources" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxFragmentCombinedOutputResources" VkPhysicalDeviceLimits = 212
type FieldOffset "maxFragmentDualSrcAttachments" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxFragmentDualSrcAttachments" VkPhysicalDeviceLimits = 208
type FieldOffset "maxFragmentInputComponents" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxFragmentInputComponents" VkPhysicalDeviceLimits = 200
type FieldOffset "maxFragmentOutputAttachments" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxFragmentOutputAttachments" VkPhysicalDeviceLimits = 204
type FieldOffset "maxFramebufferHeight" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxFramebufferHeight" VkPhysicalDeviceLimits = 368
type FieldOffset "maxFramebufferLayers" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxFramebufferLayers" VkPhysicalDeviceLimits = 372
type FieldOffset "maxFramebufferWidth" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxFramebufferWidth" VkPhysicalDeviceLimits = 364
type FieldOffset "maxGeometryInputComponents" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxGeometryInputComponents" VkPhysicalDeviceLimits = 184
type FieldOffset "maxGeometryOutputComponents" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxGeometryOutputComponents" VkPhysicalDeviceLimits = 188
type FieldOffset "maxGeometryOutputVertices" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxGeometryOutputVertices" VkPhysicalDeviceLimits = 192
type FieldOffset "maxGeometryShaderInvocations" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxGeometryShaderInvocations" VkPhysicalDeviceLimits = 180
type FieldOffset "maxGeometryTotalOutputComponents" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxGeometryTotalOutputComponents" VkPhysicalDeviceLimits = 196
type FieldOffset "maxImageArrayLayers" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxImageArrayLayers" VkPhysicalDeviceLimits = 16
type FieldOffset "maxImageDimension1D" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxImageDimension1D" VkPhysicalDeviceLimits = 0
type FieldOffset "maxImageDimension2D" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxImageDimension2D" VkPhysicalDeviceLimits = 4
type FieldOffset "maxImageDimension3D" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxImageDimension3D" VkPhysicalDeviceLimits = 8
type FieldOffset "maxImageDimensionCube" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxImageDimensionCube" VkPhysicalDeviceLimits = 12
type FieldOffset "maxInterpolationOffset" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxInterpolationOffset" VkPhysicalDeviceLimits = 356
type FieldOffset "maxMemoryAllocationCount" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxMemoryAllocationCount" VkPhysicalDeviceLimits = 36
type FieldOffset "maxPerStageDescriptorInputAttachments" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxPerStageDescriptorInputAttachments" VkPhysicalDeviceLimits = 88
type FieldOffset "maxPerStageDescriptorSampledImages" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxPerStageDescriptorSampledImages" VkPhysicalDeviceLimits = 80
type FieldOffset "maxPerStageDescriptorSamplers" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxPerStageDescriptorSamplers" VkPhysicalDeviceLimits = 68
type FieldOffset "maxPerStageDescriptorStorageBuffers" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxPerStageDescriptorStorageBuffers" VkPhysicalDeviceLimits = 76
type FieldOffset "maxPerStageDescriptorStorageImages" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxPerStageDescriptorStorageImages" VkPhysicalDeviceLimits = 84
type FieldOffset "maxPerStageDescriptorUniformBuffers" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxPerStageDescriptorUniformBuffers" VkPhysicalDeviceLimits = 72
type FieldOffset "maxPerStageResources" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxPerStageResources" VkPhysicalDeviceLimits = 92
type FieldOffset "maxPushConstantsSize" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxPushConstantsSize" VkPhysicalDeviceLimits = 32
type FieldOffset "maxSampleMaskWords" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxSampleMaskWords" VkPhysicalDeviceLimits = 416
type FieldOffset "maxSamplerAllocationCount" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxSamplerAllocationCount" VkPhysicalDeviceLimits = 40
type FieldOffset "maxSamplerAnisotropy" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxSamplerAnisotropy" VkPhysicalDeviceLimits = 272
type FieldOffset "maxSamplerLodBias" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxSamplerLodBias" VkPhysicalDeviceLimits = 268
type FieldOffset "maxStorageBufferRange" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxStorageBufferRange" VkPhysicalDeviceLimits = 28
type FieldOffset "maxTessellationControlPerPatchOutputComponents" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxTessellationControlPerPatchOutputComponents" VkPhysicalDeviceLimits = 164
type FieldOffset "maxTessellationControlPerVertexInputComponents" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxTessellationControlPerVertexInputComponents" VkPhysicalDeviceLimits = 156
type FieldOffset "maxTessellationControlPerVertexOutputComponents" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxTessellationControlPerVertexOutputComponents" VkPhysicalDeviceLimits = 160
type FieldOffset "maxTessellationControlTotalOutputComponents" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxTessellationControlTotalOutputComponents" VkPhysicalDeviceLimits = 168
type FieldOffset "maxTessellationEvaluationInputComponents" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxTessellationEvaluationInputComponents" VkPhysicalDeviceLimits = 172
type FieldOffset "maxTessellationEvaluationOutputComponents" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxTessellationEvaluationOutputComponents" VkPhysicalDeviceLimits = 176
type FieldOffset "maxTessellationGenerationLevel" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxTessellationGenerationLevel" VkPhysicalDeviceLimits = 148
type FieldOffset "maxTessellationPatchSize" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxTessellationPatchSize" VkPhysicalDeviceLimits = 152
type FieldOffset "maxTexelBufferElements" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxTexelBufferElements" VkPhysicalDeviceLimits = 20
type FieldOffset "maxTexelGatherOffset" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxTexelGatherOffset" VkPhysicalDeviceLimits = 348
type FieldOffset "maxTexelOffset" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxTexelOffset" VkPhysicalDeviceLimits = 340
type FieldOffset "maxUniformBufferRange" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxUniformBufferRange" VkPhysicalDeviceLimits = 24
type FieldOffset "maxVertexInputAttributeOffset" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxVertexInputAttributeOffset" VkPhysicalDeviceLimits = 136
type FieldOffset "maxVertexInputAttributes" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxVertexInputAttributes" VkPhysicalDeviceLimits = 128
type FieldOffset "maxVertexInputBindingStride" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxVertexInputBindingStride" VkPhysicalDeviceLimits = 140
type FieldOffset "maxVertexInputBindings" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxVertexInputBindings" VkPhysicalDeviceLimits = 132
type FieldOffset "maxVertexOutputComponents" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxVertexOutputComponents" VkPhysicalDeviceLimits = 144
type FieldOffset "maxViewportDimensions" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxViewportDimensions" VkPhysicalDeviceLimits = 280
type FieldOffset "maxViewports" VkPhysicalDeviceLimits Source # 
type FieldOffset "maxViewports" VkPhysicalDeviceLimits = 276
type FieldOffset "minInterpolationOffset" VkPhysicalDeviceLimits Source # 
type FieldOffset "minInterpolationOffset" VkPhysicalDeviceLimits = 352
type FieldOffset "minMemoryMapAlignment" VkPhysicalDeviceLimits Source # 
type FieldOffset "minMemoryMapAlignment" VkPhysicalDeviceLimits = 304
type FieldOffset "minStorageBufferOffsetAlignment" VkPhysicalDeviceLimits Source # 
type FieldOffset "minStorageBufferOffsetAlignment" VkPhysicalDeviceLimits = 328
type FieldOffset "minTexelBufferOffsetAlignment" VkPhysicalDeviceLimits Source # 
type FieldOffset "minTexelBufferOffsetAlignment" VkPhysicalDeviceLimits = 312
type FieldOffset "minTexelGatherOffset" VkPhysicalDeviceLimits Source # 
type FieldOffset "minTexelGatherOffset" VkPhysicalDeviceLimits = 344
type FieldOffset "minTexelOffset" VkPhysicalDeviceLimits Source # 
type FieldOffset "minTexelOffset" VkPhysicalDeviceLimits = 336
type FieldOffset "minUniformBufferOffsetAlignment" VkPhysicalDeviceLimits Source # 
type FieldOffset "minUniformBufferOffsetAlignment" VkPhysicalDeviceLimits = 320
type FieldOffset "mipmapPrecisionBits" VkPhysicalDeviceLimits Source # 
type FieldOffset "mipmapPrecisionBits" VkPhysicalDeviceLimits = 256
type FieldOffset "nonCoherentAtomSize" VkPhysicalDeviceLimits Source # 
type FieldOffset "nonCoherentAtomSize" VkPhysicalDeviceLimits = 496
type FieldOffset "optimalBufferCopyOffsetAlignment" VkPhysicalDeviceLimits Source # 
type FieldOffset "optimalBufferCopyOffsetAlignment" VkPhysicalDeviceLimits = 480
type FieldOffset "optimalBufferCopyRowPitchAlignment" VkPhysicalDeviceLimits Source # 
type FieldOffset "optimalBufferCopyRowPitchAlignment" VkPhysicalDeviceLimits = 488
type FieldOffset "pointSizeGranularity" VkPhysicalDeviceLimits Source # 
type FieldOffset "pointSizeGranularity" VkPhysicalDeviceLimits = 460
type FieldOffset "pointSizeRange" VkPhysicalDeviceLimits Source # 
type FieldOffset "pointSizeRange" VkPhysicalDeviceLimits = 444
type FieldOffset "sampledImageColorSampleCounts" VkPhysicalDeviceLimits Source # 
type FieldOffset "sampledImageColorSampleCounts" VkPhysicalDeviceLimits = 396
type FieldOffset "sampledImageDepthSampleCounts" VkPhysicalDeviceLimits Source # 
type FieldOffset "sampledImageDepthSampleCounts" VkPhysicalDeviceLimits = 404
type FieldOffset "sampledImageIntegerSampleCounts" VkPhysicalDeviceLimits Source # 
type FieldOffset "sampledImageIntegerSampleCounts" VkPhysicalDeviceLimits = 400
type FieldOffset "sampledImageStencilSampleCounts" VkPhysicalDeviceLimits Source # 
type FieldOffset "sampledImageStencilSampleCounts" VkPhysicalDeviceLimits = 408
type FieldOffset "sparseAddressSpaceSize" VkPhysicalDeviceLimits Source # 
type FieldOffset "sparseAddressSpaceSize" VkPhysicalDeviceLimits = 56
type FieldOffset "standardSampleLocations" VkPhysicalDeviceLimits Source # 
type FieldOffset "standardSampleLocations" VkPhysicalDeviceLimits = 472
type FieldOffset "storageImageSampleCounts" VkPhysicalDeviceLimits Source # 
type FieldOffset "storageImageSampleCounts" VkPhysicalDeviceLimits = 412
type FieldOffset "strictLines" VkPhysicalDeviceLimits Source # 
type FieldOffset "strictLines" VkPhysicalDeviceLimits = 468
type FieldOffset "subPixelInterpolationOffsetBits" VkPhysicalDeviceLimits Source # 
type FieldOffset "subPixelInterpolationOffsetBits" VkPhysicalDeviceLimits = 360
type FieldOffset "subPixelPrecisionBits" VkPhysicalDeviceLimits Source # 
type FieldOffset "subPixelPrecisionBits" VkPhysicalDeviceLimits = 248
type FieldOffset "subTexelPrecisionBits" VkPhysicalDeviceLimits Source # 
type FieldOffset "subTexelPrecisionBits" VkPhysicalDeviceLimits = 252
type FieldOffset "timestampComputeAndGraphics" VkPhysicalDeviceLimits Source # 
type FieldOffset "timestampComputeAndGraphics" VkPhysicalDeviceLimits = 420
type FieldOffset "timestampPeriod" VkPhysicalDeviceLimits Source # 
type FieldOffset "timestampPeriod" VkPhysicalDeviceLimits = 424
type FieldOffset "viewportBoundsRange" VkPhysicalDeviceLimits Source # 
type FieldOffset "viewportBoundsRange" VkPhysicalDeviceLimits = 288
type FieldOffset "viewportSubPixelBits" VkPhysicalDeviceLimits Source # 
type FieldOffset "viewportSubPixelBits" VkPhysicalDeviceLimits = 296
type FieldIsArray "bufferImageGranularity" VkPhysicalDeviceLimits Source # 
type FieldIsArray "bufferImageGranularity" VkPhysicalDeviceLimits = False
type FieldIsArray "discreteQueuePriorities" VkPhysicalDeviceLimits Source # 
type FieldIsArray "discreteQueuePriorities" VkPhysicalDeviceLimits = False
type FieldIsArray "framebufferColorSampleCounts" VkPhysicalDeviceLimits Source # 
type FieldIsArray "framebufferColorSampleCounts" VkPhysicalDeviceLimits = False
type FieldIsArray "framebufferDepthSampleCounts" VkPhysicalDeviceLimits Source # 
type FieldIsArray "framebufferDepthSampleCounts" VkPhysicalDeviceLimits = False
type FieldIsArray "framebufferNoAttachmentsSampleCounts" VkPhysicalDeviceLimits Source # 
type FieldIsArray "framebufferNoAttachmentsSampleCounts" VkPhysicalDeviceLimits = False
type FieldIsArray "framebufferStencilSampleCounts" VkPhysicalDeviceLimits Source # 
type FieldIsArray "framebufferStencilSampleCounts" VkPhysicalDeviceLimits = False
type FieldIsArray "lineWidthGranularity" VkPhysicalDeviceLimits Source # 
type FieldIsArray "lineWidthGranularity" VkPhysicalDeviceLimits = False
type FieldIsArray "lineWidthRange" VkPhysicalDeviceLimits Source # 
type FieldIsArray "lineWidthRange" VkPhysicalDeviceLimits = True
type FieldIsArray "maxBoundDescriptorSets" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxBoundDescriptorSets" VkPhysicalDeviceLimits = False
type FieldIsArray "maxClipDistances" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxClipDistances" VkPhysicalDeviceLimits = False
type FieldIsArray "maxColorAttachments" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxColorAttachments" VkPhysicalDeviceLimits = False
type FieldIsArray "maxCombinedClipAndCullDistances" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxCombinedClipAndCullDistances" VkPhysicalDeviceLimits = False
type FieldIsArray "maxComputeSharedMemorySize" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxComputeSharedMemorySize" VkPhysicalDeviceLimits = False
type FieldIsArray "maxComputeWorkGroupCount" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxComputeWorkGroupCount" VkPhysicalDeviceLimits = True
type FieldIsArray "maxComputeWorkGroupInvocations" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxComputeWorkGroupInvocations" VkPhysicalDeviceLimits = False
type FieldIsArray "maxComputeWorkGroupSize" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxComputeWorkGroupSize" VkPhysicalDeviceLimits = True
type FieldIsArray "maxCullDistances" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxCullDistances" VkPhysicalDeviceLimits = False
type FieldIsArray "maxDescriptorSetInputAttachments" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxDescriptorSetInputAttachments" VkPhysicalDeviceLimits = False
type FieldIsArray "maxDescriptorSetSampledImages" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxDescriptorSetSampledImages" VkPhysicalDeviceLimits = False
type FieldIsArray "maxDescriptorSetSamplers" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxDescriptorSetSamplers" VkPhysicalDeviceLimits = False
type FieldIsArray "maxDescriptorSetStorageBuffers" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxDescriptorSetStorageBuffers" VkPhysicalDeviceLimits = False
type FieldIsArray "maxDescriptorSetStorageBuffersDynamic" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxDescriptorSetStorageBuffersDynamic" VkPhysicalDeviceLimits = False
type FieldIsArray "maxDescriptorSetStorageImages" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxDescriptorSetStorageImages" VkPhysicalDeviceLimits = False
type FieldIsArray "maxDescriptorSetUniformBuffers" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxDescriptorSetUniformBuffers" VkPhysicalDeviceLimits = False
type FieldIsArray "maxDescriptorSetUniformBuffersDynamic" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxDescriptorSetUniformBuffersDynamic" VkPhysicalDeviceLimits = False
type FieldIsArray "maxDrawIndexedIndexValue" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxDrawIndexedIndexValue" VkPhysicalDeviceLimits = False
type FieldIsArray "maxDrawIndirectCount" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxDrawIndirectCount" VkPhysicalDeviceLimits = False
type FieldIsArray "maxFragmentCombinedOutputResources" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxFragmentCombinedOutputResources" VkPhysicalDeviceLimits = False
type FieldIsArray "maxFragmentDualSrcAttachments" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxFragmentDualSrcAttachments" VkPhysicalDeviceLimits = False
type FieldIsArray "maxFragmentInputComponents" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxFragmentInputComponents" VkPhysicalDeviceLimits = False
type FieldIsArray "maxFragmentOutputAttachments" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxFragmentOutputAttachments" VkPhysicalDeviceLimits = False
type FieldIsArray "maxFramebufferHeight" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxFramebufferHeight" VkPhysicalDeviceLimits = False
type FieldIsArray "maxFramebufferLayers" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxFramebufferLayers" VkPhysicalDeviceLimits = False
type FieldIsArray "maxFramebufferWidth" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxFramebufferWidth" VkPhysicalDeviceLimits = False
type FieldIsArray "maxGeometryInputComponents" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxGeometryInputComponents" VkPhysicalDeviceLimits = False
type FieldIsArray "maxGeometryOutputComponents" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxGeometryOutputComponents" VkPhysicalDeviceLimits = False
type FieldIsArray "maxGeometryOutputVertices" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxGeometryOutputVertices" VkPhysicalDeviceLimits = False
type FieldIsArray "maxGeometryShaderInvocations" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxGeometryShaderInvocations" VkPhysicalDeviceLimits = False
type FieldIsArray "maxGeometryTotalOutputComponents" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxGeometryTotalOutputComponents" VkPhysicalDeviceLimits = False
type FieldIsArray "maxImageArrayLayers" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxImageArrayLayers" VkPhysicalDeviceLimits = False
type FieldIsArray "maxImageDimension1D" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxImageDimension1D" VkPhysicalDeviceLimits = False
type FieldIsArray "maxImageDimension2D" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxImageDimension2D" VkPhysicalDeviceLimits = False
type FieldIsArray "maxImageDimension3D" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxImageDimension3D" VkPhysicalDeviceLimits = False
type FieldIsArray "maxImageDimensionCube" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxImageDimensionCube" VkPhysicalDeviceLimits = False
type FieldIsArray "maxInterpolationOffset" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxInterpolationOffset" VkPhysicalDeviceLimits = False
type FieldIsArray "maxMemoryAllocationCount" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxMemoryAllocationCount" VkPhysicalDeviceLimits = False
type FieldIsArray "maxPerStageDescriptorInputAttachments" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxPerStageDescriptorInputAttachments" VkPhysicalDeviceLimits = False
type FieldIsArray "maxPerStageDescriptorSampledImages" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxPerStageDescriptorSampledImages" VkPhysicalDeviceLimits = False
type FieldIsArray "maxPerStageDescriptorSamplers" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxPerStageDescriptorSamplers" VkPhysicalDeviceLimits = False
type FieldIsArray "maxPerStageDescriptorStorageBuffers" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxPerStageDescriptorStorageBuffers" VkPhysicalDeviceLimits = False
type FieldIsArray "maxPerStageDescriptorStorageImages" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxPerStageDescriptorStorageImages" VkPhysicalDeviceLimits = False
type FieldIsArray "maxPerStageDescriptorUniformBuffers" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxPerStageDescriptorUniformBuffers" VkPhysicalDeviceLimits = False
type FieldIsArray "maxPerStageResources" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxPerStageResources" VkPhysicalDeviceLimits = False
type FieldIsArray "maxPushConstantsSize" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxPushConstantsSize" VkPhysicalDeviceLimits = False
type FieldIsArray "maxSampleMaskWords" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxSampleMaskWords" VkPhysicalDeviceLimits = False
type FieldIsArray "maxSamplerAllocationCount" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxSamplerAllocationCount" VkPhysicalDeviceLimits = False
type FieldIsArray "maxSamplerAnisotropy" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxSamplerAnisotropy" VkPhysicalDeviceLimits = False
type FieldIsArray "maxSamplerLodBias" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxSamplerLodBias" VkPhysicalDeviceLimits = False
type FieldIsArray "maxStorageBufferRange" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxStorageBufferRange" VkPhysicalDeviceLimits = False
type FieldIsArray "maxTessellationControlPerPatchOutputComponents" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxTessellationControlPerPatchOutputComponents" VkPhysicalDeviceLimits = False
type FieldIsArray "maxTessellationControlPerVertexInputComponents" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxTessellationControlPerVertexInputComponents" VkPhysicalDeviceLimits = False
type FieldIsArray "maxTessellationControlPerVertexOutputComponents" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxTessellationControlPerVertexOutputComponents" VkPhysicalDeviceLimits = False
type FieldIsArray "maxTessellationControlTotalOutputComponents" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxTessellationControlTotalOutputComponents" VkPhysicalDeviceLimits = False
type FieldIsArray "maxTessellationEvaluationInputComponents" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxTessellationEvaluationInputComponents" VkPhysicalDeviceLimits = False
type FieldIsArray "maxTessellationEvaluationOutputComponents" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxTessellationEvaluationOutputComponents" VkPhysicalDeviceLimits = False
type FieldIsArray "maxTessellationGenerationLevel" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxTessellationGenerationLevel" VkPhysicalDeviceLimits = False
type FieldIsArray "maxTessellationPatchSize" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxTessellationPatchSize" VkPhysicalDeviceLimits = False
type FieldIsArray "maxTexelBufferElements" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxTexelBufferElements" VkPhysicalDeviceLimits = False
type FieldIsArray "maxTexelGatherOffset" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxTexelGatherOffset" VkPhysicalDeviceLimits = False
type FieldIsArray "maxTexelOffset" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxTexelOffset" VkPhysicalDeviceLimits = False
type FieldIsArray "maxUniformBufferRange" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxUniformBufferRange" VkPhysicalDeviceLimits = False
type FieldIsArray "maxVertexInputAttributeOffset" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxVertexInputAttributeOffset" VkPhysicalDeviceLimits = False
type FieldIsArray "maxVertexInputAttributes" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxVertexInputAttributes" VkPhysicalDeviceLimits = False
type FieldIsArray "maxVertexInputBindingStride" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxVertexInputBindingStride" VkPhysicalDeviceLimits = False
type FieldIsArray "maxVertexInputBindings" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxVertexInputBindings" VkPhysicalDeviceLimits = False
type FieldIsArray "maxVertexOutputComponents" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxVertexOutputComponents" VkPhysicalDeviceLimits = False
type FieldIsArray "maxViewportDimensions" VkPhysicalDeviceLimits Source # 
type FieldIsArray "maxViewportDimensions" VkPhysicalDeviceLimits = True
type FieldIsArray "maxViewports" VkPhysicalDeviceLimits Source # 
type FieldIsArray "minInterpolationOffset" VkPhysicalDeviceLimits Source # 
type FieldIsArray "minInterpolationOffset" VkPhysicalDeviceLimits = False
type FieldIsArray "minMemoryMapAlignment" VkPhysicalDeviceLimits Source # 
type FieldIsArray "minMemoryMapAlignment" VkPhysicalDeviceLimits = False
type FieldIsArray "minStorageBufferOffsetAlignment" VkPhysicalDeviceLimits Source # 
type FieldIsArray "minStorageBufferOffsetAlignment" VkPhysicalDeviceLimits = False
type FieldIsArray "minTexelBufferOffsetAlignment" VkPhysicalDeviceLimits Source # 
type FieldIsArray "minTexelBufferOffsetAlignment" VkPhysicalDeviceLimits = False
type FieldIsArray "minTexelGatherOffset" VkPhysicalDeviceLimits Source # 
type FieldIsArray "minTexelGatherOffset" VkPhysicalDeviceLimits = False
type FieldIsArray "minTexelOffset" VkPhysicalDeviceLimits Source # 
type FieldIsArray "minTexelOffset" VkPhysicalDeviceLimits = False
type FieldIsArray "minUniformBufferOffsetAlignment" VkPhysicalDeviceLimits Source # 
type FieldIsArray "minUniformBufferOffsetAlignment" VkPhysicalDeviceLimits = False
type FieldIsArray "mipmapPrecisionBits" VkPhysicalDeviceLimits Source # 
type FieldIsArray "mipmapPrecisionBits" VkPhysicalDeviceLimits = False
type FieldIsArray "nonCoherentAtomSize" VkPhysicalDeviceLimits Source # 
type FieldIsArray "nonCoherentAtomSize" VkPhysicalDeviceLimits = False
type FieldIsArray "optimalBufferCopyOffsetAlignment" VkPhysicalDeviceLimits Source # 
type FieldIsArray "optimalBufferCopyOffsetAlignment" VkPhysicalDeviceLimits = False
type FieldIsArray "optimalBufferCopyRowPitchAlignment" VkPhysicalDeviceLimits Source # 
type FieldIsArray "optimalBufferCopyRowPitchAlignment" VkPhysicalDeviceLimits = False
type FieldIsArray "pointSizeGranularity" VkPhysicalDeviceLimits Source # 
type FieldIsArray "pointSizeGranularity" VkPhysicalDeviceLimits = False
type FieldIsArray "pointSizeRange" VkPhysicalDeviceLimits Source # 
type FieldIsArray "pointSizeRange" VkPhysicalDeviceLimits = True
type FieldIsArray "sampledImageColorSampleCounts" VkPhysicalDeviceLimits Source # 
type FieldIsArray "sampledImageColorSampleCounts" VkPhysicalDeviceLimits = False
type FieldIsArray "sampledImageDepthSampleCounts" VkPhysicalDeviceLimits Source # 
type FieldIsArray "sampledImageDepthSampleCounts" VkPhysicalDeviceLimits = False
type FieldIsArray "sampledImageIntegerSampleCounts" VkPhysicalDeviceLimits Source # 
type FieldIsArray "sampledImageIntegerSampleCounts" VkPhysicalDeviceLimits = False
type FieldIsArray "sampledImageStencilSampleCounts" VkPhysicalDeviceLimits Source # 
type FieldIsArray "sampledImageStencilSampleCounts" VkPhysicalDeviceLimits = False
type FieldIsArray "sparseAddressSpaceSize" VkPhysicalDeviceLimits Source # 
type FieldIsArray "sparseAddressSpaceSize" VkPhysicalDeviceLimits = False
type FieldIsArray "standardSampleLocations" VkPhysicalDeviceLimits Source # 
type FieldIsArray "standardSampleLocations" VkPhysicalDeviceLimits = False
type FieldIsArray "storageImageSampleCounts" VkPhysicalDeviceLimits Source # 
type FieldIsArray "storageImageSampleCounts" VkPhysicalDeviceLimits = False
type FieldIsArray "strictLines" VkPhysicalDeviceLimits Source # 
type FieldIsArray "subPixelInterpolationOffsetBits" VkPhysicalDeviceLimits Source # 
type FieldIsArray "subPixelInterpolationOffsetBits" VkPhysicalDeviceLimits = False
type FieldIsArray "subPixelPrecisionBits" VkPhysicalDeviceLimits Source # 
type FieldIsArray "subPixelPrecisionBits" VkPhysicalDeviceLimits = False
type FieldIsArray "subTexelPrecisionBits" VkPhysicalDeviceLimits Source # 
type FieldIsArray "subTexelPrecisionBits" VkPhysicalDeviceLimits = False
type FieldIsArray "timestampComputeAndGraphics" VkPhysicalDeviceLimits Source # 
type FieldIsArray "timestampComputeAndGraphics" VkPhysicalDeviceLimits = False
type FieldIsArray "timestampPeriod" VkPhysicalDeviceLimits Source # 
type FieldIsArray "timestampPeriod" VkPhysicalDeviceLimits = False
type FieldIsArray "viewportBoundsRange" VkPhysicalDeviceLimits Source # 
type FieldIsArray "viewportBoundsRange" VkPhysicalDeviceLimits = True
type FieldIsArray "viewportSubPixelBits" VkPhysicalDeviceLimits Source # 
type FieldIsArray "viewportSubPixelBits" VkPhysicalDeviceLimits = False

data VkPhysicalDeviceMaintenance3Properties Source #

typedef struct VkPhysicalDeviceMaintenance3Properties {
    VkStructureType sType;
    void*                            pNext;
    uint32_t                         maxPerSetDescriptors;
    VkDeviceSize                     maxMemoryAllocationSize;
} VkPhysicalDeviceMaintenance3Properties;

VkPhysicalDeviceMaintenance3Properties registry at www.khronos.org

Instances

Eq VkPhysicalDeviceMaintenance3Properties Source # 
Ord VkPhysicalDeviceMaintenance3Properties Source # 
Show VkPhysicalDeviceMaintenance3Properties Source # 
Storable VkPhysicalDeviceMaintenance3Properties Source # 
VulkanMarshalPrim VkPhysicalDeviceMaintenance3Properties Source # 
VulkanMarshal VkPhysicalDeviceMaintenance3Properties Source # 
CanWriteField "maxMemoryAllocationSize" VkPhysicalDeviceMaintenance3Properties Source # 
CanWriteField "maxPerSetDescriptors" VkPhysicalDeviceMaintenance3Properties Source # 
CanWriteField "pNext" VkPhysicalDeviceMaintenance3Properties Source # 
CanWriteField "sType" VkPhysicalDeviceMaintenance3Properties Source # 
CanReadField "maxMemoryAllocationSize" VkPhysicalDeviceMaintenance3Properties Source # 
CanReadField "maxPerSetDescriptors" VkPhysicalDeviceMaintenance3Properties Source # 
CanReadField "pNext" VkPhysicalDeviceMaintenance3Properties Source # 
CanReadField "sType" VkPhysicalDeviceMaintenance3Properties Source # 
HasField "maxMemoryAllocationSize" VkPhysicalDeviceMaintenance3Properties Source # 

Associated Types

type FieldType ("maxMemoryAllocationSize" :: Symbol) VkPhysicalDeviceMaintenance3Properties :: Type Source #

type FieldOptional ("maxMemoryAllocationSize" :: Symbol) VkPhysicalDeviceMaintenance3Properties :: Bool Source #

type FieldOffset ("maxMemoryAllocationSize" :: Symbol) VkPhysicalDeviceMaintenance3Properties :: Nat Source #

type FieldIsArray ("maxMemoryAllocationSize" :: Symbol) VkPhysicalDeviceMaintenance3Properties :: Bool Source #

HasField "maxPerSetDescriptors" VkPhysicalDeviceMaintenance3Properties Source # 
HasField "pNext" VkPhysicalDeviceMaintenance3Properties Source # 
HasField "sType" VkPhysicalDeviceMaintenance3Properties Source # 
type StructFields VkPhysicalDeviceMaintenance3Properties Source # 
type StructFields VkPhysicalDeviceMaintenance3Properties = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "maxPerSetDescriptors" ((:) Symbol "maxMemoryAllocationSize" ([] Symbol))))
type CUnionType VkPhysicalDeviceMaintenance3Properties Source # 
type ReturnedOnly VkPhysicalDeviceMaintenance3Properties Source # 
type StructExtends VkPhysicalDeviceMaintenance3Properties Source # 
type FieldType "maxMemoryAllocationSize" VkPhysicalDeviceMaintenance3Properties Source # 
type FieldType "maxPerSetDescriptors" VkPhysicalDeviceMaintenance3Properties Source # 
type FieldType "pNext" VkPhysicalDeviceMaintenance3Properties Source # 
type FieldType "sType" VkPhysicalDeviceMaintenance3Properties Source # 
type FieldOptional "maxMemoryAllocationSize" VkPhysicalDeviceMaintenance3Properties Source # 
type FieldOptional "maxPerSetDescriptors" VkPhysicalDeviceMaintenance3Properties Source # 
type FieldOptional "pNext" VkPhysicalDeviceMaintenance3Properties Source # 
type FieldOptional "sType" VkPhysicalDeviceMaintenance3Properties Source # 
type FieldOffset "maxMemoryAllocationSize" VkPhysicalDeviceMaintenance3Properties Source # 
type FieldOffset "maxMemoryAllocationSize" VkPhysicalDeviceMaintenance3Properties = 24
type FieldOffset "maxPerSetDescriptors" VkPhysicalDeviceMaintenance3Properties Source # 
type FieldOffset "maxPerSetDescriptors" VkPhysicalDeviceMaintenance3Properties = 16
type FieldOffset "pNext" VkPhysicalDeviceMaintenance3Properties Source # 
type FieldOffset "sType" VkPhysicalDeviceMaintenance3Properties Source # 
type FieldIsArray "maxMemoryAllocationSize" VkPhysicalDeviceMaintenance3Properties Source # 
type FieldIsArray "maxPerSetDescriptors" VkPhysicalDeviceMaintenance3Properties Source # 
type FieldIsArray "pNext" VkPhysicalDeviceMaintenance3Properties Source # 
type FieldIsArray "sType" VkPhysicalDeviceMaintenance3Properties Source # 

data VkPhysicalDeviceMemoryProperties Source #

typedef struct VkPhysicalDeviceMemoryProperties {
    uint32_t               memoryTypeCount;
    VkMemoryType           memoryTypes[VK_MAX_MEMORY_TYPES];
    uint32_t               memoryHeapCount;
    VkMemoryHeap           memoryHeaps[VK_MAX_MEMORY_HEAPS];
} VkPhysicalDeviceMemoryProperties;

VkPhysicalDeviceMemoryProperties registry at www.khronos.org

Instances

Eq VkPhysicalDeviceMemoryProperties Source # 
Ord VkPhysicalDeviceMemoryProperties Source # 
Show VkPhysicalDeviceMemoryProperties Source # 
Storable VkPhysicalDeviceMemoryProperties Source # 
VulkanMarshalPrim VkPhysicalDeviceMemoryProperties Source # 
VulkanMarshal VkPhysicalDeviceMemoryProperties Source # 
CanWriteField "memoryHeapCount" VkPhysicalDeviceMemoryProperties Source # 
CanWriteField "memoryTypeCount" VkPhysicalDeviceMemoryProperties Source # 
CanReadField "memoryHeapCount" VkPhysicalDeviceMemoryProperties Source # 
CanReadField "memoryTypeCount" VkPhysicalDeviceMemoryProperties Source # 
HasField "memoryHeapCount" VkPhysicalDeviceMemoryProperties Source # 
HasField "memoryHeaps" VkPhysicalDeviceMemoryProperties Source # 
HasField "memoryTypeCount" VkPhysicalDeviceMemoryProperties Source # 
HasField "memoryTypes" VkPhysicalDeviceMemoryProperties Source # 
(KnownNat idx, IndexInBounds "memoryHeaps" idx VkPhysicalDeviceMemoryProperties) => CanWriteFieldArray "memoryHeaps" idx VkPhysicalDeviceMemoryProperties Source # 
(KnownNat idx, IndexInBounds "memoryTypes" idx VkPhysicalDeviceMemoryProperties) => CanWriteFieldArray "memoryTypes" idx VkPhysicalDeviceMemoryProperties Source # 
(KnownNat idx, IndexInBounds "memoryHeaps" idx VkPhysicalDeviceMemoryProperties) => CanReadFieldArray "memoryHeaps" idx VkPhysicalDeviceMemoryProperties Source # 
(KnownNat idx, IndexInBounds "memoryTypes" idx VkPhysicalDeviceMemoryProperties) => CanReadFieldArray "memoryTypes" idx VkPhysicalDeviceMemoryProperties Source # 
type StructFields VkPhysicalDeviceMemoryProperties Source # 
type StructFields VkPhysicalDeviceMemoryProperties = (:) Symbol "memoryTypeCount" ((:) Symbol "memoryTypes" ((:) Symbol "memoryHeapCount" ((:) Symbol "memoryHeaps" ([] Symbol))))
type CUnionType VkPhysicalDeviceMemoryProperties Source # 
type ReturnedOnly VkPhysicalDeviceMemoryProperties Source # 
type StructExtends VkPhysicalDeviceMemoryProperties Source # 
type FieldArrayLength "memoryHeaps" VkPhysicalDeviceMemoryProperties Source # 
type FieldArrayLength "memoryTypes" VkPhysicalDeviceMemoryProperties Source # 
type FieldType "memoryHeapCount" VkPhysicalDeviceMemoryProperties Source # 
type FieldType "memoryHeaps" VkPhysicalDeviceMemoryProperties Source # 
type FieldType "memoryTypeCount" VkPhysicalDeviceMemoryProperties Source # 
type FieldType "memoryTypes" VkPhysicalDeviceMemoryProperties Source # 
type FieldOptional "memoryHeapCount" VkPhysicalDeviceMemoryProperties Source # 
type FieldOptional "memoryHeaps" VkPhysicalDeviceMemoryProperties Source # 
type FieldOptional "memoryTypeCount" VkPhysicalDeviceMemoryProperties Source # 
type FieldOptional "memoryTypes" VkPhysicalDeviceMemoryProperties Source # 
type FieldOffset "memoryHeapCount" VkPhysicalDeviceMemoryProperties Source # 
type FieldOffset "memoryHeapCount" VkPhysicalDeviceMemoryProperties = 260
type FieldOffset "memoryHeaps" VkPhysicalDeviceMemoryProperties Source # 
type FieldOffset "memoryTypeCount" VkPhysicalDeviceMemoryProperties Source # 
type FieldOffset "memoryTypes" VkPhysicalDeviceMemoryProperties Source # 
type FieldIsArray "memoryHeapCount" VkPhysicalDeviceMemoryProperties Source # 
type FieldIsArray "memoryHeaps" VkPhysicalDeviceMemoryProperties Source # 
type FieldIsArray "memoryTypeCount" VkPhysicalDeviceMemoryProperties Source # 
type FieldIsArray "memoryTypes" VkPhysicalDeviceMemoryProperties Source # 

data VkPhysicalDeviceMemoryProperties2 Source #

typedef struct VkPhysicalDeviceMemoryProperties2 {
    VkStructureType sType;
    void*                            pNext;
    VkPhysicalDeviceMemoryProperties memoryProperties;
} VkPhysicalDeviceMemoryProperties2;

VkPhysicalDeviceMemoryProperties2 registry at www.khronos.org

Instances

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

data VkPhysicalDeviceMultiviewFeatures Source #

typedef struct VkPhysicalDeviceMultiviewFeatures {
    VkStructureType sType;
    void*                            pNext;
    VkBool32                         multiview;
    VkBool32                         multiviewGeometryShader;
    VkBool32                         multiviewTessellationShader;
} VkPhysicalDeviceMultiviewFeatures;

VkPhysicalDeviceMultiviewFeatures registry at www.khronos.org

Instances

Eq VkPhysicalDeviceMultiviewFeatures Source # 
Ord VkPhysicalDeviceMultiviewFeatures Source # 
Show VkPhysicalDeviceMultiviewFeatures Source # 
Storable VkPhysicalDeviceMultiviewFeatures Source # 
VulkanMarshalPrim VkPhysicalDeviceMultiviewFeatures Source # 
VulkanMarshal VkPhysicalDeviceMultiviewFeatures Source # 
CanWriteField "multiview" VkPhysicalDeviceMultiviewFeatures Source # 
CanWriteField "multiviewGeometryShader" VkPhysicalDeviceMultiviewFeatures Source # 
CanWriteField "multiviewTessellationShader" VkPhysicalDeviceMultiviewFeatures Source # 
CanWriteField "pNext" VkPhysicalDeviceMultiviewFeatures Source # 
CanWriteField "sType" VkPhysicalDeviceMultiviewFeatures Source # 
CanReadField "multiview" VkPhysicalDeviceMultiviewFeatures Source # 
CanReadField "multiviewGeometryShader" VkPhysicalDeviceMultiviewFeatures Source # 
CanReadField "multiviewTessellationShader" VkPhysicalDeviceMultiviewFeatures Source # 
CanReadField "pNext" VkPhysicalDeviceMultiviewFeatures Source # 
CanReadField "sType" VkPhysicalDeviceMultiviewFeatures Source # 
HasField "multiview" VkPhysicalDeviceMultiviewFeatures Source # 
HasField "multiviewGeometryShader" VkPhysicalDeviceMultiviewFeatures Source # 

Associated Types

type FieldType ("multiviewGeometryShader" :: Symbol) VkPhysicalDeviceMultiviewFeatures :: Type Source #

type FieldOptional ("multiviewGeometryShader" :: Symbol) VkPhysicalDeviceMultiviewFeatures :: Bool Source #

type FieldOffset ("multiviewGeometryShader" :: Symbol) VkPhysicalDeviceMultiviewFeatures :: Nat Source #

type FieldIsArray ("multiviewGeometryShader" :: Symbol) VkPhysicalDeviceMultiviewFeatures :: Bool Source #

HasField "multiviewTessellationShader" VkPhysicalDeviceMultiviewFeatures Source # 

Associated Types

type FieldType ("multiviewTessellationShader" :: Symbol) VkPhysicalDeviceMultiviewFeatures :: Type Source #

type FieldOptional ("multiviewTessellationShader" :: Symbol) VkPhysicalDeviceMultiviewFeatures :: Bool Source #

type FieldOffset ("multiviewTessellationShader" :: Symbol) VkPhysicalDeviceMultiviewFeatures :: Nat Source #

type FieldIsArray ("multiviewTessellationShader" :: Symbol) VkPhysicalDeviceMultiviewFeatures :: Bool Source #

HasField "pNext" VkPhysicalDeviceMultiviewFeatures Source # 
HasField "sType" VkPhysicalDeviceMultiviewFeatures Source # 
type StructFields VkPhysicalDeviceMultiviewFeatures Source # 
type StructFields VkPhysicalDeviceMultiviewFeatures = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "multiview" ((:) Symbol "multiviewGeometryShader" ((:) Symbol "multiviewTessellationShader" ([] Symbol)))))
type CUnionType VkPhysicalDeviceMultiviewFeatures Source # 
type ReturnedOnly VkPhysicalDeviceMultiviewFeatures Source # 
type StructExtends VkPhysicalDeviceMultiviewFeatures Source # 
type FieldType "multiview" VkPhysicalDeviceMultiviewFeatures Source # 
type FieldType "multiviewGeometryShader" VkPhysicalDeviceMultiviewFeatures Source # 
type FieldType "multiviewGeometryShader" VkPhysicalDeviceMultiviewFeatures = VkBool32
type FieldType "multiviewTessellationShader" VkPhysicalDeviceMultiviewFeatures Source # 
type FieldType "multiviewTessellationShader" VkPhysicalDeviceMultiviewFeatures = VkBool32
type FieldType "pNext" VkPhysicalDeviceMultiviewFeatures Source # 
type FieldType "sType" VkPhysicalDeviceMultiviewFeatures Source # 
type FieldOptional "multiview" VkPhysicalDeviceMultiviewFeatures Source # 
type FieldOptional "multiviewGeometryShader" VkPhysicalDeviceMultiviewFeatures Source # 
type FieldOptional "multiviewGeometryShader" VkPhysicalDeviceMultiviewFeatures = False
type FieldOptional "multiviewTessellationShader" VkPhysicalDeviceMultiviewFeatures Source # 
type FieldOptional "multiviewTessellationShader" VkPhysicalDeviceMultiviewFeatures = False
type FieldOptional "pNext" VkPhysicalDeviceMultiviewFeatures Source # 
type FieldOptional "sType" VkPhysicalDeviceMultiviewFeatures Source # 
type FieldOffset "multiview" VkPhysicalDeviceMultiviewFeatures Source # 
type FieldOffset "multiviewGeometryShader" VkPhysicalDeviceMultiviewFeatures Source # 
type FieldOffset "multiviewGeometryShader" VkPhysicalDeviceMultiviewFeatures = 20
type FieldOffset "multiviewTessellationShader" VkPhysicalDeviceMultiviewFeatures Source # 
type FieldOffset "multiviewTessellationShader" VkPhysicalDeviceMultiviewFeatures = 24
type FieldOffset "pNext" VkPhysicalDeviceMultiviewFeatures Source # 
type FieldOffset "sType" VkPhysicalDeviceMultiviewFeatures Source # 
type FieldIsArray "multiview" VkPhysicalDeviceMultiviewFeatures Source # 
type FieldIsArray "multiviewGeometryShader" VkPhysicalDeviceMultiviewFeatures Source # 
type FieldIsArray "multiviewGeometryShader" VkPhysicalDeviceMultiviewFeatures = False
type FieldIsArray "multiviewTessellationShader" VkPhysicalDeviceMultiviewFeatures Source # 
type FieldIsArray "multiviewTessellationShader" VkPhysicalDeviceMultiviewFeatures = False
type FieldIsArray "pNext" VkPhysicalDeviceMultiviewFeatures Source # 
type FieldIsArray "sType" VkPhysicalDeviceMultiviewFeatures Source # 

data VkPhysicalDeviceMultiviewPerViewAttributesPropertiesNVX Source #

typedef struct VkPhysicalDeviceMultiviewPerViewAttributesPropertiesNVX {
    VkStructureType sType;
    void*                            pNext;
    VkBool32                         perViewPositionAllComponents;
} VkPhysicalDeviceMultiviewPerViewAttributesPropertiesNVX;

VkPhysicalDeviceMultiviewPerViewAttributesPropertiesNVX registry at www.khronos.org

Instances

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

data VkPhysicalDeviceMultiviewProperties Source #

typedef struct VkPhysicalDeviceMultiviewProperties {
    VkStructureType sType;
    void*                            pNext;
    uint32_t                         maxMultiviewViewCount;
    uint32_t                         maxMultiviewInstanceIndex;
} VkPhysicalDeviceMultiviewProperties;

VkPhysicalDeviceMultiviewProperties registry at www.khronos.org

Instances

Eq VkPhysicalDeviceMultiviewProperties Source # 
Ord VkPhysicalDeviceMultiviewProperties Source # 
Show VkPhysicalDeviceMultiviewProperties Source # 
Storable VkPhysicalDeviceMultiviewProperties Source # 
VulkanMarshalPrim VkPhysicalDeviceMultiviewProperties Source # 
VulkanMarshal VkPhysicalDeviceMultiviewProperties Source # 
CanWriteField "maxMultiviewInstanceIndex" VkPhysicalDeviceMultiviewProperties Source # 
CanWriteField "maxMultiviewViewCount" VkPhysicalDeviceMultiviewProperties Source # 
CanWriteField "pNext" VkPhysicalDeviceMultiviewProperties Source # 
CanWriteField "sType" VkPhysicalDeviceMultiviewProperties Source # 
CanReadField "maxMultiviewInstanceIndex" VkPhysicalDeviceMultiviewProperties Source # 
CanReadField "maxMultiviewViewCount" VkPhysicalDeviceMultiviewProperties Source # 
CanReadField "pNext" VkPhysicalDeviceMultiviewProperties Source # 
CanReadField "sType" VkPhysicalDeviceMultiviewProperties Source # 
HasField "maxMultiviewInstanceIndex" VkPhysicalDeviceMultiviewProperties Source # 

Associated Types

type FieldType ("maxMultiviewInstanceIndex" :: Symbol) VkPhysicalDeviceMultiviewProperties :: Type Source #

type FieldOptional ("maxMultiviewInstanceIndex" :: Symbol) VkPhysicalDeviceMultiviewProperties :: Bool Source #

type FieldOffset ("maxMultiviewInstanceIndex" :: Symbol) VkPhysicalDeviceMultiviewProperties :: Nat Source #

type FieldIsArray ("maxMultiviewInstanceIndex" :: Symbol) VkPhysicalDeviceMultiviewProperties :: Bool Source #

HasField "maxMultiviewViewCount" VkPhysicalDeviceMultiviewProperties Source # 

Associated Types

type FieldType ("maxMultiviewViewCount" :: Symbol) VkPhysicalDeviceMultiviewProperties :: Type Source #

type FieldOptional ("maxMultiviewViewCount" :: Symbol) VkPhysicalDeviceMultiviewProperties :: Bool Source #

type FieldOffset ("maxMultiviewViewCount" :: Symbol) VkPhysicalDeviceMultiviewProperties :: Nat Source #

type FieldIsArray ("maxMultiviewViewCount" :: Symbol) VkPhysicalDeviceMultiviewProperties :: Bool Source #

HasField "pNext" VkPhysicalDeviceMultiviewProperties Source # 
HasField "sType" VkPhysicalDeviceMultiviewProperties Source # 
type StructFields VkPhysicalDeviceMultiviewProperties Source # 
type StructFields VkPhysicalDeviceMultiviewProperties = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "maxMultiviewViewCount" ((:) Symbol "maxMultiviewInstanceIndex" ([] Symbol))))
type CUnionType VkPhysicalDeviceMultiviewProperties Source # 
type ReturnedOnly VkPhysicalDeviceMultiviewProperties Source # 
type StructExtends VkPhysicalDeviceMultiviewProperties Source # 
type FieldType "maxMultiviewInstanceIndex" VkPhysicalDeviceMultiviewProperties Source # 
type FieldType "maxMultiviewInstanceIndex" VkPhysicalDeviceMultiviewProperties = Word32
type FieldType "maxMultiviewViewCount" VkPhysicalDeviceMultiviewProperties Source # 
type FieldType "pNext" VkPhysicalDeviceMultiviewProperties Source # 
type FieldType "sType" VkPhysicalDeviceMultiviewProperties Source # 
type FieldOptional "maxMultiviewInstanceIndex" VkPhysicalDeviceMultiviewProperties Source # 
type FieldOptional "maxMultiviewInstanceIndex" VkPhysicalDeviceMultiviewProperties = False
type FieldOptional "maxMultiviewViewCount" VkPhysicalDeviceMultiviewProperties Source # 
type FieldOptional "pNext" VkPhysicalDeviceMultiviewProperties Source # 
type FieldOptional "sType" VkPhysicalDeviceMultiviewProperties Source # 
type FieldOffset "maxMultiviewInstanceIndex" VkPhysicalDeviceMultiviewProperties Source # 
type FieldOffset "maxMultiviewInstanceIndex" VkPhysicalDeviceMultiviewProperties = 20
type FieldOffset "maxMultiviewViewCount" VkPhysicalDeviceMultiviewProperties Source # 
type FieldOffset "maxMultiviewViewCount" VkPhysicalDeviceMultiviewProperties = 16
type FieldOffset "pNext" VkPhysicalDeviceMultiviewProperties Source # 
type FieldOffset "sType" VkPhysicalDeviceMultiviewProperties Source # 
type FieldIsArray "maxMultiviewInstanceIndex" VkPhysicalDeviceMultiviewProperties Source # 
type FieldIsArray "maxMultiviewInstanceIndex" VkPhysicalDeviceMultiviewProperties = False
type FieldIsArray "maxMultiviewViewCount" VkPhysicalDeviceMultiviewProperties Source # 
type FieldIsArray "pNext" VkPhysicalDeviceMultiviewProperties Source # 
type FieldIsArray "sType" VkPhysicalDeviceMultiviewProperties Source # 

data VkPhysicalDevicePointClippingProperties Source #

typedef struct VkPhysicalDevicePointClippingProperties {
    VkStructureType sType;
    void*                            pNext;
    VkPointClippingBehavior      pointClippingBehavior;
} VkPhysicalDevicePointClippingProperties;

VkPhysicalDevicePointClippingProperties registry at www.khronos.org

Instances

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

data VkPhysicalDeviceProperties Source #

typedef struct VkPhysicalDeviceProperties {
    uint32_t       apiVersion;
    uint32_t       driverVersion;
    uint32_t       vendorID;
    uint32_t       deviceID;
    VkPhysicalDeviceType deviceType;
    char           deviceName[VK_MAX_PHYSICAL_DEVICE_NAME_SIZE];
    uint8_t        pipelineCacheUUID[VK_UUID_SIZE];
    VkPhysicalDeviceLimits limits;
    VkPhysicalDeviceSparseProperties sparseProperties;
} VkPhysicalDeviceProperties;

VkPhysicalDeviceProperties registry at www.khronos.org

Instances

Eq VkPhysicalDeviceProperties Source # 
Ord VkPhysicalDeviceProperties Source # 
Show VkPhysicalDeviceProperties Source # 
Storable VkPhysicalDeviceProperties Source # 
VulkanMarshalPrim VkPhysicalDeviceProperties Source # 
VulkanMarshal VkPhysicalDeviceProperties Source # 
CanWriteField "apiVersion" VkPhysicalDeviceProperties Source # 
CanWriteField "deviceID" VkPhysicalDeviceProperties Source # 
CanWriteField "deviceType" VkPhysicalDeviceProperties Source # 
CanWriteField "driverVersion" VkPhysicalDeviceProperties Source # 
CanWriteField "limits" VkPhysicalDeviceProperties Source # 
CanWriteField "sparseProperties" VkPhysicalDeviceProperties Source # 
CanWriteField "vendorID" VkPhysicalDeviceProperties Source # 
CanReadField "apiVersion" VkPhysicalDeviceProperties Source # 
CanReadField "deviceID" VkPhysicalDeviceProperties Source # 
CanReadField "deviceType" VkPhysicalDeviceProperties Source # 
CanReadField "driverVersion" VkPhysicalDeviceProperties Source # 
CanReadField "limits" VkPhysicalDeviceProperties Source # 
CanReadField "sparseProperties" VkPhysicalDeviceProperties Source # 
CanReadField "vendorID" VkPhysicalDeviceProperties Source # 
HasField "apiVersion" VkPhysicalDeviceProperties Source # 
HasField "deviceID" VkPhysicalDeviceProperties Source # 
HasField "deviceName" VkPhysicalDeviceProperties Source # 
HasField "deviceType" VkPhysicalDeviceProperties Source # 
HasField "driverVersion" VkPhysicalDeviceProperties Source # 
HasField "limits" VkPhysicalDeviceProperties Source # 
HasField "pipelineCacheUUID" VkPhysicalDeviceProperties Source # 

Associated Types

type FieldType ("pipelineCacheUUID" :: Symbol) VkPhysicalDeviceProperties :: Type Source #

type FieldOptional ("pipelineCacheUUID" :: Symbol) VkPhysicalDeviceProperties :: Bool Source #

type FieldOffset ("pipelineCacheUUID" :: Symbol) VkPhysicalDeviceProperties :: Nat Source #

type FieldIsArray ("pipelineCacheUUID" :: Symbol) VkPhysicalDeviceProperties :: Bool Source #

HasField "sparseProperties" VkPhysicalDeviceProperties Source # 

Associated Types

type FieldType ("sparseProperties" :: Symbol) VkPhysicalDeviceProperties :: Type Source #

type FieldOptional ("sparseProperties" :: Symbol) VkPhysicalDeviceProperties :: Bool Source #

type FieldOffset ("sparseProperties" :: Symbol) VkPhysicalDeviceProperties :: Nat Source #

type FieldIsArray ("sparseProperties" :: Symbol) VkPhysicalDeviceProperties :: Bool Source #

HasField "vendorID" VkPhysicalDeviceProperties Source # 
(KnownNat idx, IndexInBounds "deviceName" idx VkPhysicalDeviceProperties) => CanWriteFieldArray "deviceName" idx VkPhysicalDeviceProperties Source # 
(KnownNat idx, IndexInBounds "pipelineCacheUUID" idx VkPhysicalDeviceProperties) => CanWriteFieldArray "pipelineCacheUUID" idx VkPhysicalDeviceProperties Source # 
(KnownNat idx, IndexInBounds "deviceName" idx VkPhysicalDeviceProperties) => CanReadFieldArray "deviceName" idx VkPhysicalDeviceProperties Source # 
(KnownNat idx, IndexInBounds "pipelineCacheUUID" idx VkPhysicalDeviceProperties) => CanReadFieldArray "pipelineCacheUUID" idx VkPhysicalDeviceProperties Source # 
type StructFields VkPhysicalDeviceProperties Source # 
type StructFields VkPhysicalDeviceProperties = (:) Symbol "apiVersion" ((:) Symbol "driverVersion" ((:) Symbol "vendorID" ((:) Symbol "deviceID" ((:) Symbol "deviceType" ((:) Symbol "deviceName" ((:) Symbol "pipelineCacheUUID" ((:) Symbol "limits" ((:) Symbol "sparseProperties" ([] Symbol)))))))))
type CUnionType VkPhysicalDeviceProperties Source # 
type ReturnedOnly VkPhysicalDeviceProperties Source # 
type StructExtends VkPhysicalDeviceProperties Source # 
type FieldArrayLength "deviceName" VkPhysicalDeviceProperties Source # 
type FieldArrayLength "pipelineCacheUUID" VkPhysicalDeviceProperties Source # 
type FieldType "apiVersion" VkPhysicalDeviceProperties Source # 
type FieldType "deviceID" VkPhysicalDeviceProperties Source # 
type FieldType "deviceName" VkPhysicalDeviceProperties Source # 
type FieldType "deviceType" VkPhysicalDeviceProperties Source # 
type FieldType "driverVersion" VkPhysicalDeviceProperties Source # 
type FieldType "limits" VkPhysicalDeviceProperties Source # 
type FieldType "pipelineCacheUUID" VkPhysicalDeviceProperties Source # 
type FieldType "pipelineCacheUUID" VkPhysicalDeviceProperties = Word8
type FieldType "sparseProperties" VkPhysicalDeviceProperties Source # 
type FieldType "vendorID" VkPhysicalDeviceProperties Source # 
type FieldOptional "apiVersion" VkPhysicalDeviceProperties Source # 
type FieldOptional "deviceID" VkPhysicalDeviceProperties Source # 
type FieldOptional "deviceName" VkPhysicalDeviceProperties Source # 
type FieldOptional "deviceType" VkPhysicalDeviceProperties Source # 
type FieldOptional "driverVersion" VkPhysicalDeviceProperties Source # 
type FieldOptional "limits" VkPhysicalDeviceProperties Source # 
type FieldOptional "pipelineCacheUUID" VkPhysicalDeviceProperties Source # 
type FieldOptional "sparseProperties" VkPhysicalDeviceProperties Source # 
type FieldOptional "vendorID" VkPhysicalDeviceProperties Source # 
type FieldOffset "apiVersion" VkPhysicalDeviceProperties Source # 
type FieldOffset "deviceID" VkPhysicalDeviceProperties Source # 
type FieldOffset "deviceName" VkPhysicalDeviceProperties Source # 
type FieldOffset "deviceType" VkPhysicalDeviceProperties Source # 
type FieldOffset "driverVersion" VkPhysicalDeviceProperties Source # 
type FieldOffset "driverVersion" VkPhysicalDeviceProperties = 4
type FieldOffset "limits" VkPhysicalDeviceProperties Source # 
type FieldOffset "pipelineCacheUUID" VkPhysicalDeviceProperties Source # 
type FieldOffset "pipelineCacheUUID" VkPhysicalDeviceProperties = 276
type FieldOffset "sparseProperties" VkPhysicalDeviceProperties Source # 
type FieldOffset "sparseProperties" VkPhysicalDeviceProperties = 800
type FieldOffset "vendorID" VkPhysicalDeviceProperties Source # 
type FieldIsArray "apiVersion" VkPhysicalDeviceProperties Source # 
type FieldIsArray "deviceID" VkPhysicalDeviceProperties Source # 
type FieldIsArray "deviceName" VkPhysicalDeviceProperties Source # 
type FieldIsArray "deviceType" VkPhysicalDeviceProperties Source # 
type FieldIsArray "driverVersion" VkPhysicalDeviceProperties Source # 
type FieldIsArray "limits" VkPhysicalDeviceProperties Source # 
type FieldIsArray "pipelineCacheUUID" VkPhysicalDeviceProperties Source # 
type FieldIsArray "pipelineCacheUUID" VkPhysicalDeviceProperties = True
type FieldIsArray "sparseProperties" VkPhysicalDeviceProperties Source # 
type FieldIsArray "vendorID" VkPhysicalDeviceProperties Source # 

data VkPhysicalDeviceProperties2 Source #

typedef struct VkPhysicalDeviceProperties2 {
    VkStructureType sType;
    void*                            pNext;
    VkPhysicalDeviceProperties       properties;
} VkPhysicalDeviceProperties2;

VkPhysicalDeviceProperties2 registry at www.khronos.org

Instances

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

data VkPhysicalDeviceProtectedMemoryFeatures Source #

typedef struct VkPhysicalDeviceProtectedMemoryFeatures {
    VkStructureType sType;
    void*                               pNext;
    VkBool32                            protectedMemory;
} VkPhysicalDeviceProtectedMemoryFeatures;

VkPhysicalDeviceProtectedMemoryFeatures registry at www.khronos.org

Instances

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

data VkPhysicalDeviceProtectedMemoryProperties Source #

typedef struct VkPhysicalDeviceProtectedMemoryProperties {
    VkStructureType sType;
    void*                               pNext;
    VkBool32                            protectedNoFault;
} VkPhysicalDeviceProtectedMemoryProperties;

VkPhysicalDeviceProtectedMemoryProperties registry at www.khronos.org

Instances

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

data VkPhysicalDevicePushDescriptorPropertiesKHR Source #

typedef struct VkPhysicalDevicePushDescriptorPropertiesKHR {
    VkStructureType sType;
    void*                            pNext;
    uint32_t                         maxPushDescriptors;
} VkPhysicalDevicePushDescriptorPropertiesKHR;

VkPhysicalDevicePushDescriptorPropertiesKHR registry at www.khronos.org

Instances

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

data VkPhysicalDeviceSampleLocationsPropertiesEXT Source #

typedef struct VkPhysicalDeviceSampleLocationsPropertiesEXT {
    VkStructureType sType;
    void*                            pNext;
    VkSampleCountFlags               sampleLocationSampleCounts;
    VkExtent2D                       maxSampleLocationGridSize;
    float                            sampleLocationCoordinateRange[2];
    uint32_t                         sampleLocationSubPixelBits;
    VkBool32                         variableSampleLocations;
} VkPhysicalDeviceSampleLocationsPropertiesEXT;

VkPhysicalDeviceSampleLocationsPropertiesEXT registry at www.khronos.org

Instances

Eq VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
Ord VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
Show VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
Storable VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
VulkanMarshalPrim VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
VulkanMarshal VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
CanWriteField "maxSampleLocationGridSize" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
CanWriteField "pNext" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
CanWriteField "sType" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
CanWriteField "sampleLocationSampleCounts" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
CanWriteField "sampleLocationSubPixelBits" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
CanWriteField "variableSampleLocations" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
CanReadField "maxSampleLocationGridSize" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
CanReadField "pNext" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
CanReadField "sType" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
CanReadField "sampleLocationSampleCounts" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
CanReadField "sampleLocationSubPixelBits" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
CanReadField "variableSampleLocations" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
HasField "maxSampleLocationGridSize" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
HasField "pNext" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
HasField "sType" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
HasField "sampleLocationCoordinateRange" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 

Associated Types

type FieldType ("sampleLocationCoordinateRange" :: Symbol) VkPhysicalDeviceSampleLocationsPropertiesEXT :: Type Source #

type FieldOptional ("sampleLocationCoordinateRange" :: Symbol) VkPhysicalDeviceSampleLocationsPropertiesEXT :: Bool Source #

type FieldOffset ("sampleLocationCoordinateRange" :: Symbol) VkPhysicalDeviceSampleLocationsPropertiesEXT :: Nat Source #

type FieldIsArray ("sampleLocationCoordinateRange" :: Symbol) VkPhysicalDeviceSampleLocationsPropertiesEXT :: Bool Source #

HasField "sampleLocationSampleCounts" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 

Associated Types

type FieldType ("sampleLocationSampleCounts" :: Symbol) VkPhysicalDeviceSampleLocationsPropertiesEXT :: Type Source #

type FieldOptional ("sampleLocationSampleCounts" :: Symbol) VkPhysicalDeviceSampleLocationsPropertiesEXT :: Bool Source #

type FieldOffset ("sampleLocationSampleCounts" :: Symbol) VkPhysicalDeviceSampleLocationsPropertiesEXT :: Nat Source #

type FieldIsArray ("sampleLocationSampleCounts" :: Symbol) VkPhysicalDeviceSampleLocationsPropertiesEXT :: Bool Source #

HasField "sampleLocationSubPixelBits" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 

Associated Types

type FieldType ("sampleLocationSubPixelBits" :: Symbol) VkPhysicalDeviceSampleLocationsPropertiesEXT :: Type Source #

type FieldOptional ("sampleLocationSubPixelBits" :: Symbol) VkPhysicalDeviceSampleLocationsPropertiesEXT :: Bool Source #

type FieldOffset ("sampleLocationSubPixelBits" :: Symbol) VkPhysicalDeviceSampleLocationsPropertiesEXT :: Nat Source #

type FieldIsArray ("sampleLocationSubPixelBits" :: Symbol) VkPhysicalDeviceSampleLocationsPropertiesEXT :: Bool Source #

HasField "variableSampleLocations" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
(KnownNat idx, IndexInBounds "sampleLocationCoordinateRange" idx VkPhysicalDeviceSampleLocationsPropertiesEXT) => CanWriteFieldArray "sampleLocationCoordinateRange" idx VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
(KnownNat idx, IndexInBounds "sampleLocationCoordinateRange" idx VkPhysicalDeviceSampleLocationsPropertiesEXT) => CanReadFieldArray "sampleLocationCoordinateRange" idx VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
type StructFields VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
type StructFields VkPhysicalDeviceSampleLocationsPropertiesEXT = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "sampleLocationSampleCounts" ((:) Symbol "maxSampleLocationGridSize" ((:) Symbol "sampleLocationCoordinateRange" ((:) Symbol "sampleLocationSubPixelBits" ((:) Symbol "variableSampleLocations" ([] Symbol)))))))
type CUnionType VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
type ReturnedOnly VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
type StructExtends VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
type FieldArrayLength "sampleLocationCoordinateRange" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
type FieldArrayLength "sampleLocationCoordinateRange" VkPhysicalDeviceSampleLocationsPropertiesEXT = 2
type FieldType "maxSampleLocationGridSize" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
type FieldType "pNext" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
type FieldType "sType" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
type FieldType "sampleLocationCoordinateRange" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
type FieldType "sampleLocationCoordinateRange" VkPhysicalDeviceSampleLocationsPropertiesEXT = Float
type FieldType "sampleLocationSampleCounts" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
type FieldType "sampleLocationSubPixelBits" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
type FieldType "variableSampleLocations" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
type FieldOptional "maxSampleLocationGridSize" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
type FieldOptional "pNext" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
type FieldOptional "sType" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
type FieldOptional "sampleLocationCoordinateRange" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
type FieldOptional "sampleLocationSampleCounts" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
type FieldOptional "sampleLocationSubPixelBits" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
type FieldOptional "variableSampleLocations" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
type FieldOffset "maxSampleLocationGridSize" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
type FieldOffset "maxSampleLocationGridSize" VkPhysicalDeviceSampleLocationsPropertiesEXT = 20
type FieldOffset "pNext" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
type FieldOffset "sType" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
type FieldOffset "sampleLocationCoordinateRange" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
type FieldOffset "sampleLocationCoordinateRange" VkPhysicalDeviceSampleLocationsPropertiesEXT = 28
type FieldOffset "sampleLocationSampleCounts" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
type FieldOffset "sampleLocationSampleCounts" VkPhysicalDeviceSampleLocationsPropertiesEXT = 16
type FieldOffset "sampleLocationSubPixelBits" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
type FieldOffset "sampleLocationSubPixelBits" VkPhysicalDeviceSampleLocationsPropertiesEXT = 36
type FieldOffset "variableSampleLocations" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
type FieldOffset "variableSampleLocations" VkPhysicalDeviceSampleLocationsPropertiesEXT = 40
type FieldIsArray "maxSampleLocationGridSize" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
type FieldIsArray "pNext" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
type FieldIsArray "sType" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
type FieldIsArray "sampleLocationCoordinateRange" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
type FieldIsArray "sampleLocationCoordinateRange" VkPhysicalDeviceSampleLocationsPropertiesEXT = True
type FieldIsArray "sampleLocationSampleCounts" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
type FieldIsArray "sampleLocationSubPixelBits" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 
type FieldIsArray "variableSampleLocations" VkPhysicalDeviceSampleLocationsPropertiesEXT Source # 

data VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT Source #

typedef struct VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT {
    VkStructureType sType;
    void*                  pNext;
    VkBool32               filterMinmaxSingleComponentFormats;
    VkBool32               filterMinmaxImageComponentMapping;
} VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT;

VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT registry at www.khronos.org

Instances

Eq VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT Source # 
Ord VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT Source # 
Show VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT Source # 
Storable VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT Source # 
VulkanMarshalPrim VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT Source # 
VulkanMarshal VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT Source # 
CanWriteField "filterMinmaxImageComponentMapping" VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT Source # 
CanWriteField "filterMinmaxSingleComponentFormats" VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT Source # 
CanWriteField "pNext" VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT Source # 
CanWriteField "sType" VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT Source # 
CanReadField "filterMinmaxImageComponentMapping" VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT Source # 
CanReadField "filterMinmaxSingleComponentFormats" VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT Source # 
CanReadField "pNext" VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT Source # 
CanReadField "sType" VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT Source # 
HasField "filterMinmaxImageComponentMapping" VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT Source # 

Associated Types

type FieldType ("filterMinmaxImageComponentMapping" :: Symbol) VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT :: Type Source #

type FieldOptional ("filterMinmaxImageComponentMapping" :: Symbol) VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT :: Bool Source #

type FieldOffset ("filterMinmaxImageComponentMapping" :: Symbol) VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT :: Nat Source #

type FieldIsArray ("filterMinmaxImageComponentMapping" :: Symbol) VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT :: Bool Source #

HasField "filterMinmaxSingleComponentFormats" VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT Source # 

Associated Types

type FieldType ("filterMinmaxSingleComponentFormats" :: Symbol) VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT :: Type Source #

type FieldOptional ("filterMinmaxSingleComponentFormats" :: Symbol) VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT :: Bool Source #

type FieldOffset ("filterMinmaxSingleComponentFormats" :: Symbol) VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT :: Nat Source #

type FieldIsArray ("filterMinmaxSingleComponentFormats" :: Symbol) VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT :: Bool Source #

HasField "pNext" VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT Source # 
HasField "sType" VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT Source # 
type StructFields VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT Source # 
type StructFields VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "filterMinmaxSingleComponentFormats" ((:) Symbol "filterMinmaxImageComponentMapping" ([] Symbol))))
type CUnionType VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT Source # 
type ReturnedOnly VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT Source # 
type StructExtends VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT Source # 
type FieldType "filterMinmaxImageComponentMapping" VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT Source # 
type FieldType "filterMinmaxImageComponentMapping" VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT = VkBool32
type FieldType "filterMinmaxSingleComponentFormats" VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT Source # 
type FieldType "filterMinmaxSingleComponentFormats" VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT = VkBool32
type FieldType "pNext" VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT Source # 
type FieldType "sType" VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT Source # 
type FieldOptional "filterMinmaxImageComponentMapping" VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT Source # 
type FieldOptional "filterMinmaxImageComponentMapping" VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT = False
type FieldOptional "filterMinmaxSingleComponentFormats" VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT Source # 
type FieldOptional "filterMinmaxSingleComponentFormats" VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT = False
type FieldOptional "pNext" VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT Source # 
type FieldOptional "sType" VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT Source # 
type FieldOffset "filterMinmaxImageComponentMapping" VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT Source # 
type FieldOffset "filterMinmaxImageComponentMapping" VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT = 20
type FieldOffset "filterMinmaxSingleComponentFormats" VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT Source # 
type FieldOffset "filterMinmaxSingleComponentFormats" VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT = 16
type FieldOffset "pNext" VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT Source # 
type FieldOffset "sType" VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT Source # 
type FieldIsArray "filterMinmaxImageComponentMapping" VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT Source # 
type FieldIsArray "filterMinmaxImageComponentMapping" VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT = False
type FieldIsArray "filterMinmaxSingleComponentFormats" VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT Source # 
type FieldIsArray "filterMinmaxSingleComponentFormats" VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT = False
type FieldIsArray "pNext" VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT Source # 
type FieldIsArray "sType" VkPhysicalDeviceSamplerFilterMinmaxPropertiesEXT Source # 

data VkPhysicalDeviceSamplerYcbcrConversionFeatures Source #

typedef struct VkPhysicalDeviceSamplerYcbcrConversionFeatures {
    VkStructureType sType;
    void*      pNext;
    VkBool32                         samplerYcbcrConversion;
} VkPhysicalDeviceSamplerYcbcrConversionFeatures;

VkPhysicalDeviceSamplerYcbcrConversionFeatures registry at www.khronos.org

Instances

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

data VkPhysicalDeviceShaderCorePropertiesAMD Source #

typedef struct VkPhysicalDeviceShaderCorePropertiesAMD {
    VkStructureType sType;
    void*    pNext;
    uint32_t shaderEngineCount;
    uint32_t shaderArraysPerEngineCount;
    uint32_t computeUnitsPerShaderArray;
    uint32_t simdPerComputeUnit;
    uint32_t wavefrontsPerSimd;
    uint32_t wavefrontSize;
    uint32_t sgprsPerSimd;
    uint32_t minSgprAllocation;
    uint32_t maxSgprAllocation;
    uint32_t sgprAllocationGranularity;
    uint32_t vgprsPerSimd;
    uint32_t minVgprAllocation;
    uint32_t maxVgprAllocation;
    uint32_t vgprAllocationGranularity;
} VkPhysicalDeviceShaderCorePropertiesAMD;

VkPhysicalDeviceShaderCorePropertiesAMD registry at www.khronos.org

Instances

Eq VkPhysicalDeviceShaderCorePropertiesAMD Source # 
Ord VkPhysicalDeviceShaderCorePropertiesAMD Source # 
Show VkPhysicalDeviceShaderCorePropertiesAMD Source # 
Storable VkPhysicalDeviceShaderCorePropertiesAMD Source # 
VulkanMarshalPrim VkPhysicalDeviceShaderCorePropertiesAMD Source # 
VulkanMarshal VkPhysicalDeviceShaderCorePropertiesAMD Source # 
CanWriteField "computeUnitsPerShaderArray" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
CanWriteField "maxSgprAllocation" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
CanWriteField "maxVgprAllocation" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
CanWriteField "minSgprAllocation" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
CanWriteField "minVgprAllocation" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
CanWriteField "pNext" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
CanWriteField "sType" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
CanWriteField "sgprAllocationGranularity" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
CanWriteField "sgprsPerSimd" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
CanWriteField "shaderArraysPerEngineCount" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
CanWriteField "shaderEngineCount" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
CanWriteField "simdPerComputeUnit" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
CanWriteField "vgprAllocationGranularity" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
CanWriteField "vgprsPerSimd" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
CanWriteField "wavefrontSize" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
CanWriteField "wavefrontsPerSimd" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
CanReadField "computeUnitsPerShaderArray" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
CanReadField "maxSgprAllocation" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
CanReadField "maxVgprAllocation" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
CanReadField "minSgprAllocation" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
CanReadField "minVgprAllocation" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
CanReadField "pNext" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
CanReadField "sType" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
CanReadField "sgprAllocationGranularity" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
CanReadField "sgprsPerSimd" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
CanReadField "shaderArraysPerEngineCount" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
CanReadField "shaderEngineCount" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
CanReadField "simdPerComputeUnit" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
CanReadField "vgprAllocationGranularity" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
CanReadField "vgprsPerSimd" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
CanReadField "wavefrontSize" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
CanReadField "wavefrontsPerSimd" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
HasField "computeUnitsPerShaderArray" VkPhysicalDeviceShaderCorePropertiesAMD Source # 

Associated Types

type FieldType ("computeUnitsPerShaderArray" :: Symbol) VkPhysicalDeviceShaderCorePropertiesAMD :: Type Source #

type FieldOptional ("computeUnitsPerShaderArray" :: Symbol) VkPhysicalDeviceShaderCorePropertiesAMD :: Bool Source #

type FieldOffset ("computeUnitsPerShaderArray" :: Symbol) VkPhysicalDeviceShaderCorePropertiesAMD :: Nat Source #

type FieldIsArray ("computeUnitsPerShaderArray" :: Symbol) VkPhysicalDeviceShaderCorePropertiesAMD :: Bool Source #

HasField "maxSgprAllocation" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
HasField "maxVgprAllocation" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
HasField "minSgprAllocation" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
HasField "minVgprAllocation" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
HasField "pNext" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
HasField "sType" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
HasField "sgprAllocationGranularity" VkPhysicalDeviceShaderCorePropertiesAMD Source # 

Associated Types

type FieldType ("sgprAllocationGranularity" :: Symbol) VkPhysicalDeviceShaderCorePropertiesAMD :: Type Source #

type FieldOptional ("sgprAllocationGranularity" :: Symbol) VkPhysicalDeviceShaderCorePropertiesAMD :: Bool Source #

type FieldOffset ("sgprAllocationGranularity" :: Symbol) VkPhysicalDeviceShaderCorePropertiesAMD :: Nat Source #

type FieldIsArray ("sgprAllocationGranularity" :: Symbol) VkPhysicalDeviceShaderCorePropertiesAMD :: Bool Source #

HasField "sgprsPerSimd" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
HasField "shaderArraysPerEngineCount" VkPhysicalDeviceShaderCorePropertiesAMD Source # 

Associated Types

type FieldType ("shaderArraysPerEngineCount" :: Symbol) VkPhysicalDeviceShaderCorePropertiesAMD :: Type Source #

type FieldOptional ("shaderArraysPerEngineCount" :: Symbol) VkPhysicalDeviceShaderCorePropertiesAMD :: Bool Source #

type FieldOffset ("shaderArraysPerEngineCount" :: Symbol) VkPhysicalDeviceShaderCorePropertiesAMD :: Nat Source #

type FieldIsArray ("shaderArraysPerEngineCount" :: Symbol) VkPhysicalDeviceShaderCorePropertiesAMD :: Bool Source #

HasField "shaderEngineCount" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
HasField "simdPerComputeUnit" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
HasField "vgprAllocationGranularity" VkPhysicalDeviceShaderCorePropertiesAMD Source # 

Associated Types

type FieldType ("vgprAllocationGranularity" :: Symbol) VkPhysicalDeviceShaderCorePropertiesAMD :: Type Source #

type FieldOptional ("vgprAllocationGranularity" :: Symbol) VkPhysicalDeviceShaderCorePropertiesAMD :: Bool Source #

type FieldOffset ("vgprAllocationGranularity" :: Symbol) VkPhysicalDeviceShaderCorePropertiesAMD :: Nat Source #

type FieldIsArray ("vgprAllocationGranularity" :: Symbol) VkPhysicalDeviceShaderCorePropertiesAMD :: Bool Source #

HasField "vgprsPerSimd" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
HasField "wavefrontSize" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
HasField "wavefrontsPerSimd" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type StructFields VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type StructFields VkPhysicalDeviceShaderCorePropertiesAMD = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "shaderEngineCount" ((:) Symbol "shaderArraysPerEngineCount" ((:) Symbol "computeUnitsPerShaderArray" ((:) Symbol "simdPerComputeUnit" ((:) Symbol "wavefrontsPerSimd" ((:) Symbol "wavefrontSize" ((:) Symbol "sgprsPerSimd" ((:) Symbol "minSgprAllocation" ((:) Symbol "maxSgprAllocation" ((:) Symbol "sgprAllocationGranularity" ((:) Symbol "vgprsPerSimd" ((:) Symbol "minVgprAllocation" ((:) Symbol "maxVgprAllocation" ((:) Symbol "vgprAllocationGranularity" ([] Symbol))))))))))))))))
type CUnionType VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type ReturnedOnly VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type StructExtends VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldType "computeUnitsPerShaderArray" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldType "computeUnitsPerShaderArray" VkPhysicalDeviceShaderCorePropertiesAMD = Word32
type FieldType "maxSgprAllocation" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldType "maxVgprAllocation" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldType "minSgprAllocation" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldType "minVgprAllocation" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldType "pNext" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldType "sType" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldType "sgprAllocationGranularity" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldType "sgprAllocationGranularity" VkPhysicalDeviceShaderCorePropertiesAMD = Word32
type FieldType "sgprsPerSimd" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldType "shaderArraysPerEngineCount" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldType "shaderArraysPerEngineCount" VkPhysicalDeviceShaderCorePropertiesAMD = Word32
type FieldType "shaderEngineCount" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldType "simdPerComputeUnit" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldType "vgprAllocationGranularity" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldType "vgprAllocationGranularity" VkPhysicalDeviceShaderCorePropertiesAMD = Word32
type FieldType "vgprsPerSimd" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldType "wavefrontSize" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldType "wavefrontsPerSimd" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldOptional "computeUnitsPerShaderArray" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldOptional "computeUnitsPerShaderArray" VkPhysicalDeviceShaderCorePropertiesAMD = False
type FieldOptional "maxSgprAllocation" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldOptional "maxVgprAllocation" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldOptional "minSgprAllocation" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldOptional "minVgprAllocation" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldOptional "pNext" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldOptional "sType" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldOptional "sgprAllocationGranularity" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldOptional "sgprsPerSimd" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldOptional "shaderArraysPerEngineCount" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldOptional "shaderArraysPerEngineCount" VkPhysicalDeviceShaderCorePropertiesAMD = False
type FieldOptional "shaderEngineCount" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldOptional "simdPerComputeUnit" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldOptional "vgprAllocationGranularity" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldOptional "vgprsPerSimd" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldOptional "wavefrontSize" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldOptional "wavefrontsPerSimd" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldOffset "computeUnitsPerShaderArray" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldOffset "computeUnitsPerShaderArray" VkPhysicalDeviceShaderCorePropertiesAMD = 24
type FieldOffset "maxSgprAllocation" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldOffset "maxVgprAllocation" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldOffset "minSgprAllocation" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldOffset "minVgprAllocation" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldOffset "pNext" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldOffset "sType" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldOffset "sgprAllocationGranularity" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldOffset "sgprAllocationGranularity" VkPhysicalDeviceShaderCorePropertiesAMD = 52
type FieldOffset "sgprsPerSimd" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldOffset "shaderArraysPerEngineCount" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldOffset "shaderArraysPerEngineCount" VkPhysicalDeviceShaderCorePropertiesAMD = 20
type FieldOffset "shaderEngineCount" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldOffset "simdPerComputeUnit" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldOffset "vgprAllocationGranularity" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldOffset "vgprAllocationGranularity" VkPhysicalDeviceShaderCorePropertiesAMD = 68
type FieldOffset "vgprsPerSimd" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldOffset "wavefrontSize" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldOffset "wavefrontsPerSimd" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldIsArray "computeUnitsPerShaderArray" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldIsArray "computeUnitsPerShaderArray" VkPhysicalDeviceShaderCorePropertiesAMD = False
type FieldIsArray "maxSgprAllocation" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldIsArray "maxVgprAllocation" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldIsArray "minSgprAllocation" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldIsArray "minVgprAllocation" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldIsArray "pNext" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldIsArray "sType" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldIsArray "sgprAllocationGranularity" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldIsArray "sgprsPerSimd" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldIsArray "shaderArraysPerEngineCount" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldIsArray "shaderArraysPerEngineCount" VkPhysicalDeviceShaderCorePropertiesAMD = False
type FieldIsArray "shaderEngineCount" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldIsArray "simdPerComputeUnit" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldIsArray "vgprAllocationGranularity" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldIsArray "vgprsPerSimd" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldIsArray "wavefrontSize" VkPhysicalDeviceShaderCorePropertiesAMD Source # 
type FieldIsArray "wavefrontsPerSimd" VkPhysicalDeviceShaderCorePropertiesAMD Source # 

data VkPhysicalDeviceShaderDrawParameterFeatures Source #

typedef struct VkPhysicalDeviceShaderDrawParameterFeatures {
    VkStructureType sType;
    void*                            pNext;
    VkBool32                         shaderDrawParameters;
} VkPhysicalDeviceShaderDrawParameterFeatures;

VkPhysicalDeviceShaderDrawParameterFeatures registry at www.khronos.org

Instances

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

data VkPhysicalDeviceSparseImageFormatInfo2 Source #

typedef struct VkPhysicalDeviceSparseImageFormatInfo2 {
    VkStructureType sType;
    const void*                      pNext;
    VkFormat                         format;
    VkImageType                      type;
    VkSampleCountFlagBits            samples;
    VkImageUsageFlags                usage;
    VkImageTiling                    tiling;
} VkPhysicalDeviceSparseImageFormatInfo2;

VkPhysicalDeviceSparseImageFormatInfo2 registry at www.khronos.org

Instances

Eq VkPhysicalDeviceSparseImageFormatInfo2 Source # 
Ord VkPhysicalDeviceSparseImageFormatInfo2 Source # 
Show VkPhysicalDeviceSparseImageFormatInfo2 Source # 
Storable VkPhysicalDeviceSparseImageFormatInfo2 Source # 
VulkanMarshalPrim VkPhysicalDeviceSparseImageFormatInfo2 Source # 
VulkanMarshal VkPhysicalDeviceSparseImageFormatInfo2 Source # 
CanWriteField "format" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
CanWriteField "pNext" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
CanWriteField "sType" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
CanWriteField "samples" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
CanWriteField "tiling" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
CanWriteField "type" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
CanWriteField "usage" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
CanReadField "format" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
CanReadField "pNext" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
CanReadField "sType" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
CanReadField "samples" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
CanReadField "tiling" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
CanReadField "type" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
CanReadField "usage" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
HasField "format" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
HasField "pNext" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
HasField "sType" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
HasField "samples" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
HasField "tiling" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
HasField "type" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
HasField "usage" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
type StructFields VkPhysicalDeviceSparseImageFormatInfo2 Source # 
type StructFields VkPhysicalDeviceSparseImageFormatInfo2 = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "format" ((:) Symbol "type" ((:) Symbol "samples" ((:) Symbol "usage" ((:) Symbol "tiling" ([] Symbol)))))))
type CUnionType VkPhysicalDeviceSparseImageFormatInfo2 Source # 
type ReturnedOnly VkPhysicalDeviceSparseImageFormatInfo2 Source # 
type StructExtends VkPhysicalDeviceSparseImageFormatInfo2 Source # 
type FieldType "format" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
type FieldType "pNext" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
type FieldType "sType" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
type FieldType "samples" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
type FieldType "tiling" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
type FieldType "type" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
type FieldType "usage" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
type FieldOptional "format" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
type FieldOptional "pNext" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
type FieldOptional "sType" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
type FieldOptional "samples" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
type FieldOptional "tiling" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
type FieldOptional "type" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
type FieldOptional "usage" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
type FieldOffset "format" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
type FieldOffset "pNext" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
type FieldOffset "sType" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
type FieldOffset "samples" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
type FieldOffset "tiling" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
type FieldOffset "type" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
type FieldOffset "usage" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
type FieldIsArray "format" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
type FieldIsArray "pNext" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
type FieldIsArray "sType" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
type FieldIsArray "samples" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
type FieldIsArray "tiling" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
type FieldIsArray "type" VkPhysicalDeviceSparseImageFormatInfo2 Source # 
type FieldIsArray "usage" VkPhysicalDeviceSparseImageFormatInfo2 Source # 

data VkPhysicalDeviceSparseProperties Source #

typedef struct VkPhysicalDeviceSparseProperties {
    VkBool32               residencyStandard2DBlockShape;
    VkBool32               residencyStandard2DMultisampleBlockShape;
    VkBool32               residencyStandard3DBlockShape;
    VkBool32               residencyAlignedMipSize;
    VkBool32               residencyNonResidentStrict;
} VkPhysicalDeviceSparseProperties;

VkPhysicalDeviceSparseProperties registry at www.khronos.org

Instances

Eq VkPhysicalDeviceSparseProperties Source # 
Ord VkPhysicalDeviceSparseProperties Source # 
Show VkPhysicalDeviceSparseProperties Source # 
Storable VkPhysicalDeviceSparseProperties Source # 
VulkanMarshalPrim VkPhysicalDeviceSparseProperties Source # 
VulkanMarshal VkPhysicalDeviceSparseProperties Source # 
CanWriteField "residencyAlignedMipSize" VkPhysicalDeviceSparseProperties Source # 
CanWriteField "residencyNonResidentStrict" VkPhysicalDeviceSparseProperties Source # 
CanWriteField "residencyStandard2DBlockShape" VkPhysicalDeviceSparseProperties Source # 
CanWriteField "residencyStandard2DMultisampleBlockShape" VkPhysicalDeviceSparseProperties Source # 

Methods

writeField :: Ptr VkPhysicalDeviceSparseProperties -> FieldType "residencyStandard2DMultisampleBlockShape" VkPhysicalDeviceSparseProperties -> IO () Source #

CanWriteField "residencyStandard3DBlockShape" VkPhysicalDeviceSparseProperties Source # 
CanReadField "residencyAlignedMipSize" VkPhysicalDeviceSparseProperties Source # 
CanReadField "residencyNonResidentStrict" VkPhysicalDeviceSparseProperties Source # 
CanReadField "residencyStandard2DBlockShape" VkPhysicalDeviceSparseProperties Source # 
CanReadField "residencyStandard2DMultisampleBlockShape" VkPhysicalDeviceSparseProperties Source # 
CanReadField "residencyStandard3DBlockShape" VkPhysicalDeviceSparseProperties Source # 
HasField "residencyAlignedMipSize" VkPhysicalDeviceSparseProperties Source # 

Associated Types

type FieldType ("residencyAlignedMipSize" :: Symbol) VkPhysicalDeviceSparseProperties :: Type Source #

type FieldOptional ("residencyAlignedMipSize" :: Symbol) VkPhysicalDeviceSparseProperties :: Bool Source #

type FieldOffset ("residencyAlignedMipSize" :: Symbol) VkPhysicalDeviceSparseProperties :: Nat Source #

type FieldIsArray ("residencyAlignedMipSize" :: Symbol) VkPhysicalDeviceSparseProperties :: Bool Source #

HasField "residencyNonResidentStrict" VkPhysicalDeviceSparseProperties Source # 

Associated Types

type FieldType ("residencyNonResidentStrict" :: Symbol) VkPhysicalDeviceSparseProperties :: Type Source #

type FieldOptional ("residencyNonResidentStrict" :: Symbol) VkPhysicalDeviceSparseProperties :: Bool Source #

type FieldOffset ("residencyNonResidentStrict" :: Symbol) VkPhysicalDeviceSparseProperties :: Nat Source #

type FieldIsArray ("residencyNonResidentStrict" :: Symbol) VkPhysicalDeviceSparseProperties :: Bool Source #

HasField "residencyStandard2DBlockShape" VkPhysicalDeviceSparseProperties Source # 

Associated Types

type FieldType ("residencyStandard2DBlockShape" :: Symbol) VkPhysicalDeviceSparseProperties :: Type Source #

type FieldOptional ("residencyStandard2DBlockShape" :: Symbol) VkPhysicalDeviceSparseProperties :: Bool Source #

type FieldOffset ("residencyStandard2DBlockShape" :: Symbol) VkPhysicalDeviceSparseProperties :: Nat Source #

type FieldIsArray ("residencyStandard2DBlockShape" :: Symbol) VkPhysicalDeviceSparseProperties :: Bool Source #

HasField "residencyStandard2DMultisampleBlockShape" VkPhysicalDeviceSparseProperties Source # 

Associated Types

type FieldType ("residencyStandard2DMultisampleBlockShape" :: Symbol) VkPhysicalDeviceSparseProperties :: Type Source #

type FieldOptional ("residencyStandard2DMultisampleBlockShape" :: Symbol) VkPhysicalDeviceSparseProperties :: Bool Source #

type FieldOffset ("residencyStandard2DMultisampleBlockShape" :: Symbol) VkPhysicalDeviceSparseProperties :: Nat Source #

type FieldIsArray ("residencyStandard2DMultisampleBlockShape" :: Symbol) VkPhysicalDeviceSparseProperties :: Bool Source #

HasField "residencyStandard3DBlockShape" VkPhysicalDeviceSparseProperties Source # 

Associated Types

type FieldType ("residencyStandard3DBlockShape" :: Symbol) VkPhysicalDeviceSparseProperties :: Type Source #

type FieldOptional ("residencyStandard3DBlockShape" :: Symbol) VkPhysicalDeviceSparseProperties :: Bool Source #

type FieldOffset ("residencyStandard3DBlockShape" :: Symbol) VkPhysicalDeviceSparseProperties :: Nat Source #

type FieldIsArray ("residencyStandard3DBlockShape" :: Symbol) VkPhysicalDeviceSparseProperties :: Bool Source #

type StructFields VkPhysicalDeviceSparseProperties Source # 
type StructFields VkPhysicalDeviceSparseProperties = (:) Symbol "residencyStandard2DBlockShape" ((:) Symbol "residencyStandard2DMultisampleBlockShape" ((:) Symbol "residencyStandard3DBlockShape" ((:) Symbol "residencyAlignedMipSize" ((:) Symbol "residencyNonResidentStrict" ([] Symbol)))))
type CUnionType VkPhysicalDeviceSparseProperties Source # 
type ReturnedOnly VkPhysicalDeviceSparseProperties Source # 
type StructExtends VkPhysicalDeviceSparseProperties Source # 
type FieldType "residencyAlignedMipSize" VkPhysicalDeviceSparseProperties Source # 
type FieldType "residencyAlignedMipSize" VkPhysicalDeviceSparseProperties = VkBool32
type FieldType "residencyNonResidentStrict" VkPhysicalDeviceSparseProperties Source # 
type FieldType "residencyNonResidentStrict" VkPhysicalDeviceSparseProperties = VkBool32
type FieldType "residencyStandard2DBlockShape" VkPhysicalDeviceSparseProperties Source # 
type FieldType "residencyStandard2DBlockShape" VkPhysicalDeviceSparseProperties = VkBool32
type FieldType "residencyStandard2DMultisampleBlockShape" VkPhysicalDeviceSparseProperties Source # 
type FieldType "residencyStandard2DMultisampleBlockShape" VkPhysicalDeviceSparseProperties = VkBool32
type FieldType "residencyStandard3DBlockShape" VkPhysicalDeviceSparseProperties Source # 
type FieldType "residencyStandard3DBlockShape" VkPhysicalDeviceSparseProperties = VkBool32
type FieldOptional "residencyAlignedMipSize" VkPhysicalDeviceSparseProperties Source # 
type FieldOptional "residencyAlignedMipSize" VkPhysicalDeviceSparseProperties = False
type FieldOptional "residencyNonResidentStrict" VkPhysicalDeviceSparseProperties Source # 
type FieldOptional "residencyNonResidentStrict" VkPhysicalDeviceSparseProperties = False
type FieldOptional "residencyStandard2DBlockShape" VkPhysicalDeviceSparseProperties Source # 
type FieldOptional "residencyStandard2DBlockShape" VkPhysicalDeviceSparseProperties = False
type FieldOptional "residencyStandard2DMultisampleBlockShape" VkPhysicalDeviceSparseProperties Source # 
type FieldOptional "residencyStandard2DMultisampleBlockShape" VkPhysicalDeviceSparseProperties = False
type FieldOptional "residencyStandard3DBlockShape" VkPhysicalDeviceSparseProperties Source # 
type FieldOptional "residencyStandard3DBlockShape" VkPhysicalDeviceSparseProperties = False
type FieldOffset "residencyAlignedMipSize" VkPhysicalDeviceSparseProperties Source # 
type FieldOffset "residencyAlignedMipSize" VkPhysicalDeviceSparseProperties = 12
type FieldOffset "residencyNonResidentStrict" VkPhysicalDeviceSparseProperties Source # 
type FieldOffset "residencyNonResidentStrict" VkPhysicalDeviceSparseProperties = 16
type FieldOffset "residencyStandard2DBlockShape" VkPhysicalDeviceSparseProperties Source # 
type FieldOffset "residencyStandard2DBlockShape" VkPhysicalDeviceSparseProperties = 0
type FieldOffset "residencyStandard2DMultisampleBlockShape" VkPhysicalDeviceSparseProperties Source # 
type FieldOffset "residencyStandard2DMultisampleBlockShape" VkPhysicalDeviceSparseProperties = 4
type FieldOffset "residencyStandard3DBlockShape" VkPhysicalDeviceSparseProperties Source # 
type FieldOffset "residencyStandard3DBlockShape" VkPhysicalDeviceSparseProperties = 8
type FieldIsArray "residencyAlignedMipSize" VkPhysicalDeviceSparseProperties Source # 
type FieldIsArray "residencyAlignedMipSize" VkPhysicalDeviceSparseProperties = False
type FieldIsArray "residencyNonResidentStrict" VkPhysicalDeviceSparseProperties Source # 
type FieldIsArray "residencyNonResidentStrict" VkPhysicalDeviceSparseProperties = False
type FieldIsArray "residencyStandard2DBlockShape" VkPhysicalDeviceSparseProperties Source # 
type FieldIsArray "residencyStandard2DBlockShape" VkPhysicalDeviceSparseProperties = False
type FieldIsArray "residencyStandard2DMultisampleBlockShape" VkPhysicalDeviceSparseProperties Source # 
type FieldIsArray "residencyStandard2DMultisampleBlockShape" VkPhysicalDeviceSparseProperties = False
type FieldIsArray "residencyStandard3DBlockShape" VkPhysicalDeviceSparseProperties Source # 
type FieldIsArray "residencyStandard3DBlockShape" VkPhysicalDeviceSparseProperties = False

data VkPhysicalDeviceSubgroupProperties Source #

typedef struct VkPhysicalDeviceSubgroupProperties {
    VkStructureType sType;
    void*                   pNext;
    uint32_t                      subgroupSize;
    VkShaderStageFlags            supportedStages;
    VkSubgroupFeatureFlags        supportedOperations;
    VkBool32 quadOperationsInAllStages;
} VkPhysicalDeviceSubgroupProperties;

VkPhysicalDeviceSubgroupProperties registry at www.khronos.org

Instances

Eq VkPhysicalDeviceSubgroupProperties Source # 
Ord VkPhysicalDeviceSubgroupProperties Source # 
Show VkPhysicalDeviceSubgroupProperties Source # 
Storable VkPhysicalDeviceSubgroupProperties Source # 
VulkanMarshalPrim VkPhysicalDeviceSubgroupProperties Source # 
VulkanMarshal VkPhysicalDeviceSubgroupProperties Source # 
CanWriteField "pNext" VkPhysicalDeviceSubgroupProperties Source # 
CanWriteField "quadOperationsInAllStages" VkPhysicalDeviceSubgroupProperties Source # 
CanWriteField "sType" VkPhysicalDeviceSubgroupProperties Source # 
CanWriteField "subgroupSize" VkPhysicalDeviceSubgroupProperties Source # 
CanWriteField "supportedOperations" VkPhysicalDeviceSubgroupProperties Source # 
CanWriteField "supportedStages" VkPhysicalDeviceSubgroupProperties Source # 
CanReadField "pNext" VkPhysicalDeviceSubgroupProperties Source # 
CanReadField "quadOperationsInAllStages" VkPhysicalDeviceSubgroupProperties Source # 
CanReadField "sType" VkPhysicalDeviceSubgroupProperties Source # 
CanReadField "subgroupSize" VkPhysicalDeviceSubgroupProperties Source # 
CanReadField "supportedOperations" VkPhysicalDeviceSubgroupProperties Source # 
CanReadField "supportedStages" VkPhysicalDeviceSubgroupProperties Source # 
HasField "pNext" VkPhysicalDeviceSubgroupProperties Source # 
HasField "quadOperationsInAllStages" VkPhysicalDeviceSubgroupProperties Source # 

Associated Types

type FieldType ("quadOperationsInAllStages" :: Symbol) VkPhysicalDeviceSubgroupProperties :: Type Source #

type FieldOptional ("quadOperationsInAllStages" :: Symbol) VkPhysicalDeviceSubgroupProperties :: Bool Source #

type FieldOffset ("quadOperationsInAllStages" :: Symbol) VkPhysicalDeviceSubgroupProperties :: Nat Source #

type FieldIsArray ("quadOperationsInAllStages" :: Symbol) VkPhysicalDeviceSubgroupProperties :: Bool Source #

HasField "sType" VkPhysicalDeviceSubgroupProperties Source # 
HasField "subgroupSize" VkPhysicalDeviceSubgroupProperties Source # 
HasField "supportedOperations" VkPhysicalDeviceSubgroupProperties Source # 

Associated Types

type FieldType ("supportedOperations" :: Symbol) VkPhysicalDeviceSubgroupProperties :: Type Source #

type FieldOptional ("supportedOperations" :: Symbol) VkPhysicalDeviceSubgroupProperties :: Bool Source #

type FieldOffset ("supportedOperations" :: Symbol) VkPhysicalDeviceSubgroupProperties :: Nat Source #

type FieldIsArray ("supportedOperations" :: Symbol) VkPhysicalDeviceSubgroupProperties :: Bool Source #

HasField "supportedStages" VkPhysicalDeviceSubgroupProperties Source # 
type StructFields VkPhysicalDeviceSubgroupProperties Source # 
type StructFields VkPhysicalDeviceSubgroupProperties = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "subgroupSize" ((:) Symbol "supportedStages" ((:) Symbol "supportedOperations" ((:) Symbol "quadOperationsInAllStages" ([] Symbol))))))
type CUnionType VkPhysicalDeviceSubgroupProperties Source # 
type ReturnedOnly VkPhysicalDeviceSubgroupProperties Source # 
type StructExtends VkPhysicalDeviceSubgroupProperties Source # 
type FieldType "pNext" VkPhysicalDeviceSubgroupProperties Source # 
type FieldType "quadOperationsInAllStages" VkPhysicalDeviceSubgroupProperties Source # 
type FieldType "quadOperationsInAllStages" VkPhysicalDeviceSubgroupProperties = VkBool32
type FieldType "sType" VkPhysicalDeviceSubgroupProperties Source # 
type FieldType "subgroupSize" VkPhysicalDeviceSubgroupProperties Source # 
type FieldType "supportedOperations" VkPhysicalDeviceSubgroupProperties Source # 
type FieldType "supportedStages" VkPhysicalDeviceSubgroupProperties Source # 
type FieldOptional "pNext" VkPhysicalDeviceSubgroupProperties Source # 
type FieldOptional "quadOperationsInAllStages" VkPhysicalDeviceSubgroupProperties Source # 
type FieldOptional "quadOperationsInAllStages" VkPhysicalDeviceSubgroupProperties = False
type FieldOptional "sType" VkPhysicalDeviceSubgroupProperties Source # 
type FieldOptional "subgroupSize" VkPhysicalDeviceSubgroupProperties Source # 
type FieldOptional "supportedOperations" VkPhysicalDeviceSubgroupProperties Source # 
type FieldOptional "supportedStages" VkPhysicalDeviceSubgroupProperties Source # 
type FieldOffset "pNext" VkPhysicalDeviceSubgroupProperties Source # 
type FieldOffset "quadOperationsInAllStages" VkPhysicalDeviceSubgroupProperties Source # 
type FieldOffset "quadOperationsInAllStages" VkPhysicalDeviceSubgroupProperties = 28
type FieldOffset "sType" VkPhysicalDeviceSubgroupProperties Source # 
type FieldOffset "subgroupSize" VkPhysicalDeviceSubgroupProperties Source # 
type FieldOffset "supportedOperations" VkPhysicalDeviceSubgroupProperties Source # 
type FieldOffset "supportedOperations" VkPhysicalDeviceSubgroupProperties = 24
type FieldOffset "supportedStages" VkPhysicalDeviceSubgroupProperties Source # 
type FieldIsArray "pNext" VkPhysicalDeviceSubgroupProperties Source # 
type FieldIsArray "quadOperationsInAllStages" VkPhysicalDeviceSubgroupProperties Source # 
type FieldIsArray "quadOperationsInAllStages" VkPhysicalDeviceSubgroupProperties = False
type FieldIsArray "sType" VkPhysicalDeviceSubgroupProperties Source # 
type FieldIsArray "subgroupSize" VkPhysicalDeviceSubgroupProperties Source # 
type FieldIsArray "supportedOperations" VkPhysicalDeviceSubgroupProperties Source # 
type FieldIsArray "supportedStages" VkPhysicalDeviceSubgroupProperties Source # 

data VkPhysicalDeviceSurfaceInfo2KHR Source #

typedef struct VkPhysicalDeviceSurfaceInfo2KHR {
    VkStructureType sType;
    const void* pNext;
    VkSurfaceKHR surface;
} VkPhysicalDeviceSurfaceInfo2KHR;

VkPhysicalDeviceSurfaceInfo2KHR registry at www.khronos.org

Instances

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

data VkPhysicalDeviceVariablePointerFeatures Source #

typedef struct VkPhysicalDeviceVariablePointerFeatures {
    VkStructureType sType;
    void*                            pNext;
    VkBool32                         variablePointersStorageBuffer;
    VkBool32                         variablePointers;
} VkPhysicalDeviceVariablePointerFeatures;

VkPhysicalDeviceVariablePointerFeatures registry at www.khronos.org

Instances

Eq VkPhysicalDeviceVariablePointerFeatures Source # 
Ord VkPhysicalDeviceVariablePointerFeatures Source # 
Show VkPhysicalDeviceVariablePointerFeatures Source # 
Storable VkPhysicalDeviceVariablePointerFeatures Source # 
VulkanMarshalPrim VkPhysicalDeviceVariablePointerFeatures Source # 
VulkanMarshal VkPhysicalDeviceVariablePointerFeatures Source # 
CanWriteField "pNext" VkPhysicalDeviceVariablePointerFeatures Source # 
CanWriteField "sType" VkPhysicalDeviceVariablePointerFeatures Source # 
CanWriteField "variablePointers" VkPhysicalDeviceVariablePointerFeatures Source # 
CanWriteField "variablePointersStorageBuffer" VkPhysicalDeviceVariablePointerFeatures Source # 
CanReadField "pNext" VkPhysicalDeviceVariablePointerFeatures Source # 
CanReadField "sType" VkPhysicalDeviceVariablePointerFeatures Source # 
CanReadField "variablePointers" VkPhysicalDeviceVariablePointerFeatures Source # 
CanReadField "variablePointersStorageBuffer" VkPhysicalDeviceVariablePointerFeatures Source # 
HasField "pNext" VkPhysicalDeviceVariablePointerFeatures Source # 
HasField "sType" VkPhysicalDeviceVariablePointerFeatures Source # 
HasField "variablePointers" VkPhysicalDeviceVariablePointerFeatures Source # 
HasField "variablePointersStorageBuffer" VkPhysicalDeviceVariablePointerFeatures Source # 

Associated Types

type FieldType ("variablePointersStorageBuffer" :: Symbol) VkPhysicalDeviceVariablePointerFeatures :: Type Source #

type FieldOptional ("variablePointersStorageBuffer" :: Symbol) VkPhysicalDeviceVariablePointerFeatures :: Bool Source #

type FieldOffset ("variablePointersStorageBuffer" :: Symbol) VkPhysicalDeviceVariablePointerFeatures :: Nat Source #

type FieldIsArray ("variablePointersStorageBuffer" :: Symbol) VkPhysicalDeviceVariablePointerFeatures :: Bool Source #

type StructFields VkPhysicalDeviceVariablePointerFeatures Source # 
type StructFields VkPhysicalDeviceVariablePointerFeatures = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "variablePointersStorageBuffer" ((:) Symbol "variablePointers" ([] Symbol))))
type CUnionType VkPhysicalDeviceVariablePointerFeatures Source # 
type ReturnedOnly VkPhysicalDeviceVariablePointerFeatures Source # 
type StructExtends VkPhysicalDeviceVariablePointerFeatures Source # 
type FieldType "pNext" VkPhysicalDeviceVariablePointerFeatures Source # 
type FieldType "sType" VkPhysicalDeviceVariablePointerFeatures Source # 
type FieldType "variablePointers" VkPhysicalDeviceVariablePointerFeatures Source # 
type FieldType "variablePointersStorageBuffer" VkPhysicalDeviceVariablePointerFeatures Source # 
type FieldType "variablePointersStorageBuffer" VkPhysicalDeviceVariablePointerFeatures = VkBool32
type FieldOptional "pNext" VkPhysicalDeviceVariablePointerFeatures Source # 
type FieldOptional "sType" VkPhysicalDeviceVariablePointerFeatures Source # 
type FieldOptional "variablePointers" VkPhysicalDeviceVariablePointerFeatures Source # 
type FieldOptional "variablePointersStorageBuffer" VkPhysicalDeviceVariablePointerFeatures Source # 
type FieldOptional "variablePointersStorageBuffer" VkPhysicalDeviceVariablePointerFeatures = False
type FieldOffset "pNext" VkPhysicalDeviceVariablePointerFeatures Source # 
type FieldOffset "sType" VkPhysicalDeviceVariablePointerFeatures Source # 
type FieldOffset "variablePointers" VkPhysicalDeviceVariablePointerFeatures Source # 
type FieldOffset "variablePointersStorageBuffer" VkPhysicalDeviceVariablePointerFeatures Source # 
type FieldOffset "variablePointersStorageBuffer" VkPhysicalDeviceVariablePointerFeatures = 16
type FieldIsArray "pNext" VkPhysicalDeviceVariablePointerFeatures Source # 
type FieldIsArray "sType" VkPhysicalDeviceVariablePointerFeatures Source # 
type FieldIsArray "variablePointers" VkPhysicalDeviceVariablePointerFeatures Source # 
type FieldIsArray "variablePointersStorageBuffer" VkPhysicalDeviceVariablePointerFeatures Source # 
type FieldIsArray "variablePointersStorageBuffer" VkPhysicalDeviceVariablePointerFeatures = False

data VkPhysicalDeviceVertexAttributeDivisorPropertiesEXT Source #

typedef struct VkPhysicalDeviceVertexAttributeDivisorPropertiesEXT {
    VkStructureType sType;
    void*                  pNext;
    uint32_t               maxVertexAttribDivisor;
} VkPhysicalDeviceVertexAttributeDivisorPropertiesEXT;

VkPhysicalDeviceVertexAttributeDivisorPropertiesEXT registry at www.khronos.org

Instances

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

newtype VkPhysicalDeviceType Source #

Instances

Bounded VkPhysicalDeviceType Source # 
Enum VkPhysicalDeviceType Source # 
Eq VkPhysicalDeviceType Source # 
Data VkPhysicalDeviceType Source # 

Methods

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

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

toConstr :: VkPhysicalDeviceType -> Constr #

dataTypeOf :: VkPhysicalDeviceType -> DataType #

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

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

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

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

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

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

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

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

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

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

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

newtype VkSampleCountBitmask a Source #

Instances

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

Methods

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

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

toConstr :: VkSampleCountBitmask a -> Constr #

dataTypeOf :: VkSampleCountBitmask a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

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

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

xor :: VkSampleCountBitmask FlagMask -> VkSampleCountBitmask FlagMask -> VkSampleCountBitmask FlagMask #

complement :: VkSampleCountBitmask FlagMask -> VkSampleCountBitmask FlagMask #

shift :: VkSampleCountBitmask FlagMask -> Int -> VkSampleCountBitmask FlagMask #

rotate :: VkSampleCountBitmask FlagMask -> Int -> VkSampleCountBitmask FlagMask #

zeroBits :: VkSampleCountBitmask FlagMask #

bit :: Int -> VkSampleCountBitmask FlagMask #

setBit :: VkSampleCountBitmask FlagMask -> Int -> VkSampleCountBitmask FlagMask #

clearBit :: VkSampleCountBitmask FlagMask -> Int -> VkSampleCountBitmask FlagMask #

complementBit :: VkSampleCountBitmask FlagMask -> Int -> VkSampleCountBitmask FlagMask #

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

bitSizeMaybe :: VkSampleCountBitmask FlagMask -> Maybe Int #

bitSize :: VkSampleCountBitmask FlagMask -> Int #

isSigned :: VkSampleCountBitmask FlagMask -> Bool #

shiftL :: VkSampleCountBitmask FlagMask -> Int -> VkSampleCountBitmask FlagMask #

unsafeShiftL :: VkSampleCountBitmask FlagMask -> Int -> VkSampleCountBitmask FlagMask #

shiftR :: VkSampleCountBitmask FlagMask -> Int -> VkSampleCountBitmask FlagMask #

unsafeShiftR :: VkSampleCountBitmask FlagMask -> Int -> VkSampleCountBitmask FlagMask #

rotateL :: VkSampleCountBitmask FlagMask -> Int -> VkSampleCountBitmask FlagMask #

rotateR :: VkSampleCountBitmask FlagMask -> Int -> VkSampleCountBitmask FlagMask #

popCount :: VkSampleCountBitmask FlagMask -> Int #

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

pattern VK_SAMPLE_COUNT_1_BIT :: forall a. VkSampleCountBitmask a Source #

Sample count 1 supported

bitpos = 0

pattern VK_SAMPLE_COUNT_2_BIT :: forall a. VkSampleCountBitmask a Source #

Sample count 2 supported

bitpos = 1

pattern VK_SAMPLE_COUNT_4_BIT :: forall a. VkSampleCountBitmask a Source #

Sample count 4 supported

bitpos = 2

pattern VK_SAMPLE_COUNT_8_BIT :: forall a. VkSampleCountBitmask a Source #

Sample count 8 supported

bitpos = 3

pattern VK_SAMPLE_COUNT_16_BIT :: forall a. VkSampleCountBitmask a Source #

Sample count 16 supported

bitpos = 4

pattern VK_SAMPLE_COUNT_32_BIT :: forall a. VkSampleCountBitmask a Source #

Sample count 32 supported

bitpos = 5

pattern VK_SAMPLE_COUNT_64_BIT :: forall a. VkSampleCountBitmask a Source #

Sample count 64 supported

bitpos = 6

newtype VkShaderInfoTypeAMD Source #

Instances

Bounded VkShaderInfoTypeAMD Source # 
Enum VkShaderInfoTypeAMD Source # 
Eq VkShaderInfoTypeAMD Source # 
Data VkShaderInfoTypeAMD Source # 

Methods

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

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

toConstr :: VkShaderInfoTypeAMD -> Constr #

dataTypeOf :: VkShaderInfoTypeAMD -> DataType #

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

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

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

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

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

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

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

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

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

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

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

newtype VkShaderStageBitmask a Source #

Instances

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

Methods

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

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

toConstr :: VkShaderStageBitmask a -> Constr #

dataTypeOf :: VkShaderStageBitmask a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

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

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

xor :: VkShaderStageBitmask FlagMask -> VkShaderStageBitmask FlagMask -> VkShaderStageBitmask FlagMask #

complement :: VkShaderStageBitmask FlagMask -> VkShaderStageBitmask FlagMask #

shift :: VkShaderStageBitmask FlagMask -> Int -> VkShaderStageBitmask FlagMask #

rotate :: VkShaderStageBitmask FlagMask -> Int -> VkShaderStageBitmask FlagMask #

zeroBits :: VkShaderStageBitmask FlagMask #

bit :: Int -> VkShaderStageBitmask FlagMask #

setBit :: VkShaderStageBitmask FlagMask -> Int -> VkShaderStageBitmask FlagMask #

clearBit :: VkShaderStageBitmask FlagMask -> Int -> VkShaderStageBitmask FlagMask #

complementBit :: VkShaderStageBitmask FlagMask -> Int -> VkShaderStageBitmask FlagMask #

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

bitSizeMaybe :: VkShaderStageBitmask FlagMask -> Maybe Int #

bitSize :: VkShaderStageBitmask FlagMask -> Int #

isSigned :: VkShaderStageBitmask FlagMask -> Bool #

shiftL :: VkShaderStageBitmask FlagMask -> Int -> VkShaderStageBitmask FlagMask #

unsafeShiftL :: VkShaderStageBitmask FlagMask -> Int -> VkShaderStageBitmask FlagMask #

shiftR :: VkShaderStageBitmask FlagMask -> Int -> VkShaderStageBitmask FlagMask #

unsafeShiftR :: VkShaderStageBitmask FlagMask -> Int -> VkShaderStageBitmask FlagMask #

rotateL :: VkShaderStageBitmask FlagMask -> Int -> VkShaderStageBitmask FlagMask #

rotateR :: VkShaderStageBitmask FlagMask -> Int -> VkShaderStageBitmask FlagMask #

popCount :: VkShaderStageBitmask FlagMask -> Int #

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

pattern VK_SHADER_STAGE_VERTEX_BIT :: forall a. VkShaderStageBitmask a Source #

bitpos = 0

pattern VK_SHADER_STAGE_COMPUTE_BIT :: forall a. VkShaderStageBitmask a Source #

bitpos = 5

newtype VkStructureType Source #

Structure type enumerant

type = enum

VkStructureType registry at www.khronos.org

Constructors

VkStructureType Int32 

Instances

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

Methods

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

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

toConstr :: VkStructureType -> Constr #

dataTypeOf :: VkStructureType -> DataType #

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

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

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

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

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

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

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

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

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

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

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

pattern VK_STRUCTURE_TYPE_LOADER_INSTANCE_CREATE_INFO :: VkStructureType Source #

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

pattern VK_STRUCTURE_TYPE_LOADER_DEVICE_CREATE_INFO :: VkStructureType Source #

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

newtype VkSubgroupFeatureBitmask a Source #

Instances

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

Methods

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

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

toConstr :: VkSubgroupFeatureBitmask a -> Constr #

dataTypeOf :: VkSubgroupFeatureBitmask a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

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

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

xor :: VkSubgroupFeatureBitmask FlagMask -> VkSubgroupFeatureBitmask FlagMask -> VkSubgroupFeatureBitmask FlagMask #

complement :: VkSubgroupFeatureBitmask FlagMask -> VkSubgroupFeatureBitmask FlagMask #

shift :: VkSubgroupFeatureBitmask FlagMask -> Int -> VkSubgroupFeatureBitmask FlagMask #

rotate :: VkSubgroupFeatureBitmask FlagMask -> Int -> VkSubgroupFeatureBitmask FlagMask #

zeroBits :: VkSubgroupFeatureBitmask FlagMask #

bit :: Int -> VkSubgroupFeatureBitmask FlagMask #

setBit :: VkSubgroupFeatureBitmask FlagMask -> Int -> VkSubgroupFeatureBitmask FlagMask #

clearBit :: VkSubgroupFeatureBitmask FlagMask -> Int -> VkSubgroupFeatureBitmask FlagMask #

complementBit :: VkSubgroupFeatureBitmask FlagMask -> Int -> VkSubgroupFeatureBitmask FlagMask #

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

bitSizeMaybe :: VkSubgroupFeatureBitmask FlagMask -> Maybe Int #

bitSize :: VkSubgroupFeatureBitmask FlagMask -> Int #

isSigned :: VkSubgroupFeatureBitmask FlagMask -> Bool #

shiftL :: VkSubgroupFeatureBitmask FlagMask -> Int -> VkSubgroupFeatureBitmask FlagMask #

unsafeShiftL :: VkSubgroupFeatureBitmask FlagMask -> Int -> VkSubgroupFeatureBitmask FlagMask #

shiftR :: VkSubgroupFeatureBitmask FlagMask -> Int -> VkSubgroupFeatureBitmask FlagMask #

unsafeShiftR :: VkSubgroupFeatureBitmask FlagMask -> Int -> VkSubgroupFeatureBitmask FlagMask #

rotateL :: VkSubgroupFeatureBitmask FlagMask -> Int -> VkSubgroupFeatureBitmask FlagMask #

rotateR :: VkSubgroupFeatureBitmask FlagMask -> Int -> VkSubgroupFeatureBitmask FlagMask #

popCount :: VkSubgroupFeatureBitmask FlagMask -> Int #

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

pattern VK_SUBGROUP_FEATURE_BASIC_BIT :: forall a. VkSubgroupFeatureBitmask a Source #

Basic subgroup operations

bitpos = 0

pattern VK_SUBGROUP_FEATURE_VOTE_BIT :: forall a. VkSubgroupFeatureBitmask a Source #

Vote subgroup operations

bitpos = 1

pattern VK_SUBGROUP_FEATURE_ARITHMETIC_BIT :: forall a. VkSubgroupFeatureBitmask a Source #

Arithmetic subgroup operations

bitpos = 2

pattern VK_SUBGROUP_FEATURE_BALLOT_BIT :: forall a. VkSubgroupFeatureBitmask a Source #

Ballot subgroup operations

bitpos = 3

pattern VK_SUBGROUP_FEATURE_SHUFFLE_BIT :: forall a. VkSubgroupFeatureBitmask a Source #

Shuffle subgroup operations

bitpos = 4

pattern VK_SUBGROUP_FEATURE_SHUFFLE_RELATIVE_BIT :: forall a. VkSubgroupFeatureBitmask a Source #

Shuffle relative subgroup operations

bitpos = 5

pattern VK_SUBGROUP_FEATURE_CLUSTERED_BIT :: forall a. VkSubgroupFeatureBitmask a Source #

Clustered subgroup operations

bitpos = 6

pattern VK_SUBGROUP_FEATURE_QUAD_BIT :: forall a. VkSubgroupFeatureBitmask a Source #

Quad subgroup operations

bitpos = 7

Promoted from VK_KHR_bind_memory2

data VkBindBufferMemoryDeviceGroupInfo Source #

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

VkBindBufferMemoryDeviceGroupInfo registry at www.khronos.org

Instances

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

data VkBindBufferMemoryInfo Source #

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

VkBindBufferMemoryInfo registry at www.khronos.org

Instances

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

Associated Types

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

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

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

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

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

data VkBindImageMemoryDeviceGroupInfo Source #

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

VkBindImageMemoryDeviceGroupInfo registry at www.khronos.org

Instances

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

Associated Types

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

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

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

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

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

Associated Types

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

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

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

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

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

data VkBindImageMemoryInfo Source #

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

VkBindImageMemoryInfo registry at www.khronos.org

Instances

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

Associated Types

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

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

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

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

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

data VkBindImageMemorySwapchainInfoKHR Source #

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

VkBindImageMemorySwapchainInfoKHR registry at www.khronos.org

Instances

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

data VkBindImagePlaneMemoryInfo Source #

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

VkBindImagePlaneMemoryInfo registry at www.khronos.org

Instances

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

data VkBindSparseInfo Source #

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

VkBindSparseInfo registry at www.khronos.org

Instances

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

Methods

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

CanWriteField "imageBindCount" VkBindSparseInfo Source # 

Methods

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

CanWriteField "imageOpaqueBindCount" VkBindSparseInfo Source # 

Methods

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

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

Methods

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

CanWriteField "pNext" VkBindSparseInfo Source # 
CanWriteField "pSignalSemaphores" VkBindSparseInfo Source # 

Methods

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

CanWriteField "pWaitSemaphores" VkBindSparseInfo Source # 

Methods

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

CanWriteField "sType" VkBindSparseInfo Source # 
CanWriteField "signalSemaphoreCount" VkBindSparseInfo Source # 

Methods

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

CanWriteField "waitSemaphoreCount" VkBindSparseInfo Source # 

Methods

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

CanReadField "bufferBindCount" VkBindSparseInfo Source # 
CanReadField "imageBindCount" VkBindSparseInfo Source # 
CanReadField "imageOpaqueBindCount" VkBindSparseInfo Source # 

Methods

getField :: VkBindSparseInfo -> FieldType "imageOpaqueBindCount" VkBindSparseInfo Source #

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

CanReadField "pBufferBinds" VkBindSparseInfo Source # 
CanReadField "pImageBinds" VkBindSparseInfo Source # 
CanReadField "pImageOpaqueBinds" VkBindSparseInfo Source # 
CanReadField "pNext" VkBindSparseInfo Source # 
CanReadField "pSignalSemaphores" VkBindSparseInfo Source # 
CanReadField "pWaitSemaphores" VkBindSparseInfo Source # 
CanReadField "sType" VkBindSparseInfo Source # 
CanReadField "signalSemaphoreCount" VkBindSparseInfo Source # 

Methods

getField :: VkBindSparseInfo -> FieldType "signalSemaphoreCount" VkBindSparseInfo Source #

readField :: Ptr VkBindSparseInfo -> IO (FieldType "signalSemaphoreCount" VkBindSparseInfo) Source #

CanReadField "waitSemaphoreCount" VkBindSparseInfo Source # 
HasField "bufferBindCount" VkBindSparseInfo Source # 

Associated Types

type FieldType ("bufferBindCount" :: Symbol) VkBindSparseInfo :: Type Source #

type FieldOptional ("bufferBindCount" :: Symbol) VkBindSparseInfo :: Bool Source #

type FieldOffset ("bufferBindCount" :: Symbol) VkBindSparseInfo :: Nat Source #

type FieldIsArray ("bufferBindCount" :: Symbol) VkBindSparseInfo :: Bool Source #

HasField "imageBindCount" VkBindSparseInfo Source # 

Associated Types

type FieldType ("imageBindCount" :: Symbol) VkBindSparseInfo :: Type Source #

type FieldOptional ("imageBindCount" :: Symbol) VkBindSparseInfo :: Bool Source #

type FieldOffset ("imageBindCount" :: Symbol) VkBindSparseInfo :: Nat Source #

type FieldIsArray ("imageBindCount" :: Symbol) VkBindSparseInfo :: Bool Source #

HasField "imageOpaqueBindCount" VkBindSparseInfo Source # 

Associated Types

type FieldType ("imageOpaqueBindCount" :: Symbol) VkBindSparseInfo :: Type Source #

type FieldOptional ("imageOpaqueBindCount" :: Symbol) VkBindSparseInfo :: Bool Source #

type FieldOffset ("imageOpaqueBindCount" :: Symbol) VkBindSparseInfo :: Nat Source #

type FieldIsArray ("imageOpaqueBindCount" :: Symbol) VkBindSparseInfo :: Bool Source #

HasField "pBufferBinds" VkBindSparseInfo Source # 

Associated Types

type FieldType ("pBufferBinds" :: Symbol) VkBindSparseInfo :: Type Source #

type FieldOptional ("pBufferBinds" :: Symbol) VkBindSparseInfo :: Bool Source #

type FieldOffset ("pBufferBinds" :: Symbol) VkBindSparseInfo :: Nat Source #

type FieldIsArray ("pBufferBinds" :: Symbol) VkBindSparseInfo :: Bool Source #

HasField "pImageBinds" VkBindSparseInfo Source # 

Associated Types

type FieldType ("pImageBinds" :: Symbol) VkBindSparseInfo :: Type Source #

type FieldOptional ("pImageBinds" :: Symbol) VkBindSparseInfo :: Bool Source #

type FieldOffset ("pImageBinds" :: Symbol) VkBindSparseInfo :: Nat Source #

type FieldIsArray ("pImageBinds" :: Symbol) VkBindSparseInfo :: Bool Source #

HasField "pImageOpaqueBinds" VkBindSparseInfo Source # 

Associated Types

type FieldType ("pImageOpaqueBinds" :: Symbol) VkBindSparseInfo :: Type Source #

type FieldOptional ("pImageOpaqueBinds" :: Symbol) VkBindSparseInfo :: Bool Source #

type FieldOffset ("pImageOpaqueBinds" :: Symbol) VkBindSparseInfo :: Nat Source #

type FieldIsArray ("pImageOpaqueBinds" :: Symbol) VkBindSparseInfo :: Bool Source #

HasField "pNext" VkBindSparseInfo Source # 
HasField "pSignalSemaphores" VkBindSparseInfo Source # 

Associated Types

type FieldType ("pSignalSemaphores" :: Symbol) VkBindSparseInfo :: Type Source #

type FieldOptional ("pSignalSemaphores" :: Symbol) VkBindSparseInfo :: Bool Source #

type FieldOffset ("pSignalSemaphores" :: Symbol) VkBindSparseInfo :: Nat Source #

type FieldIsArray ("pSignalSemaphores" :: Symbol) VkBindSparseInfo :: Bool Source #

HasField "pWaitSemaphores" VkBindSparseInfo Source # 

Associated Types

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

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

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

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

HasField "sType" VkBindSparseInfo Source # 
HasField "signalSemaphoreCount" VkBindSparseInfo Source # 

Associated Types

type FieldType ("signalSemaphoreCount" :: Symbol) VkBindSparseInfo :: Type Source #

type FieldOptional ("signalSemaphoreCount" :: Symbol) VkBindSparseInfo :: Bool Source #

type FieldOffset ("signalSemaphoreCount" :: Symbol) VkBindSparseInfo :: Nat Source #

type FieldIsArray ("signalSemaphoreCount" :: Symbol) VkBindSparseInfo :: Bool Source #

HasField "waitSemaphoreCount" VkBindSparseInfo Source # 

Associated Types

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

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

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

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

type StructFields VkBindSparseInfo Source # 
type StructFields VkBindSparseInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "waitSemaphoreCount" ((:) Symbol "pWaitSemaphores" ((:) Symbol "bufferBindCount" ((:) Symbol "pBufferBinds" ((:) Symbol "imageOpaqueBindCount" ((:) Symbol "pImageOpaqueBinds" ((:) Symbol "imageBindCount" ((:) Symbol "pImageBinds" ((:) Symbol "signalSemaphoreCount" ((:) Symbol "pSignalSemaphores" ([] Symbol))))))))))))
type CUnionType VkBindSparseInfo Source # 
type ReturnedOnly VkBindSparseInfo Source # 
type StructExtends VkBindSparseInfo Source # 
type FieldType "bufferBindCount" VkBindSparseInfo Source # 
type FieldType "bufferBindCount" VkBindSparseInfo = Word32
type FieldType "imageBindCount" VkBindSparseInfo Source # 
type FieldType "imageBindCount" VkBindSparseInfo = Word32
type FieldType "imageOpaqueBindCount" VkBindSparseInfo Source # 
type FieldType "imageOpaqueBindCount" VkBindSparseInfo = Word32
type FieldType "pBufferBinds" VkBindSparseInfo Source # 
type FieldType "pImageBinds" VkBindSparseInfo Source # 
type FieldType "pImageOpaqueBinds" VkBindSparseInfo Source # 
type FieldType "pNext" VkBindSparseInfo Source # 
type FieldType "pSignalSemaphores" VkBindSparseInfo Source # 
type FieldType "pSignalSemaphores" VkBindSparseInfo = Ptr VkSemaphore
type FieldType "pWaitSemaphores" VkBindSparseInfo Source # 
type FieldType "pWaitSemaphores" VkBindSparseInfo = Ptr VkSemaphore
type FieldType "sType" VkBindSparseInfo Source # 
type FieldType "signalSemaphoreCount" VkBindSparseInfo Source # 
type FieldType "signalSemaphoreCount" VkBindSparseInfo = Word32
type FieldType "waitSemaphoreCount" VkBindSparseInfo Source # 
type FieldType "waitSemaphoreCount" VkBindSparseInfo = Word32
type FieldOptional "bufferBindCount" VkBindSparseInfo Source # 
type FieldOptional "bufferBindCount" VkBindSparseInfo = True
type FieldOptional "imageBindCount" VkBindSparseInfo Source # 
type FieldOptional "imageBindCount" VkBindSparseInfo = True
type FieldOptional "imageOpaqueBindCount" VkBindSparseInfo Source # 
type FieldOptional "imageOpaqueBindCount" VkBindSparseInfo = True
type FieldOptional "pBufferBinds" VkBindSparseInfo Source # 
type FieldOptional "pBufferBinds" VkBindSparseInfo = False
type FieldOptional "pImageBinds" VkBindSparseInfo Source # 
type FieldOptional "pImageBinds" VkBindSparseInfo = False
type FieldOptional "pImageOpaqueBinds" VkBindSparseInfo Source # 
type FieldOptional "pImageOpaqueBinds" VkBindSparseInfo = False
type FieldOptional "pNext" VkBindSparseInfo Source # 
type FieldOptional "pSignalSemaphores" VkBindSparseInfo Source # 
type FieldOptional "pSignalSemaphores" VkBindSparseInfo = False
type FieldOptional "pWaitSemaphores" VkBindSparseInfo Source # 
type FieldOptional "pWaitSemaphores" VkBindSparseInfo = False
type FieldOptional "sType" VkBindSparseInfo Source # 
type FieldOptional "signalSemaphoreCount" VkBindSparseInfo Source # 
type FieldOptional "signalSemaphoreCount" VkBindSparseInfo = True
type FieldOptional "waitSemaphoreCount" VkBindSparseInfo Source # 
type FieldOptional "waitSemaphoreCount" VkBindSparseInfo = True
type FieldOffset "bufferBindCount" VkBindSparseInfo Source # 
type FieldOffset "bufferBindCount" VkBindSparseInfo = 32
type FieldOffset "imageBindCount" VkBindSparseInfo Source # 
type FieldOffset "imageBindCount" VkBindSparseInfo = 64
type FieldOffset "imageOpaqueBindCount" VkBindSparseInfo Source # 
type FieldOffset "imageOpaqueBindCount" VkBindSparseInfo = 48
type FieldOffset "pBufferBinds" VkBindSparseInfo Source # 
type FieldOffset "pBufferBinds" VkBindSparseInfo = 40
type FieldOffset "pImageBinds" VkBindSparseInfo Source # 
type FieldOffset "pImageBinds" VkBindSparseInfo = 72
type FieldOffset "pImageOpaqueBinds" VkBindSparseInfo Source # 
type FieldOffset "pImageOpaqueBinds" VkBindSparseInfo = 56
type FieldOffset "pNext" VkBindSparseInfo Source # 
type FieldOffset "pNext" VkBindSparseInfo = 8
type FieldOffset "pSignalSemaphores" VkBindSparseInfo Source # 
type FieldOffset "pSignalSemaphores" VkBindSparseInfo = 88
type FieldOffset "pWaitSemaphores" VkBindSparseInfo Source # 
type FieldOffset "pWaitSemaphores" VkBindSparseInfo = 24
type FieldOffset "sType" VkBindSparseInfo Source # 
type FieldOffset "sType" VkBindSparseInfo = 0
type FieldOffset "signalSemaphoreCount" VkBindSparseInfo Source # 
type FieldOffset "signalSemaphoreCount" VkBindSparseInfo = 80
type FieldOffset "waitSemaphoreCount" VkBindSparseInfo Source # 
type FieldOffset "waitSemaphoreCount" VkBindSparseInfo = 16
type FieldIsArray "bufferBindCount" VkBindSparseInfo Source # 
type FieldIsArray "bufferBindCount" VkBindSparseInfo = False
type FieldIsArray "imageBindCount" VkBindSparseInfo Source # 
type FieldIsArray "imageBindCount" VkBindSparseInfo = False
type FieldIsArray "imageOpaqueBindCount" VkBindSparseInfo Source # 
type FieldIsArray "imageOpaqueBindCount" VkBindSparseInfo = False
type FieldIsArray "pBufferBinds" VkBindSparseInfo Source # 
type FieldIsArray "pBufferBinds" VkBindSparseInfo = False
type FieldIsArray "pImageBinds" VkBindSparseInfo Source # 
type FieldIsArray "pImageBinds" VkBindSparseInfo = False
type FieldIsArray "pImageOpaqueBinds" VkBindSparseInfo Source # 
type FieldIsArray "pImageOpaqueBinds" VkBindSparseInfo = False
type FieldIsArray "pNext" VkBindSparseInfo Source # 
type FieldIsArray "pSignalSemaphores" VkBindSparseInfo Source # 
type FieldIsArray "pSignalSemaphores" VkBindSparseInfo = False
type FieldIsArray "pWaitSemaphores" VkBindSparseInfo Source # 
type FieldIsArray "pWaitSemaphores" VkBindSparseInfo = False
type FieldIsArray "sType" VkBindSparseInfo Source # 
type FieldIsArray "signalSemaphoreCount" VkBindSparseInfo Source # 
type FieldIsArray "signalSemaphoreCount" VkBindSparseInfo = False
type FieldIsArray "waitSemaphoreCount" VkBindSparseInfo Source # 
type FieldIsArray "waitSemaphoreCount" VkBindSparseInfo = False

type VkBindBufferMemory2 = "vkBindBufferMemory2" Source #

type HS_vkBindBufferMemory2 Source #

Arguments

 = VkDevice

device

-> Word32

bindInfoCount

-> Ptr VkBindBufferMemoryInfo

pBindInfos

-> IO VkResult 

Success codes: VK_SUCCESS.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY.

VkResult vkBindBufferMemory2
    ( VkDevice device
    , uint32_t bindInfoCount
    , const VkBindBufferMemoryInfo* pBindInfos
    )

vkBindBufferMemory2 registry at www.khronos.org

vkBindBufferMemory2 Source #

Arguments

:: VkDevice

device

-> Word32

bindInfoCount

-> Ptr VkBindBufferMemoryInfo

pBindInfos

-> IO VkResult 

Success codes: VK_SUCCESS.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY.

VkResult vkBindBufferMemory2
    ( VkDevice device
    , uint32_t bindInfoCount
    , const VkBindBufferMemoryInfo* pBindInfos
    )

vkBindBufferMemory2 registry at www.khronos.org

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

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

myBindBufferMemory2 <- vkGetDeviceProc @VkBindBufferMemory2 vkDevice

or less efficient:

myBindBufferMemory2 <- vkGetProc @VkBindBufferMemory2

Note: vkBindBufferMemory2Unsafe and vkBindBufferMemory2Safe are the unsafe and safe FFI imports of this function, respectively. vkBindBufferMemory2 is an alias of vkBindBufferMemory2Unsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkBindBufferMemory2Safe.

vkBindBufferMemory2Unsafe Source #

Arguments

:: VkDevice

device

-> Word32

bindInfoCount

-> Ptr VkBindBufferMemoryInfo

pBindInfos

-> IO VkResult 

Success codes: VK_SUCCESS.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY.

VkResult vkBindBufferMemory2
    ( VkDevice device
    , uint32_t bindInfoCount
    , const VkBindBufferMemoryInfo* pBindInfos
    )

vkBindBufferMemory2 registry at www.khronos.org

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

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

myBindBufferMemory2 <- vkGetDeviceProc @VkBindBufferMemory2 vkDevice

or less efficient:

myBindBufferMemory2 <- vkGetProc @VkBindBufferMemory2

Note: vkBindBufferMemory2Unsafe and vkBindBufferMemory2Safe are the unsafe and safe FFI imports of this function, respectively. vkBindBufferMemory2 is an alias of vkBindBufferMemory2Unsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkBindBufferMemory2Safe.

vkBindBufferMemory2Safe Source #

Arguments

:: VkDevice

device

-> Word32

bindInfoCount

-> Ptr VkBindBufferMemoryInfo

pBindInfos

-> IO VkResult 

Success codes: VK_SUCCESS.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY.

VkResult vkBindBufferMemory2
    ( VkDevice device
    , uint32_t bindInfoCount
    , const VkBindBufferMemoryInfo* pBindInfos
    )

vkBindBufferMemory2 registry at www.khronos.org

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

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

myBindBufferMemory2 <- vkGetDeviceProc @VkBindBufferMemory2 vkDevice

or less efficient:

myBindBufferMemory2 <- vkGetProc @VkBindBufferMemory2

Note: vkBindBufferMemory2Unsafe and vkBindBufferMemory2Safe are the unsafe and safe FFI imports of this function, respectively. vkBindBufferMemory2 is an alias of vkBindBufferMemory2Unsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkBindBufferMemory2Safe.

type VkBindImageMemory2 = "vkBindImageMemory2" Source #

type HS_vkBindImageMemory2 Source #

Arguments

 = VkDevice

device

-> Word32

bindInfoCount

-> Ptr VkBindImageMemoryInfo

pBindInfos

-> IO VkResult 

Success codes: VK_SUCCESS.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY.

VkResult vkBindImageMemory2
    ( VkDevice device
    , uint32_t bindInfoCount
    , const VkBindImageMemoryInfo* pBindInfos
    )

vkBindImageMemory2 registry at www.khronos.org

vkBindImageMemory2 Source #

Arguments

:: VkDevice

device

-> Word32

bindInfoCount

-> Ptr VkBindImageMemoryInfo

pBindInfos

-> IO VkResult 

Success codes: VK_SUCCESS.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY.

VkResult vkBindImageMemory2
    ( VkDevice device
    , uint32_t bindInfoCount
    , const VkBindImageMemoryInfo* pBindInfos
    )

vkBindImageMemory2 registry at www.khronos.org

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

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

myBindImageMemory2 <- vkGetDeviceProc @VkBindImageMemory2 vkDevice

or less efficient:

myBindImageMemory2 <- vkGetProc @VkBindImageMemory2

Note: vkBindImageMemory2Unsafe and vkBindImageMemory2Safe are the unsafe and safe FFI imports of this function, respectively. vkBindImageMemory2 is an alias of vkBindImageMemory2Unsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkBindImageMemory2Safe.

vkBindImageMemory2Unsafe Source #

Arguments

:: VkDevice

device

-> Word32

bindInfoCount

-> Ptr VkBindImageMemoryInfo

pBindInfos

-> IO VkResult 

Success codes: VK_SUCCESS.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY.

VkResult vkBindImageMemory2
    ( VkDevice device
    , uint32_t bindInfoCount
    , const VkBindImageMemoryInfo* pBindInfos
    )

vkBindImageMemory2 registry at www.khronos.org

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

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

myBindImageMemory2 <- vkGetDeviceProc @VkBindImageMemory2 vkDevice

or less efficient:

myBindImageMemory2 <- vkGetProc @VkBindImageMemory2

Note: vkBindImageMemory2Unsafe and vkBindImageMemory2Safe are the unsafe and safe FFI imports of this function, respectively. vkBindImageMemory2 is an alias of vkBindImageMemory2Unsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkBindImageMemory2Safe.

vkBindImageMemory2Safe Source #

Arguments

:: VkDevice

device

-> Word32

bindInfoCount

-> Ptr VkBindImageMemoryInfo

pBindInfos

-> IO VkResult 

Success codes: VK_SUCCESS.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY.

VkResult vkBindImageMemory2
    ( VkDevice device
    , uint32_t bindInfoCount
    , const VkBindImageMemoryInfo* pBindInfos
    )

vkBindImageMemory2 registry at www.khronos.org

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

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

myBindImageMemory2 <- vkGetDeviceProc @VkBindImageMemory2 vkDevice

or less efficient:

myBindImageMemory2 <- vkGetProc @VkBindImageMemory2

Note: vkBindImageMemory2Unsafe and vkBindImageMemory2Safe are the unsafe and safe FFI imports of this function, respectively. vkBindImageMemory2 is an alias of vkBindImageMemory2Unsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkBindImageMemory2Safe.

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

Promoted from VK_KHR_16bit_storage

newtype VkAndroidSurfaceCreateFlagsKHR Source #

Instances

Bounded VkAndroidSurfaceCreateFlagsKHR Source # 
Enum VkAndroidSurfaceCreateFlagsKHR Source # 
Eq VkAndroidSurfaceCreateFlagsKHR Source # 
Integral VkAndroidSurfaceCreateFlagsKHR Source # 
Data VkAndroidSurfaceCreateFlagsKHR Source # 

Methods

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

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

toConstr :: VkAndroidSurfaceCreateFlagsKHR -> Constr #

dataTypeOf :: VkAndroidSurfaceCreateFlagsKHR -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkAndroidSurfaceCreateFlagsKHR Source # 
Ord VkAndroidSurfaceCreateFlagsKHR Source # 
Read VkAndroidSurfaceCreateFlagsKHR Source # 
Real VkAndroidSurfaceCreateFlagsKHR Source # 
Show VkAndroidSurfaceCreateFlagsKHR Source # 
Generic VkAndroidSurfaceCreateFlagsKHR Source # 
Storable VkAndroidSurfaceCreateFlagsKHR Source # 
Bits VkAndroidSurfaceCreateFlagsKHR Source # 

Methods

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

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

xor :: VkAndroidSurfaceCreateFlagsKHR -> VkAndroidSurfaceCreateFlagsKHR -> VkAndroidSurfaceCreateFlagsKHR #

complement :: VkAndroidSurfaceCreateFlagsKHR -> VkAndroidSurfaceCreateFlagsKHR #

shift :: VkAndroidSurfaceCreateFlagsKHR -> Int -> VkAndroidSurfaceCreateFlagsKHR #

rotate :: VkAndroidSurfaceCreateFlagsKHR -> Int -> VkAndroidSurfaceCreateFlagsKHR #

zeroBits :: VkAndroidSurfaceCreateFlagsKHR #

bit :: Int -> VkAndroidSurfaceCreateFlagsKHR #

setBit :: VkAndroidSurfaceCreateFlagsKHR -> Int -> VkAndroidSurfaceCreateFlagsKHR #

clearBit :: VkAndroidSurfaceCreateFlagsKHR -> Int -> VkAndroidSurfaceCreateFlagsKHR #

complementBit :: VkAndroidSurfaceCreateFlagsKHR -> Int -> VkAndroidSurfaceCreateFlagsKHR #

testBit :: VkAndroidSurfaceCreateFlagsKHR -> Int -> Bool #

bitSizeMaybe :: VkAndroidSurfaceCreateFlagsKHR -> Maybe Int #

bitSize :: VkAndroidSurfaceCreateFlagsKHR -> Int #

isSigned :: VkAndroidSurfaceCreateFlagsKHR -> Bool #

shiftL :: VkAndroidSurfaceCreateFlagsKHR -> Int -> VkAndroidSurfaceCreateFlagsKHR #

unsafeShiftL :: VkAndroidSurfaceCreateFlagsKHR -> Int -> VkAndroidSurfaceCreateFlagsKHR #

shiftR :: VkAndroidSurfaceCreateFlagsKHR -> Int -> VkAndroidSurfaceCreateFlagsKHR #

unsafeShiftR :: VkAndroidSurfaceCreateFlagsKHR -> Int -> VkAndroidSurfaceCreateFlagsKHR #

rotateL :: VkAndroidSurfaceCreateFlagsKHR -> Int -> VkAndroidSurfaceCreateFlagsKHR #

rotateR :: VkAndroidSurfaceCreateFlagsKHR -> Int -> VkAndroidSurfaceCreateFlagsKHR #

popCount :: VkAndroidSurfaceCreateFlagsKHR -> Int #

FiniteBits VkAndroidSurfaceCreateFlagsKHR Source # 
type Rep VkAndroidSurfaceCreateFlagsKHR Source # 
type Rep VkAndroidSurfaceCreateFlagsKHR = D1 (MetaData "VkAndroidSurfaceCreateFlagsKHR" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkAndroidSurfaceCreateFlagsKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkBufferViewCreateFlags Source #

Instances

Bounded VkBufferViewCreateFlags Source # 
Enum VkBufferViewCreateFlags Source # 
Eq VkBufferViewCreateFlags Source # 
Integral VkBufferViewCreateFlags Source # 
Data VkBufferViewCreateFlags Source # 

Methods

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

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

toConstr :: VkBufferViewCreateFlags -> Constr #

dataTypeOf :: VkBufferViewCreateFlags -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkBufferViewCreateFlags Source # 
Ord VkBufferViewCreateFlags Source # 
Read VkBufferViewCreateFlags Source # 
Real VkBufferViewCreateFlags Source # 
Show VkBufferViewCreateFlags Source # 
Generic VkBufferViewCreateFlags Source # 
Storable VkBufferViewCreateFlags Source # 
Bits VkBufferViewCreateFlags Source # 
FiniteBits VkBufferViewCreateFlags Source # 
type Rep VkBufferViewCreateFlags Source # 
type Rep VkBufferViewCreateFlags = D1 (MetaData "VkBufferViewCreateFlags" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkBufferViewCreateFlags" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkCommandPoolTrimFlags Source #

Instances

Bounded VkCommandPoolTrimFlags Source # 
Enum VkCommandPoolTrimFlags Source # 
Eq VkCommandPoolTrimFlags Source # 
Integral VkCommandPoolTrimFlags Source # 
Data VkCommandPoolTrimFlags Source # 

Methods

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

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

toConstr :: VkCommandPoolTrimFlags -> Constr #

dataTypeOf :: VkCommandPoolTrimFlags -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkCommandPoolTrimFlags Source # 
Ord VkCommandPoolTrimFlags Source # 
Read VkCommandPoolTrimFlags Source # 
Real VkCommandPoolTrimFlags Source # 
Show VkCommandPoolTrimFlags Source # 
Generic VkCommandPoolTrimFlags Source # 
Storable VkCommandPoolTrimFlags Source # 
Bits VkCommandPoolTrimFlags Source # 
FiniteBits VkCommandPoolTrimFlags Source # 
type Rep VkCommandPoolTrimFlags Source # 
type Rep VkCommandPoolTrimFlags = D1 (MetaData "VkCommandPoolTrimFlags" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkCommandPoolTrimFlags" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkCommandPoolTrimFlagsKHR Source #

Instances

Bounded VkCommandPoolTrimFlagsKHR Source # 
Enum VkCommandPoolTrimFlagsKHR Source # 
Eq VkCommandPoolTrimFlagsKHR Source # 
Integral VkCommandPoolTrimFlagsKHR Source # 
Data VkCommandPoolTrimFlagsKHR Source # 

Methods

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

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

toConstr :: VkCommandPoolTrimFlagsKHR -> Constr #

dataTypeOf :: VkCommandPoolTrimFlagsKHR -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkCommandPoolTrimFlagsKHR Source # 
Ord VkCommandPoolTrimFlagsKHR Source # 
Read VkCommandPoolTrimFlagsKHR Source # 
Real VkCommandPoolTrimFlagsKHR Source # 
Show VkCommandPoolTrimFlagsKHR Source # 
Generic VkCommandPoolTrimFlagsKHR Source # 
Storable VkCommandPoolTrimFlagsKHR Source # 
Bits VkCommandPoolTrimFlagsKHR Source # 

Methods

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

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

xor :: VkCommandPoolTrimFlagsKHR -> VkCommandPoolTrimFlagsKHR -> VkCommandPoolTrimFlagsKHR #

complement :: VkCommandPoolTrimFlagsKHR -> VkCommandPoolTrimFlagsKHR #

shift :: VkCommandPoolTrimFlagsKHR -> Int -> VkCommandPoolTrimFlagsKHR #

rotate :: VkCommandPoolTrimFlagsKHR -> Int -> VkCommandPoolTrimFlagsKHR #

zeroBits :: VkCommandPoolTrimFlagsKHR #

bit :: Int -> VkCommandPoolTrimFlagsKHR #

setBit :: VkCommandPoolTrimFlagsKHR -> Int -> VkCommandPoolTrimFlagsKHR #

clearBit :: VkCommandPoolTrimFlagsKHR -> Int -> VkCommandPoolTrimFlagsKHR #

complementBit :: VkCommandPoolTrimFlagsKHR -> Int -> VkCommandPoolTrimFlagsKHR #

testBit :: VkCommandPoolTrimFlagsKHR -> Int -> Bool #

bitSizeMaybe :: VkCommandPoolTrimFlagsKHR -> Maybe Int #

bitSize :: VkCommandPoolTrimFlagsKHR -> Int #

isSigned :: VkCommandPoolTrimFlagsKHR -> Bool #

shiftL :: VkCommandPoolTrimFlagsKHR -> Int -> VkCommandPoolTrimFlagsKHR #

unsafeShiftL :: VkCommandPoolTrimFlagsKHR -> Int -> VkCommandPoolTrimFlagsKHR #

shiftR :: VkCommandPoolTrimFlagsKHR -> Int -> VkCommandPoolTrimFlagsKHR #

unsafeShiftR :: VkCommandPoolTrimFlagsKHR -> Int -> VkCommandPoolTrimFlagsKHR #

rotateL :: VkCommandPoolTrimFlagsKHR -> Int -> VkCommandPoolTrimFlagsKHR #

rotateR :: VkCommandPoolTrimFlagsKHR -> Int -> VkCommandPoolTrimFlagsKHR #

popCount :: VkCommandPoolTrimFlagsKHR -> Int #

FiniteBits VkCommandPoolTrimFlagsKHR Source # 
type Rep VkCommandPoolTrimFlagsKHR Source # 
type Rep VkCommandPoolTrimFlagsKHR = D1 (MetaData "VkCommandPoolTrimFlagsKHR" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkCommandPoolTrimFlagsKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkDebugUtilsMessengerCallbackDataFlagsEXT Source #

Instances

Bounded VkDebugUtilsMessengerCallbackDataFlagsEXT Source # 
Enum VkDebugUtilsMessengerCallbackDataFlagsEXT Source # 
Eq VkDebugUtilsMessengerCallbackDataFlagsEXT Source # 
Integral VkDebugUtilsMessengerCallbackDataFlagsEXT Source # 
Data VkDebugUtilsMessengerCallbackDataFlagsEXT Source # 

Methods

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

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

toConstr :: VkDebugUtilsMessengerCallbackDataFlagsEXT -> Constr #

dataTypeOf :: VkDebugUtilsMessengerCallbackDataFlagsEXT -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkDebugUtilsMessengerCallbackDataFlagsEXT Source # 
Ord VkDebugUtilsMessengerCallbackDataFlagsEXT Source # 
Read VkDebugUtilsMessengerCallbackDataFlagsEXT Source # 
Real VkDebugUtilsMessengerCallbackDataFlagsEXT Source # 
Show VkDebugUtilsMessengerCallbackDataFlagsEXT Source # 
Generic VkDebugUtilsMessengerCallbackDataFlagsEXT Source # 
Storable VkDebugUtilsMessengerCallbackDataFlagsEXT Source # 
Bits VkDebugUtilsMessengerCallbackDataFlagsEXT Source # 

Methods

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

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

xor :: VkDebugUtilsMessengerCallbackDataFlagsEXT -> VkDebugUtilsMessengerCallbackDataFlagsEXT -> VkDebugUtilsMessengerCallbackDataFlagsEXT #

complement :: VkDebugUtilsMessengerCallbackDataFlagsEXT -> VkDebugUtilsMessengerCallbackDataFlagsEXT #

shift :: VkDebugUtilsMessengerCallbackDataFlagsEXT -> Int -> VkDebugUtilsMessengerCallbackDataFlagsEXT #

rotate :: VkDebugUtilsMessengerCallbackDataFlagsEXT -> Int -> VkDebugUtilsMessengerCallbackDataFlagsEXT #

zeroBits :: VkDebugUtilsMessengerCallbackDataFlagsEXT #

bit :: Int -> VkDebugUtilsMessengerCallbackDataFlagsEXT #

setBit :: VkDebugUtilsMessengerCallbackDataFlagsEXT -> Int -> VkDebugUtilsMessengerCallbackDataFlagsEXT #

clearBit :: VkDebugUtilsMessengerCallbackDataFlagsEXT -> Int -> VkDebugUtilsMessengerCallbackDataFlagsEXT #

complementBit :: VkDebugUtilsMessengerCallbackDataFlagsEXT -> Int -> VkDebugUtilsMessengerCallbackDataFlagsEXT #

testBit :: VkDebugUtilsMessengerCallbackDataFlagsEXT -> Int -> Bool #

bitSizeMaybe :: VkDebugUtilsMessengerCallbackDataFlagsEXT -> Maybe Int #

bitSize :: VkDebugUtilsMessengerCallbackDataFlagsEXT -> Int #

isSigned :: VkDebugUtilsMessengerCallbackDataFlagsEXT -> Bool #

shiftL :: VkDebugUtilsMessengerCallbackDataFlagsEXT -> Int -> VkDebugUtilsMessengerCallbackDataFlagsEXT #

unsafeShiftL :: VkDebugUtilsMessengerCallbackDataFlagsEXT -> Int -> VkDebugUtilsMessengerCallbackDataFlagsEXT #

shiftR :: VkDebugUtilsMessengerCallbackDataFlagsEXT -> Int -> VkDebugUtilsMessengerCallbackDataFlagsEXT #

unsafeShiftR :: VkDebugUtilsMessengerCallbackDataFlagsEXT -> Int -> VkDebugUtilsMessengerCallbackDataFlagsEXT #

rotateL :: VkDebugUtilsMessengerCallbackDataFlagsEXT -> Int -> VkDebugUtilsMessengerCallbackDataFlagsEXT #

rotateR :: VkDebugUtilsMessengerCallbackDataFlagsEXT -> Int -> VkDebugUtilsMessengerCallbackDataFlagsEXT #

popCount :: VkDebugUtilsMessengerCallbackDataFlagsEXT -> Int #

FiniteBits VkDebugUtilsMessengerCallbackDataFlagsEXT Source # 
type Rep VkDebugUtilsMessengerCallbackDataFlagsEXT Source # 
type Rep VkDebugUtilsMessengerCallbackDataFlagsEXT = D1 (MetaData "VkDebugUtilsMessengerCallbackDataFlagsEXT" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkDebugUtilsMessengerCallbackDataFlagsEXT" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkDebugUtilsMessengerCreateFlagsEXT Source #

Instances

Bounded VkDebugUtilsMessengerCreateFlagsEXT Source # 
Enum VkDebugUtilsMessengerCreateFlagsEXT Source # 
Eq VkDebugUtilsMessengerCreateFlagsEXT Source # 
Integral VkDebugUtilsMessengerCreateFlagsEXT Source # 
Data VkDebugUtilsMessengerCreateFlagsEXT Source # 

Methods

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

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

toConstr :: VkDebugUtilsMessengerCreateFlagsEXT -> Constr #

dataTypeOf :: VkDebugUtilsMessengerCreateFlagsEXT -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkDebugUtilsMessengerCreateFlagsEXT Source # 
Ord VkDebugUtilsMessengerCreateFlagsEXT Source # 
Read VkDebugUtilsMessengerCreateFlagsEXT Source # 
Real VkDebugUtilsMessengerCreateFlagsEXT Source # 
Show VkDebugUtilsMessengerCreateFlagsEXT Source # 
Generic VkDebugUtilsMessengerCreateFlagsEXT Source # 
Storable VkDebugUtilsMessengerCreateFlagsEXT Source # 
Bits VkDebugUtilsMessengerCreateFlagsEXT Source # 

Methods

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

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

xor :: VkDebugUtilsMessengerCreateFlagsEXT -> VkDebugUtilsMessengerCreateFlagsEXT -> VkDebugUtilsMessengerCreateFlagsEXT #

complement :: VkDebugUtilsMessengerCreateFlagsEXT -> VkDebugUtilsMessengerCreateFlagsEXT #

shift :: VkDebugUtilsMessengerCreateFlagsEXT -> Int -> VkDebugUtilsMessengerCreateFlagsEXT #

rotate :: VkDebugUtilsMessengerCreateFlagsEXT -> Int -> VkDebugUtilsMessengerCreateFlagsEXT #

zeroBits :: VkDebugUtilsMessengerCreateFlagsEXT #

bit :: Int -> VkDebugUtilsMessengerCreateFlagsEXT #

setBit :: VkDebugUtilsMessengerCreateFlagsEXT -> Int -> VkDebugUtilsMessengerCreateFlagsEXT #

clearBit :: VkDebugUtilsMessengerCreateFlagsEXT -> Int -> VkDebugUtilsMessengerCreateFlagsEXT #

complementBit :: VkDebugUtilsMessengerCreateFlagsEXT -> Int -> VkDebugUtilsMessengerCreateFlagsEXT #

testBit :: VkDebugUtilsMessengerCreateFlagsEXT -> Int -> Bool #

bitSizeMaybe :: VkDebugUtilsMessengerCreateFlagsEXT -> Maybe Int #

bitSize :: VkDebugUtilsMessengerCreateFlagsEXT -> Int #

isSigned :: VkDebugUtilsMessengerCreateFlagsEXT -> Bool #

shiftL :: VkDebugUtilsMessengerCreateFlagsEXT -> Int -> VkDebugUtilsMessengerCreateFlagsEXT #

unsafeShiftL :: VkDebugUtilsMessengerCreateFlagsEXT -> Int -> VkDebugUtilsMessengerCreateFlagsEXT #

shiftR :: VkDebugUtilsMessengerCreateFlagsEXT -> Int -> VkDebugUtilsMessengerCreateFlagsEXT #

unsafeShiftR :: VkDebugUtilsMessengerCreateFlagsEXT -> Int -> VkDebugUtilsMessengerCreateFlagsEXT #

rotateL :: VkDebugUtilsMessengerCreateFlagsEXT -> Int -> VkDebugUtilsMessengerCreateFlagsEXT #

rotateR :: VkDebugUtilsMessengerCreateFlagsEXT -> Int -> VkDebugUtilsMessengerCreateFlagsEXT #

popCount :: VkDebugUtilsMessengerCreateFlagsEXT -> Int #

FiniteBits VkDebugUtilsMessengerCreateFlagsEXT Source # 
type Rep VkDebugUtilsMessengerCreateFlagsEXT Source # 
type Rep VkDebugUtilsMessengerCreateFlagsEXT = D1 (MetaData "VkDebugUtilsMessengerCreateFlagsEXT" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkDebugUtilsMessengerCreateFlagsEXT" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkDescriptorPoolResetFlags Source #

Instances

Bounded VkDescriptorPoolResetFlags Source # 
Enum VkDescriptorPoolResetFlags Source # 
Eq VkDescriptorPoolResetFlags Source # 
Integral VkDescriptorPoolResetFlags Source # 
Data VkDescriptorPoolResetFlags Source # 

Methods

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

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

toConstr :: VkDescriptorPoolResetFlags -> Constr #

dataTypeOf :: VkDescriptorPoolResetFlags -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkDescriptorPoolResetFlags Source # 
Ord VkDescriptorPoolResetFlags Source # 
Read VkDescriptorPoolResetFlags Source # 
Real VkDescriptorPoolResetFlags Source # 
Show VkDescriptorPoolResetFlags Source # 
Generic VkDescriptorPoolResetFlags Source # 
Storable VkDescriptorPoolResetFlags Source # 
Bits VkDescriptorPoolResetFlags Source # 

Methods

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

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

xor :: VkDescriptorPoolResetFlags -> VkDescriptorPoolResetFlags -> VkDescriptorPoolResetFlags #

complement :: VkDescriptorPoolResetFlags -> VkDescriptorPoolResetFlags #

shift :: VkDescriptorPoolResetFlags -> Int -> VkDescriptorPoolResetFlags #

rotate :: VkDescriptorPoolResetFlags -> Int -> VkDescriptorPoolResetFlags #

zeroBits :: VkDescriptorPoolResetFlags #

bit :: Int -> VkDescriptorPoolResetFlags #

setBit :: VkDescriptorPoolResetFlags -> Int -> VkDescriptorPoolResetFlags #

clearBit :: VkDescriptorPoolResetFlags -> Int -> VkDescriptorPoolResetFlags #

complementBit :: VkDescriptorPoolResetFlags -> Int -> VkDescriptorPoolResetFlags #

testBit :: VkDescriptorPoolResetFlags -> Int -> Bool #

bitSizeMaybe :: VkDescriptorPoolResetFlags -> Maybe Int #

bitSize :: VkDescriptorPoolResetFlags -> Int #

isSigned :: VkDescriptorPoolResetFlags -> Bool #

shiftL :: VkDescriptorPoolResetFlags -> Int -> VkDescriptorPoolResetFlags #

unsafeShiftL :: VkDescriptorPoolResetFlags -> Int -> VkDescriptorPoolResetFlags #

shiftR :: VkDescriptorPoolResetFlags -> Int -> VkDescriptorPoolResetFlags #

unsafeShiftR :: VkDescriptorPoolResetFlags -> Int -> VkDescriptorPoolResetFlags #

rotateL :: VkDescriptorPoolResetFlags -> Int -> VkDescriptorPoolResetFlags #

rotateR :: VkDescriptorPoolResetFlags -> Int -> VkDescriptorPoolResetFlags #

popCount :: VkDescriptorPoolResetFlags -> Int #

FiniteBits VkDescriptorPoolResetFlags Source # 
type Rep VkDescriptorPoolResetFlags Source # 
type Rep VkDescriptorPoolResetFlags = D1 (MetaData "VkDescriptorPoolResetFlags" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkDescriptorPoolResetFlags" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkDescriptorUpdateTemplateCreateFlags Source #

Instances

Bounded VkDescriptorUpdateTemplateCreateFlags Source # 
Enum VkDescriptorUpdateTemplateCreateFlags Source # 
Eq VkDescriptorUpdateTemplateCreateFlags Source # 
Integral VkDescriptorUpdateTemplateCreateFlags Source # 
Data VkDescriptorUpdateTemplateCreateFlags Source # 

Methods

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

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

toConstr :: VkDescriptorUpdateTemplateCreateFlags -> Constr #

dataTypeOf :: VkDescriptorUpdateTemplateCreateFlags -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkDescriptorUpdateTemplateCreateFlags Source # 
Ord VkDescriptorUpdateTemplateCreateFlags Source # 
Read VkDescriptorUpdateTemplateCreateFlags Source # 
Real VkDescriptorUpdateTemplateCreateFlags Source # 
Show VkDescriptorUpdateTemplateCreateFlags Source # 
Generic VkDescriptorUpdateTemplateCreateFlags Source # 
Storable VkDescriptorUpdateTemplateCreateFlags Source # 
Bits VkDescriptorUpdateTemplateCreateFlags Source # 

Methods

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

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

xor :: VkDescriptorUpdateTemplateCreateFlags -> VkDescriptorUpdateTemplateCreateFlags -> VkDescriptorUpdateTemplateCreateFlags #

complement :: VkDescriptorUpdateTemplateCreateFlags -> VkDescriptorUpdateTemplateCreateFlags #

shift :: VkDescriptorUpdateTemplateCreateFlags -> Int -> VkDescriptorUpdateTemplateCreateFlags #

rotate :: VkDescriptorUpdateTemplateCreateFlags -> Int -> VkDescriptorUpdateTemplateCreateFlags #

zeroBits :: VkDescriptorUpdateTemplateCreateFlags #

bit :: Int -> VkDescriptorUpdateTemplateCreateFlags #

setBit :: VkDescriptorUpdateTemplateCreateFlags -> Int -> VkDescriptorUpdateTemplateCreateFlags #

clearBit :: VkDescriptorUpdateTemplateCreateFlags -> Int -> VkDescriptorUpdateTemplateCreateFlags #

complementBit :: VkDescriptorUpdateTemplateCreateFlags -> Int -> VkDescriptorUpdateTemplateCreateFlags #

testBit :: VkDescriptorUpdateTemplateCreateFlags -> Int -> Bool #

bitSizeMaybe :: VkDescriptorUpdateTemplateCreateFlags -> Maybe Int #

bitSize :: VkDescriptorUpdateTemplateCreateFlags -> Int #

isSigned :: VkDescriptorUpdateTemplateCreateFlags -> Bool #

shiftL :: VkDescriptorUpdateTemplateCreateFlags -> Int -> VkDescriptorUpdateTemplateCreateFlags #

unsafeShiftL :: VkDescriptorUpdateTemplateCreateFlags -> Int -> VkDescriptorUpdateTemplateCreateFlags #

shiftR :: VkDescriptorUpdateTemplateCreateFlags -> Int -> VkDescriptorUpdateTemplateCreateFlags #

unsafeShiftR :: VkDescriptorUpdateTemplateCreateFlags -> Int -> VkDescriptorUpdateTemplateCreateFlags #

rotateL :: VkDescriptorUpdateTemplateCreateFlags -> Int -> VkDescriptorUpdateTemplateCreateFlags #

rotateR :: VkDescriptorUpdateTemplateCreateFlags -> Int -> VkDescriptorUpdateTemplateCreateFlags #

popCount :: VkDescriptorUpdateTemplateCreateFlags -> Int #

FiniteBits VkDescriptorUpdateTemplateCreateFlags Source # 
type Rep VkDescriptorUpdateTemplateCreateFlags Source # 
type Rep VkDescriptorUpdateTemplateCreateFlags = D1 (MetaData "VkDescriptorUpdateTemplateCreateFlags" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkDescriptorUpdateTemplateCreateFlags" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkDescriptorUpdateTemplateCreateFlagsKHR Source #

Instances

Bounded VkDescriptorUpdateTemplateCreateFlagsKHR Source # 
Enum VkDescriptorUpdateTemplateCreateFlagsKHR Source # 
Eq VkDescriptorUpdateTemplateCreateFlagsKHR Source # 
Integral VkDescriptorUpdateTemplateCreateFlagsKHR Source # 
Data VkDescriptorUpdateTemplateCreateFlagsKHR Source # 

Methods

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

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

toConstr :: VkDescriptorUpdateTemplateCreateFlagsKHR -> Constr #

dataTypeOf :: VkDescriptorUpdateTemplateCreateFlagsKHR -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkDescriptorUpdateTemplateCreateFlagsKHR Source # 
Ord VkDescriptorUpdateTemplateCreateFlagsKHR Source # 
Read VkDescriptorUpdateTemplateCreateFlagsKHR Source # 
Real VkDescriptorUpdateTemplateCreateFlagsKHR Source # 
Show VkDescriptorUpdateTemplateCreateFlagsKHR Source # 
Generic VkDescriptorUpdateTemplateCreateFlagsKHR Source # 
Storable VkDescriptorUpdateTemplateCreateFlagsKHR Source # 
Bits VkDescriptorUpdateTemplateCreateFlagsKHR Source # 

Methods

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

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

xor :: VkDescriptorUpdateTemplateCreateFlagsKHR -> VkDescriptorUpdateTemplateCreateFlagsKHR -> VkDescriptorUpdateTemplateCreateFlagsKHR #

complement :: VkDescriptorUpdateTemplateCreateFlagsKHR -> VkDescriptorUpdateTemplateCreateFlagsKHR #

shift :: VkDescriptorUpdateTemplateCreateFlagsKHR -> Int -> VkDescriptorUpdateTemplateCreateFlagsKHR #

rotate :: VkDescriptorUpdateTemplateCreateFlagsKHR -> Int -> VkDescriptorUpdateTemplateCreateFlagsKHR #

zeroBits :: VkDescriptorUpdateTemplateCreateFlagsKHR #

bit :: Int -> VkDescriptorUpdateTemplateCreateFlagsKHR #

setBit :: VkDescriptorUpdateTemplateCreateFlagsKHR -> Int -> VkDescriptorUpdateTemplateCreateFlagsKHR #

clearBit :: VkDescriptorUpdateTemplateCreateFlagsKHR -> Int -> VkDescriptorUpdateTemplateCreateFlagsKHR #

complementBit :: VkDescriptorUpdateTemplateCreateFlagsKHR -> Int -> VkDescriptorUpdateTemplateCreateFlagsKHR #

testBit :: VkDescriptorUpdateTemplateCreateFlagsKHR -> Int -> Bool #

bitSizeMaybe :: VkDescriptorUpdateTemplateCreateFlagsKHR -> Maybe Int #

bitSize :: VkDescriptorUpdateTemplateCreateFlagsKHR -> Int #

isSigned :: VkDescriptorUpdateTemplateCreateFlagsKHR -> Bool #

shiftL :: VkDescriptorUpdateTemplateCreateFlagsKHR -> Int -> VkDescriptorUpdateTemplateCreateFlagsKHR #

unsafeShiftL :: VkDescriptorUpdateTemplateCreateFlagsKHR -> Int -> VkDescriptorUpdateTemplateCreateFlagsKHR #

shiftR :: VkDescriptorUpdateTemplateCreateFlagsKHR -> Int -> VkDescriptorUpdateTemplateCreateFlagsKHR #

unsafeShiftR :: VkDescriptorUpdateTemplateCreateFlagsKHR -> Int -> VkDescriptorUpdateTemplateCreateFlagsKHR #

rotateL :: VkDescriptorUpdateTemplateCreateFlagsKHR -> Int -> VkDescriptorUpdateTemplateCreateFlagsKHR #

rotateR :: VkDescriptorUpdateTemplateCreateFlagsKHR -> Int -> VkDescriptorUpdateTemplateCreateFlagsKHR #

popCount :: VkDescriptorUpdateTemplateCreateFlagsKHR -> Int #

FiniteBits VkDescriptorUpdateTemplateCreateFlagsKHR Source # 
type Rep VkDescriptorUpdateTemplateCreateFlagsKHR Source # 
type Rep VkDescriptorUpdateTemplateCreateFlagsKHR = D1 (MetaData "VkDescriptorUpdateTemplateCreateFlagsKHR" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkDescriptorUpdateTemplateCreateFlagsKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkDeviceCreateFlags Source #

Instances

Bounded VkDeviceCreateFlags Source # 
Enum VkDeviceCreateFlags Source # 
Eq VkDeviceCreateFlags Source # 
Integral VkDeviceCreateFlags Source # 
Data VkDeviceCreateFlags Source # 

Methods

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

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

toConstr :: VkDeviceCreateFlags -> Constr #

dataTypeOf :: VkDeviceCreateFlags -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkDeviceCreateFlags Source # 
Ord VkDeviceCreateFlags Source # 
Read VkDeviceCreateFlags Source # 
Real VkDeviceCreateFlags Source # 
Show VkDeviceCreateFlags Source # 
Generic VkDeviceCreateFlags Source # 
Storable VkDeviceCreateFlags Source # 
Bits VkDeviceCreateFlags Source # 
FiniteBits VkDeviceCreateFlags Source # 
type Rep VkDeviceCreateFlags Source # 
type Rep VkDeviceCreateFlags = D1 (MetaData "VkDeviceCreateFlags" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkDeviceCreateFlags" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkDisplayModeCreateFlagsKHR Source #

Instances

Bounded VkDisplayModeCreateFlagsKHR Source # 
Enum VkDisplayModeCreateFlagsKHR Source # 
Eq VkDisplayModeCreateFlagsKHR Source # 
Integral VkDisplayModeCreateFlagsKHR Source # 
Data VkDisplayModeCreateFlagsKHR Source # 

Methods

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

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

toConstr :: VkDisplayModeCreateFlagsKHR -> Constr #

dataTypeOf :: VkDisplayModeCreateFlagsKHR -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkDisplayModeCreateFlagsKHR Source # 
Ord VkDisplayModeCreateFlagsKHR Source # 
Read VkDisplayModeCreateFlagsKHR Source # 
Real VkDisplayModeCreateFlagsKHR Source # 
Show VkDisplayModeCreateFlagsKHR Source # 
Generic VkDisplayModeCreateFlagsKHR Source # 
Storable VkDisplayModeCreateFlagsKHR Source # 
Bits VkDisplayModeCreateFlagsKHR Source # 

Methods

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

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

xor :: VkDisplayModeCreateFlagsKHR -> VkDisplayModeCreateFlagsKHR -> VkDisplayModeCreateFlagsKHR #

complement :: VkDisplayModeCreateFlagsKHR -> VkDisplayModeCreateFlagsKHR #

shift :: VkDisplayModeCreateFlagsKHR -> Int -> VkDisplayModeCreateFlagsKHR #

rotate :: VkDisplayModeCreateFlagsKHR -> Int -> VkDisplayModeCreateFlagsKHR #

zeroBits :: VkDisplayModeCreateFlagsKHR #

bit :: Int -> VkDisplayModeCreateFlagsKHR #

setBit :: VkDisplayModeCreateFlagsKHR -> Int -> VkDisplayModeCreateFlagsKHR #

clearBit :: VkDisplayModeCreateFlagsKHR -> Int -> VkDisplayModeCreateFlagsKHR #

complementBit :: VkDisplayModeCreateFlagsKHR -> Int -> VkDisplayModeCreateFlagsKHR #

testBit :: VkDisplayModeCreateFlagsKHR -> Int -> Bool #

bitSizeMaybe :: VkDisplayModeCreateFlagsKHR -> Maybe Int #

bitSize :: VkDisplayModeCreateFlagsKHR -> Int #

isSigned :: VkDisplayModeCreateFlagsKHR -> Bool #

shiftL :: VkDisplayModeCreateFlagsKHR -> Int -> VkDisplayModeCreateFlagsKHR #

unsafeShiftL :: VkDisplayModeCreateFlagsKHR -> Int -> VkDisplayModeCreateFlagsKHR #

shiftR :: VkDisplayModeCreateFlagsKHR -> Int -> VkDisplayModeCreateFlagsKHR #

unsafeShiftR :: VkDisplayModeCreateFlagsKHR -> Int -> VkDisplayModeCreateFlagsKHR #

rotateL :: VkDisplayModeCreateFlagsKHR -> Int -> VkDisplayModeCreateFlagsKHR #

rotateR :: VkDisplayModeCreateFlagsKHR -> Int -> VkDisplayModeCreateFlagsKHR #

popCount :: VkDisplayModeCreateFlagsKHR -> Int #

FiniteBits VkDisplayModeCreateFlagsKHR Source # 
type Rep VkDisplayModeCreateFlagsKHR Source # 
type Rep VkDisplayModeCreateFlagsKHR = D1 (MetaData "VkDisplayModeCreateFlagsKHR" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkDisplayModeCreateFlagsKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkDisplaySurfaceCreateFlagsKHR Source #

Instances

Bounded VkDisplaySurfaceCreateFlagsKHR Source # 
Enum VkDisplaySurfaceCreateFlagsKHR Source # 
Eq VkDisplaySurfaceCreateFlagsKHR Source # 
Integral VkDisplaySurfaceCreateFlagsKHR Source # 
Data VkDisplaySurfaceCreateFlagsKHR Source # 

Methods

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

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

toConstr :: VkDisplaySurfaceCreateFlagsKHR -> Constr #

dataTypeOf :: VkDisplaySurfaceCreateFlagsKHR -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkDisplaySurfaceCreateFlagsKHR Source # 
Ord VkDisplaySurfaceCreateFlagsKHR Source # 
Read VkDisplaySurfaceCreateFlagsKHR Source # 
Real VkDisplaySurfaceCreateFlagsKHR Source # 
Show VkDisplaySurfaceCreateFlagsKHR Source # 
Generic VkDisplaySurfaceCreateFlagsKHR Source # 
Storable VkDisplaySurfaceCreateFlagsKHR Source # 
Bits VkDisplaySurfaceCreateFlagsKHR Source # 

Methods

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

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

xor :: VkDisplaySurfaceCreateFlagsKHR -> VkDisplaySurfaceCreateFlagsKHR -> VkDisplaySurfaceCreateFlagsKHR #

complement :: VkDisplaySurfaceCreateFlagsKHR -> VkDisplaySurfaceCreateFlagsKHR #

shift :: VkDisplaySurfaceCreateFlagsKHR -> Int -> VkDisplaySurfaceCreateFlagsKHR #

rotate :: VkDisplaySurfaceCreateFlagsKHR -> Int -> VkDisplaySurfaceCreateFlagsKHR #

zeroBits :: VkDisplaySurfaceCreateFlagsKHR #

bit :: Int -> VkDisplaySurfaceCreateFlagsKHR #

setBit :: VkDisplaySurfaceCreateFlagsKHR -> Int -> VkDisplaySurfaceCreateFlagsKHR #

clearBit :: VkDisplaySurfaceCreateFlagsKHR -> Int -> VkDisplaySurfaceCreateFlagsKHR #

complementBit :: VkDisplaySurfaceCreateFlagsKHR -> Int -> VkDisplaySurfaceCreateFlagsKHR #

testBit :: VkDisplaySurfaceCreateFlagsKHR -> Int -> Bool #

bitSizeMaybe :: VkDisplaySurfaceCreateFlagsKHR -> Maybe Int #

bitSize :: VkDisplaySurfaceCreateFlagsKHR -> Int #

isSigned :: VkDisplaySurfaceCreateFlagsKHR -> Bool #

shiftL :: VkDisplaySurfaceCreateFlagsKHR -> Int -> VkDisplaySurfaceCreateFlagsKHR #

unsafeShiftL :: VkDisplaySurfaceCreateFlagsKHR -> Int -> VkDisplaySurfaceCreateFlagsKHR #

shiftR :: VkDisplaySurfaceCreateFlagsKHR -> Int -> VkDisplaySurfaceCreateFlagsKHR #

unsafeShiftR :: VkDisplaySurfaceCreateFlagsKHR -> Int -> VkDisplaySurfaceCreateFlagsKHR #

rotateL :: VkDisplaySurfaceCreateFlagsKHR -> Int -> VkDisplaySurfaceCreateFlagsKHR #

rotateR :: VkDisplaySurfaceCreateFlagsKHR -> Int -> VkDisplaySurfaceCreateFlagsKHR #

popCount :: VkDisplaySurfaceCreateFlagsKHR -> Int #

FiniteBits VkDisplaySurfaceCreateFlagsKHR Source # 
type Rep VkDisplaySurfaceCreateFlagsKHR Source # 
type Rep VkDisplaySurfaceCreateFlagsKHR = D1 (MetaData "VkDisplaySurfaceCreateFlagsKHR" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkDisplaySurfaceCreateFlagsKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkEventCreateFlags Source #

Instances

Bounded VkEventCreateFlags Source # 
Enum VkEventCreateFlags Source # 
Eq VkEventCreateFlags Source # 
Integral VkEventCreateFlags Source # 
Data VkEventCreateFlags Source # 

Methods

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

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

toConstr :: VkEventCreateFlags -> Constr #

dataTypeOf :: VkEventCreateFlags -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkEventCreateFlags Source # 
Ord VkEventCreateFlags Source # 
Read VkEventCreateFlags Source # 
Real VkEventCreateFlags Source # 
Show VkEventCreateFlags Source # 
Generic VkEventCreateFlags Source # 
Storable VkEventCreateFlags Source # 
Bits VkEventCreateFlags Source # 
FiniteBits VkEventCreateFlags Source # 
type Rep VkEventCreateFlags Source # 
type Rep VkEventCreateFlags = D1 (MetaData "VkEventCreateFlags" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkEventCreateFlags" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkExternalFenceFeatureFlagsKHR Source #

Instances

Bounded VkExternalFenceFeatureFlagsKHR Source # 
Enum VkExternalFenceFeatureFlagsKHR Source # 
Eq VkExternalFenceFeatureFlagsKHR Source # 
Integral VkExternalFenceFeatureFlagsKHR Source # 
Data VkExternalFenceFeatureFlagsKHR Source # 

Methods

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

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

toConstr :: VkExternalFenceFeatureFlagsKHR -> Constr #

dataTypeOf :: VkExternalFenceFeatureFlagsKHR -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkExternalFenceFeatureFlagsKHR Source # 
Ord VkExternalFenceFeatureFlagsKHR Source # 
Read VkExternalFenceFeatureFlagsKHR Source # 
Real VkExternalFenceFeatureFlagsKHR Source # 
Show VkExternalFenceFeatureFlagsKHR Source # 
Generic VkExternalFenceFeatureFlagsKHR Source # 
Storable VkExternalFenceFeatureFlagsKHR Source # 
Bits VkExternalFenceFeatureFlagsKHR Source # 

Methods

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

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

xor :: VkExternalFenceFeatureFlagsKHR -> VkExternalFenceFeatureFlagsKHR -> VkExternalFenceFeatureFlagsKHR #

complement :: VkExternalFenceFeatureFlagsKHR -> VkExternalFenceFeatureFlagsKHR #

shift :: VkExternalFenceFeatureFlagsKHR -> Int -> VkExternalFenceFeatureFlagsKHR #

rotate :: VkExternalFenceFeatureFlagsKHR -> Int -> VkExternalFenceFeatureFlagsKHR #

zeroBits :: VkExternalFenceFeatureFlagsKHR #

bit :: Int -> VkExternalFenceFeatureFlagsKHR #

setBit :: VkExternalFenceFeatureFlagsKHR -> Int -> VkExternalFenceFeatureFlagsKHR #

clearBit :: VkExternalFenceFeatureFlagsKHR -> Int -> VkExternalFenceFeatureFlagsKHR #

complementBit :: VkExternalFenceFeatureFlagsKHR -> Int -> VkExternalFenceFeatureFlagsKHR #

testBit :: VkExternalFenceFeatureFlagsKHR -> Int -> Bool #

bitSizeMaybe :: VkExternalFenceFeatureFlagsKHR -> Maybe Int #

bitSize :: VkExternalFenceFeatureFlagsKHR -> Int #

isSigned :: VkExternalFenceFeatureFlagsKHR -> Bool #

shiftL :: VkExternalFenceFeatureFlagsKHR -> Int -> VkExternalFenceFeatureFlagsKHR #

unsafeShiftL :: VkExternalFenceFeatureFlagsKHR -> Int -> VkExternalFenceFeatureFlagsKHR #

shiftR :: VkExternalFenceFeatureFlagsKHR -> Int -> VkExternalFenceFeatureFlagsKHR #

unsafeShiftR :: VkExternalFenceFeatureFlagsKHR -> Int -> VkExternalFenceFeatureFlagsKHR #

rotateL :: VkExternalFenceFeatureFlagsKHR -> Int -> VkExternalFenceFeatureFlagsKHR #

rotateR :: VkExternalFenceFeatureFlagsKHR -> Int -> VkExternalFenceFeatureFlagsKHR #

popCount :: VkExternalFenceFeatureFlagsKHR -> Int #

FiniteBits VkExternalFenceFeatureFlagsKHR Source # 
type Rep VkExternalFenceFeatureFlagsKHR Source # 
type Rep VkExternalFenceFeatureFlagsKHR = D1 (MetaData "VkExternalFenceFeatureFlagsKHR" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkExternalFenceFeatureFlagsKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkExternalFenceHandleTypeFlagsKHR Source #

Instances

Bounded VkExternalFenceHandleTypeFlagsKHR Source # 
Enum VkExternalFenceHandleTypeFlagsKHR Source # 
Eq VkExternalFenceHandleTypeFlagsKHR Source # 
Integral VkExternalFenceHandleTypeFlagsKHR Source # 
Data VkExternalFenceHandleTypeFlagsKHR Source # 

Methods

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

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

toConstr :: VkExternalFenceHandleTypeFlagsKHR -> Constr #

dataTypeOf :: VkExternalFenceHandleTypeFlagsKHR -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkExternalFenceHandleTypeFlagsKHR Source # 
Ord VkExternalFenceHandleTypeFlagsKHR Source # 
Read VkExternalFenceHandleTypeFlagsKHR Source # 
Real VkExternalFenceHandleTypeFlagsKHR Source # 
Show VkExternalFenceHandleTypeFlagsKHR Source # 
Generic VkExternalFenceHandleTypeFlagsKHR Source # 
Storable VkExternalFenceHandleTypeFlagsKHR Source # 
Bits VkExternalFenceHandleTypeFlagsKHR Source # 

Methods

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

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

xor :: VkExternalFenceHandleTypeFlagsKHR -> VkExternalFenceHandleTypeFlagsKHR -> VkExternalFenceHandleTypeFlagsKHR #

complement :: VkExternalFenceHandleTypeFlagsKHR -> VkExternalFenceHandleTypeFlagsKHR #

shift :: VkExternalFenceHandleTypeFlagsKHR -> Int -> VkExternalFenceHandleTypeFlagsKHR #

rotate :: VkExternalFenceHandleTypeFlagsKHR -> Int -> VkExternalFenceHandleTypeFlagsKHR #

zeroBits :: VkExternalFenceHandleTypeFlagsKHR #

bit :: Int -> VkExternalFenceHandleTypeFlagsKHR #

setBit :: VkExternalFenceHandleTypeFlagsKHR -> Int -> VkExternalFenceHandleTypeFlagsKHR #

clearBit :: VkExternalFenceHandleTypeFlagsKHR -> Int -> VkExternalFenceHandleTypeFlagsKHR #

complementBit :: VkExternalFenceHandleTypeFlagsKHR -> Int -> VkExternalFenceHandleTypeFlagsKHR #

testBit :: VkExternalFenceHandleTypeFlagsKHR -> Int -> Bool #

bitSizeMaybe :: VkExternalFenceHandleTypeFlagsKHR -> Maybe Int #

bitSize :: VkExternalFenceHandleTypeFlagsKHR -> Int #

isSigned :: VkExternalFenceHandleTypeFlagsKHR -> Bool #

shiftL :: VkExternalFenceHandleTypeFlagsKHR -> Int -> VkExternalFenceHandleTypeFlagsKHR #

unsafeShiftL :: VkExternalFenceHandleTypeFlagsKHR -> Int -> VkExternalFenceHandleTypeFlagsKHR #

shiftR :: VkExternalFenceHandleTypeFlagsKHR -> Int -> VkExternalFenceHandleTypeFlagsKHR #

unsafeShiftR :: VkExternalFenceHandleTypeFlagsKHR -> Int -> VkExternalFenceHandleTypeFlagsKHR #

rotateL :: VkExternalFenceHandleTypeFlagsKHR -> Int -> VkExternalFenceHandleTypeFlagsKHR #

rotateR :: VkExternalFenceHandleTypeFlagsKHR -> Int -> VkExternalFenceHandleTypeFlagsKHR #

popCount :: VkExternalFenceHandleTypeFlagsKHR -> Int #

FiniteBits VkExternalFenceHandleTypeFlagsKHR Source # 
type Rep VkExternalFenceHandleTypeFlagsKHR Source # 
type Rep VkExternalFenceHandleTypeFlagsKHR = D1 (MetaData "VkExternalFenceHandleTypeFlagsKHR" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkExternalFenceHandleTypeFlagsKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkExternalMemoryFeatureFlagsKHR Source #

Instances

Bounded VkExternalMemoryFeatureFlagsKHR Source # 
Enum VkExternalMemoryFeatureFlagsKHR Source # 
Eq VkExternalMemoryFeatureFlagsKHR Source # 
Integral VkExternalMemoryFeatureFlagsKHR Source # 
Data VkExternalMemoryFeatureFlagsKHR Source # 

Methods

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

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

toConstr :: VkExternalMemoryFeatureFlagsKHR -> Constr #

dataTypeOf :: VkExternalMemoryFeatureFlagsKHR -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkExternalMemoryFeatureFlagsKHR Source # 
Ord VkExternalMemoryFeatureFlagsKHR Source # 
Read VkExternalMemoryFeatureFlagsKHR Source # 
Real VkExternalMemoryFeatureFlagsKHR Source # 
Show VkExternalMemoryFeatureFlagsKHR Source # 
Generic VkExternalMemoryFeatureFlagsKHR Source # 
Storable VkExternalMemoryFeatureFlagsKHR Source # 
Bits VkExternalMemoryFeatureFlagsKHR Source # 

Methods

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

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

xor :: VkExternalMemoryFeatureFlagsKHR -> VkExternalMemoryFeatureFlagsKHR -> VkExternalMemoryFeatureFlagsKHR #

complement :: VkExternalMemoryFeatureFlagsKHR -> VkExternalMemoryFeatureFlagsKHR #

shift :: VkExternalMemoryFeatureFlagsKHR -> Int -> VkExternalMemoryFeatureFlagsKHR #

rotate :: VkExternalMemoryFeatureFlagsKHR -> Int -> VkExternalMemoryFeatureFlagsKHR #

zeroBits :: VkExternalMemoryFeatureFlagsKHR #

bit :: Int -> VkExternalMemoryFeatureFlagsKHR #

setBit :: VkExternalMemoryFeatureFlagsKHR -> Int -> VkExternalMemoryFeatureFlagsKHR #

clearBit :: VkExternalMemoryFeatureFlagsKHR -> Int -> VkExternalMemoryFeatureFlagsKHR #

complementBit :: VkExternalMemoryFeatureFlagsKHR -> Int -> VkExternalMemoryFeatureFlagsKHR #

testBit :: VkExternalMemoryFeatureFlagsKHR -> Int -> Bool #

bitSizeMaybe :: VkExternalMemoryFeatureFlagsKHR -> Maybe Int #

bitSize :: VkExternalMemoryFeatureFlagsKHR -> Int #

isSigned :: VkExternalMemoryFeatureFlagsKHR -> Bool #

shiftL :: VkExternalMemoryFeatureFlagsKHR -> Int -> VkExternalMemoryFeatureFlagsKHR #

unsafeShiftL :: VkExternalMemoryFeatureFlagsKHR -> Int -> VkExternalMemoryFeatureFlagsKHR #

shiftR :: VkExternalMemoryFeatureFlagsKHR -> Int -> VkExternalMemoryFeatureFlagsKHR #

unsafeShiftR :: VkExternalMemoryFeatureFlagsKHR -> Int -> VkExternalMemoryFeatureFlagsKHR #

rotateL :: VkExternalMemoryFeatureFlagsKHR -> Int -> VkExternalMemoryFeatureFlagsKHR #

rotateR :: VkExternalMemoryFeatureFlagsKHR -> Int -> VkExternalMemoryFeatureFlagsKHR #

popCount :: VkExternalMemoryFeatureFlagsKHR -> Int #

FiniteBits VkExternalMemoryFeatureFlagsKHR Source # 
type Rep VkExternalMemoryFeatureFlagsKHR Source # 
type Rep VkExternalMemoryFeatureFlagsKHR = D1 (MetaData "VkExternalMemoryFeatureFlagsKHR" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkExternalMemoryFeatureFlagsKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkExternalMemoryHandleTypeFlagsKHR Source #

Instances

Bounded VkExternalMemoryHandleTypeFlagsKHR Source # 
Enum VkExternalMemoryHandleTypeFlagsKHR Source # 
Eq VkExternalMemoryHandleTypeFlagsKHR Source # 
Integral VkExternalMemoryHandleTypeFlagsKHR Source # 
Data VkExternalMemoryHandleTypeFlagsKHR Source # 

Methods

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

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

toConstr :: VkExternalMemoryHandleTypeFlagsKHR -> Constr #

dataTypeOf :: VkExternalMemoryHandleTypeFlagsKHR -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkExternalMemoryHandleTypeFlagsKHR Source # 
Ord VkExternalMemoryHandleTypeFlagsKHR Source # 
Read VkExternalMemoryHandleTypeFlagsKHR Source # 
Real VkExternalMemoryHandleTypeFlagsKHR Source # 
Show VkExternalMemoryHandleTypeFlagsKHR Source # 
Generic VkExternalMemoryHandleTypeFlagsKHR Source # 
Storable VkExternalMemoryHandleTypeFlagsKHR Source # 
Bits VkExternalMemoryHandleTypeFlagsKHR Source # 

Methods

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

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

xor :: VkExternalMemoryHandleTypeFlagsKHR -> VkExternalMemoryHandleTypeFlagsKHR -> VkExternalMemoryHandleTypeFlagsKHR #

complement :: VkExternalMemoryHandleTypeFlagsKHR -> VkExternalMemoryHandleTypeFlagsKHR #

shift :: VkExternalMemoryHandleTypeFlagsKHR -> Int -> VkExternalMemoryHandleTypeFlagsKHR #

rotate :: VkExternalMemoryHandleTypeFlagsKHR -> Int -> VkExternalMemoryHandleTypeFlagsKHR #

zeroBits :: VkExternalMemoryHandleTypeFlagsKHR #

bit :: Int -> VkExternalMemoryHandleTypeFlagsKHR #

setBit :: VkExternalMemoryHandleTypeFlagsKHR -> Int -> VkExternalMemoryHandleTypeFlagsKHR #

clearBit :: VkExternalMemoryHandleTypeFlagsKHR -> Int -> VkExternalMemoryHandleTypeFlagsKHR #

complementBit :: VkExternalMemoryHandleTypeFlagsKHR -> Int -> VkExternalMemoryHandleTypeFlagsKHR #

testBit :: VkExternalMemoryHandleTypeFlagsKHR -> Int -> Bool #

bitSizeMaybe :: VkExternalMemoryHandleTypeFlagsKHR -> Maybe Int #

bitSize :: VkExternalMemoryHandleTypeFlagsKHR -> Int #

isSigned :: VkExternalMemoryHandleTypeFlagsKHR -> Bool #

shiftL :: VkExternalMemoryHandleTypeFlagsKHR -> Int -> VkExternalMemoryHandleTypeFlagsKHR #

unsafeShiftL :: VkExternalMemoryHandleTypeFlagsKHR -> Int -> VkExternalMemoryHandleTypeFlagsKHR #

shiftR :: VkExternalMemoryHandleTypeFlagsKHR -> Int -> VkExternalMemoryHandleTypeFlagsKHR #

unsafeShiftR :: VkExternalMemoryHandleTypeFlagsKHR -> Int -> VkExternalMemoryHandleTypeFlagsKHR #

rotateL :: VkExternalMemoryHandleTypeFlagsKHR -> Int -> VkExternalMemoryHandleTypeFlagsKHR #

rotateR :: VkExternalMemoryHandleTypeFlagsKHR -> Int -> VkExternalMemoryHandleTypeFlagsKHR #

popCount :: VkExternalMemoryHandleTypeFlagsKHR -> Int #

FiniteBits VkExternalMemoryHandleTypeFlagsKHR Source # 
type Rep VkExternalMemoryHandleTypeFlagsKHR Source # 
type Rep VkExternalMemoryHandleTypeFlagsKHR = D1 (MetaData "VkExternalMemoryHandleTypeFlagsKHR" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkExternalMemoryHandleTypeFlagsKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkExternalSemaphoreFeatureFlagsKHR Source #

Instances

Bounded VkExternalSemaphoreFeatureFlagsKHR Source # 
Enum VkExternalSemaphoreFeatureFlagsKHR Source # 
Eq VkExternalSemaphoreFeatureFlagsKHR Source # 
Integral VkExternalSemaphoreFeatureFlagsKHR Source # 
Data VkExternalSemaphoreFeatureFlagsKHR Source # 

Methods

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

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

toConstr :: VkExternalSemaphoreFeatureFlagsKHR -> Constr #

dataTypeOf :: VkExternalSemaphoreFeatureFlagsKHR -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkExternalSemaphoreFeatureFlagsKHR Source # 
Ord VkExternalSemaphoreFeatureFlagsKHR Source # 
Read VkExternalSemaphoreFeatureFlagsKHR Source # 
Real VkExternalSemaphoreFeatureFlagsKHR Source # 
Show VkExternalSemaphoreFeatureFlagsKHR Source # 
Generic VkExternalSemaphoreFeatureFlagsKHR Source # 
Storable VkExternalSemaphoreFeatureFlagsKHR Source # 
Bits VkExternalSemaphoreFeatureFlagsKHR Source # 

Methods

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

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

xor :: VkExternalSemaphoreFeatureFlagsKHR -> VkExternalSemaphoreFeatureFlagsKHR -> VkExternalSemaphoreFeatureFlagsKHR #

complement :: VkExternalSemaphoreFeatureFlagsKHR -> VkExternalSemaphoreFeatureFlagsKHR #

shift :: VkExternalSemaphoreFeatureFlagsKHR -> Int -> VkExternalSemaphoreFeatureFlagsKHR #

rotate :: VkExternalSemaphoreFeatureFlagsKHR -> Int -> VkExternalSemaphoreFeatureFlagsKHR #

zeroBits :: VkExternalSemaphoreFeatureFlagsKHR #

bit :: Int -> VkExternalSemaphoreFeatureFlagsKHR #

setBit :: VkExternalSemaphoreFeatureFlagsKHR -> Int -> VkExternalSemaphoreFeatureFlagsKHR #

clearBit :: VkExternalSemaphoreFeatureFlagsKHR -> Int -> VkExternalSemaphoreFeatureFlagsKHR #

complementBit :: VkExternalSemaphoreFeatureFlagsKHR -> Int -> VkExternalSemaphoreFeatureFlagsKHR #

testBit :: VkExternalSemaphoreFeatureFlagsKHR -> Int -> Bool #

bitSizeMaybe :: VkExternalSemaphoreFeatureFlagsKHR -> Maybe Int #

bitSize :: VkExternalSemaphoreFeatureFlagsKHR -> Int #

isSigned :: VkExternalSemaphoreFeatureFlagsKHR -> Bool #

shiftL :: VkExternalSemaphoreFeatureFlagsKHR -> Int -> VkExternalSemaphoreFeatureFlagsKHR #

unsafeShiftL :: VkExternalSemaphoreFeatureFlagsKHR -> Int -> VkExternalSemaphoreFeatureFlagsKHR #

shiftR :: VkExternalSemaphoreFeatureFlagsKHR -> Int -> VkExternalSemaphoreFeatureFlagsKHR #

unsafeShiftR :: VkExternalSemaphoreFeatureFlagsKHR -> Int -> VkExternalSemaphoreFeatureFlagsKHR #

rotateL :: VkExternalSemaphoreFeatureFlagsKHR -> Int -> VkExternalSemaphoreFeatureFlagsKHR #

rotateR :: VkExternalSemaphoreFeatureFlagsKHR -> Int -> VkExternalSemaphoreFeatureFlagsKHR #

popCount :: VkExternalSemaphoreFeatureFlagsKHR -> Int #

FiniteBits VkExternalSemaphoreFeatureFlagsKHR Source # 
type Rep VkExternalSemaphoreFeatureFlagsKHR Source # 
type Rep VkExternalSemaphoreFeatureFlagsKHR = D1 (MetaData "VkExternalSemaphoreFeatureFlagsKHR" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkExternalSemaphoreFeatureFlagsKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkExternalSemaphoreHandleTypeFlagsKHR Source #

Instances

Bounded VkExternalSemaphoreHandleTypeFlagsKHR Source # 
Enum VkExternalSemaphoreHandleTypeFlagsKHR Source # 
Eq VkExternalSemaphoreHandleTypeFlagsKHR Source # 
Integral VkExternalSemaphoreHandleTypeFlagsKHR Source # 
Data VkExternalSemaphoreHandleTypeFlagsKHR Source # 

Methods

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

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

toConstr :: VkExternalSemaphoreHandleTypeFlagsKHR -> Constr #

dataTypeOf :: VkExternalSemaphoreHandleTypeFlagsKHR -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkExternalSemaphoreHandleTypeFlagsKHR Source # 
Ord VkExternalSemaphoreHandleTypeFlagsKHR Source # 
Read VkExternalSemaphoreHandleTypeFlagsKHR Source # 
Real VkExternalSemaphoreHandleTypeFlagsKHR Source # 
Show VkExternalSemaphoreHandleTypeFlagsKHR Source # 
Generic VkExternalSemaphoreHandleTypeFlagsKHR Source # 
Storable VkExternalSemaphoreHandleTypeFlagsKHR Source # 
Bits VkExternalSemaphoreHandleTypeFlagsKHR Source # 

Methods

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

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

xor :: VkExternalSemaphoreHandleTypeFlagsKHR -> VkExternalSemaphoreHandleTypeFlagsKHR -> VkExternalSemaphoreHandleTypeFlagsKHR #

complement :: VkExternalSemaphoreHandleTypeFlagsKHR -> VkExternalSemaphoreHandleTypeFlagsKHR #

shift :: VkExternalSemaphoreHandleTypeFlagsKHR -> Int -> VkExternalSemaphoreHandleTypeFlagsKHR #

rotate :: VkExternalSemaphoreHandleTypeFlagsKHR -> Int -> VkExternalSemaphoreHandleTypeFlagsKHR #

zeroBits :: VkExternalSemaphoreHandleTypeFlagsKHR #

bit :: Int -> VkExternalSemaphoreHandleTypeFlagsKHR #

setBit :: VkExternalSemaphoreHandleTypeFlagsKHR -> Int -> VkExternalSemaphoreHandleTypeFlagsKHR #

clearBit :: VkExternalSemaphoreHandleTypeFlagsKHR -> Int -> VkExternalSemaphoreHandleTypeFlagsKHR #

complementBit :: VkExternalSemaphoreHandleTypeFlagsKHR -> Int -> VkExternalSemaphoreHandleTypeFlagsKHR #

testBit :: VkExternalSemaphoreHandleTypeFlagsKHR -> Int -> Bool #

bitSizeMaybe :: VkExternalSemaphoreHandleTypeFlagsKHR -> Maybe Int #

bitSize :: VkExternalSemaphoreHandleTypeFlagsKHR -> Int #

isSigned :: VkExternalSemaphoreHandleTypeFlagsKHR -> Bool #

shiftL :: VkExternalSemaphoreHandleTypeFlagsKHR -> Int -> VkExternalSemaphoreHandleTypeFlagsKHR #

unsafeShiftL :: VkExternalSemaphoreHandleTypeFlagsKHR -> Int -> VkExternalSemaphoreHandleTypeFlagsKHR #

shiftR :: VkExternalSemaphoreHandleTypeFlagsKHR -> Int -> VkExternalSemaphoreHandleTypeFlagsKHR #

unsafeShiftR :: VkExternalSemaphoreHandleTypeFlagsKHR -> Int -> VkExternalSemaphoreHandleTypeFlagsKHR #

rotateL :: VkExternalSemaphoreHandleTypeFlagsKHR -> Int -> VkExternalSemaphoreHandleTypeFlagsKHR #

rotateR :: VkExternalSemaphoreHandleTypeFlagsKHR -> Int -> VkExternalSemaphoreHandleTypeFlagsKHR #

popCount :: VkExternalSemaphoreHandleTypeFlagsKHR -> Int #

FiniteBits VkExternalSemaphoreHandleTypeFlagsKHR Source # 
type Rep VkExternalSemaphoreHandleTypeFlagsKHR Source # 
type Rep VkExternalSemaphoreHandleTypeFlagsKHR = D1 (MetaData "VkExternalSemaphoreHandleTypeFlagsKHR" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkExternalSemaphoreHandleTypeFlagsKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkFenceImportFlagsKHR Source #

Instances

Bounded VkFenceImportFlagsKHR Source # 
Enum VkFenceImportFlagsKHR Source # 
Eq VkFenceImportFlagsKHR Source # 
Integral VkFenceImportFlagsKHR Source # 
Data VkFenceImportFlagsKHR Source # 

Methods

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

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

toConstr :: VkFenceImportFlagsKHR -> Constr #

dataTypeOf :: VkFenceImportFlagsKHR -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkFenceImportFlagsKHR Source # 
Ord VkFenceImportFlagsKHR Source # 
Read VkFenceImportFlagsKHR Source # 
Real VkFenceImportFlagsKHR Source # 
Show VkFenceImportFlagsKHR Source # 
Generic VkFenceImportFlagsKHR Source # 
Storable VkFenceImportFlagsKHR Source # 
Bits VkFenceImportFlagsKHR Source # 
FiniteBits VkFenceImportFlagsKHR Source # 
type Rep VkFenceImportFlagsKHR Source # 
type Rep VkFenceImportFlagsKHR = D1 (MetaData "VkFenceImportFlagsKHR" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkFenceImportFlagsKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkFramebufferCreateFlags Source #

Instances

Bounded VkFramebufferCreateFlags Source # 
Enum VkFramebufferCreateFlags Source # 
Eq VkFramebufferCreateFlags Source # 
Integral VkFramebufferCreateFlags Source # 
Data VkFramebufferCreateFlags Source # 

Methods

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

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

toConstr :: VkFramebufferCreateFlags -> Constr #

dataTypeOf :: VkFramebufferCreateFlags -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkFramebufferCreateFlags Source # 
Ord VkFramebufferCreateFlags Source # 
Read VkFramebufferCreateFlags Source # 
Real VkFramebufferCreateFlags Source # 
Show VkFramebufferCreateFlags Source # 
Generic VkFramebufferCreateFlags Source # 
Storable VkFramebufferCreateFlags Source # 
Bits VkFramebufferCreateFlags Source # 
FiniteBits VkFramebufferCreateFlags Source # 
type Rep VkFramebufferCreateFlags Source # 
type Rep VkFramebufferCreateFlags = D1 (MetaData "VkFramebufferCreateFlags" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkFramebufferCreateFlags" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkIOSSurfaceCreateFlagsMVK Source #

Instances

Bounded VkIOSSurfaceCreateFlagsMVK Source # 
Enum VkIOSSurfaceCreateFlagsMVK Source # 
Eq VkIOSSurfaceCreateFlagsMVK Source # 
Integral VkIOSSurfaceCreateFlagsMVK Source # 
Data VkIOSSurfaceCreateFlagsMVK Source # 

Methods

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

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

toConstr :: VkIOSSurfaceCreateFlagsMVK -> Constr #

dataTypeOf :: VkIOSSurfaceCreateFlagsMVK -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkIOSSurfaceCreateFlagsMVK Source # 
Ord VkIOSSurfaceCreateFlagsMVK Source # 
Read VkIOSSurfaceCreateFlagsMVK Source # 
Real VkIOSSurfaceCreateFlagsMVK Source # 
Show VkIOSSurfaceCreateFlagsMVK Source # 
Generic VkIOSSurfaceCreateFlagsMVK Source # 
Storable VkIOSSurfaceCreateFlagsMVK Source # 
Bits VkIOSSurfaceCreateFlagsMVK Source # 

Methods

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

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

xor :: VkIOSSurfaceCreateFlagsMVK -> VkIOSSurfaceCreateFlagsMVK -> VkIOSSurfaceCreateFlagsMVK #

complement :: VkIOSSurfaceCreateFlagsMVK -> VkIOSSurfaceCreateFlagsMVK #

shift :: VkIOSSurfaceCreateFlagsMVK -> Int -> VkIOSSurfaceCreateFlagsMVK #

rotate :: VkIOSSurfaceCreateFlagsMVK -> Int -> VkIOSSurfaceCreateFlagsMVK #

zeroBits :: VkIOSSurfaceCreateFlagsMVK #

bit :: Int -> VkIOSSurfaceCreateFlagsMVK #

setBit :: VkIOSSurfaceCreateFlagsMVK -> Int -> VkIOSSurfaceCreateFlagsMVK #

clearBit :: VkIOSSurfaceCreateFlagsMVK -> Int -> VkIOSSurfaceCreateFlagsMVK #

complementBit :: VkIOSSurfaceCreateFlagsMVK -> Int -> VkIOSSurfaceCreateFlagsMVK #

testBit :: VkIOSSurfaceCreateFlagsMVK -> Int -> Bool #

bitSizeMaybe :: VkIOSSurfaceCreateFlagsMVK -> Maybe Int #

bitSize :: VkIOSSurfaceCreateFlagsMVK -> Int #

isSigned :: VkIOSSurfaceCreateFlagsMVK -> Bool #

shiftL :: VkIOSSurfaceCreateFlagsMVK -> Int -> VkIOSSurfaceCreateFlagsMVK #

unsafeShiftL :: VkIOSSurfaceCreateFlagsMVK -> Int -> VkIOSSurfaceCreateFlagsMVK #

shiftR :: VkIOSSurfaceCreateFlagsMVK -> Int -> VkIOSSurfaceCreateFlagsMVK #

unsafeShiftR :: VkIOSSurfaceCreateFlagsMVK -> Int -> VkIOSSurfaceCreateFlagsMVK #

rotateL :: VkIOSSurfaceCreateFlagsMVK -> Int -> VkIOSSurfaceCreateFlagsMVK #

rotateR :: VkIOSSurfaceCreateFlagsMVK -> Int -> VkIOSSurfaceCreateFlagsMVK #

popCount :: VkIOSSurfaceCreateFlagsMVK -> Int #

FiniteBits VkIOSSurfaceCreateFlagsMVK Source # 
type Rep VkIOSSurfaceCreateFlagsMVK Source # 
type Rep VkIOSSurfaceCreateFlagsMVK = D1 (MetaData "VkIOSSurfaceCreateFlagsMVK" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkIOSSurfaceCreateFlagsMVK" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkImageViewCreateFlags Source #

Instances

Bounded VkImageViewCreateFlags Source # 
Enum VkImageViewCreateFlags Source # 
Eq VkImageViewCreateFlags Source # 
Integral VkImageViewCreateFlags Source # 
Data VkImageViewCreateFlags Source # 

Methods

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

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

toConstr :: VkImageViewCreateFlags -> Constr #

dataTypeOf :: VkImageViewCreateFlags -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkImageViewCreateFlags Source # 
Ord VkImageViewCreateFlags Source # 
Read VkImageViewCreateFlags Source # 
Real VkImageViewCreateFlags Source # 
Show VkImageViewCreateFlags Source # 
Generic VkImageViewCreateFlags Source # 
Storable VkImageViewCreateFlags Source # 
Bits VkImageViewCreateFlags Source # 
FiniteBits VkImageViewCreateFlags Source # 
type Rep VkImageViewCreateFlags Source # 
type Rep VkImageViewCreateFlags = D1 (MetaData "VkImageViewCreateFlags" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkImageViewCreateFlags" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkInstanceCreateFlags Source #

Instances

Bounded VkInstanceCreateFlags Source # 
Enum VkInstanceCreateFlags Source # 
Eq VkInstanceCreateFlags Source # 
Integral VkInstanceCreateFlags Source # 
Data VkInstanceCreateFlags Source # 

Methods

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

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

toConstr :: VkInstanceCreateFlags -> Constr #

dataTypeOf :: VkInstanceCreateFlags -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkInstanceCreateFlags Source # 
Ord VkInstanceCreateFlags Source # 
Read VkInstanceCreateFlags Source # 
Real VkInstanceCreateFlags Source # 
Show VkInstanceCreateFlags Source # 
Generic VkInstanceCreateFlags Source # 
Storable VkInstanceCreateFlags Source # 
Bits VkInstanceCreateFlags Source # 
FiniteBits VkInstanceCreateFlags Source # 
type Rep VkInstanceCreateFlags Source # 
type Rep VkInstanceCreateFlags = D1 (MetaData "VkInstanceCreateFlags" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkInstanceCreateFlags" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkMacOSSurfaceCreateFlagsMVK Source #

Instances

Bounded VkMacOSSurfaceCreateFlagsMVK Source # 
Enum VkMacOSSurfaceCreateFlagsMVK Source # 
Eq VkMacOSSurfaceCreateFlagsMVK Source # 
Integral VkMacOSSurfaceCreateFlagsMVK Source # 
Data VkMacOSSurfaceCreateFlagsMVK Source # 

Methods

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

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

toConstr :: VkMacOSSurfaceCreateFlagsMVK -> Constr #

dataTypeOf :: VkMacOSSurfaceCreateFlagsMVK -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkMacOSSurfaceCreateFlagsMVK Source # 
Ord VkMacOSSurfaceCreateFlagsMVK Source # 
Read VkMacOSSurfaceCreateFlagsMVK Source # 
Real VkMacOSSurfaceCreateFlagsMVK Source # 
Show VkMacOSSurfaceCreateFlagsMVK Source # 
Generic VkMacOSSurfaceCreateFlagsMVK Source # 
Storable VkMacOSSurfaceCreateFlagsMVK Source # 
Bits VkMacOSSurfaceCreateFlagsMVK Source # 

Methods

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

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

xor :: VkMacOSSurfaceCreateFlagsMVK -> VkMacOSSurfaceCreateFlagsMVK -> VkMacOSSurfaceCreateFlagsMVK #

complement :: VkMacOSSurfaceCreateFlagsMVK -> VkMacOSSurfaceCreateFlagsMVK #

shift :: VkMacOSSurfaceCreateFlagsMVK -> Int -> VkMacOSSurfaceCreateFlagsMVK #

rotate :: VkMacOSSurfaceCreateFlagsMVK -> Int -> VkMacOSSurfaceCreateFlagsMVK #

zeroBits :: VkMacOSSurfaceCreateFlagsMVK #

bit :: Int -> VkMacOSSurfaceCreateFlagsMVK #

setBit :: VkMacOSSurfaceCreateFlagsMVK -> Int -> VkMacOSSurfaceCreateFlagsMVK #

clearBit :: VkMacOSSurfaceCreateFlagsMVK -> Int -> VkMacOSSurfaceCreateFlagsMVK #

complementBit :: VkMacOSSurfaceCreateFlagsMVK -> Int -> VkMacOSSurfaceCreateFlagsMVK #

testBit :: VkMacOSSurfaceCreateFlagsMVK -> Int -> Bool #

bitSizeMaybe :: VkMacOSSurfaceCreateFlagsMVK -> Maybe Int #

bitSize :: VkMacOSSurfaceCreateFlagsMVK -> Int #

isSigned :: VkMacOSSurfaceCreateFlagsMVK -> Bool #

shiftL :: VkMacOSSurfaceCreateFlagsMVK -> Int -> VkMacOSSurfaceCreateFlagsMVK #

unsafeShiftL :: VkMacOSSurfaceCreateFlagsMVK -> Int -> VkMacOSSurfaceCreateFlagsMVK #

shiftR :: VkMacOSSurfaceCreateFlagsMVK -> Int -> VkMacOSSurfaceCreateFlagsMVK #

unsafeShiftR :: VkMacOSSurfaceCreateFlagsMVK -> Int -> VkMacOSSurfaceCreateFlagsMVK #

rotateL :: VkMacOSSurfaceCreateFlagsMVK -> Int -> VkMacOSSurfaceCreateFlagsMVK #

rotateR :: VkMacOSSurfaceCreateFlagsMVK -> Int -> VkMacOSSurfaceCreateFlagsMVK #

popCount :: VkMacOSSurfaceCreateFlagsMVK -> Int #

FiniteBits VkMacOSSurfaceCreateFlagsMVK Source # 
type Rep VkMacOSSurfaceCreateFlagsMVK Source # 
type Rep VkMacOSSurfaceCreateFlagsMVK = D1 (MetaData "VkMacOSSurfaceCreateFlagsMVK" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkMacOSSurfaceCreateFlagsMVK" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkMemoryAllocateFlagsKHR Source #

Instances

Bounded VkMemoryAllocateFlagsKHR Source # 
Enum VkMemoryAllocateFlagsKHR Source # 
Eq VkMemoryAllocateFlagsKHR Source # 
Integral VkMemoryAllocateFlagsKHR Source # 
Data VkMemoryAllocateFlagsKHR Source # 

Methods

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

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

toConstr :: VkMemoryAllocateFlagsKHR -> Constr #

dataTypeOf :: VkMemoryAllocateFlagsKHR -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkMemoryAllocateFlagsKHR Source # 
Ord VkMemoryAllocateFlagsKHR Source # 
Read VkMemoryAllocateFlagsKHR Source # 
Real VkMemoryAllocateFlagsKHR Source # 
Show VkMemoryAllocateFlagsKHR Source # 
Generic VkMemoryAllocateFlagsKHR Source # 
Storable VkMemoryAllocateFlagsKHR Source # 
Bits VkMemoryAllocateFlagsKHR Source # 
FiniteBits VkMemoryAllocateFlagsKHR Source # 
type Rep VkMemoryAllocateFlagsKHR Source # 
type Rep VkMemoryAllocateFlagsKHR = D1 (MetaData "VkMemoryAllocateFlagsKHR" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkMemoryAllocateFlagsKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkMemoryMapFlags Source #

Instances

Bounded VkMemoryMapFlags Source # 
Enum VkMemoryMapFlags Source # 
Eq VkMemoryMapFlags Source # 
Integral VkMemoryMapFlags Source # 
Data VkMemoryMapFlags Source # 

Methods

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

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

toConstr :: VkMemoryMapFlags -> Constr #

dataTypeOf :: VkMemoryMapFlags -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkMemoryMapFlags Source # 
Ord VkMemoryMapFlags Source # 
Read VkMemoryMapFlags Source # 
Real VkMemoryMapFlags Source # 
Show VkMemoryMapFlags Source # 
Generic VkMemoryMapFlags Source # 
Storable VkMemoryMapFlags Source # 
Bits VkMemoryMapFlags Source # 
FiniteBits VkMemoryMapFlags Source # 
type Rep VkMemoryMapFlags Source # 
type Rep VkMemoryMapFlags = D1 (MetaData "VkMemoryMapFlags" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkMemoryMapFlags" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkMirSurfaceCreateFlagsKHR Source #

Instances

Bounded VkMirSurfaceCreateFlagsKHR Source # 
Enum VkMirSurfaceCreateFlagsKHR Source # 
Eq VkMirSurfaceCreateFlagsKHR Source # 
Integral VkMirSurfaceCreateFlagsKHR Source # 
Data VkMirSurfaceCreateFlagsKHR Source # 

Methods

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

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

toConstr :: VkMirSurfaceCreateFlagsKHR -> Constr #

dataTypeOf :: VkMirSurfaceCreateFlagsKHR -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkMirSurfaceCreateFlagsKHR Source # 
Ord VkMirSurfaceCreateFlagsKHR Source # 
Read VkMirSurfaceCreateFlagsKHR Source # 
Real VkMirSurfaceCreateFlagsKHR Source # 
Show VkMirSurfaceCreateFlagsKHR Source # 
Generic VkMirSurfaceCreateFlagsKHR Source # 
Storable VkMirSurfaceCreateFlagsKHR Source # 
Bits VkMirSurfaceCreateFlagsKHR Source # 

Methods

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

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

xor :: VkMirSurfaceCreateFlagsKHR -> VkMirSurfaceCreateFlagsKHR -> VkMirSurfaceCreateFlagsKHR #

complement :: VkMirSurfaceCreateFlagsKHR -> VkMirSurfaceCreateFlagsKHR #

shift :: VkMirSurfaceCreateFlagsKHR -> Int -> VkMirSurfaceCreateFlagsKHR #

rotate :: VkMirSurfaceCreateFlagsKHR -> Int -> VkMirSurfaceCreateFlagsKHR #

zeroBits :: VkMirSurfaceCreateFlagsKHR #

bit :: Int -> VkMirSurfaceCreateFlagsKHR #

setBit :: VkMirSurfaceCreateFlagsKHR -> Int -> VkMirSurfaceCreateFlagsKHR #

clearBit :: VkMirSurfaceCreateFlagsKHR -> Int -> VkMirSurfaceCreateFlagsKHR #

complementBit :: VkMirSurfaceCreateFlagsKHR -> Int -> VkMirSurfaceCreateFlagsKHR #

testBit :: VkMirSurfaceCreateFlagsKHR -> Int -> Bool #

bitSizeMaybe :: VkMirSurfaceCreateFlagsKHR -> Maybe Int #

bitSize :: VkMirSurfaceCreateFlagsKHR -> Int #

isSigned :: VkMirSurfaceCreateFlagsKHR -> Bool #

shiftL :: VkMirSurfaceCreateFlagsKHR -> Int -> VkMirSurfaceCreateFlagsKHR #

unsafeShiftL :: VkMirSurfaceCreateFlagsKHR -> Int -> VkMirSurfaceCreateFlagsKHR #

shiftR :: VkMirSurfaceCreateFlagsKHR -> Int -> VkMirSurfaceCreateFlagsKHR #

unsafeShiftR :: VkMirSurfaceCreateFlagsKHR -> Int -> VkMirSurfaceCreateFlagsKHR #

rotateL :: VkMirSurfaceCreateFlagsKHR -> Int -> VkMirSurfaceCreateFlagsKHR #

rotateR :: VkMirSurfaceCreateFlagsKHR -> Int -> VkMirSurfaceCreateFlagsKHR #

popCount :: VkMirSurfaceCreateFlagsKHR -> Int #

FiniteBits VkMirSurfaceCreateFlagsKHR Source # 
type Rep VkMirSurfaceCreateFlagsKHR Source # 
type Rep VkMirSurfaceCreateFlagsKHR = D1 (MetaData "VkMirSurfaceCreateFlagsKHR" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkMirSurfaceCreateFlagsKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkPeerMemoryFeatureFlagsKHR Source #

Instances

Bounded VkPeerMemoryFeatureFlagsKHR Source # 
Enum VkPeerMemoryFeatureFlagsKHR Source # 
Eq VkPeerMemoryFeatureFlagsKHR Source # 
Integral VkPeerMemoryFeatureFlagsKHR Source # 
Data VkPeerMemoryFeatureFlagsKHR Source # 

Methods

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

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

toConstr :: VkPeerMemoryFeatureFlagsKHR -> Constr #

dataTypeOf :: VkPeerMemoryFeatureFlagsKHR -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkPeerMemoryFeatureFlagsKHR Source # 
Ord VkPeerMemoryFeatureFlagsKHR Source # 
Read VkPeerMemoryFeatureFlagsKHR Source # 
Real VkPeerMemoryFeatureFlagsKHR Source # 
Show VkPeerMemoryFeatureFlagsKHR Source # 
Generic VkPeerMemoryFeatureFlagsKHR Source # 
Storable VkPeerMemoryFeatureFlagsKHR Source # 
Bits VkPeerMemoryFeatureFlagsKHR Source # 

Methods

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

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

xor :: VkPeerMemoryFeatureFlagsKHR -> VkPeerMemoryFeatureFlagsKHR -> VkPeerMemoryFeatureFlagsKHR #

complement :: VkPeerMemoryFeatureFlagsKHR -> VkPeerMemoryFeatureFlagsKHR #

shift :: VkPeerMemoryFeatureFlagsKHR -> Int -> VkPeerMemoryFeatureFlagsKHR #

rotate :: VkPeerMemoryFeatureFlagsKHR -> Int -> VkPeerMemoryFeatureFlagsKHR #

zeroBits :: VkPeerMemoryFeatureFlagsKHR #

bit :: Int -> VkPeerMemoryFeatureFlagsKHR #

setBit :: VkPeerMemoryFeatureFlagsKHR -> Int -> VkPeerMemoryFeatureFlagsKHR #

clearBit :: VkPeerMemoryFeatureFlagsKHR -> Int -> VkPeerMemoryFeatureFlagsKHR #

complementBit :: VkPeerMemoryFeatureFlagsKHR -> Int -> VkPeerMemoryFeatureFlagsKHR #

testBit :: VkPeerMemoryFeatureFlagsKHR -> Int -> Bool #

bitSizeMaybe :: VkPeerMemoryFeatureFlagsKHR -> Maybe Int #

bitSize :: VkPeerMemoryFeatureFlagsKHR -> Int #

isSigned :: VkPeerMemoryFeatureFlagsKHR -> Bool #

shiftL :: VkPeerMemoryFeatureFlagsKHR -> Int -> VkPeerMemoryFeatureFlagsKHR #

unsafeShiftL :: VkPeerMemoryFeatureFlagsKHR -> Int -> VkPeerMemoryFeatureFlagsKHR #

shiftR :: VkPeerMemoryFeatureFlagsKHR -> Int -> VkPeerMemoryFeatureFlagsKHR #

unsafeShiftR :: VkPeerMemoryFeatureFlagsKHR -> Int -> VkPeerMemoryFeatureFlagsKHR #

rotateL :: VkPeerMemoryFeatureFlagsKHR -> Int -> VkPeerMemoryFeatureFlagsKHR #

rotateR :: VkPeerMemoryFeatureFlagsKHR -> Int -> VkPeerMemoryFeatureFlagsKHR #

popCount :: VkPeerMemoryFeatureFlagsKHR -> Int #

FiniteBits VkPeerMemoryFeatureFlagsKHR Source # 
type Rep VkPeerMemoryFeatureFlagsKHR Source # 
type Rep VkPeerMemoryFeatureFlagsKHR = D1 (MetaData "VkPeerMemoryFeatureFlagsKHR" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkPeerMemoryFeatureFlagsKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkPipelineCacheCreateFlags Source #

Instances

Bounded VkPipelineCacheCreateFlags Source # 
Enum VkPipelineCacheCreateFlags Source # 
Eq VkPipelineCacheCreateFlags Source # 
Integral VkPipelineCacheCreateFlags Source # 
Data VkPipelineCacheCreateFlags Source # 

Methods

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

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

toConstr :: VkPipelineCacheCreateFlags -> Constr #

dataTypeOf :: VkPipelineCacheCreateFlags -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkPipelineCacheCreateFlags Source # 
Ord VkPipelineCacheCreateFlags Source # 
Read VkPipelineCacheCreateFlags Source # 
Real VkPipelineCacheCreateFlags Source # 
Show VkPipelineCacheCreateFlags Source # 
Generic VkPipelineCacheCreateFlags Source # 
Storable VkPipelineCacheCreateFlags Source # 
Bits VkPipelineCacheCreateFlags Source # 

Methods

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

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

xor :: VkPipelineCacheCreateFlags -> VkPipelineCacheCreateFlags -> VkPipelineCacheCreateFlags #

complement :: VkPipelineCacheCreateFlags -> VkPipelineCacheCreateFlags #

shift :: VkPipelineCacheCreateFlags -> Int -> VkPipelineCacheCreateFlags #

rotate :: VkPipelineCacheCreateFlags -> Int -> VkPipelineCacheCreateFlags #

zeroBits :: VkPipelineCacheCreateFlags #

bit :: Int -> VkPipelineCacheCreateFlags #

setBit :: VkPipelineCacheCreateFlags -> Int -> VkPipelineCacheCreateFlags #

clearBit :: VkPipelineCacheCreateFlags -> Int -> VkPipelineCacheCreateFlags #

complementBit :: VkPipelineCacheCreateFlags -> Int -> VkPipelineCacheCreateFlags #

testBit :: VkPipelineCacheCreateFlags -> Int -> Bool #

bitSizeMaybe :: VkPipelineCacheCreateFlags -> Maybe Int #

bitSize :: VkPipelineCacheCreateFlags -> Int #

isSigned :: VkPipelineCacheCreateFlags -> Bool #

shiftL :: VkPipelineCacheCreateFlags -> Int -> VkPipelineCacheCreateFlags #

unsafeShiftL :: VkPipelineCacheCreateFlags -> Int -> VkPipelineCacheCreateFlags #

shiftR :: VkPipelineCacheCreateFlags -> Int -> VkPipelineCacheCreateFlags #

unsafeShiftR :: VkPipelineCacheCreateFlags -> Int -> VkPipelineCacheCreateFlags #

rotateL :: VkPipelineCacheCreateFlags -> Int -> VkPipelineCacheCreateFlags #

rotateR :: VkPipelineCacheCreateFlags -> Int -> VkPipelineCacheCreateFlags #

popCount :: VkPipelineCacheCreateFlags -> Int #

FiniteBits VkPipelineCacheCreateFlags Source # 
type Rep VkPipelineCacheCreateFlags Source # 
type Rep VkPipelineCacheCreateFlags = D1 (MetaData "VkPipelineCacheCreateFlags" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkPipelineCacheCreateFlags" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkPipelineColorBlendStateCreateFlags Source #

Instances

Bounded VkPipelineColorBlendStateCreateFlags Source # 
Enum VkPipelineColorBlendStateCreateFlags Source # 
Eq VkPipelineColorBlendStateCreateFlags Source # 
Integral VkPipelineColorBlendStateCreateFlags Source # 
Data VkPipelineColorBlendStateCreateFlags Source # 

Methods

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

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

toConstr :: VkPipelineColorBlendStateCreateFlags -> Constr #

dataTypeOf :: VkPipelineColorBlendStateCreateFlags -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkPipelineColorBlendStateCreateFlags Source # 
Ord VkPipelineColorBlendStateCreateFlags Source # 
Read VkPipelineColorBlendStateCreateFlags Source # 
Real VkPipelineColorBlendStateCreateFlags Source # 
Show VkPipelineColorBlendStateCreateFlags Source # 
Generic VkPipelineColorBlendStateCreateFlags Source # 
Storable VkPipelineColorBlendStateCreateFlags Source # 
Bits VkPipelineColorBlendStateCreateFlags Source # 

Methods

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

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

xor :: VkPipelineColorBlendStateCreateFlags -> VkPipelineColorBlendStateCreateFlags -> VkPipelineColorBlendStateCreateFlags #

complement :: VkPipelineColorBlendStateCreateFlags -> VkPipelineColorBlendStateCreateFlags #

shift :: VkPipelineColorBlendStateCreateFlags -> Int -> VkPipelineColorBlendStateCreateFlags #

rotate :: VkPipelineColorBlendStateCreateFlags -> Int -> VkPipelineColorBlendStateCreateFlags #

zeroBits :: VkPipelineColorBlendStateCreateFlags #

bit :: Int -> VkPipelineColorBlendStateCreateFlags #

setBit :: VkPipelineColorBlendStateCreateFlags -> Int -> VkPipelineColorBlendStateCreateFlags #

clearBit :: VkPipelineColorBlendStateCreateFlags -> Int -> VkPipelineColorBlendStateCreateFlags #

complementBit :: VkPipelineColorBlendStateCreateFlags -> Int -> VkPipelineColorBlendStateCreateFlags #

testBit :: VkPipelineColorBlendStateCreateFlags -> Int -> Bool #

bitSizeMaybe :: VkPipelineColorBlendStateCreateFlags -> Maybe Int #

bitSize :: VkPipelineColorBlendStateCreateFlags -> Int #

isSigned :: VkPipelineColorBlendStateCreateFlags -> Bool #

shiftL :: VkPipelineColorBlendStateCreateFlags -> Int -> VkPipelineColorBlendStateCreateFlags #

unsafeShiftL :: VkPipelineColorBlendStateCreateFlags -> Int -> VkPipelineColorBlendStateCreateFlags #

shiftR :: VkPipelineColorBlendStateCreateFlags -> Int -> VkPipelineColorBlendStateCreateFlags #

unsafeShiftR :: VkPipelineColorBlendStateCreateFlags -> Int -> VkPipelineColorBlendStateCreateFlags #

rotateL :: VkPipelineColorBlendStateCreateFlags -> Int -> VkPipelineColorBlendStateCreateFlags #

rotateR :: VkPipelineColorBlendStateCreateFlags -> Int -> VkPipelineColorBlendStateCreateFlags #

popCount :: VkPipelineColorBlendStateCreateFlags -> Int #

FiniteBits VkPipelineColorBlendStateCreateFlags Source # 
type Rep VkPipelineColorBlendStateCreateFlags Source # 
type Rep VkPipelineColorBlendStateCreateFlags = D1 (MetaData "VkPipelineColorBlendStateCreateFlags" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkPipelineColorBlendStateCreateFlags" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkPipelineCoverageModulationStateCreateFlagsNV Source #

Instances

Bounded VkPipelineCoverageModulationStateCreateFlagsNV Source # 
Enum VkPipelineCoverageModulationStateCreateFlagsNV Source # 
Eq VkPipelineCoverageModulationStateCreateFlagsNV Source # 
Integral VkPipelineCoverageModulationStateCreateFlagsNV Source # 
Data VkPipelineCoverageModulationStateCreateFlagsNV Source # 

Methods

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

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

toConstr :: VkPipelineCoverageModulationStateCreateFlagsNV -> Constr #

dataTypeOf :: VkPipelineCoverageModulationStateCreateFlagsNV -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkPipelineCoverageModulationStateCreateFlagsNV Source # 
Ord VkPipelineCoverageModulationStateCreateFlagsNV Source # 
Read VkPipelineCoverageModulationStateCreateFlagsNV Source # 
Real VkPipelineCoverageModulationStateCreateFlagsNV Source # 
Show VkPipelineCoverageModulationStateCreateFlagsNV Source # 
Generic VkPipelineCoverageModulationStateCreateFlagsNV Source # 
Storable VkPipelineCoverageModulationStateCreateFlagsNV Source # 
Bits VkPipelineCoverageModulationStateCreateFlagsNV Source # 

Methods

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

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

xor :: VkPipelineCoverageModulationStateCreateFlagsNV -> VkPipelineCoverageModulationStateCreateFlagsNV -> VkPipelineCoverageModulationStateCreateFlagsNV #

complement :: VkPipelineCoverageModulationStateCreateFlagsNV -> VkPipelineCoverageModulationStateCreateFlagsNV #

shift :: VkPipelineCoverageModulationStateCreateFlagsNV -> Int -> VkPipelineCoverageModulationStateCreateFlagsNV #

rotate :: VkPipelineCoverageModulationStateCreateFlagsNV -> Int -> VkPipelineCoverageModulationStateCreateFlagsNV #

zeroBits :: VkPipelineCoverageModulationStateCreateFlagsNV #

bit :: Int -> VkPipelineCoverageModulationStateCreateFlagsNV #

setBit :: VkPipelineCoverageModulationStateCreateFlagsNV -> Int -> VkPipelineCoverageModulationStateCreateFlagsNV #

clearBit :: VkPipelineCoverageModulationStateCreateFlagsNV -> Int -> VkPipelineCoverageModulationStateCreateFlagsNV #

complementBit :: VkPipelineCoverageModulationStateCreateFlagsNV -> Int -> VkPipelineCoverageModulationStateCreateFlagsNV #

testBit :: VkPipelineCoverageModulationStateCreateFlagsNV -> Int -> Bool #

bitSizeMaybe :: VkPipelineCoverageModulationStateCreateFlagsNV -> Maybe Int #

bitSize :: VkPipelineCoverageModulationStateCreateFlagsNV -> Int #

isSigned :: VkPipelineCoverageModulationStateCreateFlagsNV -> Bool #

shiftL :: VkPipelineCoverageModulationStateCreateFlagsNV -> Int -> VkPipelineCoverageModulationStateCreateFlagsNV #

unsafeShiftL :: VkPipelineCoverageModulationStateCreateFlagsNV -> Int -> VkPipelineCoverageModulationStateCreateFlagsNV #

shiftR :: VkPipelineCoverageModulationStateCreateFlagsNV -> Int -> VkPipelineCoverageModulationStateCreateFlagsNV #

unsafeShiftR :: VkPipelineCoverageModulationStateCreateFlagsNV -> Int -> VkPipelineCoverageModulationStateCreateFlagsNV #

rotateL :: VkPipelineCoverageModulationStateCreateFlagsNV -> Int -> VkPipelineCoverageModulationStateCreateFlagsNV #

rotateR :: VkPipelineCoverageModulationStateCreateFlagsNV -> Int -> VkPipelineCoverageModulationStateCreateFlagsNV #

popCount :: VkPipelineCoverageModulationStateCreateFlagsNV -> Int #

FiniteBits VkPipelineCoverageModulationStateCreateFlagsNV Source # 
type Rep VkPipelineCoverageModulationStateCreateFlagsNV Source # 
type Rep VkPipelineCoverageModulationStateCreateFlagsNV = D1 (MetaData "VkPipelineCoverageModulationStateCreateFlagsNV" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkPipelineCoverageModulationStateCreateFlagsNV" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkPipelineCoverageToColorStateCreateFlagsNV Source #

Instances

Bounded VkPipelineCoverageToColorStateCreateFlagsNV Source # 
Enum VkPipelineCoverageToColorStateCreateFlagsNV Source # 
Eq VkPipelineCoverageToColorStateCreateFlagsNV Source # 
Integral VkPipelineCoverageToColorStateCreateFlagsNV Source # 
Data VkPipelineCoverageToColorStateCreateFlagsNV Source # 

Methods

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

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

toConstr :: VkPipelineCoverageToColorStateCreateFlagsNV -> Constr #

dataTypeOf :: VkPipelineCoverageToColorStateCreateFlagsNV -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkPipelineCoverageToColorStateCreateFlagsNV Source # 
Ord VkPipelineCoverageToColorStateCreateFlagsNV Source # 
Read VkPipelineCoverageToColorStateCreateFlagsNV Source # 
Real VkPipelineCoverageToColorStateCreateFlagsNV Source # 
Show VkPipelineCoverageToColorStateCreateFlagsNV Source # 
Generic VkPipelineCoverageToColorStateCreateFlagsNV Source # 
Storable VkPipelineCoverageToColorStateCreateFlagsNV Source # 
Bits VkPipelineCoverageToColorStateCreateFlagsNV Source # 

Methods

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

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

xor :: VkPipelineCoverageToColorStateCreateFlagsNV -> VkPipelineCoverageToColorStateCreateFlagsNV -> VkPipelineCoverageToColorStateCreateFlagsNV #

complement :: VkPipelineCoverageToColorStateCreateFlagsNV -> VkPipelineCoverageToColorStateCreateFlagsNV #

shift :: VkPipelineCoverageToColorStateCreateFlagsNV -> Int -> VkPipelineCoverageToColorStateCreateFlagsNV #

rotate :: VkPipelineCoverageToColorStateCreateFlagsNV -> Int -> VkPipelineCoverageToColorStateCreateFlagsNV #

zeroBits :: VkPipelineCoverageToColorStateCreateFlagsNV #

bit :: Int -> VkPipelineCoverageToColorStateCreateFlagsNV #

setBit :: VkPipelineCoverageToColorStateCreateFlagsNV -> Int -> VkPipelineCoverageToColorStateCreateFlagsNV #

clearBit :: VkPipelineCoverageToColorStateCreateFlagsNV -> Int -> VkPipelineCoverageToColorStateCreateFlagsNV #

complementBit :: VkPipelineCoverageToColorStateCreateFlagsNV -> Int -> VkPipelineCoverageToColorStateCreateFlagsNV #

testBit :: VkPipelineCoverageToColorStateCreateFlagsNV -> Int -> Bool #

bitSizeMaybe :: VkPipelineCoverageToColorStateCreateFlagsNV -> Maybe Int #

bitSize :: VkPipelineCoverageToColorStateCreateFlagsNV -> Int #

isSigned :: VkPipelineCoverageToColorStateCreateFlagsNV -> Bool #

shiftL :: VkPipelineCoverageToColorStateCreateFlagsNV -> Int -> VkPipelineCoverageToColorStateCreateFlagsNV #

unsafeShiftL :: VkPipelineCoverageToColorStateCreateFlagsNV -> Int -> VkPipelineCoverageToColorStateCreateFlagsNV #

shiftR :: VkPipelineCoverageToColorStateCreateFlagsNV -> Int -> VkPipelineCoverageToColorStateCreateFlagsNV #

unsafeShiftR :: VkPipelineCoverageToColorStateCreateFlagsNV -> Int -> VkPipelineCoverageToColorStateCreateFlagsNV #

rotateL :: VkPipelineCoverageToColorStateCreateFlagsNV -> Int -> VkPipelineCoverageToColorStateCreateFlagsNV #

rotateR :: VkPipelineCoverageToColorStateCreateFlagsNV -> Int -> VkPipelineCoverageToColorStateCreateFlagsNV #

popCount :: VkPipelineCoverageToColorStateCreateFlagsNV -> Int #

FiniteBits VkPipelineCoverageToColorStateCreateFlagsNV Source # 
type Rep VkPipelineCoverageToColorStateCreateFlagsNV Source # 
type Rep VkPipelineCoverageToColorStateCreateFlagsNV = D1 (MetaData "VkPipelineCoverageToColorStateCreateFlagsNV" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkPipelineCoverageToColorStateCreateFlagsNV" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkPipelineDepthStencilStateCreateFlags Source #

Instances

Bounded VkPipelineDepthStencilStateCreateFlags Source # 
Enum VkPipelineDepthStencilStateCreateFlags Source # 
Eq VkPipelineDepthStencilStateCreateFlags Source # 
Integral VkPipelineDepthStencilStateCreateFlags Source # 
Data VkPipelineDepthStencilStateCreateFlags Source # 

Methods

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

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

toConstr :: VkPipelineDepthStencilStateCreateFlags -> Constr #

dataTypeOf :: VkPipelineDepthStencilStateCreateFlags -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkPipelineDepthStencilStateCreateFlags Source # 
Ord VkPipelineDepthStencilStateCreateFlags Source # 
Read VkPipelineDepthStencilStateCreateFlags Source # 
Real VkPipelineDepthStencilStateCreateFlags Source # 
Show VkPipelineDepthStencilStateCreateFlags Source # 
Generic VkPipelineDepthStencilStateCreateFlags Source # 
Storable VkPipelineDepthStencilStateCreateFlags Source # 
Bits VkPipelineDepthStencilStateCreateFlags Source # 

Methods

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

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

xor :: VkPipelineDepthStencilStateCreateFlags -> VkPipelineDepthStencilStateCreateFlags -> VkPipelineDepthStencilStateCreateFlags #

complement :: VkPipelineDepthStencilStateCreateFlags -> VkPipelineDepthStencilStateCreateFlags #

shift :: VkPipelineDepthStencilStateCreateFlags -> Int -> VkPipelineDepthStencilStateCreateFlags #

rotate :: VkPipelineDepthStencilStateCreateFlags -> Int -> VkPipelineDepthStencilStateCreateFlags #

zeroBits :: VkPipelineDepthStencilStateCreateFlags #

bit :: Int -> VkPipelineDepthStencilStateCreateFlags #

setBit :: VkPipelineDepthStencilStateCreateFlags -> Int -> VkPipelineDepthStencilStateCreateFlags #

clearBit :: VkPipelineDepthStencilStateCreateFlags -> Int -> VkPipelineDepthStencilStateCreateFlags #

complementBit :: VkPipelineDepthStencilStateCreateFlags -> Int -> VkPipelineDepthStencilStateCreateFlags #

testBit :: VkPipelineDepthStencilStateCreateFlags -> Int -> Bool #

bitSizeMaybe :: VkPipelineDepthStencilStateCreateFlags -> Maybe Int #

bitSize :: VkPipelineDepthStencilStateCreateFlags -> Int #

isSigned :: VkPipelineDepthStencilStateCreateFlags -> Bool #

shiftL :: VkPipelineDepthStencilStateCreateFlags -> Int -> VkPipelineDepthStencilStateCreateFlags #

unsafeShiftL :: VkPipelineDepthStencilStateCreateFlags -> Int -> VkPipelineDepthStencilStateCreateFlags #

shiftR :: VkPipelineDepthStencilStateCreateFlags -> Int -> VkPipelineDepthStencilStateCreateFlags #

unsafeShiftR :: VkPipelineDepthStencilStateCreateFlags -> Int -> VkPipelineDepthStencilStateCreateFlags #

rotateL :: VkPipelineDepthStencilStateCreateFlags -> Int -> VkPipelineDepthStencilStateCreateFlags #

rotateR :: VkPipelineDepthStencilStateCreateFlags -> Int -> VkPipelineDepthStencilStateCreateFlags #

popCount :: VkPipelineDepthStencilStateCreateFlags -> Int #

FiniteBits VkPipelineDepthStencilStateCreateFlags Source # 
type Rep VkPipelineDepthStencilStateCreateFlags Source # 
type Rep VkPipelineDepthStencilStateCreateFlags = D1 (MetaData "VkPipelineDepthStencilStateCreateFlags" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkPipelineDepthStencilStateCreateFlags" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkPipelineDiscardRectangleStateCreateFlagsEXT Source #

Instances

Bounded VkPipelineDiscardRectangleStateCreateFlagsEXT Source # 
Enum VkPipelineDiscardRectangleStateCreateFlagsEXT Source # 
Eq VkPipelineDiscardRectangleStateCreateFlagsEXT Source # 
Integral VkPipelineDiscardRectangleStateCreateFlagsEXT Source # 
Data VkPipelineDiscardRectangleStateCreateFlagsEXT Source # 

Methods

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

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

toConstr :: VkPipelineDiscardRectangleStateCreateFlagsEXT -> Constr #

dataTypeOf :: VkPipelineDiscardRectangleStateCreateFlagsEXT -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkPipelineDiscardRectangleStateCreateFlagsEXT Source # 
Ord VkPipelineDiscardRectangleStateCreateFlagsEXT Source # 
Read VkPipelineDiscardRectangleStateCreateFlagsEXT Source # 
Real VkPipelineDiscardRectangleStateCreateFlagsEXT Source # 
Show VkPipelineDiscardRectangleStateCreateFlagsEXT Source # 
Generic VkPipelineDiscardRectangleStateCreateFlagsEXT Source # 
Storable VkPipelineDiscardRectangleStateCreateFlagsEXT Source # 
Bits VkPipelineDiscardRectangleStateCreateFlagsEXT Source # 

Methods

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

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

xor :: VkPipelineDiscardRectangleStateCreateFlagsEXT -> VkPipelineDiscardRectangleStateCreateFlagsEXT -> VkPipelineDiscardRectangleStateCreateFlagsEXT #

complement :: VkPipelineDiscardRectangleStateCreateFlagsEXT -> VkPipelineDiscardRectangleStateCreateFlagsEXT #

shift :: VkPipelineDiscardRectangleStateCreateFlagsEXT -> Int -> VkPipelineDiscardRectangleStateCreateFlagsEXT #

rotate :: VkPipelineDiscardRectangleStateCreateFlagsEXT -> Int -> VkPipelineDiscardRectangleStateCreateFlagsEXT #

zeroBits :: VkPipelineDiscardRectangleStateCreateFlagsEXT #

bit :: Int -> VkPipelineDiscardRectangleStateCreateFlagsEXT #

setBit :: VkPipelineDiscardRectangleStateCreateFlagsEXT -> Int -> VkPipelineDiscardRectangleStateCreateFlagsEXT #

clearBit :: VkPipelineDiscardRectangleStateCreateFlagsEXT -> Int -> VkPipelineDiscardRectangleStateCreateFlagsEXT #

complementBit :: VkPipelineDiscardRectangleStateCreateFlagsEXT -> Int -> VkPipelineDiscardRectangleStateCreateFlagsEXT #

testBit :: VkPipelineDiscardRectangleStateCreateFlagsEXT -> Int -> Bool #

bitSizeMaybe :: VkPipelineDiscardRectangleStateCreateFlagsEXT -> Maybe Int #

bitSize :: VkPipelineDiscardRectangleStateCreateFlagsEXT -> Int #

isSigned :: VkPipelineDiscardRectangleStateCreateFlagsEXT -> Bool #

shiftL :: VkPipelineDiscardRectangleStateCreateFlagsEXT -> Int -> VkPipelineDiscardRectangleStateCreateFlagsEXT #

unsafeShiftL :: VkPipelineDiscardRectangleStateCreateFlagsEXT -> Int -> VkPipelineDiscardRectangleStateCreateFlagsEXT #

shiftR :: VkPipelineDiscardRectangleStateCreateFlagsEXT -> Int -> VkPipelineDiscardRectangleStateCreateFlagsEXT #

unsafeShiftR :: VkPipelineDiscardRectangleStateCreateFlagsEXT -> Int -> VkPipelineDiscardRectangleStateCreateFlagsEXT #

rotateL :: VkPipelineDiscardRectangleStateCreateFlagsEXT -> Int -> VkPipelineDiscardRectangleStateCreateFlagsEXT #

rotateR :: VkPipelineDiscardRectangleStateCreateFlagsEXT -> Int -> VkPipelineDiscardRectangleStateCreateFlagsEXT #

popCount :: VkPipelineDiscardRectangleStateCreateFlagsEXT -> Int #

FiniteBits VkPipelineDiscardRectangleStateCreateFlagsEXT Source # 
type Rep VkPipelineDiscardRectangleStateCreateFlagsEXT Source # 
type Rep VkPipelineDiscardRectangleStateCreateFlagsEXT = D1 (MetaData "VkPipelineDiscardRectangleStateCreateFlagsEXT" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkPipelineDiscardRectangleStateCreateFlagsEXT" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkPipelineDynamicStateCreateFlags Source #

Instances

Bounded VkPipelineDynamicStateCreateFlags Source # 
Enum VkPipelineDynamicStateCreateFlags Source # 
Eq VkPipelineDynamicStateCreateFlags Source # 
Integral VkPipelineDynamicStateCreateFlags Source # 
Data VkPipelineDynamicStateCreateFlags Source # 

Methods

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

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

toConstr :: VkPipelineDynamicStateCreateFlags -> Constr #

dataTypeOf :: VkPipelineDynamicStateCreateFlags -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkPipelineDynamicStateCreateFlags Source # 
Ord VkPipelineDynamicStateCreateFlags Source # 
Read VkPipelineDynamicStateCreateFlags Source # 
Real VkPipelineDynamicStateCreateFlags Source # 
Show VkPipelineDynamicStateCreateFlags Source # 
Generic VkPipelineDynamicStateCreateFlags Source # 
Storable VkPipelineDynamicStateCreateFlags Source # 
Bits VkPipelineDynamicStateCreateFlags Source # 

Methods

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

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

xor :: VkPipelineDynamicStateCreateFlags -> VkPipelineDynamicStateCreateFlags -> VkPipelineDynamicStateCreateFlags #

complement :: VkPipelineDynamicStateCreateFlags -> VkPipelineDynamicStateCreateFlags #

shift :: VkPipelineDynamicStateCreateFlags -> Int -> VkPipelineDynamicStateCreateFlags #

rotate :: VkPipelineDynamicStateCreateFlags -> Int -> VkPipelineDynamicStateCreateFlags #

zeroBits :: VkPipelineDynamicStateCreateFlags #

bit :: Int -> VkPipelineDynamicStateCreateFlags #

setBit :: VkPipelineDynamicStateCreateFlags -> Int -> VkPipelineDynamicStateCreateFlags #

clearBit :: VkPipelineDynamicStateCreateFlags -> Int -> VkPipelineDynamicStateCreateFlags #

complementBit :: VkPipelineDynamicStateCreateFlags -> Int -> VkPipelineDynamicStateCreateFlags #

testBit :: VkPipelineDynamicStateCreateFlags -> Int -> Bool #

bitSizeMaybe :: VkPipelineDynamicStateCreateFlags -> Maybe Int #

bitSize :: VkPipelineDynamicStateCreateFlags -> Int #

isSigned :: VkPipelineDynamicStateCreateFlags -> Bool #

shiftL :: VkPipelineDynamicStateCreateFlags -> Int -> VkPipelineDynamicStateCreateFlags #

unsafeShiftL :: VkPipelineDynamicStateCreateFlags -> Int -> VkPipelineDynamicStateCreateFlags #

shiftR :: VkPipelineDynamicStateCreateFlags -> Int -> VkPipelineDynamicStateCreateFlags #

unsafeShiftR :: VkPipelineDynamicStateCreateFlags -> Int -> VkPipelineDynamicStateCreateFlags #

rotateL :: VkPipelineDynamicStateCreateFlags -> Int -> VkPipelineDynamicStateCreateFlags #

rotateR :: VkPipelineDynamicStateCreateFlags -> Int -> VkPipelineDynamicStateCreateFlags #

popCount :: VkPipelineDynamicStateCreateFlags -> Int #

FiniteBits VkPipelineDynamicStateCreateFlags Source # 
type Rep VkPipelineDynamicStateCreateFlags Source # 
type Rep VkPipelineDynamicStateCreateFlags = D1 (MetaData "VkPipelineDynamicStateCreateFlags" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkPipelineDynamicStateCreateFlags" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkPipelineInputAssemblyStateCreateFlags Source #

Instances

Bounded VkPipelineInputAssemblyStateCreateFlags Source # 
Enum VkPipelineInputAssemblyStateCreateFlags Source # 
Eq VkPipelineInputAssemblyStateCreateFlags Source # 
Integral VkPipelineInputAssemblyStateCreateFlags Source # 
Data VkPipelineInputAssemblyStateCreateFlags Source # 

Methods

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

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

toConstr :: VkPipelineInputAssemblyStateCreateFlags -> Constr #

dataTypeOf :: VkPipelineInputAssemblyStateCreateFlags -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkPipelineInputAssemblyStateCreateFlags Source # 
Ord VkPipelineInputAssemblyStateCreateFlags Source # 
Read VkPipelineInputAssemblyStateCreateFlags Source # 
Real VkPipelineInputAssemblyStateCreateFlags Source # 
Show VkPipelineInputAssemblyStateCreateFlags Source # 
Generic VkPipelineInputAssemblyStateCreateFlags Source # 
Storable VkPipelineInputAssemblyStateCreateFlags Source # 
Bits VkPipelineInputAssemblyStateCreateFlags Source # 

Methods

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

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

xor :: VkPipelineInputAssemblyStateCreateFlags -> VkPipelineInputAssemblyStateCreateFlags -> VkPipelineInputAssemblyStateCreateFlags #

complement :: VkPipelineInputAssemblyStateCreateFlags -> VkPipelineInputAssemblyStateCreateFlags #

shift :: VkPipelineInputAssemblyStateCreateFlags -> Int -> VkPipelineInputAssemblyStateCreateFlags #

rotate :: VkPipelineInputAssemblyStateCreateFlags -> Int -> VkPipelineInputAssemblyStateCreateFlags #

zeroBits :: VkPipelineInputAssemblyStateCreateFlags #

bit :: Int -> VkPipelineInputAssemblyStateCreateFlags #

setBit :: VkPipelineInputAssemblyStateCreateFlags -> Int -> VkPipelineInputAssemblyStateCreateFlags #

clearBit :: VkPipelineInputAssemblyStateCreateFlags -> Int -> VkPipelineInputAssemblyStateCreateFlags #

complementBit :: VkPipelineInputAssemblyStateCreateFlags -> Int -> VkPipelineInputAssemblyStateCreateFlags #

testBit :: VkPipelineInputAssemblyStateCreateFlags -> Int -> Bool #

bitSizeMaybe :: VkPipelineInputAssemblyStateCreateFlags -> Maybe Int #

bitSize :: VkPipelineInputAssemblyStateCreateFlags -> Int #

isSigned :: VkPipelineInputAssemblyStateCreateFlags -> Bool #

shiftL :: VkPipelineInputAssemblyStateCreateFlags -> Int -> VkPipelineInputAssemblyStateCreateFlags #

unsafeShiftL :: VkPipelineInputAssemblyStateCreateFlags -> Int -> VkPipelineInputAssemblyStateCreateFlags #

shiftR :: VkPipelineInputAssemblyStateCreateFlags -> Int -> VkPipelineInputAssemblyStateCreateFlags #

unsafeShiftR :: VkPipelineInputAssemblyStateCreateFlags -> Int -> VkPipelineInputAssemblyStateCreateFlags #

rotateL :: VkPipelineInputAssemblyStateCreateFlags -> Int -> VkPipelineInputAssemblyStateCreateFlags #

rotateR :: VkPipelineInputAssemblyStateCreateFlags -> Int -> VkPipelineInputAssemblyStateCreateFlags #

popCount :: VkPipelineInputAssemblyStateCreateFlags -> Int #

FiniteBits VkPipelineInputAssemblyStateCreateFlags Source # 
type Rep VkPipelineInputAssemblyStateCreateFlags Source # 
type Rep VkPipelineInputAssemblyStateCreateFlags = D1 (MetaData "VkPipelineInputAssemblyStateCreateFlags" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkPipelineInputAssemblyStateCreateFlags" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkPipelineLayoutCreateFlags Source #

Instances

Bounded VkPipelineLayoutCreateFlags Source # 
Enum VkPipelineLayoutCreateFlags Source # 
Eq VkPipelineLayoutCreateFlags Source # 
Integral VkPipelineLayoutCreateFlags Source # 
Data VkPipelineLayoutCreateFlags Source # 

Methods

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

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

toConstr :: VkPipelineLayoutCreateFlags -> Constr #

dataTypeOf :: VkPipelineLayoutCreateFlags -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkPipelineLayoutCreateFlags Source # 
Ord VkPipelineLayoutCreateFlags Source # 
Read VkPipelineLayoutCreateFlags Source # 
Real VkPipelineLayoutCreateFlags Source # 
Show VkPipelineLayoutCreateFlags Source # 
Generic VkPipelineLayoutCreateFlags Source # 
Storable VkPipelineLayoutCreateFlags Source # 
Bits VkPipelineLayoutCreateFlags Source # 

Methods

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

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

xor :: VkPipelineLayoutCreateFlags -> VkPipelineLayoutCreateFlags -> VkPipelineLayoutCreateFlags #

complement :: VkPipelineLayoutCreateFlags -> VkPipelineLayoutCreateFlags #

shift :: VkPipelineLayoutCreateFlags -> Int -> VkPipelineLayoutCreateFlags #

rotate :: VkPipelineLayoutCreateFlags -> Int -> VkPipelineLayoutCreateFlags #

zeroBits :: VkPipelineLayoutCreateFlags #

bit :: Int -> VkPipelineLayoutCreateFlags #

setBit :: VkPipelineLayoutCreateFlags -> Int -> VkPipelineLayoutCreateFlags #

clearBit :: VkPipelineLayoutCreateFlags -> Int -> VkPipelineLayoutCreateFlags #

complementBit :: VkPipelineLayoutCreateFlags -> Int -> VkPipelineLayoutCreateFlags #

testBit :: VkPipelineLayoutCreateFlags -> Int -> Bool #

bitSizeMaybe :: VkPipelineLayoutCreateFlags -> Maybe Int #

bitSize :: VkPipelineLayoutCreateFlags -> Int #

isSigned :: VkPipelineLayoutCreateFlags -> Bool #

shiftL :: VkPipelineLayoutCreateFlags -> Int -> VkPipelineLayoutCreateFlags #

unsafeShiftL :: VkPipelineLayoutCreateFlags -> Int -> VkPipelineLayoutCreateFlags #

shiftR :: VkPipelineLayoutCreateFlags -> Int -> VkPipelineLayoutCreateFlags #

unsafeShiftR :: VkPipelineLayoutCreateFlags -> Int -> VkPipelineLayoutCreateFlags #

rotateL :: VkPipelineLayoutCreateFlags -> Int -> VkPipelineLayoutCreateFlags #

rotateR :: VkPipelineLayoutCreateFlags -> Int -> VkPipelineLayoutCreateFlags #

popCount :: VkPipelineLayoutCreateFlags -> Int #

FiniteBits VkPipelineLayoutCreateFlags Source # 
type Rep VkPipelineLayoutCreateFlags Source # 
type Rep VkPipelineLayoutCreateFlags = D1 (MetaData "VkPipelineLayoutCreateFlags" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkPipelineLayoutCreateFlags" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkPipelineMultisampleStateCreateFlags Source #

Instances

Bounded VkPipelineMultisampleStateCreateFlags Source # 
Enum VkPipelineMultisampleStateCreateFlags Source # 
Eq VkPipelineMultisampleStateCreateFlags Source # 
Integral VkPipelineMultisampleStateCreateFlags Source # 
Data VkPipelineMultisampleStateCreateFlags Source # 

Methods

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

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

toConstr :: VkPipelineMultisampleStateCreateFlags -> Constr #

dataTypeOf :: VkPipelineMultisampleStateCreateFlags -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkPipelineMultisampleStateCreateFlags Source # 
Ord VkPipelineMultisampleStateCreateFlags Source # 
Read VkPipelineMultisampleStateCreateFlags Source # 
Real VkPipelineMultisampleStateCreateFlags Source # 
Show VkPipelineMultisampleStateCreateFlags Source # 
Generic VkPipelineMultisampleStateCreateFlags Source # 
Storable VkPipelineMultisampleStateCreateFlags Source # 
Bits VkPipelineMultisampleStateCreateFlags Source # 

Methods

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

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

xor :: VkPipelineMultisampleStateCreateFlags -> VkPipelineMultisampleStateCreateFlags -> VkPipelineMultisampleStateCreateFlags #

complement :: VkPipelineMultisampleStateCreateFlags -> VkPipelineMultisampleStateCreateFlags #

shift :: VkPipelineMultisampleStateCreateFlags -> Int -> VkPipelineMultisampleStateCreateFlags #

rotate :: VkPipelineMultisampleStateCreateFlags -> Int -> VkPipelineMultisampleStateCreateFlags #

zeroBits :: VkPipelineMultisampleStateCreateFlags #

bit :: Int -> VkPipelineMultisampleStateCreateFlags #

setBit :: VkPipelineMultisampleStateCreateFlags -> Int -> VkPipelineMultisampleStateCreateFlags #

clearBit :: VkPipelineMultisampleStateCreateFlags -> Int -> VkPipelineMultisampleStateCreateFlags #

complementBit :: VkPipelineMultisampleStateCreateFlags -> Int -> VkPipelineMultisampleStateCreateFlags #

testBit :: VkPipelineMultisampleStateCreateFlags -> Int -> Bool #

bitSizeMaybe :: VkPipelineMultisampleStateCreateFlags -> Maybe Int #

bitSize :: VkPipelineMultisampleStateCreateFlags -> Int #

isSigned :: VkPipelineMultisampleStateCreateFlags -> Bool #

shiftL :: VkPipelineMultisampleStateCreateFlags -> Int -> VkPipelineMultisampleStateCreateFlags #

unsafeShiftL :: VkPipelineMultisampleStateCreateFlags -> Int -> VkPipelineMultisampleStateCreateFlags #

shiftR :: VkPipelineMultisampleStateCreateFlags -> Int -> VkPipelineMultisampleStateCreateFlags #

unsafeShiftR :: VkPipelineMultisampleStateCreateFlags -> Int -> VkPipelineMultisampleStateCreateFlags #

rotateL :: VkPipelineMultisampleStateCreateFlags -> Int -> VkPipelineMultisampleStateCreateFlags #

rotateR :: VkPipelineMultisampleStateCreateFlags -> Int -> VkPipelineMultisampleStateCreateFlags #

popCount :: VkPipelineMultisampleStateCreateFlags -> Int #

FiniteBits VkPipelineMultisampleStateCreateFlags Source # 
type Rep VkPipelineMultisampleStateCreateFlags Source # 
type Rep VkPipelineMultisampleStateCreateFlags = D1 (MetaData "VkPipelineMultisampleStateCreateFlags" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkPipelineMultisampleStateCreateFlags" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkPipelineRasterizationConservativeStateCreateFlagsEXT Source #

Instances

Bounded VkPipelineRasterizationConservativeStateCreateFlagsEXT Source # 
Enum VkPipelineRasterizationConservativeStateCreateFlagsEXT Source # 
Eq VkPipelineRasterizationConservativeStateCreateFlagsEXT Source # 
Integral VkPipelineRasterizationConservativeStateCreateFlagsEXT Source # 
Data VkPipelineRasterizationConservativeStateCreateFlagsEXT Source # 

Methods

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

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

toConstr :: VkPipelineRasterizationConservativeStateCreateFlagsEXT -> Constr #

dataTypeOf :: VkPipelineRasterizationConservativeStateCreateFlagsEXT -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkPipelineRasterizationConservativeStateCreateFlagsEXT Source # 
Ord VkPipelineRasterizationConservativeStateCreateFlagsEXT Source # 
Read VkPipelineRasterizationConservativeStateCreateFlagsEXT Source # 
Real VkPipelineRasterizationConservativeStateCreateFlagsEXT Source # 
Show VkPipelineRasterizationConservativeStateCreateFlagsEXT Source # 
Generic VkPipelineRasterizationConservativeStateCreateFlagsEXT Source # 
Storable VkPipelineRasterizationConservativeStateCreateFlagsEXT Source # 
Bits VkPipelineRasterizationConservativeStateCreateFlagsEXT Source # 

Methods

(.&.) :: VkPipelineRasterizationConservativeStateCreateFlagsEXT -> VkPipelineRasterizationConservativeStateCreateFlagsEXT -> VkPipelineRasterizationConservativeStateCreateFlagsEXT #

(.|.) :: VkPipelineRasterizationConservativeStateCreateFlagsEXT -> VkPipelineRasterizationConservativeStateCreateFlagsEXT -> VkPipelineRasterizationConservativeStateCreateFlagsEXT #

xor :: VkPipelineRasterizationConservativeStateCreateFlagsEXT -> VkPipelineRasterizationConservativeStateCreateFlagsEXT -> VkPipelineRasterizationConservativeStateCreateFlagsEXT #

complement :: VkPipelineRasterizationConservativeStateCreateFlagsEXT -> VkPipelineRasterizationConservativeStateCreateFlagsEXT #

shift :: VkPipelineRasterizationConservativeStateCreateFlagsEXT -> Int -> VkPipelineRasterizationConservativeStateCreateFlagsEXT #

rotate :: VkPipelineRasterizationConservativeStateCreateFlagsEXT -> Int -> VkPipelineRasterizationConservativeStateCreateFlagsEXT #

zeroBits :: VkPipelineRasterizationConservativeStateCreateFlagsEXT #

bit :: Int -> VkPipelineRasterizationConservativeStateCreateFlagsEXT #

setBit :: VkPipelineRasterizationConservativeStateCreateFlagsEXT -> Int -> VkPipelineRasterizationConservativeStateCreateFlagsEXT #

clearBit :: VkPipelineRasterizationConservativeStateCreateFlagsEXT -> Int -> VkPipelineRasterizationConservativeStateCreateFlagsEXT #

complementBit :: VkPipelineRasterizationConservativeStateCreateFlagsEXT -> Int -> VkPipelineRasterizationConservativeStateCreateFlagsEXT #

testBit :: VkPipelineRasterizationConservativeStateCreateFlagsEXT -> Int -> Bool #

bitSizeMaybe :: VkPipelineRasterizationConservativeStateCreateFlagsEXT -> Maybe Int #

bitSize :: VkPipelineRasterizationConservativeStateCreateFlagsEXT -> Int #

isSigned :: VkPipelineRasterizationConservativeStateCreateFlagsEXT -> Bool #

shiftL :: VkPipelineRasterizationConservativeStateCreateFlagsEXT -> Int -> VkPipelineRasterizationConservativeStateCreateFlagsEXT #

unsafeShiftL :: VkPipelineRasterizationConservativeStateCreateFlagsEXT -> Int -> VkPipelineRasterizationConservativeStateCreateFlagsEXT #

shiftR :: VkPipelineRasterizationConservativeStateCreateFlagsEXT -> Int -> VkPipelineRasterizationConservativeStateCreateFlagsEXT #

unsafeShiftR :: VkPipelineRasterizationConservativeStateCreateFlagsEXT -> Int -> VkPipelineRasterizationConservativeStateCreateFlagsEXT #

rotateL :: VkPipelineRasterizationConservativeStateCreateFlagsEXT -> Int -> VkPipelineRasterizationConservativeStateCreateFlagsEXT #

rotateR :: VkPipelineRasterizationConservativeStateCreateFlagsEXT -> Int -> VkPipelineRasterizationConservativeStateCreateFlagsEXT #

popCount :: VkPipelineRasterizationConservativeStateCreateFlagsEXT -> Int #

FiniteBits VkPipelineRasterizationConservativeStateCreateFlagsEXT Source # 
type Rep VkPipelineRasterizationConservativeStateCreateFlagsEXT Source # 
type Rep VkPipelineRasterizationConservativeStateCreateFlagsEXT = D1 (MetaData "VkPipelineRasterizationConservativeStateCreateFlagsEXT" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkPipelineRasterizationConservativeStateCreateFlagsEXT" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkPipelineRasterizationStateCreateFlags Source #

Instances

Bounded VkPipelineRasterizationStateCreateFlags Source # 
Enum VkPipelineRasterizationStateCreateFlags Source # 
Eq VkPipelineRasterizationStateCreateFlags Source # 
Integral VkPipelineRasterizationStateCreateFlags Source # 
Data VkPipelineRasterizationStateCreateFlags Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkPipelineRasterizationStateCreateFlags -> c VkPipelineRasterizationStateCreateFlags #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkPipelineRasterizationStateCreateFlags #

toConstr :: VkPipelineRasterizationStateCreateFlags -> Constr #

dataTypeOf :: VkPipelineRasterizationStateCreateFlags -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkPipelineRasterizationStateCreateFlags) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkPipelineRasterizationStateCreateFlags) #

gmapT :: (forall b. Data b => b -> b) -> VkPipelineRasterizationStateCreateFlags -> VkPipelineRasterizationStateCreateFlags #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineRasterizationStateCreateFlags -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineRasterizationStateCreateFlags -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkPipelineRasterizationStateCreateFlags -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkPipelineRasterizationStateCreateFlags -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkPipelineRasterizationStateCreateFlags -> m VkPipelineRasterizationStateCreateFlags #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineRasterizationStateCreateFlags -> m VkPipelineRasterizationStateCreateFlags #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineRasterizationStateCreateFlags -> m VkPipelineRasterizationStateCreateFlags #

Num VkPipelineRasterizationStateCreateFlags Source # 
Ord VkPipelineRasterizationStateCreateFlags Source # 
Read VkPipelineRasterizationStateCreateFlags Source # 
Real VkPipelineRasterizationStateCreateFlags Source # 
Show VkPipelineRasterizationStateCreateFlags Source # 
Generic VkPipelineRasterizationStateCreateFlags Source # 
Storable VkPipelineRasterizationStateCreateFlags Source # 
Bits VkPipelineRasterizationStateCreateFlags Source # 

Methods

(.&.) :: VkPipelineRasterizationStateCreateFlags -> VkPipelineRasterizationStateCreateFlags -> VkPipelineRasterizationStateCreateFlags #

(.|.) :: VkPipelineRasterizationStateCreateFlags -> VkPipelineRasterizationStateCreateFlags -> VkPipelineRasterizationStateCreateFlags #

xor :: VkPipelineRasterizationStateCreateFlags -> VkPipelineRasterizationStateCreateFlags -> VkPipelineRasterizationStateCreateFlags #

complement :: VkPipelineRasterizationStateCreateFlags -> VkPipelineRasterizationStateCreateFlags #

shift :: VkPipelineRasterizationStateCreateFlags -> Int -> VkPipelineRasterizationStateCreateFlags #

rotate :: VkPipelineRasterizationStateCreateFlags -> Int -> VkPipelineRasterizationStateCreateFlags #

zeroBits :: VkPipelineRasterizationStateCreateFlags #

bit :: Int -> VkPipelineRasterizationStateCreateFlags #

setBit :: VkPipelineRasterizationStateCreateFlags -> Int -> VkPipelineRasterizationStateCreateFlags #

clearBit :: VkPipelineRasterizationStateCreateFlags -> Int -> VkPipelineRasterizationStateCreateFlags #

complementBit :: VkPipelineRasterizationStateCreateFlags -> Int -> VkPipelineRasterizationStateCreateFlags #

testBit :: VkPipelineRasterizationStateCreateFlags -> Int -> Bool #

bitSizeMaybe :: VkPipelineRasterizationStateCreateFlags -> Maybe Int #

bitSize :: VkPipelineRasterizationStateCreateFlags -> Int #

isSigned :: VkPipelineRasterizationStateCreateFlags -> Bool #

shiftL :: VkPipelineRasterizationStateCreateFlags -> Int -> VkPipelineRasterizationStateCreateFlags #

unsafeShiftL :: VkPipelineRasterizationStateCreateFlags -> Int -> VkPipelineRasterizationStateCreateFlags #

shiftR :: VkPipelineRasterizationStateCreateFlags -> Int -> VkPipelineRasterizationStateCreateFlags #

unsafeShiftR :: VkPipelineRasterizationStateCreateFlags -> Int -> VkPipelineRasterizationStateCreateFlags #

rotateL :: VkPipelineRasterizationStateCreateFlags -> Int -> VkPipelineRasterizationStateCreateFlags #

rotateR :: VkPipelineRasterizationStateCreateFlags -> Int -> VkPipelineRasterizationStateCreateFlags #

popCount :: VkPipelineRasterizationStateCreateFlags -> Int #

FiniteBits VkPipelineRasterizationStateCreateFlags Source # 
type Rep VkPipelineRasterizationStateCreateFlags Source # 
type Rep VkPipelineRasterizationStateCreateFlags = D1 (MetaData "VkPipelineRasterizationStateCreateFlags" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkPipelineRasterizationStateCreateFlags" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkPipelineShaderStageCreateFlags Source #

Instances

Bounded VkPipelineShaderStageCreateFlags Source # 
Enum VkPipelineShaderStageCreateFlags Source # 
Eq VkPipelineShaderStageCreateFlags Source # 
Integral VkPipelineShaderStageCreateFlags Source # 
Data VkPipelineShaderStageCreateFlags Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkPipelineShaderStageCreateFlags -> c VkPipelineShaderStageCreateFlags #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkPipelineShaderStageCreateFlags #

toConstr :: VkPipelineShaderStageCreateFlags -> Constr #

dataTypeOf :: VkPipelineShaderStageCreateFlags -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkPipelineShaderStageCreateFlags) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkPipelineShaderStageCreateFlags) #

gmapT :: (forall b. Data b => b -> b) -> VkPipelineShaderStageCreateFlags -> VkPipelineShaderStageCreateFlags #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineShaderStageCreateFlags -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineShaderStageCreateFlags -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkPipelineShaderStageCreateFlags -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkPipelineShaderStageCreateFlags -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkPipelineShaderStageCreateFlags -> m VkPipelineShaderStageCreateFlags #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineShaderStageCreateFlags -> m VkPipelineShaderStageCreateFlags #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineShaderStageCreateFlags -> m VkPipelineShaderStageCreateFlags #

Num VkPipelineShaderStageCreateFlags Source # 
Ord VkPipelineShaderStageCreateFlags Source # 
Read VkPipelineShaderStageCreateFlags Source # 
Real VkPipelineShaderStageCreateFlags Source # 
Show VkPipelineShaderStageCreateFlags Source # 
Generic VkPipelineShaderStageCreateFlags Source # 
Storable VkPipelineShaderStageCreateFlags Source # 
Bits VkPipelineShaderStageCreateFlags Source # 

Methods

(.&.) :: VkPipelineShaderStageCreateFlags -> VkPipelineShaderStageCreateFlags -> VkPipelineShaderStageCreateFlags #

(.|.) :: VkPipelineShaderStageCreateFlags -> VkPipelineShaderStageCreateFlags -> VkPipelineShaderStageCreateFlags #

xor :: VkPipelineShaderStageCreateFlags -> VkPipelineShaderStageCreateFlags -> VkPipelineShaderStageCreateFlags #

complement :: VkPipelineShaderStageCreateFlags -> VkPipelineShaderStageCreateFlags #

shift :: VkPipelineShaderStageCreateFlags -> Int -> VkPipelineShaderStageCreateFlags #

rotate :: VkPipelineShaderStageCreateFlags -> Int -> VkPipelineShaderStageCreateFlags #

zeroBits :: VkPipelineShaderStageCreateFlags #

bit :: Int -> VkPipelineShaderStageCreateFlags #

setBit :: VkPipelineShaderStageCreateFlags -> Int -> VkPipelineShaderStageCreateFlags #

clearBit :: VkPipelineShaderStageCreateFlags -> Int -> VkPipelineShaderStageCreateFlags #

complementBit :: VkPipelineShaderStageCreateFlags -> Int -> VkPipelineShaderStageCreateFlags #

testBit :: VkPipelineShaderStageCreateFlags -> Int -> Bool #

bitSizeMaybe :: VkPipelineShaderStageCreateFlags -> Maybe Int #

bitSize :: VkPipelineShaderStageCreateFlags -> Int #

isSigned :: VkPipelineShaderStageCreateFlags -> Bool #

shiftL :: VkPipelineShaderStageCreateFlags -> Int -> VkPipelineShaderStageCreateFlags #

unsafeShiftL :: VkPipelineShaderStageCreateFlags -> Int -> VkPipelineShaderStageCreateFlags #

shiftR :: VkPipelineShaderStageCreateFlags -> Int -> VkPipelineShaderStageCreateFlags #

unsafeShiftR :: VkPipelineShaderStageCreateFlags -> Int -> VkPipelineShaderStageCreateFlags #

rotateL :: VkPipelineShaderStageCreateFlags -> Int -> VkPipelineShaderStageCreateFlags #

rotateR :: VkPipelineShaderStageCreateFlags -> Int -> VkPipelineShaderStageCreateFlags #

popCount :: VkPipelineShaderStageCreateFlags -> Int #

FiniteBits VkPipelineShaderStageCreateFlags Source # 
type Rep VkPipelineShaderStageCreateFlags Source # 
type Rep VkPipelineShaderStageCreateFlags = D1 (MetaData "VkPipelineShaderStageCreateFlags" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkPipelineShaderStageCreateFlags" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkPipelineTessellationStateCreateFlags Source #

Instances

Bounded VkPipelineTessellationStateCreateFlags Source # 
Enum VkPipelineTessellationStateCreateFlags Source # 
Eq VkPipelineTessellationStateCreateFlags Source # 
Integral VkPipelineTessellationStateCreateFlags Source # 
Data VkPipelineTessellationStateCreateFlags Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkPipelineTessellationStateCreateFlags -> c VkPipelineTessellationStateCreateFlags #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkPipelineTessellationStateCreateFlags #

toConstr :: VkPipelineTessellationStateCreateFlags -> Constr #

dataTypeOf :: VkPipelineTessellationStateCreateFlags -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkPipelineTessellationStateCreateFlags) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkPipelineTessellationStateCreateFlags) #

gmapT :: (forall b. Data b => b -> b) -> VkPipelineTessellationStateCreateFlags -> VkPipelineTessellationStateCreateFlags #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineTessellationStateCreateFlags -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineTessellationStateCreateFlags -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkPipelineTessellationStateCreateFlags -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkPipelineTessellationStateCreateFlags -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkPipelineTessellationStateCreateFlags -> m VkPipelineTessellationStateCreateFlags #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineTessellationStateCreateFlags -> m VkPipelineTessellationStateCreateFlags #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineTessellationStateCreateFlags -> m VkPipelineTessellationStateCreateFlags #

Num VkPipelineTessellationStateCreateFlags Source # 
Ord VkPipelineTessellationStateCreateFlags Source # 
Read VkPipelineTessellationStateCreateFlags Source # 
Real VkPipelineTessellationStateCreateFlags Source # 
Show VkPipelineTessellationStateCreateFlags Source # 
Generic VkPipelineTessellationStateCreateFlags Source # 
Storable VkPipelineTessellationStateCreateFlags Source # 
Bits VkPipelineTessellationStateCreateFlags Source # 

Methods

(.&.) :: VkPipelineTessellationStateCreateFlags -> VkPipelineTessellationStateCreateFlags -> VkPipelineTessellationStateCreateFlags #

(.|.) :: VkPipelineTessellationStateCreateFlags -> VkPipelineTessellationStateCreateFlags -> VkPipelineTessellationStateCreateFlags #

xor :: VkPipelineTessellationStateCreateFlags -> VkPipelineTessellationStateCreateFlags -> VkPipelineTessellationStateCreateFlags #

complement :: VkPipelineTessellationStateCreateFlags -> VkPipelineTessellationStateCreateFlags #

shift :: VkPipelineTessellationStateCreateFlags -> Int -> VkPipelineTessellationStateCreateFlags #

rotate :: VkPipelineTessellationStateCreateFlags -> Int -> VkPipelineTessellationStateCreateFlags #

zeroBits :: VkPipelineTessellationStateCreateFlags #

bit :: Int -> VkPipelineTessellationStateCreateFlags #

setBit :: VkPipelineTessellationStateCreateFlags -> Int -> VkPipelineTessellationStateCreateFlags #

clearBit :: VkPipelineTessellationStateCreateFlags -> Int -> VkPipelineTessellationStateCreateFlags #

complementBit :: VkPipelineTessellationStateCreateFlags -> Int -> VkPipelineTessellationStateCreateFlags #

testBit :: VkPipelineTessellationStateCreateFlags -> Int -> Bool #

bitSizeMaybe :: VkPipelineTessellationStateCreateFlags -> Maybe Int #

bitSize :: VkPipelineTessellationStateCreateFlags -> Int #

isSigned :: VkPipelineTessellationStateCreateFlags -> Bool #

shiftL :: VkPipelineTessellationStateCreateFlags -> Int -> VkPipelineTessellationStateCreateFlags #

unsafeShiftL :: VkPipelineTessellationStateCreateFlags -> Int -> VkPipelineTessellationStateCreateFlags #

shiftR :: VkPipelineTessellationStateCreateFlags -> Int -> VkPipelineTessellationStateCreateFlags #

unsafeShiftR :: VkPipelineTessellationStateCreateFlags -> Int -> VkPipelineTessellationStateCreateFlags #

rotateL :: VkPipelineTessellationStateCreateFlags -> Int -> VkPipelineTessellationStateCreateFlags #

rotateR :: VkPipelineTessellationStateCreateFlags -> Int -> VkPipelineTessellationStateCreateFlags #

popCount :: VkPipelineTessellationStateCreateFlags -> Int #

FiniteBits VkPipelineTessellationStateCreateFlags Source # 
type Rep VkPipelineTessellationStateCreateFlags Source # 
type Rep VkPipelineTessellationStateCreateFlags = D1 (MetaData "VkPipelineTessellationStateCreateFlags" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkPipelineTessellationStateCreateFlags" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkPipelineVertexInputStateCreateFlags Source #

Instances

Bounded VkPipelineVertexInputStateCreateFlags Source # 
Enum VkPipelineVertexInputStateCreateFlags Source # 
Eq VkPipelineVertexInputStateCreateFlags Source # 
Integral VkPipelineVertexInputStateCreateFlags Source # 
Data VkPipelineVertexInputStateCreateFlags Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkPipelineVertexInputStateCreateFlags -> c VkPipelineVertexInputStateCreateFlags #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkPipelineVertexInputStateCreateFlags #

toConstr :: VkPipelineVertexInputStateCreateFlags -> Constr #

dataTypeOf :: VkPipelineVertexInputStateCreateFlags -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkPipelineVertexInputStateCreateFlags) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkPipelineVertexInputStateCreateFlags) #

gmapT :: (forall b. Data b => b -> b) -> VkPipelineVertexInputStateCreateFlags -> VkPipelineVertexInputStateCreateFlags #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineVertexInputStateCreateFlags -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineVertexInputStateCreateFlags -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkPipelineVertexInputStateCreateFlags -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkPipelineVertexInputStateCreateFlags -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkPipelineVertexInputStateCreateFlags -> m VkPipelineVertexInputStateCreateFlags #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineVertexInputStateCreateFlags -> m VkPipelineVertexInputStateCreateFlags #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineVertexInputStateCreateFlags -> m VkPipelineVertexInputStateCreateFlags #

Num VkPipelineVertexInputStateCreateFlags Source # 
Ord VkPipelineVertexInputStateCreateFlags Source # 
Read VkPipelineVertexInputStateCreateFlags Source # 
Real VkPipelineVertexInputStateCreateFlags Source # 
Show VkPipelineVertexInputStateCreateFlags Source # 
Generic VkPipelineVertexInputStateCreateFlags Source # 
Storable VkPipelineVertexInputStateCreateFlags Source # 
Bits VkPipelineVertexInputStateCreateFlags Source # 

Methods

(.&.) :: VkPipelineVertexInputStateCreateFlags -> VkPipelineVertexInputStateCreateFlags -> VkPipelineVertexInputStateCreateFlags #

(.|.) :: VkPipelineVertexInputStateCreateFlags -> VkPipelineVertexInputStateCreateFlags -> VkPipelineVertexInputStateCreateFlags #

xor :: VkPipelineVertexInputStateCreateFlags -> VkPipelineVertexInputStateCreateFlags -> VkPipelineVertexInputStateCreateFlags #

complement :: VkPipelineVertexInputStateCreateFlags -> VkPipelineVertexInputStateCreateFlags #

shift :: VkPipelineVertexInputStateCreateFlags -> Int -> VkPipelineVertexInputStateCreateFlags #

rotate :: VkPipelineVertexInputStateCreateFlags -> Int -> VkPipelineVertexInputStateCreateFlags #

zeroBits :: VkPipelineVertexInputStateCreateFlags #

bit :: Int -> VkPipelineVertexInputStateCreateFlags #

setBit :: VkPipelineVertexInputStateCreateFlags -> Int -> VkPipelineVertexInputStateCreateFlags #

clearBit :: VkPipelineVertexInputStateCreateFlags -> Int -> VkPipelineVertexInputStateCreateFlags #

complementBit :: VkPipelineVertexInputStateCreateFlags -> Int -> VkPipelineVertexInputStateCreateFlags #

testBit :: VkPipelineVertexInputStateCreateFlags -> Int -> Bool #

bitSizeMaybe :: VkPipelineVertexInputStateCreateFlags -> Maybe Int #

bitSize :: VkPipelineVertexInputStateCreateFlags -> Int #

isSigned :: VkPipelineVertexInputStateCreateFlags -> Bool #

shiftL :: VkPipelineVertexInputStateCreateFlags -> Int -> VkPipelineVertexInputStateCreateFlags #

unsafeShiftL :: VkPipelineVertexInputStateCreateFlags -> Int -> VkPipelineVertexInputStateCreateFlags #

shiftR :: VkPipelineVertexInputStateCreateFlags -> Int -> VkPipelineVertexInputStateCreateFlags #

unsafeShiftR :: VkPipelineVertexInputStateCreateFlags -> Int -> VkPipelineVertexInputStateCreateFlags #

rotateL :: VkPipelineVertexInputStateCreateFlags -> Int -> VkPipelineVertexInputStateCreateFlags #

rotateR :: VkPipelineVertexInputStateCreateFlags -> Int -> VkPipelineVertexInputStateCreateFlags #

popCount :: VkPipelineVertexInputStateCreateFlags -> Int #

FiniteBits VkPipelineVertexInputStateCreateFlags Source # 
type Rep VkPipelineVertexInputStateCreateFlags Source # 
type Rep VkPipelineVertexInputStateCreateFlags = D1 (MetaData "VkPipelineVertexInputStateCreateFlags" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkPipelineVertexInputStateCreateFlags" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkPipelineViewportStateCreateFlags Source #

Instances

Bounded VkPipelineViewportStateCreateFlags Source # 
Enum VkPipelineViewportStateCreateFlags Source # 
Eq VkPipelineViewportStateCreateFlags Source # 
Integral VkPipelineViewportStateCreateFlags Source # 
Data VkPipelineViewportStateCreateFlags Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkPipelineViewportStateCreateFlags -> c VkPipelineViewportStateCreateFlags #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkPipelineViewportStateCreateFlags #

toConstr :: VkPipelineViewportStateCreateFlags -> Constr #

dataTypeOf :: VkPipelineViewportStateCreateFlags -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkPipelineViewportStateCreateFlags) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkPipelineViewportStateCreateFlags) #

gmapT :: (forall b. Data b => b -> b) -> VkPipelineViewportStateCreateFlags -> VkPipelineViewportStateCreateFlags #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineViewportStateCreateFlags -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineViewportStateCreateFlags -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkPipelineViewportStateCreateFlags -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkPipelineViewportStateCreateFlags -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkPipelineViewportStateCreateFlags -> m VkPipelineViewportStateCreateFlags #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineViewportStateCreateFlags -> m VkPipelineViewportStateCreateFlags #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineViewportStateCreateFlags -> m VkPipelineViewportStateCreateFlags #

Num VkPipelineViewportStateCreateFlags Source # 
Ord VkPipelineViewportStateCreateFlags Source # 
Read VkPipelineViewportStateCreateFlags Source # 
Real VkPipelineViewportStateCreateFlags Source # 
Show VkPipelineViewportStateCreateFlags Source # 
Generic VkPipelineViewportStateCreateFlags Source # 
Storable VkPipelineViewportStateCreateFlags Source # 
Bits VkPipelineViewportStateCreateFlags Source # 

Methods

(.&.) :: VkPipelineViewportStateCreateFlags -> VkPipelineViewportStateCreateFlags -> VkPipelineViewportStateCreateFlags #

(.|.) :: VkPipelineViewportStateCreateFlags -> VkPipelineViewportStateCreateFlags -> VkPipelineViewportStateCreateFlags #

xor :: VkPipelineViewportStateCreateFlags -> VkPipelineViewportStateCreateFlags -> VkPipelineViewportStateCreateFlags #

complement :: VkPipelineViewportStateCreateFlags -> VkPipelineViewportStateCreateFlags #

shift :: VkPipelineViewportStateCreateFlags -> Int -> VkPipelineViewportStateCreateFlags #

rotate :: VkPipelineViewportStateCreateFlags -> Int -> VkPipelineViewportStateCreateFlags #

zeroBits :: VkPipelineViewportStateCreateFlags #

bit :: Int -> VkPipelineViewportStateCreateFlags #

setBit :: VkPipelineViewportStateCreateFlags -> Int -> VkPipelineViewportStateCreateFlags #

clearBit :: VkPipelineViewportStateCreateFlags -> Int -> VkPipelineViewportStateCreateFlags #

complementBit :: VkPipelineViewportStateCreateFlags -> Int -> VkPipelineViewportStateCreateFlags #

testBit :: VkPipelineViewportStateCreateFlags -> Int -> Bool #

bitSizeMaybe :: VkPipelineViewportStateCreateFlags -> Maybe Int #

bitSize :: VkPipelineViewportStateCreateFlags -> Int #

isSigned :: VkPipelineViewportStateCreateFlags -> Bool #

shiftL :: VkPipelineViewportStateCreateFlags -> Int -> VkPipelineViewportStateCreateFlags #

unsafeShiftL :: VkPipelineViewportStateCreateFlags -> Int -> VkPipelineViewportStateCreateFlags #

shiftR :: VkPipelineViewportStateCreateFlags -> Int -> VkPipelineViewportStateCreateFlags #

unsafeShiftR :: VkPipelineViewportStateCreateFlags -> Int -> VkPipelineViewportStateCreateFlags #

rotateL :: VkPipelineViewportStateCreateFlags -> Int -> VkPipelineViewportStateCreateFlags #

rotateR :: VkPipelineViewportStateCreateFlags -> Int -> VkPipelineViewportStateCreateFlags #

popCount :: VkPipelineViewportStateCreateFlags -> Int #

FiniteBits VkPipelineViewportStateCreateFlags Source # 
type Rep VkPipelineViewportStateCreateFlags Source # 
type Rep VkPipelineViewportStateCreateFlags = D1 (MetaData "VkPipelineViewportStateCreateFlags" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkPipelineViewportStateCreateFlags" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkPipelineViewportSwizzleStateCreateFlagsNV Source #

Instances

Bounded VkPipelineViewportSwizzleStateCreateFlagsNV Source # 
Enum VkPipelineViewportSwizzleStateCreateFlagsNV Source # 
Eq VkPipelineViewportSwizzleStateCreateFlagsNV Source # 
Integral VkPipelineViewportSwizzleStateCreateFlagsNV Source # 
Data VkPipelineViewportSwizzleStateCreateFlagsNV Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkPipelineViewportSwizzleStateCreateFlagsNV -> c VkPipelineViewportSwizzleStateCreateFlagsNV #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkPipelineViewportSwizzleStateCreateFlagsNV #

toConstr :: VkPipelineViewportSwizzleStateCreateFlagsNV -> Constr #

dataTypeOf :: VkPipelineViewportSwizzleStateCreateFlagsNV -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkPipelineViewportSwizzleStateCreateFlagsNV) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkPipelineViewportSwizzleStateCreateFlagsNV) #

gmapT :: (forall b. Data b => b -> b) -> VkPipelineViewportSwizzleStateCreateFlagsNV -> VkPipelineViewportSwizzleStateCreateFlagsNV #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineViewportSwizzleStateCreateFlagsNV -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineViewportSwizzleStateCreateFlagsNV -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkPipelineViewportSwizzleStateCreateFlagsNV -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkPipelineViewportSwizzleStateCreateFlagsNV -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkPipelineViewportSwizzleStateCreateFlagsNV -> m VkPipelineViewportSwizzleStateCreateFlagsNV #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineViewportSwizzleStateCreateFlagsNV -> m VkPipelineViewportSwizzleStateCreateFlagsNV #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineViewportSwizzleStateCreateFlagsNV -> m VkPipelineViewportSwizzleStateCreateFlagsNV #

Num VkPipelineViewportSwizzleStateCreateFlagsNV Source # 
Ord VkPipelineViewportSwizzleStateCreateFlagsNV Source # 
Read VkPipelineViewportSwizzleStateCreateFlagsNV Source # 
Real VkPipelineViewportSwizzleStateCreateFlagsNV Source # 
Show VkPipelineViewportSwizzleStateCreateFlagsNV Source # 
Generic VkPipelineViewportSwizzleStateCreateFlagsNV Source # 
Storable VkPipelineViewportSwizzleStateCreateFlagsNV Source # 
Bits VkPipelineViewportSwizzleStateCreateFlagsNV Source # 

Methods

(.&.) :: VkPipelineViewportSwizzleStateCreateFlagsNV -> VkPipelineViewportSwizzleStateCreateFlagsNV -> VkPipelineViewportSwizzleStateCreateFlagsNV #

(.|.) :: VkPipelineViewportSwizzleStateCreateFlagsNV -> VkPipelineViewportSwizzleStateCreateFlagsNV -> VkPipelineViewportSwizzleStateCreateFlagsNV #

xor :: VkPipelineViewportSwizzleStateCreateFlagsNV -> VkPipelineViewportSwizzleStateCreateFlagsNV -> VkPipelineViewportSwizzleStateCreateFlagsNV #

complement :: VkPipelineViewportSwizzleStateCreateFlagsNV -> VkPipelineViewportSwizzleStateCreateFlagsNV #

shift :: VkPipelineViewportSwizzleStateCreateFlagsNV -> Int -> VkPipelineViewportSwizzleStateCreateFlagsNV #

rotate :: VkPipelineViewportSwizzleStateCreateFlagsNV -> Int -> VkPipelineViewportSwizzleStateCreateFlagsNV #

zeroBits :: VkPipelineViewportSwizzleStateCreateFlagsNV #

bit :: Int -> VkPipelineViewportSwizzleStateCreateFlagsNV #

setBit :: VkPipelineViewportSwizzleStateCreateFlagsNV -> Int -> VkPipelineViewportSwizzleStateCreateFlagsNV #

clearBit :: VkPipelineViewportSwizzleStateCreateFlagsNV -> Int -> VkPipelineViewportSwizzleStateCreateFlagsNV #

complementBit :: VkPipelineViewportSwizzleStateCreateFlagsNV -> Int -> VkPipelineViewportSwizzleStateCreateFlagsNV #

testBit :: VkPipelineViewportSwizzleStateCreateFlagsNV -> Int -> Bool #

bitSizeMaybe :: VkPipelineViewportSwizzleStateCreateFlagsNV -> Maybe Int #

bitSize :: VkPipelineViewportSwizzleStateCreateFlagsNV -> Int #

isSigned :: VkPipelineViewportSwizzleStateCreateFlagsNV -> Bool #

shiftL :: VkPipelineViewportSwizzleStateCreateFlagsNV -> Int -> VkPipelineViewportSwizzleStateCreateFlagsNV #

unsafeShiftL :: VkPipelineViewportSwizzleStateCreateFlagsNV -> Int -> VkPipelineViewportSwizzleStateCreateFlagsNV #

shiftR :: VkPipelineViewportSwizzleStateCreateFlagsNV -> Int -> VkPipelineViewportSwizzleStateCreateFlagsNV #

unsafeShiftR :: VkPipelineViewportSwizzleStateCreateFlagsNV -> Int -> VkPipelineViewportSwizzleStateCreateFlagsNV #

rotateL :: VkPipelineViewportSwizzleStateCreateFlagsNV -> Int -> VkPipelineViewportSwizzleStateCreateFlagsNV #

rotateR :: VkPipelineViewportSwizzleStateCreateFlagsNV -> Int -> VkPipelineViewportSwizzleStateCreateFlagsNV #

popCount :: VkPipelineViewportSwizzleStateCreateFlagsNV -> Int #

FiniteBits VkPipelineViewportSwizzleStateCreateFlagsNV Source # 
type Rep VkPipelineViewportSwizzleStateCreateFlagsNV Source # 
type Rep VkPipelineViewportSwizzleStateCreateFlagsNV = D1 (MetaData "VkPipelineViewportSwizzleStateCreateFlagsNV" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkPipelineViewportSwizzleStateCreateFlagsNV" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkQueryPoolCreateFlags Source #

Instances

Bounded VkQueryPoolCreateFlags Source # 
Enum VkQueryPoolCreateFlags Source # 
Eq VkQueryPoolCreateFlags Source # 
Integral VkQueryPoolCreateFlags Source # 
Data VkQueryPoolCreateFlags Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkQueryPoolCreateFlags -> c VkQueryPoolCreateFlags #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkQueryPoolCreateFlags #

toConstr :: VkQueryPoolCreateFlags -> Constr #

dataTypeOf :: VkQueryPoolCreateFlags -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkQueryPoolCreateFlags) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkQueryPoolCreateFlags) #

gmapT :: (forall b. Data b => b -> b) -> VkQueryPoolCreateFlags -> VkQueryPoolCreateFlags #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkQueryPoolCreateFlags -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkQueryPoolCreateFlags -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkQueryPoolCreateFlags -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkQueryPoolCreateFlags -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkQueryPoolCreateFlags -> m VkQueryPoolCreateFlags #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkQueryPoolCreateFlags -> m VkQueryPoolCreateFlags #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkQueryPoolCreateFlags -> m VkQueryPoolCreateFlags #

Num VkQueryPoolCreateFlags Source # 
Ord VkQueryPoolCreateFlags Source # 
Read VkQueryPoolCreateFlags Source # 
Real VkQueryPoolCreateFlags Source # 
Show VkQueryPoolCreateFlags Source # 
Generic VkQueryPoolCreateFlags Source # 
Storable VkQueryPoolCreateFlags Source # 
Bits VkQueryPoolCreateFlags Source # 
FiniteBits VkQueryPoolCreateFlags Source # 
type Rep VkQueryPoolCreateFlags Source # 
type Rep VkQueryPoolCreateFlags = D1 (MetaData "VkQueryPoolCreateFlags" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkQueryPoolCreateFlags" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkRenderPassCreateFlags Source #

Instances

Bounded VkRenderPassCreateFlags Source # 
Enum VkRenderPassCreateFlags Source # 
Eq VkRenderPassCreateFlags Source # 
Integral VkRenderPassCreateFlags Source # 
Data VkRenderPassCreateFlags Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkRenderPassCreateFlags -> c VkRenderPassCreateFlags #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkRenderPassCreateFlags #

toConstr :: VkRenderPassCreateFlags -> Constr #

dataTypeOf :: VkRenderPassCreateFlags -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkRenderPassCreateFlags) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkRenderPassCreateFlags) #

gmapT :: (forall b. Data b => b -> b) -> VkRenderPassCreateFlags -> VkRenderPassCreateFlags #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkRenderPassCreateFlags -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkRenderPassCreateFlags -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkRenderPassCreateFlags -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkRenderPassCreateFlags -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkRenderPassCreateFlags -> m VkRenderPassCreateFlags #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkRenderPassCreateFlags -> m VkRenderPassCreateFlags #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkRenderPassCreateFlags -> m VkRenderPassCreateFlags #

Num VkRenderPassCreateFlags Source # 
Ord VkRenderPassCreateFlags Source # 
Read VkRenderPassCreateFlags Source # 
Real VkRenderPassCreateFlags Source # 
Show VkRenderPassCreateFlags Source # 
Generic VkRenderPassCreateFlags Source # 
Storable VkRenderPassCreateFlags Source # 
Bits VkRenderPassCreateFlags Source # 
FiniteBits VkRenderPassCreateFlags Source # 
type Rep VkRenderPassCreateFlags Source # 
type Rep VkRenderPassCreateFlags = D1 (MetaData "VkRenderPassCreateFlags" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkRenderPassCreateFlags" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkSamplerCreateFlags Source #

Instances

Bounded VkSamplerCreateFlags Source # 
Enum VkSamplerCreateFlags Source # 
Eq VkSamplerCreateFlags Source # 
Integral VkSamplerCreateFlags Source # 
Data VkSamplerCreateFlags Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkSamplerCreateFlags -> c VkSamplerCreateFlags #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkSamplerCreateFlags #

toConstr :: VkSamplerCreateFlags -> Constr #

dataTypeOf :: VkSamplerCreateFlags -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkSamplerCreateFlags) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkSamplerCreateFlags) #

gmapT :: (forall b. Data b => b -> b) -> VkSamplerCreateFlags -> VkSamplerCreateFlags #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkSamplerCreateFlags -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkSamplerCreateFlags -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkSamplerCreateFlags -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkSamplerCreateFlags -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkSamplerCreateFlags -> m VkSamplerCreateFlags #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSamplerCreateFlags -> m VkSamplerCreateFlags #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSamplerCreateFlags -> m VkSamplerCreateFlags #

Num VkSamplerCreateFlags Source # 
Ord VkSamplerCreateFlags Source # 
Read VkSamplerCreateFlags Source # 
Real VkSamplerCreateFlags Source # 
Show VkSamplerCreateFlags Source # 
Generic VkSamplerCreateFlags Source # 
Storable VkSamplerCreateFlags Source # 
Bits VkSamplerCreateFlags Source # 
FiniteBits VkSamplerCreateFlags Source # 
type Rep VkSamplerCreateFlags Source # 
type Rep VkSamplerCreateFlags = D1 (MetaData "VkSamplerCreateFlags" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkSamplerCreateFlags" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkSemaphoreCreateFlags Source #

Instances

Bounded VkSemaphoreCreateFlags Source # 
Enum VkSemaphoreCreateFlags Source # 
Eq VkSemaphoreCreateFlags Source # 
Integral VkSemaphoreCreateFlags Source # 
Data VkSemaphoreCreateFlags Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkSemaphoreCreateFlags -> c VkSemaphoreCreateFlags #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkSemaphoreCreateFlags #

toConstr :: VkSemaphoreCreateFlags -> Constr #

dataTypeOf :: VkSemaphoreCreateFlags -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkSemaphoreCreateFlags) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkSemaphoreCreateFlags) #

gmapT :: (forall b. Data b => b -> b) -> VkSemaphoreCreateFlags -> VkSemaphoreCreateFlags #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkSemaphoreCreateFlags -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkSemaphoreCreateFlags -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkSemaphoreCreateFlags -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkSemaphoreCreateFlags -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkSemaphoreCreateFlags -> m VkSemaphoreCreateFlags #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSemaphoreCreateFlags -> m VkSemaphoreCreateFlags #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSemaphoreCreateFlags -> m VkSemaphoreCreateFlags #

Num VkSemaphoreCreateFlags Source # 
Ord VkSemaphoreCreateFlags Source # 
Read VkSemaphoreCreateFlags Source # 
Real VkSemaphoreCreateFlags Source # 
Show VkSemaphoreCreateFlags Source # 
Generic VkSemaphoreCreateFlags Source # 
Storable VkSemaphoreCreateFlags Source # 
Bits VkSemaphoreCreateFlags Source # 
FiniteBits VkSemaphoreCreateFlags Source # 
type Rep VkSemaphoreCreateFlags Source # 
type Rep VkSemaphoreCreateFlags = D1 (MetaData "VkSemaphoreCreateFlags" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkSemaphoreCreateFlags" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkSemaphoreImportFlagsKHR Source #

Instances

Bounded VkSemaphoreImportFlagsKHR Source # 
Enum VkSemaphoreImportFlagsKHR Source # 
Eq VkSemaphoreImportFlagsKHR Source # 
Integral VkSemaphoreImportFlagsKHR Source # 
Data VkSemaphoreImportFlagsKHR Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkSemaphoreImportFlagsKHR -> c VkSemaphoreImportFlagsKHR #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkSemaphoreImportFlagsKHR #

toConstr :: VkSemaphoreImportFlagsKHR -> Constr #

dataTypeOf :: VkSemaphoreImportFlagsKHR -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkSemaphoreImportFlagsKHR) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkSemaphoreImportFlagsKHR) #

gmapT :: (forall b. Data b => b -> b) -> VkSemaphoreImportFlagsKHR -> VkSemaphoreImportFlagsKHR #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkSemaphoreImportFlagsKHR -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkSemaphoreImportFlagsKHR -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkSemaphoreImportFlagsKHR -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkSemaphoreImportFlagsKHR -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkSemaphoreImportFlagsKHR -> m VkSemaphoreImportFlagsKHR #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSemaphoreImportFlagsKHR -> m VkSemaphoreImportFlagsKHR #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSemaphoreImportFlagsKHR -> m VkSemaphoreImportFlagsKHR #

Num VkSemaphoreImportFlagsKHR Source # 
Ord VkSemaphoreImportFlagsKHR Source # 
Read VkSemaphoreImportFlagsKHR Source # 
Real VkSemaphoreImportFlagsKHR Source # 
Show VkSemaphoreImportFlagsKHR Source # 
Generic VkSemaphoreImportFlagsKHR Source # 
Storable VkSemaphoreImportFlagsKHR Source # 
Bits VkSemaphoreImportFlagsKHR Source # 

Methods

(.&.) :: VkSemaphoreImportFlagsKHR -> VkSemaphoreImportFlagsKHR -> VkSemaphoreImportFlagsKHR #

(.|.) :: VkSemaphoreImportFlagsKHR -> VkSemaphoreImportFlagsKHR -> VkSemaphoreImportFlagsKHR #

xor :: VkSemaphoreImportFlagsKHR -> VkSemaphoreImportFlagsKHR -> VkSemaphoreImportFlagsKHR #

complement :: VkSemaphoreImportFlagsKHR -> VkSemaphoreImportFlagsKHR #

shift :: VkSemaphoreImportFlagsKHR -> Int -> VkSemaphoreImportFlagsKHR #

rotate :: VkSemaphoreImportFlagsKHR -> Int -> VkSemaphoreImportFlagsKHR #

zeroBits :: VkSemaphoreImportFlagsKHR #

bit :: Int -> VkSemaphoreImportFlagsKHR #

setBit :: VkSemaphoreImportFlagsKHR -> Int -> VkSemaphoreImportFlagsKHR #

clearBit :: VkSemaphoreImportFlagsKHR -> Int -> VkSemaphoreImportFlagsKHR #

complementBit :: VkSemaphoreImportFlagsKHR -> Int -> VkSemaphoreImportFlagsKHR #

testBit :: VkSemaphoreImportFlagsKHR -> Int -> Bool #

bitSizeMaybe :: VkSemaphoreImportFlagsKHR -> Maybe Int #

bitSize :: VkSemaphoreImportFlagsKHR -> Int #

isSigned :: VkSemaphoreImportFlagsKHR -> Bool #

shiftL :: VkSemaphoreImportFlagsKHR -> Int -> VkSemaphoreImportFlagsKHR #

unsafeShiftL :: VkSemaphoreImportFlagsKHR -> Int -> VkSemaphoreImportFlagsKHR #

shiftR :: VkSemaphoreImportFlagsKHR -> Int -> VkSemaphoreImportFlagsKHR #

unsafeShiftR :: VkSemaphoreImportFlagsKHR -> Int -> VkSemaphoreImportFlagsKHR #

rotateL :: VkSemaphoreImportFlagsKHR -> Int -> VkSemaphoreImportFlagsKHR #

rotateR :: VkSemaphoreImportFlagsKHR -> Int -> VkSemaphoreImportFlagsKHR #

popCount :: VkSemaphoreImportFlagsKHR -> Int #

FiniteBits VkSemaphoreImportFlagsKHR Source # 
type Rep VkSemaphoreImportFlagsKHR Source # 
type Rep VkSemaphoreImportFlagsKHR = D1 (MetaData "VkSemaphoreImportFlagsKHR" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkSemaphoreImportFlagsKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkShaderModuleCreateFlags Source #

Instances

Bounded VkShaderModuleCreateFlags Source # 
Enum VkShaderModuleCreateFlags Source # 
Eq VkShaderModuleCreateFlags Source # 
Integral VkShaderModuleCreateFlags Source # 
Data VkShaderModuleCreateFlags Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkShaderModuleCreateFlags -> c VkShaderModuleCreateFlags #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkShaderModuleCreateFlags #

toConstr :: VkShaderModuleCreateFlags -> Constr #

dataTypeOf :: VkShaderModuleCreateFlags -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkShaderModuleCreateFlags) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkShaderModuleCreateFlags) #

gmapT :: (forall b. Data b => b -> b) -> VkShaderModuleCreateFlags -> VkShaderModuleCreateFlags #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkShaderModuleCreateFlags -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkShaderModuleCreateFlags -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkShaderModuleCreateFlags -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkShaderModuleCreateFlags -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkShaderModuleCreateFlags -> m VkShaderModuleCreateFlags #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkShaderModuleCreateFlags -> m VkShaderModuleCreateFlags #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkShaderModuleCreateFlags -> m VkShaderModuleCreateFlags #

Num VkShaderModuleCreateFlags Source # 
Ord VkShaderModuleCreateFlags Source # 
Read VkShaderModuleCreateFlags Source # 
Real VkShaderModuleCreateFlags Source # 
Show VkShaderModuleCreateFlags Source # 
Generic VkShaderModuleCreateFlags Source # 
Storable VkShaderModuleCreateFlags Source # 
Bits VkShaderModuleCreateFlags Source # 

Methods

(.&.) :: VkShaderModuleCreateFlags -> VkShaderModuleCreateFlags -> VkShaderModuleCreateFlags #

(.|.) :: VkShaderModuleCreateFlags -> VkShaderModuleCreateFlags -> VkShaderModuleCreateFlags #

xor :: VkShaderModuleCreateFlags -> VkShaderModuleCreateFlags -> VkShaderModuleCreateFlags #

complement :: VkShaderModuleCreateFlags -> VkShaderModuleCreateFlags #

shift :: VkShaderModuleCreateFlags -> Int -> VkShaderModuleCreateFlags #

rotate :: VkShaderModuleCreateFlags -> Int -> VkShaderModuleCreateFlags #

zeroBits :: VkShaderModuleCreateFlags #

bit :: Int -> VkShaderModuleCreateFlags #

setBit :: VkShaderModuleCreateFlags -> Int -> VkShaderModuleCreateFlags #

clearBit :: VkShaderModuleCreateFlags -> Int -> VkShaderModuleCreateFlags #

complementBit :: VkShaderModuleCreateFlags -> Int -> VkShaderModuleCreateFlags #

testBit :: VkShaderModuleCreateFlags -> Int -> Bool #

bitSizeMaybe :: VkShaderModuleCreateFlags -> Maybe Int #

bitSize :: VkShaderModuleCreateFlags -> Int #

isSigned :: VkShaderModuleCreateFlags -> Bool #

shiftL :: VkShaderModuleCreateFlags -> Int -> VkShaderModuleCreateFlags #

unsafeShiftL :: VkShaderModuleCreateFlags -> Int -> VkShaderModuleCreateFlags #

shiftR :: VkShaderModuleCreateFlags -> Int -> VkShaderModuleCreateFlags #

unsafeShiftR :: VkShaderModuleCreateFlags -> Int -> VkShaderModuleCreateFlags #

rotateL :: VkShaderModuleCreateFlags -> Int -> VkShaderModuleCreateFlags #

rotateR :: VkShaderModuleCreateFlags -> Int -> VkShaderModuleCreateFlags #

popCount :: VkShaderModuleCreateFlags -> Int #

FiniteBits VkShaderModuleCreateFlags Source # 
type Rep VkShaderModuleCreateFlags Source # 
type Rep VkShaderModuleCreateFlags = D1 (MetaData "VkShaderModuleCreateFlags" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkShaderModuleCreateFlags" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkValidationCacheCreateFlagsEXT Source #

Instances

Bounded VkValidationCacheCreateFlagsEXT Source # 
Enum VkValidationCacheCreateFlagsEXT Source # 
Eq VkValidationCacheCreateFlagsEXT Source # 
Integral VkValidationCacheCreateFlagsEXT Source # 
Data VkValidationCacheCreateFlagsEXT Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkValidationCacheCreateFlagsEXT -> c VkValidationCacheCreateFlagsEXT #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkValidationCacheCreateFlagsEXT #

toConstr :: VkValidationCacheCreateFlagsEXT -> Constr #

dataTypeOf :: VkValidationCacheCreateFlagsEXT -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkValidationCacheCreateFlagsEXT) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkValidationCacheCreateFlagsEXT) #

gmapT :: (forall b. Data b => b -> b) -> VkValidationCacheCreateFlagsEXT -> VkValidationCacheCreateFlagsEXT #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkValidationCacheCreateFlagsEXT -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkValidationCacheCreateFlagsEXT -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkValidationCacheCreateFlagsEXT -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkValidationCacheCreateFlagsEXT -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkValidationCacheCreateFlagsEXT -> m VkValidationCacheCreateFlagsEXT #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkValidationCacheCreateFlagsEXT -> m VkValidationCacheCreateFlagsEXT #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkValidationCacheCreateFlagsEXT -> m VkValidationCacheCreateFlagsEXT #

Num VkValidationCacheCreateFlagsEXT Source # 
Ord VkValidationCacheCreateFlagsEXT Source # 
Read VkValidationCacheCreateFlagsEXT Source # 
Real VkValidationCacheCreateFlagsEXT Source # 
Show VkValidationCacheCreateFlagsEXT Source # 
Generic VkValidationCacheCreateFlagsEXT Source # 
Storable VkValidationCacheCreateFlagsEXT Source # 
Bits VkValidationCacheCreateFlagsEXT Source # 

Methods

(.&.) :: VkValidationCacheCreateFlagsEXT -> VkValidationCacheCreateFlagsEXT -> VkValidationCacheCreateFlagsEXT #

(.|.) :: VkValidationCacheCreateFlagsEXT -> VkValidationCacheCreateFlagsEXT -> VkValidationCacheCreateFlagsEXT #

xor :: VkValidationCacheCreateFlagsEXT -> VkValidationCacheCreateFlagsEXT -> VkValidationCacheCreateFlagsEXT #

complement :: VkValidationCacheCreateFlagsEXT -> VkValidationCacheCreateFlagsEXT #

shift :: VkValidationCacheCreateFlagsEXT -> Int -> VkValidationCacheCreateFlagsEXT #

rotate :: VkValidationCacheCreateFlagsEXT -> Int -> VkValidationCacheCreateFlagsEXT #

zeroBits :: VkValidationCacheCreateFlagsEXT #

bit :: Int -> VkValidationCacheCreateFlagsEXT #

setBit :: VkValidationCacheCreateFlagsEXT -> Int -> VkValidationCacheCreateFlagsEXT #

clearBit :: VkValidationCacheCreateFlagsEXT -> Int -> VkValidationCacheCreateFlagsEXT #

complementBit :: VkValidationCacheCreateFlagsEXT -> Int -> VkValidationCacheCreateFlagsEXT #

testBit :: VkValidationCacheCreateFlagsEXT -> Int -> Bool #

bitSizeMaybe :: VkValidationCacheCreateFlagsEXT -> Maybe Int #

bitSize :: VkValidationCacheCreateFlagsEXT -> Int #

isSigned :: VkValidationCacheCreateFlagsEXT -> Bool #

shiftL :: VkValidationCacheCreateFlagsEXT -> Int -> VkValidationCacheCreateFlagsEXT #

unsafeShiftL :: VkValidationCacheCreateFlagsEXT -> Int -> VkValidationCacheCreateFlagsEXT #

shiftR :: VkValidationCacheCreateFlagsEXT -> Int -> VkValidationCacheCreateFlagsEXT #

unsafeShiftR :: VkValidationCacheCreateFlagsEXT -> Int -> VkValidationCacheCreateFlagsEXT #

rotateL :: VkValidationCacheCreateFlagsEXT -> Int -> VkValidationCacheCreateFlagsEXT #

rotateR :: VkValidationCacheCreateFlagsEXT -> Int -> VkValidationCacheCreateFlagsEXT #

popCount :: VkValidationCacheCreateFlagsEXT -> Int #

FiniteBits VkValidationCacheCreateFlagsEXT Source # 
type Rep VkValidationCacheCreateFlagsEXT Source # 
type Rep VkValidationCacheCreateFlagsEXT = D1 (MetaData "VkValidationCacheCreateFlagsEXT" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkValidationCacheCreateFlagsEXT" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkViSurfaceCreateFlagsNN Source #

Instances

Bounded VkViSurfaceCreateFlagsNN Source # 
Enum VkViSurfaceCreateFlagsNN Source # 
Eq VkViSurfaceCreateFlagsNN Source # 
Integral VkViSurfaceCreateFlagsNN Source # 
Data VkViSurfaceCreateFlagsNN Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkViSurfaceCreateFlagsNN -> c VkViSurfaceCreateFlagsNN #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkViSurfaceCreateFlagsNN #

toConstr :: VkViSurfaceCreateFlagsNN -> Constr #

dataTypeOf :: VkViSurfaceCreateFlagsNN -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkViSurfaceCreateFlagsNN) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkViSurfaceCreateFlagsNN) #

gmapT :: (forall b. Data b => b -> b) -> VkViSurfaceCreateFlagsNN -> VkViSurfaceCreateFlagsNN #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkViSurfaceCreateFlagsNN -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkViSurfaceCreateFlagsNN -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkViSurfaceCreateFlagsNN -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkViSurfaceCreateFlagsNN -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkViSurfaceCreateFlagsNN -> m VkViSurfaceCreateFlagsNN #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkViSurfaceCreateFlagsNN -> m VkViSurfaceCreateFlagsNN #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkViSurfaceCreateFlagsNN -> m VkViSurfaceCreateFlagsNN #

Num VkViSurfaceCreateFlagsNN Source # 
Ord VkViSurfaceCreateFlagsNN Source # 
Read VkViSurfaceCreateFlagsNN Source # 
Real VkViSurfaceCreateFlagsNN Source # 
Show VkViSurfaceCreateFlagsNN Source # 
Generic VkViSurfaceCreateFlagsNN Source # 
Storable VkViSurfaceCreateFlagsNN Source # 
Bits VkViSurfaceCreateFlagsNN Source # 
FiniteBits VkViSurfaceCreateFlagsNN Source # 
type Rep VkViSurfaceCreateFlagsNN Source # 
type Rep VkViSurfaceCreateFlagsNN = D1 (MetaData "VkViSurfaceCreateFlagsNN" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkViSurfaceCreateFlagsNN" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkWaylandSurfaceCreateFlagsKHR Source #

Instances

Bounded VkWaylandSurfaceCreateFlagsKHR Source # 
Enum VkWaylandSurfaceCreateFlagsKHR Source # 
Eq VkWaylandSurfaceCreateFlagsKHR Source # 
Integral VkWaylandSurfaceCreateFlagsKHR Source # 
Data VkWaylandSurfaceCreateFlagsKHR Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkWaylandSurfaceCreateFlagsKHR -> c VkWaylandSurfaceCreateFlagsKHR #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkWaylandSurfaceCreateFlagsKHR #

toConstr :: VkWaylandSurfaceCreateFlagsKHR -> Constr #

dataTypeOf :: VkWaylandSurfaceCreateFlagsKHR -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkWaylandSurfaceCreateFlagsKHR) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkWaylandSurfaceCreateFlagsKHR) #

gmapT :: (forall b. Data b => b -> b) -> VkWaylandSurfaceCreateFlagsKHR -> VkWaylandSurfaceCreateFlagsKHR #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkWaylandSurfaceCreateFlagsKHR -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkWaylandSurfaceCreateFlagsKHR -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkWaylandSurfaceCreateFlagsKHR -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkWaylandSurfaceCreateFlagsKHR -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkWaylandSurfaceCreateFlagsKHR -> m VkWaylandSurfaceCreateFlagsKHR #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkWaylandSurfaceCreateFlagsKHR -> m VkWaylandSurfaceCreateFlagsKHR #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkWaylandSurfaceCreateFlagsKHR -> m VkWaylandSurfaceCreateFlagsKHR #

Num VkWaylandSurfaceCreateFlagsKHR Source # 
Ord VkWaylandSurfaceCreateFlagsKHR Source # 
Read VkWaylandSurfaceCreateFlagsKHR Source # 
Real VkWaylandSurfaceCreateFlagsKHR Source # 
Show VkWaylandSurfaceCreateFlagsKHR Source # 
Generic VkWaylandSurfaceCreateFlagsKHR Source # 
Storable VkWaylandSurfaceCreateFlagsKHR Source # 
Bits VkWaylandSurfaceCreateFlagsKHR Source # 

Methods

(.&.) :: VkWaylandSurfaceCreateFlagsKHR -> VkWaylandSurfaceCreateFlagsKHR -> VkWaylandSurfaceCreateFlagsKHR #

(.|.) :: VkWaylandSurfaceCreateFlagsKHR -> VkWaylandSurfaceCreateFlagsKHR -> VkWaylandSurfaceCreateFlagsKHR #

xor :: VkWaylandSurfaceCreateFlagsKHR -> VkWaylandSurfaceCreateFlagsKHR -> VkWaylandSurfaceCreateFlagsKHR #

complement :: VkWaylandSurfaceCreateFlagsKHR -> VkWaylandSurfaceCreateFlagsKHR #

shift :: VkWaylandSurfaceCreateFlagsKHR -> Int -> VkWaylandSurfaceCreateFlagsKHR #

rotate :: VkWaylandSurfaceCreateFlagsKHR -> Int -> VkWaylandSurfaceCreateFlagsKHR #

zeroBits :: VkWaylandSurfaceCreateFlagsKHR #

bit :: Int -> VkWaylandSurfaceCreateFlagsKHR #

setBit :: VkWaylandSurfaceCreateFlagsKHR -> Int -> VkWaylandSurfaceCreateFlagsKHR #

clearBit :: VkWaylandSurfaceCreateFlagsKHR -> Int -> VkWaylandSurfaceCreateFlagsKHR #

complementBit :: VkWaylandSurfaceCreateFlagsKHR -> Int -> VkWaylandSurfaceCreateFlagsKHR #

testBit :: VkWaylandSurfaceCreateFlagsKHR -> Int -> Bool #

bitSizeMaybe :: VkWaylandSurfaceCreateFlagsKHR -> Maybe Int #

bitSize :: VkWaylandSurfaceCreateFlagsKHR -> Int #

isSigned :: VkWaylandSurfaceCreateFlagsKHR -> Bool #

shiftL :: VkWaylandSurfaceCreateFlagsKHR -> Int -> VkWaylandSurfaceCreateFlagsKHR #

unsafeShiftL :: VkWaylandSurfaceCreateFlagsKHR -> Int -> VkWaylandSurfaceCreateFlagsKHR #

shiftR :: VkWaylandSurfaceCreateFlagsKHR -> Int -> VkWaylandSurfaceCreateFlagsKHR #

unsafeShiftR :: VkWaylandSurfaceCreateFlagsKHR -> Int -> VkWaylandSurfaceCreateFlagsKHR #

rotateL :: VkWaylandSurfaceCreateFlagsKHR -> Int -> VkWaylandSurfaceCreateFlagsKHR #

rotateR :: VkWaylandSurfaceCreateFlagsKHR -> Int -> VkWaylandSurfaceCreateFlagsKHR #

popCount :: VkWaylandSurfaceCreateFlagsKHR -> Int #

FiniteBits VkWaylandSurfaceCreateFlagsKHR Source # 
type Rep VkWaylandSurfaceCreateFlagsKHR Source # 
type Rep VkWaylandSurfaceCreateFlagsKHR = D1 (MetaData "VkWaylandSurfaceCreateFlagsKHR" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkWaylandSurfaceCreateFlagsKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkWin32SurfaceCreateFlagsKHR Source #

Instances

Bounded VkWin32SurfaceCreateFlagsKHR Source # 
Enum VkWin32SurfaceCreateFlagsKHR Source # 
Eq VkWin32SurfaceCreateFlagsKHR Source # 
Integral VkWin32SurfaceCreateFlagsKHR Source # 
Data VkWin32SurfaceCreateFlagsKHR Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkWin32SurfaceCreateFlagsKHR -> c VkWin32SurfaceCreateFlagsKHR #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkWin32SurfaceCreateFlagsKHR #

toConstr :: VkWin32SurfaceCreateFlagsKHR -> Constr #

dataTypeOf :: VkWin32SurfaceCreateFlagsKHR -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkWin32SurfaceCreateFlagsKHR) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkWin32SurfaceCreateFlagsKHR) #

gmapT :: (forall b. Data b => b -> b) -> VkWin32SurfaceCreateFlagsKHR -> VkWin32SurfaceCreateFlagsKHR #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkWin32SurfaceCreateFlagsKHR -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkWin32SurfaceCreateFlagsKHR -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkWin32SurfaceCreateFlagsKHR -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkWin32SurfaceCreateFlagsKHR -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkWin32SurfaceCreateFlagsKHR -> m VkWin32SurfaceCreateFlagsKHR #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkWin32SurfaceCreateFlagsKHR -> m VkWin32SurfaceCreateFlagsKHR #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkWin32SurfaceCreateFlagsKHR -> m VkWin32SurfaceCreateFlagsKHR #

Num VkWin32SurfaceCreateFlagsKHR Source # 
Ord VkWin32SurfaceCreateFlagsKHR Source # 
Read VkWin32SurfaceCreateFlagsKHR Source # 
Real VkWin32SurfaceCreateFlagsKHR Source # 
Show VkWin32SurfaceCreateFlagsKHR Source # 
Generic VkWin32SurfaceCreateFlagsKHR Source # 
Storable VkWin32SurfaceCreateFlagsKHR Source # 
Bits VkWin32SurfaceCreateFlagsKHR Source # 

Methods

(.&.) :: VkWin32SurfaceCreateFlagsKHR -> VkWin32SurfaceCreateFlagsKHR -> VkWin32SurfaceCreateFlagsKHR #

(.|.) :: VkWin32SurfaceCreateFlagsKHR -> VkWin32SurfaceCreateFlagsKHR -> VkWin32SurfaceCreateFlagsKHR #

xor :: VkWin32SurfaceCreateFlagsKHR -> VkWin32SurfaceCreateFlagsKHR -> VkWin32SurfaceCreateFlagsKHR #

complement :: VkWin32SurfaceCreateFlagsKHR -> VkWin32SurfaceCreateFlagsKHR #

shift :: VkWin32SurfaceCreateFlagsKHR -> Int -> VkWin32SurfaceCreateFlagsKHR #

rotate :: VkWin32SurfaceCreateFlagsKHR -> Int -> VkWin32SurfaceCreateFlagsKHR #

zeroBits :: VkWin32SurfaceCreateFlagsKHR #

bit :: Int -> VkWin32SurfaceCreateFlagsKHR #

setBit :: VkWin32SurfaceCreateFlagsKHR -> Int -> VkWin32SurfaceCreateFlagsKHR #

clearBit :: VkWin32SurfaceCreateFlagsKHR -> Int -> VkWin32SurfaceCreateFlagsKHR #

complementBit :: VkWin32SurfaceCreateFlagsKHR -> Int -> VkWin32SurfaceCreateFlagsKHR #

testBit :: VkWin32SurfaceCreateFlagsKHR -> Int -> Bool #

bitSizeMaybe :: VkWin32SurfaceCreateFlagsKHR -> Maybe Int #

bitSize :: VkWin32SurfaceCreateFlagsKHR -> Int #

isSigned :: VkWin32SurfaceCreateFlagsKHR -> Bool #

shiftL :: VkWin32SurfaceCreateFlagsKHR -> Int -> VkWin32SurfaceCreateFlagsKHR #

unsafeShiftL :: VkWin32SurfaceCreateFlagsKHR -> Int -> VkWin32SurfaceCreateFlagsKHR #

shiftR :: VkWin32SurfaceCreateFlagsKHR -> Int -> VkWin32SurfaceCreateFlagsKHR #

unsafeShiftR :: VkWin32SurfaceCreateFlagsKHR -> Int -> VkWin32SurfaceCreateFlagsKHR #

rotateL :: VkWin32SurfaceCreateFlagsKHR -> Int -> VkWin32SurfaceCreateFlagsKHR #

rotateR :: VkWin32SurfaceCreateFlagsKHR -> Int -> VkWin32SurfaceCreateFlagsKHR #

popCount :: VkWin32SurfaceCreateFlagsKHR -> Int #

FiniteBits VkWin32SurfaceCreateFlagsKHR Source # 
type Rep VkWin32SurfaceCreateFlagsKHR Source # 
type Rep VkWin32SurfaceCreateFlagsKHR = D1 (MetaData "VkWin32SurfaceCreateFlagsKHR" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkWin32SurfaceCreateFlagsKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkXcbSurfaceCreateFlagsKHR Source #

Instances

Bounded VkXcbSurfaceCreateFlagsKHR Source # 
Enum VkXcbSurfaceCreateFlagsKHR Source # 
Eq VkXcbSurfaceCreateFlagsKHR Source # 
Integral VkXcbSurfaceCreateFlagsKHR Source # 
Data VkXcbSurfaceCreateFlagsKHR Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkXcbSurfaceCreateFlagsKHR -> c VkXcbSurfaceCreateFlagsKHR #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkXcbSurfaceCreateFlagsKHR #

toConstr :: VkXcbSurfaceCreateFlagsKHR -> Constr #

dataTypeOf :: VkXcbSurfaceCreateFlagsKHR -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkXcbSurfaceCreateFlagsKHR) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkXcbSurfaceCreateFlagsKHR) #

gmapT :: (forall b. Data b => b -> b) -> VkXcbSurfaceCreateFlagsKHR -> VkXcbSurfaceCreateFlagsKHR #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkXcbSurfaceCreateFlagsKHR -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkXcbSurfaceCreateFlagsKHR -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkXcbSurfaceCreateFlagsKHR -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkXcbSurfaceCreateFlagsKHR -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkXcbSurfaceCreateFlagsKHR -> m VkXcbSurfaceCreateFlagsKHR #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkXcbSurfaceCreateFlagsKHR -> m VkXcbSurfaceCreateFlagsKHR #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkXcbSurfaceCreateFlagsKHR -> m VkXcbSurfaceCreateFlagsKHR #

Num VkXcbSurfaceCreateFlagsKHR Source # 
Ord VkXcbSurfaceCreateFlagsKHR Source # 
Read VkXcbSurfaceCreateFlagsKHR Source # 
Real VkXcbSurfaceCreateFlagsKHR Source # 
Show VkXcbSurfaceCreateFlagsKHR Source # 
Generic VkXcbSurfaceCreateFlagsKHR Source # 
Storable VkXcbSurfaceCreateFlagsKHR Source # 
Bits VkXcbSurfaceCreateFlagsKHR Source # 

Methods

(.&.) :: VkXcbSurfaceCreateFlagsKHR -> VkXcbSurfaceCreateFlagsKHR -> VkXcbSurfaceCreateFlagsKHR #

(.|.) :: VkXcbSurfaceCreateFlagsKHR -> VkXcbSurfaceCreateFlagsKHR -> VkXcbSurfaceCreateFlagsKHR #

xor :: VkXcbSurfaceCreateFlagsKHR -> VkXcbSurfaceCreateFlagsKHR -> VkXcbSurfaceCreateFlagsKHR #

complement :: VkXcbSurfaceCreateFlagsKHR -> VkXcbSurfaceCreateFlagsKHR #

shift :: VkXcbSurfaceCreateFlagsKHR -> Int -> VkXcbSurfaceCreateFlagsKHR #

rotate :: VkXcbSurfaceCreateFlagsKHR -> Int -> VkXcbSurfaceCreateFlagsKHR #

zeroBits :: VkXcbSurfaceCreateFlagsKHR #

bit :: Int -> VkXcbSurfaceCreateFlagsKHR #

setBit :: VkXcbSurfaceCreateFlagsKHR -> Int -> VkXcbSurfaceCreateFlagsKHR #

clearBit :: VkXcbSurfaceCreateFlagsKHR -> Int -> VkXcbSurfaceCreateFlagsKHR #

complementBit :: VkXcbSurfaceCreateFlagsKHR -> Int -> VkXcbSurfaceCreateFlagsKHR #

testBit :: VkXcbSurfaceCreateFlagsKHR -> Int -> Bool #

bitSizeMaybe :: VkXcbSurfaceCreateFlagsKHR -> Maybe Int #

bitSize :: VkXcbSurfaceCreateFlagsKHR -> Int #

isSigned :: VkXcbSurfaceCreateFlagsKHR -> Bool #

shiftL :: VkXcbSurfaceCreateFlagsKHR -> Int -> VkXcbSurfaceCreateFlagsKHR #

unsafeShiftL :: VkXcbSurfaceCreateFlagsKHR -> Int -> VkXcbSurfaceCreateFlagsKHR #

shiftR :: VkXcbSurfaceCreateFlagsKHR -> Int -> VkXcbSurfaceCreateFlagsKHR #

unsafeShiftR :: VkXcbSurfaceCreateFlagsKHR -> Int -> VkXcbSurfaceCreateFlagsKHR #

rotateL :: VkXcbSurfaceCreateFlagsKHR -> Int -> VkXcbSurfaceCreateFlagsKHR #

rotateR :: VkXcbSurfaceCreateFlagsKHR -> Int -> VkXcbSurfaceCreateFlagsKHR #

popCount :: VkXcbSurfaceCreateFlagsKHR -> Int #

FiniteBits VkXcbSurfaceCreateFlagsKHR Source # 
type Rep VkXcbSurfaceCreateFlagsKHR Source # 
type Rep VkXcbSurfaceCreateFlagsKHR = D1 (MetaData "VkXcbSurfaceCreateFlagsKHR" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkXcbSurfaceCreateFlagsKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkXlibSurfaceCreateFlagsKHR Source #

Instances

Bounded VkXlibSurfaceCreateFlagsKHR Source # 
Enum VkXlibSurfaceCreateFlagsKHR Source # 
Eq VkXlibSurfaceCreateFlagsKHR Source # 
Integral VkXlibSurfaceCreateFlagsKHR Source # 
Data VkXlibSurfaceCreateFlagsKHR Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkXlibSurfaceCreateFlagsKHR -> c VkXlibSurfaceCreateFlagsKHR #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkXlibSurfaceCreateFlagsKHR #

toConstr :: VkXlibSurfaceCreateFlagsKHR -> Constr #

dataTypeOf :: VkXlibSurfaceCreateFlagsKHR -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkXlibSurfaceCreateFlagsKHR) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkXlibSurfaceCreateFlagsKHR) #

gmapT :: (forall b. Data b => b -> b) -> VkXlibSurfaceCreateFlagsKHR -> VkXlibSurfaceCreateFlagsKHR #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkXlibSurfaceCreateFlagsKHR -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkXlibSurfaceCreateFlagsKHR -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkXlibSurfaceCreateFlagsKHR -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkXlibSurfaceCreateFlagsKHR -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkXlibSurfaceCreateFlagsKHR -> m VkXlibSurfaceCreateFlagsKHR #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkXlibSurfaceCreateFlagsKHR -> m VkXlibSurfaceCreateFlagsKHR #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkXlibSurfaceCreateFlagsKHR -> m VkXlibSurfaceCreateFlagsKHR #

Num VkXlibSurfaceCreateFlagsKHR Source # 
Ord VkXlibSurfaceCreateFlagsKHR Source # 
Read VkXlibSurfaceCreateFlagsKHR Source # 
Real VkXlibSurfaceCreateFlagsKHR Source # 
Show VkXlibSurfaceCreateFlagsKHR Source # 
Generic VkXlibSurfaceCreateFlagsKHR Source # 
Storable VkXlibSurfaceCreateFlagsKHR Source # 
Bits VkXlibSurfaceCreateFlagsKHR Source # 

Methods

(.&.) :: VkXlibSurfaceCreateFlagsKHR -> VkXlibSurfaceCreateFlagsKHR -> VkXlibSurfaceCreateFlagsKHR #

(.|.) :: VkXlibSurfaceCreateFlagsKHR -> VkXlibSurfaceCreateFlagsKHR -> VkXlibSurfaceCreateFlagsKHR #

xor :: VkXlibSurfaceCreateFlagsKHR -> VkXlibSurfaceCreateFlagsKHR -> VkXlibSurfaceCreateFlagsKHR #

complement :: VkXlibSurfaceCreateFlagsKHR -> VkXlibSurfaceCreateFlagsKHR #

shift :: VkXlibSurfaceCreateFlagsKHR -> Int -> VkXlibSurfaceCreateFlagsKHR #

rotate :: VkXlibSurfaceCreateFlagsKHR -> Int -> VkXlibSurfaceCreateFlagsKHR #

zeroBits :: VkXlibSurfaceCreateFlagsKHR #

bit :: Int -> VkXlibSurfaceCreateFlagsKHR #

setBit :: VkXlibSurfaceCreateFlagsKHR -> Int -> VkXlibSurfaceCreateFlagsKHR #

clearBit :: VkXlibSurfaceCreateFlagsKHR -> Int -> VkXlibSurfaceCreateFlagsKHR #

complementBit :: VkXlibSurfaceCreateFlagsKHR -> Int -> VkXlibSurfaceCreateFlagsKHR #

testBit :: VkXlibSurfaceCreateFlagsKHR -> Int -> Bool #

bitSizeMaybe :: VkXlibSurfaceCreateFlagsKHR -> Maybe Int #

bitSize :: VkXlibSurfaceCreateFlagsKHR -> Int #

isSigned :: VkXlibSurfaceCreateFlagsKHR -> Bool #

shiftL :: VkXlibSurfaceCreateFlagsKHR -> Int -> VkXlibSurfaceCreateFlagsKHR #

unsafeShiftL :: VkXlibSurfaceCreateFlagsKHR -> Int -> VkXlibSurfaceCreateFlagsKHR #

shiftR :: VkXlibSurfaceCreateFlagsKHR -> Int -> VkXlibSurfaceCreateFlagsKHR #

unsafeShiftR :: VkXlibSurfaceCreateFlagsKHR -> Int -> VkXlibSurfaceCreateFlagsKHR #

rotateL :: VkXlibSurfaceCreateFlagsKHR -> Int -> VkXlibSurfaceCreateFlagsKHR #

rotateR :: VkXlibSurfaceCreateFlagsKHR -> Int -> VkXlibSurfaceCreateFlagsKHR #

popCount :: VkXlibSurfaceCreateFlagsKHR -> Int #

FiniteBits VkXlibSurfaceCreateFlagsKHR Source # 
type Rep VkXlibSurfaceCreateFlagsKHR Source # 
type Rep VkXlibSurfaceCreateFlagsKHR = D1 (MetaData "VkXlibSurfaceCreateFlagsKHR" "Graphics.Vulkan.Types.Bitmasks" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkXlibSurfaceCreateFlagsKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

data VkDeviceCreateInfo Source #

typedef struct VkDeviceCreateInfo {
    VkStructureType sType;
    const void*     pNext;
    VkDeviceCreateFlags    flags;
    uint32_t        queueCreateInfoCount;
    const VkDeviceQueueCreateInfo* pQueueCreateInfos;
    uint32_t               enabledLayerCount;
    const char* const*      ppEnabledLayerNames;
    uint32_t               enabledExtensionCount;
    const char* const*      ppEnabledExtensionNames;
    const VkPhysicalDeviceFeatures* pEnabledFeatures;
} VkDeviceCreateInfo;

VkDeviceCreateInfo registry at www.khronos.org

Instances

Eq VkDeviceCreateInfo Source # 
Ord VkDeviceCreateInfo Source # 
Show VkDeviceCreateInfo Source # 
Storable VkDeviceCreateInfo Source # 
VulkanMarshalPrim VkDeviceCreateInfo Source # 
VulkanMarshal VkDeviceCreateInfo Source # 
CanWriteField "enabledExtensionCount" VkDeviceCreateInfo Source # 

Methods

writeField :: Ptr VkDeviceCreateInfo -> FieldType "enabledExtensionCount" VkDeviceCreateInfo -> IO () Source #

CanWriteField "enabledLayerCount" VkDeviceCreateInfo Source # 

Methods

writeField :: Ptr VkDeviceCreateInfo -> FieldType "enabledLayerCount" VkDeviceCreateInfo -> IO () Source #

CanWriteField "flags" VkDeviceCreateInfo Source # 
CanWriteField "pEnabledFeatures" VkDeviceCreateInfo Source # 

Methods

writeField :: Ptr VkDeviceCreateInfo -> FieldType "pEnabledFeatures" VkDeviceCreateInfo -> IO () Source #

CanWriteField "pNext" VkDeviceCreateInfo Source # 
CanWriteField "pQueueCreateInfos" VkDeviceCreateInfo Source # 

Methods

writeField :: Ptr VkDeviceCreateInfo -> FieldType "pQueueCreateInfos" VkDeviceCreateInfo -> IO () Source #

CanWriteField "ppEnabledExtensionNames" VkDeviceCreateInfo Source # 

Methods

writeField :: Ptr VkDeviceCreateInfo -> FieldType "ppEnabledExtensionNames" VkDeviceCreateInfo -> IO () Source #

CanWriteField "ppEnabledLayerNames" VkDeviceCreateInfo Source # 

Methods

writeField :: Ptr VkDeviceCreateInfo -> FieldType "ppEnabledLayerNames" VkDeviceCreateInfo -> IO () Source #

CanWriteField "queueCreateInfoCount" VkDeviceCreateInfo Source # 

Methods

writeField :: Ptr VkDeviceCreateInfo -> FieldType "queueCreateInfoCount" VkDeviceCreateInfo -> IO () Source #

CanWriteField "sType" VkDeviceCreateInfo Source # 
CanReadField "enabledExtensionCount" VkDeviceCreateInfo Source # 
CanReadField "enabledLayerCount" VkDeviceCreateInfo Source # 
CanReadField "flags" VkDeviceCreateInfo Source # 
CanReadField "pEnabledFeatures" VkDeviceCreateInfo Source # 
CanReadField "pNext" VkDeviceCreateInfo Source # 
CanReadField "pQueueCreateInfos" VkDeviceCreateInfo Source # 
CanReadField "ppEnabledExtensionNames" VkDeviceCreateInfo Source # 

Methods

getField :: VkDeviceCreateInfo -> FieldType "ppEnabledExtensionNames" VkDeviceCreateInfo Source #

readField :: Ptr VkDeviceCreateInfo -> IO (FieldType "ppEnabledExtensionNames" VkDeviceCreateInfo) Source #

CanReadField "ppEnabledLayerNames" VkDeviceCreateInfo Source # 
CanReadField "queueCreateInfoCount" VkDeviceCreateInfo Source # 
CanReadField "sType" VkDeviceCreateInfo Source # 
HasField "enabledExtensionCount" VkDeviceCreateInfo Source # 

Associated Types

type FieldType ("enabledExtensionCount" :: Symbol) VkDeviceCreateInfo :: Type Source #

type FieldOptional ("enabledExtensionCount" :: Symbol) VkDeviceCreateInfo :: Bool Source #

type FieldOffset ("enabledExtensionCount" :: Symbol) VkDeviceCreateInfo :: Nat Source #

type FieldIsArray ("enabledExtensionCount" :: Symbol) VkDeviceCreateInfo :: Bool Source #

HasField "enabledLayerCount" VkDeviceCreateInfo Source # 

Associated Types

type FieldType ("enabledLayerCount" :: Symbol) VkDeviceCreateInfo :: Type Source #

type FieldOptional ("enabledLayerCount" :: Symbol) VkDeviceCreateInfo :: Bool Source #

type FieldOffset ("enabledLayerCount" :: Symbol) VkDeviceCreateInfo :: Nat Source #

type FieldIsArray ("enabledLayerCount" :: Symbol) VkDeviceCreateInfo :: Bool Source #

HasField "flags" VkDeviceCreateInfo Source # 
HasField "pEnabledFeatures" VkDeviceCreateInfo Source # 

Associated Types

type FieldType ("pEnabledFeatures" :: Symbol) VkDeviceCreateInfo :: Type Source #

type FieldOptional ("pEnabledFeatures" :: Symbol) VkDeviceCreateInfo :: Bool Source #

type FieldOffset ("pEnabledFeatures" :: Symbol) VkDeviceCreateInfo :: Nat Source #

type FieldIsArray ("pEnabledFeatures" :: Symbol) VkDeviceCreateInfo :: Bool Source #

HasField "pNext" VkDeviceCreateInfo Source # 
HasField "pQueueCreateInfos" VkDeviceCreateInfo Source # 

Associated Types

type FieldType ("pQueueCreateInfos" :: Symbol) VkDeviceCreateInfo :: Type Source #

type FieldOptional ("pQueueCreateInfos" :: Symbol) VkDeviceCreateInfo :: Bool Source #

type FieldOffset ("pQueueCreateInfos" :: Symbol) VkDeviceCreateInfo :: Nat Source #

type FieldIsArray ("pQueueCreateInfos" :: Symbol) VkDeviceCreateInfo :: Bool Source #

HasField "ppEnabledExtensionNames" VkDeviceCreateInfo Source # 

Associated Types

type FieldType ("ppEnabledExtensionNames" :: Symbol) VkDeviceCreateInfo :: Type Source #

type FieldOptional ("ppEnabledExtensionNames" :: Symbol) VkDeviceCreateInfo :: Bool Source #

type FieldOffset ("ppEnabledExtensionNames" :: Symbol) VkDeviceCreateInfo :: Nat Source #

type FieldIsArray ("ppEnabledExtensionNames" :: Symbol) VkDeviceCreateInfo :: Bool Source #

HasField "ppEnabledLayerNames" VkDeviceCreateInfo Source # 

Associated Types

type FieldType ("ppEnabledLayerNames" :: Symbol) VkDeviceCreateInfo :: Type Source #

type FieldOptional ("ppEnabledLayerNames" :: Symbol) VkDeviceCreateInfo :: Bool Source #

type FieldOffset ("ppEnabledLayerNames" :: Symbol) VkDeviceCreateInfo :: Nat Source #

type FieldIsArray ("ppEnabledLayerNames" :: Symbol) VkDeviceCreateInfo :: Bool Source #

HasField "queueCreateInfoCount" VkDeviceCreateInfo Source # 

Associated Types

type FieldType ("queueCreateInfoCount" :: Symbol) VkDeviceCreateInfo :: Type Source #

type FieldOptional ("queueCreateInfoCount" :: Symbol) VkDeviceCreateInfo :: Bool Source #

type FieldOffset ("queueCreateInfoCount" :: Symbol) VkDeviceCreateInfo :: Nat Source #

type FieldIsArray ("queueCreateInfoCount" :: Symbol) VkDeviceCreateInfo :: Bool Source #

HasField "sType" VkDeviceCreateInfo Source # 
type StructFields VkDeviceCreateInfo Source # 
type StructFields VkDeviceCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "queueCreateInfoCount" ((:) Symbol "pQueueCreateInfos" ((:) Symbol "enabledLayerCount" ((:) Symbol "ppEnabledLayerNames" ((:) Symbol "enabledExtensionCount" ((:) Symbol "ppEnabledExtensionNames" ((:) Symbol "pEnabledFeatures" ([] Symbol))))))))))
type CUnionType VkDeviceCreateInfo Source # 
type ReturnedOnly VkDeviceCreateInfo Source # 
type StructExtends VkDeviceCreateInfo Source # 
type FieldType "enabledExtensionCount" VkDeviceCreateInfo Source # 
type FieldType "enabledExtensionCount" VkDeviceCreateInfo = Word32
type FieldType "enabledLayerCount" VkDeviceCreateInfo Source # 
type FieldType "enabledLayerCount" VkDeviceCreateInfo = Word32
type FieldType "flags" VkDeviceCreateInfo Source # 
type FieldType "pEnabledFeatures" VkDeviceCreateInfo Source # 
type FieldType "pNext" VkDeviceCreateInfo Source # 
type FieldType "pQueueCreateInfos" VkDeviceCreateInfo Source # 
type FieldType "ppEnabledExtensionNames" VkDeviceCreateInfo Source # 
type FieldType "ppEnabledExtensionNames" VkDeviceCreateInfo = Ptr CString
type FieldType "ppEnabledLayerNames" VkDeviceCreateInfo Source # 
type FieldType "ppEnabledLayerNames" VkDeviceCreateInfo = Ptr CString
type FieldType "queueCreateInfoCount" VkDeviceCreateInfo Source # 
type FieldType "queueCreateInfoCount" VkDeviceCreateInfo = Word32
type FieldType "sType" VkDeviceCreateInfo Source # 
type FieldOptional "enabledExtensionCount" VkDeviceCreateInfo Source # 
type FieldOptional "enabledExtensionCount" VkDeviceCreateInfo = True
type FieldOptional "enabledLayerCount" VkDeviceCreateInfo Source # 
type FieldOptional "enabledLayerCount" VkDeviceCreateInfo = True
type FieldOptional "flags" VkDeviceCreateInfo Source # 
type FieldOptional "pEnabledFeatures" VkDeviceCreateInfo Source # 
type FieldOptional "pEnabledFeatures" VkDeviceCreateInfo = True
type FieldOptional "pNext" VkDeviceCreateInfo Source # 
type FieldOptional "pQueueCreateInfos" VkDeviceCreateInfo Source # 
type FieldOptional "pQueueCreateInfos" VkDeviceCreateInfo = False
type FieldOptional "ppEnabledExtensionNames" VkDeviceCreateInfo Source # 
type FieldOptional "ppEnabledExtensionNames" VkDeviceCreateInfo = False
type FieldOptional "ppEnabledLayerNames" VkDeviceCreateInfo Source # 
type FieldOptional "ppEnabledLayerNames" VkDeviceCreateInfo = False
type FieldOptional "queueCreateInfoCount" VkDeviceCreateInfo Source # 
type FieldOptional "queueCreateInfoCount" VkDeviceCreateInfo = False
type FieldOptional "sType" VkDeviceCreateInfo Source # 
type FieldOffset "enabledExtensionCount" VkDeviceCreateInfo Source # 
type FieldOffset "enabledExtensionCount" VkDeviceCreateInfo = 48
type FieldOffset "enabledLayerCount" VkDeviceCreateInfo Source # 
type FieldOffset "enabledLayerCount" VkDeviceCreateInfo = 32
type FieldOffset "flags" VkDeviceCreateInfo Source # 
type FieldOffset "pEnabledFeatures" VkDeviceCreateInfo Source # 
type FieldOffset "pEnabledFeatures" VkDeviceCreateInfo = 64
type FieldOffset "pNext" VkDeviceCreateInfo Source # 
type FieldOffset "pQueueCreateInfos" VkDeviceCreateInfo Source # 
type FieldOffset "pQueueCreateInfos" VkDeviceCreateInfo = 24
type FieldOffset "ppEnabledExtensionNames" VkDeviceCreateInfo Source # 
type FieldOffset "ppEnabledExtensionNames" VkDeviceCreateInfo = 56
type FieldOffset "ppEnabledLayerNames" VkDeviceCreateInfo Source # 
type FieldOffset "ppEnabledLayerNames" VkDeviceCreateInfo = 40
type FieldOffset "queueCreateInfoCount" VkDeviceCreateInfo Source # 
type FieldOffset "queueCreateInfoCount" VkDeviceCreateInfo = 20
type FieldOffset "sType" VkDeviceCreateInfo Source # 
type FieldIsArray "enabledExtensionCount" VkDeviceCreateInfo Source # 
type FieldIsArray "enabledExtensionCount" VkDeviceCreateInfo = False
type FieldIsArray "enabledLayerCount" VkDeviceCreateInfo Source # 
type FieldIsArray "enabledLayerCount" VkDeviceCreateInfo = False
type FieldIsArray "flags" VkDeviceCreateInfo Source # 
type FieldIsArray "pEnabledFeatures" VkDeviceCreateInfo Source # 
type FieldIsArray "pEnabledFeatures" VkDeviceCreateInfo = False
type FieldIsArray "pNext" VkDeviceCreateInfo Source # 
type FieldIsArray "pQueueCreateInfos" VkDeviceCreateInfo Source # 
type FieldIsArray "pQueueCreateInfos" VkDeviceCreateInfo = False
type FieldIsArray "ppEnabledExtensionNames" VkDeviceCreateInfo Source # 
type FieldIsArray "ppEnabledExtensionNames" VkDeviceCreateInfo = False
type FieldIsArray "ppEnabledLayerNames" VkDeviceCreateInfo Source # 
type FieldIsArray "ppEnabledLayerNames" VkDeviceCreateInfo = False
type FieldIsArray "queueCreateInfoCount" VkDeviceCreateInfo Source # 
type FieldIsArray "queueCreateInfoCount" VkDeviceCreateInfo = False
type FieldIsArray "sType" VkDeviceCreateInfo Source # 

data VkDeviceEventInfoEXT Source #

typedef struct VkDeviceEventInfoEXT {
    VkStructureType sType;
    const void*                      pNext;
    VkDeviceEventTypeEXT             deviceEvent;
} VkDeviceEventInfoEXT;

VkDeviceEventInfoEXT registry at www.khronos.org

Instances

Eq VkDeviceEventInfoEXT Source # 
Ord VkDeviceEventInfoEXT Source # 
Show VkDeviceEventInfoEXT Source # 
Storable VkDeviceEventInfoEXT Source # 
VulkanMarshalPrim VkDeviceEventInfoEXT Source # 
VulkanMarshal VkDeviceEventInfoEXT Source # 
CanWriteField "deviceEvent" VkDeviceEventInfoEXT Source # 
CanWriteField "pNext" VkDeviceEventInfoEXT Source # 
CanWriteField "sType" VkDeviceEventInfoEXT Source # 
CanReadField "deviceEvent" VkDeviceEventInfoEXT Source # 
CanReadField "pNext" VkDeviceEventInfoEXT Source # 
CanReadField "sType" VkDeviceEventInfoEXT Source # 
HasField "deviceEvent" VkDeviceEventInfoEXT Source # 

Associated Types

type FieldType ("deviceEvent" :: Symbol) VkDeviceEventInfoEXT :: Type Source #

type FieldOptional ("deviceEvent" :: Symbol) VkDeviceEventInfoEXT :: Bool Source #

type FieldOffset ("deviceEvent" :: Symbol) VkDeviceEventInfoEXT :: Nat Source #

type FieldIsArray ("deviceEvent" :: Symbol) VkDeviceEventInfoEXT :: Bool Source #

HasField "pNext" VkDeviceEventInfoEXT Source # 
HasField "sType" VkDeviceEventInfoEXT Source # 
type StructFields VkDeviceEventInfoEXT Source # 
type StructFields VkDeviceEventInfoEXT = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "deviceEvent" ([] Symbol)))
type CUnionType VkDeviceEventInfoEXT Source # 
type ReturnedOnly VkDeviceEventInfoEXT Source # 
type StructExtends VkDeviceEventInfoEXT Source # 
type FieldType "deviceEvent" VkDeviceEventInfoEXT Source # 
type FieldType "pNext" VkDeviceEventInfoEXT Source # 
type FieldType "sType" VkDeviceEventInfoEXT Source # 
type FieldOptional "deviceEvent" VkDeviceEventInfoEXT Source # 
type FieldOptional "pNext" VkDeviceEventInfoEXT Source # 
type FieldOptional "sType" VkDeviceEventInfoEXT Source # 
type FieldOffset "deviceEvent" VkDeviceEventInfoEXT Source # 
type FieldOffset "deviceEvent" VkDeviceEventInfoEXT = 16
type FieldOffset "pNext" VkDeviceEventInfoEXT Source # 
type FieldOffset "sType" VkDeviceEventInfoEXT Source # 
type FieldIsArray "deviceEvent" VkDeviceEventInfoEXT Source # 
type FieldIsArray "pNext" VkDeviceEventInfoEXT Source # 
type FieldIsArray "sType" VkDeviceEventInfoEXT Source # 

data VkDeviceGeneratedCommandsFeaturesNVX Source #

typedef struct VkDeviceGeneratedCommandsFeaturesNVX {
    VkStructureType sType;
    const void*                      pNext;
    VkBool32                         computeBindingPointSupport;
} VkDeviceGeneratedCommandsFeaturesNVX;

VkDeviceGeneratedCommandsFeaturesNVX registry at www.khronos.org

Instances

Eq VkDeviceGeneratedCommandsFeaturesNVX Source # 
Ord VkDeviceGeneratedCommandsFeaturesNVX Source # 
Show VkDeviceGeneratedCommandsFeaturesNVX Source # 
Storable VkDeviceGeneratedCommandsFeaturesNVX Source # 
VulkanMarshalPrim VkDeviceGeneratedCommandsFeaturesNVX Source # 
VulkanMarshal VkDeviceGeneratedCommandsFeaturesNVX Source # 
CanWriteField "computeBindingPointSupport" VkDeviceGeneratedCommandsFeaturesNVX Source # 
CanWriteField "pNext" VkDeviceGeneratedCommandsFeaturesNVX Source # 
CanWriteField "sType" VkDeviceGeneratedCommandsFeaturesNVX Source # 
CanReadField "computeBindingPointSupport" VkDeviceGeneratedCommandsFeaturesNVX Source # 
CanReadField "pNext" VkDeviceGeneratedCommandsFeaturesNVX Source # 
CanReadField "sType" VkDeviceGeneratedCommandsFeaturesNVX Source # 
HasField "computeBindingPointSupport" VkDeviceGeneratedCommandsFeaturesNVX Source # 

Associated Types

type FieldType ("computeBindingPointSupport" :: Symbol) VkDeviceGeneratedCommandsFeaturesNVX :: Type Source #

type FieldOptional ("computeBindingPointSupport" :: Symbol) VkDeviceGeneratedCommandsFeaturesNVX :: Bool Source #

type FieldOffset ("computeBindingPointSupport" :: Symbol) VkDeviceGeneratedCommandsFeaturesNVX :: Nat Source #

type FieldIsArray ("computeBindingPointSupport" :: Symbol) VkDeviceGeneratedCommandsFeaturesNVX :: Bool Source #

HasField "pNext" VkDeviceGeneratedCommandsFeaturesNVX Source # 
HasField "sType" VkDeviceGeneratedCommandsFeaturesNVX Source # 
type StructFields VkDeviceGeneratedCommandsFeaturesNVX Source # 
type StructFields VkDeviceGeneratedCommandsFeaturesNVX = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "computeBindingPointSupport" ([] Symbol)))
type CUnionType VkDeviceGeneratedCommandsFeaturesNVX Source # 
type ReturnedOnly VkDeviceGeneratedCommandsFeaturesNVX Source # 
type StructExtends VkDeviceGeneratedCommandsFeaturesNVX Source # 
type FieldType "computeBindingPointSupport" VkDeviceGeneratedCommandsFeaturesNVX Source # 
type FieldType "computeBindingPointSupport" VkDeviceGeneratedCommandsFeaturesNVX = VkBool32
type FieldType "pNext" VkDeviceGeneratedCommandsFeaturesNVX Source # 
type FieldType "sType" VkDeviceGeneratedCommandsFeaturesNVX Source # 
type FieldOptional "computeBindingPointSupport" VkDeviceGeneratedCommandsFeaturesNVX Source # 
type FieldOptional "computeBindingPointSupport" VkDeviceGeneratedCommandsFeaturesNVX = False
type FieldOptional "pNext" VkDeviceGeneratedCommandsFeaturesNVX Source # 
type FieldOptional "sType" VkDeviceGeneratedCommandsFeaturesNVX Source # 
type FieldOffset "computeBindingPointSupport" VkDeviceGeneratedCommandsFeaturesNVX Source # 
type FieldOffset "computeBindingPointSupport" VkDeviceGeneratedCommandsFeaturesNVX = 16
type FieldOffset "pNext" VkDeviceGeneratedCommandsFeaturesNVX Source # 
type FieldOffset "sType" VkDeviceGeneratedCommandsFeaturesNVX Source # 
type FieldIsArray "computeBindingPointSupport" VkDeviceGeneratedCommandsFeaturesNVX Source # 
type FieldIsArray "computeBindingPointSupport" VkDeviceGeneratedCommandsFeaturesNVX = False
type FieldIsArray "pNext" VkDeviceGeneratedCommandsFeaturesNVX Source # 
type FieldIsArray "sType" VkDeviceGeneratedCommandsFeaturesNVX Source # 

data VkDeviceGeneratedCommandsLimitsNVX Source #

typedef struct VkDeviceGeneratedCommandsLimitsNVX {
    VkStructureType sType;
    const void*                      pNext;
    uint32_t                         maxIndirectCommandsLayoutTokenCount;
    uint32_t                         maxObjectEntryCounts;
    uint32_t                         minSequenceCountBufferOffsetAlignment;
    uint32_t                         minSequenceIndexBufferOffsetAlignment;
    uint32_t                         minCommandsTokenBufferOffsetAlignment;
} VkDeviceGeneratedCommandsLimitsNVX;

VkDeviceGeneratedCommandsLimitsNVX registry at www.khronos.org

Instances

Eq VkDeviceGeneratedCommandsLimitsNVX Source # 
Ord VkDeviceGeneratedCommandsLimitsNVX Source # 
Show VkDeviceGeneratedCommandsLimitsNVX Source # 
Storable VkDeviceGeneratedCommandsLimitsNVX Source # 
VulkanMarshalPrim VkDeviceGeneratedCommandsLimitsNVX Source # 
VulkanMarshal VkDeviceGeneratedCommandsLimitsNVX Source # 
CanWriteField "maxIndirectCommandsLayoutTokenCount" VkDeviceGeneratedCommandsLimitsNVX Source # 
CanWriteField "maxObjectEntryCounts" VkDeviceGeneratedCommandsLimitsNVX Source # 
CanWriteField "minCommandsTokenBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 

Methods

writeField :: Ptr VkDeviceGeneratedCommandsLimitsNVX -> FieldType "minCommandsTokenBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX -> IO () Source #

CanWriteField "minSequenceCountBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 

Methods

writeField :: Ptr VkDeviceGeneratedCommandsLimitsNVX -> FieldType "minSequenceCountBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX -> IO () Source #

CanWriteField "minSequenceIndexBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 

Methods

writeField :: Ptr VkDeviceGeneratedCommandsLimitsNVX -> FieldType "minSequenceIndexBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX -> IO () Source #

CanWriteField "pNext" VkDeviceGeneratedCommandsLimitsNVX Source # 
CanWriteField "sType" VkDeviceGeneratedCommandsLimitsNVX Source # 
CanReadField "maxIndirectCommandsLayoutTokenCount" VkDeviceGeneratedCommandsLimitsNVX Source # 
CanReadField "maxObjectEntryCounts" VkDeviceGeneratedCommandsLimitsNVX Source # 
CanReadField "minCommandsTokenBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 
CanReadField "minSequenceCountBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 
CanReadField "minSequenceIndexBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 
CanReadField "pNext" VkDeviceGeneratedCommandsLimitsNVX Source # 
CanReadField "sType" VkDeviceGeneratedCommandsLimitsNVX Source # 
HasField "maxIndirectCommandsLayoutTokenCount" VkDeviceGeneratedCommandsLimitsNVX Source # 

Associated Types

type FieldType ("maxIndirectCommandsLayoutTokenCount" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Type Source #

type FieldOptional ("maxIndirectCommandsLayoutTokenCount" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Bool Source #

type FieldOffset ("maxIndirectCommandsLayoutTokenCount" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Nat Source #

type FieldIsArray ("maxIndirectCommandsLayoutTokenCount" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Bool Source #

HasField "maxObjectEntryCounts" VkDeviceGeneratedCommandsLimitsNVX Source # 

Associated Types

type FieldType ("maxObjectEntryCounts" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Type Source #

type FieldOptional ("maxObjectEntryCounts" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Bool Source #

type FieldOffset ("maxObjectEntryCounts" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Nat Source #

type FieldIsArray ("maxObjectEntryCounts" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Bool Source #

HasField "minCommandsTokenBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 

Associated Types

type FieldType ("minCommandsTokenBufferOffsetAlignment" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Type Source #

type FieldOptional ("minCommandsTokenBufferOffsetAlignment" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Bool Source #

type FieldOffset ("minCommandsTokenBufferOffsetAlignment" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Nat Source #

type FieldIsArray ("minCommandsTokenBufferOffsetAlignment" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Bool Source #

HasField "minSequenceCountBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 

Associated Types

type FieldType ("minSequenceCountBufferOffsetAlignment" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Type Source #

type FieldOptional ("minSequenceCountBufferOffsetAlignment" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Bool Source #

type FieldOffset ("minSequenceCountBufferOffsetAlignment" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Nat Source #

type FieldIsArray ("minSequenceCountBufferOffsetAlignment" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Bool Source #

HasField "minSequenceIndexBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 

Associated Types

type FieldType ("minSequenceIndexBufferOffsetAlignment" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Type Source #

type FieldOptional ("minSequenceIndexBufferOffsetAlignment" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Bool Source #

type FieldOffset ("minSequenceIndexBufferOffsetAlignment" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Nat Source #

type FieldIsArray ("minSequenceIndexBufferOffsetAlignment" :: Symbol) VkDeviceGeneratedCommandsLimitsNVX :: Bool Source #

HasField "pNext" VkDeviceGeneratedCommandsLimitsNVX Source # 
HasField "sType" VkDeviceGeneratedCommandsLimitsNVX Source # 
type StructFields VkDeviceGeneratedCommandsLimitsNVX Source # 
type StructFields VkDeviceGeneratedCommandsLimitsNVX = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "maxIndirectCommandsLayoutTokenCount" ((:) Symbol "maxObjectEntryCounts" ((:) Symbol "minSequenceCountBufferOffsetAlignment" ((:) Symbol "minSequenceIndexBufferOffsetAlignment" ((:) Symbol "minCommandsTokenBufferOffsetAlignment" ([] Symbol)))))))
type CUnionType VkDeviceGeneratedCommandsLimitsNVX Source # 
type ReturnedOnly VkDeviceGeneratedCommandsLimitsNVX Source # 
type StructExtends VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldType "maxIndirectCommandsLayoutTokenCount" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldType "maxIndirectCommandsLayoutTokenCount" VkDeviceGeneratedCommandsLimitsNVX = Word32
type FieldType "maxObjectEntryCounts" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldType "minCommandsTokenBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldType "minCommandsTokenBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX = Word32
type FieldType "minSequenceCountBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldType "minSequenceCountBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX = Word32
type FieldType "minSequenceIndexBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldType "minSequenceIndexBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX = Word32
type FieldType "pNext" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldType "sType" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldOptional "maxIndirectCommandsLayoutTokenCount" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldOptional "maxIndirectCommandsLayoutTokenCount" VkDeviceGeneratedCommandsLimitsNVX = False
type FieldOptional "maxObjectEntryCounts" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldOptional "minCommandsTokenBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldOptional "minCommandsTokenBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX = False
type FieldOptional "minSequenceCountBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldOptional "minSequenceCountBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX = False
type FieldOptional "minSequenceIndexBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldOptional "minSequenceIndexBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX = False
type FieldOptional "pNext" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldOptional "sType" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldOffset "maxIndirectCommandsLayoutTokenCount" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldOffset "maxIndirectCommandsLayoutTokenCount" VkDeviceGeneratedCommandsLimitsNVX = 16
type FieldOffset "maxObjectEntryCounts" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldOffset "maxObjectEntryCounts" VkDeviceGeneratedCommandsLimitsNVX = 20
type FieldOffset "minCommandsTokenBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldOffset "minCommandsTokenBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX = 32
type FieldOffset "minSequenceCountBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldOffset "minSequenceCountBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX = 24
type FieldOffset "minSequenceIndexBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldOffset "minSequenceIndexBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX = 28
type FieldOffset "pNext" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldOffset "sType" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldIsArray "maxIndirectCommandsLayoutTokenCount" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldIsArray "maxIndirectCommandsLayoutTokenCount" VkDeviceGeneratedCommandsLimitsNVX = False
type FieldIsArray "maxObjectEntryCounts" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldIsArray "minCommandsTokenBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldIsArray "minCommandsTokenBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX = False
type FieldIsArray "minSequenceCountBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldIsArray "minSequenceCountBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX = False
type FieldIsArray "minSequenceIndexBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldIsArray "minSequenceIndexBufferOffsetAlignment" VkDeviceGeneratedCommandsLimitsNVX = False
type FieldIsArray "pNext" VkDeviceGeneratedCommandsLimitsNVX Source # 
type FieldIsArray "sType" VkDeviceGeneratedCommandsLimitsNVX Source # 

data VkDeviceGroupBindSparseInfo Source #

typedef struct VkDeviceGroupBindSparseInfo {
    VkStructureType sType;
    const void*                      pNext;
    uint32_t                         resourceDeviceIndex;
    uint32_t                         memoryDeviceIndex;
} VkDeviceGroupBindSparseInfo;

VkDeviceGroupBindSparseInfo registry at www.khronos.org

Instances

Eq VkDeviceGroupBindSparseInfo Source # 
Ord VkDeviceGroupBindSparseInfo Source # 
Show VkDeviceGroupBindSparseInfo Source # 
Storable VkDeviceGroupBindSparseInfo Source # 
VulkanMarshalPrim VkDeviceGroupBindSparseInfo Source # 
VulkanMarshal VkDeviceGroupBindSparseInfo Source # 
CanWriteField "memoryDeviceIndex" VkDeviceGroupBindSparseInfo Source # 
CanWriteField "pNext" VkDeviceGroupBindSparseInfo Source # 
CanWriteField "resourceDeviceIndex" VkDeviceGroupBindSparseInfo Source # 
CanWriteField "sType" VkDeviceGroupBindSparseInfo Source # 
CanReadField "memoryDeviceIndex" VkDeviceGroupBindSparseInfo Source # 
CanReadField "pNext" VkDeviceGroupBindSparseInfo Source # 
CanReadField "resourceDeviceIndex" VkDeviceGroupBindSparseInfo Source # 
CanReadField "sType" VkDeviceGroupBindSparseInfo Source # 
HasField "memoryDeviceIndex" VkDeviceGroupBindSparseInfo Source # 

Associated Types

type FieldType ("memoryDeviceIndex" :: Symbol) VkDeviceGroupBindSparseInfo :: Type Source #

type FieldOptional ("memoryDeviceIndex" :: Symbol) VkDeviceGroupBindSparseInfo :: Bool Source #

type FieldOffset ("memoryDeviceIndex" :: Symbol) VkDeviceGroupBindSparseInfo :: Nat Source #

type FieldIsArray ("memoryDeviceIndex" :: Symbol) VkDeviceGroupBindSparseInfo :: Bool Source #

HasField "pNext" VkDeviceGroupBindSparseInfo Source # 
HasField "resourceDeviceIndex" VkDeviceGroupBindSparseInfo Source # 

Associated Types

type FieldType ("resourceDeviceIndex" :: Symbol) VkDeviceGroupBindSparseInfo :: Type Source #

type FieldOptional ("resourceDeviceIndex" :: Symbol) VkDeviceGroupBindSparseInfo :: Bool Source #

type FieldOffset ("resourceDeviceIndex" :: Symbol) VkDeviceGroupBindSparseInfo :: Nat Source #

type FieldIsArray ("resourceDeviceIndex" :: Symbol) VkDeviceGroupBindSparseInfo :: Bool Source #

HasField "sType" VkDeviceGroupBindSparseInfo Source # 
type StructFields VkDeviceGroupBindSparseInfo Source # 
type StructFields VkDeviceGroupBindSparseInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "resourceDeviceIndex" ((:) Symbol "memoryDeviceIndex" ([] Symbol))))
type CUnionType VkDeviceGroupBindSparseInfo Source # 
type ReturnedOnly VkDeviceGroupBindSparseInfo Source # 
type StructExtends VkDeviceGroupBindSparseInfo Source # 
type FieldType "memoryDeviceIndex" VkDeviceGroupBindSparseInfo Source # 
type FieldType "memoryDeviceIndex" VkDeviceGroupBindSparseInfo = Word32
type FieldType "pNext" VkDeviceGroupBindSparseInfo Source # 
type FieldType "resourceDeviceIndex" VkDeviceGroupBindSparseInfo Source # 
type FieldType "resourceDeviceIndex" VkDeviceGroupBindSparseInfo = Word32
type FieldType "sType" VkDeviceGroupBindSparseInfo Source # 
type FieldOptional "memoryDeviceIndex" VkDeviceGroupBindSparseInfo Source # 
type FieldOptional "pNext" VkDeviceGroupBindSparseInfo Source # 
type FieldOptional "resourceDeviceIndex" VkDeviceGroupBindSparseInfo Source # 
type FieldOptional "resourceDeviceIndex" VkDeviceGroupBindSparseInfo = False
type FieldOptional "sType" VkDeviceGroupBindSparseInfo Source # 
type FieldOffset "memoryDeviceIndex" VkDeviceGroupBindSparseInfo Source # 
type FieldOffset "memoryDeviceIndex" VkDeviceGroupBindSparseInfo = 20
type FieldOffset "pNext" VkDeviceGroupBindSparseInfo Source # 
type FieldOffset "resourceDeviceIndex" VkDeviceGroupBindSparseInfo Source # 
type FieldOffset "resourceDeviceIndex" VkDeviceGroupBindSparseInfo = 16
type FieldOffset "sType" VkDeviceGroupBindSparseInfo Source # 
type FieldIsArray "memoryDeviceIndex" VkDeviceGroupBindSparseInfo Source # 
type FieldIsArray "pNext" VkDeviceGroupBindSparseInfo Source # 
type FieldIsArray "resourceDeviceIndex" VkDeviceGroupBindSparseInfo Source # 
type FieldIsArray "resourceDeviceIndex" VkDeviceGroupBindSparseInfo = False
type FieldIsArray "sType" VkDeviceGroupBindSparseInfo Source # 

data VkDeviceGroupCommandBufferBeginInfo Source #

typedef struct VkDeviceGroupCommandBufferBeginInfo {
    VkStructureType sType;
    const void*                      pNext;
    uint32_t                         deviceMask;
} VkDeviceGroupCommandBufferBeginInfo;

VkDeviceGroupCommandBufferBeginInfo registry at www.khronos.org

Instances

Eq VkDeviceGroupCommandBufferBeginInfo Source # 
Ord VkDeviceGroupCommandBufferBeginInfo Source # 
Show VkDeviceGroupCommandBufferBeginInfo Source # 
Storable VkDeviceGroupCommandBufferBeginInfo Source # 
VulkanMarshalPrim VkDeviceGroupCommandBufferBeginInfo Source # 
VulkanMarshal VkDeviceGroupCommandBufferBeginInfo Source # 
CanWriteField "deviceMask" VkDeviceGroupCommandBufferBeginInfo Source # 
CanWriteField "pNext" VkDeviceGroupCommandBufferBeginInfo Source # 
CanWriteField "sType" VkDeviceGroupCommandBufferBeginInfo Source # 
CanReadField "deviceMask" VkDeviceGroupCommandBufferBeginInfo Source # 
CanReadField "pNext" VkDeviceGroupCommandBufferBeginInfo Source # 
CanReadField "sType" VkDeviceGroupCommandBufferBeginInfo Source # 
HasField "deviceMask" VkDeviceGroupCommandBufferBeginInfo Source # 
HasField "pNext" VkDeviceGroupCommandBufferBeginInfo Source # 
HasField "sType" VkDeviceGroupCommandBufferBeginInfo Source # 
type StructFields VkDeviceGroupCommandBufferBeginInfo Source # 
type StructFields VkDeviceGroupCommandBufferBeginInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "deviceMask" ([] Symbol)))
type CUnionType VkDeviceGroupCommandBufferBeginInfo Source # 
type ReturnedOnly VkDeviceGroupCommandBufferBeginInfo Source # 
type StructExtends VkDeviceGroupCommandBufferBeginInfo Source # 
type FieldType "deviceMask" VkDeviceGroupCommandBufferBeginInfo Source # 
type FieldType "pNext" VkDeviceGroupCommandBufferBeginInfo Source # 
type FieldType "sType" VkDeviceGroupCommandBufferBeginInfo Source # 
type FieldOptional "deviceMask" VkDeviceGroupCommandBufferBeginInfo Source # 
type FieldOptional "pNext" VkDeviceGroupCommandBufferBeginInfo Source # 
type FieldOptional "sType" VkDeviceGroupCommandBufferBeginInfo Source # 
type FieldOffset "deviceMask" VkDeviceGroupCommandBufferBeginInfo Source # 
type FieldOffset "pNext" VkDeviceGroupCommandBufferBeginInfo Source # 
type FieldOffset "sType" VkDeviceGroupCommandBufferBeginInfo Source # 
type FieldIsArray "deviceMask" VkDeviceGroupCommandBufferBeginInfo Source # 
type FieldIsArray "pNext" VkDeviceGroupCommandBufferBeginInfo Source # 
type FieldIsArray "sType" VkDeviceGroupCommandBufferBeginInfo Source # 

data VkDeviceGroupDeviceCreateInfo Source #

typedef struct VkDeviceGroupDeviceCreateInfo {
    VkStructureType sType;
    const void*                      pNext;
    uint32_t                         physicalDeviceCount;
    const VkPhysicalDevice*  pPhysicalDevices;
} VkDeviceGroupDeviceCreateInfo;

VkDeviceGroupDeviceCreateInfo registry at www.khronos.org

Instances

Eq VkDeviceGroupDeviceCreateInfo Source # 
Ord VkDeviceGroupDeviceCreateInfo Source # 
Show VkDeviceGroupDeviceCreateInfo Source # 
Storable VkDeviceGroupDeviceCreateInfo Source # 
VulkanMarshalPrim VkDeviceGroupDeviceCreateInfo Source # 
VulkanMarshal VkDeviceGroupDeviceCreateInfo Source # 
CanWriteField "pNext" VkDeviceGroupDeviceCreateInfo Source # 
CanWriteField "pPhysicalDevices" VkDeviceGroupDeviceCreateInfo Source # 
CanWriteField "physicalDeviceCount" VkDeviceGroupDeviceCreateInfo Source # 
CanWriteField "sType" VkDeviceGroupDeviceCreateInfo Source # 
CanReadField "pNext" VkDeviceGroupDeviceCreateInfo Source # 
CanReadField "pPhysicalDevices" VkDeviceGroupDeviceCreateInfo Source # 
CanReadField "physicalDeviceCount" VkDeviceGroupDeviceCreateInfo Source # 
CanReadField "sType" VkDeviceGroupDeviceCreateInfo Source # 
HasField "pNext" VkDeviceGroupDeviceCreateInfo Source # 
HasField "pPhysicalDevices" VkDeviceGroupDeviceCreateInfo Source # 

Associated Types

type FieldType ("pPhysicalDevices" :: Symbol) VkDeviceGroupDeviceCreateInfo :: Type Source #

type FieldOptional ("pPhysicalDevices" :: Symbol) VkDeviceGroupDeviceCreateInfo :: Bool Source #

type FieldOffset ("pPhysicalDevices" :: Symbol) VkDeviceGroupDeviceCreateInfo :: Nat Source #

type FieldIsArray ("pPhysicalDevices" :: Symbol) VkDeviceGroupDeviceCreateInfo :: Bool Source #

HasField "physicalDeviceCount" VkDeviceGroupDeviceCreateInfo Source # 

Associated Types

type FieldType ("physicalDeviceCount" :: Symbol) VkDeviceGroupDeviceCreateInfo :: Type Source #

type FieldOptional ("physicalDeviceCount" :: Symbol) VkDeviceGroupDeviceCreateInfo :: Bool Source #

type FieldOffset ("physicalDeviceCount" :: Symbol) VkDeviceGroupDeviceCreateInfo :: Nat Source #

type FieldIsArray ("physicalDeviceCount" :: Symbol) VkDeviceGroupDeviceCreateInfo :: Bool Source #

HasField "sType" VkDeviceGroupDeviceCreateInfo Source # 
type StructFields VkDeviceGroupDeviceCreateInfo Source # 
type StructFields VkDeviceGroupDeviceCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "physicalDeviceCount" ((:) Symbol "pPhysicalDevices" ([] Symbol))))
type CUnionType VkDeviceGroupDeviceCreateInfo Source # 
type ReturnedOnly VkDeviceGroupDeviceCreateInfo Source # 
type StructExtends VkDeviceGroupDeviceCreateInfo Source # 
type FieldType "pNext" VkDeviceGroupDeviceCreateInfo Source # 
type FieldType "pPhysicalDevices" VkDeviceGroupDeviceCreateInfo Source # 
type FieldType "physicalDeviceCount" VkDeviceGroupDeviceCreateInfo Source # 
type FieldType "physicalDeviceCount" VkDeviceGroupDeviceCreateInfo = Word32
type FieldType "sType" VkDeviceGroupDeviceCreateInfo Source # 
type FieldOptional "pNext" VkDeviceGroupDeviceCreateInfo Source # 
type FieldOptional "pPhysicalDevices" VkDeviceGroupDeviceCreateInfo Source # 
type FieldOptional "physicalDeviceCount" VkDeviceGroupDeviceCreateInfo Source # 
type FieldOptional "physicalDeviceCount" VkDeviceGroupDeviceCreateInfo = True
type FieldOptional "sType" VkDeviceGroupDeviceCreateInfo Source # 
type FieldOffset "pNext" VkDeviceGroupDeviceCreateInfo Source # 
type FieldOffset "pPhysicalDevices" VkDeviceGroupDeviceCreateInfo Source # 
type FieldOffset "pPhysicalDevices" VkDeviceGroupDeviceCreateInfo = 24
type FieldOffset "physicalDeviceCount" VkDeviceGroupDeviceCreateInfo Source # 
type FieldOffset "physicalDeviceCount" VkDeviceGroupDeviceCreateInfo = 16
type FieldOffset "sType" VkDeviceGroupDeviceCreateInfo Source # 
type FieldIsArray "pNext" VkDeviceGroupDeviceCreateInfo Source # 
type FieldIsArray "pPhysicalDevices" VkDeviceGroupDeviceCreateInfo Source # 
type FieldIsArray "physicalDeviceCount" VkDeviceGroupDeviceCreateInfo Source # 
type FieldIsArray "physicalDeviceCount" VkDeviceGroupDeviceCreateInfo = False
type FieldIsArray "sType" VkDeviceGroupDeviceCreateInfo Source # 

data VkDeviceGroupPresentCapabilitiesKHR Source #

typedef struct VkDeviceGroupPresentCapabilitiesKHR {
    VkStructureType sType;
    const void*                      pNext;
    uint32_t                         presentMask[VK_MAX_DEVICE_GROUP_SIZE];
    VkDeviceGroupPresentModeFlagsKHR modes;
} VkDeviceGroupPresentCapabilitiesKHR;

VkDeviceGroupPresentCapabilitiesKHR registry at www.khronos.org

Instances

Eq VkDeviceGroupPresentCapabilitiesKHR Source # 
Ord VkDeviceGroupPresentCapabilitiesKHR Source # 
Show VkDeviceGroupPresentCapabilitiesKHR Source # 
Storable VkDeviceGroupPresentCapabilitiesKHR Source # 
VulkanMarshalPrim VkDeviceGroupPresentCapabilitiesKHR Source # 
VulkanMarshal VkDeviceGroupPresentCapabilitiesKHR Source # 
CanWriteField "modes" VkDeviceGroupPresentCapabilitiesKHR Source # 
CanWriteField "pNext" VkDeviceGroupPresentCapabilitiesKHR Source # 
CanWriteField "sType" VkDeviceGroupPresentCapabilitiesKHR Source # 
CanReadField "modes" VkDeviceGroupPresentCapabilitiesKHR Source # 
CanReadField "pNext" VkDeviceGroupPresentCapabilitiesKHR Source # 
CanReadField "sType" VkDeviceGroupPresentCapabilitiesKHR Source # 
HasField "modes" VkDeviceGroupPresentCapabilitiesKHR Source # 
HasField "pNext" VkDeviceGroupPresentCapabilitiesKHR Source # 
HasField "presentMask" VkDeviceGroupPresentCapabilitiesKHR Source # 
HasField "sType" VkDeviceGroupPresentCapabilitiesKHR Source # 
(KnownNat idx, IndexInBounds "presentMask" idx VkDeviceGroupPresentCapabilitiesKHR) => CanWriteFieldArray "presentMask" idx VkDeviceGroupPresentCapabilitiesKHR Source # 
(KnownNat idx, IndexInBounds "presentMask" idx VkDeviceGroupPresentCapabilitiesKHR) => CanReadFieldArray "presentMask" idx VkDeviceGroupPresentCapabilitiesKHR Source # 
type StructFields VkDeviceGroupPresentCapabilitiesKHR Source # 
type StructFields VkDeviceGroupPresentCapabilitiesKHR = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "presentMask" ((:) Symbol "modes" ([] Symbol))))
type CUnionType VkDeviceGroupPresentCapabilitiesKHR Source # 
type ReturnedOnly VkDeviceGroupPresentCapabilitiesKHR Source # 
type StructExtends VkDeviceGroupPresentCapabilitiesKHR Source # 
type FieldArrayLength "presentMask" VkDeviceGroupPresentCapabilitiesKHR Source # 
type FieldType "modes" VkDeviceGroupPresentCapabilitiesKHR Source # 
type FieldType "pNext" VkDeviceGroupPresentCapabilitiesKHR Source # 
type FieldType "presentMask" VkDeviceGroupPresentCapabilitiesKHR Source # 
type FieldType "sType" VkDeviceGroupPresentCapabilitiesKHR Source # 
type FieldOptional "modes" VkDeviceGroupPresentCapabilitiesKHR Source # 
type FieldOptional "pNext" VkDeviceGroupPresentCapabilitiesKHR Source # 
type FieldOptional "presentMask" VkDeviceGroupPresentCapabilitiesKHR Source # 
type FieldOptional "sType" VkDeviceGroupPresentCapabilitiesKHR Source # 
type FieldOffset "modes" VkDeviceGroupPresentCapabilitiesKHR Source # 
type FieldOffset "pNext" VkDeviceGroupPresentCapabilitiesKHR Source # 
type FieldOffset "presentMask" VkDeviceGroupPresentCapabilitiesKHR Source # 
type FieldOffset "sType" VkDeviceGroupPresentCapabilitiesKHR Source # 
type FieldIsArray "modes" VkDeviceGroupPresentCapabilitiesKHR Source # 
type FieldIsArray "pNext" VkDeviceGroupPresentCapabilitiesKHR Source # 
type FieldIsArray "presentMask" VkDeviceGroupPresentCapabilitiesKHR Source # 
type FieldIsArray "sType" VkDeviceGroupPresentCapabilitiesKHR Source # 

data VkDeviceGroupPresentInfoKHR Source #

typedef struct VkDeviceGroupPresentInfoKHR {
    VkStructureType sType;
    const void*                      pNext;
    uint32_t         swapchainCount;
    const uint32_t* pDeviceMasks;
    VkDeviceGroupPresentModeFlagBitsKHR mode;
} VkDeviceGroupPresentInfoKHR;

VkDeviceGroupPresentInfoKHR registry at www.khronos.org

Instances

Eq VkDeviceGroupPresentInfoKHR Source # 
Ord VkDeviceGroupPresentInfoKHR Source # 
Show VkDeviceGroupPresentInfoKHR Source # 
Storable VkDeviceGroupPresentInfoKHR Source # 
VulkanMarshalPrim VkDeviceGroupPresentInfoKHR Source # 
VulkanMarshal VkDeviceGroupPresentInfoKHR Source # 
CanWriteField "mode" VkDeviceGroupPresentInfoKHR Source # 
CanWriteField "pDeviceMasks" VkDeviceGroupPresentInfoKHR Source # 
CanWriteField "pNext" VkDeviceGroupPresentInfoKHR Source # 
CanWriteField "sType" VkDeviceGroupPresentInfoKHR Source # 
CanWriteField "swapchainCount" VkDeviceGroupPresentInfoKHR Source # 
CanReadField "mode" VkDeviceGroupPresentInfoKHR Source # 
CanReadField "pDeviceMasks" VkDeviceGroupPresentInfoKHR Source # 
CanReadField "pNext" VkDeviceGroupPresentInfoKHR Source # 
CanReadField "sType" VkDeviceGroupPresentInfoKHR Source # 
CanReadField "swapchainCount" VkDeviceGroupPresentInfoKHR Source # 
HasField "mode" VkDeviceGroupPresentInfoKHR Source # 
HasField "pDeviceMasks" VkDeviceGroupPresentInfoKHR Source # 
HasField "pNext" VkDeviceGroupPresentInfoKHR Source # 
HasField "sType" VkDeviceGroupPresentInfoKHR Source # 
HasField "swapchainCount" VkDeviceGroupPresentInfoKHR Source # 
type StructFields VkDeviceGroupPresentInfoKHR Source # 
type StructFields VkDeviceGroupPresentInfoKHR = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "swapchainCount" ((:) Symbol "pDeviceMasks" ((:) Symbol "mode" ([] Symbol)))))
type CUnionType VkDeviceGroupPresentInfoKHR Source # 
type ReturnedOnly VkDeviceGroupPresentInfoKHR Source # 
type StructExtends VkDeviceGroupPresentInfoKHR Source # 
type FieldType "mode" VkDeviceGroupPresentInfoKHR Source # 
type FieldType "pDeviceMasks" VkDeviceGroupPresentInfoKHR Source # 
type FieldType "pNext" VkDeviceGroupPresentInfoKHR Source # 
type FieldType "sType" VkDeviceGroupPresentInfoKHR Source # 
type FieldType "swapchainCount" VkDeviceGroupPresentInfoKHR Source # 
type FieldOptional "mode" VkDeviceGroupPresentInfoKHR Source # 
type FieldOptional "pDeviceMasks" VkDeviceGroupPresentInfoKHR Source # 
type FieldOptional "pNext" VkDeviceGroupPresentInfoKHR Source # 
type FieldOptional "sType" VkDeviceGroupPresentInfoKHR Source # 
type FieldOptional "swapchainCount" VkDeviceGroupPresentInfoKHR Source # 
type FieldOffset "mode" VkDeviceGroupPresentInfoKHR Source # 
type FieldOffset "pDeviceMasks" VkDeviceGroupPresentInfoKHR Source # 
type FieldOffset "pDeviceMasks" VkDeviceGroupPresentInfoKHR = 24
type FieldOffset "pNext" VkDeviceGroupPresentInfoKHR Source # 
type FieldOffset "sType" VkDeviceGroupPresentInfoKHR Source # 
type FieldOffset "swapchainCount" VkDeviceGroupPresentInfoKHR Source # 
type FieldOffset "swapchainCount" VkDeviceGroupPresentInfoKHR = 16
type FieldIsArray "mode" VkDeviceGroupPresentInfoKHR Source # 
type FieldIsArray "pDeviceMasks" VkDeviceGroupPresentInfoKHR Source # 
type FieldIsArray "pNext" VkDeviceGroupPresentInfoKHR Source # 
type FieldIsArray "sType" VkDeviceGroupPresentInfoKHR Source # 
type FieldIsArray "swapchainCount" VkDeviceGroupPresentInfoKHR Source # 

data VkDeviceGroupRenderPassBeginInfo Source #

typedef struct VkDeviceGroupRenderPassBeginInfo {
    VkStructureType sType;
    const void*                      pNext;
    uint32_t                         deviceMask;
    uint32_t         deviceRenderAreaCount;
    const VkRect2D*  pDeviceRenderAreas;
} VkDeviceGroupRenderPassBeginInfo;

VkDeviceGroupRenderPassBeginInfo registry at www.khronos.org

Instances

Eq VkDeviceGroupRenderPassBeginInfo Source # 
Ord VkDeviceGroupRenderPassBeginInfo Source # 
Show VkDeviceGroupRenderPassBeginInfo Source # 
Storable VkDeviceGroupRenderPassBeginInfo Source # 
VulkanMarshalPrim VkDeviceGroupRenderPassBeginInfo Source # 
VulkanMarshal VkDeviceGroupRenderPassBeginInfo Source # 
CanWriteField "deviceMask" VkDeviceGroupRenderPassBeginInfo Source # 
CanWriteField "deviceRenderAreaCount" VkDeviceGroupRenderPassBeginInfo Source # 
CanWriteField "pDeviceRenderAreas" VkDeviceGroupRenderPassBeginInfo Source # 
CanWriteField "pNext" VkDeviceGroupRenderPassBeginInfo Source # 
CanWriteField "sType" VkDeviceGroupRenderPassBeginInfo Source # 
CanReadField "deviceMask" VkDeviceGroupRenderPassBeginInfo Source # 
CanReadField "deviceRenderAreaCount" VkDeviceGroupRenderPassBeginInfo Source # 
CanReadField "pDeviceRenderAreas" VkDeviceGroupRenderPassBeginInfo Source # 
CanReadField "pNext" VkDeviceGroupRenderPassBeginInfo Source # 
CanReadField "sType" VkDeviceGroupRenderPassBeginInfo Source # 
HasField "deviceMask" VkDeviceGroupRenderPassBeginInfo Source # 
HasField "deviceRenderAreaCount" VkDeviceGroupRenderPassBeginInfo Source # 

Associated Types

type FieldType ("deviceRenderAreaCount" :: Symbol) VkDeviceGroupRenderPassBeginInfo :: Type Source #

type FieldOptional ("deviceRenderAreaCount" :: Symbol) VkDeviceGroupRenderPassBeginInfo :: Bool Source #

type FieldOffset ("deviceRenderAreaCount" :: Symbol) VkDeviceGroupRenderPassBeginInfo :: Nat Source #

type FieldIsArray ("deviceRenderAreaCount" :: Symbol) VkDeviceGroupRenderPassBeginInfo :: Bool Source #

HasField "pDeviceRenderAreas" VkDeviceGroupRenderPassBeginInfo Source # 

Associated Types

type FieldType ("pDeviceRenderAreas" :: Symbol) VkDeviceGroupRenderPassBeginInfo :: Type Source #

type FieldOptional ("pDeviceRenderAreas" :: Symbol) VkDeviceGroupRenderPassBeginInfo :: Bool Source #

type FieldOffset ("pDeviceRenderAreas" :: Symbol) VkDeviceGroupRenderPassBeginInfo :: Nat Source #

type FieldIsArray ("pDeviceRenderAreas" :: Symbol) VkDeviceGroupRenderPassBeginInfo :: Bool Source #

HasField "pNext" VkDeviceGroupRenderPassBeginInfo Source # 
HasField "sType" VkDeviceGroupRenderPassBeginInfo Source # 
type StructFields VkDeviceGroupRenderPassBeginInfo Source # 
type StructFields VkDeviceGroupRenderPassBeginInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "deviceMask" ((:) Symbol "deviceRenderAreaCount" ((:) Symbol "pDeviceRenderAreas" ([] Symbol)))))
type CUnionType VkDeviceGroupRenderPassBeginInfo Source # 
type ReturnedOnly VkDeviceGroupRenderPassBeginInfo Source # 
type StructExtends VkDeviceGroupRenderPassBeginInfo Source # 
type FieldType "deviceMask" VkDeviceGroupRenderPassBeginInfo Source # 
type FieldType "deviceRenderAreaCount" VkDeviceGroupRenderPassBeginInfo Source # 
type FieldType "deviceRenderAreaCount" VkDeviceGroupRenderPassBeginInfo = Word32
type FieldType "pDeviceRenderAreas" VkDeviceGroupRenderPassBeginInfo Source # 
type FieldType "pNext" VkDeviceGroupRenderPassBeginInfo Source # 
type FieldType "sType" VkDeviceGroupRenderPassBeginInfo Source # 
type FieldOptional "deviceMask" VkDeviceGroupRenderPassBeginInfo Source # 
type FieldOptional "deviceRenderAreaCount" VkDeviceGroupRenderPassBeginInfo Source # 
type FieldOptional "deviceRenderAreaCount" VkDeviceGroupRenderPassBeginInfo = True
type FieldOptional "pDeviceRenderAreas" VkDeviceGroupRenderPassBeginInfo Source # 
type FieldOptional "pNext" VkDeviceGroupRenderPassBeginInfo Source # 
type FieldOptional "sType" VkDeviceGroupRenderPassBeginInfo Source # 
type FieldOffset "deviceMask" VkDeviceGroupRenderPassBeginInfo Source # 
type FieldOffset "deviceRenderAreaCount" VkDeviceGroupRenderPassBeginInfo Source # 
type FieldOffset "deviceRenderAreaCount" VkDeviceGroupRenderPassBeginInfo = 20
type FieldOffset "pDeviceRenderAreas" VkDeviceGroupRenderPassBeginInfo Source # 
type FieldOffset "pDeviceRenderAreas" VkDeviceGroupRenderPassBeginInfo = 24
type FieldOffset "pNext" VkDeviceGroupRenderPassBeginInfo Source # 
type FieldOffset "sType" VkDeviceGroupRenderPassBeginInfo Source # 
type FieldIsArray "deviceMask" VkDeviceGroupRenderPassBeginInfo Source # 
type FieldIsArray "deviceRenderAreaCount" VkDeviceGroupRenderPassBeginInfo Source # 
type FieldIsArray "deviceRenderAreaCount" VkDeviceGroupRenderPassBeginInfo = False
type FieldIsArray "pDeviceRenderAreas" VkDeviceGroupRenderPassBeginInfo Source # 
type FieldIsArray "pNext" VkDeviceGroupRenderPassBeginInfo Source # 
type FieldIsArray "sType" VkDeviceGroupRenderPassBeginInfo Source # 

data VkDeviceGroupSubmitInfo Source #

typedef struct VkDeviceGroupSubmitInfo {
    VkStructureType sType;
    const void*                      pNext;
    uint32_t         waitSemaphoreCount;
    const uint32_t*    pWaitSemaphoreDeviceIndices;
    uint32_t         commandBufferCount;
    const uint32_t*    pCommandBufferDeviceMasks;
    uint32_t         signalSemaphoreCount;
    const uint32_t*  pSignalSemaphoreDeviceIndices;
} VkDeviceGroupSubmitInfo;

VkDeviceGroupSubmitInfo registry at www.khronos.org

Instances

Eq VkDeviceGroupSubmitInfo Source # 
Ord VkDeviceGroupSubmitInfo Source # 
Show VkDeviceGroupSubmitInfo Source # 
Storable VkDeviceGroupSubmitInfo Source # 
VulkanMarshalPrim VkDeviceGroupSubmitInfo Source # 
VulkanMarshal VkDeviceGroupSubmitInfo Source # 
CanWriteField "commandBufferCount" VkDeviceGroupSubmitInfo Source # 
CanWriteField "pCommandBufferDeviceMasks" VkDeviceGroupSubmitInfo Source # 

Methods

writeField :: Ptr VkDeviceGroupSubmitInfo -> FieldType "pCommandBufferDeviceMasks" VkDeviceGroupSubmitInfo -> IO () Source #

CanWriteField "pNext" VkDeviceGroupSubmitInfo Source # 
CanWriteField "pSignalSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo Source # 

Methods

writeField :: Ptr VkDeviceGroupSubmitInfo -> FieldType "pSignalSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo -> IO () Source #

CanWriteField "pWaitSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo Source # 

Methods

writeField :: Ptr VkDeviceGroupSubmitInfo -> FieldType "pWaitSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo -> IO () Source #

CanWriteField "sType" VkDeviceGroupSubmitInfo Source # 
CanWriteField "signalSemaphoreCount" VkDeviceGroupSubmitInfo Source # 
CanWriteField "waitSemaphoreCount" VkDeviceGroupSubmitInfo Source # 
CanReadField "commandBufferCount" VkDeviceGroupSubmitInfo Source # 
CanReadField "pCommandBufferDeviceMasks" VkDeviceGroupSubmitInfo Source # 
CanReadField "pNext" VkDeviceGroupSubmitInfo Source # 
CanReadField "pSignalSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo Source # 
CanReadField "pWaitSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo Source # 
CanReadField "sType" VkDeviceGroupSubmitInfo Source # 
CanReadField "signalSemaphoreCount" VkDeviceGroupSubmitInfo Source # 
CanReadField "waitSemaphoreCount" VkDeviceGroupSubmitInfo Source # 
HasField "commandBufferCount" VkDeviceGroupSubmitInfo Source # 

Associated Types

type FieldType ("commandBufferCount" :: Symbol) VkDeviceGroupSubmitInfo :: Type Source #

type FieldOptional ("commandBufferCount" :: Symbol) VkDeviceGroupSubmitInfo :: Bool Source #

type FieldOffset ("commandBufferCount" :: Symbol) VkDeviceGroupSubmitInfo :: Nat Source #

type FieldIsArray ("commandBufferCount" :: Symbol) VkDeviceGroupSubmitInfo :: Bool Source #

HasField "pCommandBufferDeviceMasks" VkDeviceGroupSubmitInfo Source # 

Associated Types

type FieldType ("pCommandBufferDeviceMasks" :: Symbol) VkDeviceGroupSubmitInfo :: Type Source #

type FieldOptional ("pCommandBufferDeviceMasks" :: Symbol) VkDeviceGroupSubmitInfo :: Bool Source #

type FieldOffset ("pCommandBufferDeviceMasks" :: Symbol) VkDeviceGroupSubmitInfo :: Nat Source #

type FieldIsArray ("pCommandBufferDeviceMasks" :: Symbol) VkDeviceGroupSubmitInfo :: Bool Source #

HasField "pNext" VkDeviceGroupSubmitInfo Source # 
HasField "pSignalSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo Source # 

Associated Types

type FieldType ("pSignalSemaphoreDeviceIndices" :: Symbol) VkDeviceGroupSubmitInfo :: Type Source #

type FieldOptional ("pSignalSemaphoreDeviceIndices" :: Symbol) VkDeviceGroupSubmitInfo :: Bool Source #

type FieldOffset ("pSignalSemaphoreDeviceIndices" :: Symbol) VkDeviceGroupSubmitInfo :: Nat Source #

type FieldIsArray ("pSignalSemaphoreDeviceIndices" :: Symbol) VkDeviceGroupSubmitInfo :: Bool Source #

HasField "pWaitSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo Source # 

Associated Types

type FieldType ("pWaitSemaphoreDeviceIndices" :: Symbol) VkDeviceGroupSubmitInfo :: Type Source #

type FieldOptional ("pWaitSemaphoreDeviceIndices" :: Symbol) VkDeviceGroupSubmitInfo :: Bool Source #

type FieldOffset ("pWaitSemaphoreDeviceIndices" :: Symbol) VkDeviceGroupSubmitInfo :: Nat Source #

type FieldIsArray ("pWaitSemaphoreDeviceIndices" :: Symbol) VkDeviceGroupSubmitInfo :: Bool Source #

HasField "sType" VkDeviceGroupSubmitInfo Source # 
HasField "signalSemaphoreCount" VkDeviceGroupSubmitInfo Source # 

Associated Types

type FieldType ("signalSemaphoreCount" :: Symbol) VkDeviceGroupSubmitInfo :: Type Source #

type FieldOptional ("signalSemaphoreCount" :: Symbol) VkDeviceGroupSubmitInfo :: Bool Source #

type FieldOffset ("signalSemaphoreCount" :: Symbol) VkDeviceGroupSubmitInfo :: Nat Source #

type FieldIsArray ("signalSemaphoreCount" :: Symbol) VkDeviceGroupSubmitInfo :: Bool Source #

HasField "waitSemaphoreCount" VkDeviceGroupSubmitInfo Source # 

Associated Types

type FieldType ("waitSemaphoreCount" :: Symbol) VkDeviceGroupSubmitInfo :: Type Source #

type FieldOptional ("waitSemaphoreCount" :: Symbol) VkDeviceGroupSubmitInfo :: Bool Source #

type FieldOffset ("waitSemaphoreCount" :: Symbol) VkDeviceGroupSubmitInfo :: Nat Source #

type FieldIsArray ("waitSemaphoreCount" :: Symbol) VkDeviceGroupSubmitInfo :: Bool Source #

type StructFields VkDeviceGroupSubmitInfo Source # 
type StructFields VkDeviceGroupSubmitInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "waitSemaphoreCount" ((:) Symbol "pWaitSemaphoreDeviceIndices" ((:) Symbol "commandBufferCount" ((:) Symbol "pCommandBufferDeviceMasks" ((:) Symbol "signalSemaphoreCount" ((:) Symbol "pSignalSemaphoreDeviceIndices" ([] Symbol))))))))
type CUnionType VkDeviceGroupSubmitInfo Source # 
type ReturnedOnly VkDeviceGroupSubmitInfo Source # 
type StructExtends VkDeviceGroupSubmitInfo Source # 
type FieldType "commandBufferCount" VkDeviceGroupSubmitInfo Source # 
type FieldType "commandBufferCount" VkDeviceGroupSubmitInfo = Word32
type FieldType "pCommandBufferDeviceMasks" VkDeviceGroupSubmitInfo Source # 
type FieldType "pCommandBufferDeviceMasks" VkDeviceGroupSubmitInfo = Ptr Word32
type FieldType "pNext" VkDeviceGroupSubmitInfo Source # 
type FieldType "pSignalSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo Source # 
type FieldType "pSignalSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo = Ptr Word32
type FieldType "pWaitSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo Source # 
type FieldType "pWaitSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo = Ptr Word32
type FieldType "sType" VkDeviceGroupSubmitInfo Source # 
type FieldType "signalSemaphoreCount" VkDeviceGroupSubmitInfo Source # 
type FieldType "signalSemaphoreCount" VkDeviceGroupSubmitInfo = Word32
type FieldType "waitSemaphoreCount" VkDeviceGroupSubmitInfo Source # 
type FieldType "waitSemaphoreCount" VkDeviceGroupSubmitInfo = Word32
type FieldOptional "commandBufferCount" VkDeviceGroupSubmitInfo Source # 
type FieldOptional "commandBufferCount" VkDeviceGroupSubmitInfo = True
type FieldOptional "pCommandBufferDeviceMasks" VkDeviceGroupSubmitInfo Source # 
type FieldOptional "pCommandBufferDeviceMasks" VkDeviceGroupSubmitInfo = False
type FieldOptional "pNext" VkDeviceGroupSubmitInfo Source # 
type FieldOptional "pSignalSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo Source # 
type FieldOptional "pSignalSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo = False
type FieldOptional "pWaitSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo Source # 
type FieldOptional "pWaitSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo = False
type FieldOptional "sType" VkDeviceGroupSubmitInfo Source # 
type FieldOptional "signalSemaphoreCount" VkDeviceGroupSubmitInfo Source # 
type FieldOptional "signalSemaphoreCount" VkDeviceGroupSubmitInfo = True
type FieldOptional "waitSemaphoreCount" VkDeviceGroupSubmitInfo Source # 
type FieldOptional "waitSemaphoreCount" VkDeviceGroupSubmitInfo = True
type FieldOffset "commandBufferCount" VkDeviceGroupSubmitInfo Source # 
type FieldOffset "commandBufferCount" VkDeviceGroupSubmitInfo = 32
type FieldOffset "pCommandBufferDeviceMasks" VkDeviceGroupSubmitInfo Source # 
type FieldOffset "pCommandBufferDeviceMasks" VkDeviceGroupSubmitInfo = 40
type FieldOffset "pNext" VkDeviceGroupSubmitInfo Source # 
type FieldOffset "pSignalSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo Source # 
type FieldOffset "pSignalSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo = 56
type FieldOffset "pWaitSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo Source # 
type FieldOffset "pWaitSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo = 24
type FieldOffset "sType" VkDeviceGroupSubmitInfo Source # 
type FieldOffset "signalSemaphoreCount" VkDeviceGroupSubmitInfo Source # 
type FieldOffset "signalSemaphoreCount" VkDeviceGroupSubmitInfo = 48
type FieldOffset "waitSemaphoreCount" VkDeviceGroupSubmitInfo Source # 
type FieldOffset "waitSemaphoreCount" VkDeviceGroupSubmitInfo = 16
type FieldIsArray "commandBufferCount" VkDeviceGroupSubmitInfo Source # 
type FieldIsArray "commandBufferCount" VkDeviceGroupSubmitInfo = False
type FieldIsArray "pCommandBufferDeviceMasks" VkDeviceGroupSubmitInfo Source # 
type FieldIsArray "pCommandBufferDeviceMasks" VkDeviceGroupSubmitInfo = False
type FieldIsArray "pNext" VkDeviceGroupSubmitInfo Source # 
type FieldIsArray "pSignalSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo Source # 
type FieldIsArray "pSignalSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo = False
type FieldIsArray "pWaitSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo Source # 
type FieldIsArray "pWaitSemaphoreDeviceIndices" VkDeviceGroupSubmitInfo = False
type FieldIsArray "sType" VkDeviceGroupSubmitInfo Source # 
type FieldIsArray "signalSemaphoreCount" VkDeviceGroupSubmitInfo Source # 
type FieldIsArray "signalSemaphoreCount" VkDeviceGroupSubmitInfo = False
type FieldIsArray "waitSemaphoreCount" VkDeviceGroupSubmitInfo Source # 
type FieldIsArray "waitSemaphoreCount" VkDeviceGroupSubmitInfo = False

data VkDeviceGroupSwapchainCreateInfoKHR Source #

typedef struct VkDeviceGroupSwapchainCreateInfoKHR {
    VkStructureType sType;
    const void*                      pNext;
    VkDeviceGroupPresentModeFlagsKHR                         modes;
} VkDeviceGroupSwapchainCreateInfoKHR;

VkDeviceGroupSwapchainCreateInfoKHR registry at www.khronos.org

Instances

Eq VkDeviceGroupSwapchainCreateInfoKHR Source # 
Ord VkDeviceGroupSwapchainCreateInfoKHR Source # 
Show VkDeviceGroupSwapchainCreateInfoKHR Source # 
Storable VkDeviceGroupSwapchainCreateInfoKHR Source # 
VulkanMarshalPrim VkDeviceGroupSwapchainCreateInfoKHR Source # 
VulkanMarshal VkDeviceGroupSwapchainCreateInfoKHR Source # 
CanWriteField "modes" VkDeviceGroupSwapchainCreateInfoKHR Source # 
CanWriteField "pNext" VkDeviceGroupSwapchainCreateInfoKHR Source # 
CanWriteField "sType" VkDeviceGroupSwapchainCreateInfoKHR Source # 
CanReadField "modes" VkDeviceGroupSwapchainCreateInfoKHR Source # 
CanReadField "pNext" VkDeviceGroupSwapchainCreateInfoKHR Source # 
CanReadField "sType" VkDeviceGroupSwapchainCreateInfoKHR Source # 
HasField "modes" VkDeviceGroupSwapchainCreateInfoKHR Source # 
HasField "pNext" VkDeviceGroupSwapchainCreateInfoKHR Source # 
HasField "sType" VkDeviceGroupSwapchainCreateInfoKHR Source # 
type StructFields VkDeviceGroupSwapchainCreateInfoKHR Source # 
type StructFields VkDeviceGroupSwapchainCreateInfoKHR = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "modes" ([] Symbol)))
type CUnionType VkDeviceGroupSwapchainCreateInfoKHR Source # 
type ReturnedOnly VkDeviceGroupSwapchainCreateInfoKHR Source # 
type StructExtends VkDeviceGroupSwapchainCreateInfoKHR Source # 
type FieldType "modes" VkDeviceGroupSwapchainCreateInfoKHR Source # 
type FieldType "pNext" VkDeviceGroupSwapchainCreateInfoKHR Source # 
type FieldType "sType" VkDeviceGroupSwapchainCreateInfoKHR Source # 
type FieldOptional "modes" VkDeviceGroupSwapchainCreateInfoKHR Source # 
type FieldOptional "pNext" VkDeviceGroupSwapchainCreateInfoKHR Source # 
type FieldOptional "sType" VkDeviceGroupSwapchainCreateInfoKHR Source # 
type FieldOffset "modes" VkDeviceGroupSwapchainCreateInfoKHR Source # 
type FieldOffset "pNext" VkDeviceGroupSwapchainCreateInfoKHR Source # 
type FieldOffset "sType" VkDeviceGroupSwapchainCreateInfoKHR Source # 
type FieldIsArray "modes" VkDeviceGroupSwapchainCreateInfoKHR Source # 
type FieldIsArray "pNext" VkDeviceGroupSwapchainCreateInfoKHR Source # 
type FieldIsArray "sType" VkDeviceGroupSwapchainCreateInfoKHR Source # 

data VkDeviceQueueCreateInfo Source #

typedef struct VkDeviceQueueCreateInfo {
    VkStructureType sType;
    const void*     pNext;
    VkDeviceQueueCreateFlags    flags;
    uint32_t        queueFamilyIndex;
    uint32_t        queueCount;
    const float*    pQueuePriorities;
} VkDeviceQueueCreateInfo;

VkDeviceQueueCreateInfo registry at www.khronos.org

Instances

Eq VkDeviceQueueCreateInfo Source # 
Ord VkDeviceQueueCreateInfo Source # 
Show VkDeviceQueueCreateInfo Source # 
Storable VkDeviceQueueCreateInfo Source # 
VulkanMarshalPrim VkDeviceQueueCreateInfo Source # 
VulkanMarshal VkDeviceQueueCreateInfo Source # 
CanWriteField "flags" VkDeviceQueueCreateInfo Source # 
CanWriteField "pNext" VkDeviceQueueCreateInfo Source # 
CanWriteField "pQueuePriorities" VkDeviceQueueCreateInfo Source # 
CanWriteField "queueCount" VkDeviceQueueCreateInfo Source # 
CanWriteField "queueFamilyIndex" VkDeviceQueueCreateInfo Source # 
CanWriteField "sType" VkDeviceQueueCreateInfo Source # 
CanReadField "flags" VkDeviceQueueCreateInfo Source # 
CanReadField "pNext" VkDeviceQueueCreateInfo Source # 
CanReadField "pQueuePriorities" VkDeviceQueueCreateInfo Source # 
CanReadField "queueCount" VkDeviceQueueCreateInfo Source # 
CanReadField "queueFamilyIndex" VkDeviceQueueCreateInfo Source # 
CanReadField "sType" VkDeviceQueueCreateInfo Source # 
HasField "flags" VkDeviceQueueCreateInfo Source # 
HasField "pNext" VkDeviceQueueCreateInfo Source # 
HasField "pQueuePriorities" VkDeviceQueueCreateInfo Source # 

Associated Types

type FieldType ("pQueuePriorities" :: Symbol) VkDeviceQueueCreateInfo :: Type Source #

type FieldOptional ("pQueuePriorities" :: Symbol) VkDeviceQueueCreateInfo :: Bool Source #

type FieldOffset ("pQueuePriorities" :: Symbol) VkDeviceQueueCreateInfo :: Nat Source #

type FieldIsArray ("pQueuePriorities" :: Symbol) VkDeviceQueueCreateInfo :: Bool Source #

HasField "queueCount" VkDeviceQueueCreateInfo Source # 
HasField "queueFamilyIndex" VkDeviceQueueCreateInfo Source # 

Associated Types

type FieldType ("queueFamilyIndex" :: Symbol) VkDeviceQueueCreateInfo :: Type Source #

type FieldOptional ("queueFamilyIndex" :: Symbol) VkDeviceQueueCreateInfo :: Bool Source #

type FieldOffset ("queueFamilyIndex" :: Symbol) VkDeviceQueueCreateInfo :: Nat Source #

type FieldIsArray ("queueFamilyIndex" :: Symbol) VkDeviceQueueCreateInfo :: Bool Source #

HasField "sType" VkDeviceQueueCreateInfo Source # 
type StructFields VkDeviceQueueCreateInfo Source # 
type StructFields VkDeviceQueueCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "queueFamilyIndex" ((:) Symbol "queueCount" ((:) Symbol "pQueuePriorities" ([] Symbol))))))
type CUnionType VkDeviceQueueCreateInfo Source # 
type ReturnedOnly VkDeviceQueueCreateInfo Source # 
type StructExtends VkDeviceQueueCreateInfo Source # 
type FieldType "flags" VkDeviceQueueCreateInfo Source # 
type FieldType "pNext" VkDeviceQueueCreateInfo Source # 
type FieldType "pQueuePriorities" VkDeviceQueueCreateInfo Source # 
type FieldType "pQueuePriorities" VkDeviceQueueCreateInfo = Ptr Float
type FieldType "queueCount" VkDeviceQueueCreateInfo Source # 
type FieldType "queueFamilyIndex" VkDeviceQueueCreateInfo Source # 
type FieldType "queueFamilyIndex" VkDeviceQueueCreateInfo = Word32
type FieldType "sType" VkDeviceQueueCreateInfo Source # 
type FieldOptional "flags" VkDeviceQueueCreateInfo Source # 
type FieldOptional "pNext" VkDeviceQueueCreateInfo Source # 
type FieldOptional "pQueuePriorities" VkDeviceQueueCreateInfo Source # 
type FieldOptional "pQueuePriorities" VkDeviceQueueCreateInfo = False
type FieldOptional "queueCount" VkDeviceQueueCreateInfo Source # 
type FieldOptional "queueFamilyIndex" VkDeviceQueueCreateInfo Source # 
type FieldOptional "queueFamilyIndex" VkDeviceQueueCreateInfo = False
type FieldOptional "sType" VkDeviceQueueCreateInfo Source # 
type FieldOffset "flags" VkDeviceQueueCreateInfo Source # 
type FieldOffset "pNext" VkDeviceQueueCreateInfo Source # 
type FieldOffset "pQueuePriorities" VkDeviceQueueCreateInfo Source # 
type FieldOffset "pQueuePriorities" VkDeviceQueueCreateInfo = 32
type FieldOffset "queueCount" VkDeviceQueueCreateInfo Source # 
type FieldOffset "queueCount" VkDeviceQueueCreateInfo = 24
type FieldOffset "queueFamilyIndex" VkDeviceQueueCreateInfo Source # 
type FieldOffset "queueFamilyIndex" VkDeviceQueueCreateInfo = 20
type FieldOffset "sType" VkDeviceQueueCreateInfo Source # 
type FieldIsArray "flags" VkDeviceQueueCreateInfo Source # 
type FieldIsArray "pNext" VkDeviceQueueCreateInfo Source # 
type FieldIsArray "pQueuePriorities" VkDeviceQueueCreateInfo Source # 
type FieldIsArray "pQueuePriorities" VkDeviceQueueCreateInfo = False
type FieldIsArray "queueCount" VkDeviceQueueCreateInfo Source # 
type FieldIsArray "queueFamilyIndex" VkDeviceQueueCreateInfo Source # 
type FieldIsArray "queueFamilyIndex" VkDeviceQueueCreateInfo = False
type FieldIsArray "sType" VkDeviceQueueCreateInfo Source # 

data VkDeviceQueueGlobalPriorityCreateInfoEXT Source #

typedef struct VkDeviceQueueGlobalPriorityCreateInfoEXT {
    VkStructureType sType;
    const void*                    pNext;
    VkQueueGlobalPriorityEXT       globalPriority;
} VkDeviceQueueGlobalPriorityCreateInfoEXT;

VkDeviceQueueGlobalPriorityCreateInfoEXT registry at www.khronos.org

Instances

Eq VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
Ord VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
Show VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
Storable VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
VulkanMarshalPrim VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
VulkanMarshal VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
CanWriteField "globalPriority" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
CanWriteField "pNext" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
CanWriteField "sType" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
CanReadField "globalPriority" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
CanReadField "pNext" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
CanReadField "sType" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
HasField "globalPriority" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
HasField "pNext" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
HasField "sType" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
type StructFields VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
type StructFields VkDeviceQueueGlobalPriorityCreateInfoEXT = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "globalPriority" ([] Symbol)))
type CUnionType VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
type ReturnedOnly VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
type StructExtends VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
type FieldType "globalPriority" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
type FieldType "pNext" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
type FieldType "sType" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
type FieldOptional "globalPriority" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
type FieldOptional "pNext" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
type FieldOptional "sType" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
type FieldOffset "globalPriority" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
type FieldOffset "pNext" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
type FieldOffset "sType" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
type FieldIsArray "globalPriority" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
type FieldIsArray "pNext" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 
type FieldIsArray "sType" VkDeviceQueueGlobalPriorityCreateInfoEXT Source # 

data VkDeviceQueueInfo2 Source #

typedef struct VkDeviceQueueInfo2 {
    VkStructureType sType;
    const void*                         pNext;
    VkDeviceQueueCreateFlags            flags;
    uint32_t                            queueFamilyIndex;
    uint32_t                            queueIndex;
} VkDeviceQueueInfo2;

VkDeviceQueueInfo2 registry at www.khronos.org

Instances

Eq VkDeviceQueueInfo2 Source # 
Ord VkDeviceQueueInfo2 Source # 
Show VkDeviceQueueInfo2 Source # 
Storable VkDeviceQueueInfo2 Source # 
VulkanMarshalPrim VkDeviceQueueInfo2 Source # 
VulkanMarshal VkDeviceQueueInfo2 Source # 
CanWriteField "flags" VkDeviceQueueInfo2 Source # 
CanWriteField "pNext" VkDeviceQueueInfo2 Source # 
CanWriteField "queueFamilyIndex" VkDeviceQueueInfo2 Source # 

Methods

writeField :: Ptr VkDeviceQueueInfo2 -> FieldType "queueFamilyIndex" VkDeviceQueueInfo2 -> IO () Source #

CanWriteField "queueIndex" VkDeviceQueueInfo2 Source # 
CanWriteField "sType" VkDeviceQueueInfo2 Source # 
CanReadField "flags" VkDeviceQueueInfo2 Source # 
CanReadField "pNext" VkDeviceQueueInfo2 Source # 
CanReadField "queueFamilyIndex" VkDeviceQueueInfo2 Source # 
CanReadField "queueIndex" VkDeviceQueueInfo2 Source # 
CanReadField "sType" VkDeviceQueueInfo2 Source # 
HasField "flags" VkDeviceQueueInfo2 Source # 
HasField "pNext" VkDeviceQueueInfo2 Source # 
HasField "queueFamilyIndex" VkDeviceQueueInfo2 Source # 

Associated Types

type FieldType ("queueFamilyIndex" :: Symbol) VkDeviceQueueInfo2 :: Type Source #

type FieldOptional ("queueFamilyIndex" :: Symbol) VkDeviceQueueInfo2 :: Bool Source #

type FieldOffset ("queueFamilyIndex" :: Symbol) VkDeviceQueueInfo2 :: Nat Source #

type FieldIsArray ("queueFamilyIndex" :: Symbol) VkDeviceQueueInfo2 :: Bool Source #

HasField "queueIndex" VkDeviceQueueInfo2 Source # 

Associated Types

type FieldType ("queueIndex" :: Symbol) VkDeviceQueueInfo2 :: Type Source #

type FieldOptional ("queueIndex" :: Symbol) VkDeviceQueueInfo2 :: Bool Source #

type FieldOffset ("queueIndex" :: Symbol) VkDeviceQueueInfo2 :: Nat Source #

type FieldIsArray ("queueIndex" :: Symbol) VkDeviceQueueInfo2 :: Bool Source #

HasField "sType" VkDeviceQueueInfo2 Source # 
type StructFields VkDeviceQueueInfo2 Source # 
type StructFields VkDeviceQueueInfo2 = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "queueFamilyIndex" ((:) Symbol "queueIndex" ([] Symbol)))))
type CUnionType VkDeviceQueueInfo2 Source # 
type ReturnedOnly VkDeviceQueueInfo2 Source # 
type StructExtends VkDeviceQueueInfo2 Source # 
type FieldType "flags" VkDeviceQueueInfo2 Source # 
type FieldType "pNext" VkDeviceQueueInfo2 Source # 
type FieldType "queueFamilyIndex" VkDeviceQueueInfo2 Source # 
type FieldType "queueFamilyIndex" VkDeviceQueueInfo2 = Word32
type FieldType "queueIndex" VkDeviceQueueInfo2 Source # 
type FieldType "queueIndex" VkDeviceQueueInfo2 = Word32
type FieldType "sType" VkDeviceQueueInfo2 Source # 
type FieldOptional "flags" VkDeviceQueueInfo2 Source # 
type FieldOptional "pNext" VkDeviceQueueInfo2 Source # 
type FieldOptional "queueFamilyIndex" VkDeviceQueueInfo2 Source # 
type FieldOptional "queueFamilyIndex" VkDeviceQueueInfo2 = False
type FieldOptional "queueIndex" VkDeviceQueueInfo2 Source # 
type FieldOptional "sType" VkDeviceQueueInfo2 Source # 
type FieldOffset "flags" VkDeviceQueueInfo2 Source # 
type FieldOffset "pNext" VkDeviceQueueInfo2 Source # 
type FieldOffset "queueFamilyIndex" VkDeviceQueueInfo2 Source # 
type FieldOffset "queueFamilyIndex" VkDeviceQueueInfo2 = 20
type FieldOffset "queueIndex" VkDeviceQueueInfo2 Source # 
type FieldOffset "queueIndex" VkDeviceQueueInfo2 = 24
type FieldOffset "sType" VkDeviceQueueInfo2 Source # 
type FieldIsArray "flags" VkDeviceQueueInfo2 Source # 
type FieldIsArray "pNext" VkDeviceQueueInfo2 Source # 
type FieldIsArray "queueFamilyIndex" VkDeviceQueueInfo2 Source # 
type FieldIsArray "queueFamilyIndex" VkDeviceQueueInfo2 = False
type FieldIsArray "queueIndex" VkDeviceQueueInfo2 Source # 
type FieldIsArray "sType" VkDeviceQueueInfo2 Source # 

newtype VkDeviceCreateFlagBits Source #

Instances

Bounded VkDeviceCreateFlagBits Source # 
Enum VkDeviceCreateFlagBits Source # 
Eq VkDeviceCreateFlagBits Source # 
Integral VkDeviceCreateFlagBits Source # 
Data VkDeviceCreateFlagBits Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkDeviceCreateFlagBits -> c VkDeviceCreateFlagBits #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkDeviceCreateFlagBits #

toConstr :: VkDeviceCreateFlagBits -> Constr #

dataTypeOf :: VkDeviceCreateFlagBits -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkDeviceCreateFlagBits) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkDeviceCreateFlagBits) #

gmapT :: (forall b. Data b => b -> b) -> VkDeviceCreateFlagBits -> VkDeviceCreateFlagBits #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkDeviceCreateFlagBits -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkDeviceCreateFlagBits -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkDeviceCreateFlagBits -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkDeviceCreateFlagBits -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkDeviceCreateFlagBits -> m VkDeviceCreateFlagBits #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkDeviceCreateFlagBits -> m VkDeviceCreateFlagBits #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkDeviceCreateFlagBits -> m VkDeviceCreateFlagBits #

Num VkDeviceCreateFlagBits Source # 
Ord VkDeviceCreateFlagBits Source # 
Read VkDeviceCreateFlagBits Source # 
Real VkDeviceCreateFlagBits Source # 
Show VkDeviceCreateFlagBits Source # 
Generic VkDeviceCreateFlagBits Source # 
Storable VkDeviceCreateFlagBits Source # 
Bits VkDeviceCreateFlagBits Source # 
FiniteBits VkDeviceCreateFlagBits Source # 
type Rep VkDeviceCreateFlagBits Source # 
type Rep VkDeviceCreateFlagBits = D1 (MetaData "VkDeviceCreateFlagBits" "Graphics.Vulkan.Types.Enum.Device" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkDeviceCreateFlagBits" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkDeviceEventTypeEXT Source #

Instances

Bounded VkDeviceEventTypeEXT Source # 
Enum VkDeviceEventTypeEXT Source # 
Eq VkDeviceEventTypeEXT Source # 
Data VkDeviceEventTypeEXT Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkDeviceEventTypeEXT -> c VkDeviceEventTypeEXT #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkDeviceEventTypeEXT #

toConstr :: VkDeviceEventTypeEXT -> Constr #

dataTypeOf :: VkDeviceEventTypeEXT -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkDeviceEventTypeEXT) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkDeviceEventTypeEXT) #

gmapT :: (forall b. Data b => b -> b) -> VkDeviceEventTypeEXT -> VkDeviceEventTypeEXT #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkDeviceEventTypeEXT -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkDeviceEventTypeEXT -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkDeviceEventTypeEXT -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkDeviceEventTypeEXT -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkDeviceEventTypeEXT -> m VkDeviceEventTypeEXT #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkDeviceEventTypeEXT -> m VkDeviceEventTypeEXT #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkDeviceEventTypeEXT -> m VkDeviceEventTypeEXT #

Num VkDeviceEventTypeEXT Source # 
Ord VkDeviceEventTypeEXT Source # 
Read VkDeviceEventTypeEXT Source # 
Show VkDeviceEventTypeEXT Source # 
Generic VkDeviceEventTypeEXT Source # 
Storable VkDeviceEventTypeEXT Source # 
type Rep VkDeviceEventTypeEXT Source # 
type Rep VkDeviceEventTypeEXT = D1 (MetaData "VkDeviceEventTypeEXT" "Graphics.Vulkan.Types.Enum.Device" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkDeviceEventTypeEXT" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

newtype VkDeviceGroupPresentModeBitmaskKHR a Source #

Instances

Bounded (VkDeviceGroupPresentModeBitmaskKHR FlagMask) Source # 
Enum (VkDeviceGroupPresentModeBitmaskKHR FlagMask) Source # 
Eq (VkDeviceGroupPresentModeBitmaskKHR a) Source # 
Integral (VkDeviceGroupPresentModeBitmaskKHR FlagMask) Source # 
Typeable FlagType a => Data (VkDeviceGroupPresentModeBitmaskKHR a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkDeviceGroupPresentModeBitmaskKHR a -> c (VkDeviceGroupPresentModeBitmaskKHR a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkDeviceGroupPresentModeBitmaskKHR a) #

toConstr :: VkDeviceGroupPresentModeBitmaskKHR a -> Constr #

dataTypeOf :: VkDeviceGroupPresentModeBitmaskKHR a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkDeviceGroupPresentModeBitmaskKHR a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkDeviceGroupPresentModeBitmaskKHR a)) #

gmapT :: (forall b. Data b => b -> b) -> VkDeviceGroupPresentModeBitmaskKHR a -> VkDeviceGroupPresentModeBitmaskKHR a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkDeviceGroupPresentModeBitmaskKHR a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkDeviceGroupPresentModeBitmaskKHR a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkDeviceGroupPresentModeBitmaskKHR a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkDeviceGroupPresentModeBitmaskKHR a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkDeviceGroupPresentModeBitmaskKHR a -> m (VkDeviceGroupPresentModeBitmaskKHR a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkDeviceGroupPresentModeBitmaskKHR a -> m (VkDeviceGroupPresentModeBitmaskKHR a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkDeviceGroupPresentModeBitmaskKHR a -> m (VkDeviceGroupPresentModeBitmaskKHR a) #

Num (VkDeviceGroupPresentModeBitmaskKHR FlagMask) Source # 
Ord (VkDeviceGroupPresentModeBitmaskKHR a) Source # 
Read (VkDeviceGroupPresentModeBitmaskKHR a) Source # 
Real (VkDeviceGroupPresentModeBitmaskKHR FlagMask) Source # 
Show (VkDeviceGroupPresentModeBitmaskKHR a) Source # 
Generic (VkDeviceGroupPresentModeBitmaskKHR a) Source # 
Storable (VkDeviceGroupPresentModeBitmaskKHR a) Source # 
Bits (VkDeviceGroupPresentModeBitmaskKHR FlagMask) Source # 

Methods

(.&.) :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> VkDeviceGroupPresentModeBitmaskKHR FlagMask -> VkDeviceGroupPresentModeBitmaskKHR FlagMask #

(.|.) :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> VkDeviceGroupPresentModeBitmaskKHR FlagMask -> VkDeviceGroupPresentModeBitmaskKHR FlagMask #

xor :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> VkDeviceGroupPresentModeBitmaskKHR FlagMask -> VkDeviceGroupPresentModeBitmaskKHR FlagMask #

complement :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> VkDeviceGroupPresentModeBitmaskKHR FlagMask #

shift :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> Int -> VkDeviceGroupPresentModeBitmaskKHR FlagMask #

rotate :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> Int -> VkDeviceGroupPresentModeBitmaskKHR FlagMask #

zeroBits :: VkDeviceGroupPresentModeBitmaskKHR FlagMask #

bit :: Int -> VkDeviceGroupPresentModeBitmaskKHR FlagMask #

setBit :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> Int -> VkDeviceGroupPresentModeBitmaskKHR FlagMask #

clearBit :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> Int -> VkDeviceGroupPresentModeBitmaskKHR FlagMask #

complementBit :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> Int -> VkDeviceGroupPresentModeBitmaskKHR FlagMask #

testBit :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> Int -> Bool #

bitSizeMaybe :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> Maybe Int #

bitSize :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> Int #

isSigned :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> Bool #

shiftL :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> Int -> VkDeviceGroupPresentModeBitmaskKHR FlagMask #

unsafeShiftL :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> Int -> VkDeviceGroupPresentModeBitmaskKHR FlagMask #

shiftR :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> Int -> VkDeviceGroupPresentModeBitmaskKHR FlagMask #

unsafeShiftR :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> Int -> VkDeviceGroupPresentModeBitmaskKHR FlagMask #

rotateL :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> Int -> VkDeviceGroupPresentModeBitmaskKHR FlagMask #

rotateR :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> Int -> VkDeviceGroupPresentModeBitmaskKHR FlagMask #

popCount :: VkDeviceGroupPresentModeBitmaskKHR FlagMask -> Int #

FiniteBits (VkDeviceGroupPresentModeBitmaskKHR FlagMask) Source # 
type Rep (VkDeviceGroupPresentModeBitmaskKHR a) Source # 
type Rep (VkDeviceGroupPresentModeBitmaskKHR a) = D1 (MetaData "VkDeviceGroupPresentModeBitmaskKHR" "Graphics.Vulkan.Types.Enum.Device" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkDeviceGroupPresentModeBitmaskKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

pattern VK_DEVICE_GROUP_PRESENT_MODE_LOCAL_BIT_KHR :: forall a. VkDeviceGroupPresentModeBitmaskKHR a Source #

Present from local memory

bitpos = 0

pattern VK_DEVICE_GROUP_PRESENT_MODE_REMOTE_BIT_KHR :: forall a. VkDeviceGroupPresentModeBitmaskKHR a Source #

Present from remote memory

bitpos = 1

pattern VK_DEVICE_GROUP_PRESENT_MODE_SUM_BIT_KHR :: forall a. VkDeviceGroupPresentModeBitmaskKHR a Source #

Present sum of local and/or remote memory

bitpos = 2

pattern VK_DEVICE_GROUP_PRESENT_MODE_LOCAL_MULTI_DEVICE_BIT_KHR :: forall a. VkDeviceGroupPresentModeBitmaskKHR a Source #

Each physical device presents from local memory

bitpos = 3

newtype VkDeviceQueueCreateBitmask a Source #

Instances

Bounded (VkDeviceQueueCreateBitmask FlagMask) Source # 
Enum (VkDeviceQueueCreateBitmask FlagMask) Source # 
Eq (VkDeviceQueueCreateBitmask a) Source # 
Integral (VkDeviceQueueCreateBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkDeviceQueueCreateBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkDeviceQueueCreateBitmask a -> c (VkDeviceQueueCreateBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkDeviceQueueCreateBitmask a) #

toConstr :: VkDeviceQueueCreateBitmask a -> Constr #

dataTypeOf :: VkDeviceQueueCreateBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkDeviceQueueCreateBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkDeviceQueueCreateBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkDeviceQueueCreateBitmask a -> VkDeviceQueueCreateBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkDeviceQueueCreateBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkDeviceQueueCreateBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkDeviceQueueCreateBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkDeviceQueueCreateBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkDeviceQueueCreateBitmask a -> m (VkDeviceQueueCreateBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkDeviceQueueCreateBitmask a -> m (VkDeviceQueueCreateBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkDeviceQueueCreateBitmask a -> m (VkDeviceQueueCreateBitmask a) #

Num (VkDeviceQueueCreateBitmask FlagMask) Source # 
Ord (VkDeviceQueueCreateBitmask a) Source # 
Read (VkDeviceQueueCreateBitmask a) Source # 
Real (VkDeviceQueueCreateBitmask FlagMask) Source # 
Show (VkDeviceQueueCreateBitmask a) Source # 
Generic (VkDeviceQueueCreateBitmask a) Source # 
Storable (VkDeviceQueueCreateBitmask a) Source # 
Bits (VkDeviceQueueCreateBitmask FlagMask) Source # 

Methods

(.&.) :: VkDeviceQueueCreateBitmask FlagMask -> VkDeviceQueueCreateBitmask FlagMask -> VkDeviceQueueCreateBitmask FlagMask #

(.|.) :: VkDeviceQueueCreateBitmask FlagMask -> VkDeviceQueueCreateBitmask FlagMask -> VkDeviceQueueCreateBitmask FlagMask #

xor :: VkDeviceQueueCreateBitmask FlagMask -> VkDeviceQueueCreateBitmask FlagMask -> VkDeviceQueueCreateBitmask FlagMask #

complement :: VkDeviceQueueCreateBitmask FlagMask -> VkDeviceQueueCreateBitmask FlagMask #

shift :: VkDeviceQueueCreateBitmask FlagMask -> Int -> VkDeviceQueueCreateBitmask FlagMask #

rotate :: VkDeviceQueueCreateBitmask FlagMask -> Int -> VkDeviceQueueCreateBitmask FlagMask #

zeroBits :: VkDeviceQueueCreateBitmask FlagMask #

bit :: Int -> VkDeviceQueueCreateBitmask FlagMask #

setBit :: VkDeviceQueueCreateBitmask FlagMask -> Int -> VkDeviceQueueCreateBitmask FlagMask #

clearBit :: VkDeviceQueueCreateBitmask FlagMask -> Int -> VkDeviceQueueCreateBitmask FlagMask #

complementBit :: VkDeviceQueueCreateBitmask FlagMask -> Int -> VkDeviceQueueCreateBitmask FlagMask #

testBit :: VkDeviceQueueCreateBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkDeviceQueueCreateBitmask FlagMask -> Maybe Int #

bitSize :: VkDeviceQueueCreateBitmask FlagMask -> Int #

isSigned :: VkDeviceQueueCreateBitmask FlagMask -> Bool #

shiftL :: VkDeviceQueueCreateBitmask FlagMask -> Int -> VkDeviceQueueCreateBitmask FlagMask #

unsafeShiftL :: VkDeviceQueueCreateBitmask FlagMask -> Int -> VkDeviceQueueCreateBitmask FlagMask #

shiftR :: VkDeviceQueueCreateBitmask FlagMask -> Int -> VkDeviceQueueCreateBitmask FlagMask #

unsafeShiftR :: VkDeviceQueueCreateBitmask FlagMask -> Int -> VkDeviceQueueCreateBitmask FlagMask #

rotateL :: VkDeviceQueueCreateBitmask FlagMask -> Int -> VkDeviceQueueCreateBitmask FlagMask #

rotateR :: VkDeviceQueueCreateBitmask FlagMask -> Int -> VkDeviceQueueCreateBitmask FlagMask #

popCount :: VkDeviceQueueCreateBitmask FlagMask -> Int #

FiniteBits (VkDeviceQueueCreateBitmask FlagMask) Source # 
type Rep (VkDeviceQueueCreateBitmask a) Source # 
type Rep (VkDeviceQueueCreateBitmask a) = D1 (MetaData "VkDeviceQueueCreateBitmask" "Graphics.Vulkan.Types.Enum.Device" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkDeviceQueueCreateBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

data VkPhysicalDeviceFeatures Source #

typedef struct VkPhysicalDeviceFeatures {
    VkBool32               robustBufferAccess;
    VkBool32               fullDrawIndexUint32;
    VkBool32               imageCubeArray;
    VkBool32               independentBlend;
    VkBool32               geometryShader;
    VkBool32               tessellationShader;
    VkBool32               sampleRateShading;
    VkBool32               dualSrcBlend;
    VkBool32               logicOp;
    VkBool32               multiDrawIndirect;
    VkBool32               drawIndirectFirstInstance;
    VkBool32               depthClamp;
    VkBool32               depthBiasClamp;
    VkBool32               fillModeNonSolid;
    VkBool32               depthBounds;
    VkBool32               wideLines;
    VkBool32               largePoints;
    VkBool32               alphaToOne;
    VkBool32               multiViewport;
    VkBool32               samplerAnisotropy;
    VkBool32               textureCompressionETC2;
    VkBool32               textureCompressionASTC_LDR;
    VkBool32               textureCompressionBC;
    VkBool32               occlusionQueryPrecise;
    VkBool32               pipelineStatisticsQuery;
    VkBool32               vertexPipelineStoresAndAtomics;
    VkBool32               fragmentStoresAndAtomics;
    VkBool32               shaderTessellationAndGeometryPointSize;
    VkBool32               shaderImageGatherExtended;
    VkBool32               shaderStorageImageExtendedFormats;
    VkBool32               shaderStorageImageMultisample;
    VkBool32               shaderStorageImageReadWithoutFormat;
    VkBool32               shaderStorageImageWriteWithoutFormat;
    VkBool32               shaderUniformBufferArrayDynamicIndexing;
    VkBool32               shaderSampledImageArrayDynamicIndexing;
    VkBool32               shaderStorageBufferArrayDynamicIndexing;
    VkBool32               shaderStorageImageArrayDynamicIndexing;
    VkBool32               shaderClipDistance;
    VkBool32               shaderCullDistance;
    VkBool32               shaderFloat64;
    VkBool32               shaderInt64;
    VkBool32               shaderInt16;
    VkBool32               shaderResourceResidency;
    VkBool32               shaderResourceMinLod;
    VkBool32               sparseBinding;
    VkBool32               sparseResidencyBuffer;
    VkBool32               sparseResidencyImage2D;
    VkBool32               sparseResidencyImage3D;
    VkBool32               sparseResidency2Samples;
    VkBool32               sparseResidency4Samples;
    VkBool32               sparseResidency8Samples;
    VkBool32               sparseResidency16Samples;
    VkBool32               sparseResidencyAliased;
    VkBool32               variableMultisampleRate;
    VkBool32               inheritedQueries;
} VkPhysicalDeviceFeatures;

VkPhysicalDeviceFeatures registry at www.khronos.org

Instances

Eq VkPhysicalDeviceFeatures Source # 
Ord VkPhysicalDeviceFeatures Source # 
Show VkPhysicalDeviceFeatures Source # 
Storable VkPhysicalDeviceFeatures Source # 
VulkanMarshalPrim VkPhysicalDeviceFeatures Source # 
VulkanMarshal VkPhysicalDeviceFeatures Source # 
CanWriteField "alphaToOne" VkPhysicalDeviceFeatures Source # 
CanWriteField "depthBiasClamp" VkPhysicalDeviceFeatures Source # 
CanWriteField "depthBounds" VkPhysicalDeviceFeatures Source # 
CanWriteField "depthClamp" VkPhysicalDeviceFeatures Source # 
CanWriteField "drawIndirectFirstInstance" VkPhysicalDeviceFeatures Source # 

Methods

writeField :: Ptr VkPhysicalDeviceFeatures -> FieldType "drawIndirectFirstInstance" VkPhysicalDeviceFeatures -> IO () Source #

CanWriteField "dualSrcBlend" VkPhysicalDeviceFeatures Source # 
CanWriteField "fillModeNonSolid" VkPhysicalDeviceFeatures Source # 
CanWriteField "fragmentStoresAndAtomics" VkPhysicalDeviceFeatures Source # 

Methods

writeField :: Ptr VkPhysicalDeviceFeatures -> FieldType "fragmentStoresAndAtomics" VkPhysicalDeviceFeatures -> IO () Source #

CanWriteField "fullDrawIndexUint32" VkPhysicalDeviceFeatures Source # 
CanWriteField "geometryShader" VkPhysicalDeviceFeatures Source # 
CanWriteField "imageCubeArray" VkPhysicalDeviceFeatures Source # 
CanWriteField "independentBlend" VkPhysicalDeviceFeatures Source # 
CanWriteField "inheritedQueries" VkPhysicalDeviceFeatures Source # 
CanWriteField "largePoints" VkPhysicalDeviceFeatures Source # 
CanWriteField "logicOp" VkPhysicalDeviceFeatures Source # 
CanWriteField "multiDrawIndirect" VkPhysicalDeviceFeatures Source # 
CanWriteField "multiViewport" VkPhysicalDeviceFeatures Source # 
CanWriteField "occlusionQueryPrecise" VkPhysicalDeviceFeatures Source # 
CanWriteField "pipelineStatisticsQuery" VkPhysicalDeviceFeatures Source # 
CanWriteField "robustBufferAccess" VkPhysicalDeviceFeatures Source # 
CanWriteField "sampleRateShading" VkPhysicalDeviceFeatures Source # 
CanWriteField "samplerAnisotropy" VkPhysicalDeviceFeatures Source # 
CanWriteField "shaderClipDistance" VkPhysicalDeviceFeatures Source # 
CanWriteField "shaderCullDistance" VkPhysicalDeviceFeatures Source # 
CanWriteField "shaderFloat64" VkPhysicalDeviceFeatures Source # 
CanWriteField "shaderImageGatherExtended" VkPhysicalDeviceFeatures Source # 

Methods

writeField :: Ptr VkPhysicalDeviceFeatures -> FieldType "shaderImageGatherExtended" VkPhysicalDeviceFeatures -> IO () Source #

CanWriteField "shaderInt16" VkPhysicalDeviceFeatures Source # 
CanWriteField "shaderInt64" VkPhysicalDeviceFeatures Source # 
CanWriteField "shaderResourceMinLod" VkPhysicalDeviceFeatures Source # 
CanWriteField "shaderResourceResidency" VkPhysicalDeviceFeatures Source # 
CanWriteField "shaderSampledImageArrayDynamicIndexing" VkPhysicalDeviceFeatures Source # 

Methods

writeField :: Ptr VkPhysicalDeviceFeatures -> FieldType "shaderSampledImageArrayDynamicIndexing" VkPhysicalDeviceFeatures -> IO () Source #

CanWriteField "shaderStorageBufferArrayDynamicIndexing" VkPhysicalDeviceFeatures Source # 

Methods

writeField :: Ptr VkPhysicalDeviceFeatures -> FieldType "shaderStorageBufferArrayDynamicIndexing" VkPhysicalDeviceFeatures -> IO () Source #

CanWriteField "shaderStorageImageArrayDynamicIndexing" VkPhysicalDeviceFeatures Source # 

Methods

writeField :: Ptr VkPhysicalDeviceFeatures -> FieldType "shaderStorageImageArrayDynamicIndexing" VkPhysicalDeviceFeatures -> IO () Source #

CanWriteField "shaderStorageImageExtendedFormats" VkPhysicalDeviceFeatures Source # 

Methods

writeField :: Ptr VkPhysicalDeviceFeatures -> FieldType "shaderStorageImageExtendedFormats" VkPhysicalDeviceFeatures -> IO () Source #

CanWriteField "shaderStorageImageMultisample" VkPhysicalDeviceFeatures Source # 

Methods

writeField :: Ptr VkPhysicalDeviceFeatures -> FieldType "shaderStorageImageMultisample" VkPhysicalDeviceFeatures -> IO () Source #

CanWriteField "shaderStorageImageReadWithoutFormat" VkPhysicalDeviceFeatures Source # 

Methods

writeField :: Ptr VkPhysicalDeviceFeatures -> FieldType "shaderStorageImageReadWithoutFormat" VkPhysicalDeviceFeatures -> IO () Source #

CanWriteField "shaderStorageImageWriteWithoutFormat" VkPhysicalDeviceFeatures Source # 

Methods

writeField :: Ptr VkPhysicalDeviceFeatures -> FieldType "shaderStorageImageWriteWithoutFormat" VkPhysicalDeviceFeatures -> IO () Source #

CanWriteField "shaderTessellationAndGeometryPointSize" VkPhysicalDeviceFeatures Source # 

Methods

writeField :: Ptr VkPhysicalDeviceFeatures -> FieldType "shaderTessellationAndGeometryPointSize" VkPhysicalDeviceFeatures -> IO () Source #

CanWriteField "shaderUniformBufferArrayDynamicIndexing" VkPhysicalDeviceFeatures Source # 

Methods

writeField :: Ptr VkPhysicalDeviceFeatures -> FieldType "shaderUniformBufferArrayDynamicIndexing" VkPhysicalDeviceFeatures -> IO () Source #

CanWriteField "sparseBinding" VkPhysicalDeviceFeatures Source # 
CanWriteField "sparseResidency16Samples" VkPhysicalDeviceFeatures Source # 

Methods

writeField :: Ptr VkPhysicalDeviceFeatures -> FieldType "sparseResidency16Samples" VkPhysicalDeviceFeatures -> IO () Source #

CanWriteField "sparseResidency2Samples" VkPhysicalDeviceFeatures Source # 
CanWriteField "sparseResidency4Samples" VkPhysicalDeviceFeatures Source # 
CanWriteField "sparseResidency8Samples" VkPhysicalDeviceFeatures Source # 
CanWriteField "sparseResidencyAliased" VkPhysicalDeviceFeatures Source # 
CanWriteField "sparseResidencyBuffer" VkPhysicalDeviceFeatures Source # 
CanWriteField "sparseResidencyImage2D" VkPhysicalDeviceFeatures Source # 
CanWriteField "sparseResidencyImage3D" VkPhysicalDeviceFeatures Source # 
CanWriteField "tessellationShader" VkPhysicalDeviceFeatures Source # 
CanWriteField "textureCompressionASTC_LDR" VkPhysicalDeviceFeatures Source # 

Methods

writeField :: Ptr VkPhysicalDeviceFeatures -> FieldType "textureCompressionASTC_LDR" VkPhysicalDeviceFeatures -> IO () Source #

CanWriteField "textureCompressionBC" VkPhysicalDeviceFeatures Source # 
CanWriteField "textureCompressionETC2" VkPhysicalDeviceFeatures Source # 
CanWriteField "variableMultisampleRate" VkPhysicalDeviceFeatures Source # 
CanWriteField "vertexPipelineStoresAndAtomics" VkPhysicalDeviceFeatures Source # 

Methods

writeField :: Ptr VkPhysicalDeviceFeatures -> FieldType "vertexPipelineStoresAndAtomics" VkPhysicalDeviceFeatures -> IO () Source #

CanWriteField "wideLines" VkPhysicalDeviceFeatures Source # 
CanReadField "alphaToOne" VkPhysicalDeviceFeatures Source # 
CanReadField "depthBiasClamp" VkPhysicalDeviceFeatures Source # 
CanReadField "depthBounds" VkPhysicalDeviceFeatures Source # 
CanReadField "depthClamp" VkPhysicalDeviceFeatures Source # 
CanReadField "drawIndirectFirstInstance" VkPhysicalDeviceFeatures Source # 
CanReadField "dualSrcBlend" VkPhysicalDeviceFeatures Source # 
CanReadField "fillModeNonSolid" VkPhysicalDeviceFeatures Source # 
CanReadField "fragmentStoresAndAtomics" VkPhysicalDeviceFeatures Source # 
CanReadField "fullDrawIndexUint32" VkPhysicalDeviceFeatures Source # 
CanReadField "geometryShader" VkPhysicalDeviceFeatures Source # 
CanReadField "imageCubeArray" VkPhysicalDeviceFeatures Source # 
CanReadField "independentBlend" VkPhysicalDeviceFeatures Source # 
CanReadField "inheritedQueries" VkPhysicalDeviceFeatures Source # 
CanReadField "largePoints" VkPhysicalDeviceFeatures Source # 
CanReadField "logicOp" VkPhysicalDeviceFeatures Source # 
CanReadField "multiDrawIndirect" VkPhysicalDeviceFeatures Source # 
CanReadField "multiViewport" VkPhysicalDeviceFeatures Source # 
CanReadField "occlusionQueryPrecise" VkPhysicalDeviceFeatures Source # 
CanReadField "pipelineStatisticsQuery" VkPhysicalDeviceFeatures Source # 
CanReadField "robustBufferAccess" VkPhysicalDeviceFeatures Source # 
CanReadField "sampleRateShading" VkPhysicalDeviceFeatures Source # 
CanReadField "samplerAnisotropy" VkPhysicalDeviceFeatures Source # 
CanReadField "shaderClipDistance" VkPhysicalDeviceFeatures Source # 
CanReadField "shaderCullDistance" VkPhysicalDeviceFeatures Source # 
CanReadField "shaderFloat64" VkPhysicalDeviceFeatures Source # 
CanReadField "shaderImageGatherExtended" VkPhysicalDeviceFeatures Source # 
CanReadField "shaderInt16" VkPhysicalDeviceFeatures Source # 
CanReadField "shaderInt64" VkPhysicalDeviceFeatures Source # 
CanReadField "shaderResourceMinLod" VkPhysicalDeviceFeatures Source # 
CanReadField "shaderResourceResidency" VkPhysicalDeviceFeatures Source # 
CanReadField "shaderSampledImageArrayDynamicIndexing" VkPhysicalDeviceFeatures Source # 

Methods

getField :: VkPhysicalDeviceFeatures -> FieldType "shaderSampledImageArrayDynamicIndexing" VkPhysicalDeviceFeatures Source #

readField :: Ptr VkPhysicalDeviceFeatures -> IO (FieldType "shaderSampledImageArrayDynamicIndexing" VkPhysicalDeviceFeatures) Source #

CanReadField "shaderStorageBufferArrayDynamicIndexing" VkPhysicalDeviceFeatures Source # 

Methods

getField :: VkPhysicalDeviceFeatures -> FieldType "shaderStorageBufferArrayDynamicIndexing" VkPhysicalDeviceFeatures Source #

readField :: Ptr VkPhysicalDeviceFeatures -> IO (FieldType "shaderStorageBufferArrayDynamicIndexing" VkPhysicalDeviceFeatures) Source #

CanReadField "shaderStorageImageArrayDynamicIndexing" VkPhysicalDeviceFeatures Source # 

Methods

getField :: VkPhysicalDeviceFeatures -> FieldType "shaderStorageImageArrayDynamicIndexing" VkPhysicalDeviceFeatures Source #

readField :: Ptr VkPhysicalDeviceFeatures -> IO (FieldType "shaderStorageImageArrayDynamicIndexing" VkPhysicalDeviceFeatures) Source #

CanReadField "shaderStorageImageExtendedFormats" VkPhysicalDeviceFeatures Source # 

Methods

getField :: VkPhysicalDeviceFeatures -> FieldType "shaderStorageImageExtendedFormats" VkPhysicalDeviceFeatures Source #

readField :: Ptr VkPhysicalDeviceFeatures -> IO (FieldType "shaderStorageImageExtendedFormats" VkPhysicalDeviceFeatures) Source #

CanReadField "shaderStorageImageMultisample" VkPhysicalDeviceFeatures Source # 
CanReadField "shaderStorageImageReadWithoutFormat" VkPhysicalDeviceFeatures Source # 

Methods

getField :: VkPhysicalDeviceFeatures -> FieldType "shaderStorageImageReadWithoutFormat" VkPhysicalDeviceFeatures Source #

readField :: Ptr VkPhysicalDeviceFeatures -> IO (FieldType "shaderStorageImageReadWithoutFormat" VkPhysicalDeviceFeatures) Source #

CanReadField "shaderStorageImageWriteWithoutFormat" VkPhysicalDeviceFeatures Source # 

Methods

getField :: VkPhysicalDeviceFeatures -> FieldType "shaderStorageImageWriteWithoutFormat" VkPhysicalDeviceFeatures Source #

readField :: Ptr VkPhysicalDeviceFeatures -> IO (FieldType "shaderStorageImageWriteWithoutFormat" VkPhysicalDeviceFeatures) Source #

CanReadField "shaderTessellationAndGeometryPointSize" VkPhysicalDeviceFeatures Source # 

Methods

getField :: VkPhysicalDeviceFeatures -> FieldType "shaderTessellationAndGeometryPointSize" VkPhysicalDeviceFeatures Source #

readField :: Ptr VkPhysicalDeviceFeatures -> IO (FieldType "shaderTessellationAndGeometryPointSize" VkPhysicalDeviceFeatures) Source #

CanReadField "shaderUniformBufferArrayDynamicIndexing" VkPhysicalDeviceFeatures Source # 

Methods

getField :: VkPhysicalDeviceFeatures -> FieldType "shaderUniformBufferArrayDynamicIndexing" VkPhysicalDeviceFeatures Source #

readField :: Ptr VkPhysicalDeviceFeatures -> IO (FieldType "shaderUniformBufferArrayDynamicIndexing" VkPhysicalDeviceFeatures) Source #

CanReadField "sparseBinding" VkPhysicalDeviceFeatures Source # 
CanReadField "sparseResidency16Samples" VkPhysicalDeviceFeatures Source # 
CanReadField "sparseResidency2Samples" VkPhysicalDeviceFeatures Source # 
CanReadField "sparseResidency4Samples" VkPhysicalDeviceFeatures Source # 
CanReadField "sparseResidency8Samples" VkPhysicalDeviceFeatures Source # 
CanReadField "sparseResidencyAliased" VkPhysicalDeviceFeatures Source # 
CanReadField "sparseResidencyBuffer" VkPhysicalDeviceFeatures Source # 
CanReadField "sparseResidencyImage2D" VkPhysicalDeviceFeatures Source # 
CanReadField "sparseResidencyImage3D" VkPhysicalDeviceFeatures Source # 
CanReadField "tessellationShader" VkPhysicalDeviceFeatures Source # 
CanReadField "textureCompressionASTC_LDR" VkPhysicalDeviceFeatures Source # 
CanReadField "textureCompressionBC" VkPhysicalDeviceFeatures Source # 
CanReadField "textureCompressionETC2" VkPhysicalDeviceFeatures Source # 
CanReadField "variableMultisampleRate" VkPhysicalDeviceFeatures Source # 
CanReadField "vertexPipelineStoresAndAtomics" VkPhysicalDeviceFeatures Source # 
CanReadField "wideLines" VkPhysicalDeviceFeatures Source # 
HasField "alphaToOne" VkPhysicalDeviceFeatures Source # 
HasField "depthBiasClamp" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("depthBiasClamp" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("depthBiasClamp" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("depthBiasClamp" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("depthBiasClamp" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "depthBounds" VkPhysicalDeviceFeatures Source # 
HasField "depthClamp" VkPhysicalDeviceFeatures Source # 
HasField "drawIndirectFirstInstance" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("drawIndirectFirstInstance" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("drawIndirectFirstInstance" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("drawIndirectFirstInstance" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("drawIndirectFirstInstance" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "dualSrcBlend" VkPhysicalDeviceFeatures Source # 
HasField "fillModeNonSolid" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("fillModeNonSolid" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("fillModeNonSolid" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("fillModeNonSolid" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("fillModeNonSolid" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "fragmentStoresAndAtomics" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("fragmentStoresAndAtomics" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("fragmentStoresAndAtomics" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("fragmentStoresAndAtomics" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("fragmentStoresAndAtomics" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "fullDrawIndexUint32" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("fullDrawIndexUint32" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("fullDrawIndexUint32" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("fullDrawIndexUint32" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("fullDrawIndexUint32" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "geometryShader" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("geometryShader" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("geometryShader" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("geometryShader" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("geometryShader" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "imageCubeArray" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("imageCubeArray" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("imageCubeArray" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("imageCubeArray" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("imageCubeArray" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "independentBlend" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("independentBlend" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("independentBlend" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("independentBlend" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("independentBlend" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "inheritedQueries" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("inheritedQueries" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("inheritedQueries" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("inheritedQueries" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("inheritedQueries" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "largePoints" VkPhysicalDeviceFeatures Source # 
HasField "logicOp" VkPhysicalDeviceFeatures Source # 
HasField "multiDrawIndirect" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("multiDrawIndirect" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("multiDrawIndirect" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("multiDrawIndirect" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("multiDrawIndirect" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "multiViewport" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("multiViewport" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("multiViewport" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("multiViewport" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("multiViewport" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "occlusionQueryPrecise" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("occlusionQueryPrecise" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("occlusionQueryPrecise" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("occlusionQueryPrecise" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("occlusionQueryPrecise" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "pipelineStatisticsQuery" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("pipelineStatisticsQuery" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("pipelineStatisticsQuery" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("pipelineStatisticsQuery" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("pipelineStatisticsQuery" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "robustBufferAccess" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("robustBufferAccess" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("robustBufferAccess" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("robustBufferAccess" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("robustBufferAccess" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "sampleRateShading" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("sampleRateShading" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("sampleRateShading" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("sampleRateShading" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("sampleRateShading" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "samplerAnisotropy" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("samplerAnisotropy" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("samplerAnisotropy" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("samplerAnisotropy" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("samplerAnisotropy" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "shaderClipDistance" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("shaderClipDistance" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("shaderClipDistance" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("shaderClipDistance" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("shaderClipDistance" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "shaderCullDistance" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("shaderCullDistance" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("shaderCullDistance" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("shaderCullDistance" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("shaderCullDistance" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "shaderFloat64" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("shaderFloat64" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("shaderFloat64" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("shaderFloat64" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("shaderFloat64" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "shaderImageGatherExtended" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("shaderImageGatherExtended" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("shaderImageGatherExtended" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("shaderImageGatherExtended" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("shaderImageGatherExtended" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "shaderInt16" VkPhysicalDeviceFeatures Source # 
HasField "shaderInt64" VkPhysicalDeviceFeatures Source # 
HasField "shaderResourceMinLod" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("shaderResourceMinLod" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("shaderResourceMinLod" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("shaderResourceMinLod" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("shaderResourceMinLod" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "shaderResourceResidency" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("shaderResourceResidency" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("shaderResourceResidency" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("shaderResourceResidency" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("shaderResourceResidency" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "shaderSampledImageArrayDynamicIndexing" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("shaderSampledImageArrayDynamicIndexing" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("shaderSampledImageArrayDynamicIndexing" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("shaderSampledImageArrayDynamicIndexing" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("shaderSampledImageArrayDynamicIndexing" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "shaderStorageBufferArrayDynamicIndexing" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("shaderStorageBufferArrayDynamicIndexing" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("shaderStorageBufferArrayDynamicIndexing" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("shaderStorageBufferArrayDynamicIndexing" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("shaderStorageBufferArrayDynamicIndexing" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "shaderStorageImageArrayDynamicIndexing" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("shaderStorageImageArrayDynamicIndexing" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("shaderStorageImageArrayDynamicIndexing" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("shaderStorageImageArrayDynamicIndexing" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("shaderStorageImageArrayDynamicIndexing" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "shaderStorageImageExtendedFormats" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("shaderStorageImageExtendedFormats" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("shaderStorageImageExtendedFormats" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("shaderStorageImageExtendedFormats" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("shaderStorageImageExtendedFormats" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "shaderStorageImageMultisample" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("shaderStorageImageMultisample" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("shaderStorageImageMultisample" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("shaderStorageImageMultisample" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("shaderStorageImageMultisample" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "shaderStorageImageReadWithoutFormat" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("shaderStorageImageReadWithoutFormat" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("shaderStorageImageReadWithoutFormat" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("shaderStorageImageReadWithoutFormat" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("shaderStorageImageReadWithoutFormat" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "shaderStorageImageWriteWithoutFormat" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("shaderStorageImageWriteWithoutFormat" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("shaderStorageImageWriteWithoutFormat" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("shaderStorageImageWriteWithoutFormat" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("shaderStorageImageWriteWithoutFormat" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "shaderTessellationAndGeometryPointSize" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("shaderTessellationAndGeometryPointSize" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("shaderTessellationAndGeometryPointSize" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("shaderTessellationAndGeometryPointSize" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("shaderTessellationAndGeometryPointSize" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "shaderUniformBufferArrayDynamicIndexing" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("shaderUniformBufferArrayDynamicIndexing" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("shaderUniformBufferArrayDynamicIndexing" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("shaderUniformBufferArrayDynamicIndexing" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("shaderUniformBufferArrayDynamicIndexing" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "sparseBinding" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("sparseBinding" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("sparseBinding" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("sparseBinding" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("sparseBinding" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "sparseResidency16Samples" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("sparseResidency16Samples" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("sparseResidency16Samples" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("sparseResidency16Samples" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("sparseResidency16Samples" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "sparseResidency2Samples" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("sparseResidency2Samples" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("sparseResidency2Samples" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("sparseResidency2Samples" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("sparseResidency2Samples" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "sparseResidency4Samples" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("sparseResidency4Samples" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("sparseResidency4Samples" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("sparseResidency4Samples" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("sparseResidency4Samples" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "sparseResidency8Samples" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("sparseResidency8Samples" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("sparseResidency8Samples" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("sparseResidency8Samples" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("sparseResidency8Samples" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "sparseResidencyAliased" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("sparseResidencyAliased" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("sparseResidencyAliased" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("sparseResidencyAliased" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("sparseResidencyAliased" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "sparseResidencyBuffer" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("sparseResidencyBuffer" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("sparseResidencyBuffer" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("sparseResidencyBuffer" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("sparseResidencyBuffer" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "sparseResidencyImage2D" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("sparseResidencyImage2D" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("sparseResidencyImage2D" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("sparseResidencyImage2D" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("sparseResidencyImage2D" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "sparseResidencyImage3D" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("sparseResidencyImage3D" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("sparseResidencyImage3D" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("sparseResidencyImage3D" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("sparseResidencyImage3D" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "tessellationShader" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("tessellationShader" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("tessellationShader" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("tessellationShader" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("tessellationShader" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "textureCompressionASTC_LDR" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("textureCompressionASTC_LDR" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("textureCompressionASTC_LDR" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("textureCompressionASTC_LDR" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("textureCompressionASTC_LDR" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "textureCompressionBC" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("textureCompressionBC" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("textureCompressionBC" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("textureCompressionBC" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("textureCompressionBC" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "textureCompressionETC2" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("textureCompressionETC2" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("textureCompressionETC2" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("textureCompressionETC2" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("textureCompressionETC2" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "variableMultisampleRate" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("variableMultisampleRate" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("variableMultisampleRate" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("variableMultisampleRate" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("variableMultisampleRate" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "vertexPipelineStoresAndAtomics" VkPhysicalDeviceFeatures Source # 

Associated Types

type FieldType ("vertexPipelineStoresAndAtomics" :: Symbol) VkPhysicalDeviceFeatures :: Type Source #

type FieldOptional ("vertexPipelineStoresAndAtomics" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

type FieldOffset ("vertexPipelineStoresAndAtomics" :: Symbol) VkPhysicalDeviceFeatures :: Nat Source #

type FieldIsArray ("vertexPipelineStoresAndAtomics" :: Symbol) VkPhysicalDeviceFeatures :: Bool Source #

HasField "wideLines" VkPhysicalDeviceFeatures Source # 
type StructFields VkPhysicalDeviceFeatures Source # 
type StructFields VkPhysicalDeviceFeatures = (:) Symbol "robustBufferAccess" ((:) Symbol "fullDrawIndexUint32" ((:) Symbol "imageCubeArray" ((:) Symbol "independentBlend" ((:) Symbol "geometryShader" ((:) Symbol "tessellationShader" ((:) Symbol "sampleRateShading" ((:) Symbol "dualSrcBlend" ((:) Symbol "logicOp" ((:) Symbol "multiDrawIndirect" ((:) Symbol "drawIndirectFirstInstance" ((:) Symbol "depthClamp" ((:) Symbol "depthBiasClamp" ((:) Symbol "fillModeNonSolid" ((:) Symbol "depthBounds" ((:) Symbol "wideLines" ((:) Symbol "largePoints" ((:) Symbol "alphaToOne" ((:) Symbol "multiViewport" ((:) Symbol "samplerAnisotropy" ((:) Symbol "textureCompressionETC2" ((:) Symbol "textureCompressionASTC_LDR" ((:) Symbol "textureCompressionBC" ((:) Symbol "occlusionQueryPrecise" ((:) Symbol "pipelineStatisticsQuery" ((:) Symbol "vertexPipelineStoresAndAtomics" ((:) Symbol "fragmentStoresAndAtomics" ((:) Symbol "shaderTessellationAndGeometryPointSize" ((:) Symbol "shaderImageGatherExtended" ((:) Symbol "shaderStorageImageExtendedFormats" ((:) Symbol "shaderStorageImageMultisample" ((:) Symbol "shaderStorageImageReadWithoutFormat" ((:) Symbol "shaderStorageImageWriteWithoutFormat" ((:) Symbol "shaderUniformBufferArrayDynamicIndexing" ((:) Symbol "shaderSampledImageArrayDynamicIndexing" ((:) Symbol "shaderStorageBufferArrayDynamicIndexing" ((:) Symbol "shaderStorageImageArrayDynamicIndexing" ((:) Symbol "shaderClipDistance" ((:) Symbol "shaderCullDistance" ((:) Symbol "shaderFloat64" ((:) Symbol "shaderInt64" ((:) Symbol "shaderInt16" ((:) Symbol "shaderResourceResidency" ((:) Symbol "shaderResourceMinLod" ((:) Symbol "sparseBinding" ((:) Symbol "sparseResidencyBuffer" ((:) Symbol "sparseResidencyImage2D" ((:) Symbol "sparseResidencyImage3D" ((:) Symbol "sparseResidency2Samples" ((:) Symbol "sparseResidency4Samples" ((:) Symbol "sparseResidency8Samples" ((:) Symbol "sparseResidency16Samples" ((:) Symbol "sparseResidencyAliased" ((:) Symbol "variableMultisampleRate" ((:) Symbol "inheritedQueries" ([] Symbol)))))))))))))))))))))))))))))))))))))))))))))))))))))))
type CUnionType VkPhysicalDeviceFeatures Source # 
type ReturnedOnly VkPhysicalDeviceFeatures Source # 
type StructExtends VkPhysicalDeviceFeatures Source # 
type FieldType "alphaToOne" VkPhysicalDeviceFeatures Source # 
type FieldType "depthBiasClamp" VkPhysicalDeviceFeatures Source # 
type FieldType "depthBounds" VkPhysicalDeviceFeatures Source # 
type FieldType "depthClamp" VkPhysicalDeviceFeatures Source # 
type FieldType "drawIndirectFirstInstance" VkPhysicalDeviceFeatures Source # 
type FieldType "drawIndirectFirstInstance" VkPhysicalDeviceFeatures = VkBool32
type FieldType "dualSrcBlend" VkPhysicalDeviceFeatures Source # 
type FieldType "fillModeNonSolid" VkPhysicalDeviceFeatures Source # 
type FieldType "fillModeNonSolid" VkPhysicalDeviceFeatures = VkBool32
type FieldType "fragmentStoresAndAtomics" VkPhysicalDeviceFeatures Source # 
type FieldType "fragmentStoresAndAtomics" VkPhysicalDeviceFeatures = VkBool32
type FieldType "fullDrawIndexUint32" VkPhysicalDeviceFeatures Source # 
type FieldType "fullDrawIndexUint32" VkPhysicalDeviceFeatures = VkBool32
type FieldType "geometryShader" VkPhysicalDeviceFeatures Source # 
type FieldType "imageCubeArray" VkPhysicalDeviceFeatures Source # 
type FieldType "independentBlend" VkPhysicalDeviceFeatures Source # 
type FieldType "independentBlend" VkPhysicalDeviceFeatures = VkBool32
type FieldType "inheritedQueries" VkPhysicalDeviceFeatures Source # 
type FieldType "inheritedQueries" VkPhysicalDeviceFeatures = VkBool32
type FieldType "largePoints" VkPhysicalDeviceFeatures Source # 
type FieldType "logicOp" VkPhysicalDeviceFeatures Source # 
type FieldType "multiDrawIndirect" VkPhysicalDeviceFeatures Source # 
type FieldType "multiDrawIndirect" VkPhysicalDeviceFeatures = VkBool32
type FieldType "multiViewport" VkPhysicalDeviceFeatures Source # 
type FieldType "occlusionQueryPrecise" VkPhysicalDeviceFeatures Source # 
type FieldType "occlusionQueryPrecise" VkPhysicalDeviceFeatures = VkBool32
type FieldType "pipelineStatisticsQuery" VkPhysicalDeviceFeatures Source # 
type FieldType "pipelineStatisticsQuery" VkPhysicalDeviceFeatures = VkBool32
type FieldType "robustBufferAccess" VkPhysicalDeviceFeatures Source # 
type FieldType "robustBufferAccess" VkPhysicalDeviceFeatures = VkBool32
type FieldType "sampleRateShading" VkPhysicalDeviceFeatures Source # 
type FieldType "sampleRateShading" VkPhysicalDeviceFeatures = VkBool32
type FieldType "samplerAnisotropy" VkPhysicalDeviceFeatures Source # 
type FieldType "samplerAnisotropy" VkPhysicalDeviceFeatures = VkBool32
type FieldType "shaderClipDistance" VkPhysicalDeviceFeatures Source # 
type FieldType "shaderClipDistance" VkPhysicalDeviceFeatures = VkBool32
type FieldType "shaderCullDistance" VkPhysicalDeviceFeatures Source # 
type FieldType "shaderCullDistance" VkPhysicalDeviceFeatures = VkBool32
type FieldType "shaderFloat64" VkPhysicalDeviceFeatures Source # 
type FieldType "shaderImageGatherExtended" VkPhysicalDeviceFeatures Source # 
type FieldType "shaderImageGatherExtended" VkPhysicalDeviceFeatures = VkBool32
type FieldType "shaderInt16" VkPhysicalDeviceFeatures Source # 
type FieldType "shaderInt64" VkPhysicalDeviceFeatures Source # 
type FieldType "shaderResourceMinLod" VkPhysicalDeviceFeatures Source # 
type FieldType "shaderResourceMinLod" VkPhysicalDeviceFeatures = VkBool32
type FieldType "shaderResourceResidency" VkPhysicalDeviceFeatures Source # 
type FieldType "shaderResourceResidency" VkPhysicalDeviceFeatures = VkBool32
type FieldType "shaderSampledImageArrayDynamicIndexing" VkPhysicalDeviceFeatures Source # 
type FieldType "shaderSampledImageArrayDynamicIndexing" VkPhysicalDeviceFeatures = VkBool32
type FieldType "shaderStorageBufferArrayDynamicIndexing" VkPhysicalDeviceFeatures Source # 
type FieldType "shaderStorageBufferArrayDynamicIndexing" VkPhysicalDeviceFeatures = VkBool32
type FieldType "shaderStorageImageArrayDynamicIndexing" VkPhysicalDeviceFeatures Source # 
type FieldType "shaderStorageImageArrayDynamicIndexing" VkPhysicalDeviceFeatures = VkBool32
type FieldType "shaderStorageImageExtendedFormats" VkPhysicalDeviceFeatures Source # 
type FieldType "shaderStorageImageExtendedFormats" VkPhysicalDeviceFeatures = VkBool32
type FieldType "shaderStorageImageMultisample" VkPhysicalDeviceFeatures Source # 
type FieldType "shaderStorageImageMultisample" VkPhysicalDeviceFeatures = VkBool32
type FieldType "shaderStorageImageReadWithoutFormat" VkPhysicalDeviceFeatures Source # 
type FieldType "shaderStorageImageReadWithoutFormat" VkPhysicalDeviceFeatures = VkBool32
type FieldType "shaderStorageImageWriteWithoutFormat" VkPhysicalDeviceFeatures Source # 
type FieldType "shaderStorageImageWriteWithoutFormat" VkPhysicalDeviceFeatures = VkBool32
type FieldType "shaderTessellationAndGeometryPointSize" VkPhysicalDeviceFeatures Source # 
type FieldType "shaderTessellationAndGeometryPointSize" VkPhysicalDeviceFeatures = VkBool32
type FieldType "shaderUniformBufferArrayDynamicIndexing" VkPhysicalDeviceFeatures Source # 
type FieldType "shaderUniformBufferArrayDynamicIndexing" VkPhysicalDeviceFeatures = VkBool32
type FieldType "sparseBinding" VkPhysicalDeviceFeatures Source # 
type FieldType "sparseResidency16Samples" VkPhysicalDeviceFeatures Source # 
type FieldType "sparseResidency16Samples" VkPhysicalDeviceFeatures = VkBool32
type FieldType "sparseResidency2Samples" VkPhysicalDeviceFeatures Source # 
type FieldType "sparseResidency2Samples" VkPhysicalDeviceFeatures = VkBool32
type FieldType "sparseResidency4Samples" VkPhysicalDeviceFeatures Source # 
type FieldType "sparseResidency4Samples" VkPhysicalDeviceFeatures = VkBool32
type FieldType "sparseResidency8Samples" VkPhysicalDeviceFeatures Source # 
type FieldType "sparseResidency8Samples" VkPhysicalDeviceFeatures = VkBool32
type FieldType "sparseResidencyAliased" VkPhysicalDeviceFeatures Source # 
type FieldType "sparseResidencyAliased" VkPhysicalDeviceFeatures = VkBool32
type FieldType "sparseResidencyBuffer" VkPhysicalDeviceFeatures Source # 
type FieldType "sparseResidencyBuffer" VkPhysicalDeviceFeatures = VkBool32
type FieldType "sparseResidencyImage2D" VkPhysicalDeviceFeatures Source # 
type FieldType "sparseResidencyImage2D" VkPhysicalDeviceFeatures = VkBool32
type FieldType "sparseResidencyImage3D" VkPhysicalDeviceFeatures Source # 
type FieldType "sparseResidencyImage3D" VkPhysicalDeviceFeatures = VkBool32
type FieldType "tessellationShader" VkPhysicalDeviceFeatures Source # 
type FieldType "tessellationShader" VkPhysicalDeviceFeatures = VkBool32
type FieldType "textureCompressionASTC_LDR" VkPhysicalDeviceFeatures Source # 
type FieldType "textureCompressionASTC_LDR" VkPhysicalDeviceFeatures = VkBool32
type FieldType "textureCompressionBC" VkPhysicalDeviceFeatures Source # 
type FieldType "textureCompressionBC" VkPhysicalDeviceFeatures = VkBool32
type FieldType "textureCompressionETC2" VkPhysicalDeviceFeatures Source # 
type FieldType "textureCompressionETC2" VkPhysicalDeviceFeatures = VkBool32
type FieldType "variableMultisampleRate" VkPhysicalDeviceFeatures Source # 
type FieldType "variableMultisampleRate" VkPhysicalDeviceFeatures = VkBool32
type FieldType "vertexPipelineStoresAndAtomics" VkPhysicalDeviceFeatures Source # 
type FieldType "vertexPipelineStoresAndAtomics" VkPhysicalDeviceFeatures = VkBool32
type FieldType "wideLines" VkPhysicalDeviceFeatures Source # 
type FieldOptional "alphaToOne" VkPhysicalDeviceFeatures Source # 
type FieldOptional "depthBiasClamp" VkPhysicalDeviceFeatures Source # 
type FieldOptional "depthBounds" VkPhysicalDeviceFeatures Source # 
type FieldOptional "depthClamp" VkPhysicalDeviceFeatures Source # 
type FieldOptional "drawIndirectFirstInstance" VkPhysicalDeviceFeatures Source # 
type FieldOptional "drawIndirectFirstInstance" VkPhysicalDeviceFeatures = False
type FieldOptional "dualSrcBlend" VkPhysicalDeviceFeatures Source # 
type FieldOptional "fillModeNonSolid" VkPhysicalDeviceFeatures Source # 
type FieldOptional "fillModeNonSolid" VkPhysicalDeviceFeatures = False
type FieldOptional "fragmentStoresAndAtomics" VkPhysicalDeviceFeatures Source # 
type FieldOptional "fragmentStoresAndAtomics" VkPhysicalDeviceFeatures = False
type FieldOptional "fullDrawIndexUint32" VkPhysicalDeviceFeatures Source # 
type FieldOptional "fullDrawIndexUint32" VkPhysicalDeviceFeatures = False
type FieldOptional "geometryShader" VkPhysicalDeviceFeatures Source # 
type FieldOptional "imageCubeArray" VkPhysicalDeviceFeatures Source # 
type FieldOptional "independentBlend" VkPhysicalDeviceFeatures Source # 
type FieldOptional "independentBlend" VkPhysicalDeviceFeatures = False
type FieldOptional "inheritedQueries" VkPhysicalDeviceFeatures Source # 
type FieldOptional "inheritedQueries" VkPhysicalDeviceFeatures = False
type FieldOptional "largePoints" VkPhysicalDeviceFeatures Source # 
type FieldOptional "logicOp" VkPhysicalDeviceFeatures Source # 
type FieldOptional "multiDrawIndirect" VkPhysicalDeviceFeatures Source # 
type FieldOptional "multiDrawIndirect" VkPhysicalDeviceFeatures = False
type FieldOptional "multiViewport" VkPhysicalDeviceFeatures Source # 
type FieldOptional "occlusionQueryPrecise" VkPhysicalDeviceFeatures Source # 
type FieldOptional "occlusionQueryPrecise" VkPhysicalDeviceFeatures = False
type FieldOptional "pipelineStatisticsQuery" VkPhysicalDeviceFeatures Source # 
type FieldOptional "pipelineStatisticsQuery" VkPhysicalDeviceFeatures = False
type FieldOptional "robustBufferAccess" VkPhysicalDeviceFeatures Source # 
type FieldOptional "robustBufferAccess" VkPhysicalDeviceFeatures = False
type FieldOptional "sampleRateShading" VkPhysicalDeviceFeatures Source # 
type FieldOptional "sampleRateShading" VkPhysicalDeviceFeatures = False
type FieldOptional "samplerAnisotropy" VkPhysicalDeviceFeatures Source # 
type FieldOptional "samplerAnisotropy" VkPhysicalDeviceFeatures = False
type FieldOptional "shaderClipDistance" VkPhysicalDeviceFeatures Source # 
type FieldOptional "shaderClipDistance" VkPhysicalDeviceFeatures = False
type FieldOptional "shaderCullDistance" VkPhysicalDeviceFeatures Source # 
type FieldOptional "shaderCullDistance" VkPhysicalDeviceFeatures = False
type FieldOptional "shaderFloat64" VkPhysicalDeviceFeatures Source # 
type FieldOptional "shaderImageGatherExtended" VkPhysicalDeviceFeatures Source # 
type FieldOptional "shaderImageGatherExtended" VkPhysicalDeviceFeatures = False
type FieldOptional "shaderInt16" VkPhysicalDeviceFeatures Source # 
type FieldOptional "shaderInt64" VkPhysicalDeviceFeatures Source # 
type FieldOptional "shaderResourceMinLod" VkPhysicalDeviceFeatures Source # 
type FieldOptional "shaderResourceMinLod" VkPhysicalDeviceFeatures = False
type FieldOptional "shaderResourceResidency" VkPhysicalDeviceFeatures Source # 
type FieldOptional "shaderResourceResidency" VkPhysicalDeviceFeatures = False
type FieldOptional "shaderSampledImageArrayDynamicIndexing" VkPhysicalDeviceFeatures Source # 
type FieldOptional "shaderSampledImageArrayDynamicIndexing" VkPhysicalDeviceFeatures = False
type FieldOptional "shaderStorageBufferArrayDynamicIndexing" VkPhysicalDeviceFeatures Source # 
type FieldOptional "shaderStorageBufferArrayDynamicIndexing" VkPhysicalDeviceFeatures = False
type FieldOptional "shaderStorageImageArrayDynamicIndexing" VkPhysicalDeviceFeatures Source # 
type FieldOptional "shaderStorageImageArrayDynamicIndexing" VkPhysicalDeviceFeatures = False
type FieldOptional "shaderStorageImageExtendedFormats" VkPhysicalDeviceFeatures Source # 
type FieldOptional "shaderStorageImageExtendedFormats" VkPhysicalDeviceFeatures = False
type FieldOptional "shaderStorageImageMultisample" VkPhysicalDeviceFeatures Source # 
type FieldOptional "shaderStorageImageMultisample" VkPhysicalDeviceFeatures = False
type FieldOptional "shaderStorageImageReadWithoutFormat" VkPhysicalDeviceFeatures Source # 
type FieldOptional "shaderStorageImageReadWithoutFormat" VkPhysicalDeviceFeatures = False
type FieldOptional "shaderStorageImageWriteWithoutFormat" VkPhysicalDeviceFeatures Source # 
type FieldOptional "shaderStorageImageWriteWithoutFormat" VkPhysicalDeviceFeatures = False
type FieldOptional "shaderTessellationAndGeometryPointSize" VkPhysicalDeviceFeatures Source # 
type FieldOptional "shaderTessellationAndGeometryPointSize" VkPhysicalDeviceFeatures = False
type FieldOptional "shaderUniformBufferArrayDynamicIndexing" VkPhysicalDeviceFeatures Source # 
type FieldOptional "shaderUniformBufferArrayDynamicIndexing" VkPhysicalDeviceFeatures = False
type FieldOptional "sparseBinding" VkPhysicalDeviceFeatures Source # 
type FieldOptional "sparseResidency16Samples" VkPhysicalDeviceFeatures Source # 
type FieldOptional "sparseResidency16Samples" VkPhysicalDeviceFeatures = False
type FieldOptional "sparseResidency2Samples" VkPhysicalDeviceFeatures Source # 
type FieldOptional "sparseResidency2Samples" VkPhysicalDeviceFeatures = False
type FieldOptional "sparseResidency4Samples" VkPhysicalDeviceFeatures Source # 
type FieldOptional "sparseResidency4Samples" VkPhysicalDeviceFeatures = False
type FieldOptional "sparseResidency8Samples" VkPhysicalDeviceFeatures Source # 
type FieldOptional "sparseResidency8Samples" VkPhysicalDeviceFeatures = False
type FieldOptional "sparseResidencyAliased" VkPhysicalDeviceFeatures Source # 
type FieldOptional "sparseResidencyAliased" VkPhysicalDeviceFeatures = False
type FieldOptional "sparseResidencyBuffer" VkPhysicalDeviceFeatures Source # 
type FieldOptional "sparseResidencyBuffer" VkPhysicalDeviceFeatures = False
type FieldOptional "sparseResidencyImage2D" VkPhysicalDeviceFeatures Source # 
type FieldOptional "sparseResidencyImage2D" VkPhysicalDeviceFeatures = False
type FieldOptional "sparseResidencyImage3D" VkPhysicalDeviceFeatures Source # 
type FieldOptional "sparseResidencyImage3D" VkPhysicalDeviceFeatures = False
type FieldOptional "tessellationShader" VkPhysicalDeviceFeatures Source # 
type FieldOptional "tessellationShader" VkPhysicalDeviceFeatures = False
type FieldOptional "textureCompressionASTC_LDR" VkPhysicalDeviceFeatures Source # 
type FieldOptional "textureCompressionASTC_LDR" VkPhysicalDeviceFeatures = False
type FieldOptional "textureCompressionBC" VkPhysicalDeviceFeatures Source # 
type FieldOptional "textureCompressionBC" VkPhysicalDeviceFeatures = False
type FieldOptional "textureCompressionETC2" VkPhysicalDeviceFeatures Source # 
type FieldOptional "textureCompressionETC2" VkPhysicalDeviceFeatures = False
type FieldOptional "variableMultisampleRate" VkPhysicalDeviceFeatures Source # 
type FieldOptional "variableMultisampleRate" VkPhysicalDeviceFeatures = False
type FieldOptional "vertexPipelineStoresAndAtomics" VkPhysicalDeviceFeatures Source # 
type FieldOptional "vertexPipelineStoresAndAtomics" VkPhysicalDeviceFeatures = False
type FieldOptional "wideLines" VkPhysicalDeviceFeatures Source # 
type FieldOffset "alphaToOne" VkPhysicalDeviceFeatures Source # 
type FieldOffset "alphaToOne" VkPhysicalDeviceFeatures = 68
type FieldOffset "depthBiasClamp" VkPhysicalDeviceFeatures Source # 
type FieldOffset "depthBiasClamp" VkPhysicalDeviceFeatures = 48
type FieldOffset "depthBounds" VkPhysicalDeviceFeatures Source # 
type FieldOffset "depthBounds" VkPhysicalDeviceFeatures = 56
type FieldOffset "depthClamp" VkPhysicalDeviceFeatures Source # 
type FieldOffset "depthClamp" VkPhysicalDeviceFeatures = 44
type FieldOffset "drawIndirectFirstInstance" VkPhysicalDeviceFeatures Source # 
type FieldOffset "drawIndirectFirstInstance" VkPhysicalDeviceFeatures = 40
type FieldOffset "dualSrcBlend" VkPhysicalDeviceFeatures Source # 
type FieldOffset "dualSrcBlend" VkPhysicalDeviceFeatures = 28
type FieldOffset "fillModeNonSolid" VkPhysicalDeviceFeatures Source # 
type FieldOffset "fillModeNonSolid" VkPhysicalDeviceFeatures = 52
type FieldOffset "fragmentStoresAndAtomics" VkPhysicalDeviceFeatures Source # 
type FieldOffset "fragmentStoresAndAtomics" VkPhysicalDeviceFeatures = 104
type FieldOffset "fullDrawIndexUint32" VkPhysicalDeviceFeatures Source # 
type FieldOffset "fullDrawIndexUint32" VkPhysicalDeviceFeatures = 4
type FieldOffset "geometryShader" VkPhysicalDeviceFeatures Source # 
type FieldOffset "geometryShader" VkPhysicalDeviceFeatures = 16
type FieldOffset "imageCubeArray" VkPhysicalDeviceFeatures Source # 
type FieldOffset "imageCubeArray" VkPhysicalDeviceFeatures = 8
type FieldOffset "independentBlend" VkPhysicalDeviceFeatures Source # 
type FieldOffset "independentBlend" VkPhysicalDeviceFeatures = 12
type FieldOffset "inheritedQueries" VkPhysicalDeviceFeatures Source # 
type FieldOffset "inheritedQueries" VkPhysicalDeviceFeatures = 216
type FieldOffset "largePoints" VkPhysicalDeviceFeatures Source # 
type FieldOffset "largePoints" VkPhysicalDeviceFeatures = 64
type FieldOffset "logicOp" VkPhysicalDeviceFeatures Source # 
type FieldOffset "multiDrawIndirect" VkPhysicalDeviceFeatures Source # 
type FieldOffset "multiDrawIndirect" VkPhysicalDeviceFeatures = 36
type FieldOffset "multiViewport" VkPhysicalDeviceFeatures Source # 
type FieldOffset "multiViewport" VkPhysicalDeviceFeatures = 72
type FieldOffset "occlusionQueryPrecise" VkPhysicalDeviceFeatures Source # 
type FieldOffset "occlusionQueryPrecise" VkPhysicalDeviceFeatures = 92
type FieldOffset "pipelineStatisticsQuery" VkPhysicalDeviceFeatures Source # 
type FieldOffset "pipelineStatisticsQuery" VkPhysicalDeviceFeatures = 96
type FieldOffset "robustBufferAccess" VkPhysicalDeviceFeatures Source # 
type FieldOffset "robustBufferAccess" VkPhysicalDeviceFeatures = 0
type FieldOffset "sampleRateShading" VkPhysicalDeviceFeatures Source # 
type FieldOffset "sampleRateShading" VkPhysicalDeviceFeatures = 24
type FieldOffset "samplerAnisotropy" VkPhysicalDeviceFeatures Source # 
type FieldOffset "samplerAnisotropy" VkPhysicalDeviceFeatures = 76
type FieldOffset "shaderClipDistance" VkPhysicalDeviceFeatures Source # 
type FieldOffset "shaderClipDistance" VkPhysicalDeviceFeatures = 148
type FieldOffset "shaderCullDistance" VkPhysicalDeviceFeatures Source # 
type FieldOffset "shaderCullDistance" VkPhysicalDeviceFeatures = 152
type FieldOffset "shaderFloat64" VkPhysicalDeviceFeatures Source # 
type FieldOffset "shaderFloat64" VkPhysicalDeviceFeatures = 156
type FieldOffset "shaderImageGatherExtended" VkPhysicalDeviceFeatures Source # 
type FieldOffset "shaderImageGatherExtended" VkPhysicalDeviceFeatures = 112
type FieldOffset "shaderInt16" VkPhysicalDeviceFeatures Source # 
type FieldOffset "shaderInt16" VkPhysicalDeviceFeatures = 164
type FieldOffset "shaderInt64" VkPhysicalDeviceFeatures Source # 
type FieldOffset "shaderInt64" VkPhysicalDeviceFeatures = 160
type FieldOffset "shaderResourceMinLod" VkPhysicalDeviceFeatures Source # 
type FieldOffset "shaderResourceMinLod" VkPhysicalDeviceFeatures = 172
type FieldOffset "shaderResourceResidency" VkPhysicalDeviceFeatures Source # 
type FieldOffset "shaderResourceResidency" VkPhysicalDeviceFeatures = 168
type FieldOffset "shaderSampledImageArrayDynamicIndexing" VkPhysicalDeviceFeatures Source # 
type FieldOffset "shaderSampledImageArrayDynamicIndexing" VkPhysicalDeviceFeatures = 136
type FieldOffset "shaderStorageBufferArrayDynamicIndexing" VkPhysicalDeviceFeatures Source # 
type FieldOffset "shaderStorageBufferArrayDynamicIndexing" VkPhysicalDeviceFeatures = 140
type FieldOffset "shaderStorageImageArrayDynamicIndexing" VkPhysicalDeviceFeatures Source # 
type FieldOffset "shaderStorageImageArrayDynamicIndexing" VkPhysicalDeviceFeatures = 144
type FieldOffset "shaderStorageImageExtendedFormats" VkPhysicalDeviceFeatures Source # 
type FieldOffset "shaderStorageImageExtendedFormats" VkPhysicalDeviceFeatures = 116
type FieldOffset "shaderStorageImageMultisample" VkPhysicalDeviceFeatures Source # 
type FieldOffset "shaderStorageImageMultisample" VkPhysicalDeviceFeatures = 120
type FieldOffset "shaderStorageImageReadWithoutFormat" VkPhysicalDeviceFeatures Source # 
type FieldOffset "shaderStorageImageReadWithoutFormat" VkPhysicalDeviceFeatures = 124
type FieldOffset "shaderStorageImageWriteWithoutFormat" VkPhysicalDeviceFeatures Source # 
type FieldOffset "shaderStorageImageWriteWithoutFormat" VkPhysicalDeviceFeatures = 128
type FieldOffset "shaderTessellationAndGeometryPointSize" VkPhysicalDeviceFeatures Source # 
type FieldOffset "shaderTessellationAndGeometryPointSize" VkPhysicalDeviceFeatures = 108
type FieldOffset "shaderUniformBufferArrayDynamicIndexing" VkPhysicalDeviceFeatures Source # 
type FieldOffset "shaderUniformBufferArrayDynamicIndexing" VkPhysicalDeviceFeatures = 132
type FieldOffset "sparseBinding" VkPhysicalDeviceFeatures Source # 
type FieldOffset "sparseBinding" VkPhysicalDeviceFeatures = 176
type FieldOffset "sparseResidency16Samples" VkPhysicalDeviceFeatures Source # 
type FieldOffset "sparseResidency16Samples" VkPhysicalDeviceFeatures = 204
type FieldOffset "sparseResidency2Samples" VkPhysicalDeviceFeatures Source # 
type FieldOffset "sparseResidency2Samples" VkPhysicalDeviceFeatures = 192
type FieldOffset "sparseResidency4Samples" VkPhysicalDeviceFeatures Source # 
type FieldOffset "sparseResidency4Samples" VkPhysicalDeviceFeatures = 196
type FieldOffset "sparseResidency8Samples" VkPhysicalDeviceFeatures Source # 
type FieldOffset "sparseResidency8Samples" VkPhysicalDeviceFeatures = 200
type FieldOffset "sparseResidencyAliased" VkPhysicalDeviceFeatures Source # 
type FieldOffset "sparseResidencyAliased" VkPhysicalDeviceFeatures = 208
type FieldOffset "sparseResidencyBuffer" VkPhysicalDeviceFeatures Source # 
type FieldOffset "sparseResidencyBuffer" VkPhysicalDeviceFeatures = 180
type FieldOffset "sparseResidencyImage2D" VkPhysicalDeviceFeatures Source # 
type FieldOffset "sparseResidencyImage2D" VkPhysicalDeviceFeatures = 184
type FieldOffset "sparseResidencyImage3D" VkPhysicalDeviceFeatures Source # 
type FieldOffset "sparseResidencyImage3D" VkPhysicalDeviceFeatures = 188
type FieldOffset "tessellationShader" VkPhysicalDeviceFeatures Source # 
type FieldOffset "tessellationShader" VkPhysicalDeviceFeatures = 20
type FieldOffset "textureCompressionASTC_LDR" VkPhysicalDeviceFeatures Source # 
type FieldOffset "textureCompressionASTC_LDR" VkPhysicalDeviceFeatures = 84
type FieldOffset "textureCompressionBC" VkPhysicalDeviceFeatures Source # 
type FieldOffset "textureCompressionBC" VkPhysicalDeviceFeatures = 88
type FieldOffset "textureCompressionETC2" VkPhysicalDeviceFeatures Source # 
type FieldOffset "textureCompressionETC2" VkPhysicalDeviceFeatures = 80
type FieldOffset "variableMultisampleRate" VkPhysicalDeviceFeatures Source # 
type FieldOffset "variableMultisampleRate" VkPhysicalDeviceFeatures = 212
type FieldOffset "vertexPipelineStoresAndAtomics" VkPhysicalDeviceFeatures Source # 
type FieldOffset "vertexPipelineStoresAndAtomics" VkPhysicalDeviceFeatures = 100
type FieldOffset "wideLines" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "alphaToOne" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "depthBiasClamp" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "depthBounds" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "depthClamp" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "drawIndirectFirstInstance" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "drawIndirectFirstInstance" VkPhysicalDeviceFeatures = False
type FieldIsArray "dualSrcBlend" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "fillModeNonSolid" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "fillModeNonSolid" VkPhysicalDeviceFeatures = False
type FieldIsArray "fragmentStoresAndAtomics" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "fragmentStoresAndAtomics" VkPhysicalDeviceFeatures = False
type FieldIsArray "fullDrawIndexUint32" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "fullDrawIndexUint32" VkPhysicalDeviceFeatures = False
type FieldIsArray "geometryShader" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "imageCubeArray" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "independentBlend" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "independentBlend" VkPhysicalDeviceFeatures = False
type FieldIsArray "inheritedQueries" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "inheritedQueries" VkPhysicalDeviceFeatures = False
type FieldIsArray "largePoints" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "logicOp" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "multiDrawIndirect" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "multiDrawIndirect" VkPhysicalDeviceFeatures = False
type FieldIsArray "multiViewport" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "occlusionQueryPrecise" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "occlusionQueryPrecise" VkPhysicalDeviceFeatures = False
type FieldIsArray "pipelineStatisticsQuery" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "pipelineStatisticsQuery" VkPhysicalDeviceFeatures = False
type FieldIsArray "robustBufferAccess" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "robustBufferAccess" VkPhysicalDeviceFeatures = False
type FieldIsArray "sampleRateShading" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "sampleRateShading" VkPhysicalDeviceFeatures = False
type FieldIsArray "samplerAnisotropy" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "samplerAnisotropy" VkPhysicalDeviceFeatures = False
type FieldIsArray "shaderClipDistance" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "shaderClipDistance" VkPhysicalDeviceFeatures = False
type FieldIsArray "shaderCullDistance" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "shaderCullDistance" VkPhysicalDeviceFeatures = False
type FieldIsArray "shaderFloat64" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "shaderImageGatherExtended" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "shaderImageGatherExtended" VkPhysicalDeviceFeatures = False
type FieldIsArray "shaderInt16" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "shaderInt64" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "shaderResourceMinLod" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "shaderResourceMinLod" VkPhysicalDeviceFeatures = False
type FieldIsArray "shaderResourceResidency" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "shaderResourceResidency" VkPhysicalDeviceFeatures = False
type FieldIsArray "shaderSampledImageArrayDynamicIndexing" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "shaderSampledImageArrayDynamicIndexing" VkPhysicalDeviceFeatures = False
type FieldIsArray "shaderStorageBufferArrayDynamicIndexing" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "shaderStorageBufferArrayDynamicIndexing" VkPhysicalDeviceFeatures = False
type FieldIsArray "shaderStorageImageArrayDynamicIndexing" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "shaderStorageImageArrayDynamicIndexing" VkPhysicalDeviceFeatures = False
type FieldIsArray "shaderStorageImageExtendedFormats" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "shaderStorageImageExtendedFormats" VkPhysicalDeviceFeatures = False
type FieldIsArray "shaderStorageImageMultisample" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "shaderStorageImageMultisample" VkPhysicalDeviceFeatures = False
type FieldIsArray "shaderStorageImageReadWithoutFormat" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "shaderStorageImageReadWithoutFormat" VkPhysicalDeviceFeatures = False
type FieldIsArray "shaderStorageImageWriteWithoutFormat" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "shaderStorageImageWriteWithoutFormat" VkPhysicalDeviceFeatures = False
type FieldIsArray "shaderTessellationAndGeometryPointSize" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "shaderTessellationAndGeometryPointSize" VkPhysicalDeviceFeatures = False
type FieldIsArray "shaderUniformBufferArrayDynamicIndexing" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "shaderUniformBufferArrayDynamicIndexing" VkPhysicalDeviceFeatures = False
type FieldIsArray "sparseBinding" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "sparseResidency16Samples" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "sparseResidency16Samples" VkPhysicalDeviceFeatures = False
type FieldIsArray "sparseResidency2Samples" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "sparseResidency2Samples" VkPhysicalDeviceFeatures = False
type FieldIsArray "sparseResidency4Samples" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "sparseResidency4Samples" VkPhysicalDeviceFeatures = False
type FieldIsArray "sparseResidency8Samples" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "sparseResidency8Samples" VkPhysicalDeviceFeatures = False
type FieldIsArray "sparseResidencyAliased" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "sparseResidencyAliased" VkPhysicalDeviceFeatures = False
type FieldIsArray "sparseResidencyBuffer" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "sparseResidencyBuffer" VkPhysicalDeviceFeatures = False
type FieldIsArray "sparseResidencyImage2D" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "sparseResidencyImage2D" VkPhysicalDeviceFeatures = False
type FieldIsArray "sparseResidencyImage3D" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "sparseResidencyImage3D" VkPhysicalDeviceFeatures = False
type FieldIsArray "tessellationShader" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "tessellationShader" VkPhysicalDeviceFeatures = False
type FieldIsArray "textureCompressionASTC_LDR" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "textureCompressionASTC_LDR" VkPhysicalDeviceFeatures = False
type FieldIsArray "textureCompressionBC" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "textureCompressionBC" VkPhysicalDeviceFeatures = False
type FieldIsArray "textureCompressionETC2" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "textureCompressionETC2" VkPhysicalDeviceFeatures = False
type FieldIsArray "variableMultisampleRate" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "variableMultisampleRate" VkPhysicalDeviceFeatures = False
type FieldIsArray "vertexPipelineStoresAndAtomics" VkPhysicalDeviceFeatures Source # 
type FieldIsArray "vertexPipelineStoresAndAtomics" VkPhysicalDeviceFeatures = False
type FieldIsArray "wideLines" VkPhysicalDeviceFeatures Source # 

Promoted from VK_KHR_dedicated_allocation

data VkMemoryAllocateFlagsInfo Source #

typedef struct VkMemoryAllocateFlagsInfo {
    VkStructureType sType;
    const void*                      pNext;
    VkMemoryAllocateFlags flags;
    uint32_t                         deviceMask;
} VkMemoryAllocateFlagsInfo;

VkMemoryAllocateFlagsInfo registry at www.khronos.org

Instances

Eq VkMemoryAllocateFlagsInfo Source # 
Ord VkMemoryAllocateFlagsInfo Source # 
Show VkMemoryAllocateFlagsInfo Source # 
Storable VkMemoryAllocateFlagsInfo Source # 
VulkanMarshalPrim VkMemoryAllocateFlagsInfo Source # 
VulkanMarshal VkMemoryAllocateFlagsInfo Source # 
CanWriteField "deviceMask" VkMemoryAllocateFlagsInfo Source # 
CanWriteField "flags" VkMemoryAllocateFlagsInfo Source # 
CanWriteField "pNext" VkMemoryAllocateFlagsInfo Source # 
CanWriteField "sType" VkMemoryAllocateFlagsInfo Source # 
CanReadField "deviceMask" VkMemoryAllocateFlagsInfo Source # 
CanReadField "flags" VkMemoryAllocateFlagsInfo Source # 
CanReadField "pNext" VkMemoryAllocateFlagsInfo Source # 
CanReadField "sType" VkMemoryAllocateFlagsInfo Source # 
HasField "deviceMask" VkMemoryAllocateFlagsInfo Source # 
HasField "flags" VkMemoryAllocateFlagsInfo Source # 
HasField "pNext" VkMemoryAllocateFlagsInfo Source # 
HasField "sType" VkMemoryAllocateFlagsInfo Source # 
type StructFields VkMemoryAllocateFlagsInfo Source # 
type StructFields VkMemoryAllocateFlagsInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "deviceMask" ([] Symbol))))
type CUnionType VkMemoryAllocateFlagsInfo Source # 
type ReturnedOnly VkMemoryAllocateFlagsInfo Source # 
type StructExtends VkMemoryAllocateFlagsInfo Source # 
type FieldType "deviceMask" VkMemoryAllocateFlagsInfo Source # 
type FieldType "flags" VkMemoryAllocateFlagsInfo Source # 
type FieldType "pNext" VkMemoryAllocateFlagsInfo Source # 
type FieldType "sType" VkMemoryAllocateFlagsInfo Source # 
type FieldOptional "deviceMask" VkMemoryAllocateFlagsInfo Source # 
type FieldOptional "flags" VkMemoryAllocateFlagsInfo Source # 
type FieldOptional "pNext" VkMemoryAllocateFlagsInfo Source # 
type FieldOptional "sType" VkMemoryAllocateFlagsInfo Source # 
type FieldOffset "deviceMask" VkMemoryAllocateFlagsInfo Source # 
type FieldOffset "deviceMask" VkMemoryAllocateFlagsInfo = 20
type FieldOffset "flags" VkMemoryAllocateFlagsInfo Source # 
type FieldOffset "pNext" VkMemoryAllocateFlagsInfo Source # 
type FieldOffset "sType" VkMemoryAllocateFlagsInfo Source # 
type FieldIsArray "deviceMask" VkMemoryAllocateFlagsInfo Source # 
type FieldIsArray "flags" VkMemoryAllocateFlagsInfo Source # 
type FieldIsArray "pNext" VkMemoryAllocateFlagsInfo Source # 
type FieldIsArray "sType" VkMemoryAllocateFlagsInfo Source # 

data VkMemoryAllocateInfo Source #

typedef struct VkMemoryAllocateInfo {
    VkStructureType sType;
    const void*            pNext;
    VkDeviceSize           allocationSize;
    uint32_t               memoryTypeIndex;
} VkMemoryAllocateInfo;

VkMemoryAllocateInfo registry at www.khronos.org

Instances

Eq VkMemoryAllocateInfo Source # 
Ord VkMemoryAllocateInfo Source # 
Show VkMemoryAllocateInfo Source # 
Storable VkMemoryAllocateInfo Source # 
VulkanMarshalPrim VkMemoryAllocateInfo Source # 
VulkanMarshal VkMemoryAllocateInfo Source # 
CanWriteField "allocationSize" VkMemoryAllocateInfo Source # 
CanWriteField "memoryTypeIndex" VkMemoryAllocateInfo Source # 
CanWriteField "pNext" VkMemoryAllocateInfo Source # 
CanWriteField "sType" VkMemoryAllocateInfo Source # 
CanReadField "allocationSize" VkMemoryAllocateInfo Source # 
CanReadField "memoryTypeIndex" VkMemoryAllocateInfo Source # 
CanReadField "pNext" VkMemoryAllocateInfo Source # 
CanReadField "sType" VkMemoryAllocateInfo Source # 
HasField "allocationSize" VkMemoryAllocateInfo Source # 

Associated Types

type FieldType ("allocationSize" :: Symbol) VkMemoryAllocateInfo :: Type Source #

type FieldOptional ("allocationSize" :: Symbol) VkMemoryAllocateInfo :: Bool Source #

type FieldOffset ("allocationSize" :: Symbol) VkMemoryAllocateInfo :: Nat Source #

type FieldIsArray ("allocationSize" :: Symbol) VkMemoryAllocateInfo :: Bool Source #

HasField "memoryTypeIndex" VkMemoryAllocateInfo Source # 

Associated Types

type FieldType ("memoryTypeIndex" :: Symbol) VkMemoryAllocateInfo :: Type Source #

type FieldOptional ("memoryTypeIndex" :: Symbol) VkMemoryAllocateInfo :: Bool Source #

type FieldOffset ("memoryTypeIndex" :: Symbol) VkMemoryAllocateInfo :: Nat Source #

type FieldIsArray ("memoryTypeIndex" :: Symbol) VkMemoryAllocateInfo :: Bool Source #

HasField "pNext" VkMemoryAllocateInfo Source # 
HasField "sType" VkMemoryAllocateInfo Source # 
type StructFields VkMemoryAllocateInfo Source # 
type StructFields VkMemoryAllocateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "allocationSize" ((:) Symbol "memoryTypeIndex" ([] Symbol))))
type CUnionType VkMemoryAllocateInfo Source # 
type ReturnedOnly VkMemoryAllocateInfo Source # 
type StructExtends VkMemoryAllocateInfo Source # 
type FieldType "allocationSize" VkMemoryAllocateInfo Source # 
type FieldType "memoryTypeIndex" VkMemoryAllocateInfo Source # 
type FieldType "memoryTypeIndex" VkMemoryAllocateInfo = Word32
type FieldType "pNext" VkMemoryAllocateInfo Source # 
type FieldType "sType" VkMemoryAllocateInfo Source # 
type FieldOptional "allocationSize" VkMemoryAllocateInfo Source # 
type FieldOptional "allocationSize" VkMemoryAllocateInfo = False
type FieldOptional "memoryTypeIndex" VkMemoryAllocateInfo Source # 
type FieldOptional "memoryTypeIndex" VkMemoryAllocateInfo = False
type FieldOptional "pNext" VkMemoryAllocateInfo Source # 
type FieldOptional "sType" VkMemoryAllocateInfo Source # 
type FieldOffset "allocationSize" VkMemoryAllocateInfo Source # 
type FieldOffset "allocationSize" VkMemoryAllocateInfo = 16
type FieldOffset "memoryTypeIndex" VkMemoryAllocateInfo Source # 
type FieldOffset "memoryTypeIndex" VkMemoryAllocateInfo = 24
type FieldOffset "pNext" VkMemoryAllocateInfo Source # 
type FieldOffset "sType" VkMemoryAllocateInfo Source # 
type FieldIsArray "allocationSize" VkMemoryAllocateInfo Source # 
type FieldIsArray "allocationSize" VkMemoryAllocateInfo = False
type FieldIsArray "memoryTypeIndex" VkMemoryAllocateInfo Source # 
type FieldIsArray "memoryTypeIndex" VkMemoryAllocateInfo = False
type FieldIsArray "pNext" VkMemoryAllocateInfo Source # 
type FieldIsArray "sType" VkMemoryAllocateInfo Source # 

data VkMemoryBarrier Source #

typedef struct VkMemoryBarrier {
    VkStructureType sType;
    const void*            pNext;
    VkAccessFlags          srcAccessMask;
    VkAccessFlags          dstAccessMask;
} VkMemoryBarrier;

VkMemoryBarrier registry at www.khronos.org

Instances

Eq VkMemoryBarrier Source # 
Ord VkMemoryBarrier Source # 
Show VkMemoryBarrier Source # 
Storable VkMemoryBarrier Source # 
VulkanMarshalPrim VkMemoryBarrier Source # 
VulkanMarshal VkMemoryBarrier Source # 
CanWriteField "dstAccessMask" VkMemoryBarrier Source # 

Methods

writeField :: Ptr VkMemoryBarrier -> FieldType "dstAccessMask" VkMemoryBarrier -> IO () Source #

CanWriteField "pNext" VkMemoryBarrier Source # 
CanWriteField "sType" VkMemoryBarrier Source # 
CanWriteField "srcAccessMask" VkMemoryBarrier Source # 

Methods

writeField :: Ptr VkMemoryBarrier -> FieldType "srcAccessMask" VkMemoryBarrier -> IO () Source #

CanReadField "dstAccessMask" VkMemoryBarrier Source # 
CanReadField "pNext" VkMemoryBarrier Source # 
CanReadField "sType" VkMemoryBarrier Source # 
CanReadField "srcAccessMask" VkMemoryBarrier Source # 
HasField "dstAccessMask" VkMemoryBarrier Source # 

Associated Types

type FieldType ("dstAccessMask" :: Symbol) VkMemoryBarrier :: Type Source #

type FieldOptional ("dstAccessMask" :: Symbol) VkMemoryBarrier :: Bool Source #

type FieldOffset ("dstAccessMask" :: Symbol) VkMemoryBarrier :: Nat Source #

type FieldIsArray ("dstAccessMask" :: Symbol) VkMemoryBarrier :: Bool Source #

HasField "pNext" VkMemoryBarrier Source # 
HasField "sType" VkMemoryBarrier Source # 
HasField "srcAccessMask" VkMemoryBarrier Source # 

Associated Types

type FieldType ("srcAccessMask" :: Symbol) VkMemoryBarrier :: Type Source #

type FieldOptional ("srcAccessMask" :: Symbol) VkMemoryBarrier :: Bool Source #

type FieldOffset ("srcAccessMask" :: Symbol) VkMemoryBarrier :: Nat Source #

type FieldIsArray ("srcAccessMask" :: Symbol) VkMemoryBarrier :: Bool Source #

type StructFields VkMemoryBarrier Source # 
type StructFields VkMemoryBarrier = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "srcAccessMask" ((:) Symbol "dstAccessMask" ([] Symbol))))
type CUnionType VkMemoryBarrier Source # 
type ReturnedOnly VkMemoryBarrier Source # 
type StructExtends VkMemoryBarrier Source # 
type FieldType "dstAccessMask" VkMemoryBarrier Source # 
type FieldType "dstAccessMask" VkMemoryBarrier = VkAccessFlags
type FieldType "pNext" VkMemoryBarrier Source # 
type FieldType "sType" VkMemoryBarrier Source # 
type FieldType "srcAccessMask" VkMemoryBarrier Source # 
type FieldType "srcAccessMask" VkMemoryBarrier = VkAccessFlags
type FieldOptional "dstAccessMask" VkMemoryBarrier Source # 
type FieldOptional "dstAccessMask" VkMemoryBarrier = True
type FieldOptional "pNext" VkMemoryBarrier Source # 
type FieldOptional "sType" VkMemoryBarrier Source # 
type FieldOptional "srcAccessMask" VkMemoryBarrier Source # 
type FieldOptional "srcAccessMask" VkMemoryBarrier = True
type FieldOffset "dstAccessMask" VkMemoryBarrier Source # 
type FieldOffset "dstAccessMask" VkMemoryBarrier = 20
type FieldOffset "pNext" VkMemoryBarrier Source # 
type FieldOffset "pNext" VkMemoryBarrier = 8
type FieldOffset "sType" VkMemoryBarrier Source # 
type FieldOffset "sType" VkMemoryBarrier = 0
type FieldOffset "srcAccessMask" VkMemoryBarrier Source # 
type FieldOffset "srcAccessMask" VkMemoryBarrier = 16
type FieldIsArray "dstAccessMask" VkMemoryBarrier Source # 
type FieldIsArray "dstAccessMask" VkMemoryBarrier = False
type FieldIsArray "pNext" VkMemoryBarrier Source # 
type FieldIsArray "sType" VkMemoryBarrier Source # 
type FieldIsArray "srcAccessMask" VkMemoryBarrier Source # 
type FieldIsArray "srcAccessMask" VkMemoryBarrier = False

data VkMemoryDedicatedAllocateInfo Source #

typedef struct VkMemoryDedicatedAllocateInfo {
    VkStructureType sType;
    const void*                      pNext;
    VkImage          image;
    VkBuffer         buffer;
} VkMemoryDedicatedAllocateInfo;

VkMemoryDedicatedAllocateInfo registry at www.khronos.org

Instances

Eq VkMemoryDedicatedAllocateInfo Source # 
Ord VkMemoryDedicatedAllocateInfo Source # 
Show VkMemoryDedicatedAllocateInfo Source # 
Storable VkMemoryDedicatedAllocateInfo Source # 
VulkanMarshalPrim VkMemoryDedicatedAllocateInfo Source # 
VulkanMarshal VkMemoryDedicatedAllocateInfo Source # 
CanWriteField "buffer" VkMemoryDedicatedAllocateInfo Source # 
CanWriteField "image" VkMemoryDedicatedAllocateInfo Source # 
CanWriteField "pNext" VkMemoryDedicatedAllocateInfo Source # 
CanWriteField "sType" VkMemoryDedicatedAllocateInfo Source # 
CanReadField "buffer" VkMemoryDedicatedAllocateInfo Source # 
CanReadField "image" VkMemoryDedicatedAllocateInfo Source # 
CanReadField "pNext" VkMemoryDedicatedAllocateInfo Source # 
CanReadField "sType" VkMemoryDedicatedAllocateInfo Source # 
HasField "buffer" VkMemoryDedicatedAllocateInfo Source # 
HasField "image" VkMemoryDedicatedAllocateInfo Source # 
HasField "pNext" VkMemoryDedicatedAllocateInfo Source # 
HasField "sType" VkMemoryDedicatedAllocateInfo Source # 
type StructFields VkMemoryDedicatedAllocateInfo Source # 
type StructFields VkMemoryDedicatedAllocateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "image" ((:) Symbol "buffer" ([] Symbol))))
type CUnionType VkMemoryDedicatedAllocateInfo Source # 
type ReturnedOnly VkMemoryDedicatedAllocateInfo Source # 
type StructExtends VkMemoryDedicatedAllocateInfo Source # 
type FieldType "buffer" VkMemoryDedicatedAllocateInfo Source # 
type FieldType "image" VkMemoryDedicatedAllocateInfo Source # 
type FieldType "pNext" VkMemoryDedicatedAllocateInfo Source # 
type FieldType "sType" VkMemoryDedicatedAllocateInfo Source # 
type FieldOptional "buffer" VkMemoryDedicatedAllocateInfo Source # 
type FieldOptional "image" VkMemoryDedicatedAllocateInfo Source # 
type FieldOptional "pNext" VkMemoryDedicatedAllocateInfo Source # 
type FieldOptional "sType" VkMemoryDedicatedAllocateInfo Source # 
type FieldOffset "buffer" VkMemoryDedicatedAllocateInfo Source # 
type FieldOffset "image" VkMemoryDedicatedAllocateInfo Source # 
type FieldOffset "pNext" VkMemoryDedicatedAllocateInfo Source # 
type FieldOffset "sType" VkMemoryDedicatedAllocateInfo Source # 
type FieldIsArray "buffer" VkMemoryDedicatedAllocateInfo Source # 
type FieldIsArray "image" VkMemoryDedicatedAllocateInfo Source # 
type FieldIsArray "pNext" VkMemoryDedicatedAllocateInfo Source # 
type FieldIsArray "sType" VkMemoryDedicatedAllocateInfo Source # 

data VkMemoryDedicatedRequirements Source #

typedef struct VkMemoryDedicatedRequirements {
    VkStructureType sType;
    void*                            pNext;
    VkBool32                         prefersDedicatedAllocation;
    VkBool32                         requiresDedicatedAllocation;
} VkMemoryDedicatedRequirements;

VkMemoryDedicatedRequirements registry at www.khronos.org

Instances

Eq VkMemoryDedicatedRequirements Source # 
Ord VkMemoryDedicatedRequirements Source # 
Show VkMemoryDedicatedRequirements Source # 
Storable VkMemoryDedicatedRequirements Source # 
VulkanMarshalPrim VkMemoryDedicatedRequirements Source # 
VulkanMarshal VkMemoryDedicatedRequirements Source # 
CanWriteField "pNext" VkMemoryDedicatedRequirements Source # 
CanWriteField "prefersDedicatedAllocation" VkMemoryDedicatedRequirements Source # 
CanWriteField "requiresDedicatedAllocation" VkMemoryDedicatedRequirements Source # 
CanWriteField "sType" VkMemoryDedicatedRequirements Source # 
CanReadField "pNext" VkMemoryDedicatedRequirements Source # 
CanReadField "prefersDedicatedAllocation" VkMemoryDedicatedRequirements Source # 
CanReadField "requiresDedicatedAllocation" VkMemoryDedicatedRequirements Source # 
CanReadField "sType" VkMemoryDedicatedRequirements Source # 
HasField "pNext" VkMemoryDedicatedRequirements Source # 
HasField "prefersDedicatedAllocation" VkMemoryDedicatedRequirements Source # 

Associated Types

type FieldType ("prefersDedicatedAllocation" :: Symbol) VkMemoryDedicatedRequirements :: Type Source #

type FieldOptional ("prefersDedicatedAllocation" :: Symbol) VkMemoryDedicatedRequirements :: Bool Source #

type FieldOffset ("prefersDedicatedAllocation" :: Symbol) VkMemoryDedicatedRequirements :: Nat Source #

type FieldIsArray ("prefersDedicatedAllocation" :: Symbol) VkMemoryDedicatedRequirements :: Bool Source #

HasField "requiresDedicatedAllocation" VkMemoryDedicatedRequirements Source # 

Associated Types

type FieldType ("requiresDedicatedAllocation" :: Symbol) VkMemoryDedicatedRequirements :: Type Source #

type FieldOptional ("requiresDedicatedAllocation" :: Symbol) VkMemoryDedicatedRequirements :: Bool Source #

type FieldOffset ("requiresDedicatedAllocation" :: Symbol) VkMemoryDedicatedRequirements :: Nat Source #

type FieldIsArray ("requiresDedicatedAllocation" :: Symbol) VkMemoryDedicatedRequirements :: Bool Source #

HasField "sType" VkMemoryDedicatedRequirements Source # 
type StructFields VkMemoryDedicatedRequirements Source # 
type StructFields VkMemoryDedicatedRequirements = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "prefersDedicatedAllocation" ((:) Symbol "requiresDedicatedAllocation" ([] Symbol))))
type CUnionType VkMemoryDedicatedRequirements Source # 
type ReturnedOnly VkMemoryDedicatedRequirements Source # 
type StructExtends VkMemoryDedicatedRequirements Source # 
type FieldType "pNext" VkMemoryDedicatedRequirements Source # 
type FieldType "prefersDedicatedAllocation" VkMemoryDedicatedRequirements Source # 
type FieldType "prefersDedicatedAllocation" VkMemoryDedicatedRequirements = VkBool32
type FieldType "requiresDedicatedAllocation" VkMemoryDedicatedRequirements Source # 
type FieldType "requiresDedicatedAllocation" VkMemoryDedicatedRequirements = VkBool32
type FieldType "sType" VkMemoryDedicatedRequirements Source # 
type FieldOptional "pNext" VkMemoryDedicatedRequirements Source # 
type FieldOptional "prefersDedicatedAllocation" VkMemoryDedicatedRequirements Source # 
type FieldOptional "prefersDedicatedAllocation" VkMemoryDedicatedRequirements = False
type FieldOptional "requiresDedicatedAllocation" VkMemoryDedicatedRequirements Source # 
type FieldOptional "requiresDedicatedAllocation" VkMemoryDedicatedRequirements = False
type FieldOptional "sType" VkMemoryDedicatedRequirements Source # 
type FieldOffset "pNext" VkMemoryDedicatedRequirements Source # 
type FieldOffset "prefersDedicatedAllocation" VkMemoryDedicatedRequirements Source # 
type FieldOffset "prefersDedicatedAllocation" VkMemoryDedicatedRequirements = 16
type FieldOffset "requiresDedicatedAllocation" VkMemoryDedicatedRequirements Source # 
type FieldOffset "requiresDedicatedAllocation" VkMemoryDedicatedRequirements = 20
type FieldOffset "sType" VkMemoryDedicatedRequirements Source # 
type FieldIsArray "pNext" VkMemoryDedicatedRequirements Source # 
type FieldIsArray "prefersDedicatedAllocation" VkMemoryDedicatedRequirements Source # 
type FieldIsArray "prefersDedicatedAllocation" VkMemoryDedicatedRequirements = False
type FieldIsArray "requiresDedicatedAllocation" VkMemoryDedicatedRequirements Source # 
type FieldIsArray "requiresDedicatedAllocation" VkMemoryDedicatedRequirements = False
type FieldIsArray "sType" VkMemoryDedicatedRequirements Source # 

data VkMemoryFdPropertiesKHR Source #

typedef struct VkMemoryFdPropertiesKHR {
    VkStructureType sType;
    void*                            pNext;
    uint32_t                         memoryTypeBits;
} VkMemoryFdPropertiesKHR;

VkMemoryFdPropertiesKHR registry at www.khronos.org

Instances

Eq VkMemoryFdPropertiesKHR Source # 
Ord VkMemoryFdPropertiesKHR Source # 
Show VkMemoryFdPropertiesKHR Source # 
Storable VkMemoryFdPropertiesKHR Source # 
VulkanMarshalPrim VkMemoryFdPropertiesKHR Source # 
VulkanMarshal VkMemoryFdPropertiesKHR Source # 
CanWriteField "memoryTypeBits" VkMemoryFdPropertiesKHR Source # 
CanWriteField "pNext" VkMemoryFdPropertiesKHR Source # 
CanWriteField "sType" VkMemoryFdPropertiesKHR Source # 
CanReadField "memoryTypeBits" VkMemoryFdPropertiesKHR Source # 
CanReadField "pNext" VkMemoryFdPropertiesKHR Source # 
CanReadField "sType" VkMemoryFdPropertiesKHR Source # 
HasField "memoryTypeBits" VkMemoryFdPropertiesKHR Source # 

Associated Types

type FieldType ("memoryTypeBits" :: Symbol) VkMemoryFdPropertiesKHR :: Type Source #

type FieldOptional ("memoryTypeBits" :: Symbol) VkMemoryFdPropertiesKHR :: Bool Source #

type FieldOffset ("memoryTypeBits" :: Symbol) VkMemoryFdPropertiesKHR :: Nat Source #

type FieldIsArray ("memoryTypeBits" :: Symbol) VkMemoryFdPropertiesKHR :: Bool Source #

HasField "pNext" VkMemoryFdPropertiesKHR Source # 
HasField "sType" VkMemoryFdPropertiesKHR Source # 
type StructFields VkMemoryFdPropertiesKHR Source # 
type StructFields VkMemoryFdPropertiesKHR = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "memoryTypeBits" ([] Symbol)))
type CUnionType VkMemoryFdPropertiesKHR Source # 
type ReturnedOnly VkMemoryFdPropertiesKHR Source # 
type StructExtends VkMemoryFdPropertiesKHR Source # 
type FieldType "memoryTypeBits" VkMemoryFdPropertiesKHR Source # 
type FieldType "memoryTypeBits" VkMemoryFdPropertiesKHR = Word32
type FieldType "pNext" VkMemoryFdPropertiesKHR Source # 
type FieldType "sType" VkMemoryFdPropertiesKHR Source # 
type FieldOptional "memoryTypeBits" VkMemoryFdPropertiesKHR Source # 
type FieldOptional "pNext" VkMemoryFdPropertiesKHR Source # 
type FieldOptional "sType" VkMemoryFdPropertiesKHR Source # 
type FieldOffset "memoryTypeBits" VkMemoryFdPropertiesKHR Source # 
type FieldOffset "memoryTypeBits" VkMemoryFdPropertiesKHR = 16
type FieldOffset "pNext" VkMemoryFdPropertiesKHR Source # 
type FieldOffset "sType" VkMemoryFdPropertiesKHR Source # 
type FieldIsArray "memoryTypeBits" VkMemoryFdPropertiesKHR Source # 
type FieldIsArray "pNext" VkMemoryFdPropertiesKHR Source # 
type FieldIsArray "sType" VkMemoryFdPropertiesKHR Source # 

data VkMemoryGetFdInfoKHR Source #

typedef struct VkMemoryGetFdInfoKHR {
    VkStructureType sType;
    const void*                      pNext;
    VkDeviceMemory                   memory;
    VkExternalMemoryHandleTypeFlagBits handleType;
} VkMemoryGetFdInfoKHR;

VkMemoryGetFdInfoKHR registry at www.khronos.org

Instances

Eq VkMemoryGetFdInfoKHR Source # 
Ord VkMemoryGetFdInfoKHR Source # 
Show VkMemoryGetFdInfoKHR Source # 
Storable VkMemoryGetFdInfoKHR Source # 
VulkanMarshalPrim VkMemoryGetFdInfoKHR Source # 
VulkanMarshal VkMemoryGetFdInfoKHR Source # 
CanWriteField "handleType" VkMemoryGetFdInfoKHR Source # 
CanWriteField "memory" VkMemoryGetFdInfoKHR Source # 
CanWriteField "pNext" VkMemoryGetFdInfoKHR Source # 
CanWriteField "sType" VkMemoryGetFdInfoKHR Source # 
CanReadField "handleType" VkMemoryGetFdInfoKHR Source # 
CanReadField "memory" VkMemoryGetFdInfoKHR Source # 
CanReadField "pNext" VkMemoryGetFdInfoKHR Source # 
CanReadField "sType" VkMemoryGetFdInfoKHR Source # 
HasField "handleType" VkMemoryGetFdInfoKHR Source # 

Associated Types

type FieldType ("handleType" :: Symbol) VkMemoryGetFdInfoKHR :: Type Source #

type FieldOptional ("handleType" :: Symbol) VkMemoryGetFdInfoKHR :: Bool Source #

type FieldOffset ("handleType" :: Symbol) VkMemoryGetFdInfoKHR :: Nat Source #

type FieldIsArray ("handleType" :: Symbol) VkMemoryGetFdInfoKHR :: Bool Source #

HasField "memory" VkMemoryGetFdInfoKHR Source # 
HasField "pNext" VkMemoryGetFdInfoKHR Source # 
HasField "sType" VkMemoryGetFdInfoKHR Source # 
type StructFields VkMemoryGetFdInfoKHR Source # 
type StructFields VkMemoryGetFdInfoKHR = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "memory" ((:) Symbol "handleType" ([] Symbol))))
type CUnionType VkMemoryGetFdInfoKHR Source # 
type ReturnedOnly VkMemoryGetFdInfoKHR Source # 
type StructExtends VkMemoryGetFdInfoKHR Source # 
type FieldType "handleType" VkMemoryGetFdInfoKHR Source # 
type FieldType "memory" VkMemoryGetFdInfoKHR Source # 
type FieldType "pNext" VkMemoryGetFdInfoKHR Source # 
type FieldType "sType" VkMemoryGetFdInfoKHR Source # 
type FieldOptional "handleType" VkMemoryGetFdInfoKHR Source # 
type FieldOptional "memory" VkMemoryGetFdInfoKHR Source # 
type FieldOptional "pNext" VkMemoryGetFdInfoKHR Source # 
type FieldOptional "sType" VkMemoryGetFdInfoKHR Source # 
type FieldOffset "handleType" VkMemoryGetFdInfoKHR Source # 
type FieldOffset "handleType" VkMemoryGetFdInfoKHR = 24
type FieldOffset "memory" VkMemoryGetFdInfoKHR Source # 
type FieldOffset "pNext" VkMemoryGetFdInfoKHR Source # 
type FieldOffset "sType" VkMemoryGetFdInfoKHR Source # 
type FieldIsArray "handleType" VkMemoryGetFdInfoKHR Source # 
type FieldIsArray "memory" VkMemoryGetFdInfoKHR Source # 
type FieldIsArray "pNext" VkMemoryGetFdInfoKHR Source # 
type FieldIsArray "sType" VkMemoryGetFdInfoKHR Source # 

data VkMemoryHeap Source #

typedef struct VkMemoryHeap {
    VkDeviceSize           size;
    VkMemoryHeapFlags      flags;
} VkMemoryHeap;

VkMemoryHeap registry at www.khronos.org

Instances

Eq VkMemoryHeap Source # 
Ord VkMemoryHeap Source # 
Show VkMemoryHeap Source # 
Storable VkMemoryHeap Source # 
VulkanMarshalPrim VkMemoryHeap Source # 
VulkanMarshal VkMemoryHeap Source # 
CanWriteField "flags" VkMemoryHeap Source # 
CanWriteField "size" VkMemoryHeap Source # 
CanReadField "flags" VkMemoryHeap Source # 
CanReadField "size" VkMemoryHeap Source # 
HasField "flags" VkMemoryHeap Source # 

Associated Types

type FieldType ("flags" :: Symbol) VkMemoryHeap :: Type Source #

type FieldOptional ("flags" :: Symbol) VkMemoryHeap :: Bool Source #

type FieldOffset ("flags" :: Symbol) VkMemoryHeap :: Nat Source #

type FieldIsArray ("flags" :: Symbol) VkMemoryHeap :: Bool Source #

HasField "size" VkMemoryHeap Source # 
type StructFields VkMemoryHeap Source # 
type StructFields VkMemoryHeap = (:) Symbol "size" ((:) Symbol "flags" ([] Symbol))
type CUnionType VkMemoryHeap Source # 
type ReturnedOnly VkMemoryHeap Source # 
type StructExtends VkMemoryHeap Source # 
type FieldType "flags" VkMemoryHeap Source # 
type FieldType "size" VkMemoryHeap Source # 
type FieldOptional "flags" VkMemoryHeap Source # 
type FieldOptional "size" VkMemoryHeap Source # 
type FieldOffset "flags" VkMemoryHeap Source # 
type FieldOffset "flags" VkMemoryHeap = 8
type FieldOffset "size" VkMemoryHeap Source # 
type FieldOffset "size" VkMemoryHeap = 0
type FieldIsArray "flags" VkMemoryHeap Source # 
type FieldIsArray "size" VkMemoryHeap Source # 

data VkMemoryHostPointerPropertiesEXT Source #

typedef struct VkMemoryHostPointerPropertiesEXT {
    VkStructureType sType;
    void* pNext;
    uint32_t memoryTypeBits;
} VkMemoryHostPointerPropertiesEXT;

VkMemoryHostPointerPropertiesEXT registry at www.khronos.org

Instances

Eq VkMemoryHostPointerPropertiesEXT Source # 
Ord VkMemoryHostPointerPropertiesEXT Source # 
Show VkMemoryHostPointerPropertiesEXT Source # 
Storable VkMemoryHostPointerPropertiesEXT Source # 
VulkanMarshalPrim VkMemoryHostPointerPropertiesEXT Source # 
VulkanMarshal VkMemoryHostPointerPropertiesEXT Source # 
CanWriteField "memoryTypeBits" VkMemoryHostPointerPropertiesEXT Source # 
CanWriteField "pNext" VkMemoryHostPointerPropertiesEXT Source # 
CanWriteField "sType" VkMemoryHostPointerPropertiesEXT Source # 
CanReadField "memoryTypeBits" VkMemoryHostPointerPropertiesEXT Source # 
CanReadField "pNext" VkMemoryHostPointerPropertiesEXT Source # 
CanReadField "sType" VkMemoryHostPointerPropertiesEXT Source # 
HasField "memoryTypeBits" VkMemoryHostPointerPropertiesEXT Source # 
HasField "pNext" VkMemoryHostPointerPropertiesEXT Source # 
HasField "sType" VkMemoryHostPointerPropertiesEXT Source # 
type StructFields VkMemoryHostPointerPropertiesEXT Source # 
type StructFields VkMemoryHostPointerPropertiesEXT = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "memoryTypeBits" ([] Symbol)))
type CUnionType VkMemoryHostPointerPropertiesEXT Source # 
type ReturnedOnly VkMemoryHostPointerPropertiesEXT Source # 
type StructExtends VkMemoryHostPointerPropertiesEXT Source # 
type FieldType "memoryTypeBits" VkMemoryHostPointerPropertiesEXT Source # 
type FieldType "pNext" VkMemoryHostPointerPropertiesEXT Source # 
type FieldType "sType" VkMemoryHostPointerPropertiesEXT Source # 
type FieldOptional "memoryTypeBits" VkMemoryHostPointerPropertiesEXT Source # 
type FieldOptional "pNext" VkMemoryHostPointerPropertiesEXT Source # 
type FieldOptional "sType" VkMemoryHostPointerPropertiesEXT Source # 
type FieldOffset "memoryTypeBits" VkMemoryHostPointerPropertiesEXT Source # 
type FieldOffset "pNext" VkMemoryHostPointerPropertiesEXT Source # 
type FieldOffset "sType" VkMemoryHostPointerPropertiesEXT Source # 
type FieldIsArray "memoryTypeBits" VkMemoryHostPointerPropertiesEXT Source # 
type FieldIsArray "pNext" VkMemoryHostPointerPropertiesEXT Source # 
type FieldIsArray "sType" VkMemoryHostPointerPropertiesEXT Source # 

data VkMemoryRequirements Source #

typedef struct VkMemoryRequirements {
    VkDeviceSize           size;
    VkDeviceSize           alignment;
    uint32_t               memoryTypeBits;
} VkMemoryRequirements;

VkMemoryRequirements registry at www.khronos.org

Instances

Eq VkMemoryRequirements Source # 
Ord VkMemoryRequirements Source # 
Show VkMemoryRequirements Source # 
Storable VkMemoryRequirements Source # 
VulkanMarshalPrim VkMemoryRequirements Source # 
VulkanMarshal VkMemoryRequirements Source # 
CanWriteField "alignment" VkMemoryRequirements Source # 
CanWriteField "memoryTypeBits" VkMemoryRequirements Source # 
CanWriteField "size" VkMemoryRequirements Source # 
CanReadField "alignment" VkMemoryRequirements Source # 
CanReadField "memoryTypeBits" VkMemoryRequirements Source # 
CanReadField "size" VkMemoryRequirements Source # 
HasField "alignment" VkMemoryRequirements Source # 
HasField "memoryTypeBits" VkMemoryRequirements Source # 

Associated Types

type FieldType ("memoryTypeBits" :: Symbol) VkMemoryRequirements :: Type Source #

type FieldOptional ("memoryTypeBits" :: Symbol) VkMemoryRequirements :: Bool Source #

type FieldOffset ("memoryTypeBits" :: Symbol) VkMemoryRequirements :: Nat Source #

type FieldIsArray ("memoryTypeBits" :: Symbol) VkMemoryRequirements :: Bool Source #

HasField "size" VkMemoryRequirements Source # 
type StructFields VkMemoryRequirements Source # 
type StructFields VkMemoryRequirements = (:) Symbol "size" ((:) Symbol "alignment" ((:) Symbol "memoryTypeBits" ([] Symbol)))
type CUnionType VkMemoryRequirements Source # 
type ReturnedOnly VkMemoryRequirements Source # 
type StructExtends VkMemoryRequirements Source # 
type FieldType "alignment" VkMemoryRequirements Source # 
type FieldType "memoryTypeBits" VkMemoryRequirements Source # 
type FieldType "memoryTypeBits" VkMemoryRequirements = Word32
type FieldType "size" VkMemoryRequirements Source # 
type FieldOptional "alignment" VkMemoryRequirements Source # 
type FieldOptional "memoryTypeBits" VkMemoryRequirements Source # 
type FieldOptional "memoryTypeBits" VkMemoryRequirements = False
type FieldOptional "size" VkMemoryRequirements Source # 
type FieldOffset "alignment" VkMemoryRequirements Source # 
type FieldOffset "alignment" VkMemoryRequirements = 8
type FieldOffset "memoryTypeBits" VkMemoryRequirements Source # 
type FieldOffset "memoryTypeBits" VkMemoryRequirements = 16
type FieldOffset "size" VkMemoryRequirements Source # 
type FieldIsArray "alignment" VkMemoryRequirements Source # 
type FieldIsArray "memoryTypeBits" VkMemoryRequirements Source # 
type FieldIsArray "memoryTypeBits" VkMemoryRequirements = False
type FieldIsArray "size" VkMemoryRequirements Source # 

data VkMemoryRequirements2 Source #

typedef struct VkMemoryRequirements2 {
    VkStructureType sType;
    void* pNext;
    VkMemoryRequirements                                                 memoryRequirements;
} VkMemoryRequirements2;

VkMemoryRequirements2 registry at www.khronos.org

Instances

Eq VkMemoryRequirements2 Source # 
Ord VkMemoryRequirements2 Source # 
Show VkMemoryRequirements2 Source # 
Storable VkMemoryRequirements2 Source # 
VulkanMarshalPrim VkMemoryRequirements2 Source # 
VulkanMarshal VkMemoryRequirements2 Source # 
CanWriteField "memoryRequirements" VkMemoryRequirements2 Source # 
CanWriteField "pNext" VkMemoryRequirements2 Source # 
CanWriteField "sType" VkMemoryRequirements2 Source # 
CanReadField "memoryRequirements" VkMemoryRequirements2 Source # 
CanReadField "pNext" VkMemoryRequirements2 Source # 
CanReadField "sType" VkMemoryRequirements2 Source # 
HasField "memoryRequirements" VkMemoryRequirements2 Source # 

Associated Types

type FieldType ("memoryRequirements" :: Symbol) VkMemoryRequirements2 :: Type Source #

type FieldOptional ("memoryRequirements" :: Symbol) VkMemoryRequirements2 :: Bool Source #

type FieldOffset ("memoryRequirements" :: Symbol) VkMemoryRequirements2 :: Nat Source #

type FieldIsArray ("memoryRequirements" :: Symbol) VkMemoryRequirements2 :: Bool Source #

HasField "pNext" VkMemoryRequirements2 Source # 
HasField "sType" VkMemoryRequirements2 Source # 
type StructFields VkMemoryRequirements2 Source # 
type StructFields VkMemoryRequirements2 = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "memoryRequirements" ([] Symbol)))
type CUnionType VkMemoryRequirements2 Source # 
type ReturnedOnly VkMemoryRequirements2 Source # 
type StructExtends VkMemoryRequirements2 Source # 
type FieldType "memoryRequirements" VkMemoryRequirements2 Source # 
type FieldType "pNext" VkMemoryRequirements2 Source # 
type FieldType "sType" VkMemoryRequirements2 Source # 
type FieldOptional "memoryRequirements" VkMemoryRequirements2 Source # 
type FieldOptional "memoryRequirements" VkMemoryRequirements2 = False
type FieldOptional "pNext" VkMemoryRequirements2 Source # 
type FieldOptional "sType" VkMemoryRequirements2 Source # 
type FieldOffset "memoryRequirements" VkMemoryRequirements2 Source # 
type FieldOffset "memoryRequirements" VkMemoryRequirements2 = 16
type FieldOffset "pNext" VkMemoryRequirements2 Source # 
type FieldOffset "sType" VkMemoryRequirements2 Source # 
type FieldIsArray "memoryRequirements" VkMemoryRequirements2 Source # 
type FieldIsArray "memoryRequirements" VkMemoryRequirements2 = False
type FieldIsArray "pNext" VkMemoryRequirements2 Source # 
type FieldIsArray "sType" VkMemoryRequirements2 Source # 

data VkMemoryType Source #

typedef struct VkMemoryType {
    VkMemoryPropertyFlags  propertyFlags;
    uint32_t               heapIndex;
} VkMemoryType;

VkMemoryType registry at www.khronos.org

Instances

Eq VkMemoryType Source # 
Ord VkMemoryType Source # 
Show VkMemoryType Source # 
Storable VkMemoryType Source # 
VulkanMarshalPrim VkMemoryType Source # 
VulkanMarshal VkMemoryType Source # 
CanWriteField "heapIndex" VkMemoryType Source # 

Methods

writeField :: Ptr VkMemoryType -> FieldType "heapIndex" VkMemoryType -> IO () Source #

CanWriteField "propertyFlags" VkMemoryType Source # 

Methods

writeField :: Ptr VkMemoryType -> FieldType "propertyFlags" VkMemoryType -> IO () Source #

CanReadField "heapIndex" VkMemoryType Source # 
CanReadField "propertyFlags" VkMemoryType Source # 
HasField "heapIndex" VkMemoryType Source # 

Associated Types

type FieldType ("heapIndex" :: Symbol) VkMemoryType :: Type Source #

type FieldOptional ("heapIndex" :: Symbol) VkMemoryType :: Bool Source #

type FieldOffset ("heapIndex" :: Symbol) VkMemoryType :: Nat Source #

type FieldIsArray ("heapIndex" :: Symbol) VkMemoryType :: Bool Source #

HasField "propertyFlags" VkMemoryType Source # 

Associated Types

type FieldType ("propertyFlags" :: Symbol) VkMemoryType :: Type Source #

type FieldOptional ("propertyFlags" :: Symbol) VkMemoryType :: Bool Source #

type FieldOffset ("propertyFlags" :: Symbol) VkMemoryType :: Nat Source #

type FieldIsArray ("propertyFlags" :: Symbol) VkMemoryType :: Bool Source #

type StructFields VkMemoryType Source # 
type StructFields VkMemoryType = (:) Symbol "propertyFlags" ((:) Symbol "heapIndex" ([] Symbol))
type CUnionType VkMemoryType Source # 
type ReturnedOnly VkMemoryType Source # 
type StructExtends VkMemoryType Source # 
type FieldType "heapIndex" VkMemoryType Source # 
type FieldType "heapIndex" VkMemoryType = Word32
type FieldType "propertyFlags" VkMemoryType Source # 
type FieldOptional "heapIndex" VkMemoryType Source # 
type FieldOptional "heapIndex" VkMemoryType = False
type FieldOptional "propertyFlags" VkMemoryType Source # 
type FieldOptional "propertyFlags" VkMemoryType = True
type FieldOffset "heapIndex" VkMemoryType Source # 
type FieldOffset "heapIndex" VkMemoryType = 4
type FieldOffset "propertyFlags" VkMemoryType Source # 
type FieldOffset "propertyFlags" VkMemoryType = 0
type FieldIsArray "heapIndex" VkMemoryType Source # 
type FieldIsArray "heapIndex" VkMemoryType = False
type FieldIsArray "propertyFlags" VkMemoryType Source # 
type FieldIsArray "propertyFlags" VkMemoryType = False

Promoted from VK_KHR_device_group

data VkClearAttachment Source #

typedef struct VkClearAttachment {
    VkImageAspectFlags     aspectMask;
    uint32_t               colorAttachment;
    VkClearValue           clearValue;
} VkClearAttachment;

VkClearAttachment registry at www.khronos.org

Instances

Eq VkClearAttachment Source # 
Ord VkClearAttachment Source # 
Show VkClearAttachment Source # 
Storable VkClearAttachment Source # 
VulkanMarshalPrim VkClearAttachment Source # 
VulkanMarshal VkClearAttachment Source # 
CanWriteField "aspectMask" VkClearAttachment Source # 
CanWriteField "clearValue" VkClearAttachment Source # 
CanWriteField "colorAttachment" VkClearAttachment Source # 

Methods

writeField :: Ptr VkClearAttachment -> FieldType "colorAttachment" VkClearAttachment -> IO () Source #

CanReadField "aspectMask" VkClearAttachment Source # 
CanReadField "clearValue" VkClearAttachment Source # 
CanReadField "colorAttachment" VkClearAttachment Source # 
HasField "aspectMask" VkClearAttachment Source # 

Associated Types

type FieldType ("aspectMask" :: Symbol) VkClearAttachment :: Type Source #

type FieldOptional ("aspectMask" :: Symbol) VkClearAttachment :: Bool Source #

type FieldOffset ("aspectMask" :: Symbol) VkClearAttachment :: Nat Source #

type FieldIsArray ("aspectMask" :: Symbol) VkClearAttachment :: Bool Source #

HasField "clearValue" VkClearAttachment Source # 

Associated Types

type FieldType ("clearValue" :: Symbol) VkClearAttachment :: Type Source #

type FieldOptional ("clearValue" :: Symbol) VkClearAttachment :: Bool Source #

type FieldOffset ("clearValue" :: Symbol) VkClearAttachment :: Nat Source #

type FieldIsArray ("clearValue" :: Symbol) VkClearAttachment :: Bool Source #

HasField "colorAttachment" VkClearAttachment Source # 

Associated Types

type FieldType ("colorAttachment" :: Symbol) VkClearAttachment :: Type Source #

type FieldOptional ("colorAttachment" :: Symbol) VkClearAttachment :: Bool Source #

type FieldOffset ("colorAttachment" :: Symbol) VkClearAttachment :: Nat Source #

type FieldIsArray ("colorAttachment" :: Symbol) VkClearAttachment :: Bool Source #

type StructFields VkClearAttachment Source # 
type StructFields VkClearAttachment = (:) Symbol "aspectMask" ((:) Symbol "colorAttachment" ((:) Symbol "clearValue" ([] Symbol)))
type CUnionType VkClearAttachment Source # 
type ReturnedOnly VkClearAttachment Source # 
type StructExtends VkClearAttachment Source # 
type FieldType "aspectMask" VkClearAttachment Source # 
type FieldType "clearValue" VkClearAttachment Source # 
type FieldType "colorAttachment" VkClearAttachment Source # 
type FieldType "colorAttachment" VkClearAttachment = Word32
type FieldOptional "aspectMask" VkClearAttachment Source # 
type FieldOptional "clearValue" VkClearAttachment Source # 
type FieldOptional "colorAttachment" VkClearAttachment Source # 
type FieldOptional "colorAttachment" VkClearAttachment = False
type FieldOffset "aspectMask" VkClearAttachment Source # 
type FieldOffset "aspectMask" VkClearAttachment = 0
type FieldOffset "clearValue" VkClearAttachment Source # 
type FieldOffset "clearValue" VkClearAttachment = 8
type FieldOffset "colorAttachment" VkClearAttachment Source # 
type FieldOffset "colorAttachment" VkClearAttachment = 4
type FieldIsArray "aspectMask" VkClearAttachment Source # 
type FieldIsArray "clearValue" VkClearAttachment Source # 
type FieldIsArray "colorAttachment" VkClearAttachment Source # 
type FieldIsArray "colorAttachment" VkClearAttachment = False

data VkClearColorValue Source #

/ Union allowing specification of floating point, integer, or unsigned integer color data. Actual value selected is based on imageattachment being cleared.

typedef union VkClearColorValue {
    float                  float32[4];
    int32_t                int32[4];
    uint32_t               uint32[4];
} VkClearColorValue;

VkClearColorValue registry at www.khronos.org

Instances

Eq VkClearColorValue Source # 
Ord VkClearColorValue Source # 
Show VkClearColorValue Source # 
Storable VkClearColorValue Source # 
VulkanMarshalPrim VkClearColorValue Source # 
VulkanMarshal VkClearColorValue Source # 
HasField "float32" VkClearColorValue Source # 
HasField "int32" VkClearColorValue Source # 
HasField "uint32" VkClearColorValue Source # 
(KnownNat idx, IndexInBounds "float32" idx VkClearColorValue) => CanWriteFieldArray "float32" idx VkClearColorValue Source # 
(KnownNat idx, IndexInBounds "int32" idx VkClearColorValue) => CanWriteFieldArray "int32" idx VkClearColorValue Source # 
(KnownNat idx, IndexInBounds "uint32" idx VkClearColorValue) => CanWriteFieldArray "uint32" idx VkClearColorValue Source # 
(KnownNat idx, IndexInBounds "float32" idx VkClearColorValue) => CanReadFieldArray "float32" idx VkClearColorValue Source # 
(KnownNat idx, IndexInBounds "int32" idx VkClearColorValue) => CanReadFieldArray "int32" idx VkClearColorValue Source # 
(KnownNat idx, IndexInBounds "uint32" idx VkClearColorValue) => CanReadFieldArray "uint32" idx VkClearColorValue Source # 
type StructFields VkClearColorValue Source # 
type StructFields VkClearColorValue = (:) Symbol "float32" ((:) Symbol "int32" ((:) Symbol "uint32" ([] Symbol)))
type CUnionType VkClearColorValue Source # 
type ReturnedOnly VkClearColorValue Source # 
type StructExtends VkClearColorValue Source # 
type FieldArrayLength "float32" VkClearColorValue Source # 
type FieldArrayLength "int32" VkClearColorValue Source # 
type FieldArrayLength "uint32" VkClearColorValue Source # 
type FieldType "float32" VkClearColorValue Source # 
type FieldType "int32" VkClearColorValue Source # 
type FieldType "uint32" VkClearColorValue Source # 
type FieldOptional "float32" VkClearColorValue Source # 
type FieldOptional "int32" VkClearColorValue Source # 
type FieldOptional "uint32" VkClearColorValue Source # 
type FieldOffset "float32" VkClearColorValue Source # 
type FieldOffset "float32" VkClearColorValue = 0
type FieldOffset "int32" VkClearColorValue Source # 
type FieldOffset "uint32" VkClearColorValue Source # 
type FieldOffset "uint32" VkClearColorValue = 0
type FieldIsArray "float32" VkClearColorValue Source # 
type FieldIsArray "int32" VkClearColorValue Source # 
type FieldIsArray "uint32" VkClearColorValue Source # 

data VkClearDepthStencilValue Source #

typedef struct VkClearDepthStencilValue {
    float                  depth;
    uint32_t               stencil;
} VkClearDepthStencilValue;

VkClearDepthStencilValue registry at www.khronos.org

Instances

Eq VkClearDepthStencilValue Source # 
Ord VkClearDepthStencilValue Source # 
Show VkClearDepthStencilValue Source # 
Storable VkClearDepthStencilValue Source # 
VulkanMarshalPrim VkClearDepthStencilValue Source # 
VulkanMarshal VkClearDepthStencilValue Source # 
CanWriteField "depth" VkClearDepthStencilValue Source # 
CanWriteField "stencil" VkClearDepthStencilValue Source # 
CanReadField "depth" VkClearDepthStencilValue Source # 
CanReadField "stencil" VkClearDepthStencilValue Source # 
HasField "depth" VkClearDepthStencilValue Source # 
HasField "stencil" VkClearDepthStencilValue Source # 
type StructFields VkClearDepthStencilValue Source # 
type StructFields VkClearDepthStencilValue = (:) Symbol "depth" ((:) Symbol "stencil" ([] Symbol))
type CUnionType VkClearDepthStencilValue Source # 
type ReturnedOnly VkClearDepthStencilValue Source # 
type StructExtends VkClearDepthStencilValue Source # 
type FieldType "depth" VkClearDepthStencilValue Source # 
type FieldType "stencil" VkClearDepthStencilValue Source # 
type FieldOptional "depth" VkClearDepthStencilValue Source # 
type FieldOptional "stencil" VkClearDepthStencilValue Source # 
type FieldOffset "depth" VkClearDepthStencilValue Source # 
type FieldOffset "stencil" VkClearDepthStencilValue Source # 
type FieldIsArray "depth" VkClearDepthStencilValue Source # 
type FieldIsArray "stencil" VkClearDepthStencilValue Source # 

data VkClearRect Source #

typedef struct VkClearRect {
    VkRect2D       rect;
    uint32_t       baseArrayLayer;
    uint32_t       layerCount;
} VkClearRect;

VkClearRect registry at www.khronos.org

Instances

Eq VkClearRect Source # 
Ord VkClearRect Source # 
Show VkClearRect Source # 
Storable VkClearRect Source # 
VulkanMarshalPrim VkClearRect Source # 
VulkanMarshal VkClearRect Source # 
CanWriteField "baseArrayLayer" VkClearRect Source # 

Methods

writeField :: Ptr VkClearRect -> FieldType "baseArrayLayer" VkClearRect -> IO () Source #

CanWriteField "layerCount" VkClearRect Source # 

Methods

writeField :: Ptr VkClearRect -> FieldType "layerCount" VkClearRect -> IO () Source #

CanWriteField "rect" VkClearRect Source # 
CanReadField "baseArrayLayer" VkClearRect Source # 

Methods

getField :: VkClearRect -> FieldType "baseArrayLayer" VkClearRect Source #

readField :: Ptr VkClearRect -> IO (FieldType "baseArrayLayer" VkClearRect) Source #

CanReadField "layerCount" VkClearRect Source # 
CanReadField "rect" VkClearRect Source # 
HasField "baseArrayLayer" VkClearRect Source # 

Associated Types

type FieldType ("baseArrayLayer" :: Symbol) VkClearRect :: Type Source #

type FieldOptional ("baseArrayLayer" :: Symbol) VkClearRect :: Bool Source #

type FieldOffset ("baseArrayLayer" :: Symbol) VkClearRect :: Nat Source #

type FieldIsArray ("baseArrayLayer" :: Symbol) VkClearRect :: Bool Source #

HasField "layerCount" VkClearRect Source # 

Associated Types

type FieldType ("layerCount" :: Symbol) VkClearRect :: Type Source #

type FieldOptional ("layerCount" :: Symbol) VkClearRect :: Bool Source #

type FieldOffset ("layerCount" :: Symbol) VkClearRect :: Nat Source #

type FieldIsArray ("layerCount" :: Symbol) VkClearRect :: Bool Source #

HasField "rect" VkClearRect Source # 

Associated Types

type FieldType ("rect" :: Symbol) VkClearRect :: Type Source #

type FieldOptional ("rect" :: Symbol) VkClearRect :: Bool Source #

type FieldOffset ("rect" :: Symbol) VkClearRect :: Nat Source #

type FieldIsArray ("rect" :: Symbol) VkClearRect :: Bool Source #

type StructFields VkClearRect Source # 
type StructFields VkClearRect = (:) Symbol "rect" ((:) Symbol "baseArrayLayer" ((:) Symbol "layerCount" ([] Symbol)))
type CUnionType VkClearRect Source # 
type ReturnedOnly VkClearRect Source # 
type StructExtends VkClearRect Source # 
type FieldType "baseArrayLayer" VkClearRect Source # 
type FieldType "baseArrayLayer" VkClearRect = Word32
type FieldType "layerCount" VkClearRect Source # 
type FieldType "layerCount" VkClearRect = Word32
type FieldType "rect" VkClearRect Source # 
type FieldOptional "baseArrayLayer" VkClearRect Source # 
type FieldOptional "baseArrayLayer" VkClearRect = False
type FieldOptional "layerCount" VkClearRect Source # 
type FieldOptional "layerCount" VkClearRect = False
type FieldOptional "rect" VkClearRect Source # 
type FieldOffset "baseArrayLayer" VkClearRect Source # 
type FieldOffset "baseArrayLayer" VkClearRect = 16
type FieldOffset "layerCount" VkClearRect Source # 
type FieldOffset "layerCount" VkClearRect = 20
type FieldOffset "rect" VkClearRect Source # 
type FieldOffset "rect" VkClearRect = 0
type FieldIsArray "baseArrayLayer" VkClearRect Source # 
type FieldIsArray "baseArrayLayer" VkClearRect = False
type FieldIsArray "layerCount" VkClearRect Source # 
type FieldIsArray "layerCount" VkClearRect = False
type FieldIsArray "rect" VkClearRect Source # 

data VkClearValue Source #

// Union allowing specification of color or depth and stencil values. Actual value selected is based on attachment being cleared.

typedef union VkClearValue {
    VkClearColorValue      color;
    VkClearDepthStencilValue depthStencil;
} VkClearValue;

VkClearValue registry at www.khronos.org

Instances

Eq VkClearValue Source # 
Ord VkClearValue Source # 
Show VkClearValue Source # 
Storable VkClearValue Source # 
VulkanMarshalPrim VkClearValue Source # 
VulkanMarshal VkClearValue Source # 
CanWriteField "color" VkClearValue Source # 
CanWriteField "depthStencil" VkClearValue Source # 

Methods

writeField :: Ptr VkClearValue -> FieldType "depthStencil" VkClearValue -> IO () Source #

CanReadField "color" VkClearValue Source # 
CanReadField "depthStencil" VkClearValue Source # 
HasField "color" VkClearValue Source # 

Associated Types

type FieldType ("color" :: Symbol) VkClearValue :: Type Source #

type FieldOptional ("color" :: Symbol) VkClearValue :: Bool Source #

type FieldOffset ("color" :: Symbol) VkClearValue :: Nat Source #

type FieldIsArray ("color" :: Symbol) VkClearValue :: Bool Source #

HasField "depthStencil" VkClearValue Source # 

Associated Types

type FieldType ("depthStencil" :: Symbol) VkClearValue :: Type Source #

type FieldOptional ("depthStencil" :: Symbol) VkClearValue :: Bool Source #

type FieldOffset ("depthStencil" :: Symbol) VkClearValue :: Nat Source #

type FieldIsArray ("depthStencil" :: Symbol) VkClearValue :: Bool Source #

type StructFields VkClearValue Source # 
type StructFields VkClearValue = (:) Symbol "color" ((:) Symbol "depthStencil" ([] Symbol))
type CUnionType VkClearValue Source # 
type ReturnedOnly VkClearValue Source # 
type StructExtends VkClearValue Source # 
type FieldType "color" VkClearValue Source # 
type FieldType "depthStencil" VkClearValue Source # 
type FieldOptional "color" VkClearValue Source # 
type FieldOptional "depthStencil" VkClearValue Source # 
type FieldOptional "depthStencil" VkClearValue = False
type FieldOffset "color" VkClearValue Source # 
type FieldOffset "color" VkClearValue = 0
type FieldOffset "depthStencil" VkClearValue Source # 
type FieldOffset "depthStencil" VkClearValue = 0
type FieldIsArray "color" VkClearValue Source # 
type FieldIsArray "depthStencil" VkClearValue Source # 
type FieldIsArray "depthStencil" VkClearValue = False

data VkCommandBufferAllocateInfo Source #

typedef struct VkCommandBufferAllocateInfo {
    VkStructureType sType;
    const void*            pNext;
    VkCommandPool          commandPool;
    VkCommandBufferLevel   level;
    uint32_t               commandBufferCount;
} VkCommandBufferAllocateInfo;

VkCommandBufferAllocateInfo registry at www.khronos.org

Instances

Eq VkCommandBufferAllocateInfo Source # 
Ord VkCommandBufferAllocateInfo Source # 
Show VkCommandBufferAllocateInfo Source # 
Storable VkCommandBufferAllocateInfo Source # 
VulkanMarshalPrim VkCommandBufferAllocateInfo Source # 
VulkanMarshal VkCommandBufferAllocateInfo Source # 
CanWriteField "commandBufferCount" VkCommandBufferAllocateInfo Source # 
CanWriteField "commandPool" VkCommandBufferAllocateInfo Source # 
CanWriteField "level" VkCommandBufferAllocateInfo Source # 
CanWriteField "pNext" VkCommandBufferAllocateInfo Source # 
CanWriteField "sType" VkCommandBufferAllocateInfo Source # 
CanReadField "commandBufferCount" VkCommandBufferAllocateInfo Source # 
CanReadField "commandPool" VkCommandBufferAllocateInfo Source # 
CanReadField "level" VkCommandBufferAllocateInfo Source # 
CanReadField "pNext" VkCommandBufferAllocateInfo Source # 
CanReadField "sType" VkCommandBufferAllocateInfo Source # 
HasField "commandBufferCount" VkCommandBufferAllocateInfo Source # 

Associated Types

type FieldType ("commandBufferCount" :: Symbol) VkCommandBufferAllocateInfo :: Type Source #

type FieldOptional ("commandBufferCount" :: Symbol) VkCommandBufferAllocateInfo :: Bool Source #

type FieldOffset ("commandBufferCount" :: Symbol) VkCommandBufferAllocateInfo :: Nat Source #

type FieldIsArray ("commandBufferCount" :: Symbol) VkCommandBufferAllocateInfo :: Bool Source #

HasField "commandPool" VkCommandBufferAllocateInfo Source # 
HasField "level" VkCommandBufferAllocateInfo Source # 
HasField "pNext" VkCommandBufferAllocateInfo Source # 
HasField "sType" VkCommandBufferAllocateInfo Source # 
type StructFields VkCommandBufferAllocateInfo Source # 
type StructFields VkCommandBufferAllocateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "commandPool" ((:) Symbol "level" ((:) Symbol "commandBufferCount" ([] Symbol)))))
type CUnionType VkCommandBufferAllocateInfo Source # 
type ReturnedOnly VkCommandBufferAllocateInfo Source # 
type StructExtends VkCommandBufferAllocateInfo Source # 
type FieldType "commandBufferCount" VkCommandBufferAllocateInfo Source # 
type FieldType "commandBufferCount" VkCommandBufferAllocateInfo = Word32
type FieldType "commandPool" VkCommandBufferAllocateInfo Source # 
type FieldType "level" VkCommandBufferAllocateInfo Source # 
type FieldType "pNext" VkCommandBufferAllocateInfo Source # 
type FieldType "sType" VkCommandBufferAllocateInfo Source # 
type FieldOptional "commandBufferCount" VkCommandBufferAllocateInfo Source # 
type FieldOptional "commandBufferCount" VkCommandBufferAllocateInfo = False
type FieldOptional "commandPool" VkCommandBufferAllocateInfo Source # 
type FieldOptional "level" VkCommandBufferAllocateInfo Source # 
type FieldOptional "pNext" VkCommandBufferAllocateInfo Source # 
type FieldOptional "sType" VkCommandBufferAllocateInfo Source # 
type FieldOffset "commandBufferCount" VkCommandBufferAllocateInfo Source # 
type FieldOffset "commandBufferCount" VkCommandBufferAllocateInfo = 28
type FieldOffset "commandPool" VkCommandBufferAllocateInfo Source # 
type FieldOffset "level" VkCommandBufferAllocateInfo Source # 
type FieldOffset "pNext" VkCommandBufferAllocateInfo Source # 
type FieldOffset "sType" VkCommandBufferAllocateInfo Source # 
type FieldIsArray "commandBufferCount" VkCommandBufferAllocateInfo Source # 
type FieldIsArray "commandBufferCount" VkCommandBufferAllocateInfo = False
type FieldIsArray "commandPool" VkCommandBufferAllocateInfo Source # 
type FieldIsArray "level" VkCommandBufferAllocateInfo Source # 
type FieldIsArray "pNext" VkCommandBufferAllocateInfo Source # 
type FieldIsArray "sType" VkCommandBufferAllocateInfo Source # 

data VkCommandBufferBeginInfo Source #

typedef struct VkCommandBufferBeginInfo {
    VkStructureType sType;
    const void*            pNext;
    VkCommandBufferUsageFlags  flags;
    const VkCommandBufferInheritanceInfo*       pInheritanceInfo;
} VkCommandBufferBeginInfo;

VkCommandBufferBeginInfo registry at www.khronos.org

Instances

Eq VkCommandBufferBeginInfo Source # 
Ord VkCommandBufferBeginInfo Source # 
Show VkCommandBufferBeginInfo Source # 
Storable VkCommandBufferBeginInfo Source # 
VulkanMarshalPrim VkCommandBufferBeginInfo Source # 
VulkanMarshal VkCommandBufferBeginInfo Source # 
CanWriteField "flags" VkCommandBufferBeginInfo Source # 
CanWriteField "pInheritanceInfo" VkCommandBufferBeginInfo Source # 
CanWriteField "pNext" VkCommandBufferBeginInfo Source # 
CanWriteField "sType" VkCommandBufferBeginInfo Source # 
CanReadField "flags" VkCommandBufferBeginInfo Source # 
CanReadField "pInheritanceInfo" VkCommandBufferBeginInfo Source # 
CanReadField "pNext" VkCommandBufferBeginInfo Source # 
CanReadField "sType" VkCommandBufferBeginInfo Source # 
HasField "flags" VkCommandBufferBeginInfo Source # 
HasField "pInheritanceInfo" VkCommandBufferBeginInfo Source # 

Associated Types

type FieldType ("pInheritanceInfo" :: Symbol) VkCommandBufferBeginInfo :: Type Source #

type FieldOptional ("pInheritanceInfo" :: Symbol) VkCommandBufferBeginInfo :: Bool Source #

type FieldOffset ("pInheritanceInfo" :: Symbol) VkCommandBufferBeginInfo :: Nat Source #

type FieldIsArray ("pInheritanceInfo" :: Symbol) VkCommandBufferBeginInfo :: Bool Source #

HasField "pNext" VkCommandBufferBeginInfo Source # 
HasField "sType" VkCommandBufferBeginInfo Source # 
type StructFields VkCommandBufferBeginInfo Source # 
type StructFields VkCommandBufferBeginInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "pInheritanceInfo" ([] Symbol))))
type CUnionType VkCommandBufferBeginInfo Source # 
type ReturnedOnly VkCommandBufferBeginInfo Source # 
type StructExtends VkCommandBufferBeginInfo Source # 
type FieldType "flags" VkCommandBufferBeginInfo Source # 
type FieldType "pInheritanceInfo" VkCommandBufferBeginInfo Source # 
type FieldType "pNext" VkCommandBufferBeginInfo Source # 
type FieldType "sType" VkCommandBufferBeginInfo Source # 
type FieldOptional "flags" VkCommandBufferBeginInfo Source # 
type FieldOptional "pInheritanceInfo" VkCommandBufferBeginInfo Source # 
type FieldOptional "pInheritanceInfo" VkCommandBufferBeginInfo = True
type FieldOptional "pNext" VkCommandBufferBeginInfo Source # 
type FieldOptional "sType" VkCommandBufferBeginInfo Source # 
type FieldOffset "flags" VkCommandBufferBeginInfo Source # 
type FieldOffset "pInheritanceInfo" VkCommandBufferBeginInfo Source # 
type FieldOffset "pInheritanceInfo" VkCommandBufferBeginInfo = 24
type FieldOffset "pNext" VkCommandBufferBeginInfo Source # 
type FieldOffset "sType" VkCommandBufferBeginInfo Source # 
type FieldIsArray "flags" VkCommandBufferBeginInfo Source # 
type FieldIsArray "pInheritanceInfo" VkCommandBufferBeginInfo Source # 
type FieldIsArray "pInheritanceInfo" VkCommandBufferBeginInfo = False
type FieldIsArray "pNext" VkCommandBufferBeginInfo Source # 
type FieldIsArray "sType" VkCommandBufferBeginInfo Source # 

data VkCommandBufferInheritanceInfo Source #

typedef struct VkCommandBufferInheritanceInfo {
    VkStructureType sType;
    const void*            pNext;
    VkRenderPass    renderPass;
    uint32_t               subpass;
    VkFramebuffer   framebuffer;
    VkBool32               occlusionQueryEnable;
    VkQueryControlFlags    queryFlags;
    VkQueryPipelineStatisticFlags pipelineStatistics;
} VkCommandBufferInheritanceInfo;

VkCommandBufferInheritanceInfo registry at www.khronos.org

Instances

Eq VkCommandBufferInheritanceInfo Source # 
Ord VkCommandBufferInheritanceInfo Source # 
Show VkCommandBufferInheritanceInfo Source # 
Storable VkCommandBufferInheritanceInfo Source # 
VulkanMarshalPrim VkCommandBufferInheritanceInfo Source # 
VulkanMarshal VkCommandBufferInheritanceInfo Source # 
CanWriteField "framebuffer" VkCommandBufferInheritanceInfo Source # 
CanWriteField "occlusionQueryEnable" VkCommandBufferInheritanceInfo Source # 
CanWriteField "pNext" VkCommandBufferInheritanceInfo Source # 
CanWriteField "pipelineStatistics" VkCommandBufferInheritanceInfo Source # 
CanWriteField "queryFlags" VkCommandBufferInheritanceInfo Source # 
CanWriteField "renderPass" VkCommandBufferInheritanceInfo Source # 
CanWriteField "sType" VkCommandBufferInheritanceInfo Source # 
CanWriteField "subpass" VkCommandBufferInheritanceInfo Source # 
CanReadField "framebuffer" VkCommandBufferInheritanceInfo Source # 
CanReadField "occlusionQueryEnable" VkCommandBufferInheritanceInfo Source # 
CanReadField "pNext" VkCommandBufferInheritanceInfo Source # 
CanReadField "pipelineStatistics" VkCommandBufferInheritanceInfo Source # 
CanReadField "queryFlags" VkCommandBufferInheritanceInfo Source # 
CanReadField "renderPass" VkCommandBufferInheritanceInfo Source # 
CanReadField "sType" VkCommandBufferInheritanceInfo Source # 
CanReadField "subpass" VkCommandBufferInheritanceInfo Source # 
HasField "framebuffer" VkCommandBufferInheritanceInfo Source # 
HasField "occlusionQueryEnable" VkCommandBufferInheritanceInfo Source # 

Associated Types

type FieldType ("occlusionQueryEnable" :: Symbol) VkCommandBufferInheritanceInfo :: Type Source #

type FieldOptional ("occlusionQueryEnable" :: Symbol) VkCommandBufferInheritanceInfo :: Bool Source #

type FieldOffset ("occlusionQueryEnable" :: Symbol) VkCommandBufferInheritanceInfo :: Nat Source #

type FieldIsArray ("occlusionQueryEnable" :: Symbol) VkCommandBufferInheritanceInfo :: Bool Source #

HasField "pNext" VkCommandBufferInheritanceInfo Source # 
HasField "pipelineStatistics" VkCommandBufferInheritanceInfo Source # 

Associated Types

type FieldType ("pipelineStatistics" :: Symbol) VkCommandBufferInheritanceInfo :: Type Source #

type FieldOptional ("pipelineStatistics" :: Symbol) VkCommandBufferInheritanceInfo :: Bool Source #

type FieldOffset ("pipelineStatistics" :: Symbol) VkCommandBufferInheritanceInfo :: Nat Source #

type FieldIsArray ("pipelineStatistics" :: Symbol) VkCommandBufferInheritanceInfo :: Bool Source #

HasField "queryFlags" VkCommandBufferInheritanceInfo Source # 
HasField "renderPass" VkCommandBufferInheritanceInfo Source # 
HasField "sType" VkCommandBufferInheritanceInfo Source # 
HasField "subpass" VkCommandBufferInheritanceInfo Source # 
type StructFields VkCommandBufferInheritanceInfo Source # 
type StructFields VkCommandBufferInheritanceInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "renderPass" ((:) Symbol "subpass" ((:) Symbol "framebuffer" ((:) Symbol "occlusionQueryEnable" ((:) Symbol "queryFlags" ((:) Symbol "pipelineStatistics" ([] Symbol))))))))
type CUnionType VkCommandBufferInheritanceInfo Source # 
type ReturnedOnly VkCommandBufferInheritanceInfo Source # 
type StructExtends VkCommandBufferInheritanceInfo Source # 
type FieldType "framebuffer" VkCommandBufferInheritanceInfo Source # 
type FieldType "occlusionQueryEnable" VkCommandBufferInheritanceInfo Source # 
type FieldType "occlusionQueryEnable" VkCommandBufferInheritanceInfo = VkBool32
type FieldType "pNext" VkCommandBufferInheritanceInfo Source # 
type FieldType "pipelineStatistics" VkCommandBufferInheritanceInfo Source # 
type FieldType "queryFlags" VkCommandBufferInheritanceInfo Source # 
type FieldType "renderPass" VkCommandBufferInheritanceInfo Source # 
type FieldType "sType" VkCommandBufferInheritanceInfo Source # 
type FieldType "subpass" VkCommandBufferInheritanceInfo Source # 
type FieldOptional "framebuffer" VkCommandBufferInheritanceInfo Source # 
type FieldOptional "occlusionQueryEnable" VkCommandBufferInheritanceInfo Source # 
type FieldOptional "occlusionQueryEnable" VkCommandBufferInheritanceInfo = False
type FieldOptional "pNext" VkCommandBufferInheritanceInfo Source # 
type FieldOptional "pipelineStatistics" VkCommandBufferInheritanceInfo Source # 
type FieldOptional "queryFlags" VkCommandBufferInheritanceInfo Source # 
type FieldOptional "renderPass" VkCommandBufferInheritanceInfo Source # 
type FieldOptional "sType" VkCommandBufferInheritanceInfo Source # 
type FieldOptional "subpass" VkCommandBufferInheritanceInfo Source # 
type FieldOffset "framebuffer" VkCommandBufferInheritanceInfo Source # 
type FieldOffset "occlusionQueryEnable" VkCommandBufferInheritanceInfo Source # 
type FieldOffset "occlusionQueryEnable" VkCommandBufferInheritanceInfo = 40
type FieldOffset "pNext" VkCommandBufferInheritanceInfo Source # 
type FieldOffset "pipelineStatistics" VkCommandBufferInheritanceInfo Source # 
type FieldOffset "pipelineStatistics" VkCommandBufferInheritanceInfo = 48
type FieldOffset "queryFlags" VkCommandBufferInheritanceInfo Source # 
type FieldOffset "renderPass" VkCommandBufferInheritanceInfo Source # 
type FieldOffset "sType" VkCommandBufferInheritanceInfo Source # 
type FieldOffset "subpass" VkCommandBufferInheritanceInfo Source # 
type FieldIsArray "framebuffer" VkCommandBufferInheritanceInfo Source # 
type FieldIsArray "occlusionQueryEnable" VkCommandBufferInheritanceInfo Source # 
type FieldIsArray "occlusionQueryEnable" VkCommandBufferInheritanceInfo = False
type FieldIsArray "pNext" VkCommandBufferInheritanceInfo Source # 
type FieldIsArray "pipelineStatistics" VkCommandBufferInheritanceInfo Source # 
type FieldIsArray "queryFlags" VkCommandBufferInheritanceInfo Source # 
type FieldIsArray "renderPass" VkCommandBufferInheritanceInfo Source # 
type FieldIsArray "sType" VkCommandBufferInheritanceInfo Source # 
type FieldIsArray "subpass" VkCommandBufferInheritanceInfo Source # 

data VkCommandPoolCreateInfo Source #

typedef struct VkCommandPoolCreateInfo {
    VkStructureType sType;
    const void*            pNext;
    VkCommandPoolCreateFlags   flags;
    uint32_t               queueFamilyIndex;
} VkCommandPoolCreateInfo;

VkCommandPoolCreateInfo registry at www.khronos.org

Instances

Eq VkCommandPoolCreateInfo Source # 
Ord VkCommandPoolCreateInfo Source # 
Show VkCommandPoolCreateInfo Source # 
Storable VkCommandPoolCreateInfo Source # 
VulkanMarshalPrim VkCommandPoolCreateInfo Source # 
VulkanMarshal VkCommandPoolCreateInfo Source # 
CanWriteField "flags" VkCommandPoolCreateInfo Source # 
CanWriteField "pNext" VkCommandPoolCreateInfo Source # 
CanWriteField "queueFamilyIndex" VkCommandPoolCreateInfo Source # 
CanWriteField "sType" VkCommandPoolCreateInfo Source # 
CanReadField "flags" VkCommandPoolCreateInfo Source # 
CanReadField "pNext" VkCommandPoolCreateInfo Source # 
CanReadField "queueFamilyIndex" VkCommandPoolCreateInfo Source # 
CanReadField "sType" VkCommandPoolCreateInfo Source # 
HasField "flags" VkCommandPoolCreateInfo Source # 
HasField "pNext" VkCommandPoolCreateInfo Source # 
HasField "queueFamilyIndex" VkCommandPoolCreateInfo Source # 

Associated Types

type FieldType ("queueFamilyIndex" :: Symbol) VkCommandPoolCreateInfo :: Type Source #

type FieldOptional ("queueFamilyIndex" :: Symbol) VkCommandPoolCreateInfo :: Bool Source #

type FieldOffset ("queueFamilyIndex" :: Symbol) VkCommandPoolCreateInfo :: Nat Source #

type FieldIsArray ("queueFamilyIndex" :: Symbol) VkCommandPoolCreateInfo :: Bool Source #

HasField "sType" VkCommandPoolCreateInfo Source # 
type StructFields VkCommandPoolCreateInfo Source # 
type StructFields VkCommandPoolCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "queueFamilyIndex" ([] Symbol))))
type CUnionType VkCommandPoolCreateInfo Source # 
type ReturnedOnly VkCommandPoolCreateInfo Source # 
type StructExtends VkCommandPoolCreateInfo Source # 
type FieldType "flags" VkCommandPoolCreateInfo Source # 
type FieldType "pNext" VkCommandPoolCreateInfo Source # 
type FieldType "queueFamilyIndex" VkCommandPoolCreateInfo Source # 
type FieldType "queueFamilyIndex" VkCommandPoolCreateInfo = Word32
type FieldType "sType" VkCommandPoolCreateInfo Source # 
type FieldOptional "flags" VkCommandPoolCreateInfo Source # 
type FieldOptional "pNext" VkCommandPoolCreateInfo Source # 
type FieldOptional "queueFamilyIndex" VkCommandPoolCreateInfo Source # 
type FieldOptional "queueFamilyIndex" VkCommandPoolCreateInfo = False
type FieldOptional "sType" VkCommandPoolCreateInfo Source # 
type FieldOffset "flags" VkCommandPoolCreateInfo Source # 
type FieldOffset "pNext" VkCommandPoolCreateInfo Source # 
type FieldOffset "queueFamilyIndex" VkCommandPoolCreateInfo Source # 
type FieldOffset "queueFamilyIndex" VkCommandPoolCreateInfo = 20
type FieldOffset "sType" VkCommandPoolCreateInfo Source # 
type FieldIsArray "flags" VkCommandPoolCreateInfo Source # 
type FieldIsArray "pNext" VkCommandPoolCreateInfo Source # 
type FieldIsArray "queueFamilyIndex" VkCommandPoolCreateInfo Source # 
type FieldIsArray "queueFamilyIndex" VkCommandPoolCreateInfo = False
type FieldIsArray "sType" VkCommandPoolCreateInfo Source # 

newtype VkCommandBufferLevel Source #

Instances

Bounded VkCommandBufferLevel Source # 
Enum VkCommandBufferLevel Source # 
Eq VkCommandBufferLevel Source # 
Data VkCommandBufferLevel Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkCommandBufferLevel -> c VkCommandBufferLevel #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkCommandBufferLevel #

toConstr :: VkCommandBufferLevel -> Constr #

dataTypeOf :: VkCommandBufferLevel -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkCommandBufferLevel) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkCommandBufferLevel) #

gmapT :: (forall b. Data b => b -> b) -> VkCommandBufferLevel -> VkCommandBufferLevel #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkCommandBufferLevel -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkCommandBufferLevel -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkCommandBufferLevel -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkCommandBufferLevel -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkCommandBufferLevel -> m VkCommandBufferLevel #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkCommandBufferLevel -> m VkCommandBufferLevel #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkCommandBufferLevel -> m VkCommandBufferLevel #

Num VkCommandBufferLevel Source # 
Ord VkCommandBufferLevel Source # 
Read VkCommandBufferLevel Source # 
Show VkCommandBufferLevel Source # 
Generic VkCommandBufferLevel Source # 
Storable VkCommandBufferLevel Source # 
type Rep VkCommandBufferLevel Source # 
type Rep VkCommandBufferLevel = D1 (MetaData "VkCommandBufferLevel" "Graphics.Vulkan.Types.Enum.Command" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkCommandBufferLevel" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

newtype VkCommandBufferResetBitmask a Source #

Instances

Bounded (VkCommandBufferResetBitmask FlagMask) Source # 
Enum (VkCommandBufferResetBitmask FlagMask) Source # 
Eq (VkCommandBufferResetBitmask a) Source # 
Integral (VkCommandBufferResetBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkCommandBufferResetBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkCommandBufferResetBitmask a -> c (VkCommandBufferResetBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkCommandBufferResetBitmask a) #

toConstr :: VkCommandBufferResetBitmask a -> Constr #

dataTypeOf :: VkCommandBufferResetBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkCommandBufferResetBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkCommandBufferResetBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkCommandBufferResetBitmask a -> VkCommandBufferResetBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkCommandBufferResetBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkCommandBufferResetBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkCommandBufferResetBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkCommandBufferResetBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkCommandBufferResetBitmask a -> m (VkCommandBufferResetBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkCommandBufferResetBitmask a -> m (VkCommandBufferResetBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkCommandBufferResetBitmask a -> m (VkCommandBufferResetBitmask a) #

Num (VkCommandBufferResetBitmask FlagMask) Source # 
Ord (VkCommandBufferResetBitmask a) Source # 
Read (VkCommandBufferResetBitmask a) Source # 
Real (VkCommandBufferResetBitmask FlagMask) Source # 
Show (VkCommandBufferResetBitmask a) Source # 
Generic (VkCommandBufferResetBitmask a) Source # 
Storable (VkCommandBufferResetBitmask a) Source # 
Bits (VkCommandBufferResetBitmask FlagMask) Source # 

Methods

(.&.) :: VkCommandBufferResetBitmask FlagMask -> VkCommandBufferResetBitmask FlagMask -> VkCommandBufferResetBitmask FlagMask #

(.|.) :: VkCommandBufferResetBitmask FlagMask -> VkCommandBufferResetBitmask FlagMask -> VkCommandBufferResetBitmask FlagMask #

xor :: VkCommandBufferResetBitmask FlagMask -> VkCommandBufferResetBitmask FlagMask -> VkCommandBufferResetBitmask FlagMask #

complement :: VkCommandBufferResetBitmask FlagMask -> VkCommandBufferResetBitmask FlagMask #

shift :: VkCommandBufferResetBitmask FlagMask -> Int -> VkCommandBufferResetBitmask FlagMask #

rotate :: VkCommandBufferResetBitmask FlagMask -> Int -> VkCommandBufferResetBitmask FlagMask #

zeroBits :: VkCommandBufferResetBitmask FlagMask #

bit :: Int -> VkCommandBufferResetBitmask FlagMask #

setBit :: VkCommandBufferResetBitmask FlagMask -> Int -> VkCommandBufferResetBitmask FlagMask #

clearBit :: VkCommandBufferResetBitmask FlagMask -> Int -> VkCommandBufferResetBitmask FlagMask #

complementBit :: VkCommandBufferResetBitmask FlagMask -> Int -> VkCommandBufferResetBitmask FlagMask #

testBit :: VkCommandBufferResetBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkCommandBufferResetBitmask FlagMask -> Maybe Int #

bitSize :: VkCommandBufferResetBitmask FlagMask -> Int #

isSigned :: VkCommandBufferResetBitmask FlagMask -> Bool #

shiftL :: VkCommandBufferResetBitmask FlagMask -> Int -> VkCommandBufferResetBitmask FlagMask #

unsafeShiftL :: VkCommandBufferResetBitmask FlagMask -> Int -> VkCommandBufferResetBitmask FlagMask #

shiftR :: VkCommandBufferResetBitmask FlagMask -> Int -> VkCommandBufferResetBitmask FlagMask #

unsafeShiftR :: VkCommandBufferResetBitmask FlagMask -> Int -> VkCommandBufferResetBitmask FlagMask #

rotateL :: VkCommandBufferResetBitmask FlagMask -> Int -> VkCommandBufferResetBitmask FlagMask #

rotateR :: VkCommandBufferResetBitmask FlagMask -> Int -> VkCommandBufferResetBitmask FlagMask #

popCount :: VkCommandBufferResetBitmask FlagMask -> Int #

FiniteBits (VkCommandBufferResetBitmask FlagMask) Source # 
type Rep (VkCommandBufferResetBitmask a) Source # 
type Rep (VkCommandBufferResetBitmask a) = D1 (MetaData "VkCommandBufferResetBitmask" "Graphics.Vulkan.Types.Enum.Command" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkCommandBufferResetBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

pattern VK_COMMAND_BUFFER_RESET_RELEASE_RESOURCES_BIT :: forall a. VkCommandBufferResetBitmask a Source #

Release resources owned by the buffer

bitpos = 0

newtype VkCommandBufferUsageBitmask a Source #

Instances

Bounded (VkCommandBufferUsageBitmask FlagMask) Source # 
Enum (VkCommandBufferUsageBitmask FlagMask) Source # 
Eq (VkCommandBufferUsageBitmask a) Source # 
Integral (VkCommandBufferUsageBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkCommandBufferUsageBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkCommandBufferUsageBitmask a -> c (VkCommandBufferUsageBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkCommandBufferUsageBitmask a) #

toConstr :: VkCommandBufferUsageBitmask a -> Constr #

dataTypeOf :: VkCommandBufferUsageBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkCommandBufferUsageBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkCommandBufferUsageBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkCommandBufferUsageBitmask a -> VkCommandBufferUsageBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkCommandBufferUsageBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkCommandBufferUsageBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkCommandBufferUsageBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkCommandBufferUsageBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkCommandBufferUsageBitmask a -> m (VkCommandBufferUsageBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkCommandBufferUsageBitmask a -> m (VkCommandBufferUsageBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkCommandBufferUsageBitmask a -> m (VkCommandBufferUsageBitmask a) #

Num (VkCommandBufferUsageBitmask FlagMask) Source # 
Ord (VkCommandBufferUsageBitmask a) Source # 
Read (VkCommandBufferUsageBitmask a) Source # 
Real (VkCommandBufferUsageBitmask FlagMask) Source # 
Show (VkCommandBufferUsageBitmask a) Source # 
Generic (VkCommandBufferUsageBitmask a) Source # 
Storable (VkCommandBufferUsageBitmask a) Source # 
Bits (VkCommandBufferUsageBitmask FlagMask) Source # 

Methods

(.&.) :: VkCommandBufferUsageBitmask FlagMask -> VkCommandBufferUsageBitmask FlagMask -> VkCommandBufferUsageBitmask FlagMask #

(.|.) :: VkCommandBufferUsageBitmask FlagMask -> VkCommandBufferUsageBitmask FlagMask -> VkCommandBufferUsageBitmask FlagMask #

xor :: VkCommandBufferUsageBitmask FlagMask -> VkCommandBufferUsageBitmask FlagMask -> VkCommandBufferUsageBitmask FlagMask #

complement :: VkCommandBufferUsageBitmask FlagMask -> VkCommandBufferUsageBitmask FlagMask #

shift :: VkCommandBufferUsageBitmask FlagMask -> Int -> VkCommandBufferUsageBitmask FlagMask #

rotate :: VkCommandBufferUsageBitmask FlagMask -> Int -> VkCommandBufferUsageBitmask FlagMask #

zeroBits :: VkCommandBufferUsageBitmask FlagMask #

bit :: Int -> VkCommandBufferUsageBitmask FlagMask #

setBit :: VkCommandBufferUsageBitmask FlagMask -> Int -> VkCommandBufferUsageBitmask FlagMask #

clearBit :: VkCommandBufferUsageBitmask FlagMask -> Int -> VkCommandBufferUsageBitmask FlagMask #

complementBit :: VkCommandBufferUsageBitmask FlagMask -> Int -> VkCommandBufferUsageBitmask FlagMask #

testBit :: VkCommandBufferUsageBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkCommandBufferUsageBitmask FlagMask -> Maybe Int #

bitSize :: VkCommandBufferUsageBitmask FlagMask -> Int #

isSigned :: VkCommandBufferUsageBitmask FlagMask -> Bool #

shiftL :: VkCommandBufferUsageBitmask FlagMask -> Int -> VkCommandBufferUsageBitmask FlagMask #

unsafeShiftL :: VkCommandBufferUsageBitmask FlagMask -> Int -> VkCommandBufferUsageBitmask FlagMask #

shiftR :: VkCommandBufferUsageBitmask FlagMask -> Int -> VkCommandBufferUsageBitmask FlagMask #

unsafeShiftR :: VkCommandBufferUsageBitmask FlagMask -> Int -> VkCommandBufferUsageBitmask FlagMask #

rotateL :: VkCommandBufferUsageBitmask FlagMask -> Int -> VkCommandBufferUsageBitmask FlagMask #

rotateR :: VkCommandBufferUsageBitmask FlagMask -> Int -> VkCommandBufferUsageBitmask FlagMask #

popCount :: VkCommandBufferUsageBitmask FlagMask -> Int #

FiniteBits (VkCommandBufferUsageBitmask FlagMask) Source # 
type Rep (VkCommandBufferUsageBitmask a) Source # 
type Rep (VkCommandBufferUsageBitmask a) = D1 (MetaData "VkCommandBufferUsageBitmask" "Graphics.Vulkan.Types.Enum.Command" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkCommandBufferUsageBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

pattern VK_COMMAND_BUFFER_USAGE_SIMULTANEOUS_USE_BIT :: forall a. VkCommandBufferUsageBitmask a Source #

Command buffer may be submitted/executed more than once simultaneously

bitpos = 2

newtype VkCommandPoolCreateBitmask a Source #

Instances

Bounded (VkCommandPoolCreateBitmask FlagMask) Source # 
Enum (VkCommandPoolCreateBitmask FlagMask) Source # 
Eq (VkCommandPoolCreateBitmask a) Source # 
Integral (VkCommandPoolCreateBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkCommandPoolCreateBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkCommandPoolCreateBitmask a -> c (VkCommandPoolCreateBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkCommandPoolCreateBitmask a) #

toConstr :: VkCommandPoolCreateBitmask a -> Constr #

dataTypeOf :: VkCommandPoolCreateBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkCommandPoolCreateBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkCommandPoolCreateBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkCommandPoolCreateBitmask a -> VkCommandPoolCreateBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkCommandPoolCreateBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkCommandPoolCreateBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkCommandPoolCreateBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkCommandPoolCreateBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkCommandPoolCreateBitmask a -> m (VkCommandPoolCreateBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkCommandPoolCreateBitmask a -> m (VkCommandPoolCreateBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkCommandPoolCreateBitmask a -> m (VkCommandPoolCreateBitmask a) #

Num (VkCommandPoolCreateBitmask FlagMask) Source # 
Ord (VkCommandPoolCreateBitmask a) Source # 
Read (VkCommandPoolCreateBitmask a) Source # 
Real (VkCommandPoolCreateBitmask FlagMask) Source # 
Show (VkCommandPoolCreateBitmask a) Source # 
Generic (VkCommandPoolCreateBitmask a) Source # 
Storable (VkCommandPoolCreateBitmask a) Source # 
Bits (VkCommandPoolCreateBitmask FlagMask) Source # 

Methods

(.&.) :: VkCommandPoolCreateBitmask FlagMask -> VkCommandPoolCreateBitmask FlagMask -> VkCommandPoolCreateBitmask FlagMask #

(.|.) :: VkCommandPoolCreateBitmask FlagMask -> VkCommandPoolCreateBitmask FlagMask -> VkCommandPoolCreateBitmask FlagMask #

xor :: VkCommandPoolCreateBitmask FlagMask -> VkCommandPoolCreateBitmask FlagMask -> VkCommandPoolCreateBitmask FlagMask #

complement :: VkCommandPoolCreateBitmask FlagMask -> VkCommandPoolCreateBitmask FlagMask #

shift :: VkCommandPoolCreateBitmask FlagMask -> Int -> VkCommandPoolCreateBitmask FlagMask #

rotate :: VkCommandPoolCreateBitmask FlagMask -> Int -> VkCommandPoolCreateBitmask FlagMask #

zeroBits :: VkCommandPoolCreateBitmask FlagMask #

bit :: Int -> VkCommandPoolCreateBitmask FlagMask #

setBit :: VkCommandPoolCreateBitmask FlagMask -> Int -> VkCommandPoolCreateBitmask FlagMask #

clearBit :: VkCommandPoolCreateBitmask FlagMask -> Int -> VkCommandPoolCreateBitmask FlagMask #

complementBit :: VkCommandPoolCreateBitmask FlagMask -> Int -> VkCommandPoolCreateBitmask FlagMask #

testBit :: VkCommandPoolCreateBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkCommandPoolCreateBitmask FlagMask -> Maybe Int #

bitSize :: VkCommandPoolCreateBitmask FlagMask -> Int #

isSigned :: VkCommandPoolCreateBitmask FlagMask -> Bool #

shiftL :: VkCommandPoolCreateBitmask FlagMask -> Int -> VkCommandPoolCreateBitmask FlagMask #

unsafeShiftL :: VkCommandPoolCreateBitmask FlagMask -> Int -> VkCommandPoolCreateBitmask FlagMask #

shiftR :: VkCommandPoolCreateBitmask FlagMask -> Int -> VkCommandPoolCreateBitmask FlagMask #

unsafeShiftR :: VkCommandPoolCreateBitmask FlagMask -> Int -> VkCommandPoolCreateBitmask FlagMask #

rotateL :: VkCommandPoolCreateBitmask FlagMask -> Int -> VkCommandPoolCreateBitmask FlagMask #

rotateR :: VkCommandPoolCreateBitmask FlagMask -> Int -> VkCommandPoolCreateBitmask FlagMask #

popCount :: VkCommandPoolCreateBitmask FlagMask -> Int #

FiniteBits (VkCommandPoolCreateBitmask FlagMask) Source # 
type Rep (VkCommandPoolCreateBitmask a) Source # 
type Rep (VkCommandPoolCreateBitmask a) = D1 (MetaData "VkCommandPoolCreateBitmask" "Graphics.Vulkan.Types.Enum.Command" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkCommandPoolCreateBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

pattern VK_COMMAND_POOL_CREATE_TRANSIENT_BIT :: forall a. VkCommandPoolCreateBitmask a Source #

Command buffers have a short lifetime

bitpos = 0

pattern VK_COMMAND_POOL_CREATE_RESET_COMMAND_BUFFER_BIT :: forall a. VkCommandPoolCreateBitmask a Source #

Command buffers may release their memory individually

bitpos = 1

newtype VkCommandPoolResetBitmask a Source #

Instances

Bounded (VkCommandPoolResetBitmask FlagMask) Source # 
Enum (VkCommandPoolResetBitmask FlagMask) Source # 
Eq (VkCommandPoolResetBitmask a) Source # 
Integral (VkCommandPoolResetBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkCommandPoolResetBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkCommandPoolResetBitmask a -> c (VkCommandPoolResetBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkCommandPoolResetBitmask a) #

toConstr :: VkCommandPoolResetBitmask a -> Constr #

dataTypeOf :: VkCommandPoolResetBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkCommandPoolResetBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkCommandPoolResetBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkCommandPoolResetBitmask a -> VkCommandPoolResetBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkCommandPoolResetBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkCommandPoolResetBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkCommandPoolResetBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkCommandPoolResetBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkCommandPoolResetBitmask a -> m (VkCommandPoolResetBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkCommandPoolResetBitmask a -> m (VkCommandPoolResetBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkCommandPoolResetBitmask a -> m (VkCommandPoolResetBitmask a) #

Num (VkCommandPoolResetBitmask FlagMask) Source # 
Ord (VkCommandPoolResetBitmask a) Source # 
Read (VkCommandPoolResetBitmask a) Source # 
Real (VkCommandPoolResetBitmask FlagMask) Source # 
Show (VkCommandPoolResetBitmask a) Source # 
Generic (VkCommandPoolResetBitmask a) Source # 
Storable (VkCommandPoolResetBitmask a) Source # 
Bits (VkCommandPoolResetBitmask FlagMask) Source # 

Methods

(.&.) :: VkCommandPoolResetBitmask FlagMask -> VkCommandPoolResetBitmask FlagMask -> VkCommandPoolResetBitmask FlagMask #

(.|.) :: VkCommandPoolResetBitmask FlagMask -> VkCommandPoolResetBitmask FlagMask -> VkCommandPoolResetBitmask FlagMask #

xor :: VkCommandPoolResetBitmask FlagMask -> VkCommandPoolResetBitmask FlagMask -> VkCommandPoolResetBitmask FlagMask #

complement :: VkCommandPoolResetBitmask FlagMask -> VkCommandPoolResetBitmask FlagMask #

shift :: VkCommandPoolResetBitmask FlagMask -> Int -> VkCommandPoolResetBitmask FlagMask #

rotate :: VkCommandPoolResetBitmask FlagMask -> Int -> VkCommandPoolResetBitmask FlagMask #

zeroBits :: VkCommandPoolResetBitmask FlagMask #

bit :: Int -> VkCommandPoolResetBitmask FlagMask #

setBit :: VkCommandPoolResetBitmask FlagMask -> Int -> VkCommandPoolResetBitmask FlagMask #

clearBit :: VkCommandPoolResetBitmask FlagMask -> Int -> VkCommandPoolResetBitmask FlagMask #

complementBit :: VkCommandPoolResetBitmask FlagMask -> Int -> VkCommandPoolResetBitmask FlagMask #

testBit :: VkCommandPoolResetBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkCommandPoolResetBitmask FlagMask -> Maybe Int #

bitSize :: VkCommandPoolResetBitmask FlagMask -> Int #

isSigned :: VkCommandPoolResetBitmask FlagMask -> Bool #

shiftL :: VkCommandPoolResetBitmask FlagMask -> Int -> VkCommandPoolResetBitmask FlagMask #

unsafeShiftL :: VkCommandPoolResetBitmask FlagMask -> Int -> VkCommandPoolResetBitmask FlagMask #

shiftR :: VkCommandPoolResetBitmask FlagMask -> Int -> VkCommandPoolResetBitmask FlagMask #

unsafeShiftR :: VkCommandPoolResetBitmask FlagMask -> Int -> VkCommandPoolResetBitmask FlagMask #

rotateL :: VkCommandPoolResetBitmask FlagMask -> Int -> VkCommandPoolResetBitmask FlagMask #

rotateR :: VkCommandPoolResetBitmask FlagMask -> Int -> VkCommandPoolResetBitmask FlagMask #

popCount :: VkCommandPoolResetBitmask FlagMask -> Int #

FiniteBits (VkCommandPoolResetBitmask FlagMask) Source # 
type Rep (VkCommandPoolResetBitmask a) Source # 
type Rep (VkCommandPoolResetBitmask a) = D1 (MetaData "VkCommandPoolResetBitmask" "Graphics.Vulkan.Types.Enum.Command" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkCommandPoolResetBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

pattern VK_COMMAND_POOL_RESET_RELEASE_RESOURCES_BIT :: forall a. VkCommandPoolResetBitmask a Source #

Release resources owned by the pool

bitpos = 0

data VkExtent2D Source #

typedef struct VkExtent2D {
    uint32_t        width;
    uint32_t        height;
} VkExtent2D;

VkExtent2D registry at www.khronos.org

Instances

Eq VkExtent2D Source # 
Ord VkExtent2D Source # 
Show VkExtent2D Source # 
Storable VkExtent2D Source # 
VulkanMarshalPrim VkExtent2D Source # 
VulkanMarshal VkExtent2D Source # 
CanWriteField "height" VkExtent2D Source # 

Methods

writeField :: Ptr VkExtent2D -> FieldType "height" VkExtent2D -> IO () Source #

CanWriteField "width" VkExtent2D Source # 

Methods

writeField :: Ptr VkExtent2D -> FieldType "width" VkExtent2D -> IO () Source #

CanReadField "height" VkExtent2D Source # 
CanReadField "width" VkExtent2D Source # 
HasField "height" VkExtent2D Source # 

Associated Types

type FieldType ("height" :: Symbol) VkExtent2D :: Type Source #

type FieldOptional ("height" :: Symbol) VkExtent2D :: Bool Source #

type FieldOffset ("height" :: Symbol) VkExtent2D :: Nat Source #

type FieldIsArray ("height" :: Symbol) VkExtent2D :: Bool Source #

HasField "width" VkExtent2D Source # 

Associated Types

type FieldType ("width" :: Symbol) VkExtent2D :: Type Source #

type FieldOptional ("width" :: Symbol) VkExtent2D :: Bool Source #

type FieldOffset ("width" :: Symbol) VkExtent2D :: Nat Source #

type FieldIsArray ("width" :: Symbol) VkExtent2D :: Bool Source #

type StructFields VkExtent2D Source # 
type StructFields VkExtent2D = (:) Symbol "width" ((:) Symbol "height" ([] Symbol))
type CUnionType VkExtent2D Source # 
type ReturnedOnly VkExtent2D Source # 
type StructExtends VkExtent2D Source # 
type FieldType "height" VkExtent2D Source # 
type FieldType "height" VkExtent2D = Word32
type FieldType "width" VkExtent2D Source # 
type FieldType "width" VkExtent2D = Word32
type FieldOptional "height" VkExtent2D Source # 
type FieldOptional "width" VkExtent2D Source # 
type FieldOffset "height" VkExtent2D Source # 
type FieldOffset "height" VkExtent2D = 4
type FieldOffset "width" VkExtent2D Source # 
type FieldOffset "width" VkExtent2D = 0
type FieldIsArray "height" VkExtent2D Source # 
type FieldIsArray "height" VkExtent2D = False
type FieldIsArray "width" VkExtent2D Source # 

data VkExtent3D Source #

typedef struct VkExtent3D {
    uint32_t        width;
    uint32_t        height;
    uint32_t        depth;
} VkExtent3D;

VkExtent3D registry at www.khronos.org

Instances

Eq VkExtent3D Source # 
Ord VkExtent3D Source # 
Show VkExtent3D Source # 
Storable VkExtent3D Source # 
VulkanMarshalPrim VkExtent3D Source # 
VulkanMarshal VkExtent3D Source # 
CanWriteField "depth" VkExtent3D Source # 

Methods

writeField :: Ptr VkExtent3D -> FieldType "depth" VkExtent3D -> IO () Source #

CanWriteField "height" VkExtent3D Source # 

Methods

writeField :: Ptr VkExtent3D -> FieldType "height" VkExtent3D -> IO () Source #

CanWriteField "width" VkExtent3D Source # 

Methods

writeField :: Ptr VkExtent3D -> FieldType "width" VkExtent3D -> IO () Source #

CanReadField "depth" VkExtent3D Source # 
CanReadField "height" VkExtent3D Source # 
CanReadField "width" VkExtent3D Source # 
HasField "depth" VkExtent3D Source # 

Associated Types

type FieldType ("depth" :: Symbol) VkExtent3D :: Type Source #

type FieldOptional ("depth" :: Symbol) VkExtent3D :: Bool Source #

type FieldOffset ("depth" :: Symbol) VkExtent3D :: Nat Source #

type FieldIsArray ("depth" :: Symbol) VkExtent3D :: Bool Source #

HasField "height" VkExtent3D Source # 

Associated Types

type FieldType ("height" :: Symbol) VkExtent3D :: Type Source #

type FieldOptional ("height" :: Symbol) VkExtent3D :: Bool Source #

type FieldOffset ("height" :: Symbol) VkExtent3D :: Nat Source #

type FieldIsArray ("height" :: Symbol) VkExtent3D :: Bool Source #

HasField "width" VkExtent3D Source # 

Associated Types

type FieldType ("width" :: Symbol) VkExtent3D :: Type Source #

type FieldOptional ("width" :: Symbol) VkExtent3D :: Bool Source #

type FieldOffset ("width" :: Symbol) VkExtent3D :: Nat Source #

type FieldIsArray ("width" :: Symbol) VkExtent3D :: Bool Source #

type StructFields VkExtent3D Source # 
type StructFields VkExtent3D = (:) Symbol "width" ((:) Symbol "height" ((:) Symbol "depth" ([] Symbol)))
type CUnionType VkExtent3D Source # 
type ReturnedOnly VkExtent3D Source # 
type StructExtends VkExtent3D Source # 
type FieldType "depth" VkExtent3D Source # 
type FieldType "depth" VkExtent3D = Word32
type FieldType "height" VkExtent3D Source # 
type FieldType "height" VkExtent3D = Word32
type FieldType "width" VkExtent3D Source # 
type FieldType "width" VkExtent3D = Word32
type FieldOptional "depth" VkExtent3D Source # 
type FieldOptional "height" VkExtent3D Source # 
type FieldOptional "width" VkExtent3D Source # 
type FieldOffset "depth" VkExtent3D Source # 
type FieldOffset "depth" VkExtent3D = 8
type FieldOffset "height" VkExtent3D Source # 
type FieldOffset "height" VkExtent3D = 4
type FieldOffset "width" VkExtent3D Source # 
type FieldOffset "width" VkExtent3D = 0
type FieldIsArray "depth" VkExtent3D Source # 
type FieldIsArray "height" VkExtent3D Source # 
type FieldIsArray "height" VkExtent3D = False
type FieldIsArray "width" VkExtent3D Source # 

newtype VkImageAspectBitmask a Source #

Instances

Bounded (VkImageAspectBitmask FlagMask) Source # 
Enum (VkImageAspectBitmask FlagMask) Source # 
Eq (VkImageAspectBitmask a) Source # 
Integral (VkImageAspectBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkImageAspectBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkImageAspectBitmask a -> c (VkImageAspectBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkImageAspectBitmask a) #

toConstr :: VkImageAspectBitmask a -> Constr #

dataTypeOf :: VkImageAspectBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkImageAspectBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkImageAspectBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkImageAspectBitmask a -> VkImageAspectBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkImageAspectBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkImageAspectBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkImageAspectBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkImageAspectBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkImageAspectBitmask a -> m (VkImageAspectBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkImageAspectBitmask a -> m (VkImageAspectBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkImageAspectBitmask a -> m (VkImageAspectBitmask a) #

Num (VkImageAspectBitmask FlagMask) Source # 
Ord (VkImageAspectBitmask a) Source # 
Read (VkImageAspectBitmask a) Source # 
Real (VkImageAspectBitmask FlagMask) Source # 
Show (VkImageAspectBitmask a) Source # 
Generic (VkImageAspectBitmask a) Source # 
Storable (VkImageAspectBitmask a) Source # 
Bits (VkImageAspectBitmask FlagMask) Source # 

Methods

(.&.) :: VkImageAspectBitmask FlagMask -> VkImageAspectBitmask FlagMask -> VkImageAspectBitmask FlagMask #

(.|.) :: VkImageAspectBitmask FlagMask -> VkImageAspectBitmask FlagMask -> VkImageAspectBitmask FlagMask #

xor :: VkImageAspectBitmask FlagMask -> VkImageAspectBitmask FlagMask -> VkImageAspectBitmask FlagMask #

complement :: VkImageAspectBitmask FlagMask -> VkImageAspectBitmask FlagMask #

shift :: VkImageAspectBitmask FlagMask -> Int -> VkImageAspectBitmask FlagMask #

rotate :: VkImageAspectBitmask FlagMask -> Int -> VkImageAspectBitmask FlagMask #

zeroBits :: VkImageAspectBitmask FlagMask #

bit :: Int -> VkImageAspectBitmask FlagMask #

setBit :: VkImageAspectBitmask FlagMask -> Int -> VkImageAspectBitmask FlagMask #

clearBit :: VkImageAspectBitmask FlagMask -> Int -> VkImageAspectBitmask FlagMask #

complementBit :: VkImageAspectBitmask FlagMask -> Int -> VkImageAspectBitmask FlagMask #

testBit :: VkImageAspectBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkImageAspectBitmask FlagMask -> Maybe Int #

bitSize :: VkImageAspectBitmask FlagMask -> Int #

isSigned :: VkImageAspectBitmask FlagMask -> Bool #

shiftL :: VkImageAspectBitmask FlagMask -> Int -> VkImageAspectBitmask FlagMask #

unsafeShiftL :: VkImageAspectBitmask FlagMask -> Int -> VkImageAspectBitmask FlagMask #

shiftR :: VkImageAspectBitmask FlagMask -> Int -> VkImageAspectBitmask FlagMask #

unsafeShiftR :: VkImageAspectBitmask FlagMask -> Int -> VkImageAspectBitmask FlagMask #

rotateL :: VkImageAspectBitmask FlagMask -> Int -> VkImageAspectBitmask FlagMask #

rotateR :: VkImageAspectBitmask FlagMask -> Int -> VkImageAspectBitmask FlagMask #

popCount :: VkImageAspectBitmask FlagMask -> Int #

FiniteBits (VkImageAspectBitmask FlagMask) Source # 
type Rep (VkImageAspectBitmask a) Source # 
type Rep (VkImageAspectBitmask a) = D1 (MetaData "VkImageAspectBitmask" "Graphics.Vulkan.Types.Enum.Image" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkImageAspectBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

pattern VK_IMAGE_ASPECT_COLOR_BIT :: forall a. VkImageAspectBitmask a Source #

bitpos = 0

pattern VK_IMAGE_ASPECT_DEPTH_BIT :: forall a. VkImageAspectBitmask a Source #

bitpos = 1

pattern VK_IMAGE_ASPECT_STENCIL_BIT :: forall a. VkImageAspectBitmask a Source #

bitpos = 2

newtype VkImageCreateBitmask a Source #

Instances

Bounded (VkImageCreateBitmask FlagMask) Source # 
Enum (VkImageCreateBitmask FlagMask) Source # 
Eq (VkImageCreateBitmask a) Source # 
Integral (VkImageCreateBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkImageCreateBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkImageCreateBitmask a -> c (VkImageCreateBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkImageCreateBitmask a) #

toConstr :: VkImageCreateBitmask a -> Constr #

dataTypeOf :: VkImageCreateBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkImageCreateBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkImageCreateBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkImageCreateBitmask a -> VkImageCreateBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkImageCreateBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkImageCreateBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkImageCreateBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkImageCreateBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkImageCreateBitmask a -> m (VkImageCreateBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkImageCreateBitmask a -> m (VkImageCreateBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkImageCreateBitmask a -> m (VkImageCreateBitmask a) #

Num (VkImageCreateBitmask FlagMask) Source # 
Ord (VkImageCreateBitmask a) Source # 
Read (VkImageCreateBitmask a) Source # 
Real (VkImageCreateBitmask FlagMask) Source # 
Show (VkImageCreateBitmask a) Source # 
Generic (VkImageCreateBitmask a) Source # 
Storable (VkImageCreateBitmask a) Source # 
Bits (VkImageCreateBitmask FlagMask) Source # 

Methods

(.&.) :: VkImageCreateBitmask FlagMask -> VkImageCreateBitmask FlagMask -> VkImageCreateBitmask FlagMask #

(.|.) :: VkImageCreateBitmask FlagMask -> VkImageCreateBitmask FlagMask -> VkImageCreateBitmask FlagMask #

xor :: VkImageCreateBitmask FlagMask -> VkImageCreateBitmask FlagMask -> VkImageCreateBitmask FlagMask #

complement :: VkImageCreateBitmask FlagMask -> VkImageCreateBitmask FlagMask #

shift :: VkImageCreateBitmask FlagMask -> Int -> VkImageCreateBitmask FlagMask #

rotate :: VkImageCreateBitmask FlagMask -> Int -> VkImageCreateBitmask FlagMask #

zeroBits :: VkImageCreateBitmask FlagMask #

bit :: Int -> VkImageCreateBitmask FlagMask #

setBit :: VkImageCreateBitmask FlagMask -> Int -> VkImageCreateBitmask FlagMask #

clearBit :: VkImageCreateBitmask FlagMask -> Int -> VkImageCreateBitmask FlagMask #

complementBit :: VkImageCreateBitmask FlagMask -> Int -> VkImageCreateBitmask FlagMask #

testBit :: VkImageCreateBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkImageCreateBitmask FlagMask -> Maybe Int #

bitSize :: VkImageCreateBitmask FlagMask -> Int #

isSigned :: VkImageCreateBitmask FlagMask -> Bool #

shiftL :: VkImageCreateBitmask FlagMask -> Int -> VkImageCreateBitmask FlagMask #

unsafeShiftL :: VkImageCreateBitmask FlagMask -> Int -> VkImageCreateBitmask FlagMask #

shiftR :: VkImageCreateBitmask FlagMask -> Int -> VkImageCreateBitmask FlagMask #

unsafeShiftR :: VkImageCreateBitmask FlagMask -> Int -> VkImageCreateBitmask FlagMask #

rotateL :: VkImageCreateBitmask FlagMask -> Int -> VkImageCreateBitmask FlagMask #

rotateR :: VkImageCreateBitmask FlagMask -> Int -> VkImageCreateBitmask FlagMask #

popCount :: VkImageCreateBitmask FlagMask -> Int #

FiniteBits (VkImageCreateBitmask FlagMask) Source # 
type Rep (VkImageCreateBitmask a) Source # 
type Rep (VkImageCreateBitmask a) = D1 (MetaData "VkImageCreateBitmask" "Graphics.Vulkan.Types.Enum.Image" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkImageCreateBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

pattern VK_IMAGE_CREATE_SPARSE_BINDING_BIT :: forall a. VkImageCreateBitmask a Source #

Image should support sparse backing

bitpos = 0

pattern VK_IMAGE_CREATE_SPARSE_RESIDENCY_BIT :: forall a. VkImageCreateBitmask a Source #

Image should support sparse backing with partial residency

bitpos = 1

pattern VK_IMAGE_CREATE_SPARSE_ALIASED_BIT :: forall a. VkImageCreateBitmask a Source #

Image should support constent data access to physical memory ranges mapped into multiple locations of sparse images

bitpos = 2

pattern VK_IMAGE_CREATE_MUTABLE_FORMAT_BIT :: forall a. VkImageCreateBitmask a Source #

Allows image views to have different format than the base image

bitpos = 3

pattern VK_IMAGE_CREATE_CUBE_COMPATIBLE_BIT :: forall a. VkImageCreateBitmask a Source #

Allows creating image views with cube type from the created image

bitpos = 4

newtype VkImageLayout Source #

Constructors

VkImageLayout Int32 

Instances

Bounded VkImageLayout Source # 
Enum VkImageLayout Source # 
Eq VkImageLayout Source # 
Data VkImageLayout Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkImageLayout -> c VkImageLayout #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkImageLayout #

toConstr :: VkImageLayout -> Constr #

dataTypeOf :: VkImageLayout -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkImageLayout) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkImageLayout) #

gmapT :: (forall b. Data b => b -> b) -> VkImageLayout -> VkImageLayout #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkImageLayout -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkImageLayout -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkImageLayout -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkImageLayout -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkImageLayout -> m VkImageLayout #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkImageLayout -> m VkImageLayout #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkImageLayout -> m VkImageLayout #

Num VkImageLayout Source # 
Ord VkImageLayout Source # 
Read VkImageLayout Source # 
Show VkImageLayout Source # 
Generic VkImageLayout Source # 

Associated Types

type Rep VkImageLayout :: * -> * #

Storable VkImageLayout Source # 
type Rep VkImageLayout Source # 
type Rep VkImageLayout = D1 (MetaData "VkImageLayout" "Graphics.Vulkan.Types.Enum.Image" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkImageLayout" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

pattern VK_IMAGE_LAYOUT_UNDEFINED :: VkImageLayout Source #

Implicit layout an image is when its contents are undefined due to various reasons (e.g. right after creation)

pattern VK_IMAGE_LAYOUT_GENERAL :: VkImageLayout Source #

General layout when image can be used for any kind of access

pattern VK_IMAGE_LAYOUT_COLOR_ATTACHMENT_OPTIMAL :: VkImageLayout Source #

Optimal layout when image is only used for color attachment read/write

pattern VK_IMAGE_LAYOUT_DEPTH_STENCIL_ATTACHMENT_OPTIMAL :: VkImageLayout Source #

Optimal layout when image is only used for depthstencil attachment readwrite

pattern VK_IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL :: VkImageLayout Source #

Optimal layout when image is used for read only depth/stencil attachment and shader access

pattern VK_IMAGE_LAYOUT_SHADER_READ_ONLY_OPTIMAL :: VkImageLayout Source #

Optimal layout when image is used for read only shader access

pattern VK_IMAGE_LAYOUT_TRANSFER_SRC_OPTIMAL :: VkImageLayout Source #

Optimal layout when image is used only as source of transfer operations

pattern VK_IMAGE_LAYOUT_TRANSFER_DST_OPTIMAL :: VkImageLayout Source #

Optimal layout when image is used only as destination of transfer operations

pattern VK_IMAGE_LAYOUT_PREINITIALIZED :: VkImageLayout Source #

Initial layout used when the data is populated by the CPU

newtype VkImageTiling Source #

Constructors

VkImageTiling Int32 

Instances

Bounded VkImageTiling Source # 
Enum VkImageTiling Source # 
Eq VkImageTiling Source # 
Data VkImageTiling Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkImageTiling -> c VkImageTiling #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkImageTiling #

toConstr :: VkImageTiling -> Constr #

dataTypeOf :: VkImageTiling -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkImageTiling) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkImageTiling) #

gmapT :: (forall b. Data b => b -> b) -> VkImageTiling -> VkImageTiling #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkImageTiling -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkImageTiling -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkImageTiling -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkImageTiling -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkImageTiling -> m VkImageTiling #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkImageTiling -> m VkImageTiling #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkImageTiling -> m VkImageTiling #

Num VkImageTiling Source # 
Ord VkImageTiling Source # 
Read VkImageTiling Source # 
Show VkImageTiling Source # 
Generic VkImageTiling Source # 

Associated Types

type Rep VkImageTiling :: * -> * #

Storable VkImageTiling Source # 
type Rep VkImageTiling Source # 
type Rep VkImageTiling = D1 (MetaData "VkImageTiling" "Graphics.Vulkan.Types.Enum.Image" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkImageTiling" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

newtype VkImageType Source #

Constructors

VkImageType Int32 

Instances

Bounded VkImageType Source # 
Enum VkImageType Source # 
Eq VkImageType Source # 
Data VkImageType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkImageType -> c VkImageType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkImageType #

toConstr :: VkImageType -> Constr #

dataTypeOf :: VkImageType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkImageType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkImageType) #

gmapT :: (forall b. Data b => b -> b) -> VkImageType -> VkImageType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkImageType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkImageType -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkImageType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkImageType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkImageType -> m VkImageType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkImageType -> m VkImageType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkImageType -> m VkImageType #

Num VkImageType Source # 
Ord VkImageType Source # 
Read VkImageType Source # 
Show VkImageType Source # 
Generic VkImageType Source # 

Associated Types

type Rep VkImageType :: * -> * #

Storable VkImageType Source # 
type Rep VkImageType Source # 
type Rep VkImageType = D1 (MetaData "VkImageType" "Graphics.Vulkan.Types.Enum.Image" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkImageType" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

newtype VkImageUsageBitmask a Source #

Instances

Bounded (VkImageUsageBitmask FlagMask) Source # 
Enum (VkImageUsageBitmask FlagMask) Source # 
Eq (VkImageUsageBitmask a) Source # 
Integral (VkImageUsageBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkImageUsageBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkImageUsageBitmask a -> c (VkImageUsageBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkImageUsageBitmask a) #

toConstr :: VkImageUsageBitmask a -> Constr #

dataTypeOf :: VkImageUsageBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkImageUsageBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkImageUsageBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkImageUsageBitmask a -> VkImageUsageBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkImageUsageBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkImageUsageBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkImageUsageBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkImageUsageBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkImageUsageBitmask a -> m (VkImageUsageBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkImageUsageBitmask a -> m (VkImageUsageBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkImageUsageBitmask a -> m (VkImageUsageBitmask a) #

Num (VkImageUsageBitmask FlagMask) Source # 
Ord (VkImageUsageBitmask a) Source # 
Read (VkImageUsageBitmask a) Source # 
Real (VkImageUsageBitmask FlagMask) Source # 
Show (VkImageUsageBitmask a) Source # 
Generic (VkImageUsageBitmask a) Source # 

Associated Types

type Rep (VkImageUsageBitmask a) :: * -> * #

Storable (VkImageUsageBitmask a) Source # 
Bits (VkImageUsageBitmask FlagMask) Source # 

Methods

(.&.) :: VkImageUsageBitmask FlagMask -> VkImageUsageBitmask FlagMask -> VkImageUsageBitmask FlagMask #

(.|.) :: VkImageUsageBitmask FlagMask -> VkImageUsageBitmask FlagMask -> VkImageUsageBitmask FlagMask #

xor :: VkImageUsageBitmask FlagMask -> VkImageUsageBitmask FlagMask -> VkImageUsageBitmask FlagMask #

complement :: VkImageUsageBitmask FlagMask -> VkImageUsageBitmask FlagMask #

shift :: VkImageUsageBitmask FlagMask -> Int -> VkImageUsageBitmask FlagMask #

rotate :: VkImageUsageBitmask FlagMask -> Int -> VkImageUsageBitmask FlagMask #

zeroBits :: VkImageUsageBitmask FlagMask #

bit :: Int -> VkImageUsageBitmask FlagMask #

setBit :: VkImageUsageBitmask FlagMask -> Int -> VkImageUsageBitmask FlagMask #

clearBit :: VkImageUsageBitmask FlagMask -> Int -> VkImageUsageBitmask FlagMask #

complementBit :: VkImageUsageBitmask FlagMask -> Int -> VkImageUsageBitmask FlagMask #

testBit :: VkImageUsageBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkImageUsageBitmask FlagMask -> Maybe Int #

bitSize :: VkImageUsageBitmask FlagMask -> Int #

isSigned :: VkImageUsageBitmask FlagMask -> Bool #

shiftL :: VkImageUsageBitmask FlagMask -> Int -> VkImageUsageBitmask FlagMask #

unsafeShiftL :: VkImageUsageBitmask FlagMask -> Int -> VkImageUsageBitmask FlagMask #

shiftR :: VkImageUsageBitmask FlagMask -> Int -> VkImageUsageBitmask FlagMask #

unsafeShiftR :: VkImageUsageBitmask FlagMask -> Int -> VkImageUsageBitmask FlagMask #

rotateL :: VkImageUsageBitmask FlagMask -> Int -> VkImageUsageBitmask FlagMask #

rotateR :: VkImageUsageBitmask FlagMask -> Int -> VkImageUsageBitmask FlagMask #

popCount :: VkImageUsageBitmask FlagMask -> Int #

FiniteBits (VkImageUsageBitmask FlagMask) Source # 
type Rep (VkImageUsageBitmask a) Source # 
type Rep (VkImageUsageBitmask a) = D1 (MetaData "VkImageUsageBitmask" "Graphics.Vulkan.Types.Enum.Image" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkImageUsageBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

pattern VK_IMAGE_USAGE_TRANSFER_SRC_BIT :: forall a. VkImageUsageBitmask a Source #

Can be used as a source of transfer operations

bitpos = 0

pattern VK_IMAGE_USAGE_TRANSFER_DST_BIT :: forall a. VkImageUsageBitmask a Source #

Can be used as a destination of transfer operations

bitpos = 1

pattern VK_IMAGE_USAGE_SAMPLED_BIT :: forall a. VkImageUsageBitmask a Source #

Can be sampled from (SAMPLED_IMAGE and COMBINED_IMAGE_SAMPLER descriptor types)

bitpos = 2

pattern VK_IMAGE_USAGE_STORAGE_BIT :: forall a. VkImageUsageBitmask a Source #

Can be used as storage image (STORAGE_IMAGE descriptor type)

bitpos = 3

pattern VK_IMAGE_USAGE_COLOR_ATTACHMENT_BIT :: forall a. VkImageUsageBitmask a Source #

Can be used as framebuffer color attachment

bitpos = 4

pattern VK_IMAGE_USAGE_DEPTH_STENCIL_ATTACHMENT_BIT :: forall a. VkImageUsageBitmask a Source #

Can be used as framebuffer depth/stencil attachment

bitpos = 5

pattern VK_IMAGE_USAGE_TRANSIENT_ATTACHMENT_BIT :: forall a. VkImageUsageBitmask a Source #

Image data not needed outside of rendering

bitpos = 6

pattern VK_IMAGE_USAGE_INPUT_ATTACHMENT_BIT :: forall a. VkImageUsageBitmask a Source #

Can be used as framebuffer input attachment

bitpos = 7

newtype VkImageViewType Source #

Constructors

VkImageViewType Int32 

Instances

Bounded VkImageViewType Source # 
Enum VkImageViewType Source # 
Eq VkImageViewType Source # 
Data VkImageViewType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkImageViewType -> c VkImageViewType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkImageViewType #

toConstr :: VkImageViewType -> Constr #

dataTypeOf :: VkImageViewType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkImageViewType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkImageViewType) #

gmapT :: (forall b. Data b => b -> b) -> VkImageViewType -> VkImageViewType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkImageViewType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkImageViewType -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkImageViewType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkImageViewType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkImageViewType -> m VkImageViewType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkImageViewType -> m VkImageViewType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkImageViewType -> m VkImageViewType #

Num VkImageViewType Source # 
Ord VkImageViewType Source # 
Read VkImageViewType Source # 
Show VkImageViewType Source # 
Generic VkImageViewType Source # 
Storable VkImageViewType Source # 
type Rep VkImageViewType Source # 
type Rep VkImageViewType = D1 (MetaData "VkImageViewType" "Graphics.Vulkan.Types.Enum.Image" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkImageViewType" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

data VkImageBlit Source #

typedef struct VkImageBlit {
    VkImageSubresourceLayers srcSubresource;
    VkOffset3D             srcOffsets[2];
    VkImageSubresourceLayers dstSubresource;
    VkOffset3D             dstOffsets[2];
} VkImageBlit;

VkImageBlit registry at www.khronos.org

Instances

Eq VkImageBlit Source # 
Ord VkImageBlit Source # 
Show VkImageBlit Source # 
Storable VkImageBlit Source # 
VulkanMarshalPrim VkImageBlit Source # 
VulkanMarshal VkImageBlit Source # 
CanWriteField "dstSubresource" VkImageBlit Source # 

Methods

writeField :: Ptr VkImageBlit -> FieldType "dstSubresource" VkImageBlit -> IO () Source #

CanWriteField "srcSubresource" VkImageBlit Source # 

Methods

writeField :: Ptr VkImageBlit -> FieldType "srcSubresource" VkImageBlit -> IO () Source #

CanReadField "dstSubresource" VkImageBlit Source # 

Methods

getField :: VkImageBlit -> FieldType "dstSubresource" VkImageBlit Source #

readField :: Ptr VkImageBlit -> IO (FieldType "dstSubresource" VkImageBlit) Source #

CanReadField "srcSubresource" VkImageBlit Source # 

Methods

getField :: VkImageBlit -> FieldType "srcSubresource" VkImageBlit Source #

readField :: Ptr VkImageBlit -> IO (FieldType "srcSubresource" VkImageBlit) Source #

HasField "dstOffsets" VkImageBlit Source # 

Associated Types

type FieldType ("dstOffsets" :: Symbol) VkImageBlit :: Type Source #

type FieldOptional ("dstOffsets" :: Symbol) VkImageBlit :: Bool Source #

type FieldOffset ("dstOffsets" :: Symbol) VkImageBlit :: Nat Source #

type FieldIsArray ("dstOffsets" :: Symbol) VkImageBlit :: Bool Source #

HasField "dstSubresource" VkImageBlit Source # 

Associated Types

type FieldType ("dstSubresource" :: Symbol) VkImageBlit :: Type Source #

type FieldOptional ("dstSubresource" :: Symbol) VkImageBlit :: Bool Source #

type FieldOffset ("dstSubresource" :: Symbol) VkImageBlit :: Nat Source #

type FieldIsArray ("dstSubresource" :: Symbol) VkImageBlit :: Bool Source #

HasField "srcOffsets" VkImageBlit Source # 

Associated Types

type FieldType ("srcOffsets" :: Symbol) VkImageBlit :: Type Source #

type FieldOptional ("srcOffsets" :: Symbol) VkImageBlit :: Bool Source #

type FieldOffset ("srcOffsets" :: Symbol) VkImageBlit :: Nat Source #

type FieldIsArray ("srcOffsets" :: Symbol) VkImageBlit :: Bool Source #

HasField "srcSubresource" VkImageBlit Source # 

Associated Types

type FieldType ("srcSubresource" :: Symbol) VkImageBlit :: Type Source #

type FieldOptional ("srcSubresource" :: Symbol) VkImageBlit :: Bool Source #

type FieldOffset ("srcSubresource" :: Symbol) VkImageBlit :: Nat Source #

type FieldIsArray ("srcSubresource" :: Symbol) VkImageBlit :: Bool Source #

(KnownNat idx, IndexInBounds "dstOffsets" idx VkImageBlit) => CanWriteFieldArray "dstOffsets" idx VkImageBlit Source # 

Methods

writeFieldArray :: Ptr VkImageBlit -> FieldType "dstOffsets" VkImageBlit -> IO () Source #

(KnownNat idx, IndexInBounds "srcOffsets" idx VkImageBlit) => CanWriteFieldArray "srcOffsets" idx VkImageBlit Source # 

Methods

writeFieldArray :: Ptr VkImageBlit -> FieldType "srcOffsets" VkImageBlit -> IO () Source #

(KnownNat idx, IndexInBounds "dstOffsets" idx VkImageBlit) => CanReadFieldArray "dstOffsets" idx VkImageBlit Source # 
(KnownNat idx, IndexInBounds "srcOffsets" idx VkImageBlit) => CanReadFieldArray "srcOffsets" idx VkImageBlit Source # 
type StructFields VkImageBlit Source # 
type StructFields VkImageBlit = (:) Symbol "srcSubresource" ((:) Symbol "srcOffsets" ((:) Symbol "dstSubresource" ((:) Symbol "dstOffsets" ([] Symbol))))
type CUnionType VkImageBlit Source # 
type ReturnedOnly VkImageBlit Source # 
type StructExtends VkImageBlit Source # 
type FieldArrayLength "dstOffsets" VkImageBlit Source # 
type FieldArrayLength "dstOffsets" VkImageBlit = 2
type FieldArrayLength "srcOffsets" VkImageBlit Source # 
type FieldArrayLength "srcOffsets" VkImageBlit = 2
type FieldType "dstOffsets" VkImageBlit Source # 
type FieldType "dstOffsets" VkImageBlit = VkOffset3D
type FieldType "dstSubresource" VkImageBlit Source # 
type FieldType "srcOffsets" VkImageBlit Source # 
type FieldType "srcOffsets" VkImageBlit = VkOffset3D
type FieldType "srcSubresource" VkImageBlit Source # 
type FieldOptional "dstOffsets" VkImageBlit Source # 
type FieldOptional "dstOffsets" VkImageBlit = False
type FieldOptional "dstSubresource" VkImageBlit Source # 
type FieldOptional "dstSubresource" VkImageBlit = False
type FieldOptional "srcOffsets" VkImageBlit Source # 
type FieldOptional "srcOffsets" VkImageBlit = False
type FieldOptional "srcSubresource" VkImageBlit Source # 
type FieldOptional "srcSubresource" VkImageBlit = False
type FieldOffset "dstOffsets" VkImageBlit Source # 
type FieldOffset "dstOffsets" VkImageBlit = 56
type FieldOffset "dstSubresource" VkImageBlit Source # 
type FieldOffset "dstSubresource" VkImageBlit = 40
type FieldOffset "srcOffsets" VkImageBlit Source # 
type FieldOffset "srcOffsets" VkImageBlit = 16
type FieldOffset "srcSubresource" VkImageBlit Source # 
type FieldOffset "srcSubresource" VkImageBlit = 0
type FieldIsArray "dstOffsets" VkImageBlit Source # 
type FieldIsArray "dstOffsets" VkImageBlit = True
type FieldIsArray "dstSubresource" VkImageBlit Source # 
type FieldIsArray "dstSubresource" VkImageBlit = False
type FieldIsArray "srcOffsets" VkImageBlit Source # 
type FieldIsArray "srcOffsets" VkImageBlit = True
type FieldIsArray "srcSubresource" VkImageBlit Source # 
type FieldIsArray "srcSubresource" VkImageBlit = False

data VkImageCopy Source #

typedef struct VkImageCopy {
    VkImageSubresourceLayers srcSubresource;
    VkOffset3D             srcOffset;
    VkImageSubresourceLayers dstSubresource;
    VkOffset3D             dstOffset;
    VkExtent3D             extent;
} VkImageCopy;

VkImageCopy registry at www.khronos.org

Instances

Eq VkImageCopy Source # 
Ord VkImageCopy Source # 
Show VkImageCopy Source # 
Storable VkImageCopy Source # 
VulkanMarshalPrim VkImageCopy Source # 
VulkanMarshal VkImageCopy Source # 
CanWriteField "dstOffset" VkImageCopy Source # 

Methods

writeField :: Ptr VkImageCopy -> FieldType "dstOffset" VkImageCopy -> IO () Source #

CanWriteField "dstSubresource" VkImageCopy Source # 

Methods

writeField :: Ptr VkImageCopy -> FieldType "dstSubresource" VkImageCopy -> IO () Source #

CanWriteField "extent" VkImageCopy Source # 
CanWriteField "srcOffset" VkImageCopy Source # 

Methods

writeField :: Ptr VkImageCopy -> FieldType "srcOffset" VkImageCopy -> IO () Source #

CanWriteField "srcSubresource" VkImageCopy Source # 

Methods

writeField :: Ptr VkImageCopy -> FieldType "srcSubresource" VkImageCopy -> IO () Source #

CanReadField "dstOffset" VkImageCopy Source # 
CanReadField "dstSubresource" VkImageCopy Source # 

Methods

getField :: VkImageCopy -> FieldType "dstSubresource" VkImageCopy Source #

readField :: Ptr VkImageCopy -> IO (FieldType "dstSubresource" VkImageCopy) Source #

CanReadField "extent" VkImageCopy Source # 
CanReadField "srcOffset" VkImageCopy Source # 
CanReadField "srcSubresource" VkImageCopy Source # 

Methods

getField :: VkImageCopy -> FieldType "srcSubresource" VkImageCopy Source #

readField :: Ptr VkImageCopy -> IO (FieldType "srcSubresource" VkImageCopy) Source #

HasField "dstOffset" VkImageCopy Source # 

Associated Types

type FieldType ("dstOffset" :: Symbol) VkImageCopy :: Type Source #

type FieldOptional ("dstOffset" :: Symbol) VkImageCopy :: Bool Source #

type FieldOffset ("dstOffset" :: Symbol) VkImageCopy :: Nat Source #

type FieldIsArray ("dstOffset" :: Symbol) VkImageCopy :: Bool Source #

HasField "dstSubresource" VkImageCopy Source # 

Associated Types

type FieldType ("dstSubresource" :: Symbol) VkImageCopy :: Type Source #

type FieldOptional ("dstSubresource" :: Symbol) VkImageCopy :: Bool Source #

type FieldOffset ("dstSubresource" :: Symbol) VkImageCopy :: Nat Source #

type FieldIsArray ("dstSubresource" :: Symbol) VkImageCopy :: Bool Source #

HasField "extent" VkImageCopy Source # 

Associated Types

type FieldType ("extent" :: Symbol) VkImageCopy :: Type Source #

type FieldOptional ("extent" :: Symbol) VkImageCopy :: Bool Source #

type FieldOffset ("extent" :: Symbol) VkImageCopy :: Nat Source #

type FieldIsArray ("extent" :: Symbol) VkImageCopy :: Bool Source #

HasField "srcOffset" VkImageCopy Source # 

Associated Types

type FieldType ("srcOffset" :: Symbol) VkImageCopy :: Type Source #

type FieldOptional ("srcOffset" :: Symbol) VkImageCopy :: Bool Source #

type FieldOffset ("srcOffset" :: Symbol) VkImageCopy :: Nat Source #

type FieldIsArray ("srcOffset" :: Symbol) VkImageCopy :: Bool Source #

HasField "srcSubresource" VkImageCopy Source # 

Associated Types

type FieldType ("srcSubresource" :: Symbol) VkImageCopy :: Type Source #

type FieldOptional ("srcSubresource" :: Symbol) VkImageCopy :: Bool Source #

type FieldOffset ("srcSubresource" :: Symbol) VkImageCopy :: Nat Source #

type FieldIsArray ("srcSubresource" :: Symbol) VkImageCopy :: Bool Source #

type StructFields VkImageCopy Source # 
type StructFields VkImageCopy = (:) Symbol "srcSubresource" ((:) Symbol "srcOffset" ((:) Symbol "dstSubresource" ((:) Symbol "dstOffset" ((:) Symbol "extent" ([] Symbol)))))
type CUnionType VkImageCopy Source # 
type ReturnedOnly VkImageCopy Source # 
type StructExtends VkImageCopy Source # 
type FieldType "dstOffset" VkImageCopy Source # 
type FieldType "dstOffset" VkImageCopy = VkOffset3D
type FieldType "dstSubresource" VkImageCopy Source # 
type FieldType "extent" VkImageCopy Source # 
type FieldType "srcOffset" VkImageCopy Source # 
type FieldType "srcOffset" VkImageCopy = VkOffset3D
type FieldType "srcSubresource" VkImageCopy Source # 
type FieldOptional "dstOffset" VkImageCopy Source # 
type FieldOptional "dstOffset" VkImageCopy = False
type FieldOptional "dstSubresource" VkImageCopy Source # 
type FieldOptional "dstSubresource" VkImageCopy = False
type FieldOptional "extent" VkImageCopy Source # 
type FieldOptional "srcOffset" VkImageCopy Source # 
type FieldOptional "srcOffset" VkImageCopy = False
type FieldOptional "srcSubresource" VkImageCopy Source # 
type FieldOptional "srcSubresource" VkImageCopy = False
type FieldOffset "dstOffset" VkImageCopy Source # 
type FieldOffset "dstOffset" VkImageCopy = 44
type FieldOffset "dstSubresource" VkImageCopy Source # 
type FieldOffset "dstSubresource" VkImageCopy = 28
type FieldOffset "extent" VkImageCopy Source # 
type FieldOffset "extent" VkImageCopy = 56
type FieldOffset "srcOffset" VkImageCopy Source # 
type FieldOffset "srcOffset" VkImageCopy = 16
type FieldOffset "srcSubresource" VkImageCopy Source # 
type FieldOffset "srcSubresource" VkImageCopy = 0
type FieldIsArray "dstOffset" VkImageCopy Source # 
type FieldIsArray "dstOffset" VkImageCopy = False
type FieldIsArray "dstSubresource" VkImageCopy Source # 
type FieldIsArray "dstSubresource" VkImageCopy = False
type FieldIsArray "extent" VkImageCopy Source # 
type FieldIsArray "srcOffset" VkImageCopy Source # 
type FieldIsArray "srcOffset" VkImageCopy = False
type FieldIsArray "srcSubresource" VkImageCopy Source # 
type FieldIsArray "srcSubresource" VkImageCopy = False

data VkImageCreateInfo Source #

typedef struct VkImageCreateInfo {
    VkStructureType sType;
    const void*            pNext;
    VkImageCreateFlags     flags;
    VkImageType            imageType;
    VkFormat               format;
    VkExtent3D             extent;
    uint32_t               mipLevels;
    uint32_t               arrayLayers;
    VkSampleCountFlagBits  samples;
    VkImageTiling          tiling;
    VkImageUsageFlags      usage;
    VkSharingMode          sharingMode;
    uint32_t               queueFamilyIndexCount;
    const uint32_t*        pQueueFamilyIndices;
    VkImageLayout          initialLayout;
} VkImageCreateInfo;

VkImageCreateInfo registry at www.khronos.org

Instances

Eq VkImageCreateInfo Source # 
Ord VkImageCreateInfo Source # 
Show VkImageCreateInfo Source # 
Storable VkImageCreateInfo Source # 
VulkanMarshalPrim VkImageCreateInfo Source # 
VulkanMarshal VkImageCreateInfo Source # 
CanWriteField "arrayLayers" VkImageCreateInfo Source # 
CanWriteField "extent" VkImageCreateInfo Source # 
CanWriteField "flags" VkImageCreateInfo Source # 
CanWriteField "format" VkImageCreateInfo Source # 
CanWriteField "imageType" VkImageCreateInfo Source # 
CanWriteField "initialLayout" VkImageCreateInfo Source # 
CanWriteField "mipLevels" VkImageCreateInfo Source # 
CanWriteField "pNext" VkImageCreateInfo Source # 
CanWriteField "pQueueFamilyIndices" VkImageCreateInfo Source # 

Methods

writeField :: Ptr VkImageCreateInfo -> FieldType "pQueueFamilyIndices" VkImageCreateInfo -> IO () Source #

CanWriteField "queueFamilyIndexCount" VkImageCreateInfo Source # 

Methods

writeField :: Ptr VkImageCreateInfo -> FieldType "queueFamilyIndexCount" VkImageCreateInfo -> IO () Source #

CanWriteField "sType" VkImageCreateInfo Source # 
CanWriteField "samples" VkImageCreateInfo Source # 
CanWriteField "sharingMode" VkImageCreateInfo Source # 
CanWriteField "tiling" VkImageCreateInfo Source # 
CanWriteField "usage" VkImageCreateInfo Source # 
CanReadField "arrayLayers" VkImageCreateInfo Source # 
CanReadField "extent" VkImageCreateInfo Source # 
CanReadField "flags" VkImageCreateInfo Source # 
CanReadField "format" VkImageCreateInfo Source # 
CanReadField "imageType" VkImageCreateInfo Source # 
CanReadField "initialLayout" VkImageCreateInfo Source # 
CanReadField "mipLevels" VkImageCreateInfo Source # 
CanReadField "pNext" VkImageCreateInfo Source # 
CanReadField "pQueueFamilyIndices" VkImageCreateInfo Source # 
CanReadField "queueFamilyIndexCount" VkImageCreateInfo Source # 
CanReadField "sType" VkImageCreateInfo Source # 
CanReadField "samples" VkImageCreateInfo Source # 
CanReadField "sharingMode" VkImageCreateInfo Source # 
CanReadField "tiling" VkImageCreateInfo Source # 
CanReadField "usage" VkImageCreateInfo Source # 
HasField "arrayLayers" VkImageCreateInfo Source # 

Associated Types

type FieldType ("arrayLayers" :: Symbol) VkImageCreateInfo :: Type Source #

type FieldOptional ("arrayLayers" :: Symbol) VkImageCreateInfo :: Bool Source #

type FieldOffset ("arrayLayers" :: Symbol) VkImageCreateInfo :: Nat Source #

type FieldIsArray ("arrayLayers" :: Symbol) VkImageCreateInfo :: Bool Source #

HasField "extent" VkImageCreateInfo Source # 
HasField "flags" VkImageCreateInfo Source # 
HasField "format" VkImageCreateInfo Source # 
HasField "imageType" VkImageCreateInfo Source # 

Associated Types

type FieldType ("imageType" :: Symbol) VkImageCreateInfo :: Type Source #

type FieldOptional ("imageType" :: Symbol) VkImageCreateInfo :: Bool Source #

type FieldOffset ("imageType" :: Symbol) VkImageCreateInfo :: Nat Source #

type FieldIsArray ("imageType" :: Symbol) VkImageCreateInfo :: Bool Source #

HasField "initialLayout" VkImageCreateInfo Source # 

Associated Types

type FieldType ("initialLayout" :: Symbol) VkImageCreateInfo :: Type Source #

type FieldOptional ("initialLayout" :: Symbol) VkImageCreateInfo :: Bool Source #

type FieldOffset ("initialLayout" :: Symbol) VkImageCreateInfo :: Nat Source #

type FieldIsArray ("initialLayout" :: Symbol) VkImageCreateInfo :: Bool Source #

HasField "mipLevels" VkImageCreateInfo Source # 

Associated Types

type FieldType ("mipLevels" :: Symbol) VkImageCreateInfo :: Type Source #

type FieldOptional ("mipLevels" :: Symbol) VkImageCreateInfo :: Bool Source #

type FieldOffset ("mipLevels" :: Symbol) VkImageCreateInfo :: Nat Source #

type FieldIsArray ("mipLevels" :: Symbol) VkImageCreateInfo :: Bool Source #

HasField "pNext" VkImageCreateInfo Source # 
HasField "pQueueFamilyIndices" VkImageCreateInfo Source # 

Associated Types

type FieldType ("pQueueFamilyIndices" :: Symbol) VkImageCreateInfo :: Type Source #

type FieldOptional ("pQueueFamilyIndices" :: Symbol) VkImageCreateInfo :: Bool Source #

type FieldOffset ("pQueueFamilyIndices" :: Symbol) VkImageCreateInfo :: Nat Source #

type FieldIsArray ("pQueueFamilyIndices" :: Symbol) VkImageCreateInfo :: Bool Source #

HasField "queueFamilyIndexCount" VkImageCreateInfo Source # 

Associated Types

type FieldType ("queueFamilyIndexCount" :: Symbol) VkImageCreateInfo :: Type Source #

type FieldOptional ("queueFamilyIndexCount" :: Symbol) VkImageCreateInfo :: Bool Source #

type FieldOffset ("queueFamilyIndexCount" :: Symbol) VkImageCreateInfo :: Nat Source #

type FieldIsArray ("queueFamilyIndexCount" :: Symbol) VkImageCreateInfo :: Bool Source #

HasField "sType" VkImageCreateInfo Source # 
HasField "samples" VkImageCreateInfo Source # 
HasField "sharingMode" VkImageCreateInfo Source # 

Associated Types

type FieldType ("sharingMode" :: Symbol) VkImageCreateInfo :: Type Source #

type FieldOptional ("sharingMode" :: Symbol) VkImageCreateInfo :: Bool Source #

type FieldOffset ("sharingMode" :: Symbol) VkImageCreateInfo :: Nat Source #

type FieldIsArray ("sharingMode" :: Symbol) VkImageCreateInfo :: Bool Source #

HasField "tiling" VkImageCreateInfo Source # 
HasField "usage" VkImageCreateInfo Source # 
type StructFields VkImageCreateInfo Source # 
type StructFields VkImageCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "imageType" ((:) Symbol "format" ((:) Symbol "extent" ((:) Symbol "mipLevels" ((:) Symbol "arrayLayers" ((:) Symbol "samples" ((:) Symbol "tiling" ((:) Symbol "usage" ((:) Symbol "sharingMode" ((:) Symbol "queueFamilyIndexCount" ((:) Symbol "pQueueFamilyIndices" ((:) Symbol "initialLayout" ([] Symbol)))))))))))))))
type CUnionType VkImageCreateInfo Source # 
type ReturnedOnly VkImageCreateInfo Source # 
type StructExtends VkImageCreateInfo Source # 
type FieldType "arrayLayers" VkImageCreateInfo Source # 
type FieldType "arrayLayers" VkImageCreateInfo = Word32
type FieldType "extent" VkImageCreateInfo Source # 
type FieldType "flags" VkImageCreateInfo Source # 
type FieldType "format" VkImageCreateInfo Source # 
type FieldType "imageType" VkImageCreateInfo Source # 
type FieldType "initialLayout" VkImageCreateInfo Source # 
type FieldType "mipLevels" VkImageCreateInfo Source # 
type FieldType "pNext" VkImageCreateInfo Source # 
type FieldType "pQueueFamilyIndices" VkImageCreateInfo Source # 
type FieldType "pQueueFamilyIndices" VkImageCreateInfo = Ptr Word32
type FieldType "queueFamilyIndexCount" VkImageCreateInfo Source # 
type FieldType "queueFamilyIndexCount" VkImageCreateInfo = Word32
type FieldType "sType" VkImageCreateInfo Source # 
type FieldType "samples" VkImageCreateInfo Source # 
type FieldType "sharingMode" VkImageCreateInfo Source # 
type FieldType "tiling" VkImageCreateInfo Source # 
type FieldType "usage" VkImageCreateInfo Source # 
type FieldOptional "arrayLayers" VkImageCreateInfo Source # 
type FieldOptional "extent" VkImageCreateInfo Source # 
type FieldOptional "flags" VkImageCreateInfo Source # 
type FieldOptional "format" VkImageCreateInfo Source # 
type FieldOptional "imageType" VkImageCreateInfo Source # 
type FieldOptional "initialLayout" VkImageCreateInfo Source # 
type FieldOptional "initialLayout" VkImageCreateInfo = False
type FieldOptional "mipLevels" VkImageCreateInfo Source # 
type FieldOptional "pNext" VkImageCreateInfo Source # 
type FieldOptional "pQueueFamilyIndices" VkImageCreateInfo Source # 
type FieldOptional "pQueueFamilyIndices" VkImageCreateInfo = False
type FieldOptional "queueFamilyIndexCount" VkImageCreateInfo Source # 
type FieldOptional "queueFamilyIndexCount" VkImageCreateInfo = True
type FieldOptional "sType" VkImageCreateInfo Source # 
type FieldOptional "samples" VkImageCreateInfo Source # 
type FieldOptional "sharingMode" VkImageCreateInfo Source # 
type FieldOptional "tiling" VkImageCreateInfo Source # 
type FieldOptional "usage" VkImageCreateInfo Source # 
type FieldOffset "arrayLayers" VkImageCreateInfo Source # 
type FieldOffset "arrayLayers" VkImageCreateInfo = 44
type FieldOffset "extent" VkImageCreateInfo Source # 
type FieldOffset "extent" VkImageCreateInfo = 28
type FieldOffset "flags" VkImageCreateInfo Source # 
type FieldOffset "flags" VkImageCreateInfo = 16
type FieldOffset "format" VkImageCreateInfo Source # 
type FieldOffset "format" VkImageCreateInfo = 24
type FieldOffset "imageType" VkImageCreateInfo Source # 
type FieldOffset "imageType" VkImageCreateInfo = 20
type FieldOffset "initialLayout" VkImageCreateInfo Source # 
type FieldOffset "initialLayout" VkImageCreateInfo = 80
type FieldOffset "mipLevels" VkImageCreateInfo Source # 
type FieldOffset "mipLevels" VkImageCreateInfo = 40
type FieldOffset "pNext" VkImageCreateInfo Source # 
type FieldOffset "pQueueFamilyIndices" VkImageCreateInfo Source # 
type FieldOffset "pQueueFamilyIndices" VkImageCreateInfo = 72
type FieldOffset "queueFamilyIndexCount" VkImageCreateInfo Source # 
type FieldOffset "queueFamilyIndexCount" VkImageCreateInfo = 64
type FieldOffset "sType" VkImageCreateInfo Source # 
type FieldOffset "samples" VkImageCreateInfo Source # 
type FieldOffset "samples" VkImageCreateInfo = 48
type FieldOffset "sharingMode" VkImageCreateInfo Source # 
type FieldOffset "sharingMode" VkImageCreateInfo = 60
type FieldOffset "tiling" VkImageCreateInfo Source # 
type FieldOffset "tiling" VkImageCreateInfo = 52
type FieldOffset "usage" VkImageCreateInfo Source # 
type FieldOffset "usage" VkImageCreateInfo = 56
type FieldIsArray "arrayLayers" VkImageCreateInfo Source # 
type FieldIsArray "arrayLayers" VkImageCreateInfo = False
type FieldIsArray "extent" VkImageCreateInfo Source # 
type FieldIsArray "flags" VkImageCreateInfo Source # 
type FieldIsArray "format" VkImageCreateInfo Source # 
type FieldIsArray "imageType" VkImageCreateInfo Source # 
type FieldIsArray "initialLayout" VkImageCreateInfo Source # 
type FieldIsArray "initialLayout" VkImageCreateInfo = False
type FieldIsArray "mipLevels" VkImageCreateInfo Source # 
type FieldIsArray "pNext" VkImageCreateInfo Source # 
type FieldIsArray "pQueueFamilyIndices" VkImageCreateInfo Source # 
type FieldIsArray "pQueueFamilyIndices" VkImageCreateInfo = False
type FieldIsArray "queueFamilyIndexCount" VkImageCreateInfo Source # 
type FieldIsArray "queueFamilyIndexCount" VkImageCreateInfo = False
type FieldIsArray "sType" VkImageCreateInfo Source # 
type FieldIsArray "samples" VkImageCreateInfo Source # 
type FieldIsArray "sharingMode" VkImageCreateInfo Source # 
type FieldIsArray "sharingMode" VkImageCreateInfo = False
type FieldIsArray "tiling" VkImageCreateInfo Source # 
type FieldIsArray "usage" VkImageCreateInfo Source # 

data VkImageFormatListCreateInfoKHR Source #

typedef struct VkImageFormatListCreateInfoKHR {
    VkStructureType sType;
    const void*            pNext;
    uint32_t               viewFormatCount;
    const VkFormat*      pViewFormats;
} VkImageFormatListCreateInfoKHR;

VkImageFormatListCreateInfoKHR registry at www.khronos.org

Instances

Eq VkImageFormatListCreateInfoKHR Source # 
Ord VkImageFormatListCreateInfoKHR Source # 
Show VkImageFormatListCreateInfoKHR Source # 
Storable VkImageFormatListCreateInfoKHR Source # 
VulkanMarshalPrim VkImageFormatListCreateInfoKHR Source # 
VulkanMarshal VkImageFormatListCreateInfoKHR Source # 
CanWriteField "pNext" VkImageFormatListCreateInfoKHR Source # 
CanWriteField "pViewFormats" VkImageFormatListCreateInfoKHR Source # 
CanWriteField "sType" VkImageFormatListCreateInfoKHR Source # 
CanWriteField "viewFormatCount" VkImageFormatListCreateInfoKHR Source # 
CanReadField "pNext" VkImageFormatListCreateInfoKHR Source # 
CanReadField "pViewFormats" VkImageFormatListCreateInfoKHR Source # 
CanReadField "sType" VkImageFormatListCreateInfoKHR Source # 
CanReadField "viewFormatCount" VkImageFormatListCreateInfoKHR Source # 
HasField "pNext" VkImageFormatListCreateInfoKHR Source # 
HasField "pViewFormats" VkImageFormatListCreateInfoKHR Source # 
HasField "sType" VkImageFormatListCreateInfoKHR Source # 
HasField "viewFormatCount" VkImageFormatListCreateInfoKHR Source # 
type StructFields VkImageFormatListCreateInfoKHR Source # 
type StructFields VkImageFormatListCreateInfoKHR = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "viewFormatCount" ((:) Symbol "pViewFormats" ([] Symbol))))
type CUnionType VkImageFormatListCreateInfoKHR Source # 
type ReturnedOnly VkImageFormatListCreateInfoKHR Source # 
type StructExtends VkImageFormatListCreateInfoKHR Source # 
type FieldType "pNext" VkImageFormatListCreateInfoKHR Source # 
type FieldType "pViewFormats" VkImageFormatListCreateInfoKHR Source # 
type FieldType "sType" VkImageFormatListCreateInfoKHR Source # 
type FieldType "viewFormatCount" VkImageFormatListCreateInfoKHR Source # 
type FieldOptional "pNext" VkImageFormatListCreateInfoKHR Source # 
type FieldOptional "pViewFormats" VkImageFormatListCreateInfoKHR Source # 
type FieldOptional "sType" VkImageFormatListCreateInfoKHR Source # 
type FieldOptional "viewFormatCount" VkImageFormatListCreateInfoKHR Source # 
type FieldOffset "pNext" VkImageFormatListCreateInfoKHR Source # 
type FieldOffset "pViewFormats" VkImageFormatListCreateInfoKHR Source # 
type FieldOffset "sType" VkImageFormatListCreateInfoKHR Source # 
type FieldOffset "viewFormatCount" VkImageFormatListCreateInfoKHR Source # 
type FieldOffset "viewFormatCount" VkImageFormatListCreateInfoKHR = 16
type FieldIsArray "pNext" VkImageFormatListCreateInfoKHR Source # 
type FieldIsArray "pViewFormats" VkImageFormatListCreateInfoKHR Source # 
type FieldIsArray "sType" VkImageFormatListCreateInfoKHR Source # 
type FieldIsArray "viewFormatCount" VkImageFormatListCreateInfoKHR Source # 

data VkImageFormatProperties Source #

typedef struct VkImageFormatProperties {
    VkExtent3D             maxExtent;
    uint32_t               maxMipLevels;
    uint32_t               maxArrayLayers;
    VkSampleCountFlags     sampleCounts;
    VkDeviceSize           maxResourceSize;
} VkImageFormatProperties;

VkImageFormatProperties registry at www.khronos.org

Instances

Eq VkImageFormatProperties Source # 
Ord VkImageFormatProperties Source # 
Show VkImageFormatProperties Source # 
Storable VkImageFormatProperties Source # 
VulkanMarshalPrim VkImageFormatProperties Source # 
VulkanMarshal VkImageFormatProperties Source # 
CanWriteField "maxArrayLayers" VkImageFormatProperties Source # 
CanWriteField "maxExtent" VkImageFormatProperties Source # 
CanWriteField "maxMipLevels" VkImageFormatProperties Source # 
CanWriteField "maxResourceSize" VkImageFormatProperties Source # 
CanWriteField "sampleCounts" VkImageFormatProperties Source # 
CanReadField "maxArrayLayers" VkImageFormatProperties Source # 
CanReadField "maxExtent" VkImageFormatProperties Source # 
CanReadField "maxMipLevels" VkImageFormatProperties Source # 
CanReadField "maxResourceSize" VkImageFormatProperties Source # 
CanReadField "sampleCounts" VkImageFormatProperties Source # 
HasField "maxArrayLayers" VkImageFormatProperties Source # 

Associated Types

type FieldType ("maxArrayLayers" :: Symbol) VkImageFormatProperties :: Type Source #

type FieldOptional ("maxArrayLayers" :: Symbol) VkImageFormatProperties :: Bool Source #

type FieldOffset ("maxArrayLayers" :: Symbol) VkImageFormatProperties :: Nat Source #

type FieldIsArray ("maxArrayLayers" :: Symbol) VkImageFormatProperties :: Bool Source #

HasField "maxExtent" VkImageFormatProperties Source # 
HasField "maxMipLevels" VkImageFormatProperties Source # 

Associated Types

type FieldType ("maxMipLevels" :: Symbol) VkImageFormatProperties :: Type Source #

type FieldOptional ("maxMipLevels" :: Symbol) VkImageFormatProperties :: Bool Source #

type FieldOffset ("maxMipLevels" :: Symbol) VkImageFormatProperties :: Nat Source #

type FieldIsArray ("maxMipLevels" :: Symbol) VkImageFormatProperties :: Bool Source #

HasField "maxResourceSize" VkImageFormatProperties Source # 

Associated Types

type FieldType ("maxResourceSize" :: Symbol) VkImageFormatProperties :: Type Source #

type FieldOptional ("maxResourceSize" :: Symbol) VkImageFormatProperties :: Bool Source #

type FieldOffset ("maxResourceSize" :: Symbol) VkImageFormatProperties :: Nat Source #

type FieldIsArray ("maxResourceSize" :: Symbol) VkImageFormatProperties :: Bool Source #

HasField "sampleCounts" VkImageFormatProperties Source # 

Associated Types

type FieldType ("sampleCounts" :: Symbol) VkImageFormatProperties :: Type Source #

type FieldOptional ("sampleCounts" :: Symbol) VkImageFormatProperties :: Bool Source #

type FieldOffset ("sampleCounts" :: Symbol) VkImageFormatProperties :: Nat Source #

type FieldIsArray ("sampleCounts" :: Symbol) VkImageFormatProperties :: Bool Source #

type StructFields VkImageFormatProperties Source # 
type StructFields VkImageFormatProperties = (:) Symbol "maxExtent" ((:) Symbol "maxMipLevels" ((:) Symbol "maxArrayLayers" ((:) Symbol "sampleCounts" ((:) Symbol "maxResourceSize" ([] Symbol)))))
type CUnionType VkImageFormatProperties Source # 
type ReturnedOnly VkImageFormatProperties Source # 
type StructExtends VkImageFormatProperties Source # 
type FieldType "maxArrayLayers" VkImageFormatProperties Source # 
type FieldType "maxArrayLayers" VkImageFormatProperties = Word32
type FieldType "maxExtent" VkImageFormatProperties Source # 
type FieldType "maxMipLevels" VkImageFormatProperties Source # 
type FieldType "maxResourceSize" VkImageFormatProperties Source # 
type FieldType "sampleCounts" VkImageFormatProperties Source # 
type FieldOptional "maxArrayLayers" VkImageFormatProperties Source # 
type FieldOptional "maxExtent" VkImageFormatProperties Source # 
type FieldOptional "maxMipLevels" VkImageFormatProperties Source # 
type FieldOptional "maxResourceSize" VkImageFormatProperties Source # 
type FieldOptional "sampleCounts" VkImageFormatProperties Source # 
type FieldOffset "maxArrayLayers" VkImageFormatProperties Source # 
type FieldOffset "maxArrayLayers" VkImageFormatProperties = 16
type FieldOffset "maxExtent" VkImageFormatProperties Source # 
type FieldOffset "maxMipLevels" VkImageFormatProperties Source # 
type FieldOffset "maxMipLevels" VkImageFormatProperties = 12
type FieldOffset "maxResourceSize" VkImageFormatProperties Source # 
type FieldOffset "maxResourceSize" VkImageFormatProperties = 24
type FieldOffset "sampleCounts" VkImageFormatProperties Source # 
type FieldOffset "sampleCounts" VkImageFormatProperties = 20
type FieldIsArray "maxArrayLayers" VkImageFormatProperties Source # 
type FieldIsArray "maxExtent" VkImageFormatProperties Source # 
type FieldIsArray "maxMipLevels" VkImageFormatProperties Source # 
type FieldIsArray "maxResourceSize" VkImageFormatProperties Source # 
type FieldIsArray "maxResourceSize" VkImageFormatProperties = False
type FieldIsArray "sampleCounts" VkImageFormatProperties Source # 

data VkImageFormatProperties2 Source #

typedef struct VkImageFormatProperties2 {
    VkStructureType sType;
    void* pNext;
    VkImageFormatProperties          imageFormatProperties;
} VkImageFormatProperties2;

VkImageFormatProperties2 registry at www.khronos.org

Instances

Eq VkImageFormatProperties2 Source # 
Ord VkImageFormatProperties2 Source # 
Show VkImageFormatProperties2 Source # 
Storable VkImageFormatProperties2 Source # 
VulkanMarshalPrim VkImageFormatProperties2 Source # 
VulkanMarshal VkImageFormatProperties2 Source # 
CanWriteField "imageFormatProperties" VkImageFormatProperties2 Source # 
CanWriteField "pNext" VkImageFormatProperties2 Source # 
CanWriteField "sType" VkImageFormatProperties2 Source # 
CanReadField "imageFormatProperties" VkImageFormatProperties2 Source # 
CanReadField "pNext" VkImageFormatProperties2 Source # 
CanReadField "sType" VkImageFormatProperties2 Source # 
HasField "imageFormatProperties" VkImageFormatProperties2 Source # 

Associated Types

type FieldType ("imageFormatProperties" :: Symbol) VkImageFormatProperties2 :: Type Source #

type FieldOptional ("imageFormatProperties" :: Symbol) VkImageFormatProperties2 :: Bool Source #

type FieldOffset ("imageFormatProperties" :: Symbol) VkImageFormatProperties2 :: Nat Source #

type FieldIsArray ("imageFormatProperties" :: Symbol) VkImageFormatProperties2 :: Bool Source #

HasField "pNext" VkImageFormatProperties2 Source # 
HasField "sType" VkImageFormatProperties2 Source # 
type StructFields VkImageFormatProperties2 Source # 
type StructFields VkImageFormatProperties2 = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "imageFormatProperties" ([] Symbol)))
type CUnionType VkImageFormatProperties2 Source # 
type ReturnedOnly VkImageFormatProperties2 Source # 
type StructExtends VkImageFormatProperties2 Source # 
type FieldType "imageFormatProperties" VkImageFormatProperties2 Source # 
type FieldType "pNext" VkImageFormatProperties2 Source # 
type FieldType "sType" VkImageFormatProperties2 Source # 
type FieldOptional "imageFormatProperties" VkImageFormatProperties2 Source # 
type FieldOptional "imageFormatProperties" VkImageFormatProperties2 = False
type FieldOptional "pNext" VkImageFormatProperties2 Source # 
type FieldOptional "sType" VkImageFormatProperties2 Source # 
type FieldOffset "imageFormatProperties" VkImageFormatProperties2 Source # 
type FieldOffset "imageFormatProperties" VkImageFormatProperties2 = 16
type FieldOffset "pNext" VkImageFormatProperties2 Source # 
type FieldOffset "sType" VkImageFormatProperties2 Source # 
type FieldIsArray "imageFormatProperties" VkImageFormatProperties2 Source # 
type FieldIsArray "imageFormatProperties" VkImageFormatProperties2 = False
type FieldIsArray "pNext" VkImageFormatProperties2 Source # 
type FieldIsArray "sType" VkImageFormatProperties2 Source # 

data VkImageMemoryBarrier Source #

typedef struct VkImageMemoryBarrier {
    VkStructureType sType;
    const void*            pNext;
    VkAccessFlags          srcAccessMask;
    VkAccessFlags          dstAccessMask;
    VkImageLayout          oldLayout;
    VkImageLayout          newLayout;
    uint32_t               srcQueueFamilyIndex;
    uint32_t               dstQueueFamilyIndex;
    VkImage                image;
    VkImageSubresourceRange subresourceRange;
} VkImageMemoryBarrier;

VkImageMemoryBarrier registry at www.khronos.org

Instances

Eq VkImageMemoryBarrier Source # 
Ord VkImageMemoryBarrier Source # 
Show VkImageMemoryBarrier Source # 
Storable VkImageMemoryBarrier Source # 
VulkanMarshalPrim VkImageMemoryBarrier Source # 
VulkanMarshal VkImageMemoryBarrier Source # 
CanWriteField "dstAccessMask" VkImageMemoryBarrier Source # 
CanWriteField "dstQueueFamilyIndex" VkImageMemoryBarrier Source # 

Methods

writeField :: Ptr VkImageMemoryBarrier -> FieldType "dstQueueFamilyIndex" VkImageMemoryBarrier -> IO () Source #

CanWriteField "image" VkImageMemoryBarrier Source # 
CanWriteField "newLayout" VkImageMemoryBarrier Source # 
CanWriteField "oldLayout" VkImageMemoryBarrier Source # 
CanWriteField "pNext" VkImageMemoryBarrier Source # 
CanWriteField "sType" VkImageMemoryBarrier Source # 
CanWriteField "srcAccessMask" VkImageMemoryBarrier Source # 
CanWriteField "srcQueueFamilyIndex" VkImageMemoryBarrier Source # 

Methods

writeField :: Ptr VkImageMemoryBarrier -> FieldType "srcQueueFamilyIndex" VkImageMemoryBarrier -> IO () Source #

CanWriteField "subresourceRange" VkImageMemoryBarrier Source # 
CanReadField "dstAccessMask" VkImageMemoryBarrier Source # 
CanReadField "dstQueueFamilyIndex" VkImageMemoryBarrier Source # 
CanReadField "image" VkImageMemoryBarrier Source # 
CanReadField "newLayout" VkImageMemoryBarrier Source # 
CanReadField "oldLayout" VkImageMemoryBarrier Source # 
CanReadField "pNext" VkImageMemoryBarrier Source # 
CanReadField "sType" VkImageMemoryBarrier Source # 
CanReadField "srcAccessMask" VkImageMemoryBarrier Source # 
CanReadField "srcQueueFamilyIndex" VkImageMemoryBarrier Source # 
CanReadField "subresourceRange" VkImageMemoryBarrier Source # 
HasField "dstAccessMask" VkImageMemoryBarrier Source # 

Associated Types

type FieldType ("dstAccessMask" :: Symbol) VkImageMemoryBarrier :: Type Source #

type FieldOptional ("dstAccessMask" :: Symbol) VkImageMemoryBarrier :: Bool Source #

type FieldOffset ("dstAccessMask" :: Symbol) VkImageMemoryBarrier :: Nat Source #

type FieldIsArray ("dstAccessMask" :: Symbol) VkImageMemoryBarrier :: Bool Source #

HasField "dstQueueFamilyIndex" VkImageMemoryBarrier Source # 

Associated Types

type FieldType ("dstQueueFamilyIndex" :: Symbol) VkImageMemoryBarrier :: Type Source #

type FieldOptional ("dstQueueFamilyIndex" :: Symbol) VkImageMemoryBarrier :: Bool Source #

type FieldOffset ("dstQueueFamilyIndex" :: Symbol) VkImageMemoryBarrier :: Nat Source #

type FieldIsArray ("dstQueueFamilyIndex" :: Symbol) VkImageMemoryBarrier :: Bool Source #

HasField "image" VkImageMemoryBarrier Source # 
HasField "newLayout" VkImageMemoryBarrier Source # 
HasField "oldLayout" VkImageMemoryBarrier Source # 
HasField "pNext" VkImageMemoryBarrier Source # 
HasField "sType" VkImageMemoryBarrier Source # 
HasField "srcAccessMask" VkImageMemoryBarrier Source # 

Associated Types

type FieldType ("srcAccessMask" :: Symbol) VkImageMemoryBarrier :: Type Source #

type FieldOptional ("srcAccessMask" :: Symbol) VkImageMemoryBarrier :: Bool Source #

type FieldOffset ("srcAccessMask" :: Symbol) VkImageMemoryBarrier :: Nat Source #

type FieldIsArray ("srcAccessMask" :: Symbol) VkImageMemoryBarrier :: Bool Source #

HasField "srcQueueFamilyIndex" VkImageMemoryBarrier Source # 

Associated Types

type FieldType ("srcQueueFamilyIndex" :: Symbol) VkImageMemoryBarrier :: Type Source #

type FieldOptional ("srcQueueFamilyIndex" :: Symbol) VkImageMemoryBarrier :: Bool Source #

type FieldOffset ("srcQueueFamilyIndex" :: Symbol) VkImageMemoryBarrier :: Nat Source #

type FieldIsArray ("srcQueueFamilyIndex" :: Symbol) VkImageMemoryBarrier :: Bool Source #

HasField "subresourceRange" VkImageMemoryBarrier Source # 

Associated Types

type FieldType ("subresourceRange" :: Symbol) VkImageMemoryBarrier :: Type Source #

type FieldOptional ("subresourceRange" :: Symbol) VkImageMemoryBarrier :: Bool Source #

type FieldOffset ("subresourceRange" :: Symbol) VkImageMemoryBarrier :: Nat Source #

type FieldIsArray ("subresourceRange" :: Symbol) VkImageMemoryBarrier :: Bool Source #

type StructFields VkImageMemoryBarrier Source # 
type StructFields VkImageMemoryBarrier = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "srcAccessMask" ((:) Symbol "dstAccessMask" ((:) Symbol "oldLayout" ((:) Symbol "newLayout" ((:) Symbol "srcQueueFamilyIndex" ((:) Symbol "dstQueueFamilyIndex" ((:) Symbol "image" ((:) Symbol "subresourceRange" ([] Symbol))))))))))
type CUnionType VkImageMemoryBarrier Source # 
type ReturnedOnly VkImageMemoryBarrier Source # 
type StructExtends VkImageMemoryBarrier Source # 
type FieldType "dstAccessMask" VkImageMemoryBarrier Source # 
type FieldType "dstQueueFamilyIndex" VkImageMemoryBarrier Source # 
type FieldType "dstQueueFamilyIndex" VkImageMemoryBarrier = Word32
type FieldType "image" VkImageMemoryBarrier Source # 
type FieldType "newLayout" VkImageMemoryBarrier Source # 
type FieldType "oldLayout" VkImageMemoryBarrier Source # 
type FieldType "pNext" VkImageMemoryBarrier Source # 
type FieldType "sType" VkImageMemoryBarrier Source # 
type FieldType "srcAccessMask" VkImageMemoryBarrier Source # 
type FieldType "srcQueueFamilyIndex" VkImageMemoryBarrier Source # 
type FieldType "srcQueueFamilyIndex" VkImageMemoryBarrier = Word32
type FieldType "subresourceRange" VkImageMemoryBarrier Source # 
type FieldOptional "dstAccessMask" VkImageMemoryBarrier Source # 
type FieldOptional "dstAccessMask" VkImageMemoryBarrier = True
type FieldOptional "dstQueueFamilyIndex" VkImageMemoryBarrier Source # 
type FieldOptional "dstQueueFamilyIndex" VkImageMemoryBarrier = False
type FieldOptional "image" VkImageMemoryBarrier Source # 
type FieldOptional "newLayout" VkImageMemoryBarrier Source # 
type FieldOptional "oldLayout" VkImageMemoryBarrier Source # 
type FieldOptional "pNext" VkImageMemoryBarrier Source # 
type FieldOptional "sType" VkImageMemoryBarrier Source # 
type FieldOptional "srcAccessMask" VkImageMemoryBarrier Source # 
type FieldOptional "srcAccessMask" VkImageMemoryBarrier = True
type FieldOptional "srcQueueFamilyIndex" VkImageMemoryBarrier Source # 
type FieldOptional "srcQueueFamilyIndex" VkImageMemoryBarrier = False
type FieldOptional "subresourceRange" VkImageMemoryBarrier Source # 
type FieldOptional "subresourceRange" VkImageMemoryBarrier = False
type FieldOffset "dstAccessMask" VkImageMemoryBarrier Source # 
type FieldOffset "dstAccessMask" VkImageMemoryBarrier = 20
type FieldOffset "dstQueueFamilyIndex" VkImageMemoryBarrier Source # 
type FieldOffset "dstQueueFamilyIndex" VkImageMemoryBarrier = 36
type FieldOffset "image" VkImageMemoryBarrier Source # 
type FieldOffset "newLayout" VkImageMemoryBarrier Source # 
type FieldOffset "newLayout" VkImageMemoryBarrier = 28
type FieldOffset "oldLayout" VkImageMemoryBarrier Source # 
type FieldOffset "oldLayout" VkImageMemoryBarrier = 24
type FieldOffset "pNext" VkImageMemoryBarrier Source # 
type FieldOffset "sType" VkImageMemoryBarrier Source # 
type FieldOffset "srcAccessMask" VkImageMemoryBarrier Source # 
type FieldOffset "srcAccessMask" VkImageMemoryBarrier = 16
type FieldOffset "srcQueueFamilyIndex" VkImageMemoryBarrier Source # 
type FieldOffset "srcQueueFamilyIndex" VkImageMemoryBarrier = 32
type FieldOffset "subresourceRange" VkImageMemoryBarrier Source # 
type FieldOffset "subresourceRange" VkImageMemoryBarrier = 48
type FieldIsArray "dstAccessMask" VkImageMemoryBarrier Source # 
type FieldIsArray "dstAccessMask" VkImageMemoryBarrier = False
type FieldIsArray "dstQueueFamilyIndex" VkImageMemoryBarrier Source # 
type FieldIsArray "dstQueueFamilyIndex" VkImageMemoryBarrier = False
type FieldIsArray "image" VkImageMemoryBarrier Source # 
type FieldIsArray "newLayout" VkImageMemoryBarrier Source # 
type FieldIsArray "oldLayout" VkImageMemoryBarrier Source # 
type FieldIsArray "pNext" VkImageMemoryBarrier Source # 
type FieldIsArray "sType" VkImageMemoryBarrier Source # 
type FieldIsArray "srcAccessMask" VkImageMemoryBarrier Source # 
type FieldIsArray "srcAccessMask" VkImageMemoryBarrier = False
type FieldIsArray "srcQueueFamilyIndex" VkImageMemoryBarrier Source # 
type FieldIsArray "srcQueueFamilyIndex" VkImageMemoryBarrier = False
type FieldIsArray "subresourceRange" VkImageMemoryBarrier Source # 
type FieldIsArray "subresourceRange" VkImageMemoryBarrier = False

data VkImageMemoryRequirementsInfo2 Source #

typedef struct VkImageMemoryRequirementsInfo2 {
    VkStructureType sType;
    const void*                                                          pNext;
    VkImage                                                              image;
} VkImageMemoryRequirementsInfo2;

VkImageMemoryRequirementsInfo2 registry at www.khronos.org

Instances

Eq VkImageMemoryRequirementsInfo2 Source # 
Ord VkImageMemoryRequirementsInfo2 Source # 
Show VkImageMemoryRequirementsInfo2 Source # 
Storable VkImageMemoryRequirementsInfo2 Source # 
VulkanMarshalPrim VkImageMemoryRequirementsInfo2 Source # 
VulkanMarshal VkImageMemoryRequirementsInfo2 Source # 
CanWriteField "image" VkImageMemoryRequirementsInfo2 Source # 
CanWriteField "pNext" VkImageMemoryRequirementsInfo2 Source # 
CanWriteField "sType" VkImageMemoryRequirementsInfo2 Source # 
CanReadField "image" VkImageMemoryRequirementsInfo2 Source # 
CanReadField "pNext" VkImageMemoryRequirementsInfo2 Source # 
CanReadField "sType" VkImageMemoryRequirementsInfo2 Source # 
HasField "image" VkImageMemoryRequirementsInfo2 Source # 
HasField "pNext" VkImageMemoryRequirementsInfo2 Source # 
HasField "sType" VkImageMemoryRequirementsInfo2 Source # 
type StructFields VkImageMemoryRequirementsInfo2 Source # 
type StructFields VkImageMemoryRequirementsInfo2 = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "image" ([] Symbol)))
type CUnionType VkImageMemoryRequirementsInfo2 Source # 
type ReturnedOnly VkImageMemoryRequirementsInfo2 Source # 
type StructExtends VkImageMemoryRequirementsInfo2 Source # 
type FieldType "image" VkImageMemoryRequirementsInfo2 Source # 
type FieldType "pNext" VkImageMemoryRequirementsInfo2 Source # 
type FieldType "sType" VkImageMemoryRequirementsInfo2 Source # 
type FieldOptional "image" VkImageMemoryRequirementsInfo2 Source # 
type FieldOptional "pNext" VkImageMemoryRequirementsInfo2 Source # 
type FieldOptional "sType" VkImageMemoryRequirementsInfo2 Source # 
type FieldOffset "image" VkImageMemoryRequirementsInfo2 Source # 
type FieldOffset "pNext" VkImageMemoryRequirementsInfo2 Source # 
type FieldOffset "sType" VkImageMemoryRequirementsInfo2 Source # 
type FieldIsArray "image" VkImageMemoryRequirementsInfo2 Source # 
type FieldIsArray "pNext" VkImageMemoryRequirementsInfo2 Source # 
type FieldIsArray "sType" VkImageMemoryRequirementsInfo2 Source # 

data VkImagePlaneMemoryRequirementsInfo Source #

typedef struct VkImagePlaneMemoryRequirementsInfo {
    VkStructureType sType;
    const void*                      pNext;
    VkImageAspectFlagBits            planeAspect;
} VkImagePlaneMemoryRequirementsInfo;

VkImagePlaneMemoryRequirementsInfo registry at www.khronos.org

Instances

Eq VkImagePlaneMemoryRequirementsInfo Source # 
Ord VkImagePlaneMemoryRequirementsInfo Source # 
Show VkImagePlaneMemoryRequirementsInfo Source # 
Storable VkImagePlaneMemoryRequirementsInfo Source # 
VulkanMarshalPrim VkImagePlaneMemoryRequirementsInfo Source # 
VulkanMarshal VkImagePlaneMemoryRequirementsInfo Source # 
CanWriteField "pNext" VkImagePlaneMemoryRequirementsInfo Source # 
CanWriteField "planeAspect" VkImagePlaneMemoryRequirementsInfo Source # 
CanWriteField "sType" VkImagePlaneMemoryRequirementsInfo Source # 
CanReadField "pNext" VkImagePlaneMemoryRequirementsInfo Source # 
CanReadField "planeAspect" VkImagePlaneMemoryRequirementsInfo Source # 
CanReadField "sType" VkImagePlaneMemoryRequirementsInfo Source # 
HasField "pNext" VkImagePlaneMemoryRequirementsInfo Source # 
HasField "planeAspect" VkImagePlaneMemoryRequirementsInfo Source # 
HasField "sType" VkImagePlaneMemoryRequirementsInfo Source # 
type StructFields VkImagePlaneMemoryRequirementsInfo Source # 
type StructFields VkImagePlaneMemoryRequirementsInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "planeAspect" ([] Symbol)))
type CUnionType VkImagePlaneMemoryRequirementsInfo Source # 
type ReturnedOnly VkImagePlaneMemoryRequirementsInfo Source # 
type StructExtends VkImagePlaneMemoryRequirementsInfo Source # 
type FieldType "pNext" VkImagePlaneMemoryRequirementsInfo Source # 
type FieldType "planeAspect" VkImagePlaneMemoryRequirementsInfo Source # 
type FieldType "sType" VkImagePlaneMemoryRequirementsInfo Source # 
type FieldOptional "pNext" VkImagePlaneMemoryRequirementsInfo Source # 
type FieldOptional "planeAspect" VkImagePlaneMemoryRequirementsInfo Source # 
type FieldOptional "sType" VkImagePlaneMemoryRequirementsInfo Source # 
type FieldOffset "pNext" VkImagePlaneMemoryRequirementsInfo Source # 
type FieldOffset "planeAspect" VkImagePlaneMemoryRequirementsInfo Source # 
type FieldOffset "sType" VkImagePlaneMemoryRequirementsInfo Source # 
type FieldIsArray "pNext" VkImagePlaneMemoryRequirementsInfo Source # 
type FieldIsArray "planeAspect" VkImagePlaneMemoryRequirementsInfo Source # 
type FieldIsArray "sType" VkImagePlaneMemoryRequirementsInfo Source # 

data VkImageResolve Source #

typedef struct VkImageResolve {
    VkImageSubresourceLayers srcSubresource;
    VkOffset3D             srcOffset;
    VkImageSubresourceLayers dstSubresource;
    VkOffset3D             dstOffset;
    VkExtent3D             extent;
} VkImageResolve;

VkImageResolve registry at www.khronos.org

Instances

Eq VkImageResolve Source # 
Ord VkImageResolve Source # 
Show VkImageResolve Source # 
Storable VkImageResolve Source # 
VulkanMarshalPrim VkImageResolve Source # 
VulkanMarshal VkImageResolve Source # 
CanWriteField "dstOffset" VkImageResolve Source # 
CanWriteField "dstSubresource" VkImageResolve Source # 

Methods

writeField :: Ptr VkImageResolve -> FieldType "dstSubresource" VkImageResolve -> IO () Source #

CanWriteField "extent" VkImageResolve Source # 
CanWriteField "srcOffset" VkImageResolve Source # 
CanWriteField "srcSubresource" VkImageResolve Source # 

Methods

writeField :: Ptr VkImageResolve -> FieldType "srcSubresource" VkImageResolve -> IO () Source #

CanReadField "dstOffset" VkImageResolve Source # 
CanReadField "dstSubresource" VkImageResolve Source # 
CanReadField "extent" VkImageResolve Source # 
CanReadField "srcOffset" VkImageResolve Source # 
CanReadField "srcSubresource" VkImageResolve Source # 
HasField "dstOffset" VkImageResolve Source # 

Associated Types

type FieldType ("dstOffset" :: Symbol) VkImageResolve :: Type Source #

type FieldOptional ("dstOffset" :: Symbol) VkImageResolve :: Bool Source #

type FieldOffset ("dstOffset" :: Symbol) VkImageResolve :: Nat Source #

type FieldIsArray ("dstOffset" :: Symbol) VkImageResolve :: Bool Source #

HasField "dstSubresource" VkImageResolve Source # 

Associated Types

type FieldType ("dstSubresource" :: Symbol) VkImageResolve :: Type Source #

type FieldOptional ("dstSubresource" :: Symbol) VkImageResolve :: Bool Source #

type FieldOffset ("dstSubresource" :: Symbol) VkImageResolve :: Nat Source #

type FieldIsArray ("dstSubresource" :: Symbol) VkImageResolve :: Bool Source #

HasField "extent" VkImageResolve Source # 

Associated Types

type FieldType ("extent" :: Symbol) VkImageResolve :: Type Source #

type FieldOptional ("extent" :: Symbol) VkImageResolve :: Bool Source #

type FieldOffset ("extent" :: Symbol) VkImageResolve :: Nat Source #

type FieldIsArray ("extent" :: Symbol) VkImageResolve :: Bool Source #

HasField "srcOffset" VkImageResolve Source # 

Associated Types

type FieldType ("srcOffset" :: Symbol) VkImageResolve :: Type Source #

type FieldOptional ("srcOffset" :: Symbol) VkImageResolve :: Bool Source #

type FieldOffset ("srcOffset" :: Symbol) VkImageResolve :: Nat Source #

type FieldIsArray ("srcOffset" :: Symbol) VkImageResolve :: Bool Source #

HasField "srcSubresource" VkImageResolve Source # 

Associated Types

type FieldType ("srcSubresource" :: Symbol) VkImageResolve :: Type Source #

type FieldOptional ("srcSubresource" :: Symbol) VkImageResolve :: Bool Source #

type FieldOffset ("srcSubresource" :: Symbol) VkImageResolve :: Nat Source #

type FieldIsArray ("srcSubresource" :: Symbol) VkImageResolve :: Bool Source #

type StructFields VkImageResolve Source # 
type StructFields VkImageResolve = (:) Symbol "srcSubresource" ((:) Symbol "srcOffset" ((:) Symbol "dstSubresource" ((:) Symbol "dstOffset" ((:) Symbol "extent" ([] Symbol)))))
type CUnionType VkImageResolve Source # 
type ReturnedOnly VkImageResolve Source # 
type StructExtends VkImageResolve Source # 
type FieldType "dstOffset" VkImageResolve Source # 
type FieldType "dstSubresource" VkImageResolve Source # 
type FieldType "extent" VkImageResolve Source # 
type FieldType "srcOffset" VkImageResolve Source # 
type FieldType "srcSubresource" VkImageResolve Source # 
type FieldOptional "dstOffset" VkImageResolve Source # 
type FieldOptional "dstSubresource" VkImageResolve Source # 
type FieldOptional "dstSubresource" VkImageResolve = False
type FieldOptional "extent" VkImageResolve Source # 
type FieldOptional "srcOffset" VkImageResolve Source # 
type FieldOptional "srcSubresource" VkImageResolve Source # 
type FieldOptional "srcSubresource" VkImageResolve = False
type FieldOffset "dstOffset" VkImageResolve Source # 
type FieldOffset "dstOffset" VkImageResolve = 44
type FieldOffset "dstSubresource" VkImageResolve Source # 
type FieldOffset "dstSubresource" VkImageResolve = 28
type FieldOffset "extent" VkImageResolve Source # 
type FieldOffset "extent" VkImageResolve = 56
type FieldOffset "srcOffset" VkImageResolve Source # 
type FieldOffset "srcOffset" VkImageResolve = 16
type FieldOffset "srcSubresource" VkImageResolve Source # 
type FieldOffset "srcSubresource" VkImageResolve = 0
type FieldIsArray "dstOffset" VkImageResolve Source # 
type FieldIsArray "dstOffset" VkImageResolve = False
type FieldIsArray "dstSubresource" VkImageResolve Source # 
type FieldIsArray "dstSubresource" VkImageResolve = False
type FieldIsArray "extent" VkImageResolve Source # 
type FieldIsArray "srcOffset" VkImageResolve Source # 
type FieldIsArray "srcOffset" VkImageResolve = False
type FieldIsArray "srcSubresource" VkImageResolve Source # 
type FieldIsArray "srcSubresource" VkImageResolve = False

data VkImageSparseMemoryRequirementsInfo2 Source #

typedef struct VkImageSparseMemoryRequirementsInfo2 {
    VkStructureType sType;
    const void*                                                          pNext;
    VkImage                                                              image;
} VkImageSparseMemoryRequirementsInfo2;

VkImageSparseMemoryRequirementsInfo2 registry at www.khronos.org

Instances

Eq VkImageSparseMemoryRequirementsInfo2 Source # 
Ord VkImageSparseMemoryRequirementsInfo2 Source # 
Show VkImageSparseMemoryRequirementsInfo2 Source # 
Storable VkImageSparseMemoryRequirementsInfo2 Source # 
VulkanMarshalPrim VkImageSparseMemoryRequirementsInfo2 Source # 
VulkanMarshal VkImageSparseMemoryRequirementsInfo2 Source # 
CanWriteField "image" VkImageSparseMemoryRequirementsInfo2 Source # 
CanWriteField "pNext" VkImageSparseMemoryRequirementsInfo2 Source # 
CanWriteField "sType" VkImageSparseMemoryRequirementsInfo2 Source # 
CanReadField "image" VkImageSparseMemoryRequirementsInfo2 Source # 
CanReadField "pNext" VkImageSparseMemoryRequirementsInfo2 Source # 
CanReadField "sType" VkImageSparseMemoryRequirementsInfo2 Source # 
HasField "image" VkImageSparseMemoryRequirementsInfo2 Source # 
HasField "pNext" VkImageSparseMemoryRequirementsInfo2 Source # 
HasField "sType" VkImageSparseMemoryRequirementsInfo2 Source # 
type StructFields VkImageSparseMemoryRequirementsInfo2 Source # 
type StructFields VkImageSparseMemoryRequirementsInfo2 = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "image" ([] Symbol)))
type CUnionType VkImageSparseMemoryRequirementsInfo2 Source # 
type ReturnedOnly VkImageSparseMemoryRequirementsInfo2 Source # 
type StructExtends VkImageSparseMemoryRequirementsInfo2 Source # 
type FieldType "image" VkImageSparseMemoryRequirementsInfo2 Source # 
type FieldType "pNext" VkImageSparseMemoryRequirementsInfo2 Source # 
type FieldType "sType" VkImageSparseMemoryRequirementsInfo2 Source # 
type FieldOptional "image" VkImageSparseMemoryRequirementsInfo2 Source # 
type FieldOptional "pNext" VkImageSparseMemoryRequirementsInfo2 Source # 
type FieldOptional "sType" VkImageSparseMemoryRequirementsInfo2 Source # 
type FieldOffset "image" VkImageSparseMemoryRequirementsInfo2 Source # 
type FieldOffset "pNext" VkImageSparseMemoryRequirementsInfo2 Source # 
type FieldOffset "sType" VkImageSparseMemoryRequirementsInfo2 Source # 
type FieldIsArray "image" VkImageSparseMemoryRequirementsInfo2 Source # 
type FieldIsArray "pNext" VkImageSparseMemoryRequirementsInfo2 Source # 
type FieldIsArray "sType" VkImageSparseMemoryRequirementsInfo2 Source # 

data VkImageSubresource Source #

typedef struct VkImageSubresource {
    VkImageAspectFlags     aspectMask;
    uint32_t               mipLevel;
    uint32_t               arrayLayer;
} VkImageSubresource;

VkImageSubresource registry at www.khronos.org

Instances

Eq VkImageSubresource Source # 
Ord VkImageSubresource Source # 
Show VkImageSubresource Source # 
Storable VkImageSubresource Source # 
VulkanMarshalPrim VkImageSubresource Source # 
VulkanMarshal VkImageSubresource Source # 
CanWriteField "arrayLayer" VkImageSubresource Source # 
CanWriteField "aspectMask" VkImageSubresource Source # 
CanWriteField "mipLevel" VkImageSubresource Source # 
CanReadField "arrayLayer" VkImageSubresource Source # 
CanReadField "aspectMask" VkImageSubresource Source # 
CanReadField "mipLevel" VkImageSubresource Source # 
HasField "arrayLayer" VkImageSubresource Source # 

Associated Types

type FieldType ("arrayLayer" :: Symbol) VkImageSubresource :: Type Source #

type FieldOptional ("arrayLayer" :: Symbol) VkImageSubresource :: Bool Source #

type FieldOffset ("arrayLayer" :: Symbol) VkImageSubresource :: Nat Source #

type FieldIsArray ("arrayLayer" :: Symbol) VkImageSubresource :: Bool Source #

HasField "aspectMask" VkImageSubresource Source # 

Associated Types

type FieldType ("aspectMask" :: Symbol) VkImageSubresource :: Type Source #

type FieldOptional ("aspectMask" :: Symbol) VkImageSubresource :: Bool Source #

type FieldOffset ("aspectMask" :: Symbol) VkImageSubresource :: Nat Source #

type FieldIsArray ("aspectMask" :: Symbol) VkImageSubresource :: Bool Source #

HasField "mipLevel" VkImageSubresource Source # 
type StructFields VkImageSubresource Source # 
type StructFields VkImageSubresource = (:) Symbol "aspectMask" ((:) Symbol "mipLevel" ((:) Symbol "arrayLayer" ([] Symbol)))
type CUnionType VkImageSubresource Source # 
type ReturnedOnly VkImageSubresource Source # 
type StructExtends VkImageSubresource Source # 
type FieldType "arrayLayer" VkImageSubresource Source # 
type FieldType "arrayLayer" VkImageSubresource = Word32
type FieldType "aspectMask" VkImageSubresource Source # 
type FieldType "mipLevel" VkImageSubresource Source # 
type FieldOptional "arrayLayer" VkImageSubresource Source # 
type FieldOptional "aspectMask" VkImageSubresource Source # 
type FieldOptional "mipLevel" VkImageSubresource Source # 
type FieldOffset "arrayLayer" VkImageSubresource Source # 
type FieldOffset "arrayLayer" VkImageSubresource = 8
type FieldOffset "aspectMask" VkImageSubresource Source # 
type FieldOffset "aspectMask" VkImageSubresource = 0
type FieldOffset "mipLevel" VkImageSubresource Source # 
type FieldOffset "mipLevel" VkImageSubresource = 4
type FieldIsArray "arrayLayer" VkImageSubresource Source # 
type FieldIsArray "aspectMask" VkImageSubresource Source # 
type FieldIsArray "mipLevel" VkImageSubresource Source # 

data VkImageSubresourceLayers Source #

typedef struct VkImageSubresourceLayers {
    VkImageAspectFlags     aspectMask;
    uint32_t               mipLevel;
    uint32_t               baseArrayLayer;
    uint32_t               layerCount;
} VkImageSubresourceLayers;

VkImageSubresourceLayers registry at www.khronos.org

Instances

Eq VkImageSubresourceLayers Source # 
Ord VkImageSubresourceLayers Source # 
Show VkImageSubresourceLayers Source # 
Storable VkImageSubresourceLayers Source # 
VulkanMarshalPrim VkImageSubresourceLayers Source # 
VulkanMarshal VkImageSubresourceLayers Source # 
CanWriteField "aspectMask" VkImageSubresourceLayers Source # 
CanWriteField "baseArrayLayer" VkImageSubresourceLayers Source # 
CanWriteField "layerCount" VkImageSubresourceLayers Source # 
CanWriteField "mipLevel" VkImageSubresourceLayers Source # 
CanReadField "aspectMask" VkImageSubresourceLayers Source # 
CanReadField "baseArrayLayer" VkImageSubresourceLayers Source # 
CanReadField "layerCount" VkImageSubresourceLayers Source # 
CanReadField "mipLevel" VkImageSubresourceLayers Source # 
HasField "aspectMask" VkImageSubresourceLayers Source # 
HasField "baseArrayLayer" VkImageSubresourceLayers Source # 

Associated Types

type FieldType ("baseArrayLayer" :: Symbol) VkImageSubresourceLayers :: Type Source #

type FieldOptional ("baseArrayLayer" :: Symbol) VkImageSubresourceLayers :: Bool Source #

type FieldOffset ("baseArrayLayer" :: Symbol) VkImageSubresourceLayers :: Nat Source #

type FieldIsArray ("baseArrayLayer" :: Symbol) VkImageSubresourceLayers :: Bool Source #

HasField "layerCount" VkImageSubresourceLayers Source # 
HasField "mipLevel" VkImageSubresourceLayers Source # 
type StructFields VkImageSubresourceLayers Source # 
type StructFields VkImageSubresourceLayers = (:) Symbol "aspectMask" ((:) Symbol "mipLevel" ((:) Symbol "baseArrayLayer" ((:) Symbol "layerCount" ([] Symbol))))
type CUnionType VkImageSubresourceLayers Source # 
type ReturnedOnly VkImageSubresourceLayers Source # 
type StructExtends VkImageSubresourceLayers Source # 
type FieldType "aspectMask" VkImageSubresourceLayers Source # 
type FieldType "baseArrayLayer" VkImageSubresourceLayers Source # 
type FieldType "baseArrayLayer" VkImageSubresourceLayers = Word32
type FieldType "layerCount" VkImageSubresourceLayers Source # 
type FieldType "mipLevel" VkImageSubresourceLayers Source # 
type FieldOptional "aspectMask" VkImageSubresourceLayers Source # 
type FieldOptional "baseArrayLayer" VkImageSubresourceLayers Source # 
type FieldOptional "layerCount" VkImageSubresourceLayers Source # 
type FieldOptional "mipLevel" VkImageSubresourceLayers Source # 
type FieldOffset "aspectMask" VkImageSubresourceLayers Source # 
type FieldOffset "baseArrayLayer" VkImageSubresourceLayers Source # 
type FieldOffset "baseArrayLayer" VkImageSubresourceLayers = 8
type FieldOffset "layerCount" VkImageSubresourceLayers Source # 
type FieldOffset "layerCount" VkImageSubresourceLayers = 12
type FieldOffset "mipLevel" VkImageSubresourceLayers Source # 
type FieldIsArray "aspectMask" VkImageSubresourceLayers Source # 
type FieldIsArray "baseArrayLayer" VkImageSubresourceLayers Source # 
type FieldIsArray "layerCount" VkImageSubresourceLayers Source # 
type FieldIsArray "mipLevel" VkImageSubresourceLayers Source # 

data VkImageSubresourceRange Source #

typedef struct VkImageSubresourceRange {
    VkImageAspectFlags     aspectMask;
    uint32_t               baseMipLevel;
    uint32_t               levelCount;
    uint32_t               baseArrayLayer;
    uint32_t               layerCount;
} VkImageSubresourceRange;

VkImageSubresourceRange registry at www.khronos.org

Instances

Eq VkImageSubresourceRange Source # 
Ord VkImageSubresourceRange Source # 
Show VkImageSubresourceRange Source # 
Storable VkImageSubresourceRange Source # 
VulkanMarshalPrim VkImageSubresourceRange Source # 
VulkanMarshal VkImageSubresourceRange Source # 
CanWriteField "aspectMask" VkImageSubresourceRange Source # 
CanWriteField "baseArrayLayer" VkImageSubresourceRange Source # 
CanWriteField "baseMipLevel" VkImageSubresourceRange Source # 
CanWriteField "layerCount" VkImageSubresourceRange Source # 
CanWriteField "levelCount" VkImageSubresourceRange Source # 
CanReadField "aspectMask" VkImageSubresourceRange Source # 
CanReadField "baseArrayLayer" VkImageSubresourceRange Source # 
CanReadField "baseMipLevel" VkImageSubresourceRange Source # 
CanReadField "layerCount" VkImageSubresourceRange Source # 
CanReadField "levelCount" VkImageSubresourceRange Source # 
HasField "aspectMask" VkImageSubresourceRange Source # 
HasField "baseArrayLayer" VkImageSubresourceRange Source # 

Associated Types

type FieldType ("baseArrayLayer" :: Symbol) VkImageSubresourceRange :: Type Source #

type FieldOptional ("baseArrayLayer" :: Symbol) VkImageSubresourceRange :: Bool Source #

type FieldOffset ("baseArrayLayer" :: Symbol) VkImageSubresourceRange :: Nat Source #

type FieldIsArray ("baseArrayLayer" :: Symbol) VkImageSubresourceRange :: Bool Source #

HasField "baseMipLevel" VkImageSubresourceRange Source # 

Associated Types

type FieldType ("baseMipLevel" :: Symbol) VkImageSubresourceRange :: Type Source #

type FieldOptional ("baseMipLevel" :: Symbol) VkImageSubresourceRange :: Bool Source #

type FieldOffset ("baseMipLevel" :: Symbol) VkImageSubresourceRange :: Nat Source #

type FieldIsArray ("baseMipLevel" :: Symbol) VkImageSubresourceRange :: Bool Source #

HasField "layerCount" VkImageSubresourceRange Source # 
HasField "levelCount" VkImageSubresourceRange Source # 
type StructFields VkImageSubresourceRange Source # 
type StructFields VkImageSubresourceRange = (:) Symbol "aspectMask" ((:) Symbol "baseMipLevel" ((:) Symbol "levelCount" ((:) Symbol "baseArrayLayer" ((:) Symbol "layerCount" ([] Symbol)))))
type CUnionType VkImageSubresourceRange Source # 
type ReturnedOnly VkImageSubresourceRange Source # 
type StructExtends VkImageSubresourceRange Source # 
type FieldType "aspectMask" VkImageSubresourceRange Source # 
type FieldType "baseArrayLayer" VkImageSubresourceRange Source # 
type FieldType "baseArrayLayer" VkImageSubresourceRange = Word32
type FieldType "baseMipLevel" VkImageSubresourceRange Source # 
type FieldType "layerCount" VkImageSubresourceRange Source # 
type FieldType "levelCount" VkImageSubresourceRange Source # 
type FieldOptional "aspectMask" VkImageSubresourceRange Source # 
type FieldOptional "baseArrayLayer" VkImageSubresourceRange Source # 
type FieldOptional "baseMipLevel" VkImageSubresourceRange Source # 
type FieldOptional "layerCount" VkImageSubresourceRange Source # 
type FieldOptional "levelCount" VkImageSubresourceRange Source # 
type FieldOffset "aspectMask" VkImageSubresourceRange Source # 
type FieldOffset "aspectMask" VkImageSubresourceRange = 0
type FieldOffset "baseArrayLayer" VkImageSubresourceRange Source # 
type FieldOffset "baseArrayLayer" VkImageSubresourceRange = 12
type FieldOffset "baseMipLevel" VkImageSubresourceRange Source # 
type FieldOffset "baseMipLevel" VkImageSubresourceRange = 4
type FieldOffset "layerCount" VkImageSubresourceRange Source # 
type FieldOffset "layerCount" VkImageSubresourceRange = 16
type FieldOffset "levelCount" VkImageSubresourceRange Source # 
type FieldOffset "levelCount" VkImageSubresourceRange = 8
type FieldIsArray "aspectMask" VkImageSubresourceRange Source # 
type FieldIsArray "baseArrayLayer" VkImageSubresourceRange Source # 
type FieldIsArray "baseMipLevel" VkImageSubresourceRange Source # 
type FieldIsArray "layerCount" VkImageSubresourceRange Source # 
type FieldIsArray "levelCount" VkImageSubresourceRange Source # 

data VkImageSwapchainCreateInfoKHR Source #

typedef struct VkImageSwapchainCreateInfoKHR {
    VkStructureType sType;
    const void*                      pNext;
    VkSwapchainKHR   swapchain;
} VkImageSwapchainCreateInfoKHR;

VkImageSwapchainCreateInfoKHR registry at www.khronos.org

Instances

Eq VkImageSwapchainCreateInfoKHR Source # 
Ord VkImageSwapchainCreateInfoKHR Source # 
Show VkImageSwapchainCreateInfoKHR Source # 
Storable VkImageSwapchainCreateInfoKHR Source # 
VulkanMarshalPrim VkImageSwapchainCreateInfoKHR Source # 
VulkanMarshal VkImageSwapchainCreateInfoKHR Source # 
CanWriteField "pNext" VkImageSwapchainCreateInfoKHR Source # 
CanWriteField "sType" VkImageSwapchainCreateInfoKHR Source # 
CanWriteField "swapchain" VkImageSwapchainCreateInfoKHR Source # 
CanReadField "pNext" VkImageSwapchainCreateInfoKHR Source # 
CanReadField "sType" VkImageSwapchainCreateInfoKHR Source # 
CanReadField "swapchain" VkImageSwapchainCreateInfoKHR Source # 
HasField "pNext" VkImageSwapchainCreateInfoKHR Source # 
HasField "sType" VkImageSwapchainCreateInfoKHR Source # 
HasField "swapchain" VkImageSwapchainCreateInfoKHR Source # 
type StructFields VkImageSwapchainCreateInfoKHR Source # 
type StructFields VkImageSwapchainCreateInfoKHR = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "swapchain" ([] Symbol)))
type CUnionType VkImageSwapchainCreateInfoKHR Source # 
type ReturnedOnly VkImageSwapchainCreateInfoKHR Source # 
type StructExtends VkImageSwapchainCreateInfoKHR Source # 
type FieldType "pNext" VkImageSwapchainCreateInfoKHR Source # 
type FieldType "sType" VkImageSwapchainCreateInfoKHR Source # 
type FieldType "swapchain" VkImageSwapchainCreateInfoKHR Source # 
type FieldOptional "pNext" VkImageSwapchainCreateInfoKHR Source # 
type FieldOptional "sType" VkImageSwapchainCreateInfoKHR Source # 
type FieldOptional "swapchain" VkImageSwapchainCreateInfoKHR Source # 
type FieldOffset "pNext" VkImageSwapchainCreateInfoKHR Source # 
type FieldOffset "sType" VkImageSwapchainCreateInfoKHR Source # 
type FieldOffset "swapchain" VkImageSwapchainCreateInfoKHR Source # 
type FieldIsArray "pNext" VkImageSwapchainCreateInfoKHR Source # 
type FieldIsArray "sType" VkImageSwapchainCreateInfoKHR Source # 
type FieldIsArray "swapchain" VkImageSwapchainCreateInfoKHR Source # 

data VkImageViewCreateInfo Source #

typedef struct VkImageViewCreateInfo {
    VkStructureType sType;
    const void*            pNext;
    VkImageViewCreateFlags flags;
    VkImage                image;
    VkImageViewType        viewType;
    VkFormat               format;
    VkComponentMapping     components;
    VkImageSubresourceRange subresourceRange;
} VkImageViewCreateInfo;

VkImageViewCreateInfo registry at www.khronos.org

Instances

Eq VkImageViewCreateInfo Source # 
Ord VkImageViewCreateInfo Source # 
Show VkImageViewCreateInfo Source # 
Storable VkImageViewCreateInfo Source # 
VulkanMarshalPrim VkImageViewCreateInfo Source # 
VulkanMarshal VkImageViewCreateInfo Source # 
CanWriteField "components" VkImageViewCreateInfo Source # 
CanWriteField "flags" VkImageViewCreateInfo Source # 
CanWriteField "format" VkImageViewCreateInfo Source # 
CanWriteField "image" VkImageViewCreateInfo Source # 
CanWriteField "pNext" VkImageViewCreateInfo Source # 
CanWriteField "sType" VkImageViewCreateInfo Source # 
CanWriteField "subresourceRange" VkImageViewCreateInfo Source # 
CanWriteField "viewType" VkImageViewCreateInfo Source # 
CanReadField "components" VkImageViewCreateInfo Source # 
CanReadField "flags" VkImageViewCreateInfo Source # 
CanReadField "format" VkImageViewCreateInfo Source # 
CanReadField "image" VkImageViewCreateInfo Source # 
CanReadField "pNext" VkImageViewCreateInfo Source # 
CanReadField "sType" VkImageViewCreateInfo Source # 
CanReadField "subresourceRange" VkImageViewCreateInfo Source # 
CanReadField "viewType" VkImageViewCreateInfo Source # 
HasField "components" VkImageViewCreateInfo Source # 
HasField "flags" VkImageViewCreateInfo Source # 
HasField "format" VkImageViewCreateInfo Source # 
HasField "image" VkImageViewCreateInfo Source # 
HasField "pNext" VkImageViewCreateInfo Source # 
HasField "sType" VkImageViewCreateInfo Source # 
HasField "subresourceRange" VkImageViewCreateInfo Source # 

Associated Types

type FieldType ("subresourceRange" :: Symbol) VkImageViewCreateInfo :: Type Source #

type FieldOptional ("subresourceRange" :: Symbol) VkImageViewCreateInfo :: Bool Source #

type FieldOffset ("subresourceRange" :: Symbol) VkImageViewCreateInfo :: Nat Source #

type FieldIsArray ("subresourceRange" :: Symbol) VkImageViewCreateInfo :: Bool Source #

HasField "viewType" VkImageViewCreateInfo Source # 
type StructFields VkImageViewCreateInfo Source # 
type StructFields VkImageViewCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "image" ((:) Symbol "viewType" ((:) Symbol "format" ((:) Symbol "components" ((:) Symbol "subresourceRange" ([] Symbol))))))))
type CUnionType VkImageViewCreateInfo Source # 
type ReturnedOnly VkImageViewCreateInfo Source # 
type StructExtends VkImageViewCreateInfo Source # 
type FieldType "components" VkImageViewCreateInfo Source # 
type FieldType "flags" VkImageViewCreateInfo Source # 
type FieldType "format" VkImageViewCreateInfo Source # 
type FieldType "image" VkImageViewCreateInfo Source # 
type FieldType "pNext" VkImageViewCreateInfo Source # 
type FieldType "sType" VkImageViewCreateInfo Source # 
type FieldType "subresourceRange" VkImageViewCreateInfo Source # 
type FieldType "viewType" VkImageViewCreateInfo Source # 
type FieldOptional "components" VkImageViewCreateInfo Source # 
type FieldOptional "flags" VkImageViewCreateInfo Source # 
type FieldOptional "format" VkImageViewCreateInfo Source # 
type FieldOptional "image" VkImageViewCreateInfo Source # 
type FieldOptional "pNext" VkImageViewCreateInfo Source # 
type FieldOptional "sType" VkImageViewCreateInfo Source # 
type FieldOptional "subresourceRange" VkImageViewCreateInfo Source # 
type FieldOptional "subresourceRange" VkImageViewCreateInfo = False
type FieldOptional "viewType" VkImageViewCreateInfo Source # 
type FieldOffset "components" VkImageViewCreateInfo Source # 
type FieldOffset "components" VkImageViewCreateInfo = 40
type FieldOffset "flags" VkImageViewCreateInfo Source # 
type FieldOffset "format" VkImageViewCreateInfo Source # 
type FieldOffset "image" VkImageViewCreateInfo Source # 
type FieldOffset "pNext" VkImageViewCreateInfo Source # 
type FieldOffset "sType" VkImageViewCreateInfo Source # 
type FieldOffset "subresourceRange" VkImageViewCreateInfo Source # 
type FieldOffset "subresourceRange" VkImageViewCreateInfo = 56
type FieldOffset "viewType" VkImageViewCreateInfo Source # 
type FieldOffset "viewType" VkImageViewCreateInfo = 32
type FieldIsArray "components" VkImageViewCreateInfo Source # 
type FieldIsArray "flags" VkImageViewCreateInfo Source # 
type FieldIsArray "format" VkImageViewCreateInfo Source # 
type FieldIsArray "image" VkImageViewCreateInfo Source # 
type FieldIsArray "pNext" VkImageViewCreateInfo Source # 
type FieldIsArray "sType" VkImageViewCreateInfo Source # 
type FieldIsArray "subresourceRange" VkImageViewCreateInfo Source # 
type FieldIsArray "subresourceRange" VkImageViewCreateInfo = False
type FieldIsArray "viewType" VkImageViewCreateInfo Source # 

data VkImageViewUsageCreateInfo Source #

typedef struct VkImageViewUsageCreateInfo {
    VkStructureType sType;
    const void* pNext;
    VkImageUsageFlags usage;
} VkImageViewUsageCreateInfo;

VkImageViewUsageCreateInfo registry at www.khronos.org

Instances

Eq VkImageViewUsageCreateInfo Source # 
Ord VkImageViewUsageCreateInfo Source # 
Show VkImageViewUsageCreateInfo Source # 
Storable VkImageViewUsageCreateInfo Source # 
VulkanMarshalPrim VkImageViewUsageCreateInfo Source # 
VulkanMarshal VkImageViewUsageCreateInfo Source # 
CanWriteField "pNext" VkImageViewUsageCreateInfo Source # 
CanWriteField "sType" VkImageViewUsageCreateInfo Source # 
CanWriteField "usage" VkImageViewUsageCreateInfo Source # 
CanReadField "pNext" VkImageViewUsageCreateInfo Source # 
CanReadField "sType" VkImageViewUsageCreateInfo Source # 
CanReadField "usage" VkImageViewUsageCreateInfo Source # 
HasField "pNext" VkImageViewUsageCreateInfo Source # 
HasField "sType" VkImageViewUsageCreateInfo Source # 
HasField "usage" VkImageViewUsageCreateInfo Source # 
type StructFields VkImageViewUsageCreateInfo Source # 
type StructFields VkImageViewUsageCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "usage" ([] Symbol)))
type CUnionType VkImageViewUsageCreateInfo Source # 
type ReturnedOnly VkImageViewUsageCreateInfo Source # 
type StructExtends VkImageViewUsageCreateInfo Source # 
type FieldType "pNext" VkImageViewUsageCreateInfo Source # 
type FieldType "sType" VkImageViewUsageCreateInfo Source # 
type FieldType "usage" VkImageViewUsageCreateInfo Source # 
type FieldOptional "pNext" VkImageViewUsageCreateInfo Source # 
type FieldOptional "sType" VkImageViewUsageCreateInfo Source # 
type FieldOptional "usage" VkImageViewUsageCreateInfo Source # 
type FieldOffset "pNext" VkImageViewUsageCreateInfo Source # 
type FieldOffset "sType" VkImageViewUsageCreateInfo Source # 
type FieldOffset "usage" VkImageViewUsageCreateInfo Source # 
type FieldIsArray "pNext" VkImageViewUsageCreateInfo Source # 
type FieldIsArray "sType" VkImageViewUsageCreateInfo Source # 
type FieldIsArray "usage" VkImageViewUsageCreateInfo Source # 

newtype VkMemoryAllocateFlagBitsKHR Source #

Instances

Bounded VkMemoryAllocateFlagBitsKHR Source # 
Enum VkMemoryAllocateFlagBitsKHR Source # 
Eq VkMemoryAllocateFlagBitsKHR Source # 
Integral VkMemoryAllocateFlagBitsKHR Source # 
Data VkMemoryAllocateFlagBitsKHR Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkMemoryAllocateFlagBitsKHR -> c VkMemoryAllocateFlagBitsKHR #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkMemoryAllocateFlagBitsKHR #

toConstr :: VkMemoryAllocateFlagBitsKHR -> Constr #

dataTypeOf :: VkMemoryAllocateFlagBitsKHR -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkMemoryAllocateFlagBitsKHR) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkMemoryAllocateFlagBitsKHR) #

gmapT :: (forall b. Data b => b -> b) -> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkMemoryAllocateFlagBitsKHR -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkMemoryAllocateFlagBitsKHR -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkMemoryAllocateFlagBitsKHR -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkMemoryAllocateFlagBitsKHR -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkMemoryAllocateFlagBitsKHR -> m VkMemoryAllocateFlagBitsKHR #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkMemoryAllocateFlagBitsKHR -> m VkMemoryAllocateFlagBitsKHR #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkMemoryAllocateFlagBitsKHR -> m VkMemoryAllocateFlagBitsKHR #

Num VkMemoryAllocateFlagBitsKHR Source # 
Ord VkMemoryAllocateFlagBitsKHR Source # 
Read VkMemoryAllocateFlagBitsKHR Source # 
Real VkMemoryAllocateFlagBitsKHR Source # 
Show VkMemoryAllocateFlagBitsKHR Source # 
Generic VkMemoryAllocateFlagBitsKHR Source # 
Storable VkMemoryAllocateFlagBitsKHR Source # 
Bits VkMemoryAllocateFlagBitsKHR Source # 

Methods

(.&.) :: VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR #

(.|.) :: VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR #

xor :: VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR #

complement :: VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR #

shift :: VkMemoryAllocateFlagBitsKHR -> Int -> VkMemoryAllocateFlagBitsKHR #

rotate :: VkMemoryAllocateFlagBitsKHR -> Int -> VkMemoryAllocateFlagBitsKHR #

zeroBits :: VkMemoryAllocateFlagBitsKHR #

bit :: Int -> VkMemoryAllocateFlagBitsKHR #

setBit :: VkMemoryAllocateFlagBitsKHR -> Int -> VkMemoryAllocateFlagBitsKHR #

clearBit :: VkMemoryAllocateFlagBitsKHR -> Int -> VkMemoryAllocateFlagBitsKHR #

complementBit :: VkMemoryAllocateFlagBitsKHR -> Int -> VkMemoryAllocateFlagBitsKHR #

testBit :: VkMemoryAllocateFlagBitsKHR -> Int -> Bool #

bitSizeMaybe :: VkMemoryAllocateFlagBitsKHR -> Maybe Int #

bitSize :: VkMemoryAllocateFlagBitsKHR -> Int #

isSigned :: VkMemoryAllocateFlagBitsKHR -> Bool #

shiftL :: VkMemoryAllocateFlagBitsKHR -> Int -> VkMemoryAllocateFlagBitsKHR #

unsafeShiftL :: VkMemoryAllocateFlagBitsKHR -> Int -> VkMemoryAllocateFlagBitsKHR #

shiftR :: VkMemoryAllocateFlagBitsKHR -> Int -> VkMemoryAllocateFlagBitsKHR #

unsafeShiftR :: VkMemoryAllocateFlagBitsKHR -> Int -> VkMemoryAllocateFlagBitsKHR #

rotateL :: VkMemoryAllocateFlagBitsKHR -> Int -> VkMemoryAllocateFlagBitsKHR #

rotateR :: VkMemoryAllocateFlagBitsKHR -> Int -> VkMemoryAllocateFlagBitsKHR #

popCount :: VkMemoryAllocateFlagBitsKHR -> Int #

FiniteBits VkMemoryAllocateFlagBitsKHR Source # 
type Rep VkMemoryAllocateFlagBitsKHR Source # 
type Rep VkMemoryAllocateFlagBitsKHR = D1 (MetaData "VkMemoryAllocateFlagBitsKHR" "Graphics.Vulkan.Types.Enum.Memory" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkMemoryAllocateFlagBitsKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkMemoryAllocateBitmask a Source #

Instances

Bounded (VkMemoryAllocateBitmask FlagMask) Source # 
Enum (VkMemoryAllocateBitmask FlagMask) Source # 
Eq (VkMemoryAllocateBitmask a) Source # 
Integral (VkMemoryAllocateBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkMemoryAllocateBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkMemoryAllocateBitmask a -> c (VkMemoryAllocateBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkMemoryAllocateBitmask a) #

toConstr :: VkMemoryAllocateBitmask a -> Constr #

dataTypeOf :: VkMemoryAllocateBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkMemoryAllocateBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkMemoryAllocateBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkMemoryAllocateBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkMemoryAllocateBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkMemoryAllocateBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkMemoryAllocateBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkMemoryAllocateBitmask a -> m (VkMemoryAllocateBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkMemoryAllocateBitmask a -> m (VkMemoryAllocateBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkMemoryAllocateBitmask a -> m (VkMemoryAllocateBitmask a) #

Num (VkMemoryAllocateBitmask FlagMask) Source # 
Ord (VkMemoryAllocateBitmask a) Source # 
Read (VkMemoryAllocateBitmask a) Source # 
Real (VkMemoryAllocateBitmask FlagMask) Source # 
Show (VkMemoryAllocateBitmask a) Source # 
Generic (VkMemoryAllocateBitmask a) Source # 
Storable (VkMemoryAllocateBitmask a) Source # 
Bits (VkMemoryAllocateBitmask FlagMask) Source # 

Methods

(.&.) :: VkMemoryAllocateBitmask FlagMask -> VkMemoryAllocateBitmask FlagMask -> VkMemoryAllocateBitmask FlagMask #

(.|.) :: VkMemoryAllocateBitmask FlagMask -> VkMemoryAllocateBitmask FlagMask -> VkMemoryAllocateBitmask FlagMask #

xor :: VkMemoryAllocateBitmask FlagMask -> VkMemoryAllocateBitmask FlagMask -> VkMemoryAllocateBitmask FlagMask #

complement :: VkMemoryAllocateBitmask FlagMask -> VkMemoryAllocateBitmask FlagMask #

shift :: VkMemoryAllocateBitmask FlagMask -> Int -> VkMemoryAllocateBitmask FlagMask #

rotate :: VkMemoryAllocateBitmask FlagMask -> Int -> VkMemoryAllocateBitmask FlagMask #

zeroBits :: VkMemoryAllocateBitmask FlagMask #

bit :: Int -> VkMemoryAllocateBitmask FlagMask #

setBit :: VkMemoryAllocateBitmask FlagMask -> Int -> VkMemoryAllocateBitmask FlagMask #

clearBit :: VkMemoryAllocateBitmask FlagMask -> Int -> VkMemoryAllocateBitmask FlagMask #

complementBit :: VkMemoryAllocateBitmask FlagMask -> Int -> VkMemoryAllocateBitmask FlagMask #

testBit :: VkMemoryAllocateBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkMemoryAllocateBitmask FlagMask -> Maybe Int #

bitSize :: VkMemoryAllocateBitmask FlagMask -> Int #

isSigned :: VkMemoryAllocateBitmask FlagMask -> Bool #

shiftL :: VkMemoryAllocateBitmask FlagMask -> Int -> VkMemoryAllocateBitmask FlagMask #

unsafeShiftL :: VkMemoryAllocateBitmask FlagMask -> Int -> VkMemoryAllocateBitmask FlagMask #

shiftR :: VkMemoryAllocateBitmask FlagMask -> Int -> VkMemoryAllocateBitmask FlagMask #

unsafeShiftR :: VkMemoryAllocateBitmask FlagMask -> Int -> VkMemoryAllocateBitmask FlagMask #

rotateL :: VkMemoryAllocateBitmask FlagMask -> Int -> VkMemoryAllocateBitmask FlagMask #

rotateR :: VkMemoryAllocateBitmask FlagMask -> Int -> VkMemoryAllocateBitmask FlagMask #

popCount :: VkMemoryAllocateBitmask FlagMask -> Int #

FiniteBits (VkMemoryAllocateBitmask FlagMask) Source # 
type Rep (VkMemoryAllocateBitmask a) Source # 
type Rep (VkMemoryAllocateBitmask a) = D1 (MetaData "VkMemoryAllocateBitmask" "Graphics.Vulkan.Types.Enum.Memory" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkMemoryAllocateBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

pattern VK_MEMORY_ALLOCATE_DEVICE_MASK_BIT :: forall a. VkMemoryAllocateBitmask a Source #

Force allocation on specific devices

bitpos = 0

newtype VkMemoryHeapBitmask a Source #

Instances

Bounded (VkMemoryHeapBitmask FlagMask) Source # 
Enum (VkMemoryHeapBitmask FlagMask) Source # 
Eq (VkMemoryHeapBitmask a) Source # 
Integral (VkMemoryHeapBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkMemoryHeapBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkMemoryHeapBitmask a -> c (VkMemoryHeapBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkMemoryHeapBitmask a) #

toConstr :: VkMemoryHeapBitmask a -> Constr #

dataTypeOf :: VkMemoryHeapBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkMemoryHeapBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkMemoryHeapBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkMemoryHeapBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkMemoryHeapBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkMemoryHeapBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkMemoryHeapBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkMemoryHeapBitmask a -> m (VkMemoryHeapBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkMemoryHeapBitmask a -> m (VkMemoryHeapBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkMemoryHeapBitmask a -> m (VkMemoryHeapBitmask a) #

Num (VkMemoryHeapBitmask FlagMask) Source # 
Ord (VkMemoryHeapBitmask a) Source # 
Read (VkMemoryHeapBitmask a) Source # 
Real (VkMemoryHeapBitmask FlagMask) Source # 
Show (VkMemoryHeapBitmask a) Source # 
Generic (VkMemoryHeapBitmask a) Source # 

Associated Types

type Rep (VkMemoryHeapBitmask a) :: * -> * #

Storable (VkMemoryHeapBitmask a) Source # 
Bits (VkMemoryHeapBitmask FlagMask) Source # 

Methods

(.&.) :: VkMemoryHeapBitmask FlagMask -> VkMemoryHeapBitmask FlagMask -> VkMemoryHeapBitmask FlagMask #

(.|.) :: VkMemoryHeapBitmask FlagMask -> VkMemoryHeapBitmask FlagMask -> VkMemoryHeapBitmask FlagMask #

xor :: VkMemoryHeapBitmask FlagMask -> VkMemoryHeapBitmask FlagMask -> VkMemoryHeapBitmask FlagMask #

complement :: VkMemoryHeapBitmask FlagMask -> VkMemoryHeapBitmask FlagMask #

shift :: VkMemoryHeapBitmask FlagMask -> Int -> VkMemoryHeapBitmask FlagMask #

rotate :: VkMemoryHeapBitmask FlagMask -> Int -> VkMemoryHeapBitmask FlagMask #

zeroBits :: VkMemoryHeapBitmask FlagMask #

bit :: Int -> VkMemoryHeapBitmask FlagMask #

setBit :: VkMemoryHeapBitmask FlagMask -> Int -> VkMemoryHeapBitmask FlagMask #

clearBit :: VkMemoryHeapBitmask FlagMask -> Int -> VkMemoryHeapBitmask FlagMask #

complementBit :: VkMemoryHeapBitmask FlagMask -> Int -> VkMemoryHeapBitmask FlagMask #

testBit :: VkMemoryHeapBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkMemoryHeapBitmask FlagMask -> Maybe Int #

bitSize :: VkMemoryHeapBitmask FlagMask -> Int #

isSigned :: VkMemoryHeapBitmask FlagMask -> Bool #

shiftL :: VkMemoryHeapBitmask FlagMask -> Int -> VkMemoryHeapBitmask FlagMask #

unsafeShiftL :: VkMemoryHeapBitmask FlagMask -> Int -> VkMemoryHeapBitmask FlagMask #

shiftR :: VkMemoryHeapBitmask FlagMask -> Int -> VkMemoryHeapBitmask FlagMask #

unsafeShiftR :: VkMemoryHeapBitmask FlagMask -> Int -> VkMemoryHeapBitmask FlagMask #

rotateL :: VkMemoryHeapBitmask FlagMask -> Int -> VkMemoryHeapBitmask FlagMask #

rotateR :: VkMemoryHeapBitmask FlagMask -> Int -> VkMemoryHeapBitmask FlagMask #

popCount :: VkMemoryHeapBitmask FlagMask -> Int #

FiniteBits (VkMemoryHeapBitmask FlagMask) Source # 
type Rep (VkMemoryHeapBitmask a) Source # 
type Rep (VkMemoryHeapBitmask a) = D1 (MetaData "VkMemoryHeapBitmask" "Graphics.Vulkan.Types.Enum.Memory" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkMemoryHeapBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

pattern VK_MEMORY_HEAP_DEVICE_LOCAL_BIT :: forall a. VkMemoryHeapBitmask a Source #

If set, heap represents device memory

bitpos = 0

newtype VkMemoryPropertyBitmask a Source #

Instances

Bounded (VkMemoryPropertyBitmask FlagMask) Source # 
Enum (VkMemoryPropertyBitmask FlagMask) Source # 
Eq (VkMemoryPropertyBitmask a) Source # 
Integral (VkMemoryPropertyBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkMemoryPropertyBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkMemoryPropertyBitmask a -> c (VkMemoryPropertyBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkMemoryPropertyBitmask a) #

toConstr :: VkMemoryPropertyBitmask a -> Constr #

dataTypeOf :: VkMemoryPropertyBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkMemoryPropertyBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkMemoryPropertyBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkMemoryPropertyBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkMemoryPropertyBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkMemoryPropertyBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkMemoryPropertyBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkMemoryPropertyBitmask a -> m (VkMemoryPropertyBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkMemoryPropertyBitmask a -> m (VkMemoryPropertyBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkMemoryPropertyBitmask a -> m (VkMemoryPropertyBitmask a) #

Num (VkMemoryPropertyBitmask FlagMask) Source # 
Ord (VkMemoryPropertyBitmask a) Source # 
Read (VkMemoryPropertyBitmask a) Source # 
Real (VkMemoryPropertyBitmask FlagMask) Source # 
Show (VkMemoryPropertyBitmask a) Source # 
Generic (VkMemoryPropertyBitmask a) Source # 
Storable (VkMemoryPropertyBitmask a) Source # 
Bits (VkMemoryPropertyBitmask FlagMask) Source # 

Methods

(.&.) :: VkMemoryPropertyBitmask FlagMask -> VkMemoryPropertyBitmask FlagMask -> VkMemoryPropertyBitmask FlagMask #

(.|.) :: VkMemoryPropertyBitmask FlagMask -> VkMemoryPropertyBitmask FlagMask -> VkMemoryPropertyBitmask FlagMask #

xor :: VkMemoryPropertyBitmask FlagMask -> VkMemoryPropertyBitmask FlagMask -> VkMemoryPropertyBitmask FlagMask #

complement :: VkMemoryPropertyBitmask FlagMask -> VkMemoryPropertyBitmask FlagMask #

shift :: VkMemoryPropertyBitmask FlagMask -> Int -> VkMemoryPropertyBitmask FlagMask #

rotate :: VkMemoryPropertyBitmask FlagMask -> Int -> VkMemoryPropertyBitmask FlagMask #

zeroBits :: VkMemoryPropertyBitmask FlagMask #

bit :: Int -> VkMemoryPropertyBitmask FlagMask #

setBit :: VkMemoryPropertyBitmask FlagMask -> Int -> VkMemoryPropertyBitmask FlagMask #

clearBit :: VkMemoryPropertyBitmask FlagMask -> Int -> VkMemoryPropertyBitmask FlagMask #

complementBit :: VkMemoryPropertyBitmask FlagMask -> Int -> VkMemoryPropertyBitmask FlagMask #

testBit :: VkMemoryPropertyBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkMemoryPropertyBitmask FlagMask -> Maybe Int #

bitSize :: VkMemoryPropertyBitmask FlagMask -> Int #

isSigned :: VkMemoryPropertyBitmask FlagMask -> Bool #

shiftL :: VkMemoryPropertyBitmask FlagMask -> Int -> VkMemoryPropertyBitmask FlagMask #

unsafeShiftL :: VkMemoryPropertyBitmask FlagMask -> Int -> VkMemoryPropertyBitmask FlagMask #

shiftR :: VkMemoryPropertyBitmask FlagMask -> Int -> VkMemoryPropertyBitmask FlagMask #

unsafeShiftR :: VkMemoryPropertyBitmask FlagMask -> Int -> VkMemoryPropertyBitmask FlagMask #

rotateL :: VkMemoryPropertyBitmask FlagMask -> Int -> VkMemoryPropertyBitmask FlagMask #

rotateR :: VkMemoryPropertyBitmask FlagMask -> Int -> VkMemoryPropertyBitmask FlagMask #

popCount :: VkMemoryPropertyBitmask FlagMask -> Int #

FiniteBits (VkMemoryPropertyBitmask FlagMask) Source # 
type Rep (VkMemoryPropertyBitmask a) Source # 
type Rep (VkMemoryPropertyBitmask a) = D1 (MetaData "VkMemoryPropertyBitmask" "Graphics.Vulkan.Types.Enum.Memory" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkMemoryPropertyBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

pattern VK_MEMORY_PROPERTY_DEVICE_LOCAL_BIT :: forall a. VkMemoryPropertyBitmask a Source #

If otherwise stated, then allocate memory on device

bitpos = 0

pattern VK_MEMORY_PROPERTY_HOST_VISIBLE_BIT :: forall a. VkMemoryPropertyBitmask a Source #

Memory is mappable by host

bitpos = 1

pattern VK_MEMORY_PROPERTY_HOST_COHERENT_BIT :: forall a. VkMemoryPropertyBitmask a Source #

Memory will have io coherency. If not set, application may need to use vkFlushMappedMemoryRanges and vkInvalidateMappedMemoryRanges to flushinvalidate host cache

bitpos = 2

pattern VK_MEMORY_PROPERTY_HOST_CACHED_BIT :: forall a. VkMemoryPropertyBitmask a Source #

Memory will be cached by the host

bitpos = 3

pattern VK_MEMORY_PROPERTY_LAZILY_ALLOCATED_BIT :: forall a. VkMemoryPropertyBitmask a Source #

Memory may be allocated by the driver when it is required

bitpos = 4

data VkOffset2D Source #

typedef struct VkOffset2D {
    int32_t        x;
    int32_t        y;
} VkOffset2D;

VkOffset2D registry at www.khronos.org

Instances

Eq VkOffset2D Source # 
Ord VkOffset2D Source # 
Show VkOffset2D Source # 
Storable VkOffset2D Source # 
VulkanMarshalPrim VkOffset2D Source # 
VulkanMarshal VkOffset2D Source # 
CanWriteField "x" VkOffset2D Source # 
CanWriteField "y" VkOffset2D Source # 
CanReadField "x" VkOffset2D Source # 
CanReadField "y" VkOffset2D Source # 
HasField "x" VkOffset2D Source # 
HasField "y" VkOffset2D Source # 
type StructFields VkOffset2D Source # 
type StructFields VkOffset2D = (:) Symbol "x" ((:) Symbol "y" ([] Symbol))
type CUnionType VkOffset2D Source # 
type ReturnedOnly VkOffset2D Source # 
type StructExtends VkOffset2D Source # 
type FieldType "x" VkOffset2D Source # 
type FieldType "y" VkOffset2D Source # 
type FieldOptional "x" VkOffset2D Source # 
type FieldOptional "y" VkOffset2D Source # 
type FieldOffset "x" VkOffset2D Source # 
type FieldOffset "x" VkOffset2D = 0
type FieldOffset "y" VkOffset2D Source # 
type FieldOffset "y" VkOffset2D = 4
type FieldIsArray "x" VkOffset2D Source # 
type FieldIsArray "y" VkOffset2D Source # 

data VkOffset3D Source #

typedef struct VkOffset3D {
    int32_t        x;
    int32_t        y;
    int32_t        z;
} VkOffset3D;

VkOffset3D registry at www.khronos.org

Instances

Eq VkOffset3D Source # 
Ord VkOffset3D Source # 
Show VkOffset3D Source # 
Storable VkOffset3D Source # 
VulkanMarshalPrim VkOffset3D Source # 
VulkanMarshal VkOffset3D Source # 
CanWriteField "x" VkOffset3D Source # 
CanWriteField "y" VkOffset3D Source # 
CanWriteField "z" VkOffset3D Source # 
CanReadField "x" VkOffset3D Source # 
CanReadField "y" VkOffset3D Source # 
CanReadField "z" VkOffset3D Source # 
HasField "x" VkOffset3D Source # 
HasField "y" VkOffset3D Source # 
HasField "z" VkOffset3D Source # 
type StructFields VkOffset3D Source # 
type StructFields VkOffset3D = (:) Symbol "x" ((:) Symbol "y" ((:) Symbol "z" ([] Symbol)))
type CUnionType VkOffset3D Source # 
type ReturnedOnly VkOffset3D Source # 
type StructExtends VkOffset3D Source # 
type FieldType "x" VkOffset3D Source # 
type FieldType "y" VkOffset3D Source # 
type FieldType "z" VkOffset3D Source # 
type FieldOptional "x" VkOffset3D Source # 
type FieldOptional "y" VkOffset3D Source # 
type FieldOptional "z" VkOffset3D Source # 
type FieldOffset "x" VkOffset3D Source # 
type FieldOffset "x" VkOffset3D = 0
type FieldOffset "y" VkOffset3D Source # 
type FieldOffset "y" VkOffset3D = 4
type FieldOffset "z" VkOffset3D Source # 
type FieldOffset "z" VkOffset3D = 8
type FieldIsArray "x" VkOffset3D Source # 
type FieldIsArray "y" VkOffset3D Source # 
type FieldIsArray "z" VkOffset3D Source # 

newtype VkPeerMemoryFeatureFlagBitsKHR Source #

Instances

Bounded VkPeerMemoryFeatureFlagBitsKHR Source # 
Enum VkPeerMemoryFeatureFlagBitsKHR Source # 
Eq VkPeerMemoryFeatureFlagBitsKHR Source # 
Integral VkPeerMemoryFeatureFlagBitsKHR Source # 
Data VkPeerMemoryFeatureFlagBitsKHR Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkPeerMemoryFeatureFlagBitsKHR -> c VkPeerMemoryFeatureFlagBitsKHR #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkPeerMemoryFeatureFlagBitsKHR #

toConstr :: VkPeerMemoryFeatureFlagBitsKHR -> Constr #

dataTypeOf :: VkPeerMemoryFeatureFlagBitsKHR -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkPeerMemoryFeatureFlagBitsKHR) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkPeerMemoryFeatureFlagBitsKHR) #

gmapT :: (forall b. Data b => b -> b) -> VkPeerMemoryFeatureFlagBitsKHR -> VkPeerMemoryFeatureFlagBitsKHR #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkPeerMemoryFeatureFlagBitsKHR -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkPeerMemoryFeatureFlagBitsKHR -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkPeerMemoryFeatureFlagBitsKHR -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkPeerMemoryFeatureFlagBitsKHR -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkPeerMemoryFeatureFlagBitsKHR -> m VkPeerMemoryFeatureFlagBitsKHR #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPeerMemoryFeatureFlagBitsKHR -> m VkPeerMemoryFeatureFlagBitsKHR #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPeerMemoryFeatureFlagBitsKHR -> m VkPeerMemoryFeatureFlagBitsKHR #

Num VkPeerMemoryFeatureFlagBitsKHR Source # 
Ord VkPeerMemoryFeatureFlagBitsKHR Source # 
Read VkPeerMemoryFeatureFlagBitsKHR Source # 
Real VkPeerMemoryFeatureFlagBitsKHR Source # 
Show VkPeerMemoryFeatureFlagBitsKHR Source # 
Generic VkPeerMemoryFeatureFlagBitsKHR Source # 
Storable VkPeerMemoryFeatureFlagBitsKHR Source # 
Bits VkPeerMemoryFeatureFlagBitsKHR Source # 

Methods

(.&.) :: VkPeerMemoryFeatureFlagBitsKHR -> VkPeerMemoryFeatureFlagBitsKHR -> VkPeerMemoryFeatureFlagBitsKHR #

(.|.) :: VkPeerMemoryFeatureFlagBitsKHR -> VkPeerMemoryFeatureFlagBitsKHR -> VkPeerMemoryFeatureFlagBitsKHR #

xor :: VkPeerMemoryFeatureFlagBitsKHR -> VkPeerMemoryFeatureFlagBitsKHR -> VkPeerMemoryFeatureFlagBitsKHR #

complement :: VkPeerMemoryFeatureFlagBitsKHR -> VkPeerMemoryFeatureFlagBitsKHR #

shift :: VkPeerMemoryFeatureFlagBitsKHR -> Int -> VkPeerMemoryFeatureFlagBitsKHR #

rotate :: VkPeerMemoryFeatureFlagBitsKHR -> Int -> VkPeerMemoryFeatureFlagBitsKHR #

zeroBits :: VkPeerMemoryFeatureFlagBitsKHR #

bit :: Int -> VkPeerMemoryFeatureFlagBitsKHR #

setBit :: VkPeerMemoryFeatureFlagBitsKHR -> Int -> VkPeerMemoryFeatureFlagBitsKHR #

clearBit :: VkPeerMemoryFeatureFlagBitsKHR -> Int -> VkPeerMemoryFeatureFlagBitsKHR #

complementBit :: VkPeerMemoryFeatureFlagBitsKHR -> Int -> VkPeerMemoryFeatureFlagBitsKHR #

testBit :: VkPeerMemoryFeatureFlagBitsKHR -> Int -> Bool #

bitSizeMaybe :: VkPeerMemoryFeatureFlagBitsKHR -> Maybe Int #

bitSize :: VkPeerMemoryFeatureFlagBitsKHR -> Int #

isSigned :: VkPeerMemoryFeatureFlagBitsKHR -> Bool #

shiftL :: VkPeerMemoryFeatureFlagBitsKHR -> Int -> VkPeerMemoryFeatureFlagBitsKHR #

unsafeShiftL :: VkPeerMemoryFeatureFlagBitsKHR -> Int -> VkPeerMemoryFeatureFlagBitsKHR #

shiftR :: VkPeerMemoryFeatureFlagBitsKHR -> Int -> VkPeerMemoryFeatureFlagBitsKHR #

unsafeShiftR :: VkPeerMemoryFeatureFlagBitsKHR -> Int -> VkPeerMemoryFeatureFlagBitsKHR #

rotateL :: VkPeerMemoryFeatureFlagBitsKHR -> Int -> VkPeerMemoryFeatureFlagBitsKHR #

rotateR :: VkPeerMemoryFeatureFlagBitsKHR -> Int -> VkPeerMemoryFeatureFlagBitsKHR #

popCount :: VkPeerMemoryFeatureFlagBitsKHR -> Int #

FiniteBits VkPeerMemoryFeatureFlagBitsKHR Source # 
type Rep VkPeerMemoryFeatureFlagBitsKHR Source # 
type Rep VkPeerMemoryFeatureFlagBitsKHR = D1 (MetaData "VkPeerMemoryFeatureFlagBitsKHR" "Graphics.Vulkan.Types.Enum.PeerMemoryFeatureFlag" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkPeerMemoryFeatureFlagBitsKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkPeerMemoryFeatureBitmask a Source #

Instances

Bounded (VkPeerMemoryFeatureBitmask FlagMask) Source # 
Enum (VkPeerMemoryFeatureBitmask FlagMask) Source # 
Eq (VkPeerMemoryFeatureBitmask a) Source # 
Integral (VkPeerMemoryFeatureBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkPeerMemoryFeatureBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkPeerMemoryFeatureBitmask a -> c (VkPeerMemoryFeatureBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkPeerMemoryFeatureBitmask a) #

toConstr :: VkPeerMemoryFeatureBitmask a -> Constr #

dataTypeOf :: VkPeerMemoryFeatureBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkPeerMemoryFeatureBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkPeerMemoryFeatureBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkPeerMemoryFeatureBitmask a -> VkPeerMemoryFeatureBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkPeerMemoryFeatureBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkPeerMemoryFeatureBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkPeerMemoryFeatureBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkPeerMemoryFeatureBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkPeerMemoryFeatureBitmask a -> m (VkPeerMemoryFeatureBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPeerMemoryFeatureBitmask a -> m (VkPeerMemoryFeatureBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPeerMemoryFeatureBitmask a -> m (VkPeerMemoryFeatureBitmask a) #

Num (VkPeerMemoryFeatureBitmask FlagMask) Source # 
Ord (VkPeerMemoryFeatureBitmask a) Source # 
Read (VkPeerMemoryFeatureBitmask a) Source # 
Real (VkPeerMemoryFeatureBitmask FlagMask) Source # 
Show (VkPeerMemoryFeatureBitmask a) Source # 
Generic (VkPeerMemoryFeatureBitmask a) Source # 
Storable (VkPeerMemoryFeatureBitmask a) Source # 
Bits (VkPeerMemoryFeatureBitmask FlagMask) Source # 

Methods

(.&.) :: VkPeerMemoryFeatureBitmask FlagMask -> VkPeerMemoryFeatureBitmask FlagMask -> VkPeerMemoryFeatureBitmask FlagMask #

(.|.) :: VkPeerMemoryFeatureBitmask FlagMask -> VkPeerMemoryFeatureBitmask FlagMask -> VkPeerMemoryFeatureBitmask FlagMask #

xor :: VkPeerMemoryFeatureBitmask FlagMask -> VkPeerMemoryFeatureBitmask FlagMask -> VkPeerMemoryFeatureBitmask FlagMask #

complement :: VkPeerMemoryFeatureBitmask FlagMask -> VkPeerMemoryFeatureBitmask FlagMask #

shift :: VkPeerMemoryFeatureBitmask FlagMask -> Int -> VkPeerMemoryFeatureBitmask FlagMask #

rotate :: VkPeerMemoryFeatureBitmask FlagMask -> Int -> VkPeerMemoryFeatureBitmask FlagMask #

zeroBits :: VkPeerMemoryFeatureBitmask FlagMask #

bit :: Int -> VkPeerMemoryFeatureBitmask FlagMask #

setBit :: VkPeerMemoryFeatureBitmask FlagMask -> Int -> VkPeerMemoryFeatureBitmask FlagMask #

clearBit :: VkPeerMemoryFeatureBitmask FlagMask -> Int -> VkPeerMemoryFeatureBitmask FlagMask #

complementBit :: VkPeerMemoryFeatureBitmask FlagMask -> Int -> VkPeerMemoryFeatureBitmask FlagMask #

testBit :: VkPeerMemoryFeatureBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkPeerMemoryFeatureBitmask FlagMask -> Maybe Int #

bitSize :: VkPeerMemoryFeatureBitmask FlagMask -> Int #

isSigned :: VkPeerMemoryFeatureBitmask FlagMask -> Bool #

shiftL :: VkPeerMemoryFeatureBitmask FlagMask -> Int -> VkPeerMemoryFeatureBitmask FlagMask #

unsafeShiftL :: VkPeerMemoryFeatureBitmask FlagMask -> Int -> VkPeerMemoryFeatureBitmask FlagMask #

shiftR :: VkPeerMemoryFeatureBitmask FlagMask -> Int -> VkPeerMemoryFeatureBitmask FlagMask #

unsafeShiftR :: VkPeerMemoryFeatureBitmask FlagMask -> Int -> VkPeerMemoryFeatureBitmask FlagMask #

rotateL :: VkPeerMemoryFeatureBitmask FlagMask -> Int -> VkPeerMemoryFeatureBitmask FlagMask #

rotateR :: VkPeerMemoryFeatureBitmask FlagMask -> Int -> VkPeerMemoryFeatureBitmask FlagMask #

popCount :: VkPeerMemoryFeatureBitmask FlagMask -> Int #

FiniteBits (VkPeerMemoryFeatureBitmask FlagMask) Source # 
type Rep (VkPeerMemoryFeatureBitmask a) Source # 
type Rep (VkPeerMemoryFeatureBitmask a) = D1 (MetaData "VkPeerMemoryFeatureBitmask" "Graphics.Vulkan.Types.Enum.PeerMemoryFeatureFlag" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkPeerMemoryFeatureBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

pattern VK_PEER_MEMORY_FEATURE_COPY_SRC_BIT :: forall a. VkPeerMemoryFeatureBitmask a Source #

Can read with vkCmdCopy commands

bitpos = 0

pattern VK_PEER_MEMORY_FEATURE_COPY_DST_BIT :: forall a. VkPeerMemoryFeatureBitmask a Source #

Can write with vkCmdCopy commands

bitpos = 1

pattern VK_PEER_MEMORY_FEATURE_GENERIC_SRC_BIT :: forall a. VkPeerMemoryFeatureBitmask a Source #

Can read with any access type/command

bitpos = 2

pattern VK_PEER_MEMORY_FEATURE_GENERIC_DST_BIT :: forall a. VkPeerMemoryFeatureBitmask a Source #

Can write with and access type/command

bitpos = 3

newtype VkPipelineBindPoint Source #

Instances

Bounded VkPipelineBindPoint Source # 
Enum VkPipelineBindPoint Source # 
Eq VkPipelineBindPoint Source # 
Data VkPipelineBindPoint Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkPipelineBindPoint -> c VkPipelineBindPoint #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkPipelineBindPoint #

toConstr :: VkPipelineBindPoint -> Constr #

dataTypeOf :: VkPipelineBindPoint -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkPipelineBindPoint) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkPipelineBindPoint) #

gmapT :: (forall b. Data b => b -> b) -> VkPipelineBindPoint -> VkPipelineBindPoint #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineBindPoint -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineBindPoint -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkPipelineBindPoint -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkPipelineBindPoint -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkPipelineBindPoint -> m VkPipelineBindPoint #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineBindPoint -> m VkPipelineBindPoint #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineBindPoint -> m VkPipelineBindPoint #

Num VkPipelineBindPoint Source # 
Ord VkPipelineBindPoint Source # 
Read VkPipelineBindPoint Source # 
Show VkPipelineBindPoint Source # 
Generic VkPipelineBindPoint Source # 
Storable VkPipelineBindPoint Source # 
type Rep VkPipelineBindPoint Source # 
type Rep VkPipelineBindPoint = D1 (MetaData "VkPipelineBindPoint" "Graphics.Vulkan.Types.Enum.Pipeline" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkPipelineBindPoint" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

newtype VkPipelineCacheCreateFlagBits Source #

Instances

Bounded VkPipelineCacheCreateFlagBits Source # 
Enum VkPipelineCacheCreateFlagBits Source # 
Eq VkPipelineCacheCreateFlagBits Source # 
Integral VkPipelineCacheCreateFlagBits Source # 
Data VkPipelineCacheCreateFlagBits Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkPipelineCacheCreateFlagBits -> c VkPipelineCacheCreateFlagBits #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkPipelineCacheCreateFlagBits #

toConstr :: VkPipelineCacheCreateFlagBits -> Constr #

dataTypeOf :: VkPipelineCacheCreateFlagBits -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkPipelineCacheCreateFlagBits) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkPipelineCacheCreateFlagBits) #

gmapT :: (forall b. Data b => b -> b) -> VkPipelineCacheCreateFlagBits -> VkPipelineCacheCreateFlagBits #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineCacheCreateFlagBits -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineCacheCreateFlagBits -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkPipelineCacheCreateFlagBits -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkPipelineCacheCreateFlagBits -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkPipelineCacheCreateFlagBits -> m VkPipelineCacheCreateFlagBits #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineCacheCreateFlagBits -> m VkPipelineCacheCreateFlagBits #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineCacheCreateFlagBits -> m VkPipelineCacheCreateFlagBits #

Num VkPipelineCacheCreateFlagBits Source # 
Ord VkPipelineCacheCreateFlagBits Source # 
Read VkPipelineCacheCreateFlagBits Source # 
Real VkPipelineCacheCreateFlagBits Source # 
Show VkPipelineCacheCreateFlagBits Source # 
Generic VkPipelineCacheCreateFlagBits Source # 
Storable VkPipelineCacheCreateFlagBits Source # 
Bits VkPipelineCacheCreateFlagBits Source # 

Methods

(.&.) :: VkPipelineCacheCreateFlagBits -> VkPipelineCacheCreateFlagBits -> VkPipelineCacheCreateFlagBits #

(.|.) :: VkPipelineCacheCreateFlagBits -> VkPipelineCacheCreateFlagBits -> VkPipelineCacheCreateFlagBits #

xor :: VkPipelineCacheCreateFlagBits -> VkPipelineCacheCreateFlagBits -> VkPipelineCacheCreateFlagBits #

complement :: VkPipelineCacheCreateFlagBits -> VkPipelineCacheCreateFlagBits #

shift :: VkPipelineCacheCreateFlagBits -> Int -> VkPipelineCacheCreateFlagBits #

rotate :: VkPipelineCacheCreateFlagBits -> Int -> VkPipelineCacheCreateFlagBits #

zeroBits :: VkPipelineCacheCreateFlagBits #

bit :: Int -> VkPipelineCacheCreateFlagBits #

setBit :: VkPipelineCacheCreateFlagBits -> Int -> VkPipelineCacheCreateFlagBits #

clearBit :: VkPipelineCacheCreateFlagBits -> Int -> VkPipelineCacheCreateFlagBits #

complementBit :: VkPipelineCacheCreateFlagBits -> Int -> VkPipelineCacheCreateFlagBits #

testBit :: VkPipelineCacheCreateFlagBits -> Int -> Bool #

bitSizeMaybe :: VkPipelineCacheCreateFlagBits -> Maybe Int #

bitSize :: VkPipelineCacheCreateFlagBits -> Int #

isSigned :: VkPipelineCacheCreateFlagBits -> Bool #

shiftL :: VkPipelineCacheCreateFlagBits -> Int -> VkPipelineCacheCreateFlagBits #

unsafeShiftL :: VkPipelineCacheCreateFlagBits -> Int -> VkPipelineCacheCreateFlagBits #

shiftR :: VkPipelineCacheCreateFlagBits -> Int -> VkPipelineCacheCreateFlagBits #

unsafeShiftR :: VkPipelineCacheCreateFlagBits -> Int -> VkPipelineCacheCreateFlagBits #

rotateL :: VkPipelineCacheCreateFlagBits -> Int -> VkPipelineCacheCreateFlagBits #

rotateR :: VkPipelineCacheCreateFlagBits -> Int -> VkPipelineCacheCreateFlagBits #

popCount :: VkPipelineCacheCreateFlagBits -> Int #

FiniteBits VkPipelineCacheCreateFlagBits Source # 
type Rep VkPipelineCacheCreateFlagBits Source # 
type Rep VkPipelineCacheCreateFlagBits = D1 (MetaData "VkPipelineCacheCreateFlagBits" "Graphics.Vulkan.Types.Enum.Pipeline" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkPipelineCacheCreateFlagBits" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkPipelineCacheHeaderVersion Source #

Instances

Bounded VkPipelineCacheHeaderVersion Source # 
Enum VkPipelineCacheHeaderVersion Source # 
Eq VkPipelineCacheHeaderVersion Source # 
Data VkPipelineCacheHeaderVersion Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkPipelineCacheHeaderVersion -> c VkPipelineCacheHeaderVersion #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkPipelineCacheHeaderVersion #

toConstr :: VkPipelineCacheHeaderVersion -> Constr #

dataTypeOf :: VkPipelineCacheHeaderVersion -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkPipelineCacheHeaderVersion) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkPipelineCacheHeaderVersion) #

gmapT :: (forall b. Data b => b -> b) -> VkPipelineCacheHeaderVersion -> VkPipelineCacheHeaderVersion #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineCacheHeaderVersion -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineCacheHeaderVersion -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkPipelineCacheHeaderVersion -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkPipelineCacheHeaderVersion -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkPipelineCacheHeaderVersion -> m VkPipelineCacheHeaderVersion #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineCacheHeaderVersion -> m VkPipelineCacheHeaderVersion #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineCacheHeaderVersion -> m VkPipelineCacheHeaderVersion #

Num VkPipelineCacheHeaderVersion Source # 
Ord VkPipelineCacheHeaderVersion Source # 
Read VkPipelineCacheHeaderVersion Source # 
Show VkPipelineCacheHeaderVersion Source # 
Generic VkPipelineCacheHeaderVersion Source # 
Storable VkPipelineCacheHeaderVersion Source # 
type Rep VkPipelineCacheHeaderVersion Source # 
type Rep VkPipelineCacheHeaderVersion = D1 (MetaData "VkPipelineCacheHeaderVersion" "Graphics.Vulkan.Types.Enum.Pipeline" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkPipelineCacheHeaderVersion" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

newtype VkPipelineColorBlendStateCreateFlagBits Source #

Instances

Bounded VkPipelineColorBlendStateCreateFlagBits Source # 
Enum VkPipelineColorBlendStateCreateFlagBits Source # 
Eq VkPipelineColorBlendStateCreateFlagBits Source # 
Integral VkPipelineColorBlendStateCreateFlagBits Source # 
Data VkPipelineColorBlendStateCreateFlagBits Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkPipelineColorBlendStateCreateFlagBits -> c VkPipelineColorBlendStateCreateFlagBits #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkPipelineColorBlendStateCreateFlagBits #

toConstr :: VkPipelineColorBlendStateCreateFlagBits -> Constr #

dataTypeOf :: VkPipelineColorBlendStateCreateFlagBits -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkPipelineColorBlendStateCreateFlagBits) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkPipelineColorBlendStateCreateFlagBits) #

gmapT :: (forall b. Data b => b -> b) -> VkPipelineColorBlendStateCreateFlagBits -> VkPipelineColorBlendStateCreateFlagBits #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineColorBlendStateCreateFlagBits -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineColorBlendStateCreateFlagBits -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkPipelineColorBlendStateCreateFlagBits -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkPipelineColorBlendStateCreateFlagBits -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkPipelineColorBlendStateCreateFlagBits -> m VkPipelineColorBlendStateCreateFlagBits #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineColorBlendStateCreateFlagBits -> m VkPipelineColorBlendStateCreateFlagBits #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineColorBlendStateCreateFlagBits -> m VkPipelineColorBlendStateCreateFlagBits #

Num VkPipelineColorBlendStateCreateFlagBits Source # 
Ord VkPipelineColorBlendStateCreateFlagBits Source # 
Read VkPipelineColorBlendStateCreateFlagBits Source # 
Real VkPipelineColorBlendStateCreateFlagBits Source # 
Show VkPipelineColorBlendStateCreateFlagBits Source # 
Generic VkPipelineColorBlendStateCreateFlagBits Source # 
Storable VkPipelineColorBlendStateCreateFlagBits Source # 
Bits VkPipelineColorBlendStateCreateFlagBits Source # 

Methods

(.&.) :: VkPipelineColorBlendStateCreateFlagBits -> VkPipelineColorBlendStateCreateFlagBits -> VkPipelineColorBlendStateCreateFlagBits #

(.|.) :: VkPipelineColorBlendStateCreateFlagBits -> VkPipelineColorBlendStateCreateFlagBits -> VkPipelineColorBlendStateCreateFlagBits #

xor :: VkPipelineColorBlendStateCreateFlagBits -> VkPipelineColorBlendStateCreateFlagBits -> VkPipelineColorBlendStateCreateFlagBits #

complement :: VkPipelineColorBlendStateCreateFlagBits -> VkPipelineColorBlendStateCreateFlagBits #

shift :: VkPipelineColorBlendStateCreateFlagBits -> Int -> VkPipelineColorBlendStateCreateFlagBits #

rotate :: VkPipelineColorBlendStateCreateFlagBits -> Int -> VkPipelineColorBlendStateCreateFlagBits #

zeroBits :: VkPipelineColorBlendStateCreateFlagBits #

bit :: Int -> VkPipelineColorBlendStateCreateFlagBits #

setBit :: VkPipelineColorBlendStateCreateFlagBits -> Int -> VkPipelineColorBlendStateCreateFlagBits #

clearBit :: VkPipelineColorBlendStateCreateFlagBits -> Int -> VkPipelineColorBlendStateCreateFlagBits #

complementBit :: VkPipelineColorBlendStateCreateFlagBits -> Int -> VkPipelineColorBlendStateCreateFlagBits #

testBit :: VkPipelineColorBlendStateCreateFlagBits -> Int -> Bool #

bitSizeMaybe :: VkPipelineColorBlendStateCreateFlagBits -> Maybe Int #

bitSize :: VkPipelineColorBlendStateCreateFlagBits -> Int #

isSigned :: VkPipelineColorBlendStateCreateFlagBits -> Bool #

shiftL :: VkPipelineColorBlendStateCreateFlagBits -> Int -> VkPipelineColorBlendStateCreateFlagBits #

unsafeShiftL :: VkPipelineColorBlendStateCreateFlagBits -> Int -> VkPipelineColorBlendStateCreateFlagBits #

shiftR :: VkPipelineColorBlendStateCreateFlagBits -> Int -> VkPipelineColorBlendStateCreateFlagBits #

unsafeShiftR :: VkPipelineColorBlendStateCreateFlagBits -> Int -> VkPipelineColorBlendStateCreateFlagBits #

rotateL :: VkPipelineColorBlendStateCreateFlagBits -> Int -> VkPipelineColorBlendStateCreateFlagBits #

rotateR :: VkPipelineColorBlendStateCreateFlagBits -> Int -> VkPipelineColorBlendStateCreateFlagBits #

popCount :: VkPipelineColorBlendStateCreateFlagBits -> Int #

FiniteBits VkPipelineColorBlendStateCreateFlagBits Source # 
type Rep VkPipelineColorBlendStateCreateFlagBits Source # 
type Rep VkPipelineColorBlendStateCreateFlagBits = D1 (MetaData "VkPipelineColorBlendStateCreateFlagBits" "Graphics.Vulkan.Types.Enum.Pipeline" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkPipelineColorBlendStateCreateFlagBits" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkPipelineCreateBitmask a Source #

Instances

Bounded (VkPipelineCreateBitmask FlagMask) Source # 
Enum (VkPipelineCreateBitmask FlagMask) Source # 
Eq (VkPipelineCreateBitmask a) Source # 
Integral (VkPipelineCreateBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkPipelineCreateBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkPipelineCreateBitmask a -> c (VkPipelineCreateBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkPipelineCreateBitmask a) #

toConstr :: VkPipelineCreateBitmask a -> Constr #

dataTypeOf :: VkPipelineCreateBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkPipelineCreateBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkPipelineCreateBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkPipelineCreateBitmask a -> VkPipelineCreateBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineCreateBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineCreateBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkPipelineCreateBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkPipelineCreateBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkPipelineCreateBitmask a -> m (VkPipelineCreateBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineCreateBitmask a -> m (VkPipelineCreateBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineCreateBitmask a -> m (VkPipelineCreateBitmask a) #

Num (VkPipelineCreateBitmask FlagMask) Source # 
Ord (VkPipelineCreateBitmask a) Source # 
Read (VkPipelineCreateBitmask a) Source # 
Real (VkPipelineCreateBitmask FlagMask) Source # 
Show (VkPipelineCreateBitmask a) Source # 
Generic (VkPipelineCreateBitmask a) Source # 
Storable (VkPipelineCreateBitmask a) Source # 
Bits (VkPipelineCreateBitmask FlagMask) Source # 

Methods

(.&.) :: VkPipelineCreateBitmask FlagMask -> VkPipelineCreateBitmask FlagMask -> VkPipelineCreateBitmask FlagMask #

(.|.) :: VkPipelineCreateBitmask FlagMask -> VkPipelineCreateBitmask FlagMask -> VkPipelineCreateBitmask FlagMask #

xor :: VkPipelineCreateBitmask FlagMask -> VkPipelineCreateBitmask FlagMask -> VkPipelineCreateBitmask FlagMask #

complement :: VkPipelineCreateBitmask FlagMask -> VkPipelineCreateBitmask FlagMask #

shift :: VkPipelineCreateBitmask FlagMask -> Int -> VkPipelineCreateBitmask FlagMask #

rotate :: VkPipelineCreateBitmask FlagMask -> Int -> VkPipelineCreateBitmask FlagMask #

zeroBits :: VkPipelineCreateBitmask FlagMask #

bit :: Int -> VkPipelineCreateBitmask FlagMask #

setBit :: VkPipelineCreateBitmask FlagMask -> Int -> VkPipelineCreateBitmask FlagMask #

clearBit :: VkPipelineCreateBitmask FlagMask -> Int -> VkPipelineCreateBitmask FlagMask #

complementBit :: VkPipelineCreateBitmask FlagMask -> Int -> VkPipelineCreateBitmask FlagMask #

testBit :: VkPipelineCreateBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkPipelineCreateBitmask FlagMask -> Maybe Int #

bitSize :: VkPipelineCreateBitmask FlagMask -> Int #

isSigned :: VkPipelineCreateBitmask FlagMask -> Bool #

shiftL :: VkPipelineCreateBitmask FlagMask -> Int -> VkPipelineCreateBitmask FlagMask #

unsafeShiftL :: VkPipelineCreateBitmask FlagMask -> Int -> VkPipelineCreateBitmask FlagMask #

shiftR :: VkPipelineCreateBitmask FlagMask -> Int -> VkPipelineCreateBitmask FlagMask #

unsafeShiftR :: VkPipelineCreateBitmask FlagMask -> Int -> VkPipelineCreateBitmask FlagMask #

rotateL :: VkPipelineCreateBitmask FlagMask -> Int -> VkPipelineCreateBitmask FlagMask #

rotateR :: VkPipelineCreateBitmask FlagMask -> Int -> VkPipelineCreateBitmask FlagMask #

popCount :: VkPipelineCreateBitmask FlagMask -> Int #

FiniteBits (VkPipelineCreateBitmask FlagMask) Source # 
type Rep (VkPipelineCreateBitmask a) Source # 
type Rep (VkPipelineCreateBitmask a) = D1 (MetaData "VkPipelineCreateBitmask" "Graphics.Vulkan.Types.Enum.Pipeline" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkPipelineCreateBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkPipelineDepthStencilStateCreateFlagBits Source #

Instances

Bounded VkPipelineDepthStencilStateCreateFlagBits Source # 
Enum VkPipelineDepthStencilStateCreateFlagBits Source # 
Eq VkPipelineDepthStencilStateCreateFlagBits Source # 
Integral VkPipelineDepthStencilStateCreateFlagBits Source # 
Data VkPipelineDepthStencilStateCreateFlagBits Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkPipelineDepthStencilStateCreateFlagBits -> c VkPipelineDepthStencilStateCreateFlagBits #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkPipelineDepthStencilStateCreateFlagBits #

toConstr :: VkPipelineDepthStencilStateCreateFlagBits -> Constr #

dataTypeOf :: VkPipelineDepthStencilStateCreateFlagBits -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkPipelineDepthStencilStateCreateFlagBits) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkPipelineDepthStencilStateCreateFlagBits) #

gmapT :: (forall b. Data b => b -> b) -> VkPipelineDepthStencilStateCreateFlagBits -> VkPipelineDepthStencilStateCreateFlagBits #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineDepthStencilStateCreateFlagBits -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineDepthStencilStateCreateFlagBits -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkPipelineDepthStencilStateCreateFlagBits -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkPipelineDepthStencilStateCreateFlagBits -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkPipelineDepthStencilStateCreateFlagBits -> m VkPipelineDepthStencilStateCreateFlagBits #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineDepthStencilStateCreateFlagBits -> m VkPipelineDepthStencilStateCreateFlagBits #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineDepthStencilStateCreateFlagBits -> m VkPipelineDepthStencilStateCreateFlagBits #

Num VkPipelineDepthStencilStateCreateFlagBits Source # 
Ord VkPipelineDepthStencilStateCreateFlagBits Source # 
Read VkPipelineDepthStencilStateCreateFlagBits Source # 
Real VkPipelineDepthStencilStateCreateFlagBits Source # 
Show VkPipelineDepthStencilStateCreateFlagBits Source # 
Generic VkPipelineDepthStencilStateCreateFlagBits Source # 
Storable VkPipelineDepthStencilStateCreateFlagBits Source # 
Bits VkPipelineDepthStencilStateCreateFlagBits Source # 

Methods

(.&.) :: VkPipelineDepthStencilStateCreateFlagBits -> VkPipelineDepthStencilStateCreateFlagBits -> VkPipelineDepthStencilStateCreateFlagBits #

(.|.) :: VkPipelineDepthStencilStateCreateFlagBits -> VkPipelineDepthStencilStateCreateFlagBits -> VkPipelineDepthStencilStateCreateFlagBits #

xor :: VkPipelineDepthStencilStateCreateFlagBits -> VkPipelineDepthStencilStateCreateFlagBits -> VkPipelineDepthStencilStateCreateFlagBits #

complement :: VkPipelineDepthStencilStateCreateFlagBits -> VkPipelineDepthStencilStateCreateFlagBits #

shift :: VkPipelineDepthStencilStateCreateFlagBits -> Int -> VkPipelineDepthStencilStateCreateFlagBits #

rotate :: VkPipelineDepthStencilStateCreateFlagBits -> Int -> VkPipelineDepthStencilStateCreateFlagBits #

zeroBits :: VkPipelineDepthStencilStateCreateFlagBits #

bit :: Int -> VkPipelineDepthStencilStateCreateFlagBits #

setBit :: VkPipelineDepthStencilStateCreateFlagBits -> Int -> VkPipelineDepthStencilStateCreateFlagBits #

clearBit :: VkPipelineDepthStencilStateCreateFlagBits -> Int -> VkPipelineDepthStencilStateCreateFlagBits #

complementBit :: VkPipelineDepthStencilStateCreateFlagBits -> Int -> VkPipelineDepthStencilStateCreateFlagBits #

testBit :: VkPipelineDepthStencilStateCreateFlagBits -> Int -> Bool #

bitSizeMaybe :: VkPipelineDepthStencilStateCreateFlagBits -> Maybe Int #

bitSize :: VkPipelineDepthStencilStateCreateFlagBits -> Int #

isSigned :: VkPipelineDepthStencilStateCreateFlagBits -> Bool #

shiftL :: VkPipelineDepthStencilStateCreateFlagBits -> Int -> VkPipelineDepthStencilStateCreateFlagBits #

unsafeShiftL :: VkPipelineDepthStencilStateCreateFlagBits -> Int -> VkPipelineDepthStencilStateCreateFlagBits #

shiftR :: VkPipelineDepthStencilStateCreateFlagBits -> Int -> VkPipelineDepthStencilStateCreateFlagBits #

unsafeShiftR :: VkPipelineDepthStencilStateCreateFlagBits -> Int -> VkPipelineDepthStencilStateCreateFlagBits #

rotateL :: VkPipelineDepthStencilStateCreateFlagBits -> Int -> VkPipelineDepthStencilStateCreateFlagBits #

rotateR :: VkPipelineDepthStencilStateCreateFlagBits -> Int -> VkPipelineDepthStencilStateCreateFlagBits #

popCount :: VkPipelineDepthStencilStateCreateFlagBits -> Int #

FiniteBits VkPipelineDepthStencilStateCreateFlagBits Source # 
type Rep VkPipelineDepthStencilStateCreateFlagBits Source # 
type Rep VkPipelineDepthStencilStateCreateFlagBits = D1 (MetaData "VkPipelineDepthStencilStateCreateFlagBits" "Graphics.Vulkan.Types.Enum.Pipeline" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkPipelineDepthStencilStateCreateFlagBits" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkPipelineDynamicStateCreateFlagBits Source #

Instances

Bounded VkPipelineDynamicStateCreateFlagBits Source # 
Enum VkPipelineDynamicStateCreateFlagBits Source # 
Eq VkPipelineDynamicStateCreateFlagBits Source # 
Integral VkPipelineDynamicStateCreateFlagBits Source # 
Data VkPipelineDynamicStateCreateFlagBits Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkPipelineDynamicStateCreateFlagBits -> c VkPipelineDynamicStateCreateFlagBits #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkPipelineDynamicStateCreateFlagBits #

toConstr :: VkPipelineDynamicStateCreateFlagBits -> Constr #

dataTypeOf :: VkPipelineDynamicStateCreateFlagBits -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkPipelineDynamicStateCreateFlagBits) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkPipelineDynamicStateCreateFlagBits) #

gmapT :: (forall b. Data b => b -> b) -> VkPipelineDynamicStateCreateFlagBits -> VkPipelineDynamicStateCreateFlagBits #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineDynamicStateCreateFlagBits -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineDynamicStateCreateFlagBits -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkPipelineDynamicStateCreateFlagBits -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkPipelineDynamicStateCreateFlagBits -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkPipelineDynamicStateCreateFlagBits -> m VkPipelineDynamicStateCreateFlagBits #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineDynamicStateCreateFlagBits -> m VkPipelineDynamicStateCreateFlagBits #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineDynamicStateCreateFlagBits -> m VkPipelineDynamicStateCreateFlagBits #

Num VkPipelineDynamicStateCreateFlagBits Source # 
Ord VkPipelineDynamicStateCreateFlagBits Source # 
Read VkPipelineDynamicStateCreateFlagBits Source # 
Real VkPipelineDynamicStateCreateFlagBits Source # 
Show VkPipelineDynamicStateCreateFlagBits Source # 
Generic VkPipelineDynamicStateCreateFlagBits Source # 
Storable VkPipelineDynamicStateCreateFlagBits Source # 
Bits VkPipelineDynamicStateCreateFlagBits Source # 

Methods

(.&.) :: VkPipelineDynamicStateCreateFlagBits -> VkPipelineDynamicStateCreateFlagBits -> VkPipelineDynamicStateCreateFlagBits #

(.|.) :: VkPipelineDynamicStateCreateFlagBits -> VkPipelineDynamicStateCreateFlagBits -> VkPipelineDynamicStateCreateFlagBits #

xor :: VkPipelineDynamicStateCreateFlagBits -> VkPipelineDynamicStateCreateFlagBits -> VkPipelineDynamicStateCreateFlagBits #

complement :: VkPipelineDynamicStateCreateFlagBits -> VkPipelineDynamicStateCreateFlagBits #

shift :: VkPipelineDynamicStateCreateFlagBits -> Int -> VkPipelineDynamicStateCreateFlagBits #

rotate :: VkPipelineDynamicStateCreateFlagBits -> Int -> VkPipelineDynamicStateCreateFlagBits #

zeroBits :: VkPipelineDynamicStateCreateFlagBits #

bit :: Int -> VkPipelineDynamicStateCreateFlagBits #

setBit :: VkPipelineDynamicStateCreateFlagBits -> Int -> VkPipelineDynamicStateCreateFlagBits #

clearBit :: VkPipelineDynamicStateCreateFlagBits -> Int -> VkPipelineDynamicStateCreateFlagBits #

complementBit :: VkPipelineDynamicStateCreateFlagBits -> Int -> VkPipelineDynamicStateCreateFlagBits #

testBit :: VkPipelineDynamicStateCreateFlagBits -> Int -> Bool #

bitSizeMaybe :: VkPipelineDynamicStateCreateFlagBits -> Maybe Int #

bitSize :: VkPipelineDynamicStateCreateFlagBits -> Int #

isSigned :: VkPipelineDynamicStateCreateFlagBits -> Bool #

shiftL :: VkPipelineDynamicStateCreateFlagBits -> Int -> VkPipelineDynamicStateCreateFlagBits #

unsafeShiftL :: VkPipelineDynamicStateCreateFlagBits -> Int -> VkPipelineDynamicStateCreateFlagBits #

shiftR :: VkPipelineDynamicStateCreateFlagBits -> Int -> VkPipelineDynamicStateCreateFlagBits #

unsafeShiftR :: VkPipelineDynamicStateCreateFlagBits -> Int -> VkPipelineDynamicStateCreateFlagBits #

rotateL :: VkPipelineDynamicStateCreateFlagBits -> Int -> VkPipelineDynamicStateCreateFlagBits #

rotateR :: VkPipelineDynamicStateCreateFlagBits -> Int -> VkPipelineDynamicStateCreateFlagBits #

popCount :: VkPipelineDynamicStateCreateFlagBits -> Int #

FiniteBits VkPipelineDynamicStateCreateFlagBits Source # 
type Rep VkPipelineDynamicStateCreateFlagBits Source # 
type Rep VkPipelineDynamicStateCreateFlagBits = D1 (MetaData "VkPipelineDynamicStateCreateFlagBits" "Graphics.Vulkan.Types.Enum.Pipeline" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkPipelineDynamicStateCreateFlagBits" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkPipelineInputAssemblyStateCreateFlagBits Source #

Instances

Bounded VkPipelineInputAssemblyStateCreateFlagBits Source # 
Enum VkPipelineInputAssemblyStateCreateFlagBits Source # 
Eq VkPipelineInputAssemblyStateCreateFlagBits Source # 
Integral VkPipelineInputAssemblyStateCreateFlagBits Source # 
Data VkPipelineInputAssemblyStateCreateFlagBits Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkPipelineInputAssemblyStateCreateFlagBits -> c VkPipelineInputAssemblyStateCreateFlagBits #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkPipelineInputAssemblyStateCreateFlagBits #

toConstr :: VkPipelineInputAssemblyStateCreateFlagBits -> Constr #

dataTypeOf :: VkPipelineInputAssemblyStateCreateFlagBits -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkPipelineInputAssemblyStateCreateFlagBits) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkPipelineInputAssemblyStateCreateFlagBits) #

gmapT :: (forall b. Data b => b -> b) -> VkPipelineInputAssemblyStateCreateFlagBits -> VkPipelineInputAssemblyStateCreateFlagBits #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineInputAssemblyStateCreateFlagBits -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineInputAssemblyStateCreateFlagBits -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkPipelineInputAssemblyStateCreateFlagBits -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkPipelineInputAssemblyStateCreateFlagBits -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkPipelineInputAssemblyStateCreateFlagBits -> m VkPipelineInputAssemblyStateCreateFlagBits #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineInputAssemblyStateCreateFlagBits -> m VkPipelineInputAssemblyStateCreateFlagBits #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineInputAssemblyStateCreateFlagBits -> m VkPipelineInputAssemblyStateCreateFlagBits #

Num VkPipelineInputAssemblyStateCreateFlagBits Source # 
Ord VkPipelineInputAssemblyStateCreateFlagBits Source # 
Read VkPipelineInputAssemblyStateCreateFlagBits Source # 
Real VkPipelineInputAssemblyStateCreateFlagBits Source # 
Show VkPipelineInputAssemblyStateCreateFlagBits Source # 
Generic VkPipelineInputAssemblyStateCreateFlagBits Source # 
Storable VkPipelineInputAssemblyStateCreateFlagBits Source # 
Bits VkPipelineInputAssemblyStateCreateFlagBits Source # 

Methods

(.&.) :: VkPipelineInputAssemblyStateCreateFlagBits -> VkPipelineInputAssemblyStateCreateFlagBits -> VkPipelineInputAssemblyStateCreateFlagBits #

(.|.) :: VkPipelineInputAssemblyStateCreateFlagBits -> VkPipelineInputAssemblyStateCreateFlagBits -> VkPipelineInputAssemblyStateCreateFlagBits #

xor :: VkPipelineInputAssemblyStateCreateFlagBits -> VkPipelineInputAssemblyStateCreateFlagBits -> VkPipelineInputAssemblyStateCreateFlagBits #

complement :: VkPipelineInputAssemblyStateCreateFlagBits -> VkPipelineInputAssemblyStateCreateFlagBits #

shift :: VkPipelineInputAssemblyStateCreateFlagBits -> Int -> VkPipelineInputAssemblyStateCreateFlagBits #

rotate :: VkPipelineInputAssemblyStateCreateFlagBits -> Int -> VkPipelineInputAssemblyStateCreateFlagBits #

zeroBits :: VkPipelineInputAssemblyStateCreateFlagBits #

bit :: Int -> VkPipelineInputAssemblyStateCreateFlagBits #

setBit :: VkPipelineInputAssemblyStateCreateFlagBits -> Int -> VkPipelineInputAssemblyStateCreateFlagBits #

clearBit :: VkPipelineInputAssemblyStateCreateFlagBits -> Int -> VkPipelineInputAssemblyStateCreateFlagBits #

complementBit :: VkPipelineInputAssemblyStateCreateFlagBits -> Int -> VkPipelineInputAssemblyStateCreateFlagBits #

testBit :: VkPipelineInputAssemblyStateCreateFlagBits -> Int -> Bool #

bitSizeMaybe :: VkPipelineInputAssemblyStateCreateFlagBits -> Maybe Int #

bitSize :: VkPipelineInputAssemblyStateCreateFlagBits -> Int #

isSigned :: VkPipelineInputAssemblyStateCreateFlagBits -> Bool #

shiftL :: VkPipelineInputAssemblyStateCreateFlagBits -> Int -> VkPipelineInputAssemblyStateCreateFlagBits #

unsafeShiftL :: VkPipelineInputAssemblyStateCreateFlagBits -> Int -> VkPipelineInputAssemblyStateCreateFlagBits #

shiftR :: VkPipelineInputAssemblyStateCreateFlagBits -> Int -> VkPipelineInputAssemblyStateCreateFlagBits #

unsafeShiftR :: VkPipelineInputAssemblyStateCreateFlagBits -> Int -> VkPipelineInputAssemblyStateCreateFlagBits #

rotateL :: VkPipelineInputAssemblyStateCreateFlagBits -> Int -> VkPipelineInputAssemblyStateCreateFlagBits #

rotateR :: VkPipelineInputAssemblyStateCreateFlagBits -> Int -> VkPipelineInputAssemblyStateCreateFlagBits #

popCount :: VkPipelineInputAssemblyStateCreateFlagBits -> Int #

FiniteBits VkPipelineInputAssemblyStateCreateFlagBits Source # 
type Rep VkPipelineInputAssemblyStateCreateFlagBits Source # 
type Rep VkPipelineInputAssemblyStateCreateFlagBits = D1 (MetaData "VkPipelineInputAssemblyStateCreateFlagBits" "Graphics.Vulkan.Types.Enum.Pipeline" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkPipelineInputAssemblyStateCreateFlagBits" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkPipelineLayoutCreateFlagBits Source #

Instances

Bounded VkPipelineLayoutCreateFlagBits Source # 
Enum VkPipelineLayoutCreateFlagBits Source # 
Eq VkPipelineLayoutCreateFlagBits Source # 
Integral VkPipelineLayoutCreateFlagBits Source # 
Data VkPipelineLayoutCreateFlagBits Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkPipelineLayoutCreateFlagBits -> c VkPipelineLayoutCreateFlagBits #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkPipelineLayoutCreateFlagBits #

toConstr :: VkPipelineLayoutCreateFlagBits -> Constr #

dataTypeOf :: VkPipelineLayoutCreateFlagBits -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkPipelineLayoutCreateFlagBits) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkPipelineLayoutCreateFlagBits) #

gmapT :: (forall b. Data b => b -> b) -> VkPipelineLayoutCreateFlagBits -> VkPipelineLayoutCreateFlagBits #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineLayoutCreateFlagBits -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineLayoutCreateFlagBits -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkPipelineLayoutCreateFlagBits -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkPipelineLayoutCreateFlagBits -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkPipelineLayoutCreateFlagBits -> m VkPipelineLayoutCreateFlagBits #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineLayoutCreateFlagBits -> m VkPipelineLayoutCreateFlagBits #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineLayoutCreateFlagBits -> m VkPipelineLayoutCreateFlagBits #

Num VkPipelineLayoutCreateFlagBits Source # 
Ord VkPipelineLayoutCreateFlagBits Source # 
Read VkPipelineLayoutCreateFlagBits Source # 
Real VkPipelineLayoutCreateFlagBits Source # 
Show VkPipelineLayoutCreateFlagBits Source # 
Generic VkPipelineLayoutCreateFlagBits Source # 
Storable VkPipelineLayoutCreateFlagBits Source # 
Bits VkPipelineLayoutCreateFlagBits Source # 

Methods

(.&.) :: VkPipelineLayoutCreateFlagBits -> VkPipelineLayoutCreateFlagBits -> VkPipelineLayoutCreateFlagBits #

(.|.) :: VkPipelineLayoutCreateFlagBits -> VkPipelineLayoutCreateFlagBits -> VkPipelineLayoutCreateFlagBits #

xor :: VkPipelineLayoutCreateFlagBits -> VkPipelineLayoutCreateFlagBits -> VkPipelineLayoutCreateFlagBits #

complement :: VkPipelineLayoutCreateFlagBits -> VkPipelineLayoutCreateFlagBits #

shift :: VkPipelineLayoutCreateFlagBits -> Int -> VkPipelineLayoutCreateFlagBits #

rotate :: VkPipelineLayoutCreateFlagBits -> Int -> VkPipelineLayoutCreateFlagBits #

zeroBits :: VkPipelineLayoutCreateFlagBits #

bit :: Int -> VkPipelineLayoutCreateFlagBits #

setBit :: VkPipelineLayoutCreateFlagBits -> Int -> VkPipelineLayoutCreateFlagBits #

clearBit :: VkPipelineLayoutCreateFlagBits -> Int -> VkPipelineLayoutCreateFlagBits #

complementBit :: VkPipelineLayoutCreateFlagBits -> Int -> VkPipelineLayoutCreateFlagBits #

testBit :: VkPipelineLayoutCreateFlagBits -> Int -> Bool #

bitSizeMaybe :: VkPipelineLayoutCreateFlagBits -> Maybe Int #

bitSize :: VkPipelineLayoutCreateFlagBits -> Int #

isSigned :: VkPipelineLayoutCreateFlagBits -> Bool #

shiftL :: VkPipelineLayoutCreateFlagBits -> Int -> VkPipelineLayoutCreateFlagBits #

unsafeShiftL :: VkPipelineLayoutCreateFlagBits -> Int -> VkPipelineLayoutCreateFlagBits #

shiftR :: VkPipelineLayoutCreateFlagBits -> Int -> VkPipelineLayoutCreateFlagBits #

unsafeShiftR :: VkPipelineLayoutCreateFlagBits -> Int -> VkPipelineLayoutCreateFlagBits #

rotateL :: VkPipelineLayoutCreateFlagBits -> Int -> VkPipelineLayoutCreateFlagBits #

rotateR :: VkPipelineLayoutCreateFlagBits -> Int -> VkPipelineLayoutCreateFlagBits #

popCount :: VkPipelineLayoutCreateFlagBits -> Int #

FiniteBits VkPipelineLayoutCreateFlagBits Source # 
type Rep VkPipelineLayoutCreateFlagBits Source # 
type Rep VkPipelineLayoutCreateFlagBits = D1 (MetaData "VkPipelineLayoutCreateFlagBits" "Graphics.Vulkan.Types.Enum.Pipeline" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkPipelineLayoutCreateFlagBits" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkPipelineMultisampleStateCreateFlagBits Source #

Instances

Bounded VkPipelineMultisampleStateCreateFlagBits Source # 
Enum VkPipelineMultisampleStateCreateFlagBits Source # 
Eq VkPipelineMultisampleStateCreateFlagBits Source # 
Integral VkPipelineMultisampleStateCreateFlagBits Source # 
Data VkPipelineMultisampleStateCreateFlagBits Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkPipelineMultisampleStateCreateFlagBits -> c VkPipelineMultisampleStateCreateFlagBits #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkPipelineMultisampleStateCreateFlagBits #

toConstr :: VkPipelineMultisampleStateCreateFlagBits -> Constr #

dataTypeOf :: VkPipelineMultisampleStateCreateFlagBits -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkPipelineMultisampleStateCreateFlagBits) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkPipelineMultisampleStateCreateFlagBits) #

gmapT :: (forall b. Data b => b -> b) -> VkPipelineMultisampleStateCreateFlagBits -> VkPipelineMultisampleStateCreateFlagBits #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineMultisampleStateCreateFlagBits -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineMultisampleStateCreateFlagBits -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkPipelineMultisampleStateCreateFlagBits -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkPipelineMultisampleStateCreateFlagBits -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkPipelineMultisampleStateCreateFlagBits -> m VkPipelineMultisampleStateCreateFlagBits #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineMultisampleStateCreateFlagBits -> m VkPipelineMultisampleStateCreateFlagBits #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineMultisampleStateCreateFlagBits -> m VkPipelineMultisampleStateCreateFlagBits #

Num VkPipelineMultisampleStateCreateFlagBits Source # 
Ord VkPipelineMultisampleStateCreateFlagBits Source # 
Read VkPipelineMultisampleStateCreateFlagBits Source # 
Real VkPipelineMultisampleStateCreateFlagBits Source # 
Show VkPipelineMultisampleStateCreateFlagBits Source # 
Generic VkPipelineMultisampleStateCreateFlagBits Source # 
Storable VkPipelineMultisampleStateCreateFlagBits Source # 
Bits VkPipelineMultisampleStateCreateFlagBits Source # 

Methods

(.&.) :: VkPipelineMultisampleStateCreateFlagBits -> VkPipelineMultisampleStateCreateFlagBits -> VkPipelineMultisampleStateCreateFlagBits #

(.|.) :: VkPipelineMultisampleStateCreateFlagBits -> VkPipelineMultisampleStateCreateFlagBits -> VkPipelineMultisampleStateCreateFlagBits #

xor :: VkPipelineMultisampleStateCreateFlagBits -> VkPipelineMultisampleStateCreateFlagBits -> VkPipelineMultisampleStateCreateFlagBits #

complement :: VkPipelineMultisampleStateCreateFlagBits -> VkPipelineMultisampleStateCreateFlagBits #

shift :: VkPipelineMultisampleStateCreateFlagBits -> Int -> VkPipelineMultisampleStateCreateFlagBits #

rotate :: VkPipelineMultisampleStateCreateFlagBits -> Int -> VkPipelineMultisampleStateCreateFlagBits #

zeroBits :: VkPipelineMultisampleStateCreateFlagBits #

bit :: Int -> VkPipelineMultisampleStateCreateFlagBits #

setBit :: VkPipelineMultisampleStateCreateFlagBits -> Int -> VkPipelineMultisampleStateCreateFlagBits #

clearBit :: VkPipelineMultisampleStateCreateFlagBits -> Int -> VkPipelineMultisampleStateCreateFlagBits #

complementBit :: VkPipelineMultisampleStateCreateFlagBits -> Int -> VkPipelineMultisampleStateCreateFlagBits #

testBit :: VkPipelineMultisampleStateCreateFlagBits -> Int -> Bool #

bitSizeMaybe :: VkPipelineMultisampleStateCreateFlagBits -> Maybe Int #

bitSize :: VkPipelineMultisampleStateCreateFlagBits -> Int #

isSigned :: VkPipelineMultisampleStateCreateFlagBits -> Bool #

shiftL :: VkPipelineMultisampleStateCreateFlagBits -> Int -> VkPipelineMultisampleStateCreateFlagBits #

unsafeShiftL :: VkPipelineMultisampleStateCreateFlagBits -> Int -> VkPipelineMultisampleStateCreateFlagBits #

shiftR :: VkPipelineMultisampleStateCreateFlagBits -> Int -> VkPipelineMultisampleStateCreateFlagBits #

unsafeShiftR :: VkPipelineMultisampleStateCreateFlagBits -> Int -> VkPipelineMultisampleStateCreateFlagBits #

rotateL :: VkPipelineMultisampleStateCreateFlagBits -> Int -> VkPipelineMultisampleStateCreateFlagBits #

rotateR :: VkPipelineMultisampleStateCreateFlagBits -> Int -> VkPipelineMultisampleStateCreateFlagBits #

popCount :: VkPipelineMultisampleStateCreateFlagBits -> Int #

FiniteBits VkPipelineMultisampleStateCreateFlagBits Source # 
type Rep VkPipelineMultisampleStateCreateFlagBits Source # 
type Rep VkPipelineMultisampleStateCreateFlagBits = D1 (MetaData "VkPipelineMultisampleStateCreateFlagBits" "Graphics.Vulkan.Types.Enum.Pipeline" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkPipelineMultisampleStateCreateFlagBits" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkPipelineRasterizationStateCreateFlagBits Source #

Instances

Bounded VkPipelineRasterizationStateCreateFlagBits Source # 
Enum VkPipelineRasterizationStateCreateFlagBits Source # 
Eq VkPipelineRasterizationStateCreateFlagBits Source # 
Integral VkPipelineRasterizationStateCreateFlagBits Source # 
Data VkPipelineRasterizationStateCreateFlagBits Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkPipelineRasterizationStateCreateFlagBits -> c VkPipelineRasterizationStateCreateFlagBits #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkPipelineRasterizationStateCreateFlagBits #

toConstr :: VkPipelineRasterizationStateCreateFlagBits -> Constr #

dataTypeOf :: VkPipelineRasterizationStateCreateFlagBits -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkPipelineRasterizationStateCreateFlagBits) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkPipelineRasterizationStateCreateFlagBits) #

gmapT :: (forall b. Data b => b -> b) -> VkPipelineRasterizationStateCreateFlagBits -> VkPipelineRasterizationStateCreateFlagBits #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineRasterizationStateCreateFlagBits -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineRasterizationStateCreateFlagBits -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkPipelineRasterizationStateCreateFlagBits -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkPipelineRasterizationStateCreateFlagBits -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkPipelineRasterizationStateCreateFlagBits -> m VkPipelineRasterizationStateCreateFlagBits #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineRasterizationStateCreateFlagBits -> m VkPipelineRasterizationStateCreateFlagBits #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineRasterizationStateCreateFlagBits -> m VkPipelineRasterizationStateCreateFlagBits #

Num VkPipelineRasterizationStateCreateFlagBits Source # 
Ord VkPipelineRasterizationStateCreateFlagBits Source # 
Read VkPipelineRasterizationStateCreateFlagBits Source # 
Real VkPipelineRasterizationStateCreateFlagBits Source # 
Show VkPipelineRasterizationStateCreateFlagBits Source # 
Generic VkPipelineRasterizationStateCreateFlagBits Source # 
Storable VkPipelineRasterizationStateCreateFlagBits Source # 
Bits VkPipelineRasterizationStateCreateFlagBits Source # 

Methods

(.&.) :: VkPipelineRasterizationStateCreateFlagBits -> VkPipelineRasterizationStateCreateFlagBits -> VkPipelineRasterizationStateCreateFlagBits #

(.|.) :: VkPipelineRasterizationStateCreateFlagBits -> VkPipelineRasterizationStateCreateFlagBits -> VkPipelineRasterizationStateCreateFlagBits #

xor :: VkPipelineRasterizationStateCreateFlagBits -> VkPipelineRasterizationStateCreateFlagBits -> VkPipelineRasterizationStateCreateFlagBits #

complement :: VkPipelineRasterizationStateCreateFlagBits -> VkPipelineRasterizationStateCreateFlagBits #

shift :: VkPipelineRasterizationStateCreateFlagBits -> Int -> VkPipelineRasterizationStateCreateFlagBits #

rotate :: VkPipelineRasterizationStateCreateFlagBits -> Int -> VkPipelineRasterizationStateCreateFlagBits #

zeroBits :: VkPipelineRasterizationStateCreateFlagBits #

bit :: Int -> VkPipelineRasterizationStateCreateFlagBits #

setBit :: VkPipelineRasterizationStateCreateFlagBits -> Int -> VkPipelineRasterizationStateCreateFlagBits #

clearBit :: VkPipelineRasterizationStateCreateFlagBits -> Int -> VkPipelineRasterizationStateCreateFlagBits #

complementBit :: VkPipelineRasterizationStateCreateFlagBits -> Int -> VkPipelineRasterizationStateCreateFlagBits #

testBit :: VkPipelineRasterizationStateCreateFlagBits -> Int -> Bool #

bitSizeMaybe :: VkPipelineRasterizationStateCreateFlagBits -> Maybe Int #

bitSize :: VkPipelineRasterizationStateCreateFlagBits -> Int #

isSigned :: VkPipelineRasterizationStateCreateFlagBits -> Bool #

shiftL :: VkPipelineRasterizationStateCreateFlagBits -> Int -> VkPipelineRasterizationStateCreateFlagBits #

unsafeShiftL :: VkPipelineRasterizationStateCreateFlagBits -> Int -> VkPipelineRasterizationStateCreateFlagBits #

shiftR :: VkPipelineRasterizationStateCreateFlagBits -> Int -> VkPipelineRasterizationStateCreateFlagBits #

unsafeShiftR :: VkPipelineRasterizationStateCreateFlagBits -> Int -> VkPipelineRasterizationStateCreateFlagBits #

rotateL :: VkPipelineRasterizationStateCreateFlagBits -> Int -> VkPipelineRasterizationStateCreateFlagBits #

rotateR :: VkPipelineRasterizationStateCreateFlagBits -> Int -> VkPipelineRasterizationStateCreateFlagBits #

popCount :: VkPipelineRasterizationStateCreateFlagBits -> Int #

FiniteBits VkPipelineRasterizationStateCreateFlagBits Source # 
type Rep VkPipelineRasterizationStateCreateFlagBits Source # 
type Rep VkPipelineRasterizationStateCreateFlagBits = D1 (MetaData "VkPipelineRasterizationStateCreateFlagBits" "Graphics.Vulkan.Types.Enum.Pipeline" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkPipelineRasterizationStateCreateFlagBits" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkPipelineShaderStageCreateFlagBits Source #

Instances

Bounded VkPipelineShaderStageCreateFlagBits Source # 
Enum VkPipelineShaderStageCreateFlagBits Source # 
Eq VkPipelineShaderStageCreateFlagBits Source # 
Integral VkPipelineShaderStageCreateFlagBits Source # 
Data VkPipelineShaderStageCreateFlagBits Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkPipelineShaderStageCreateFlagBits -> c VkPipelineShaderStageCreateFlagBits #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkPipelineShaderStageCreateFlagBits #

toConstr :: VkPipelineShaderStageCreateFlagBits -> Constr #

dataTypeOf :: VkPipelineShaderStageCreateFlagBits -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkPipelineShaderStageCreateFlagBits) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkPipelineShaderStageCreateFlagBits) #

gmapT :: (forall b. Data b => b -> b) -> VkPipelineShaderStageCreateFlagBits -> VkPipelineShaderStageCreateFlagBits #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineShaderStageCreateFlagBits -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineShaderStageCreateFlagBits -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkPipelineShaderStageCreateFlagBits -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkPipelineShaderStageCreateFlagBits -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkPipelineShaderStageCreateFlagBits -> m VkPipelineShaderStageCreateFlagBits #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineShaderStageCreateFlagBits -> m VkPipelineShaderStageCreateFlagBits #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineShaderStageCreateFlagBits -> m VkPipelineShaderStageCreateFlagBits #

Num VkPipelineShaderStageCreateFlagBits Source # 
Ord VkPipelineShaderStageCreateFlagBits Source # 
Read VkPipelineShaderStageCreateFlagBits Source # 
Real VkPipelineShaderStageCreateFlagBits Source # 
Show VkPipelineShaderStageCreateFlagBits Source # 
Generic VkPipelineShaderStageCreateFlagBits Source # 
Storable VkPipelineShaderStageCreateFlagBits Source # 
Bits VkPipelineShaderStageCreateFlagBits Source # 

Methods

(.&.) :: VkPipelineShaderStageCreateFlagBits -> VkPipelineShaderStageCreateFlagBits -> VkPipelineShaderStageCreateFlagBits #

(.|.) :: VkPipelineShaderStageCreateFlagBits -> VkPipelineShaderStageCreateFlagBits -> VkPipelineShaderStageCreateFlagBits #

xor :: VkPipelineShaderStageCreateFlagBits -> VkPipelineShaderStageCreateFlagBits -> VkPipelineShaderStageCreateFlagBits #

complement :: VkPipelineShaderStageCreateFlagBits -> VkPipelineShaderStageCreateFlagBits #

shift :: VkPipelineShaderStageCreateFlagBits -> Int -> VkPipelineShaderStageCreateFlagBits #

rotate :: VkPipelineShaderStageCreateFlagBits -> Int -> VkPipelineShaderStageCreateFlagBits #

zeroBits :: VkPipelineShaderStageCreateFlagBits #

bit :: Int -> VkPipelineShaderStageCreateFlagBits #

setBit :: VkPipelineShaderStageCreateFlagBits -> Int -> VkPipelineShaderStageCreateFlagBits #

clearBit :: VkPipelineShaderStageCreateFlagBits -> Int -> VkPipelineShaderStageCreateFlagBits #

complementBit :: VkPipelineShaderStageCreateFlagBits -> Int -> VkPipelineShaderStageCreateFlagBits #

testBit :: VkPipelineShaderStageCreateFlagBits -> Int -> Bool #

bitSizeMaybe :: VkPipelineShaderStageCreateFlagBits -> Maybe Int #

bitSize :: VkPipelineShaderStageCreateFlagBits -> Int #

isSigned :: VkPipelineShaderStageCreateFlagBits -> Bool #

shiftL :: VkPipelineShaderStageCreateFlagBits -> Int -> VkPipelineShaderStageCreateFlagBits #

unsafeShiftL :: VkPipelineShaderStageCreateFlagBits -> Int -> VkPipelineShaderStageCreateFlagBits #

shiftR :: VkPipelineShaderStageCreateFlagBits -> Int -> VkPipelineShaderStageCreateFlagBits #

unsafeShiftR :: VkPipelineShaderStageCreateFlagBits -> Int -> VkPipelineShaderStageCreateFlagBits #

rotateL :: VkPipelineShaderStageCreateFlagBits -> Int -> VkPipelineShaderStageCreateFlagBits #

rotateR :: VkPipelineShaderStageCreateFlagBits -> Int -> VkPipelineShaderStageCreateFlagBits #

popCount :: VkPipelineShaderStageCreateFlagBits -> Int #

FiniteBits VkPipelineShaderStageCreateFlagBits Source # 
type Rep VkPipelineShaderStageCreateFlagBits Source # 
type Rep VkPipelineShaderStageCreateFlagBits = D1 (MetaData "VkPipelineShaderStageCreateFlagBits" "Graphics.Vulkan.Types.Enum.Pipeline" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkPipelineShaderStageCreateFlagBits" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkPipelineStageBitmask a Source #

Instances

Bounded (VkPipelineStageBitmask FlagMask) Source # 
Enum (VkPipelineStageBitmask FlagMask) Source # 
Eq (VkPipelineStageBitmask a) Source # 
Integral (VkPipelineStageBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkPipelineStageBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkPipelineStageBitmask a -> c (VkPipelineStageBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkPipelineStageBitmask a) #

toConstr :: VkPipelineStageBitmask a -> Constr #

dataTypeOf :: VkPipelineStageBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkPipelineStageBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkPipelineStageBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkPipelineStageBitmask a -> VkPipelineStageBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineStageBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineStageBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkPipelineStageBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkPipelineStageBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkPipelineStageBitmask a -> m (VkPipelineStageBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineStageBitmask a -> m (VkPipelineStageBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineStageBitmask a -> m (VkPipelineStageBitmask a) #

Num (VkPipelineStageBitmask FlagMask) Source # 
Ord (VkPipelineStageBitmask a) Source # 
Read (VkPipelineStageBitmask a) Source # 
Real (VkPipelineStageBitmask FlagMask) Source # 
Show (VkPipelineStageBitmask a) Source # 
Generic (VkPipelineStageBitmask a) Source # 
Storable (VkPipelineStageBitmask a) Source # 
Bits (VkPipelineStageBitmask FlagMask) Source # 

Methods

(.&.) :: VkPipelineStageBitmask FlagMask -> VkPipelineStageBitmask FlagMask -> VkPipelineStageBitmask FlagMask #

(.|.) :: VkPipelineStageBitmask FlagMask -> VkPipelineStageBitmask FlagMask -> VkPipelineStageBitmask FlagMask #

xor :: VkPipelineStageBitmask FlagMask -> VkPipelineStageBitmask FlagMask -> VkPipelineStageBitmask FlagMask #

complement :: VkPipelineStageBitmask FlagMask -> VkPipelineStageBitmask FlagMask #

shift :: VkPipelineStageBitmask FlagMask -> Int -> VkPipelineStageBitmask FlagMask #

rotate :: VkPipelineStageBitmask FlagMask -> Int -> VkPipelineStageBitmask FlagMask #

zeroBits :: VkPipelineStageBitmask FlagMask #

bit :: Int -> VkPipelineStageBitmask FlagMask #

setBit :: VkPipelineStageBitmask FlagMask -> Int -> VkPipelineStageBitmask FlagMask #

clearBit :: VkPipelineStageBitmask FlagMask -> Int -> VkPipelineStageBitmask FlagMask #

complementBit :: VkPipelineStageBitmask FlagMask -> Int -> VkPipelineStageBitmask FlagMask #

testBit :: VkPipelineStageBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkPipelineStageBitmask FlagMask -> Maybe Int #

bitSize :: VkPipelineStageBitmask FlagMask -> Int #

isSigned :: VkPipelineStageBitmask FlagMask -> Bool #

shiftL :: VkPipelineStageBitmask FlagMask -> Int -> VkPipelineStageBitmask FlagMask #

unsafeShiftL :: VkPipelineStageBitmask FlagMask -> Int -> VkPipelineStageBitmask FlagMask #

shiftR :: VkPipelineStageBitmask FlagMask -> Int -> VkPipelineStageBitmask FlagMask #

unsafeShiftR :: VkPipelineStageBitmask FlagMask -> Int -> VkPipelineStageBitmask FlagMask #

rotateL :: VkPipelineStageBitmask FlagMask -> Int -> VkPipelineStageBitmask FlagMask #

rotateR :: VkPipelineStageBitmask FlagMask -> Int -> VkPipelineStageBitmask FlagMask #

popCount :: VkPipelineStageBitmask FlagMask -> Int #

FiniteBits (VkPipelineStageBitmask FlagMask) Source # 
type Rep (VkPipelineStageBitmask a) Source # 
type Rep (VkPipelineStageBitmask a) = D1 (MetaData "VkPipelineStageBitmask" "Graphics.Vulkan.Types.Enum.Pipeline" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkPipelineStageBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

pattern VK_PIPELINE_STAGE_TOP_OF_PIPE_BIT :: forall a. VkPipelineStageBitmask a Source #

Before subsequent commands are processed

bitpos = 0

pattern VK_PIPELINE_STAGE_DRAW_INDIRECT_BIT :: forall a. VkPipelineStageBitmask a Source #

Draw/DispatchIndirect command fetch

bitpos = 1

pattern VK_PIPELINE_STAGE_VERTEX_INPUT_BIT :: forall a. VkPipelineStageBitmask a Source #

Vertex/index fetch

bitpos = 2

pattern VK_PIPELINE_STAGE_VERTEX_SHADER_BIT :: forall a. VkPipelineStageBitmask a Source #

Vertex shading

bitpos = 3

pattern VK_PIPELINE_STAGE_TESSELLATION_CONTROL_SHADER_BIT :: forall a. VkPipelineStageBitmask a Source #

Tessellation control shading

bitpos = 4

pattern VK_PIPELINE_STAGE_TESSELLATION_EVALUATION_SHADER_BIT :: forall a. VkPipelineStageBitmask a Source #

Tessellation evaluation shading

bitpos = 5

pattern VK_PIPELINE_STAGE_GEOMETRY_SHADER_BIT :: forall a. VkPipelineStageBitmask a Source #

Geometry shading

bitpos = 6

pattern VK_PIPELINE_STAGE_FRAGMENT_SHADER_BIT :: forall a. VkPipelineStageBitmask a Source #

Fragment shading

bitpos = 7

pattern VK_PIPELINE_STAGE_EARLY_FRAGMENT_TESTS_BIT :: forall a. VkPipelineStageBitmask a Source #

Early fragment (depth and stencil) tests

bitpos = 8

pattern VK_PIPELINE_STAGE_LATE_FRAGMENT_TESTS_BIT :: forall a. VkPipelineStageBitmask a Source #

Late fragment (depth and stencil) tests

bitpos = 9

pattern VK_PIPELINE_STAGE_COLOR_ATTACHMENT_OUTPUT_BIT :: forall a. VkPipelineStageBitmask a Source #

Color attachment writes

bitpos = 10

pattern VK_PIPELINE_STAGE_COMPUTE_SHADER_BIT :: forall a. VkPipelineStageBitmask a Source #

Compute shading

bitpos = 11

pattern VK_PIPELINE_STAGE_TRANSFER_BIT :: forall a. VkPipelineStageBitmask a Source #

Transfer/copy operations

bitpos = 12

pattern VK_PIPELINE_STAGE_BOTTOM_OF_PIPE_BIT :: forall a. VkPipelineStageBitmask a Source #

After previous commands have completed

bitpos = 13

pattern VK_PIPELINE_STAGE_HOST_BIT :: forall a. VkPipelineStageBitmask a Source #

Indicates host (CPU) is a source/sink of the dependency

bitpos = 14

pattern VK_PIPELINE_STAGE_ALL_GRAPHICS_BIT :: forall a. VkPipelineStageBitmask a Source #

All stages of the graphics pipeline

bitpos = 15

pattern VK_PIPELINE_STAGE_ALL_COMMANDS_BIT :: forall a. VkPipelineStageBitmask a Source #

All stages supported on the queue

bitpos = 16

newtype VkPipelineTessellationStateCreateFlagBits Source #

Instances

Bounded VkPipelineTessellationStateCreateFlagBits Source # 
Enum VkPipelineTessellationStateCreateFlagBits Source # 
Eq VkPipelineTessellationStateCreateFlagBits Source # 
Integral VkPipelineTessellationStateCreateFlagBits Source # 
Data VkPipelineTessellationStateCreateFlagBits Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkPipelineTessellationStateCreateFlagBits -> c VkPipelineTessellationStateCreateFlagBits #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkPipelineTessellationStateCreateFlagBits #

toConstr :: VkPipelineTessellationStateCreateFlagBits -> Constr #

dataTypeOf :: VkPipelineTessellationStateCreateFlagBits -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkPipelineTessellationStateCreateFlagBits) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkPipelineTessellationStateCreateFlagBits) #

gmapT :: (forall b. Data b => b -> b) -> VkPipelineTessellationStateCreateFlagBits -> VkPipelineTessellationStateCreateFlagBits #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineTessellationStateCreateFlagBits -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineTessellationStateCreateFlagBits -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkPipelineTessellationStateCreateFlagBits -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkPipelineTessellationStateCreateFlagBits -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkPipelineTessellationStateCreateFlagBits -> m VkPipelineTessellationStateCreateFlagBits #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineTessellationStateCreateFlagBits -> m VkPipelineTessellationStateCreateFlagBits #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineTessellationStateCreateFlagBits -> m VkPipelineTessellationStateCreateFlagBits #

Num VkPipelineTessellationStateCreateFlagBits Source # 
Ord VkPipelineTessellationStateCreateFlagBits Source # 
Read VkPipelineTessellationStateCreateFlagBits Source # 
Real VkPipelineTessellationStateCreateFlagBits Source # 
Show VkPipelineTessellationStateCreateFlagBits Source # 
Generic VkPipelineTessellationStateCreateFlagBits Source # 
Storable VkPipelineTessellationStateCreateFlagBits Source # 
Bits VkPipelineTessellationStateCreateFlagBits Source # 

Methods

(.&.) :: VkPipelineTessellationStateCreateFlagBits -> VkPipelineTessellationStateCreateFlagBits -> VkPipelineTessellationStateCreateFlagBits #

(.|.) :: VkPipelineTessellationStateCreateFlagBits -> VkPipelineTessellationStateCreateFlagBits -> VkPipelineTessellationStateCreateFlagBits #

xor :: VkPipelineTessellationStateCreateFlagBits -> VkPipelineTessellationStateCreateFlagBits -> VkPipelineTessellationStateCreateFlagBits #

complement :: VkPipelineTessellationStateCreateFlagBits -> VkPipelineTessellationStateCreateFlagBits #

shift :: VkPipelineTessellationStateCreateFlagBits -> Int -> VkPipelineTessellationStateCreateFlagBits #

rotate :: VkPipelineTessellationStateCreateFlagBits -> Int -> VkPipelineTessellationStateCreateFlagBits #

zeroBits :: VkPipelineTessellationStateCreateFlagBits #

bit :: Int -> VkPipelineTessellationStateCreateFlagBits #

setBit :: VkPipelineTessellationStateCreateFlagBits -> Int -> VkPipelineTessellationStateCreateFlagBits #

clearBit :: VkPipelineTessellationStateCreateFlagBits -> Int -> VkPipelineTessellationStateCreateFlagBits #

complementBit :: VkPipelineTessellationStateCreateFlagBits -> Int -> VkPipelineTessellationStateCreateFlagBits #

testBit :: VkPipelineTessellationStateCreateFlagBits -> Int -> Bool #

bitSizeMaybe :: VkPipelineTessellationStateCreateFlagBits -> Maybe Int #

bitSize :: VkPipelineTessellationStateCreateFlagBits -> Int #

isSigned :: VkPipelineTessellationStateCreateFlagBits -> Bool #

shiftL :: VkPipelineTessellationStateCreateFlagBits -> Int -> VkPipelineTessellationStateCreateFlagBits #

unsafeShiftL :: VkPipelineTessellationStateCreateFlagBits -> Int -> VkPipelineTessellationStateCreateFlagBits #

shiftR :: VkPipelineTessellationStateCreateFlagBits -> Int -> VkPipelineTessellationStateCreateFlagBits #

unsafeShiftR :: VkPipelineTessellationStateCreateFlagBits -> Int -> VkPipelineTessellationStateCreateFlagBits #

rotateL :: VkPipelineTessellationStateCreateFlagBits -> Int -> VkPipelineTessellationStateCreateFlagBits #

rotateR :: VkPipelineTessellationStateCreateFlagBits -> Int -> VkPipelineTessellationStateCreateFlagBits #

popCount :: VkPipelineTessellationStateCreateFlagBits -> Int #

FiniteBits VkPipelineTessellationStateCreateFlagBits Source # 
type Rep VkPipelineTessellationStateCreateFlagBits Source # 
type Rep VkPipelineTessellationStateCreateFlagBits = D1 (MetaData "VkPipelineTessellationStateCreateFlagBits" "Graphics.Vulkan.Types.Enum.Pipeline" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkPipelineTessellationStateCreateFlagBits" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkPipelineVertexInputStateCreateFlagBits Source #

Instances

Bounded VkPipelineVertexInputStateCreateFlagBits Source # 
Enum VkPipelineVertexInputStateCreateFlagBits Source # 
Eq VkPipelineVertexInputStateCreateFlagBits Source # 
Integral VkPipelineVertexInputStateCreateFlagBits Source # 
Data VkPipelineVertexInputStateCreateFlagBits Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkPipelineVertexInputStateCreateFlagBits -> c VkPipelineVertexInputStateCreateFlagBits #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkPipelineVertexInputStateCreateFlagBits #

toConstr :: VkPipelineVertexInputStateCreateFlagBits -> Constr #

dataTypeOf :: VkPipelineVertexInputStateCreateFlagBits -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkPipelineVertexInputStateCreateFlagBits) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkPipelineVertexInputStateCreateFlagBits) #

gmapT :: (forall b. Data b => b -> b) -> VkPipelineVertexInputStateCreateFlagBits -> VkPipelineVertexInputStateCreateFlagBits #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineVertexInputStateCreateFlagBits -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineVertexInputStateCreateFlagBits -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkPipelineVertexInputStateCreateFlagBits -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkPipelineVertexInputStateCreateFlagBits -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkPipelineVertexInputStateCreateFlagBits -> m VkPipelineVertexInputStateCreateFlagBits #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineVertexInputStateCreateFlagBits -> m VkPipelineVertexInputStateCreateFlagBits #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineVertexInputStateCreateFlagBits -> m VkPipelineVertexInputStateCreateFlagBits #

Num VkPipelineVertexInputStateCreateFlagBits Source # 
Ord VkPipelineVertexInputStateCreateFlagBits Source # 
Read VkPipelineVertexInputStateCreateFlagBits Source # 
Real VkPipelineVertexInputStateCreateFlagBits Source # 
Show VkPipelineVertexInputStateCreateFlagBits Source # 
Generic VkPipelineVertexInputStateCreateFlagBits Source # 
Storable VkPipelineVertexInputStateCreateFlagBits Source # 
Bits VkPipelineVertexInputStateCreateFlagBits Source # 

Methods

(.&.) :: VkPipelineVertexInputStateCreateFlagBits -> VkPipelineVertexInputStateCreateFlagBits -> VkPipelineVertexInputStateCreateFlagBits #

(.|.) :: VkPipelineVertexInputStateCreateFlagBits -> VkPipelineVertexInputStateCreateFlagBits -> VkPipelineVertexInputStateCreateFlagBits #

xor :: VkPipelineVertexInputStateCreateFlagBits -> VkPipelineVertexInputStateCreateFlagBits -> VkPipelineVertexInputStateCreateFlagBits #

complement :: VkPipelineVertexInputStateCreateFlagBits -> VkPipelineVertexInputStateCreateFlagBits #

shift :: VkPipelineVertexInputStateCreateFlagBits -> Int -> VkPipelineVertexInputStateCreateFlagBits #

rotate :: VkPipelineVertexInputStateCreateFlagBits -> Int -> VkPipelineVertexInputStateCreateFlagBits #

zeroBits :: VkPipelineVertexInputStateCreateFlagBits #

bit :: Int -> VkPipelineVertexInputStateCreateFlagBits #

setBit :: VkPipelineVertexInputStateCreateFlagBits -> Int -> VkPipelineVertexInputStateCreateFlagBits #

clearBit :: VkPipelineVertexInputStateCreateFlagBits -> Int -> VkPipelineVertexInputStateCreateFlagBits #

complementBit :: VkPipelineVertexInputStateCreateFlagBits -> Int -> VkPipelineVertexInputStateCreateFlagBits #

testBit :: VkPipelineVertexInputStateCreateFlagBits -> Int -> Bool #

bitSizeMaybe :: VkPipelineVertexInputStateCreateFlagBits -> Maybe Int #

bitSize :: VkPipelineVertexInputStateCreateFlagBits -> Int #

isSigned :: VkPipelineVertexInputStateCreateFlagBits -> Bool #

shiftL :: VkPipelineVertexInputStateCreateFlagBits -> Int -> VkPipelineVertexInputStateCreateFlagBits #

unsafeShiftL :: VkPipelineVertexInputStateCreateFlagBits -> Int -> VkPipelineVertexInputStateCreateFlagBits #

shiftR :: VkPipelineVertexInputStateCreateFlagBits -> Int -> VkPipelineVertexInputStateCreateFlagBits #

unsafeShiftR :: VkPipelineVertexInputStateCreateFlagBits -> Int -> VkPipelineVertexInputStateCreateFlagBits #

rotateL :: VkPipelineVertexInputStateCreateFlagBits -> Int -> VkPipelineVertexInputStateCreateFlagBits #

rotateR :: VkPipelineVertexInputStateCreateFlagBits -> Int -> VkPipelineVertexInputStateCreateFlagBits #

popCount :: VkPipelineVertexInputStateCreateFlagBits -> Int #

FiniteBits VkPipelineVertexInputStateCreateFlagBits Source # 
type Rep VkPipelineVertexInputStateCreateFlagBits Source # 
type Rep VkPipelineVertexInputStateCreateFlagBits = D1 (MetaData "VkPipelineVertexInputStateCreateFlagBits" "Graphics.Vulkan.Types.Enum.Pipeline" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkPipelineVertexInputStateCreateFlagBits" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkPipelineViewportStateCreateFlagBits Source #

Instances

Bounded VkPipelineViewportStateCreateFlagBits Source # 
Enum VkPipelineViewportStateCreateFlagBits Source # 
Eq VkPipelineViewportStateCreateFlagBits Source # 
Integral VkPipelineViewportStateCreateFlagBits Source # 
Data VkPipelineViewportStateCreateFlagBits Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkPipelineViewportStateCreateFlagBits -> c VkPipelineViewportStateCreateFlagBits #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkPipelineViewportStateCreateFlagBits #

toConstr :: VkPipelineViewportStateCreateFlagBits -> Constr #

dataTypeOf :: VkPipelineViewportStateCreateFlagBits -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkPipelineViewportStateCreateFlagBits) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkPipelineViewportStateCreateFlagBits) #

gmapT :: (forall b. Data b => b -> b) -> VkPipelineViewportStateCreateFlagBits -> VkPipelineViewportStateCreateFlagBits #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineViewportStateCreateFlagBits -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkPipelineViewportStateCreateFlagBits -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkPipelineViewportStateCreateFlagBits -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkPipelineViewportStateCreateFlagBits -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkPipelineViewportStateCreateFlagBits -> m VkPipelineViewportStateCreateFlagBits #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineViewportStateCreateFlagBits -> m VkPipelineViewportStateCreateFlagBits #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPipelineViewportStateCreateFlagBits -> m VkPipelineViewportStateCreateFlagBits #

Num VkPipelineViewportStateCreateFlagBits Source # 
Ord VkPipelineViewportStateCreateFlagBits Source # 
Read VkPipelineViewportStateCreateFlagBits Source # 
Real VkPipelineViewportStateCreateFlagBits Source # 
Show VkPipelineViewportStateCreateFlagBits Source # 
Generic VkPipelineViewportStateCreateFlagBits Source # 
Storable VkPipelineViewportStateCreateFlagBits Source # 
Bits VkPipelineViewportStateCreateFlagBits Source # 

Methods

(.&.) :: VkPipelineViewportStateCreateFlagBits -> VkPipelineViewportStateCreateFlagBits -> VkPipelineViewportStateCreateFlagBits #

(.|.) :: VkPipelineViewportStateCreateFlagBits -> VkPipelineViewportStateCreateFlagBits -> VkPipelineViewportStateCreateFlagBits #

xor :: VkPipelineViewportStateCreateFlagBits -> VkPipelineViewportStateCreateFlagBits -> VkPipelineViewportStateCreateFlagBits #

complement :: VkPipelineViewportStateCreateFlagBits -> VkPipelineViewportStateCreateFlagBits #

shift :: VkPipelineViewportStateCreateFlagBits -> Int -> VkPipelineViewportStateCreateFlagBits #

rotate :: VkPipelineViewportStateCreateFlagBits -> Int -> VkPipelineViewportStateCreateFlagBits #

zeroBits :: VkPipelineViewportStateCreateFlagBits #

bit :: Int -> VkPipelineViewportStateCreateFlagBits #

setBit :: VkPipelineViewportStateCreateFlagBits -> Int -> VkPipelineViewportStateCreateFlagBits #

clearBit :: VkPipelineViewportStateCreateFlagBits -> Int -> VkPipelineViewportStateCreateFlagBits #

complementBit :: VkPipelineViewportStateCreateFlagBits -> Int -> VkPipelineViewportStateCreateFlagBits #

testBit :: VkPipelineViewportStateCreateFlagBits -> Int -> Bool #

bitSizeMaybe :: VkPipelineViewportStateCreateFlagBits -> Maybe Int #

bitSize :: VkPipelineViewportStateCreateFlagBits -> Int #

isSigned :: VkPipelineViewportStateCreateFlagBits -> Bool #

shiftL :: VkPipelineViewportStateCreateFlagBits -> Int -> VkPipelineViewportStateCreateFlagBits #

unsafeShiftL :: VkPipelineViewportStateCreateFlagBits -> Int -> VkPipelineViewportStateCreateFlagBits #

shiftR :: VkPipelineViewportStateCreateFlagBits -> Int -> VkPipelineViewportStateCreateFlagBits #

unsafeShiftR :: VkPipelineViewportStateCreateFlagBits -> Int -> VkPipelineViewportStateCreateFlagBits #

rotateL :: VkPipelineViewportStateCreateFlagBits -> Int -> VkPipelineViewportStateCreateFlagBits #

rotateR :: VkPipelineViewportStateCreateFlagBits -> Int -> VkPipelineViewportStateCreateFlagBits #

popCount :: VkPipelineViewportStateCreateFlagBits -> Int #

FiniteBits VkPipelineViewportStateCreateFlagBits Source # 
type Rep VkPipelineViewportStateCreateFlagBits Source # 
type Rep VkPipelineViewportStateCreateFlagBits = D1 (MetaData "VkPipelineViewportStateCreateFlagBits" "Graphics.Vulkan.Types.Enum.Pipeline" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkPipelineViewportStateCreateFlagBits" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkQueryControlBitmask a Source #

Instances

Bounded (VkQueryControlBitmask FlagMask) Source # 
Enum (VkQueryControlBitmask FlagMask) Source # 
Eq (VkQueryControlBitmask a) Source # 
Integral (VkQueryControlBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkQueryControlBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkQueryControlBitmask a -> c (VkQueryControlBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkQueryControlBitmask a) #

toConstr :: VkQueryControlBitmask a -> Constr #

dataTypeOf :: VkQueryControlBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkQueryControlBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkQueryControlBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkQueryControlBitmask a -> VkQueryControlBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkQueryControlBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkQueryControlBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkQueryControlBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkQueryControlBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkQueryControlBitmask a -> m (VkQueryControlBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkQueryControlBitmask a -> m (VkQueryControlBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkQueryControlBitmask a -> m (VkQueryControlBitmask a) #

Num (VkQueryControlBitmask FlagMask) Source # 
Ord (VkQueryControlBitmask a) Source # 
Read (VkQueryControlBitmask a) Source # 
Real (VkQueryControlBitmask FlagMask) Source # 
Show (VkQueryControlBitmask a) Source # 
Generic (VkQueryControlBitmask a) Source # 
Storable (VkQueryControlBitmask a) Source # 
Bits (VkQueryControlBitmask FlagMask) Source # 

Methods

(.&.) :: VkQueryControlBitmask FlagMask -> VkQueryControlBitmask FlagMask -> VkQueryControlBitmask FlagMask #

(.|.) :: VkQueryControlBitmask FlagMask -> VkQueryControlBitmask FlagMask -> VkQueryControlBitmask FlagMask #

xor :: VkQueryControlBitmask FlagMask -> VkQueryControlBitmask FlagMask -> VkQueryControlBitmask FlagMask #

complement :: VkQueryControlBitmask FlagMask -> VkQueryControlBitmask FlagMask #

shift :: VkQueryControlBitmask FlagMask -> Int -> VkQueryControlBitmask FlagMask #

rotate :: VkQueryControlBitmask FlagMask -> Int -> VkQueryControlBitmask FlagMask #

zeroBits :: VkQueryControlBitmask FlagMask #

bit :: Int -> VkQueryControlBitmask FlagMask #

setBit :: VkQueryControlBitmask FlagMask -> Int -> VkQueryControlBitmask FlagMask #

clearBit :: VkQueryControlBitmask FlagMask -> Int -> VkQueryControlBitmask FlagMask #

complementBit :: VkQueryControlBitmask FlagMask -> Int -> VkQueryControlBitmask FlagMask #

testBit :: VkQueryControlBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkQueryControlBitmask FlagMask -> Maybe Int #

bitSize :: VkQueryControlBitmask FlagMask -> Int #

isSigned :: VkQueryControlBitmask FlagMask -> Bool #

shiftL :: VkQueryControlBitmask FlagMask -> Int -> VkQueryControlBitmask FlagMask #

unsafeShiftL :: VkQueryControlBitmask FlagMask -> Int -> VkQueryControlBitmask FlagMask #

shiftR :: VkQueryControlBitmask FlagMask -> Int -> VkQueryControlBitmask FlagMask #

unsafeShiftR :: VkQueryControlBitmask FlagMask -> Int -> VkQueryControlBitmask FlagMask #

rotateL :: VkQueryControlBitmask FlagMask -> Int -> VkQueryControlBitmask FlagMask #

rotateR :: VkQueryControlBitmask FlagMask -> Int -> VkQueryControlBitmask FlagMask #

popCount :: VkQueryControlBitmask FlagMask -> Int #

FiniteBits (VkQueryControlBitmask FlagMask) Source # 
type Rep (VkQueryControlBitmask a) Source # 
type Rep (VkQueryControlBitmask a) = D1 (MetaData "VkQueryControlBitmask" "Graphics.Vulkan.Types.Enum.Query" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkQueryControlBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

pattern VK_QUERY_CONTROL_PRECISE_BIT :: forall a. VkQueryControlBitmask a Source #

Require precise results to be collected by the query

bitpos = 0

newtype VkQueryPipelineStatisticBitmask a Source #

Instances

Bounded (VkQueryPipelineStatisticBitmask FlagMask) Source # 
Enum (VkQueryPipelineStatisticBitmask FlagMask) Source # 
Eq (VkQueryPipelineStatisticBitmask a) Source # 
Integral (VkQueryPipelineStatisticBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkQueryPipelineStatisticBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkQueryPipelineStatisticBitmask a -> c (VkQueryPipelineStatisticBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkQueryPipelineStatisticBitmask a) #

toConstr :: VkQueryPipelineStatisticBitmask a -> Constr #

dataTypeOf :: VkQueryPipelineStatisticBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkQueryPipelineStatisticBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkQueryPipelineStatisticBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkQueryPipelineStatisticBitmask a -> VkQueryPipelineStatisticBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkQueryPipelineStatisticBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkQueryPipelineStatisticBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkQueryPipelineStatisticBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkQueryPipelineStatisticBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkQueryPipelineStatisticBitmask a -> m (VkQueryPipelineStatisticBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkQueryPipelineStatisticBitmask a -> m (VkQueryPipelineStatisticBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkQueryPipelineStatisticBitmask a -> m (VkQueryPipelineStatisticBitmask a) #

Num (VkQueryPipelineStatisticBitmask FlagMask) Source # 
Ord (VkQueryPipelineStatisticBitmask a) Source # 
Read (VkQueryPipelineStatisticBitmask a) Source # 
Real (VkQueryPipelineStatisticBitmask FlagMask) Source # 
Show (VkQueryPipelineStatisticBitmask a) Source # 
Generic (VkQueryPipelineStatisticBitmask a) Source # 
Storable (VkQueryPipelineStatisticBitmask a) Source # 
Bits (VkQueryPipelineStatisticBitmask FlagMask) Source # 

Methods

(.&.) :: VkQueryPipelineStatisticBitmask FlagMask -> VkQueryPipelineStatisticBitmask FlagMask -> VkQueryPipelineStatisticBitmask FlagMask #

(.|.) :: VkQueryPipelineStatisticBitmask FlagMask -> VkQueryPipelineStatisticBitmask FlagMask -> VkQueryPipelineStatisticBitmask FlagMask #

xor :: VkQueryPipelineStatisticBitmask FlagMask -> VkQueryPipelineStatisticBitmask FlagMask -> VkQueryPipelineStatisticBitmask FlagMask #

complement :: VkQueryPipelineStatisticBitmask FlagMask -> VkQueryPipelineStatisticBitmask FlagMask #

shift :: VkQueryPipelineStatisticBitmask FlagMask -> Int -> VkQueryPipelineStatisticBitmask FlagMask #

rotate :: VkQueryPipelineStatisticBitmask FlagMask -> Int -> VkQueryPipelineStatisticBitmask FlagMask #

zeroBits :: VkQueryPipelineStatisticBitmask FlagMask #

bit :: Int -> VkQueryPipelineStatisticBitmask FlagMask #

setBit :: VkQueryPipelineStatisticBitmask FlagMask -> Int -> VkQueryPipelineStatisticBitmask FlagMask #

clearBit :: VkQueryPipelineStatisticBitmask FlagMask -> Int -> VkQueryPipelineStatisticBitmask FlagMask #

complementBit :: VkQueryPipelineStatisticBitmask FlagMask -> Int -> VkQueryPipelineStatisticBitmask FlagMask #

testBit :: VkQueryPipelineStatisticBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkQueryPipelineStatisticBitmask FlagMask -> Maybe Int #

bitSize :: VkQueryPipelineStatisticBitmask FlagMask -> Int #

isSigned :: VkQueryPipelineStatisticBitmask FlagMask -> Bool #

shiftL :: VkQueryPipelineStatisticBitmask FlagMask -> Int -> VkQueryPipelineStatisticBitmask FlagMask #

unsafeShiftL :: VkQueryPipelineStatisticBitmask FlagMask -> Int -> VkQueryPipelineStatisticBitmask FlagMask #

shiftR :: VkQueryPipelineStatisticBitmask FlagMask -> Int -> VkQueryPipelineStatisticBitmask FlagMask #

unsafeShiftR :: VkQueryPipelineStatisticBitmask FlagMask -> Int -> VkQueryPipelineStatisticBitmask FlagMask #

rotateL :: VkQueryPipelineStatisticBitmask FlagMask -> Int -> VkQueryPipelineStatisticBitmask FlagMask #

rotateR :: VkQueryPipelineStatisticBitmask FlagMask -> Int -> VkQueryPipelineStatisticBitmask FlagMask #

popCount :: VkQueryPipelineStatisticBitmask FlagMask -> Int #

FiniteBits (VkQueryPipelineStatisticBitmask FlagMask) Source # 
type Rep (VkQueryPipelineStatisticBitmask a) Source # 
type Rep (VkQueryPipelineStatisticBitmask a) = D1 (MetaData "VkQueryPipelineStatisticBitmask" "Graphics.Vulkan.Types.Enum.Query" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkQueryPipelineStatisticBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkQueryPoolCreateFlagBits Source #

Instances

Bounded VkQueryPoolCreateFlagBits Source # 
Enum VkQueryPoolCreateFlagBits Source # 
Eq VkQueryPoolCreateFlagBits Source # 
Integral VkQueryPoolCreateFlagBits Source # 
Data VkQueryPoolCreateFlagBits Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkQueryPoolCreateFlagBits -> c VkQueryPoolCreateFlagBits #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkQueryPoolCreateFlagBits #

toConstr :: VkQueryPoolCreateFlagBits -> Constr #

dataTypeOf :: VkQueryPoolCreateFlagBits -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkQueryPoolCreateFlagBits) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkQueryPoolCreateFlagBits) #

gmapT :: (forall b. Data b => b -> b) -> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkQueryPoolCreateFlagBits -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkQueryPoolCreateFlagBits -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkQueryPoolCreateFlagBits -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkQueryPoolCreateFlagBits -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkQueryPoolCreateFlagBits -> m VkQueryPoolCreateFlagBits #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkQueryPoolCreateFlagBits -> m VkQueryPoolCreateFlagBits #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkQueryPoolCreateFlagBits -> m VkQueryPoolCreateFlagBits #

Num VkQueryPoolCreateFlagBits Source # 
Ord VkQueryPoolCreateFlagBits Source # 
Read VkQueryPoolCreateFlagBits Source # 
Real VkQueryPoolCreateFlagBits Source # 
Show VkQueryPoolCreateFlagBits Source # 
Generic VkQueryPoolCreateFlagBits Source # 
Storable VkQueryPoolCreateFlagBits Source # 
Bits VkQueryPoolCreateFlagBits Source # 

Methods

(.&.) :: VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits #

(.|.) :: VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits #

xor :: VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits #

complement :: VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits #

shift :: VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits #

rotate :: VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits #

zeroBits :: VkQueryPoolCreateFlagBits #

bit :: Int -> VkQueryPoolCreateFlagBits #

setBit :: VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits #

clearBit :: VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits #

complementBit :: VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits #

testBit :: VkQueryPoolCreateFlagBits -> Int -> Bool #

bitSizeMaybe :: VkQueryPoolCreateFlagBits -> Maybe Int #

bitSize :: VkQueryPoolCreateFlagBits -> Int #

isSigned :: VkQueryPoolCreateFlagBits -> Bool #

shiftL :: VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits #

unsafeShiftL :: VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits #

shiftR :: VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits #

unsafeShiftR :: VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits #

rotateL :: VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits #

rotateR :: VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits #

popCount :: VkQueryPoolCreateFlagBits -> Int #

FiniteBits VkQueryPoolCreateFlagBits Source # 
type Rep VkQueryPoolCreateFlagBits Source # 
type Rep VkQueryPoolCreateFlagBits = D1 (MetaData "VkQueryPoolCreateFlagBits" "Graphics.Vulkan.Types.Enum.Query" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkQueryPoolCreateFlagBits" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkQueryResultBitmask a Source #

Instances

Bounded (VkQueryResultBitmask FlagMask) Source # 
Enum (VkQueryResultBitmask FlagMask) Source # 
Eq (VkQueryResultBitmask a) Source # 
Integral (VkQueryResultBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkQueryResultBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkQueryResultBitmask a -> c (VkQueryResultBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkQueryResultBitmask a) #

toConstr :: VkQueryResultBitmask a -> Constr #

dataTypeOf :: VkQueryResultBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkQueryResultBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkQueryResultBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkQueryResultBitmask a -> VkQueryResultBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkQueryResultBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkQueryResultBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkQueryResultBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkQueryResultBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkQueryResultBitmask a -> m (VkQueryResultBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkQueryResultBitmask a -> m (VkQueryResultBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkQueryResultBitmask a -> m (VkQueryResultBitmask a) #

Num (VkQueryResultBitmask FlagMask) Source # 
Ord (VkQueryResultBitmask a) Source # 
Read (VkQueryResultBitmask a) Source # 
Real (VkQueryResultBitmask FlagMask) Source # 
Show (VkQueryResultBitmask a) Source # 
Generic (VkQueryResultBitmask a) Source # 
Storable (VkQueryResultBitmask a) Source # 
Bits (VkQueryResultBitmask FlagMask) Source # 

Methods

(.&.) :: VkQueryResultBitmask FlagMask -> VkQueryResultBitmask FlagMask -> VkQueryResultBitmask FlagMask #

(.|.) :: VkQueryResultBitmask FlagMask -> VkQueryResultBitmask FlagMask -> VkQueryResultBitmask FlagMask #

xor :: VkQueryResultBitmask FlagMask -> VkQueryResultBitmask FlagMask -> VkQueryResultBitmask FlagMask #

complement :: VkQueryResultBitmask FlagMask -> VkQueryResultBitmask FlagMask #

shift :: VkQueryResultBitmask FlagMask -> Int -> VkQueryResultBitmask FlagMask #

rotate :: VkQueryResultBitmask FlagMask -> Int -> VkQueryResultBitmask FlagMask #

zeroBits :: VkQueryResultBitmask FlagMask #

bit :: Int -> VkQueryResultBitmask FlagMask #

setBit :: VkQueryResultBitmask FlagMask -> Int -> VkQueryResultBitmask FlagMask #

clearBit :: VkQueryResultBitmask FlagMask -> Int -> VkQueryResultBitmask FlagMask #

complementBit :: VkQueryResultBitmask FlagMask -> Int -> VkQueryResultBitmask FlagMask #

testBit :: VkQueryResultBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkQueryResultBitmask FlagMask -> Maybe Int #

bitSize :: VkQueryResultBitmask FlagMask -> Int #

isSigned :: VkQueryResultBitmask FlagMask -> Bool #

shiftL :: VkQueryResultBitmask FlagMask -> Int -> VkQueryResultBitmask FlagMask #

unsafeShiftL :: VkQueryResultBitmask FlagMask -> Int -> VkQueryResultBitmask FlagMask #

shiftR :: VkQueryResultBitmask FlagMask -> Int -> VkQueryResultBitmask FlagMask #

unsafeShiftR :: VkQueryResultBitmask FlagMask -> Int -> VkQueryResultBitmask FlagMask #

rotateL :: VkQueryResultBitmask FlagMask -> Int -> VkQueryResultBitmask FlagMask #

rotateR :: VkQueryResultBitmask FlagMask -> Int -> VkQueryResultBitmask FlagMask #

popCount :: VkQueryResultBitmask FlagMask -> Int #

FiniteBits (VkQueryResultBitmask FlagMask) Source # 
type Rep (VkQueryResultBitmask a) Source # 
type Rep (VkQueryResultBitmask a) = D1 (MetaData "VkQueryResultBitmask" "Graphics.Vulkan.Types.Enum.Query" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkQueryResultBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

pattern VK_QUERY_RESULT_64_BIT :: forall a. VkQueryResultBitmask a Source #

Results of the queries are written to the destination buffer as 64-bit values

bitpos = 0

pattern VK_QUERY_RESULT_WAIT_BIT :: forall a. VkQueryResultBitmask a Source #

Results of the queries are waited on before proceeding with the result copy

bitpos = 1

pattern VK_QUERY_RESULT_WITH_AVAILABILITY_BIT :: forall a. VkQueryResultBitmask a Source #

Besides the results of the query, the availability of the results is also written

bitpos = 2

pattern VK_QUERY_RESULT_PARTIAL_BIT :: forall a. VkQueryResultBitmask a Source #

Copy the partial results of the query even if the final results are not available

bitpos = 3

newtype VkQueryType Source #

Constructors

VkQueryType Int32 

Instances

Bounded VkQueryType Source # 
Enum VkQueryType Source # 
Eq VkQueryType Source # 
Data VkQueryType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkQueryType -> c VkQueryType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkQueryType #

toConstr :: VkQueryType -> Constr #

dataTypeOf :: VkQueryType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkQueryType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkQueryType) #

gmapT :: (forall b. Data b => b -> b) -> VkQueryType -> VkQueryType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkQueryType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkQueryType -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkQueryType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkQueryType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkQueryType -> m VkQueryType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkQueryType -> m VkQueryType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkQueryType -> m VkQueryType #

Num VkQueryType Source # 
Ord VkQueryType Source # 
Read VkQueryType Source # 
Show VkQueryType Source # 
Generic VkQueryType Source # 

Associated Types

type Rep VkQueryType :: * -> * #

Storable VkQueryType Source # 
type Rep VkQueryType Source # 
type Rep VkQueryType = D1 (MetaData "VkQueryType" "Graphics.Vulkan.Types.Enum.Query" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkQueryType" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

data VkRect2D Source #

typedef struct VkRect2D {
    VkOffset2D     offset;
    VkExtent2D     extent;
} VkRect2D;

VkRect2D registry at www.khronos.org

Constructors

VkRect2D# Addr# ByteArray# 

Instances

Eq VkRect2D Source # 
Ord VkRect2D Source # 
Show VkRect2D Source # 
Storable VkRect2D Source # 
VulkanMarshalPrim VkRect2D Source # 
VulkanMarshal VkRect2D Source # 
CanWriteField "extent" VkRect2D Source # 

Methods

writeField :: Ptr VkRect2D -> FieldType "extent" VkRect2D -> IO () Source #

CanWriteField "offset" VkRect2D Source # 

Methods

writeField :: Ptr VkRect2D -> FieldType "offset" VkRect2D -> IO () Source #

CanReadField "extent" VkRect2D Source # 
CanReadField "offset" VkRect2D Source # 
HasField "extent" VkRect2D Source # 

Associated Types

type FieldType ("extent" :: Symbol) VkRect2D :: Type Source #

type FieldOptional ("extent" :: Symbol) VkRect2D :: Bool Source #

type FieldOffset ("extent" :: Symbol) VkRect2D :: Nat Source #

type FieldIsArray ("extent" :: Symbol) VkRect2D :: Bool Source #

HasField "offset" VkRect2D Source # 

Associated Types

type FieldType ("offset" :: Symbol) VkRect2D :: Type Source #

type FieldOptional ("offset" :: Symbol) VkRect2D :: Bool Source #

type FieldOffset ("offset" :: Symbol) VkRect2D :: Nat Source #

type FieldIsArray ("offset" :: Symbol) VkRect2D :: Bool Source #

type StructFields VkRect2D Source # 
type StructFields VkRect2D = (:) Symbol "offset" ((:) Symbol "extent" ([] Symbol))
type CUnionType VkRect2D Source # 
type ReturnedOnly VkRect2D Source # 
type StructExtends VkRect2D Source # 
type FieldType "extent" VkRect2D Source # 
type FieldType "extent" VkRect2D = VkExtent2D
type FieldType "offset" VkRect2D Source # 
type FieldType "offset" VkRect2D = VkOffset2D
type FieldOptional "extent" VkRect2D Source # 
type FieldOptional "extent" VkRect2D = False
type FieldOptional "offset" VkRect2D Source # 
type FieldOptional "offset" VkRect2D = False
type FieldOffset "extent" VkRect2D Source # 
type FieldOffset "extent" VkRect2D = 8
type FieldOffset "offset" VkRect2D Source # 
type FieldOffset "offset" VkRect2D = 0
type FieldIsArray "extent" VkRect2D Source # 
type FieldIsArray "extent" VkRect2D = False
type FieldIsArray "offset" VkRect2D Source # 
type FieldIsArray "offset" VkRect2D = False

data VkRectLayerKHR Source #

typedef struct VkRectLayerKHR {
    VkOffset2D                       offset;
    VkExtent2D                       extent;
    uint32_t                         layer;
} VkRectLayerKHR;

VkRectLayerKHR registry at www.khronos.org

Instances

Eq VkRectLayerKHR Source # 
Ord VkRectLayerKHR Source # 
Show VkRectLayerKHR Source # 
Storable VkRectLayerKHR Source # 
VulkanMarshalPrim VkRectLayerKHR Source # 
VulkanMarshal VkRectLayerKHR Source # 
CanWriteField "extent" VkRectLayerKHR Source # 
CanWriteField "layer" VkRectLayerKHR Source # 
CanWriteField "offset" VkRectLayerKHR Source # 
CanReadField "extent" VkRectLayerKHR Source # 
CanReadField "layer" VkRectLayerKHR Source # 
CanReadField "offset" VkRectLayerKHR Source # 
HasField "extent" VkRectLayerKHR Source # 

Associated Types

type FieldType ("extent" :: Symbol) VkRectLayerKHR :: Type Source #

type FieldOptional ("extent" :: Symbol) VkRectLayerKHR :: Bool Source #

type FieldOffset ("extent" :: Symbol) VkRectLayerKHR :: Nat Source #

type FieldIsArray ("extent" :: Symbol) VkRectLayerKHR :: Bool Source #

HasField "layer" VkRectLayerKHR Source # 
HasField "offset" VkRectLayerKHR Source # 

Associated Types

type FieldType ("offset" :: Symbol) VkRectLayerKHR :: Type Source #

type FieldOptional ("offset" :: Symbol) VkRectLayerKHR :: Bool Source #

type FieldOffset ("offset" :: Symbol) VkRectLayerKHR :: Nat Source #

type FieldIsArray ("offset" :: Symbol) VkRectLayerKHR :: Bool Source #

type StructFields VkRectLayerKHR Source # 
type StructFields VkRectLayerKHR = (:) Symbol "offset" ((:) Symbol "extent" ((:) Symbol "layer" ([] Symbol)))
type CUnionType VkRectLayerKHR Source # 
type ReturnedOnly VkRectLayerKHR Source # 
type StructExtends VkRectLayerKHR Source # 
type FieldType "extent" VkRectLayerKHR Source # 
type FieldType "layer" VkRectLayerKHR Source # 
type FieldType "offset" VkRectLayerKHR Source # 
type FieldOptional "extent" VkRectLayerKHR Source # 
type FieldOptional "layer" VkRectLayerKHR Source # 
type FieldOptional "offset" VkRectLayerKHR Source # 
type FieldOffset "extent" VkRectLayerKHR Source # 
type FieldOffset "extent" VkRectLayerKHR = 8
type FieldOffset "layer" VkRectLayerKHR Source # 
type FieldOffset "layer" VkRectLayerKHR = 16
type FieldOffset "offset" VkRectLayerKHR Source # 
type FieldOffset "offset" VkRectLayerKHR = 0
type FieldIsArray "extent" VkRectLayerKHR Source # 
type FieldIsArray "layer" VkRectLayerKHR Source # 
type FieldIsArray "offset" VkRectLayerKHR Source # 

data VkRenderPassBeginInfo Source #

typedef struct VkRenderPassBeginInfo {
    VkStructureType sType;
    const void*            pNext;
    VkRenderPass           renderPass;
    VkFramebuffer          framebuffer;
    VkRect2D               renderArea;
    uint32_t               clearValueCount;
    const VkClearValue*    pClearValues;
} VkRenderPassBeginInfo;

VkRenderPassBeginInfo registry at www.khronos.org

Instances

Eq VkRenderPassBeginInfo Source # 
Ord VkRenderPassBeginInfo Source # 
Show VkRenderPassBeginInfo Source # 
Storable VkRenderPassBeginInfo Source # 
VulkanMarshalPrim VkRenderPassBeginInfo Source # 
VulkanMarshal VkRenderPassBeginInfo Source # 
CanWriteField "clearValueCount" VkRenderPassBeginInfo Source # 
CanWriteField "framebuffer" VkRenderPassBeginInfo Source # 
CanWriteField "pClearValues" VkRenderPassBeginInfo Source # 
CanWriteField "pNext" VkRenderPassBeginInfo Source # 
CanWriteField "renderArea" VkRenderPassBeginInfo Source # 
CanWriteField "renderPass" VkRenderPassBeginInfo Source # 
CanWriteField "sType" VkRenderPassBeginInfo Source # 
CanReadField "clearValueCount" VkRenderPassBeginInfo Source # 
CanReadField "framebuffer" VkRenderPassBeginInfo Source # 
CanReadField "pClearValues" VkRenderPassBeginInfo Source # 
CanReadField "pNext" VkRenderPassBeginInfo Source # 
CanReadField "renderArea" VkRenderPassBeginInfo Source # 
CanReadField "renderPass" VkRenderPassBeginInfo Source # 
CanReadField "sType" VkRenderPassBeginInfo Source # 
HasField "clearValueCount" VkRenderPassBeginInfo Source # 

Associated Types

type FieldType ("clearValueCount" :: Symbol) VkRenderPassBeginInfo :: Type Source #

type FieldOptional ("clearValueCount" :: Symbol) VkRenderPassBeginInfo :: Bool Source #

type FieldOffset ("clearValueCount" :: Symbol) VkRenderPassBeginInfo :: Nat Source #

type FieldIsArray ("clearValueCount" :: Symbol) VkRenderPassBeginInfo :: Bool Source #

HasField "framebuffer" VkRenderPassBeginInfo Source # 

Associated Types

type FieldType ("framebuffer" :: Symbol) VkRenderPassBeginInfo :: Type Source #

type FieldOptional ("framebuffer" :: Symbol) VkRenderPassBeginInfo :: Bool Source #

type FieldOffset ("framebuffer" :: Symbol) VkRenderPassBeginInfo :: Nat Source #

type FieldIsArray ("framebuffer" :: Symbol) VkRenderPassBeginInfo :: Bool Source #

HasField "pClearValues" VkRenderPassBeginInfo Source # 

Associated Types

type FieldType ("pClearValues" :: Symbol) VkRenderPassBeginInfo :: Type Source #

type FieldOptional ("pClearValues" :: Symbol) VkRenderPassBeginInfo :: Bool Source #

type FieldOffset ("pClearValues" :: Symbol) VkRenderPassBeginInfo :: Nat Source #

type FieldIsArray ("pClearValues" :: Symbol) VkRenderPassBeginInfo :: Bool Source #

HasField "pNext" VkRenderPassBeginInfo Source # 
HasField "renderArea" VkRenderPassBeginInfo Source # 
HasField "renderPass" VkRenderPassBeginInfo Source # 
HasField "sType" VkRenderPassBeginInfo Source # 
type StructFields VkRenderPassBeginInfo Source # 
type StructFields VkRenderPassBeginInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "renderPass" ((:) Symbol "framebuffer" ((:) Symbol "renderArea" ((:) Symbol "clearValueCount" ((:) Symbol "pClearValues" ([] Symbol)))))))
type CUnionType VkRenderPassBeginInfo Source # 
type ReturnedOnly VkRenderPassBeginInfo Source # 
type StructExtends VkRenderPassBeginInfo Source # 
type FieldType "clearValueCount" VkRenderPassBeginInfo Source # 
type FieldType "clearValueCount" VkRenderPassBeginInfo = Word32
type FieldType "framebuffer" VkRenderPassBeginInfo Source # 
type FieldType "pClearValues" VkRenderPassBeginInfo Source # 
type FieldType "pNext" VkRenderPassBeginInfo Source # 
type FieldType "renderArea" VkRenderPassBeginInfo Source # 
type FieldType "renderPass" VkRenderPassBeginInfo Source # 
type FieldType "sType" VkRenderPassBeginInfo Source # 
type FieldOptional "clearValueCount" VkRenderPassBeginInfo Source # 
type FieldOptional "clearValueCount" VkRenderPassBeginInfo = True
type FieldOptional "framebuffer" VkRenderPassBeginInfo Source # 
type FieldOptional "pClearValues" VkRenderPassBeginInfo Source # 
type FieldOptional "pNext" VkRenderPassBeginInfo Source # 
type FieldOptional "renderArea" VkRenderPassBeginInfo Source # 
type FieldOptional "renderPass" VkRenderPassBeginInfo Source # 
type FieldOptional "sType" VkRenderPassBeginInfo Source # 
type FieldOffset "clearValueCount" VkRenderPassBeginInfo Source # 
type FieldOffset "clearValueCount" VkRenderPassBeginInfo = 48
type FieldOffset "framebuffer" VkRenderPassBeginInfo Source # 
type FieldOffset "framebuffer" VkRenderPassBeginInfo = 24
type FieldOffset "pClearValues" VkRenderPassBeginInfo Source # 
type FieldOffset "pClearValues" VkRenderPassBeginInfo = 56
type FieldOffset "pNext" VkRenderPassBeginInfo Source # 
type FieldOffset "renderArea" VkRenderPassBeginInfo Source # 
type FieldOffset "renderArea" VkRenderPassBeginInfo = 32
type FieldOffset "renderPass" VkRenderPassBeginInfo Source # 
type FieldOffset "renderPass" VkRenderPassBeginInfo = 16
type FieldOffset "sType" VkRenderPassBeginInfo Source # 
type FieldIsArray "clearValueCount" VkRenderPassBeginInfo Source # 
type FieldIsArray "clearValueCount" VkRenderPassBeginInfo = False
type FieldIsArray "framebuffer" VkRenderPassBeginInfo Source # 
type FieldIsArray "pClearValues" VkRenderPassBeginInfo Source # 
type FieldIsArray "pNext" VkRenderPassBeginInfo Source # 
type FieldIsArray "renderArea" VkRenderPassBeginInfo Source # 
type FieldIsArray "renderPass" VkRenderPassBeginInfo Source # 
type FieldIsArray "sType" VkRenderPassBeginInfo Source # 

data VkRenderPassCreateInfo Source #

typedef struct VkRenderPassCreateInfo {
    VkStructureType sType;
    const void*            pNext;
    VkRenderPassCreateFlags    flags;
    uint32_t   attachmentCount;
    const VkAttachmentDescription* pAttachments;
    uint32_t               subpassCount;
    const VkSubpassDescription* pSubpasses;
    uint32_t       dependencyCount;
    const VkSubpassDependency* pDependencies;
} VkRenderPassCreateInfo;

VkRenderPassCreateInfo registry at www.khronos.org

Instances

Eq VkRenderPassCreateInfo Source # 
Ord VkRenderPassCreateInfo Source # 
Show VkRenderPassCreateInfo Source # 
Storable VkRenderPassCreateInfo Source # 
VulkanMarshalPrim VkRenderPassCreateInfo Source # 
VulkanMarshal VkRenderPassCreateInfo Source # 
CanWriteField "attachmentCount" VkRenderPassCreateInfo Source # 
CanWriteField "dependencyCount" VkRenderPassCreateInfo Source # 
CanWriteField "flags" VkRenderPassCreateInfo Source # 
CanWriteField "pAttachments" VkRenderPassCreateInfo Source # 
CanWriteField "pDependencies" VkRenderPassCreateInfo Source # 
CanWriteField "pNext" VkRenderPassCreateInfo Source # 
CanWriteField "pSubpasses" VkRenderPassCreateInfo Source # 
CanWriteField "sType" VkRenderPassCreateInfo Source # 
CanWriteField "subpassCount" VkRenderPassCreateInfo Source # 
CanReadField "attachmentCount" VkRenderPassCreateInfo Source # 
CanReadField "dependencyCount" VkRenderPassCreateInfo Source # 
CanReadField "flags" VkRenderPassCreateInfo Source # 
CanReadField "pAttachments" VkRenderPassCreateInfo Source # 
CanReadField "pDependencies" VkRenderPassCreateInfo Source # 
CanReadField "pNext" VkRenderPassCreateInfo Source # 
CanReadField "pSubpasses" VkRenderPassCreateInfo Source # 
CanReadField "sType" VkRenderPassCreateInfo Source # 
CanReadField "subpassCount" VkRenderPassCreateInfo Source # 
HasField "attachmentCount" VkRenderPassCreateInfo Source # 

Associated Types

type FieldType ("attachmentCount" :: Symbol) VkRenderPassCreateInfo :: Type Source #

type FieldOptional ("attachmentCount" :: Symbol) VkRenderPassCreateInfo :: Bool Source #

type FieldOffset ("attachmentCount" :: Symbol) VkRenderPassCreateInfo :: Nat Source #

type FieldIsArray ("attachmentCount" :: Symbol) VkRenderPassCreateInfo :: Bool Source #

HasField "dependencyCount" VkRenderPassCreateInfo Source # 

Associated Types

type FieldType ("dependencyCount" :: Symbol) VkRenderPassCreateInfo :: Type Source #

type FieldOptional ("dependencyCount" :: Symbol) VkRenderPassCreateInfo :: Bool Source #

type FieldOffset ("dependencyCount" :: Symbol) VkRenderPassCreateInfo :: Nat Source #

type FieldIsArray ("dependencyCount" :: Symbol) VkRenderPassCreateInfo :: Bool Source #

HasField "flags" VkRenderPassCreateInfo Source # 
HasField "pAttachments" VkRenderPassCreateInfo Source # 

Associated Types

type FieldType ("pAttachments" :: Symbol) VkRenderPassCreateInfo :: Type Source #

type FieldOptional ("pAttachments" :: Symbol) VkRenderPassCreateInfo :: Bool Source #

type FieldOffset ("pAttachments" :: Symbol) VkRenderPassCreateInfo :: Nat Source #

type FieldIsArray ("pAttachments" :: Symbol) VkRenderPassCreateInfo :: Bool Source #

HasField "pDependencies" VkRenderPassCreateInfo Source # 

Associated Types

type FieldType ("pDependencies" :: Symbol) VkRenderPassCreateInfo :: Type Source #

type FieldOptional ("pDependencies" :: Symbol) VkRenderPassCreateInfo :: Bool Source #

type FieldOffset ("pDependencies" :: Symbol) VkRenderPassCreateInfo :: Nat Source #

type FieldIsArray ("pDependencies" :: Symbol) VkRenderPassCreateInfo :: Bool Source #

HasField "pNext" VkRenderPassCreateInfo Source # 
HasField "pSubpasses" VkRenderPassCreateInfo Source # 
HasField "sType" VkRenderPassCreateInfo Source # 
HasField "subpassCount" VkRenderPassCreateInfo Source # 

Associated Types

type FieldType ("subpassCount" :: Symbol) VkRenderPassCreateInfo :: Type Source #

type FieldOptional ("subpassCount" :: Symbol) VkRenderPassCreateInfo :: Bool Source #

type FieldOffset ("subpassCount" :: Symbol) VkRenderPassCreateInfo :: Nat Source #

type FieldIsArray ("subpassCount" :: Symbol) VkRenderPassCreateInfo :: Bool Source #

type StructFields VkRenderPassCreateInfo Source # 
type StructFields VkRenderPassCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "attachmentCount" ((:) Symbol "pAttachments" ((:) Symbol "subpassCount" ((:) Symbol "pSubpasses" ((:) Symbol "dependencyCount" ((:) Symbol "pDependencies" ([] Symbol)))))))))
type CUnionType VkRenderPassCreateInfo Source # 
type ReturnedOnly VkRenderPassCreateInfo Source # 
type StructExtends VkRenderPassCreateInfo Source # 
type FieldType "attachmentCount" VkRenderPassCreateInfo Source # 
type FieldType "attachmentCount" VkRenderPassCreateInfo = Word32
type FieldType "dependencyCount" VkRenderPassCreateInfo Source # 
type FieldType "dependencyCount" VkRenderPassCreateInfo = Word32
type FieldType "flags" VkRenderPassCreateInfo Source # 
type FieldType "pAttachments" VkRenderPassCreateInfo Source # 
type FieldType "pDependencies" VkRenderPassCreateInfo Source # 
type FieldType "pNext" VkRenderPassCreateInfo Source # 
type FieldType "pSubpasses" VkRenderPassCreateInfo Source # 
type FieldType "sType" VkRenderPassCreateInfo Source # 
type FieldType "subpassCount" VkRenderPassCreateInfo Source # 
type FieldOptional "attachmentCount" VkRenderPassCreateInfo Source # 
type FieldOptional "attachmentCount" VkRenderPassCreateInfo = True
type FieldOptional "dependencyCount" VkRenderPassCreateInfo Source # 
type FieldOptional "dependencyCount" VkRenderPassCreateInfo = True
type FieldOptional "flags" VkRenderPassCreateInfo Source # 
type FieldOptional "pAttachments" VkRenderPassCreateInfo Source # 
type FieldOptional "pDependencies" VkRenderPassCreateInfo Source # 
type FieldOptional "pNext" VkRenderPassCreateInfo Source # 
type FieldOptional "pSubpasses" VkRenderPassCreateInfo Source # 
type FieldOptional "sType" VkRenderPassCreateInfo Source # 
type FieldOptional "subpassCount" VkRenderPassCreateInfo Source # 
type FieldOffset "attachmentCount" VkRenderPassCreateInfo Source # 
type FieldOffset "attachmentCount" VkRenderPassCreateInfo = 20
type FieldOffset "dependencyCount" VkRenderPassCreateInfo Source # 
type FieldOffset "dependencyCount" VkRenderPassCreateInfo = 48
type FieldOffset "flags" VkRenderPassCreateInfo Source # 
type FieldOffset "pAttachments" VkRenderPassCreateInfo Source # 
type FieldOffset "pAttachments" VkRenderPassCreateInfo = 24
type FieldOffset "pDependencies" VkRenderPassCreateInfo Source # 
type FieldOffset "pDependencies" VkRenderPassCreateInfo = 56
type FieldOffset "pNext" VkRenderPassCreateInfo Source # 
type FieldOffset "pSubpasses" VkRenderPassCreateInfo Source # 
type FieldOffset "pSubpasses" VkRenderPassCreateInfo = 40
type FieldOffset "sType" VkRenderPassCreateInfo Source # 
type FieldOffset "subpassCount" VkRenderPassCreateInfo Source # 
type FieldOffset "subpassCount" VkRenderPassCreateInfo = 32
type FieldIsArray "attachmentCount" VkRenderPassCreateInfo Source # 
type FieldIsArray "attachmentCount" VkRenderPassCreateInfo = False
type FieldIsArray "dependencyCount" VkRenderPassCreateInfo Source # 
type FieldIsArray "dependencyCount" VkRenderPassCreateInfo = False
type FieldIsArray "flags" VkRenderPassCreateInfo Source # 
type FieldIsArray "pAttachments" VkRenderPassCreateInfo Source # 
type FieldIsArray "pDependencies" VkRenderPassCreateInfo Source # 
type FieldIsArray "pNext" VkRenderPassCreateInfo Source # 
type FieldIsArray "pSubpasses" VkRenderPassCreateInfo Source # 
type FieldIsArray "sType" VkRenderPassCreateInfo Source # 
type FieldIsArray "subpassCount" VkRenderPassCreateInfo Source # 

data VkRenderPassInputAttachmentAspectCreateInfo Source #

typedef struct VkRenderPassInputAttachmentAspectCreateInfo {
    VkStructureType sType;
    const void*                     pNext;
    uint32_t                        aspectReferenceCount;
    const VkInputAttachmentAspectReference* pAspectReferences;
} VkRenderPassInputAttachmentAspectCreateInfo;

VkRenderPassInputAttachmentAspectCreateInfo registry at www.khronos.org

Instances

Eq VkRenderPassInputAttachmentAspectCreateInfo Source # 
Ord VkRenderPassInputAttachmentAspectCreateInfo Source # 
Show VkRenderPassInputAttachmentAspectCreateInfo Source # 
Storable VkRenderPassInputAttachmentAspectCreateInfo Source # 
VulkanMarshalPrim VkRenderPassInputAttachmentAspectCreateInfo Source # 
VulkanMarshal VkRenderPassInputAttachmentAspectCreateInfo Source # 
CanWriteField "aspectReferenceCount" VkRenderPassInputAttachmentAspectCreateInfo Source # 
CanWriteField "pAspectReferences" VkRenderPassInputAttachmentAspectCreateInfo Source # 
CanWriteField "pNext" VkRenderPassInputAttachmentAspectCreateInfo Source # 
CanWriteField "sType" VkRenderPassInputAttachmentAspectCreateInfo Source # 
CanReadField "aspectReferenceCount" VkRenderPassInputAttachmentAspectCreateInfo Source # 
CanReadField "pAspectReferences" VkRenderPassInputAttachmentAspectCreateInfo Source # 
CanReadField "pNext" VkRenderPassInputAttachmentAspectCreateInfo Source # 
CanReadField "sType" VkRenderPassInputAttachmentAspectCreateInfo Source # 
HasField "aspectReferenceCount" VkRenderPassInputAttachmentAspectCreateInfo Source # 
HasField "pAspectReferences" VkRenderPassInputAttachmentAspectCreateInfo Source # 
HasField "pNext" VkRenderPassInputAttachmentAspectCreateInfo Source # 
HasField "sType" VkRenderPassInputAttachmentAspectCreateInfo Source # 
type StructFields VkRenderPassInputAttachmentAspectCreateInfo Source # 
type StructFields VkRenderPassInputAttachmentAspectCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "aspectReferenceCount" ((:) Symbol "pAspectReferences" ([] Symbol))))
type CUnionType VkRenderPassInputAttachmentAspectCreateInfo Source # 
type ReturnedOnly VkRenderPassInputAttachmentAspectCreateInfo Source # 
type StructExtends VkRenderPassInputAttachmentAspectCreateInfo Source # 
type FieldType "aspectReferenceCount" VkRenderPassInputAttachmentAspectCreateInfo Source # 
type FieldType "pAspectReferences" VkRenderPassInputAttachmentAspectCreateInfo Source # 
type FieldType "pNext" VkRenderPassInputAttachmentAspectCreateInfo Source # 
type FieldType "sType" VkRenderPassInputAttachmentAspectCreateInfo Source # 
type FieldOptional "aspectReferenceCount" VkRenderPassInputAttachmentAspectCreateInfo Source # 
type FieldOptional "pAspectReferences" VkRenderPassInputAttachmentAspectCreateInfo Source # 
type FieldOptional "pNext" VkRenderPassInputAttachmentAspectCreateInfo Source # 
type FieldOptional "sType" VkRenderPassInputAttachmentAspectCreateInfo Source # 
type FieldOffset "aspectReferenceCount" VkRenderPassInputAttachmentAspectCreateInfo Source # 
type FieldOffset "pAspectReferences" VkRenderPassInputAttachmentAspectCreateInfo Source # 
type FieldOffset "pNext" VkRenderPassInputAttachmentAspectCreateInfo Source # 
type FieldOffset "sType" VkRenderPassInputAttachmentAspectCreateInfo Source # 
type FieldIsArray "aspectReferenceCount" VkRenderPassInputAttachmentAspectCreateInfo Source # 
type FieldIsArray "pAspectReferences" VkRenderPassInputAttachmentAspectCreateInfo Source # 
type FieldIsArray "pNext" VkRenderPassInputAttachmentAspectCreateInfo Source # 
type FieldIsArray "sType" VkRenderPassInputAttachmentAspectCreateInfo Source # 

data VkRenderPassMultiviewCreateInfo Source #

typedef struct VkRenderPassMultiviewCreateInfo {
    VkStructureType        sType;
    const void*            pNext;
    uint32_t               subpassCount;
    const uint32_t*     pViewMasks;
    uint32_t               dependencyCount;
    const int32_t*   pViewOffsets;
    uint32_t               correlationMaskCount;
    const uint32_t* pCorrelationMasks;
} VkRenderPassMultiviewCreateInfo;

VkRenderPassMultiviewCreateInfo registry at www.khronos.org

Instances

Eq VkRenderPassMultiviewCreateInfo Source # 
Ord VkRenderPassMultiviewCreateInfo Source # 
Show VkRenderPassMultiviewCreateInfo Source # 
Storable VkRenderPassMultiviewCreateInfo Source # 
VulkanMarshalPrim VkRenderPassMultiviewCreateInfo Source # 
VulkanMarshal VkRenderPassMultiviewCreateInfo Source # 
CanWriteField "correlationMaskCount" VkRenderPassMultiviewCreateInfo Source # 
CanWriteField "dependencyCount" VkRenderPassMultiviewCreateInfo Source # 
CanWriteField "pCorrelationMasks" VkRenderPassMultiviewCreateInfo Source # 
CanWriteField "pNext" VkRenderPassMultiviewCreateInfo Source # 
CanWriteField "pViewMasks" VkRenderPassMultiviewCreateInfo Source # 
CanWriteField "pViewOffsets" VkRenderPassMultiviewCreateInfo Source # 
CanWriteField "sType" VkRenderPassMultiviewCreateInfo Source # 
CanWriteField "subpassCount" VkRenderPassMultiviewCreateInfo Source # 
CanReadField "correlationMaskCount" VkRenderPassMultiviewCreateInfo Source # 
CanReadField "dependencyCount" VkRenderPassMultiviewCreateInfo Source # 
CanReadField "pCorrelationMasks" VkRenderPassMultiviewCreateInfo Source # 
CanReadField "pNext" VkRenderPassMultiviewCreateInfo Source # 
CanReadField "pViewMasks" VkRenderPassMultiviewCreateInfo Source # 
CanReadField "pViewOffsets" VkRenderPassMultiviewCreateInfo Source # 
CanReadField "sType" VkRenderPassMultiviewCreateInfo Source # 
CanReadField "subpassCount" VkRenderPassMultiviewCreateInfo Source # 
HasField "correlationMaskCount" VkRenderPassMultiviewCreateInfo Source # 

Associated Types

type FieldType ("correlationMaskCount" :: Symbol) VkRenderPassMultiviewCreateInfo :: Type Source #

type FieldOptional ("correlationMaskCount" :: Symbol) VkRenderPassMultiviewCreateInfo :: Bool Source #

type FieldOffset ("correlationMaskCount" :: Symbol) VkRenderPassMultiviewCreateInfo :: Nat Source #

type FieldIsArray ("correlationMaskCount" :: Symbol) VkRenderPassMultiviewCreateInfo :: Bool Source #

HasField "dependencyCount" VkRenderPassMultiviewCreateInfo Source # 
HasField "pCorrelationMasks" VkRenderPassMultiviewCreateInfo Source # 

Associated Types

type FieldType ("pCorrelationMasks" :: Symbol) VkRenderPassMultiviewCreateInfo :: Type Source #

type FieldOptional ("pCorrelationMasks" :: Symbol) VkRenderPassMultiviewCreateInfo :: Bool Source #

type FieldOffset ("pCorrelationMasks" :: Symbol) VkRenderPassMultiviewCreateInfo :: Nat Source #

type FieldIsArray ("pCorrelationMasks" :: Symbol) VkRenderPassMultiviewCreateInfo :: Bool Source #

HasField "pNext" VkRenderPassMultiviewCreateInfo Source # 
HasField "pViewMasks" VkRenderPassMultiviewCreateInfo Source # 
HasField "pViewOffsets" VkRenderPassMultiviewCreateInfo Source # 
HasField "sType" VkRenderPassMultiviewCreateInfo Source # 
HasField "subpassCount" VkRenderPassMultiviewCreateInfo Source # 
type StructFields VkRenderPassMultiviewCreateInfo Source # 
type StructFields VkRenderPassMultiviewCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "subpassCount" ((:) Symbol "pViewMasks" ((:) Symbol "dependencyCount" ((:) Symbol "pViewOffsets" ((:) Symbol "correlationMaskCount" ((:) Symbol "pCorrelationMasks" ([] Symbol))))))))
type CUnionType VkRenderPassMultiviewCreateInfo Source # 
type ReturnedOnly VkRenderPassMultiviewCreateInfo Source # 
type StructExtends VkRenderPassMultiviewCreateInfo Source # 
type FieldType "correlationMaskCount" VkRenderPassMultiviewCreateInfo Source # 
type FieldType "correlationMaskCount" VkRenderPassMultiviewCreateInfo = Word32
type FieldType "dependencyCount" VkRenderPassMultiviewCreateInfo Source # 
type FieldType "pCorrelationMasks" VkRenderPassMultiviewCreateInfo Source # 
type FieldType "pNext" VkRenderPassMultiviewCreateInfo Source # 
type FieldType "pViewMasks" VkRenderPassMultiviewCreateInfo Source # 
type FieldType "pViewOffsets" VkRenderPassMultiviewCreateInfo Source # 
type FieldType "sType" VkRenderPassMultiviewCreateInfo Source # 
type FieldType "subpassCount" VkRenderPassMultiviewCreateInfo Source # 
type FieldOptional "correlationMaskCount" VkRenderPassMultiviewCreateInfo Source # 
type FieldOptional "correlationMaskCount" VkRenderPassMultiviewCreateInfo = True
type FieldOptional "dependencyCount" VkRenderPassMultiviewCreateInfo Source # 
type FieldOptional "pCorrelationMasks" VkRenderPassMultiviewCreateInfo Source # 
type FieldOptional "pNext" VkRenderPassMultiviewCreateInfo Source # 
type FieldOptional "pViewMasks" VkRenderPassMultiviewCreateInfo Source # 
type FieldOptional "pViewOffsets" VkRenderPassMultiviewCreateInfo Source # 
type FieldOptional "sType" VkRenderPassMultiviewCreateInfo Source # 
type FieldOptional "subpassCount" VkRenderPassMultiviewCreateInfo Source # 
type FieldOffset "correlationMaskCount" VkRenderPassMultiviewCreateInfo Source # 
type FieldOffset "correlationMaskCount" VkRenderPassMultiviewCreateInfo = 48
type FieldOffset "dependencyCount" VkRenderPassMultiviewCreateInfo Source # 
type FieldOffset "dependencyCount" VkRenderPassMultiviewCreateInfo = 32
type FieldOffset "pCorrelationMasks" VkRenderPassMultiviewCreateInfo Source # 
type FieldOffset "pCorrelationMasks" VkRenderPassMultiviewCreateInfo = 56
type FieldOffset "pNext" VkRenderPassMultiviewCreateInfo Source # 
type FieldOffset "pViewMasks" VkRenderPassMultiviewCreateInfo Source # 
type FieldOffset "pViewOffsets" VkRenderPassMultiviewCreateInfo Source # 
type FieldOffset "sType" VkRenderPassMultiviewCreateInfo Source # 
type FieldOffset "subpassCount" VkRenderPassMultiviewCreateInfo Source # 
type FieldIsArray "correlationMaskCount" VkRenderPassMultiviewCreateInfo Source # 
type FieldIsArray "correlationMaskCount" VkRenderPassMultiviewCreateInfo = False
type FieldIsArray "dependencyCount" VkRenderPassMultiviewCreateInfo Source # 
type FieldIsArray "pCorrelationMasks" VkRenderPassMultiviewCreateInfo Source # 
type FieldIsArray "pNext" VkRenderPassMultiviewCreateInfo Source # 
type FieldIsArray "pViewMasks" VkRenderPassMultiviewCreateInfo Source # 
type FieldIsArray "pViewOffsets" VkRenderPassMultiviewCreateInfo Source # 
type FieldIsArray "sType" VkRenderPassMultiviewCreateInfo Source # 
type FieldIsArray "subpassCount" VkRenderPassMultiviewCreateInfo Source # 

data VkRenderPassSampleLocationsBeginInfoEXT Source #

typedef struct VkRenderPassSampleLocationsBeginInfoEXT {
    VkStructureType sType;
    const void*                      pNext;
    uint32_t         attachmentInitialSampleLocationsCount;
    const VkAttachmentSampleLocationsEXT* pAttachmentInitialSampleLocations;
    uint32_t         postSubpassSampleLocationsCount;
    const VkSubpassSampleLocationsEXT* pPostSubpassSampleLocations;
} VkRenderPassSampleLocationsBeginInfoEXT;

VkRenderPassSampleLocationsBeginInfoEXT registry at www.khronos.org

Instances

Eq VkRenderPassSampleLocationsBeginInfoEXT Source # 
Ord VkRenderPassSampleLocationsBeginInfoEXT Source # 
Show VkRenderPassSampleLocationsBeginInfoEXT Source # 
Storable VkRenderPassSampleLocationsBeginInfoEXT Source # 
VulkanMarshalPrim VkRenderPassSampleLocationsBeginInfoEXT Source # 
VulkanMarshal VkRenderPassSampleLocationsBeginInfoEXT Source # 
CanWriteField "attachmentInitialSampleLocationsCount" VkRenderPassSampleLocationsBeginInfoEXT Source # 
CanWriteField "pAttachmentInitialSampleLocations" VkRenderPassSampleLocationsBeginInfoEXT Source # 
CanWriteField "pNext" VkRenderPassSampleLocationsBeginInfoEXT Source # 
CanWriteField "pPostSubpassSampleLocations" VkRenderPassSampleLocationsBeginInfoEXT Source # 
CanWriteField "postSubpassSampleLocationsCount" VkRenderPassSampleLocationsBeginInfoEXT Source # 
CanWriteField "sType" VkRenderPassSampleLocationsBeginInfoEXT Source # 
CanReadField "attachmentInitialSampleLocationsCount" VkRenderPassSampleLocationsBeginInfoEXT Source # 
CanReadField "pAttachmentInitialSampleLocations" VkRenderPassSampleLocationsBeginInfoEXT Source # 
CanReadField "pNext" VkRenderPassSampleLocationsBeginInfoEXT Source # 
CanReadField "pPostSubpassSampleLocations" VkRenderPassSampleLocationsBeginInfoEXT Source # 
CanReadField "postSubpassSampleLocationsCount" VkRenderPassSampleLocationsBeginInfoEXT Source # 
CanReadField "sType" VkRenderPassSampleLocationsBeginInfoEXT Source # 
HasField "attachmentInitialSampleLocationsCount" VkRenderPassSampleLocationsBeginInfoEXT Source # 

Associated Types

type FieldType ("attachmentInitialSampleLocationsCount" :: Symbol) VkRenderPassSampleLocationsBeginInfoEXT :: Type Source #

type FieldOptional ("attachmentInitialSampleLocationsCount" :: Symbol) VkRenderPassSampleLocationsBeginInfoEXT :: Bool Source #

type FieldOffset ("attachmentInitialSampleLocationsCount" :: Symbol) VkRenderPassSampleLocationsBeginInfoEXT :: Nat Source #

type FieldIsArray ("attachmentInitialSampleLocationsCount" :: Symbol) VkRenderPassSampleLocationsBeginInfoEXT :: Bool Source #

HasField "pAttachmentInitialSampleLocations" VkRenderPassSampleLocationsBeginInfoEXT Source # 

Associated Types

type FieldType ("pAttachmentInitialSampleLocations" :: Symbol) VkRenderPassSampleLocationsBeginInfoEXT :: Type Source #

type FieldOptional ("pAttachmentInitialSampleLocations" :: Symbol) VkRenderPassSampleLocationsBeginInfoEXT :: Bool Source #

type FieldOffset ("pAttachmentInitialSampleLocations" :: Symbol) VkRenderPassSampleLocationsBeginInfoEXT :: Nat Source #

type FieldIsArray ("pAttachmentInitialSampleLocations" :: Symbol) VkRenderPassSampleLocationsBeginInfoEXT :: Bool Source #

HasField "pNext" VkRenderPassSampleLocationsBeginInfoEXT Source # 
HasField "pPostSubpassSampleLocations" VkRenderPassSampleLocationsBeginInfoEXT Source # 

Associated Types

type FieldType ("pPostSubpassSampleLocations" :: Symbol) VkRenderPassSampleLocationsBeginInfoEXT :: Type Source #

type FieldOptional ("pPostSubpassSampleLocations" :: Symbol) VkRenderPassSampleLocationsBeginInfoEXT :: Bool Source #

type FieldOffset ("pPostSubpassSampleLocations" :: Symbol) VkRenderPassSampleLocationsBeginInfoEXT :: Nat Source #

type FieldIsArray ("pPostSubpassSampleLocations" :: Symbol) VkRenderPassSampleLocationsBeginInfoEXT :: Bool Source #

HasField "postSubpassSampleLocationsCount" VkRenderPassSampleLocationsBeginInfoEXT Source # 

Associated Types

type FieldType ("postSubpassSampleLocationsCount" :: Symbol) VkRenderPassSampleLocationsBeginInfoEXT :: Type Source #

type FieldOptional ("postSubpassSampleLocationsCount" :: Symbol) VkRenderPassSampleLocationsBeginInfoEXT :: Bool Source #

type FieldOffset ("postSubpassSampleLocationsCount" :: Symbol) VkRenderPassSampleLocationsBeginInfoEXT :: Nat Source #

type FieldIsArray ("postSubpassSampleLocationsCount" :: Symbol) VkRenderPassSampleLocationsBeginInfoEXT :: Bool Source #

HasField "sType" VkRenderPassSampleLocationsBeginInfoEXT Source # 
type StructFields VkRenderPassSampleLocationsBeginInfoEXT Source # 
type StructFields VkRenderPassSampleLocationsBeginInfoEXT = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "attachmentInitialSampleLocationsCount" ((:) Symbol "pAttachmentInitialSampleLocations" ((:) Symbol "postSubpassSampleLocationsCount" ((:) Symbol "pPostSubpassSampleLocations" ([] Symbol))))))
type CUnionType VkRenderPassSampleLocationsBeginInfoEXT Source # 
type ReturnedOnly VkRenderPassSampleLocationsBeginInfoEXT Source # 
type StructExtends VkRenderPassSampleLocationsBeginInfoEXT Source # 
type FieldType "attachmentInitialSampleLocationsCount" VkRenderPassSampleLocationsBeginInfoEXT Source # 
type FieldType "attachmentInitialSampleLocationsCount" VkRenderPassSampleLocationsBeginInfoEXT = Word32
type FieldType "pAttachmentInitialSampleLocations" VkRenderPassSampleLocationsBeginInfoEXT Source # 
type FieldType "pNext" VkRenderPassSampleLocationsBeginInfoEXT Source # 
type FieldType "pPostSubpassSampleLocations" VkRenderPassSampleLocationsBeginInfoEXT Source # 
type FieldType "postSubpassSampleLocationsCount" VkRenderPassSampleLocationsBeginInfoEXT Source # 
type FieldType "postSubpassSampleLocationsCount" VkRenderPassSampleLocationsBeginInfoEXT = Word32
type FieldType "sType" VkRenderPassSampleLocationsBeginInfoEXT Source # 
type FieldOptional "attachmentInitialSampleLocationsCount" VkRenderPassSampleLocationsBeginInfoEXT Source # 
type FieldOptional "attachmentInitialSampleLocationsCount" VkRenderPassSampleLocationsBeginInfoEXT = True
type FieldOptional "pAttachmentInitialSampleLocations" VkRenderPassSampleLocationsBeginInfoEXT Source # 
type FieldOptional "pAttachmentInitialSampleLocations" VkRenderPassSampleLocationsBeginInfoEXT = False
type FieldOptional "pNext" VkRenderPassSampleLocationsBeginInfoEXT Source # 
type FieldOptional "pPostSubpassSampleLocations" VkRenderPassSampleLocationsBeginInfoEXT Source # 
type FieldOptional "pPostSubpassSampleLocations" VkRenderPassSampleLocationsBeginInfoEXT = False
type FieldOptional "postSubpassSampleLocationsCount" VkRenderPassSampleLocationsBeginInfoEXT Source # 
type FieldOptional "postSubpassSampleLocationsCount" VkRenderPassSampleLocationsBeginInfoEXT = True
type FieldOptional "sType" VkRenderPassSampleLocationsBeginInfoEXT Source # 
type FieldOffset "attachmentInitialSampleLocationsCount" VkRenderPassSampleLocationsBeginInfoEXT Source # 
type FieldOffset "attachmentInitialSampleLocationsCount" VkRenderPassSampleLocationsBeginInfoEXT = 16
type FieldOffset "pAttachmentInitialSampleLocations" VkRenderPassSampleLocationsBeginInfoEXT Source # 
type FieldOffset "pAttachmentInitialSampleLocations" VkRenderPassSampleLocationsBeginInfoEXT = 24
type FieldOffset "pNext" VkRenderPassSampleLocationsBeginInfoEXT Source # 
type FieldOffset "pPostSubpassSampleLocations" VkRenderPassSampleLocationsBeginInfoEXT Source # 
type FieldOffset "pPostSubpassSampleLocations" VkRenderPassSampleLocationsBeginInfoEXT = 40
type FieldOffset "postSubpassSampleLocationsCount" VkRenderPassSampleLocationsBeginInfoEXT Source # 
type FieldOffset "postSubpassSampleLocationsCount" VkRenderPassSampleLocationsBeginInfoEXT = 32
type FieldOffset "sType" VkRenderPassSampleLocationsBeginInfoEXT Source # 
type FieldIsArray "attachmentInitialSampleLocationsCount" VkRenderPassSampleLocationsBeginInfoEXT Source # 
type FieldIsArray "attachmentInitialSampleLocationsCount" VkRenderPassSampleLocationsBeginInfoEXT = False
type FieldIsArray "pAttachmentInitialSampleLocations" VkRenderPassSampleLocationsBeginInfoEXT Source # 
type FieldIsArray "pAttachmentInitialSampleLocations" VkRenderPassSampleLocationsBeginInfoEXT = False
type FieldIsArray "pNext" VkRenderPassSampleLocationsBeginInfoEXT Source # 
type FieldIsArray "pPostSubpassSampleLocations" VkRenderPassSampleLocationsBeginInfoEXT Source # 
type FieldIsArray "pPostSubpassSampleLocations" VkRenderPassSampleLocationsBeginInfoEXT = False
type FieldIsArray "postSubpassSampleLocationsCount" VkRenderPassSampleLocationsBeginInfoEXT Source # 
type FieldIsArray "postSubpassSampleLocationsCount" VkRenderPassSampleLocationsBeginInfoEXT = False
type FieldIsArray "sType" VkRenderPassSampleLocationsBeginInfoEXT Source # 

data VkSparseBufferMemoryBindInfo Source #

typedef struct VkSparseBufferMemoryBindInfo {
    VkBuffer buffer;
    uint32_t               bindCount;
    const VkSparseMemoryBind* pBinds;
} VkSparseBufferMemoryBindInfo;

VkSparseBufferMemoryBindInfo registry at www.khronos.org

Instances

Eq VkSparseBufferMemoryBindInfo Source # 
Ord VkSparseBufferMemoryBindInfo Source # 
Show VkSparseBufferMemoryBindInfo Source # 
Storable VkSparseBufferMemoryBindInfo Source # 
VulkanMarshalPrim VkSparseBufferMemoryBindInfo Source # 
VulkanMarshal VkSparseBufferMemoryBindInfo Source # 
CanWriteField "bindCount" VkSparseBufferMemoryBindInfo Source # 
CanWriteField "buffer" VkSparseBufferMemoryBindInfo Source # 
CanWriteField "pBinds" VkSparseBufferMemoryBindInfo Source # 
CanReadField "bindCount" VkSparseBufferMemoryBindInfo Source # 
CanReadField "buffer" VkSparseBufferMemoryBindInfo Source # 
CanReadField "pBinds" VkSparseBufferMemoryBindInfo Source # 
HasField "bindCount" VkSparseBufferMemoryBindInfo Source # 
HasField "buffer" VkSparseBufferMemoryBindInfo Source # 
HasField "pBinds" VkSparseBufferMemoryBindInfo Source # 
type StructFields VkSparseBufferMemoryBindInfo Source # 
type StructFields VkSparseBufferMemoryBindInfo = (:) Symbol "buffer" ((:) Symbol "bindCount" ((:) Symbol "pBinds" ([] Symbol)))
type CUnionType VkSparseBufferMemoryBindInfo Source # 
type ReturnedOnly VkSparseBufferMemoryBindInfo Source # 
type StructExtends VkSparseBufferMemoryBindInfo Source # 
type FieldType "bindCount" VkSparseBufferMemoryBindInfo Source # 
type FieldType "buffer" VkSparseBufferMemoryBindInfo Source # 
type FieldType "pBinds" VkSparseBufferMemoryBindInfo Source # 
type FieldOptional "bindCount" VkSparseBufferMemoryBindInfo Source # 
type FieldOptional "buffer" VkSparseBufferMemoryBindInfo Source # 
type FieldOptional "pBinds" VkSparseBufferMemoryBindInfo Source # 
type FieldOffset "bindCount" VkSparseBufferMemoryBindInfo Source # 
type FieldOffset "buffer" VkSparseBufferMemoryBindInfo Source # 
type FieldOffset "pBinds" VkSparseBufferMemoryBindInfo Source # 
type FieldIsArray "bindCount" VkSparseBufferMemoryBindInfo Source # 
type FieldIsArray "buffer" VkSparseBufferMemoryBindInfo Source # 
type FieldIsArray "pBinds" VkSparseBufferMemoryBindInfo Source # 

data VkSparseImageFormatProperties Source #

typedef struct VkSparseImageFormatProperties {
    VkImageAspectFlags     aspectMask;
    VkExtent3D             imageGranularity;
    VkSparseImageFormatFlags flags;
} VkSparseImageFormatProperties;

VkSparseImageFormatProperties registry at www.khronos.org

Instances

Eq VkSparseImageFormatProperties Source # 
Ord VkSparseImageFormatProperties Source # 
Show VkSparseImageFormatProperties Source # 
Storable VkSparseImageFormatProperties Source # 
VulkanMarshalPrim VkSparseImageFormatProperties Source # 
VulkanMarshal VkSparseImageFormatProperties Source # 
CanWriteField "aspectMask" VkSparseImageFormatProperties Source # 
CanWriteField "flags" VkSparseImageFormatProperties Source # 
CanWriteField "imageGranularity" VkSparseImageFormatProperties Source # 
CanReadField "aspectMask" VkSparseImageFormatProperties Source # 
CanReadField "flags" VkSparseImageFormatProperties Source # 
CanReadField "imageGranularity" VkSparseImageFormatProperties Source # 
HasField "aspectMask" VkSparseImageFormatProperties Source # 
HasField "flags" VkSparseImageFormatProperties Source # 
HasField "imageGranularity" VkSparseImageFormatProperties Source # 

Associated Types

type FieldType ("imageGranularity" :: Symbol) VkSparseImageFormatProperties :: Type Source #

type FieldOptional ("imageGranularity" :: Symbol) VkSparseImageFormatProperties :: Bool Source #

type FieldOffset ("imageGranularity" :: Symbol) VkSparseImageFormatProperties :: Nat Source #

type FieldIsArray ("imageGranularity" :: Symbol) VkSparseImageFormatProperties :: Bool Source #

type StructFields VkSparseImageFormatProperties Source # 
type StructFields VkSparseImageFormatProperties = (:) Symbol "aspectMask" ((:) Symbol "imageGranularity" ((:) Symbol "flags" ([] Symbol)))
type CUnionType VkSparseImageFormatProperties Source # 
type ReturnedOnly VkSparseImageFormatProperties Source # 
type StructExtends VkSparseImageFormatProperties Source # 
type FieldType "aspectMask" VkSparseImageFormatProperties Source # 
type FieldType "flags" VkSparseImageFormatProperties Source # 
type FieldType "imageGranularity" VkSparseImageFormatProperties Source # 
type FieldOptional "aspectMask" VkSparseImageFormatProperties Source # 
type FieldOptional "flags" VkSparseImageFormatProperties Source # 
type FieldOptional "imageGranularity" VkSparseImageFormatProperties Source # 
type FieldOffset "aspectMask" VkSparseImageFormatProperties Source # 
type FieldOffset "flags" VkSparseImageFormatProperties Source # 
type FieldOffset "imageGranularity" VkSparseImageFormatProperties Source # 
type FieldOffset "imageGranularity" VkSparseImageFormatProperties = 4
type FieldIsArray "aspectMask" VkSparseImageFormatProperties Source # 
type FieldIsArray "flags" VkSparseImageFormatProperties Source # 
type FieldIsArray "imageGranularity" VkSparseImageFormatProperties Source # 

data VkSparseImageFormatProperties2 Source #

typedef struct VkSparseImageFormatProperties2 {
    VkStructureType sType;
    void*                            pNext;
    VkSparseImageFormatProperties    properties;
} VkSparseImageFormatProperties2;

VkSparseImageFormatProperties2 registry at www.khronos.org

Instances

Eq VkSparseImageFormatProperties2 Source # 
Ord VkSparseImageFormatProperties2 Source # 
Show VkSparseImageFormatProperties2 Source # 
Storable VkSparseImageFormatProperties2 Source # 
VulkanMarshalPrim VkSparseImageFormatProperties2 Source # 
VulkanMarshal VkSparseImageFormatProperties2 Source # 
CanWriteField "pNext" VkSparseImageFormatProperties2 Source # 
CanWriteField "properties" VkSparseImageFormatProperties2 Source # 
CanWriteField "sType" VkSparseImageFormatProperties2 Source # 
CanReadField "pNext" VkSparseImageFormatProperties2 Source # 
CanReadField "properties" VkSparseImageFormatProperties2 Source # 
CanReadField "sType" VkSparseImageFormatProperties2 Source # 
HasField "pNext" VkSparseImageFormatProperties2 Source # 
HasField "properties" VkSparseImageFormatProperties2 Source # 
HasField "sType" VkSparseImageFormatProperties2 Source # 
type StructFields VkSparseImageFormatProperties2 Source # 
type StructFields VkSparseImageFormatProperties2 = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "properties" ([] Symbol)))
type CUnionType VkSparseImageFormatProperties2 Source # 
type ReturnedOnly VkSparseImageFormatProperties2 Source # 
type StructExtends VkSparseImageFormatProperties2 Source # 
type FieldType "pNext" VkSparseImageFormatProperties2 Source # 
type FieldType "properties" VkSparseImageFormatProperties2 Source # 
type FieldType "sType" VkSparseImageFormatProperties2 Source # 
type FieldOptional "pNext" VkSparseImageFormatProperties2 Source # 
type FieldOptional "properties" VkSparseImageFormatProperties2 Source # 
type FieldOptional "sType" VkSparseImageFormatProperties2 Source # 
type FieldOffset "pNext" VkSparseImageFormatProperties2 Source # 
type FieldOffset "properties" VkSparseImageFormatProperties2 Source # 
type FieldOffset "sType" VkSparseImageFormatProperties2 Source # 
type FieldIsArray "pNext" VkSparseImageFormatProperties2 Source # 
type FieldIsArray "properties" VkSparseImageFormatProperties2 Source # 
type FieldIsArray "sType" VkSparseImageFormatProperties2 Source # 

data VkSparseImageMemoryBind Source #

typedef struct VkSparseImageMemoryBind {
    VkImageSubresource     subresource;
    VkOffset3D             offset;
    VkExtent3D             extent;
    VkDeviceMemory         memory;
    VkDeviceSize           memoryOffset;
    VkSparseMemoryBindFlagsflags;
} VkSparseImageMemoryBind;

VkSparseImageMemoryBind registry at www.khronos.org

Instances

Eq VkSparseImageMemoryBind Source # 
Ord VkSparseImageMemoryBind Source # 
Show VkSparseImageMemoryBind Source # 
Storable VkSparseImageMemoryBind Source # 
VulkanMarshalPrim VkSparseImageMemoryBind Source # 
VulkanMarshal VkSparseImageMemoryBind Source # 
CanWriteField "extent" VkSparseImageMemoryBind Source # 
CanWriteField "flags" VkSparseImageMemoryBind Source # 
CanWriteField "memory" VkSparseImageMemoryBind Source # 
CanWriteField "memoryOffset" VkSparseImageMemoryBind Source # 
CanWriteField "offset" VkSparseImageMemoryBind Source # 
CanWriteField "subresource" VkSparseImageMemoryBind Source # 
CanReadField "extent" VkSparseImageMemoryBind Source # 
CanReadField "flags" VkSparseImageMemoryBind Source # 
CanReadField "memory" VkSparseImageMemoryBind Source # 
CanReadField "memoryOffset" VkSparseImageMemoryBind Source # 
CanReadField "offset" VkSparseImageMemoryBind Source # 
CanReadField "subresource" VkSparseImageMemoryBind Source # 
HasField "extent" VkSparseImageMemoryBind Source # 
HasField "flags" VkSparseImageMemoryBind Source # 
HasField "memory" VkSparseImageMemoryBind Source # 
HasField "memoryOffset" VkSparseImageMemoryBind Source # 

Associated Types

type FieldType ("memoryOffset" :: Symbol) VkSparseImageMemoryBind :: Type Source #

type FieldOptional ("memoryOffset" :: Symbol) VkSparseImageMemoryBind :: Bool Source #

type FieldOffset ("memoryOffset" :: Symbol) VkSparseImageMemoryBind :: Nat Source #

type FieldIsArray ("memoryOffset" :: Symbol) VkSparseImageMemoryBind :: Bool Source #

HasField "offset" VkSparseImageMemoryBind Source # 
HasField "subresource" VkSparseImageMemoryBind Source # 
type StructFields VkSparseImageMemoryBind Source # 
type StructFields VkSparseImageMemoryBind = (:) Symbol "subresource" ((:) Symbol "offset" ((:) Symbol "extent" ((:) Symbol "memory" ((:) Symbol "memoryOffset" ((:) Symbol "flags" ([] Symbol))))))
type CUnionType VkSparseImageMemoryBind Source # 
type ReturnedOnly VkSparseImageMemoryBind Source # 
type StructExtends VkSparseImageMemoryBind Source # 
type FieldType "extent" VkSparseImageMemoryBind Source # 
type FieldType "flags" VkSparseImageMemoryBind Source # 
type FieldType "memory" VkSparseImageMemoryBind Source # 
type FieldType "memoryOffset" VkSparseImageMemoryBind Source # 
type FieldType "offset" VkSparseImageMemoryBind Source # 
type FieldType "subresource" VkSparseImageMemoryBind Source # 
type FieldOptional "extent" VkSparseImageMemoryBind Source # 
type FieldOptional "flags" VkSparseImageMemoryBind Source # 
type FieldOptional "memory" VkSparseImageMemoryBind Source # 
type FieldOptional "memoryOffset" VkSparseImageMemoryBind Source # 
type FieldOptional "offset" VkSparseImageMemoryBind Source # 
type FieldOptional "subresource" VkSparseImageMemoryBind Source # 
type FieldOffset "extent" VkSparseImageMemoryBind Source # 
type FieldOffset "flags" VkSparseImageMemoryBind Source # 
type FieldOffset "memory" VkSparseImageMemoryBind Source # 
type FieldOffset "memoryOffset" VkSparseImageMemoryBind Source # 
type FieldOffset "memoryOffset" VkSparseImageMemoryBind = 48
type FieldOffset "offset" VkSparseImageMemoryBind Source # 
type FieldOffset "subresource" VkSparseImageMemoryBind Source # 
type FieldOffset "subresource" VkSparseImageMemoryBind = 0
type FieldIsArray "extent" VkSparseImageMemoryBind Source # 
type FieldIsArray "flags" VkSparseImageMemoryBind Source # 
type FieldIsArray "memory" VkSparseImageMemoryBind Source # 
type FieldIsArray "memoryOffset" VkSparseImageMemoryBind Source # 
type FieldIsArray "offset" VkSparseImageMemoryBind Source # 
type FieldIsArray "subresource" VkSparseImageMemoryBind Source # 

data VkSparseImageMemoryBindInfo Source #

typedef struct VkSparseImageMemoryBindInfo {
    VkImage image;
    uint32_t               bindCount;
    const VkSparseImageMemoryBind* pBinds;
} VkSparseImageMemoryBindInfo;

VkSparseImageMemoryBindInfo registry at www.khronos.org

Instances

Eq VkSparseImageMemoryBindInfo Source # 
Ord VkSparseImageMemoryBindInfo Source # 
Show VkSparseImageMemoryBindInfo Source # 
Storable VkSparseImageMemoryBindInfo Source # 
VulkanMarshalPrim VkSparseImageMemoryBindInfo Source # 
VulkanMarshal VkSparseImageMemoryBindInfo Source # 
CanWriteField "bindCount" VkSparseImageMemoryBindInfo Source # 
CanWriteField "image" VkSparseImageMemoryBindInfo Source # 
CanWriteField "pBinds" VkSparseImageMemoryBindInfo Source # 
CanReadField "bindCount" VkSparseImageMemoryBindInfo Source # 
CanReadField "image" VkSparseImageMemoryBindInfo Source # 
CanReadField "pBinds" VkSparseImageMemoryBindInfo Source # 
HasField "bindCount" VkSparseImageMemoryBindInfo Source # 
HasField "image" VkSparseImageMemoryBindInfo Source # 
HasField "pBinds" VkSparseImageMemoryBindInfo Source # 
type StructFields VkSparseImageMemoryBindInfo Source # 
type StructFields VkSparseImageMemoryBindInfo = (:) Symbol "image" ((:) Symbol "bindCount" ((:) Symbol "pBinds" ([] Symbol)))
type CUnionType VkSparseImageMemoryBindInfo Source # 
type ReturnedOnly VkSparseImageMemoryBindInfo Source # 
type StructExtends VkSparseImageMemoryBindInfo Source # 
type FieldType "bindCount" VkSparseImageMemoryBindInfo Source # 
type FieldType "image" VkSparseImageMemoryBindInfo Source # 
type FieldType "pBinds" VkSparseImageMemoryBindInfo Source # 
type FieldOptional "bindCount" VkSparseImageMemoryBindInfo Source # 
type FieldOptional "image" VkSparseImageMemoryBindInfo Source # 
type FieldOptional "pBinds" VkSparseImageMemoryBindInfo Source # 
type FieldOffset "bindCount" VkSparseImageMemoryBindInfo Source # 
type FieldOffset "image" VkSparseImageMemoryBindInfo Source # 
type FieldOffset "pBinds" VkSparseImageMemoryBindInfo Source # 
type FieldIsArray "bindCount" VkSparseImageMemoryBindInfo Source # 
type FieldIsArray "image" VkSparseImageMemoryBindInfo Source # 
type FieldIsArray "pBinds" VkSparseImageMemoryBindInfo Source # 

data VkSparseImageMemoryRequirements Source #

typedef struct VkSparseImageMemoryRequirements {
    VkSparseImageFormatProperties formatProperties;
    uint32_t               imageMipTailFirstLod;
    VkDeviceSize           imageMipTailSize;
    VkDeviceSize           imageMipTailOffset;
    VkDeviceSize           imageMipTailStride;
} VkSparseImageMemoryRequirements;

VkSparseImageMemoryRequirements registry at www.khronos.org

Instances

Eq VkSparseImageMemoryRequirements Source # 
Ord VkSparseImageMemoryRequirements Source # 
Show VkSparseImageMemoryRequirements Source # 
Storable VkSparseImageMemoryRequirements Source # 
VulkanMarshalPrim VkSparseImageMemoryRequirements Source # 
VulkanMarshal VkSparseImageMemoryRequirements Source # 
CanWriteField "formatProperties" VkSparseImageMemoryRequirements Source # 
CanWriteField "imageMipTailFirstLod" VkSparseImageMemoryRequirements Source # 
CanWriteField "imageMipTailOffset" VkSparseImageMemoryRequirements Source # 
CanWriteField "imageMipTailSize" VkSparseImageMemoryRequirements Source # 
CanWriteField "imageMipTailStride" VkSparseImageMemoryRequirements Source # 
CanReadField "formatProperties" VkSparseImageMemoryRequirements Source # 
CanReadField "imageMipTailFirstLod" VkSparseImageMemoryRequirements Source # 
CanReadField "imageMipTailOffset" VkSparseImageMemoryRequirements Source # 
CanReadField "imageMipTailSize" VkSparseImageMemoryRequirements Source # 
CanReadField "imageMipTailStride" VkSparseImageMemoryRequirements Source # 
HasField "formatProperties" VkSparseImageMemoryRequirements Source # 
HasField "imageMipTailFirstLod" VkSparseImageMemoryRequirements Source # 

Associated Types

type FieldType ("imageMipTailFirstLod" :: Symbol) VkSparseImageMemoryRequirements :: Type Source #

type FieldOptional ("imageMipTailFirstLod" :: Symbol) VkSparseImageMemoryRequirements :: Bool Source #

type FieldOffset ("imageMipTailFirstLod" :: Symbol) VkSparseImageMemoryRequirements :: Nat Source #

type FieldIsArray ("imageMipTailFirstLod" :: Symbol) VkSparseImageMemoryRequirements :: Bool Source #

HasField "imageMipTailOffset" VkSparseImageMemoryRequirements Source # 

Associated Types

type FieldType ("imageMipTailOffset" :: Symbol) VkSparseImageMemoryRequirements :: Type Source #

type FieldOptional ("imageMipTailOffset" :: Symbol) VkSparseImageMemoryRequirements :: Bool Source #

type FieldOffset ("imageMipTailOffset" :: Symbol) VkSparseImageMemoryRequirements :: Nat Source #

type FieldIsArray ("imageMipTailOffset" :: Symbol) VkSparseImageMemoryRequirements :: Bool Source #

HasField "imageMipTailSize" VkSparseImageMemoryRequirements Source # 
HasField "imageMipTailStride" VkSparseImageMemoryRequirements Source # 

Associated Types

type FieldType ("imageMipTailStride" :: Symbol) VkSparseImageMemoryRequirements :: Type Source #

type FieldOptional ("imageMipTailStride" :: Symbol) VkSparseImageMemoryRequirements :: Bool Source #

type FieldOffset ("imageMipTailStride" :: Symbol) VkSparseImageMemoryRequirements :: Nat Source #

type FieldIsArray ("imageMipTailStride" :: Symbol) VkSparseImageMemoryRequirements :: Bool Source #

type StructFields VkSparseImageMemoryRequirements Source # 
type StructFields VkSparseImageMemoryRequirements = (:) Symbol "formatProperties" ((:) Symbol "imageMipTailFirstLod" ((:) Symbol "imageMipTailSize" ((:) Symbol "imageMipTailOffset" ((:) Symbol "imageMipTailStride" ([] Symbol)))))
type CUnionType VkSparseImageMemoryRequirements Source # 
type ReturnedOnly VkSparseImageMemoryRequirements Source # 
type StructExtends VkSparseImageMemoryRequirements Source # 
type FieldType "formatProperties" VkSparseImageMemoryRequirements Source # 
type FieldType "imageMipTailFirstLod" VkSparseImageMemoryRequirements Source # 
type FieldType "imageMipTailFirstLod" VkSparseImageMemoryRequirements = Word32
type FieldType "imageMipTailOffset" VkSparseImageMemoryRequirements Source # 
type FieldType "imageMipTailSize" VkSparseImageMemoryRequirements Source # 
type FieldType "imageMipTailStride" VkSparseImageMemoryRequirements Source # 
type FieldOptional "formatProperties" VkSparseImageMemoryRequirements Source # 
type FieldOptional "imageMipTailFirstLod" VkSparseImageMemoryRequirements Source # 
type FieldOptional "imageMipTailOffset" VkSparseImageMemoryRequirements Source # 
type FieldOptional "imageMipTailSize" VkSparseImageMemoryRequirements Source # 
type FieldOptional "imageMipTailStride" VkSparseImageMemoryRequirements Source # 
type FieldOffset "formatProperties" VkSparseImageMemoryRequirements Source # 
type FieldOffset "formatProperties" VkSparseImageMemoryRequirements = 0
type FieldOffset "imageMipTailFirstLod" VkSparseImageMemoryRequirements Source # 
type FieldOffset "imageMipTailFirstLod" VkSparseImageMemoryRequirements = 20
type FieldOffset "imageMipTailOffset" VkSparseImageMemoryRequirements Source # 
type FieldOffset "imageMipTailOffset" VkSparseImageMemoryRequirements = 32
type FieldOffset "imageMipTailSize" VkSparseImageMemoryRequirements Source # 
type FieldOffset "imageMipTailSize" VkSparseImageMemoryRequirements = 24
type FieldOffset "imageMipTailStride" VkSparseImageMemoryRequirements Source # 
type FieldOffset "imageMipTailStride" VkSparseImageMemoryRequirements = 40
type FieldIsArray "formatProperties" VkSparseImageMemoryRequirements Source # 
type FieldIsArray "imageMipTailFirstLod" VkSparseImageMemoryRequirements Source # 
type FieldIsArray "imageMipTailFirstLod" VkSparseImageMemoryRequirements = False
type FieldIsArray "imageMipTailOffset" VkSparseImageMemoryRequirements Source # 
type FieldIsArray "imageMipTailSize" VkSparseImageMemoryRequirements Source # 
type FieldIsArray "imageMipTailStride" VkSparseImageMemoryRequirements Source # 

data VkSparseImageMemoryRequirements2 Source #

typedef struct VkSparseImageMemoryRequirements2 {
    VkStructureType sType;
    void*                                       pNext;
    VkSparseImageMemoryRequirements                                      memoryRequirements;
} VkSparseImageMemoryRequirements2;

VkSparseImageMemoryRequirements2 registry at www.khronos.org

Instances

Eq VkSparseImageMemoryRequirements2 Source # 
Ord VkSparseImageMemoryRequirements2 Source # 
Show VkSparseImageMemoryRequirements2 Source # 
Storable VkSparseImageMemoryRequirements2 Source # 
VulkanMarshalPrim VkSparseImageMemoryRequirements2 Source # 
VulkanMarshal VkSparseImageMemoryRequirements2 Source # 
CanWriteField "memoryRequirements" VkSparseImageMemoryRequirements2 Source # 
CanWriteField "pNext" VkSparseImageMemoryRequirements2 Source # 
CanWriteField "sType" VkSparseImageMemoryRequirements2 Source # 
CanReadField "memoryRequirements" VkSparseImageMemoryRequirements2 Source # 
CanReadField "pNext" VkSparseImageMemoryRequirements2 Source # 
CanReadField "sType" VkSparseImageMemoryRequirements2 Source # 
HasField "memoryRequirements" VkSparseImageMemoryRequirements2 Source # 

Associated Types

type FieldType ("memoryRequirements" :: Symbol) VkSparseImageMemoryRequirements2 :: Type Source #

type FieldOptional ("memoryRequirements" :: Symbol) VkSparseImageMemoryRequirements2 :: Bool Source #

type FieldOffset ("memoryRequirements" :: Symbol) VkSparseImageMemoryRequirements2 :: Nat Source #

type FieldIsArray ("memoryRequirements" :: Symbol) VkSparseImageMemoryRequirements2 :: Bool Source #

HasField "pNext" VkSparseImageMemoryRequirements2 Source # 
HasField "sType" VkSparseImageMemoryRequirements2 Source # 
type StructFields VkSparseImageMemoryRequirements2 Source # 
type StructFields VkSparseImageMemoryRequirements2 = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "memoryRequirements" ([] Symbol)))
type CUnionType VkSparseImageMemoryRequirements2 Source # 
type ReturnedOnly VkSparseImageMemoryRequirements2 Source # 
type StructExtends VkSparseImageMemoryRequirements2 Source # 
type FieldType "memoryRequirements" VkSparseImageMemoryRequirements2 Source # 
type FieldType "pNext" VkSparseImageMemoryRequirements2 Source # 
type FieldType "sType" VkSparseImageMemoryRequirements2 Source # 
type FieldOptional "memoryRequirements" VkSparseImageMemoryRequirements2 Source # 
type FieldOptional "pNext" VkSparseImageMemoryRequirements2 Source # 
type FieldOptional "sType" VkSparseImageMemoryRequirements2 Source # 
type FieldOffset "memoryRequirements" VkSparseImageMemoryRequirements2 Source # 
type FieldOffset "memoryRequirements" VkSparseImageMemoryRequirements2 = 16
type FieldOffset "pNext" VkSparseImageMemoryRequirements2 Source # 
type FieldOffset "sType" VkSparseImageMemoryRequirements2 Source # 
type FieldIsArray "memoryRequirements" VkSparseImageMemoryRequirements2 Source # 
type FieldIsArray "pNext" VkSparseImageMemoryRequirements2 Source # 
type FieldIsArray "sType" VkSparseImageMemoryRequirements2 Source # 

data VkSparseImageOpaqueMemoryBindInfo Source #

typedef struct VkSparseImageOpaqueMemoryBindInfo {
    VkImage image;
    uint32_t               bindCount;
    const VkSparseMemoryBind* pBinds;
} VkSparseImageOpaqueMemoryBindInfo;

VkSparseImageOpaqueMemoryBindInfo registry at www.khronos.org

Instances

Eq VkSparseImageOpaqueMemoryBindInfo Source # 
Ord VkSparseImageOpaqueMemoryBindInfo Source # 
Show VkSparseImageOpaqueMemoryBindInfo Source # 
Storable VkSparseImageOpaqueMemoryBindInfo Source # 
VulkanMarshalPrim VkSparseImageOpaqueMemoryBindInfo Source # 
VulkanMarshal VkSparseImageOpaqueMemoryBindInfo Source # 
CanWriteField "bindCount" VkSparseImageOpaqueMemoryBindInfo Source # 
CanWriteField "image" VkSparseImageOpaqueMemoryBindInfo Source # 
CanWriteField "pBinds" VkSparseImageOpaqueMemoryBindInfo Source # 
CanReadField "bindCount" VkSparseImageOpaqueMemoryBindInfo Source # 
CanReadField "image" VkSparseImageOpaqueMemoryBindInfo Source # 
CanReadField "pBinds" VkSparseImageOpaqueMemoryBindInfo Source # 
HasField "bindCount" VkSparseImageOpaqueMemoryBindInfo Source # 
HasField "image" VkSparseImageOpaqueMemoryBindInfo Source # 
HasField "pBinds" VkSparseImageOpaqueMemoryBindInfo Source # 
type StructFields VkSparseImageOpaqueMemoryBindInfo Source # 
type StructFields VkSparseImageOpaqueMemoryBindInfo = (:) Symbol "image" ((:) Symbol "bindCount" ((:) Symbol "pBinds" ([] Symbol)))
type CUnionType VkSparseImageOpaqueMemoryBindInfo Source # 
type ReturnedOnly VkSparseImageOpaqueMemoryBindInfo Source # 
type StructExtends VkSparseImageOpaqueMemoryBindInfo Source # 
type FieldType "bindCount" VkSparseImageOpaqueMemoryBindInfo Source # 
type FieldType "image" VkSparseImageOpaqueMemoryBindInfo Source # 
type FieldType "pBinds" VkSparseImageOpaqueMemoryBindInfo Source # 
type FieldOptional "bindCount" VkSparseImageOpaqueMemoryBindInfo Source # 
type FieldOptional "image" VkSparseImageOpaqueMemoryBindInfo Source # 
type FieldOptional "pBinds" VkSparseImageOpaqueMemoryBindInfo Source # 
type FieldOffset "bindCount" VkSparseImageOpaqueMemoryBindInfo Source # 
type FieldOffset "image" VkSparseImageOpaqueMemoryBindInfo Source # 
type FieldOffset "pBinds" VkSparseImageOpaqueMemoryBindInfo Source # 
type FieldIsArray "bindCount" VkSparseImageOpaqueMemoryBindInfo Source # 
type FieldIsArray "image" VkSparseImageOpaqueMemoryBindInfo Source # 
type FieldIsArray "pBinds" VkSparseImageOpaqueMemoryBindInfo Source # 

data VkSparseMemoryBind Source #

typedef struct VkSparseMemoryBind {
    VkDeviceSize           resourceOffset;
    VkDeviceSize           size;
    VkDeviceMemory         memory;
    VkDeviceSize           memoryOffset;
    VkSparseMemoryBindFlagsflags;
} VkSparseMemoryBind;

VkSparseMemoryBind registry at www.khronos.org

Instances

Eq VkSparseMemoryBind Source # 
Ord VkSparseMemoryBind Source # 
Show VkSparseMemoryBind Source # 
Storable VkSparseMemoryBind Source # 
VulkanMarshalPrim VkSparseMemoryBind Source # 
VulkanMarshal VkSparseMemoryBind Source # 
CanWriteField "flags" VkSparseMemoryBind Source # 
CanWriteField "memory" VkSparseMemoryBind Source # 
CanWriteField "memoryOffset" VkSparseMemoryBind Source # 
CanWriteField "resourceOffset" VkSparseMemoryBind Source # 
CanWriteField "size" VkSparseMemoryBind Source # 
CanReadField "flags" VkSparseMemoryBind Source # 
CanReadField "memory" VkSparseMemoryBind Source # 
CanReadField "memoryOffset" VkSparseMemoryBind Source # 
CanReadField "resourceOffset" VkSparseMemoryBind Source # 
CanReadField "size" VkSparseMemoryBind Source # 
HasField "flags" VkSparseMemoryBind Source # 
HasField "memory" VkSparseMemoryBind Source # 
HasField "memoryOffset" VkSparseMemoryBind Source # 

Associated Types

type FieldType ("memoryOffset" :: Symbol) VkSparseMemoryBind :: Type Source #

type FieldOptional ("memoryOffset" :: Symbol) VkSparseMemoryBind :: Bool Source #

type FieldOffset ("memoryOffset" :: Symbol) VkSparseMemoryBind :: Nat Source #

type FieldIsArray ("memoryOffset" :: Symbol) VkSparseMemoryBind :: Bool Source #

HasField "resourceOffset" VkSparseMemoryBind Source # 

Associated Types

type FieldType ("resourceOffset" :: Symbol) VkSparseMemoryBind :: Type Source #

type FieldOptional ("resourceOffset" :: Symbol) VkSparseMemoryBind :: Bool Source #

type FieldOffset ("resourceOffset" :: Symbol) VkSparseMemoryBind :: Nat Source #

type FieldIsArray ("resourceOffset" :: Symbol) VkSparseMemoryBind :: Bool Source #

HasField "size" VkSparseMemoryBind Source # 
type StructFields VkSparseMemoryBind Source # 
type StructFields VkSparseMemoryBind = (:) Symbol "resourceOffset" ((:) Symbol "size" ((:) Symbol "memory" ((:) Symbol "memoryOffset" ((:) Symbol "flags" ([] Symbol)))))
type CUnionType VkSparseMemoryBind Source # 
type ReturnedOnly VkSparseMemoryBind Source # 
type StructExtends VkSparseMemoryBind Source # 
type FieldType "flags" VkSparseMemoryBind Source # 
type FieldType "memory" VkSparseMemoryBind Source # 
type FieldType "memoryOffset" VkSparseMemoryBind Source # 
type FieldType "resourceOffset" VkSparseMemoryBind Source # 
type FieldType "resourceOffset" VkSparseMemoryBind = VkDeviceSize
type FieldType "size" VkSparseMemoryBind Source # 
type FieldOptional "flags" VkSparseMemoryBind Source # 
type FieldOptional "memory" VkSparseMemoryBind Source # 
type FieldOptional "memoryOffset" VkSparseMemoryBind Source # 
type FieldOptional "memoryOffset" VkSparseMemoryBind = False
type FieldOptional "resourceOffset" VkSparseMemoryBind Source # 
type FieldOptional "resourceOffset" VkSparseMemoryBind = False
type FieldOptional "size" VkSparseMemoryBind Source # 
type FieldOffset "flags" VkSparseMemoryBind Source # 
type FieldOffset "memory" VkSparseMemoryBind Source # 
type FieldOffset "memory" VkSparseMemoryBind = 16
type FieldOffset "memoryOffset" VkSparseMemoryBind Source # 
type FieldOffset "memoryOffset" VkSparseMemoryBind = 24
type FieldOffset "resourceOffset" VkSparseMemoryBind Source # 
type FieldOffset "resourceOffset" VkSparseMemoryBind = 0
type FieldOffset "size" VkSparseMemoryBind Source # 
type FieldIsArray "flags" VkSparseMemoryBind Source # 
type FieldIsArray "memory" VkSparseMemoryBind Source # 
type FieldIsArray "memoryOffset" VkSparseMemoryBind Source # 
type FieldIsArray "memoryOffset" VkSparseMemoryBind = False
type FieldIsArray "resourceOffset" VkSparseMemoryBind Source # 
type FieldIsArray "resourceOffset" VkSparseMemoryBind = False
type FieldIsArray "size" VkSparseMemoryBind Source # 

newtype VkSparseImageFormatBitmask a Source #

Instances

Bounded (VkSparseImageFormatBitmask FlagMask) Source # 
Enum (VkSparseImageFormatBitmask FlagMask) Source # 
Eq (VkSparseImageFormatBitmask a) Source # 
Integral (VkSparseImageFormatBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkSparseImageFormatBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkSparseImageFormatBitmask a -> c (VkSparseImageFormatBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkSparseImageFormatBitmask a) #

toConstr :: VkSparseImageFormatBitmask a -> Constr #

dataTypeOf :: VkSparseImageFormatBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkSparseImageFormatBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkSparseImageFormatBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkSparseImageFormatBitmask a -> VkSparseImageFormatBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkSparseImageFormatBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkSparseImageFormatBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkSparseImageFormatBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkSparseImageFormatBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkSparseImageFormatBitmask a -> m (VkSparseImageFormatBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSparseImageFormatBitmask a -> m (VkSparseImageFormatBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSparseImageFormatBitmask a -> m (VkSparseImageFormatBitmask a) #

Num (VkSparseImageFormatBitmask FlagMask) Source # 
Ord (VkSparseImageFormatBitmask a) Source # 
Read (VkSparseImageFormatBitmask a) Source # 
Real (VkSparseImageFormatBitmask FlagMask) Source # 
Show (VkSparseImageFormatBitmask a) Source # 
Generic (VkSparseImageFormatBitmask a) Source # 
Storable (VkSparseImageFormatBitmask a) Source # 
Bits (VkSparseImageFormatBitmask FlagMask) Source # 

Methods

(.&.) :: VkSparseImageFormatBitmask FlagMask -> VkSparseImageFormatBitmask FlagMask -> VkSparseImageFormatBitmask FlagMask #

(.|.) :: VkSparseImageFormatBitmask FlagMask -> VkSparseImageFormatBitmask FlagMask -> VkSparseImageFormatBitmask FlagMask #

xor :: VkSparseImageFormatBitmask FlagMask -> VkSparseImageFormatBitmask FlagMask -> VkSparseImageFormatBitmask FlagMask #

complement :: VkSparseImageFormatBitmask FlagMask -> VkSparseImageFormatBitmask FlagMask #

shift :: VkSparseImageFormatBitmask FlagMask -> Int -> VkSparseImageFormatBitmask FlagMask #

rotate :: VkSparseImageFormatBitmask FlagMask -> Int -> VkSparseImageFormatBitmask FlagMask #

zeroBits :: VkSparseImageFormatBitmask FlagMask #

bit :: Int -> VkSparseImageFormatBitmask FlagMask #

setBit :: VkSparseImageFormatBitmask FlagMask -> Int -> VkSparseImageFormatBitmask FlagMask #

clearBit :: VkSparseImageFormatBitmask FlagMask -> Int -> VkSparseImageFormatBitmask FlagMask #

complementBit :: VkSparseImageFormatBitmask FlagMask -> Int -> VkSparseImageFormatBitmask FlagMask #

testBit :: VkSparseImageFormatBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkSparseImageFormatBitmask FlagMask -> Maybe Int #

bitSize :: VkSparseImageFormatBitmask FlagMask -> Int #

isSigned :: VkSparseImageFormatBitmask FlagMask -> Bool #

shiftL :: VkSparseImageFormatBitmask FlagMask -> Int -> VkSparseImageFormatBitmask FlagMask #

unsafeShiftL :: VkSparseImageFormatBitmask FlagMask -> Int -> VkSparseImageFormatBitmask FlagMask #

shiftR :: VkSparseImageFormatBitmask FlagMask -> Int -> VkSparseImageFormatBitmask FlagMask #

unsafeShiftR :: VkSparseImageFormatBitmask FlagMask -> Int -> VkSparseImageFormatBitmask FlagMask #

rotateL :: VkSparseImageFormatBitmask FlagMask -> Int -> VkSparseImageFormatBitmask FlagMask #

rotateR :: VkSparseImageFormatBitmask FlagMask -> Int -> VkSparseImageFormatBitmask FlagMask #

popCount :: VkSparseImageFormatBitmask FlagMask -> Int #

FiniteBits (VkSparseImageFormatBitmask FlagMask) Source # 
type Rep (VkSparseImageFormatBitmask a) Source # 
type Rep (VkSparseImageFormatBitmask a) = D1 (MetaData "VkSparseImageFormatBitmask" "Graphics.Vulkan.Types.Enum.Sparse" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkSparseImageFormatBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

pattern VK_SPARSE_IMAGE_FORMAT_SINGLE_MIPTAIL_BIT :: forall a. VkSparseImageFormatBitmask a Source #

Image uses a single mip tail region for all array layers

bitpos = 0

pattern VK_SPARSE_IMAGE_FORMAT_ALIGNED_MIP_SIZE_BIT :: forall a. VkSparseImageFormatBitmask a Source #

Image requires mip level dimensions to be an integer multiple of the sparse image block dimensions for non-tail mip levels.

bitpos = 1

pattern VK_SPARSE_IMAGE_FORMAT_NONSTANDARD_BLOCK_SIZE_BIT :: forall a. VkSparseImageFormatBitmask a Source #

Image uses a non-standard sparse image block dimensions

bitpos = 2

newtype VkSparseMemoryBindBitmask a Source #

Instances

Bounded (VkSparseMemoryBindBitmask FlagMask) Source # 
Enum (VkSparseMemoryBindBitmask FlagMask) Source # 
Eq (VkSparseMemoryBindBitmask a) Source # 
Integral (VkSparseMemoryBindBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkSparseMemoryBindBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkSparseMemoryBindBitmask a -> c (VkSparseMemoryBindBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkSparseMemoryBindBitmask a) #

toConstr :: VkSparseMemoryBindBitmask a -> Constr #

dataTypeOf :: VkSparseMemoryBindBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkSparseMemoryBindBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkSparseMemoryBindBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkSparseMemoryBindBitmask a -> VkSparseMemoryBindBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkSparseMemoryBindBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkSparseMemoryBindBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkSparseMemoryBindBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkSparseMemoryBindBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkSparseMemoryBindBitmask a -> m (VkSparseMemoryBindBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSparseMemoryBindBitmask a -> m (VkSparseMemoryBindBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSparseMemoryBindBitmask a -> m (VkSparseMemoryBindBitmask a) #

Num (VkSparseMemoryBindBitmask FlagMask) Source # 
Ord (VkSparseMemoryBindBitmask a) Source # 
Read (VkSparseMemoryBindBitmask a) Source # 
Real (VkSparseMemoryBindBitmask FlagMask) Source # 
Show (VkSparseMemoryBindBitmask a) Source # 
Generic (VkSparseMemoryBindBitmask a) Source # 
Storable (VkSparseMemoryBindBitmask a) Source # 
Bits (VkSparseMemoryBindBitmask FlagMask) Source # 

Methods

(.&.) :: VkSparseMemoryBindBitmask FlagMask -> VkSparseMemoryBindBitmask FlagMask -> VkSparseMemoryBindBitmask FlagMask #

(.|.) :: VkSparseMemoryBindBitmask FlagMask -> VkSparseMemoryBindBitmask FlagMask -> VkSparseMemoryBindBitmask FlagMask #

xor :: VkSparseMemoryBindBitmask FlagMask -> VkSparseMemoryBindBitmask FlagMask -> VkSparseMemoryBindBitmask FlagMask #

complement :: VkSparseMemoryBindBitmask FlagMask -> VkSparseMemoryBindBitmask FlagMask #

shift :: VkSparseMemoryBindBitmask FlagMask -> Int -> VkSparseMemoryBindBitmask FlagMask #

rotate :: VkSparseMemoryBindBitmask FlagMask -> Int -> VkSparseMemoryBindBitmask FlagMask #

zeroBits :: VkSparseMemoryBindBitmask FlagMask #

bit :: Int -> VkSparseMemoryBindBitmask FlagMask #

setBit :: VkSparseMemoryBindBitmask FlagMask -> Int -> VkSparseMemoryBindBitmask FlagMask #

clearBit :: VkSparseMemoryBindBitmask FlagMask -> Int -> VkSparseMemoryBindBitmask FlagMask #

complementBit :: VkSparseMemoryBindBitmask FlagMask -> Int -> VkSparseMemoryBindBitmask FlagMask #

testBit :: VkSparseMemoryBindBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkSparseMemoryBindBitmask FlagMask -> Maybe Int #

bitSize :: VkSparseMemoryBindBitmask FlagMask -> Int #

isSigned :: VkSparseMemoryBindBitmask FlagMask -> Bool #

shiftL :: VkSparseMemoryBindBitmask FlagMask -> Int -> VkSparseMemoryBindBitmask FlagMask #

unsafeShiftL :: VkSparseMemoryBindBitmask FlagMask -> Int -> VkSparseMemoryBindBitmask FlagMask #

shiftR :: VkSparseMemoryBindBitmask FlagMask -> Int -> VkSparseMemoryBindBitmask FlagMask #

unsafeShiftR :: VkSparseMemoryBindBitmask FlagMask -> Int -> VkSparseMemoryBindBitmask FlagMask #

rotateL :: VkSparseMemoryBindBitmask FlagMask -> Int -> VkSparseMemoryBindBitmask FlagMask #

rotateR :: VkSparseMemoryBindBitmask FlagMask -> Int -> VkSparseMemoryBindBitmask FlagMask #

popCount :: VkSparseMemoryBindBitmask FlagMask -> Int #

FiniteBits (VkSparseMemoryBindBitmask FlagMask) Source # 
type Rep (VkSparseMemoryBindBitmask a) Source # 
type Rep (VkSparseMemoryBindBitmask a) = D1 (MetaData "VkSparseMemoryBindBitmask" "Graphics.Vulkan.Types.Enum.Sparse" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkSparseMemoryBindBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

pattern VK_SPARSE_MEMORY_BIND_METADATA_BIT :: forall a. VkSparseMemoryBindBitmask a Source #

Operation binds resource metadata to memory

bitpos = 0

data VkSubmitInfo Source #

typedef struct VkSubmitInfo {
    VkStructureType sType;
    const void* pNext;
    uint32_t       waitSemaphoreCount;
    const VkSemaphore*     pWaitSemaphores;
    const VkPipelineStageFlags*           pWaitDstStageMask;
    uint32_t       commandBufferCount;
    const VkCommandBuffer*     pCommandBuffers;
    uint32_t       signalSemaphoreCount;
    const VkSemaphore*     pSignalSemaphores;
} VkSubmitInfo;

VkSubmitInfo registry at www.khronos.org

Instances

Eq VkSubmitInfo Source # 
Ord VkSubmitInfo Source # 
Show VkSubmitInfo Source # 
Storable VkSubmitInfo Source # 
VulkanMarshalPrim VkSubmitInfo Source # 
VulkanMarshal VkSubmitInfo Source # 
CanWriteField "commandBufferCount" VkSubmitInfo Source # 

Methods

writeField :: Ptr VkSubmitInfo -> FieldType "commandBufferCount" VkSubmitInfo -> IO () Source #

CanWriteField "pCommandBuffers" VkSubmitInfo Source # 

Methods

writeField :: Ptr VkSubmitInfo -> FieldType "pCommandBuffers" VkSubmitInfo -> IO () Source #

CanWriteField "pNext" VkSubmitInfo Source # 
CanWriteField "pSignalSemaphores" VkSubmitInfo Source # 

Methods

writeField :: Ptr VkSubmitInfo -> FieldType "pSignalSemaphores" VkSubmitInfo -> IO () Source #

CanWriteField "pWaitDstStageMask" VkSubmitInfo Source # 

Methods

writeField :: Ptr VkSubmitInfo -> FieldType "pWaitDstStageMask" VkSubmitInfo -> IO () Source #

CanWriteField "pWaitSemaphores" VkSubmitInfo Source # 

Methods

writeField :: Ptr VkSubmitInfo -> FieldType "pWaitSemaphores" VkSubmitInfo -> IO () Source #

CanWriteField "sType" VkSubmitInfo Source # 
CanWriteField "signalSemaphoreCount" VkSubmitInfo Source # 

Methods

writeField :: Ptr VkSubmitInfo -> FieldType "signalSemaphoreCount" VkSubmitInfo -> IO () Source #

CanWriteField "waitSemaphoreCount" VkSubmitInfo Source # 

Methods

writeField :: Ptr VkSubmitInfo -> FieldType "waitSemaphoreCount" VkSubmitInfo -> IO () Source #

CanReadField "commandBufferCount" VkSubmitInfo Source # 

Methods

getField :: VkSubmitInfo -> FieldType "commandBufferCount" VkSubmitInfo Source #

readField :: Ptr VkSubmitInfo -> IO (FieldType "commandBufferCount" VkSubmitInfo) Source #

CanReadField "pCommandBuffers" VkSubmitInfo Source # 

Methods

getField :: VkSubmitInfo -> FieldType "pCommandBuffers" VkSubmitInfo Source #

readField :: Ptr VkSubmitInfo -> IO (FieldType "pCommandBuffers" VkSubmitInfo) Source #

CanReadField "pNext" VkSubmitInfo Source # 
CanReadField "pSignalSemaphores" VkSubmitInfo Source # 

Methods

getField :: VkSubmitInfo -> FieldType "pSignalSemaphores" VkSubmitInfo Source #

readField :: Ptr VkSubmitInfo -> IO (FieldType "pSignalSemaphores" VkSubmitInfo) Source #

CanReadField "pWaitDstStageMask" VkSubmitInfo Source # 

Methods

getField :: VkSubmitInfo -> FieldType "pWaitDstStageMask" VkSubmitInfo Source #

readField :: Ptr VkSubmitInfo -> IO (FieldType "pWaitDstStageMask" VkSubmitInfo) Source #

CanReadField "pWaitSemaphores" VkSubmitInfo Source # 

Methods

getField :: VkSubmitInfo -> FieldType "pWaitSemaphores" VkSubmitInfo Source #

readField :: Ptr VkSubmitInfo -> IO (FieldType "pWaitSemaphores" VkSubmitInfo) Source #

CanReadField "sType" VkSubmitInfo Source # 
CanReadField "signalSemaphoreCount" VkSubmitInfo Source # 

Methods

getField :: VkSubmitInfo -> FieldType "signalSemaphoreCount" VkSubmitInfo Source #

readField :: Ptr VkSubmitInfo -> IO (FieldType "signalSemaphoreCount" VkSubmitInfo) Source #

CanReadField "waitSemaphoreCount" VkSubmitInfo Source # 

Methods

getField :: VkSubmitInfo -> FieldType "waitSemaphoreCount" VkSubmitInfo Source #

readField :: Ptr VkSubmitInfo -> IO (FieldType "waitSemaphoreCount" VkSubmitInfo) Source #

HasField "commandBufferCount" VkSubmitInfo Source # 

Associated Types

type FieldType ("commandBufferCount" :: Symbol) VkSubmitInfo :: Type Source #

type FieldOptional ("commandBufferCount" :: Symbol) VkSubmitInfo :: Bool Source #

type FieldOffset ("commandBufferCount" :: Symbol) VkSubmitInfo :: Nat Source #

type FieldIsArray ("commandBufferCount" :: Symbol) VkSubmitInfo :: Bool Source #

HasField "pCommandBuffers" VkSubmitInfo Source # 

Associated Types

type FieldType ("pCommandBuffers" :: Symbol) VkSubmitInfo :: Type Source #

type FieldOptional ("pCommandBuffers" :: Symbol) VkSubmitInfo :: Bool Source #

type FieldOffset ("pCommandBuffers" :: Symbol) VkSubmitInfo :: Nat Source #

type FieldIsArray ("pCommandBuffers" :: Symbol) VkSubmitInfo :: Bool Source #

HasField "pNext" VkSubmitInfo Source # 

Associated Types

type FieldType ("pNext" :: Symbol) VkSubmitInfo :: Type Source #

type FieldOptional ("pNext" :: Symbol) VkSubmitInfo :: Bool Source #

type FieldOffset ("pNext" :: Symbol) VkSubmitInfo :: Nat Source #

type FieldIsArray ("pNext" :: Symbol) VkSubmitInfo :: Bool Source #

HasField "pSignalSemaphores" VkSubmitInfo Source # 

Associated Types

type FieldType ("pSignalSemaphores" :: Symbol) VkSubmitInfo :: Type Source #

type FieldOptional ("pSignalSemaphores" :: Symbol) VkSubmitInfo :: Bool Source #

type FieldOffset ("pSignalSemaphores" :: Symbol) VkSubmitInfo :: Nat Source #

type FieldIsArray ("pSignalSemaphores" :: Symbol) VkSubmitInfo :: Bool Source #

HasField "pWaitDstStageMask" VkSubmitInfo Source # 

Associated Types

type FieldType ("pWaitDstStageMask" :: Symbol) VkSubmitInfo :: Type Source #

type FieldOptional ("pWaitDstStageMask" :: Symbol) VkSubmitInfo :: Bool Source #

type FieldOffset ("pWaitDstStageMask" :: Symbol) VkSubmitInfo :: Nat Source #

type FieldIsArray ("pWaitDstStageMask" :: Symbol) VkSubmitInfo :: Bool Source #

HasField "pWaitSemaphores" VkSubmitInfo Source # 

Associated Types

type FieldType ("pWaitSemaphores" :: Symbol) VkSubmitInfo :: Type Source #

type FieldOptional ("pWaitSemaphores" :: Symbol) VkSubmitInfo :: Bool Source #

type FieldOffset ("pWaitSemaphores" :: Symbol) VkSubmitInfo :: Nat Source #

type FieldIsArray ("pWaitSemaphores" :: Symbol) VkSubmitInfo :: Bool Source #

HasField "sType" VkSubmitInfo Source # 

Associated Types

type FieldType ("sType" :: Symbol) VkSubmitInfo :: Type Source #

type FieldOptional ("sType" :: Symbol) VkSubmitInfo :: Bool Source #

type FieldOffset ("sType" :: Symbol) VkSubmitInfo :: Nat Source #

type FieldIsArray ("sType" :: Symbol) VkSubmitInfo :: Bool Source #

HasField "signalSemaphoreCount" VkSubmitInfo Source # 

Associated Types

type FieldType ("signalSemaphoreCount" :: Symbol) VkSubmitInfo :: Type Source #

type FieldOptional ("signalSemaphoreCount" :: Symbol) VkSubmitInfo :: Bool Source #

type FieldOffset ("signalSemaphoreCount" :: Symbol) VkSubmitInfo :: Nat Source #

type FieldIsArray ("signalSemaphoreCount" :: Symbol) VkSubmitInfo :: Bool Source #

HasField "waitSemaphoreCount" VkSubmitInfo Source # 

Associated Types

type FieldType ("waitSemaphoreCount" :: Symbol) VkSubmitInfo :: Type Source #

type FieldOptional ("waitSemaphoreCount" :: Symbol) VkSubmitInfo :: Bool Source #

type FieldOffset ("waitSemaphoreCount" :: Symbol) VkSubmitInfo :: Nat Source #

type FieldIsArray ("waitSemaphoreCount" :: Symbol) VkSubmitInfo :: Bool Source #

type StructFields VkSubmitInfo Source # 
type StructFields VkSubmitInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "waitSemaphoreCount" ((:) Symbol "pWaitSemaphores" ((:) Symbol "pWaitDstStageMask" ((:) Symbol "commandBufferCount" ((:) Symbol "pCommandBuffers" ((:) Symbol "signalSemaphoreCount" ((:) Symbol "pSignalSemaphores" ([] Symbol)))))))))
type CUnionType VkSubmitInfo Source # 
type ReturnedOnly VkSubmitInfo Source # 
type StructExtends VkSubmitInfo Source # 
type FieldType "commandBufferCount" VkSubmitInfo Source # 
type FieldType "commandBufferCount" VkSubmitInfo = Word32
type FieldType "pCommandBuffers" VkSubmitInfo Source # 
type FieldType "pCommandBuffers" VkSubmitInfo = Ptr VkCommandBuffer
type FieldType "pNext" VkSubmitInfo Source # 
type FieldType "pSignalSemaphores" VkSubmitInfo Source # 
type FieldType "pSignalSemaphores" VkSubmitInfo = Ptr VkSemaphore
type FieldType "pWaitDstStageMask" VkSubmitInfo Source # 
type FieldType "pWaitDstStageMask" VkSubmitInfo = Ptr VkPipelineStageFlags
type FieldType "pWaitSemaphores" VkSubmitInfo Source # 
type FieldType "pWaitSemaphores" VkSubmitInfo = Ptr VkSemaphore
type FieldType "sType" VkSubmitInfo Source # 
type FieldType "signalSemaphoreCount" VkSubmitInfo Source # 
type FieldType "signalSemaphoreCount" VkSubmitInfo = Word32
type FieldType "waitSemaphoreCount" VkSubmitInfo Source # 
type FieldType "waitSemaphoreCount" VkSubmitInfo = Word32
type FieldOptional "commandBufferCount" VkSubmitInfo Source # 
type FieldOptional "commandBufferCount" VkSubmitInfo = True
type FieldOptional "pCommandBuffers" VkSubmitInfo Source # 
type FieldOptional "pCommandBuffers" VkSubmitInfo = False
type FieldOptional "pNext" VkSubmitInfo Source # 
type FieldOptional "pSignalSemaphores" VkSubmitInfo Source # 
type FieldOptional "pSignalSemaphores" VkSubmitInfo = False
type FieldOptional "pWaitDstStageMask" VkSubmitInfo Source # 
type FieldOptional "pWaitDstStageMask" VkSubmitInfo = False
type FieldOptional "pWaitSemaphores" VkSubmitInfo Source # 
type FieldOptional "pWaitSemaphores" VkSubmitInfo = False
type FieldOptional "sType" VkSubmitInfo Source # 
type FieldOptional "signalSemaphoreCount" VkSubmitInfo Source # 
type FieldOptional "signalSemaphoreCount" VkSubmitInfo = True
type FieldOptional "waitSemaphoreCount" VkSubmitInfo Source # 
type FieldOptional "waitSemaphoreCount" VkSubmitInfo = True
type FieldOffset "commandBufferCount" VkSubmitInfo Source # 
type FieldOffset "commandBufferCount" VkSubmitInfo = 40
type FieldOffset "pCommandBuffers" VkSubmitInfo Source # 
type FieldOffset "pCommandBuffers" VkSubmitInfo = 48
type FieldOffset "pNext" VkSubmitInfo Source # 
type FieldOffset "pNext" VkSubmitInfo = 8
type FieldOffset "pSignalSemaphores" VkSubmitInfo Source # 
type FieldOffset "pSignalSemaphores" VkSubmitInfo = 64
type FieldOffset "pWaitDstStageMask" VkSubmitInfo Source # 
type FieldOffset "pWaitDstStageMask" VkSubmitInfo = 32
type FieldOffset "pWaitSemaphores" VkSubmitInfo Source # 
type FieldOffset "pWaitSemaphores" VkSubmitInfo = 24
type FieldOffset "sType" VkSubmitInfo Source # 
type FieldOffset "sType" VkSubmitInfo = 0
type FieldOffset "signalSemaphoreCount" VkSubmitInfo Source # 
type FieldOffset "signalSemaphoreCount" VkSubmitInfo = 56
type FieldOffset "waitSemaphoreCount" VkSubmitInfo Source # 
type FieldOffset "waitSemaphoreCount" VkSubmitInfo = 16
type FieldIsArray "commandBufferCount" VkSubmitInfo Source # 
type FieldIsArray "commandBufferCount" VkSubmitInfo = False
type FieldIsArray "pCommandBuffers" VkSubmitInfo Source # 
type FieldIsArray "pCommandBuffers" VkSubmitInfo = False
type FieldIsArray "pNext" VkSubmitInfo Source # 
type FieldIsArray "pSignalSemaphores" VkSubmitInfo Source # 
type FieldIsArray "pSignalSemaphores" VkSubmitInfo = False
type FieldIsArray "pWaitDstStageMask" VkSubmitInfo Source # 
type FieldIsArray "pWaitDstStageMask" VkSubmitInfo = False
type FieldIsArray "pWaitSemaphores" VkSubmitInfo Source # 
type FieldIsArray "pWaitSemaphores" VkSubmitInfo = False
type FieldIsArray "sType" VkSubmitInfo Source # 
type FieldIsArray "signalSemaphoreCount" VkSubmitInfo Source # 
type FieldIsArray "signalSemaphoreCount" VkSubmitInfo = False
type FieldIsArray "waitSemaphoreCount" VkSubmitInfo Source # 
type FieldIsArray "waitSemaphoreCount" VkSubmitInfo = False

type VkGetDeviceGroupPeerMemoryFeatures = "vkGetDeviceGroupPeerMemoryFeatures" Source #

type HS_vkGetDeviceGroupPeerMemoryFeatures Source #

Arguments

 = VkDevice

device

-> Word32

heapIndex

-> Word32

localDeviceIndex

-> Word32

remoteDeviceIndex

-> Ptr VkPeerMemoryFeatureFlags

pPeerMemoryFeatures

-> IO () 
void vkGetDeviceGroupPeerMemoryFeatures
    ( VkDevice device
    , uint32_t heapIndex
    , uint32_t localDeviceIndex
    , uint32_t remoteDeviceIndex
    , VkPeerMemoryFeatureFlags* pPeerMemoryFeatures
    )

vkGetDeviceGroupPeerMemoryFeatures registry at www.khronos.org

vkGetDeviceGroupPeerMemoryFeatures Source #

Arguments

:: VkDevice

device

-> Word32

heapIndex

-> Word32

localDeviceIndex

-> Word32

remoteDeviceIndex

-> Ptr VkPeerMemoryFeatureFlags

pPeerMemoryFeatures

-> IO () 
void vkGetDeviceGroupPeerMemoryFeatures
    ( VkDevice device
    , uint32_t heapIndex
    , uint32_t localDeviceIndex
    , uint32_t remoteDeviceIndex
    , VkPeerMemoryFeatureFlags* pPeerMemoryFeatures
    )

vkGetDeviceGroupPeerMemoryFeatures registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetDeviceGroupPeerMemoryFeatures <- vkGetDeviceProc @VkGetDeviceGroupPeerMemoryFeatures vkDevice

or less efficient:

myGetDeviceGroupPeerMemoryFeatures <- vkGetProc @VkGetDeviceGroupPeerMemoryFeatures

Note: vkGetDeviceGroupPeerMemoryFeaturesUnsafe and vkGetDeviceGroupPeerMemoryFeaturesSafe are the unsafe and safe FFI imports of this function, respectively. vkGetDeviceGroupPeerMemoryFeatures is an alias of vkGetDeviceGroupPeerMemoryFeaturesUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetDeviceGroupPeerMemoryFeaturesSafe.

vkGetDeviceGroupPeerMemoryFeaturesUnsafe Source #

Arguments

:: VkDevice

device

-> Word32

heapIndex

-> Word32

localDeviceIndex

-> Word32

remoteDeviceIndex

-> Ptr VkPeerMemoryFeatureFlags

pPeerMemoryFeatures

-> IO () 
void vkGetDeviceGroupPeerMemoryFeatures
    ( VkDevice device
    , uint32_t heapIndex
    , uint32_t localDeviceIndex
    , uint32_t remoteDeviceIndex
    , VkPeerMemoryFeatureFlags* pPeerMemoryFeatures
    )

vkGetDeviceGroupPeerMemoryFeatures registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetDeviceGroupPeerMemoryFeatures <- vkGetDeviceProc @VkGetDeviceGroupPeerMemoryFeatures vkDevice

or less efficient:

myGetDeviceGroupPeerMemoryFeatures <- vkGetProc @VkGetDeviceGroupPeerMemoryFeatures

Note: vkGetDeviceGroupPeerMemoryFeaturesUnsafe and vkGetDeviceGroupPeerMemoryFeaturesSafe are the unsafe and safe FFI imports of this function, respectively. vkGetDeviceGroupPeerMemoryFeatures is an alias of vkGetDeviceGroupPeerMemoryFeaturesUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetDeviceGroupPeerMemoryFeaturesSafe.

vkGetDeviceGroupPeerMemoryFeaturesSafe Source #

Arguments

:: VkDevice

device

-> Word32

heapIndex

-> Word32

localDeviceIndex

-> Word32

remoteDeviceIndex

-> Ptr VkPeerMemoryFeatureFlags

pPeerMemoryFeatures

-> IO () 
void vkGetDeviceGroupPeerMemoryFeatures
    ( VkDevice device
    , uint32_t heapIndex
    , uint32_t localDeviceIndex
    , uint32_t remoteDeviceIndex
    , VkPeerMemoryFeatureFlags* pPeerMemoryFeatures
    )

vkGetDeviceGroupPeerMemoryFeatures registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetDeviceGroupPeerMemoryFeatures <- vkGetDeviceProc @VkGetDeviceGroupPeerMemoryFeatures vkDevice

or less efficient:

myGetDeviceGroupPeerMemoryFeatures <- vkGetProc @VkGetDeviceGroupPeerMemoryFeatures

Note: vkGetDeviceGroupPeerMemoryFeaturesUnsafe and vkGetDeviceGroupPeerMemoryFeaturesSafe are the unsafe and safe FFI imports of this function, respectively. vkGetDeviceGroupPeerMemoryFeatures is an alias of vkGetDeviceGroupPeerMemoryFeaturesUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetDeviceGroupPeerMemoryFeaturesSafe.

type VkCmdSetDeviceMask = "vkCmdSetDeviceMask" Source #

type HS_vkCmdSetDeviceMask Source #

Arguments

 = VkCommandBuffer

commandBuffer

-> Word32

deviceMask

-> IO () 

Queues: graphics, compute, transfer.

Renderpass: both

void vkCmdSetDeviceMask
    ( VkCommandBuffer commandBuffer
    , uint32_t deviceMask
    )

vkCmdSetDeviceMask registry at www.khronos.org

vkCmdSetDeviceMask Source #

Arguments

:: VkCommandBuffer

commandBuffer

-> Word32

deviceMask

-> IO () 

Queues: graphics, compute, transfer.

Renderpass: both

void vkCmdSetDeviceMask
    ( VkCommandBuffer commandBuffer
    , uint32_t deviceMask
    )

vkCmdSetDeviceMask registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myCmdSetDeviceMask <- vkGetInstanceProc @VkCmdSetDeviceMask vkInstance

or less efficient:

myCmdSetDeviceMask <- vkGetProc @VkCmdSetDeviceMask

Note: vkCmdSetDeviceMaskUnsafe and vkCmdSetDeviceMaskSafe are the unsafe and safe FFI imports of this function, respectively. vkCmdSetDeviceMask is an alias of vkCmdSetDeviceMaskUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkCmdSetDeviceMaskSafe.

vkCmdSetDeviceMaskUnsafe Source #

Arguments

:: VkCommandBuffer

commandBuffer

-> Word32

deviceMask

-> IO () 

Queues: graphics, compute, transfer.

Renderpass: both

void vkCmdSetDeviceMask
    ( VkCommandBuffer commandBuffer
    , uint32_t deviceMask
    )

vkCmdSetDeviceMask registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myCmdSetDeviceMask <- vkGetInstanceProc @VkCmdSetDeviceMask vkInstance

or less efficient:

myCmdSetDeviceMask <- vkGetProc @VkCmdSetDeviceMask

Note: vkCmdSetDeviceMaskUnsafe and vkCmdSetDeviceMaskSafe are the unsafe and safe FFI imports of this function, respectively. vkCmdSetDeviceMask is an alias of vkCmdSetDeviceMaskUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkCmdSetDeviceMaskSafe.

vkCmdSetDeviceMaskSafe Source #

Arguments

:: VkCommandBuffer

commandBuffer

-> Word32

deviceMask

-> IO () 

Queues: graphics, compute, transfer.

Renderpass: both

void vkCmdSetDeviceMask
    ( VkCommandBuffer commandBuffer
    , uint32_t deviceMask
    )

vkCmdSetDeviceMask registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myCmdSetDeviceMask <- vkGetInstanceProc @VkCmdSetDeviceMask vkInstance

or less efficient:

myCmdSetDeviceMask <- vkGetProc @VkCmdSetDeviceMask

Note: vkCmdSetDeviceMaskUnsafe and vkCmdSetDeviceMaskSafe are the unsafe and safe FFI imports of this function, respectively. vkCmdSetDeviceMask is an alias of vkCmdSetDeviceMaskUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkCmdSetDeviceMaskSafe.

type VkCmdDispatchBase = "vkCmdDispatchBase" Source #

type HS_vkCmdDispatchBase Source #

Arguments

 = VkCommandBuffer

commandBuffer

-> Word32

baseGroupX

-> Word32

baseGroupY

-> Word32

baseGroupZ

-> Word32

groupCountX

-> Word32

groupCountY

-> Word32

groupCountZ

-> IO () 

Queues: compute.

Renderpass: outside

void vkCmdDispatchBase
    ( VkCommandBuffer commandBuffer
    , uint32_t baseGroupX
    , uint32_t baseGroupY
    , uint32_t baseGroupZ
    , uint32_t groupCountX
    , uint32_t groupCountY
    , uint32_t groupCountZ
    )

vkCmdDispatchBase registry at www.khronos.org

vkCmdDispatchBase Source #

Arguments

:: VkCommandBuffer

commandBuffer

-> Word32

baseGroupX

-> Word32

baseGroupY

-> Word32

baseGroupZ

-> Word32

groupCountX

-> Word32

groupCountY

-> Word32

groupCountZ

-> IO () 

Queues: compute.

Renderpass: outside

void vkCmdDispatchBase
    ( VkCommandBuffer commandBuffer
    , uint32_t baseGroupX
    , uint32_t baseGroupY
    , uint32_t baseGroupZ
    , uint32_t groupCountX
    , uint32_t groupCountY
    , uint32_t groupCountZ
    )

vkCmdDispatchBase registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myCmdDispatchBase <- vkGetInstanceProc @VkCmdDispatchBase vkInstance

or less efficient:

myCmdDispatchBase <- vkGetProc @VkCmdDispatchBase

Note: vkCmdDispatchBaseUnsafe and vkCmdDispatchBaseSafe are the unsafe and safe FFI imports of this function, respectively. vkCmdDispatchBase is an alias of vkCmdDispatchBaseUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkCmdDispatchBaseSafe.

vkCmdDispatchBaseUnsafe Source #

Arguments

:: VkCommandBuffer

commandBuffer

-> Word32

baseGroupX

-> Word32

baseGroupY

-> Word32

baseGroupZ

-> Word32

groupCountX

-> Word32

groupCountY

-> Word32

groupCountZ

-> IO () 

Queues: compute.

Renderpass: outside

void vkCmdDispatchBase
    ( VkCommandBuffer commandBuffer
    , uint32_t baseGroupX
    , uint32_t baseGroupY
    , uint32_t baseGroupZ
    , uint32_t groupCountX
    , uint32_t groupCountY
    , uint32_t groupCountZ
    )

vkCmdDispatchBase registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myCmdDispatchBase <- vkGetInstanceProc @VkCmdDispatchBase vkInstance

or less efficient:

myCmdDispatchBase <- vkGetProc @VkCmdDispatchBase

Note: vkCmdDispatchBaseUnsafe and vkCmdDispatchBaseSafe are the unsafe and safe FFI imports of this function, respectively. vkCmdDispatchBase is an alias of vkCmdDispatchBaseUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkCmdDispatchBaseSafe.

vkCmdDispatchBaseSafe Source #

Arguments

:: VkCommandBuffer

commandBuffer

-> Word32

baseGroupX

-> Word32

baseGroupY

-> Word32

baseGroupZ

-> Word32

groupCountX

-> Word32

groupCountY

-> Word32

groupCountZ

-> IO () 

Queues: compute.

Renderpass: outside

void vkCmdDispatchBase
    ( VkCommandBuffer commandBuffer
    , uint32_t baseGroupX
    , uint32_t baseGroupY
    , uint32_t baseGroupZ
    , uint32_t groupCountX
    , uint32_t groupCountY
    , uint32_t groupCountZ
    )

vkCmdDispatchBase registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myCmdDispatchBase <- vkGetInstanceProc @VkCmdDispatchBase vkInstance

or less efficient:

myCmdDispatchBase <- vkGetProc @VkCmdDispatchBase

Note: vkCmdDispatchBaseUnsafe and vkCmdDispatchBaseSafe are the unsafe and safe FFI imports of this function, respectively. vkCmdDispatchBase is an alias of vkCmdDispatchBaseUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkCmdDispatchBaseSafe.

pattern VK_DEPENDENCY_DEVICE_GROUP_BIT :: VkDependencyFlagBits Source #

Dependency is across devices

bitpos = 2

Promoted from VK_KHR_device_group + VK_KHR_bind_memory2

#include "vk_platform.h"

pattern VK_IMAGE_CREATE_SPLIT_INSTANCE_BIND_REGIONS_BIT :: VkImageCreateFlagBits Source #

Allows using VkBindImageMemoryDeviceGroupInfo::pSplitInstanceBindRegions when binding memory to the image

bitpos = 6

Promoted from VK_KHR_device_group_creation

#include "vk_platform.h"

type VkEnumeratePhysicalDeviceGroups = "vkEnumeratePhysicalDeviceGroups" Source #

type HS_vkEnumeratePhysicalDeviceGroups Source #

Arguments

 = VkInstance

instance

-> Ptr Word32

pPhysicalDeviceGroupCount

-> Ptr VkPhysicalDeviceGroupProperties

pPhysicalDeviceGroupProperties

-> IO VkResult 

Success codes: VK_SUCCESS, VK_INCOMPLETE.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY, VK_ERROR_INITIALIZATION_FAILED.

VkResult vkEnumeratePhysicalDeviceGroups
    ( VkInstance instance
    , uint32_t* pPhysicalDeviceGroupCount
    , VkPhysicalDeviceGroupProperties* pPhysicalDeviceGroupProperties
    )

vkEnumeratePhysicalDeviceGroups registry at www.khronos.org

vkEnumeratePhysicalDeviceGroups Source #

Arguments

:: VkInstance

instance

-> Ptr Word32

pPhysicalDeviceGroupCount

-> Ptr VkPhysicalDeviceGroupProperties

pPhysicalDeviceGroupProperties

-> IO VkResult 

Success codes: VK_SUCCESS, VK_INCOMPLETE.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY, VK_ERROR_INITIALIZATION_FAILED.

VkResult vkEnumeratePhysicalDeviceGroups
    ( VkInstance instance
    , uint32_t* pPhysicalDeviceGroupCount
    , VkPhysicalDeviceGroupProperties* pPhysicalDeviceGroupProperties
    )

vkEnumeratePhysicalDeviceGroups registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myEnumeratePhysicalDeviceGroups <- vkGetInstanceProc @VkEnumeratePhysicalDeviceGroups vkInstance

or less efficient:

myEnumeratePhysicalDeviceGroups <- vkGetProc @VkEnumeratePhysicalDeviceGroups

Note: vkEnumeratePhysicalDeviceGroupsUnsafe and vkEnumeratePhysicalDeviceGroupsSafe are the unsafe and safe FFI imports of this function, respectively. vkEnumeratePhysicalDeviceGroups is an alias of vkEnumeratePhysicalDeviceGroupsUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkEnumeratePhysicalDeviceGroupsSafe.

vkEnumeratePhysicalDeviceGroupsUnsafe Source #

Arguments

:: VkInstance

instance

-> Ptr Word32

pPhysicalDeviceGroupCount

-> Ptr VkPhysicalDeviceGroupProperties

pPhysicalDeviceGroupProperties

-> IO VkResult 

Success codes: VK_SUCCESS, VK_INCOMPLETE.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY, VK_ERROR_INITIALIZATION_FAILED.

VkResult vkEnumeratePhysicalDeviceGroups
    ( VkInstance instance
    , uint32_t* pPhysicalDeviceGroupCount
    , VkPhysicalDeviceGroupProperties* pPhysicalDeviceGroupProperties
    )

vkEnumeratePhysicalDeviceGroups registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myEnumeratePhysicalDeviceGroups <- vkGetInstanceProc @VkEnumeratePhysicalDeviceGroups vkInstance

or less efficient:

myEnumeratePhysicalDeviceGroups <- vkGetProc @VkEnumeratePhysicalDeviceGroups

Note: vkEnumeratePhysicalDeviceGroupsUnsafe and vkEnumeratePhysicalDeviceGroupsSafe are the unsafe and safe FFI imports of this function, respectively. vkEnumeratePhysicalDeviceGroups is an alias of vkEnumeratePhysicalDeviceGroupsUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkEnumeratePhysicalDeviceGroupsSafe.

vkEnumeratePhysicalDeviceGroupsSafe Source #

Arguments

:: VkInstance

instance

-> Ptr Word32

pPhysicalDeviceGroupCount

-> Ptr VkPhysicalDeviceGroupProperties

pPhysicalDeviceGroupProperties

-> IO VkResult 

Success codes: VK_SUCCESS, VK_INCOMPLETE.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY, VK_ERROR_INITIALIZATION_FAILED.

VkResult vkEnumeratePhysicalDeviceGroups
    ( VkInstance instance
    , uint32_t* pPhysicalDeviceGroupCount
    , VkPhysicalDeviceGroupProperties* pPhysicalDeviceGroupProperties
    )

vkEnumeratePhysicalDeviceGroups registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myEnumeratePhysicalDeviceGroups <- vkGetInstanceProc @VkEnumeratePhysicalDeviceGroups vkInstance

or less efficient:

myEnumeratePhysicalDeviceGroups <- vkGetProc @VkEnumeratePhysicalDeviceGroups

Note: vkEnumeratePhysicalDeviceGroupsUnsafe and vkEnumeratePhysicalDeviceGroupsSafe are the unsafe and safe FFI imports of this function, respectively. vkEnumeratePhysicalDeviceGroups is an alias of vkEnumeratePhysicalDeviceGroupsUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkEnumeratePhysicalDeviceGroupsSafe.

pattern VK_MAX_DEVICE_GROUP_SIZE :: forall a. (Num a, Eq a) => a Source #

pattern VK_MEMORY_HEAP_MULTI_INSTANCE_BIT :: VkMemoryHeapFlagBits Source #

If set, heap allocations allocate multiple instances by default

bitpos = 1

Promoted from VK_KHR_get_memory_requirements2

data VkBufferCopy Source #

typedef struct VkBufferCopy {
    VkDeviceSize           srcOffset;
    VkDeviceSize           dstOffset;
    VkDeviceSize           size;
} VkBufferCopy;

VkBufferCopy registry at www.khronos.org

Instances

Eq VkBufferCopy Source # 
Ord VkBufferCopy Source # 
Show VkBufferCopy Source # 
Storable VkBufferCopy Source # 
VulkanMarshalPrim VkBufferCopy Source # 
VulkanMarshal VkBufferCopy Source # 
CanWriteField "dstOffset" VkBufferCopy Source # 

Methods

writeField :: Ptr VkBufferCopy -> FieldType "dstOffset" VkBufferCopy -> IO () Source #

CanWriteField "size" VkBufferCopy Source # 
CanWriteField "srcOffset" VkBufferCopy Source # 

Methods

writeField :: Ptr VkBufferCopy -> FieldType "srcOffset" VkBufferCopy -> IO () Source #

CanReadField "dstOffset" VkBufferCopy Source # 
CanReadField "size" VkBufferCopy Source # 
CanReadField "srcOffset" VkBufferCopy Source # 
HasField "dstOffset" VkBufferCopy Source # 

Associated Types

type FieldType ("dstOffset" :: Symbol) VkBufferCopy :: Type Source #

type FieldOptional ("dstOffset" :: Symbol) VkBufferCopy :: Bool Source #

type FieldOffset ("dstOffset" :: Symbol) VkBufferCopy :: Nat Source #

type FieldIsArray ("dstOffset" :: Symbol) VkBufferCopy :: Bool Source #

HasField "size" VkBufferCopy Source # 
HasField "srcOffset" VkBufferCopy Source # 

Associated Types

type FieldType ("srcOffset" :: Symbol) VkBufferCopy :: Type Source #

type FieldOptional ("srcOffset" :: Symbol) VkBufferCopy :: Bool Source #

type FieldOffset ("srcOffset" :: Symbol) VkBufferCopy :: Nat Source #

type FieldIsArray ("srcOffset" :: Symbol) VkBufferCopy :: Bool Source #

type StructFields VkBufferCopy Source # 
type StructFields VkBufferCopy = (:) Symbol "srcOffset" ((:) Symbol "dstOffset" ((:) Symbol "size" ([] Symbol)))
type CUnionType VkBufferCopy Source # 
type ReturnedOnly VkBufferCopy Source # 
type StructExtends VkBufferCopy Source # 
type FieldType "dstOffset" VkBufferCopy Source # 
type FieldType "size" VkBufferCopy Source # 
type FieldType "srcOffset" VkBufferCopy Source # 
type FieldOptional "dstOffset" VkBufferCopy Source # 
type FieldOptional "dstOffset" VkBufferCopy = False
type FieldOptional "size" VkBufferCopy Source # 
type FieldOptional "srcOffset" VkBufferCopy Source # 
type FieldOptional "srcOffset" VkBufferCopy = False
type FieldOffset "dstOffset" VkBufferCopy Source # 
type FieldOffset "dstOffset" VkBufferCopy = 8
type FieldOffset "size" VkBufferCopy Source # 
type FieldOffset "size" VkBufferCopy = 16
type FieldOffset "srcOffset" VkBufferCopy Source # 
type FieldOffset "srcOffset" VkBufferCopy = 0
type FieldIsArray "dstOffset" VkBufferCopy Source # 
type FieldIsArray "dstOffset" VkBufferCopy = False
type FieldIsArray "size" VkBufferCopy Source # 
type FieldIsArray "srcOffset" VkBufferCopy Source # 
type FieldIsArray "srcOffset" VkBufferCopy = False

data VkBufferCreateInfo Source #

typedef struct VkBufferCreateInfo {
    VkStructureType sType;
    const void*            pNext;
    VkBufferCreateFlags    flags;
    VkDeviceSize           size;
    VkBufferUsageFlags     usage;
    VkSharingMode          sharingMode;
    uint32_t               queueFamilyIndexCount;
    const uint32_t*        pQueueFamilyIndices;
} VkBufferCreateInfo;

VkBufferCreateInfo registry at www.khronos.org

Instances

Eq VkBufferCreateInfo Source # 
Ord VkBufferCreateInfo Source # 
Show VkBufferCreateInfo Source # 
Storable VkBufferCreateInfo Source # 
VulkanMarshalPrim VkBufferCreateInfo Source # 
VulkanMarshal VkBufferCreateInfo Source # 
CanWriteField "flags" VkBufferCreateInfo Source # 
CanWriteField "pNext" VkBufferCreateInfo Source # 
CanWriteField "pQueueFamilyIndices" VkBufferCreateInfo Source # 

Methods

writeField :: Ptr VkBufferCreateInfo -> FieldType "pQueueFamilyIndices" VkBufferCreateInfo -> IO () Source #

CanWriteField "queueFamilyIndexCount" VkBufferCreateInfo Source # 

Methods

writeField :: Ptr VkBufferCreateInfo -> FieldType "queueFamilyIndexCount" VkBufferCreateInfo -> IO () Source #

CanWriteField "sType" VkBufferCreateInfo Source # 
CanWriteField "sharingMode" VkBufferCreateInfo Source # 
CanWriteField "size" VkBufferCreateInfo Source # 
CanWriteField "usage" VkBufferCreateInfo Source # 
CanReadField "flags" VkBufferCreateInfo Source # 
CanReadField "pNext" VkBufferCreateInfo Source # 
CanReadField "pQueueFamilyIndices" VkBufferCreateInfo Source # 
CanReadField "queueFamilyIndexCount" VkBufferCreateInfo Source # 
CanReadField "sType" VkBufferCreateInfo Source # 
CanReadField "sharingMode" VkBufferCreateInfo Source # 
CanReadField "size" VkBufferCreateInfo Source # 
CanReadField "usage" VkBufferCreateInfo Source # 
HasField "flags" VkBufferCreateInfo Source # 
HasField "pNext" VkBufferCreateInfo Source # 
HasField "pQueueFamilyIndices" VkBufferCreateInfo Source # 

Associated Types

type FieldType ("pQueueFamilyIndices" :: Symbol) VkBufferCreateInfo :: Type Source #

type FieldOptional ("pQueueFamilyIndices" :: Symbol) VkBufferCreateInfo :: Bool Source #

type FieldOffset ("pQueueFamilyIndices" :: Symbol) VkBufferCreateInfo :: Nat Source #

type FieldIsArray ("pQueueFamilyIndices" :: Symbol) VkBufferCreateInfo :: Bool Source #

HasField "queueFamilyIndexCount" VkBufferCreateInfo Source # 

Associated Types

type FieldType ("queueFamilyIndexCount" :: Symbol) VkBufferCreateInfo :: Type Source #

type FieldOptional ("queueFamilyIndexCount" :: Symbol) VkBufferCreateInfo :: Bool Source #

type FieldOffset ("queueFamilyIndexCount" :: Symbol) VkBufferCreateInfo :: Nat Source #

type FieldIsArray ("queueFamilyIndexCount" :: Symbol) VkBufferCreateInfo :: Bool Source #

HasField "sType" VkBufferCreateInfo Source # 
HasField "sharingMode" VkBufferCreateInfo Source # 

Associated Types

type FieldType ("sharingMode" :: Symbol) VkBufferCreateInfo :: Type Source #

type FieldOptional ("sharingMode" :: Symbol) VkBufferCreateInfo :: Bool Source #

type FieldOffset ("sharingMode" :: Symbol) VkBufferCreateInfo :: Nat Source #

type FieldIsArray ("sharingMode" :: Symbol) VkBufferCreateInfo :: Bool Source #

HasField "size" VkBufferCreateInfo Source # 
HasField "usage" VkBufferCreateInfo Source # 
type StructFields VkBufferCreateInfo Source # 
type StructFields VkBufferCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "size" ((:) Symbol "usage" ((:) Symbol "sharingMode" ((:) Symbol "queueFamilyIndexCount" ((:) Symbol "pQueueFamilyIndices" ([] Symbol))))))))
type CUnionType VkBufferCreateInfo Source # 
type ReturnedOnly VkBufferCreateInfo Source # 
type StructExtends VkBufferCreateInfo Source # 
type FieldType "flags" VkBufferCreateInfo Source # 
type FieldType "pNext" VkBufferCreateInfo Source # 
type FieldType "pQueueFamilyIndices" VkBufferCreateInfo Source # 
type FieldType "pQueueFamilyIndices" VkBufferCreateInfo = Ptr Word32
type FieldType "queueFamilyIndexCount" VkBufferCreateInfo Source # 
type FieldType "queueFamilyIndexCount" VkBufferCreateInfo = Word32
type FieldType "sType" VkBufferCreateInfo Source # 
type FieldType "sharingMode" VkBufferCreateInfo Source # 
type FieldType "size" VkBufferCreateInfo Source # 
type FieldType "usage" VkBufferCreateInfo Source # 
type FieldOptional "flags" VkBufferCreateInfo Source # 
type FieldOptional "pNext" VkBufferCreateInfo Source # 
type FieldOptional "pQueueFamilyIndices" VkBufferCreateInfo Source # 
type FieldOptional "pQueueFamilyIndices" VkBufferCreateInfo = False
type FieldOptional "queueFamilyIndexCount" VkBufferCreateInfo Source # 
type FieldOptional "queueFamilyIndexCount" VkBufferCreateInfo = True
type FieldOptional "sType" VkBufferCreateInfo Source # 
type FieldOptional "sharingMode" VkBufferCreateInfo Source # 
type FieldOptional "size" VkBufferCreateInfo Source # 
type FieldOptional "usage" VkBufferCreateInfo Source # 
type FieldOffset "flags" VkBufferCreateInfo Source # 
type FieldOffset "pNext" VkBufferCreateInfo Source # 
type FieldOffset "pQueueFamilyIndices" VkBufferCreateInfo Source # 
type FieldOffset "pQueueFamilyIndices" VkBufferCreateInfo = 48
type FieldOffset "queueFamilyIndexCount" VkBufferCreateInfo Source # 
type FieldOffset "queueFamilyIndexCount" VkBufferCreateInfo = 40
type FieldOffset "sType" VkBufferCreateInfo Source # 
type FieldOffset "sharingMode" VkBufferCreateInfo Source # 
type FieldOffset "sharingMode" VkBufferCreateInfo = 36
type FieldOffset "size" VkBufferCreateInfo Source # 
type FieldOffset "usage" VkBufferCreateInfo Source # 
type FieldIsArray "flags" VkBufferCreateInfo Source # 
type FieldIsArray "pNext" VkBufferCreateInfo Source # 
type FieldIsArray "pQueueFamilyIndices" VkBufferCreateInfo Source # 
type FieldIsArray "pQueueFamilyIndices" VkBufferCreateInfo = False
type FieldIsArray "queueFamilyIndexCount" VkBufferCreateInfo Source # 
type FieldIsArray "queueFamilyIndexCount" VkBufferCreateInfo = False
type FieldIsArray "sType" VkBufferCreateInfo Source # 
type FieldIsArray "sharingMode" VkBufferCreateInfo Source # 
type FieldIsArray "size" VkBufferCreateInfo Source # 
type FieldIsArray "usage" VkBufferCreateInfo Source # 

data VkBufferImageCopy Source #

typedef struct VkBufferImageCopy {
    VkDeviceSize           bufferOffset;
    uint32_t               bufferRowLength;
    uint32_t               bufferImageHeight;
    VkImageSubresourceLayers imageSubresource;
    VkOffset3D             imageOffset;
    VkExtent3D             imageExtent;
} VkBufferImageCopy;

VkBufferImageCopy registry at www.khronos.org

Instances

Eq VkBufferImageCopy Source # 
Ord VkBufferImageCopy Source # 
Show VkBufferImageCopy Source # 
Storable VkBufferImageCopy Source # 
VulkanMarshalPrim VkBufferImageCopy Source # 
VulkanMarshal VkBufferImageCopy Source # 
CanWriteField "bufferImageHeight" VkBufferImageCopy Source # 

Methods

writeField :: Ptr VkBufferImageCopy -> FieldType "bufferImageHeight" VkBufferImageCopy -> IO () Source #

CanWriteField "bufferOffset" VkBufferImageCopy Source # 
CanWriteField "bufferRowLength" VkBufferImageCopy Source # 

Methods

writeField :: Ptr VkBufferImageCopy -> FieldType "bufferRowLength" VkBufferImageCopy -> IO () Source #

CanWriteField "imageExtent" VkBufferImageCopy Source # 
CanWriteField "imageOffset" VkBufferImageCopy Source # 
CanWriteField "imageSubresource" VkBufferImageCopy Source # 

Methods

writeField :: Ptr VkBufferImageCopy -> FieldType "imageSubresource" VkBufferImageCopy -> IO () Source #

CanReadField "bufferImageHeight" VkBufferImageCopy Source # 
CanReadField "bufferOffset" VkBufferImageCopy Source # 
CanReadField "bufferRowLength" VkBufferImageCopy Source # 
CanReadField "imageExtent" VkBufferImageCopy Source # 
CanReadField "imageOffset" VkBufferImageCopy Source # 
CanReadField "imageSubresource" VkBufferImageCopy Source # 
HasField "bufferImageHeight" VkBufferImageCopy Source # 

Associated Types

type FieldType ("bufferImageHeight" :: Symbol) VkBufferImageCopy :: Type Source #

type FieldOptional ("bufferImageHeight" :: Symbol) VkBufferImageCopy :: Bool Source #

type FieldOffset ("bufferImageHeight" :: Symbol) VkBufferImageCopy :: Nat Source #

type FieldIsArray ("bufferImageHeight" :: Symbol) VkBufferImageCopy :: Bool Source #

HasField "bufferOffset" VkBufferImageCopy Source # 

Associated Types

type FieldType ("bufferOffset" :: Symbol) VkBufferImageCopy :: Type Source #

type FieldOptional ("bufferOffset" :: Symbol) VkBufferImageCopy :: Bool Source #

type FieldOffset ("bufferOffset" :: Symbol) VkBufferImageCopy :: Nat Source #

type FieldIsArray ("bufferOffset" :: Symbol) VkBufferImageCopy :: Bool Source #

HasField "bufferRowLength" VkBufferImageCopy Source # 

Associated Types

type FieldType ("bufferRowLength" :: Symbol) VkBufferImageCopy :: Type Source #

type FieldOptional ("bufferRowLength" :: Symbol) VkBufferImageCopy :: Bool Source #

type FieldOffset ("bufferRowLength" :: Symbol) VkBufferImageCopy :: Nat Source #

type FieldIsArray ("bufferRowLength" :: Symbol) VkBufferImageCopy :: Bool Source #

HasField "imageExtent" VkBufferImageCopy Source # 

Associated Types

type FieldType ("imageExtent" :: Symbol) VkBufferImageCopy :: Type Source #

type FieldOptional ("imageExtent" :: Symbol) VkBufferImageCopy :: Bool Source #

type FieldOffset ("imageExtent" :: Symbol) VkBufferImageCopy :: Nat Source #

type FieldIsArray ("imageExtent" :: Symbol) VkBufferImageCopy :: Bool Source #

HasField "imageOffset" VkBufferImageCopy Source # 

Associated Types

type FieldType ("imageOffset" :: Symbol) VkBufferImageCopy :: Type Source #

type FieldOptional ("imageOffset" :: Symbol) VkBufferImageCopy :: Bool Source #

type FieldOffset ("imageOffset" :: Symbol) VkBufferImageCopy :: Nat Source #

type FieldIsArray ("imageOffset" :: Symbol) VkBufferImageCopy :: Bool Source #

HasField "imageSubresource" VkBufferImageCopy Source # 

Associated Types

type FieldType ("imageSubresource" :: Symbol) VkBufferImageCopy :: Type Source #

type FieldOptional ("imageSubresource" :: Symbol) VkBufferImageCopy :: Bool Source #

type FieldOffset ("imageSubresource" :: Symbol) VkBufferImageCopy :: Nat Source #

type FieldIsArray ("imageSubresource" :: Symbol) VkBufferImageCopy :: Bool Source #

type StructFields VkBufferImageCopy Source # 
type StructFields VkBufferImageCopy = (:) Symbol "bufferOffset" ((:) Symbol "bufferRowLength" ((:) Symbol "bufferImageHeight" ((:) Symbol "imageSubresource" ((:) Symbol "imageOffset" ((:) Symbol "imageExtent" ([] Symbol))))))
type CUnionType VkBufferImageCopy Source # 
type ReturnedOnly VkBufferImageCopy Source # 
type StructExtends VkBufferImageCopy Source # 
type FieldType "bufferImageHeight" VkBufferImageCopy Source # 
type FieldType "bufferImageHeight" VkBufferImageCopy = Word32
type FieldType "bufferOffset" VkBufferImageCopy Source # 
type FieldType "bufferRowLength" VkBufferImageCopy Source # 
type FieldType "bufferRowLength" VkBufferImageCopy = Word32
type FieldType "imageExtent" VkBufferImageCopy Source # 
type FieldType "imageOffset" VkBufferImageCopy Source # 
type FieldType "imageSubresource" VkBufferImageCopy Source # 
type FieldOptional "bufferImageHeight" VkBufferImageCopy Source # 
type FieldOptional "bufferImageHeight" VkBufferImageCopy = False
type FieldOptional "bufferOffset" VkBufferImageCopy Source # 
type FieldOptional "bufferOffset" VkBufferImageCopy = False
type FieldOptional "bufferRowLength" VkBufferImageCopy Source # 
type FieldOptional "bufferRowLength" VkBufferImageCopy = False
type FieldOptional "imageExtent" VkBufferImageCopy Source # 
type FieldOptional "imageOffset" VkBufferImageCopy Source # 
type FieldOptional "imageSubresource" VkBufferImageCopy Source # 
type FieldOptional "imageSubresource" VkBufferImageCopy = False
type FieldOffset "bufferImageHeight" VkBufferImageCopy Source # 
type FieldOffset "bufferImageHeight" VkBufferImageCopy = 12
type FieldOffset "bufferOffset" VkBufferImageCopy Source # 
type FieldOffset "bufferOffset" VkBufferImageCopy = 0
type FieldOffset "bufferRowLength" VkBufferImageCopy Source # 
type FieldOffset "bufferRowLength" VkBufferImageCopy = 8
type FieldOffset "imageExtent" VkBufferImageCopy Source # 
type FieldOffset "imageExtent" VkBufferImageCopy = 44
type FieldOffset "imageOffset" VkBufferImageCopy Source # 
type FieldOffset "imageOffset" VkBufferImageCopy = 32
type FieldOffset "imageSubresource" VkBufferImageCopy Source # 
type FieldOffset "imageSubresource" VkBufferImageCopy = 16
type FieldIsArray "bufferImageHeight" VkBufferImageCopy Source # 
type FieldIsArray "bufferImageHeight" VkBufferImageCopy = False
type FieldIsArray "bufferOffset" VkBufferImageCopy Source # 
type FieldIsArray "bufferOffset" VkBufferImageCopy = False
type FieldIsArray "bufferRowLength" VkBufferImageCopy Source # 
type FieldIsArray "bufferRowLength" VkBufferImageCopy = False
type FieldIsArray "imageExtent" VkBufferImageCopy Source # 
type FieldIsArray "imageExtent" VkBufferImageCopy = False
type FieldIsArray "imageOffset" VkBufferImageCopy Source # 
type FieldIsArray "imageOffset" VkBufferImageCopy = False
type FieldIsArray "imageSubresource" VkBufferImageCopy Source # 
type FieldIsArray "imageSubresource" VkBufferImageCopy = False

data VkBufferMemoryBarrier Source #

typedef struct VkBufferMemoryBarrier {
    VkStructureType sType;
    const void*            pNext;
    VkAccessFlags          srcAccessMask;
    VkAccessFlags          dstAccessMask;
    uint32_t               srcQueueFamilyIndex;
    uint32_t               dstQueueFamilyIndex;
    VkBuffer               buffer;
    VkDeviceSize           offset;
    VkDeviceSize           size;
} VkBufferMemoryBarrier;

VkBufferMemoryBarrier registry at www.khronos.org

Instances

Eq VkBufferMemoryBarrier Source # 
Ord VkBufferMemoryBarrier Source # 
Show VkBufferMemoryBarrier Source # 
Storable VkBufferMemoryBarrier Source # 
VulkanMarshalPrim VkBufferMemoryBarrier Source # 
VulkanMarshal VkBufferMemoryBarrier Source # 
CanWriteField "buffer" VkBufferMemoryBarrier Source # 
CanWriteField "dstAccessMask" VkBufferMemoryBarrier Source # 
CanWriteField "dstQueueFamilyIndex" VkBufferMemoryBarrier Source # 
CanWriteField "offset" VkBufferMemoryBarrier Source # 
CanWriteField "pNext" VkBufferMemoryBarrier Source # 
CanWriteField "sType" VkBufferMemoryBarrier Source # 
CanWriteField "size" VkBufferMemoryBarrier Source # 
CanWriteField "srcAccessMask" VkBufferMemoryBarrier Source # 
CanWriteField "srcQueueFamilyIndex" VkBufferMemoryBarrier Source # 
CanReadField "buffer" VkBufferMemoryBarrier Source # 
CanReadField "dstAccessMask" VkBufferMemoryBarrier Source # 
CanReadField "dstQueueFamilyIndex" VkBufferMemoryBarrier Source # 
CanReadField "offset" VkBufferMemoryBarrier Source # 
CanReadField "pNext" VkBufferMemoryBarrier Source # 
CanReadField "sType" VkBufferMemoryBarrier Source # 
CanReadField "size" VkBufferMemoryBarrier Source # 
CanReadField "srcAccessMask" VkBufferMemoryBarrier Source # 
CanReadField "srcQueueFamilyIndex" VkBufferMemoryBarrier Source # 
HasField "buffer" VkBufferMemoryBarrier Source # 
HasField "dstAccessMask" VkBufferMemoryBarrier Source # 

Associated Types

type FieldType ("dstAccessMask" :: Symbol) VkBufferMemoryBarrier :: Type Source #

type FieldOptional ("dstAccessMask" :: Symbol) VkBufferMemoryBarrier :: Bool Source #

type FieldOffset ("dstAccessMask" :: Symbol) VkBufferMemoryBarrier :: Nat Source #

type FieldIsArray ("dstAccessMask" :: Symbol) VkBufferMemoryBarrier :: Bool Source #

HasField "dstQueueFamilyIndex" VkBufferMemoryBarrier Source # 

Associated Types

type FieldType ("dstQueueFamilyIndex" :: Symbol) VkBufferMemoryBarrier :: Type Source #

type FieldOptional ("dstQueueFamilyIndex" :: Symbol) VkBufferMemoryBarrier :: Bool Source #

type FieldOffset ("dstQueueFamilyIndex" :: Symbol) VkBufferMemoryBarrier :: Nat Source #

type FieldIsArray ("dstQueueFamilyIndex" :: Symbol) VkBufferMemoryBarrier :: Bool Source #

HasField "offset" VkBufferMemoryBarrier Source # 
HasField "pNext" VkBufferMemoryBarrier Source # 
HasField "sType" VkBufferMemoryBarrier Source # 
HasField "size" VkBufferMemoryBarrier Source # 
HasField "srcAccessMask" VkBufferMemoryBarrier Source # 

Associated Types

type FieldType ("srcAccessMask" :: Symbol) VkBufferMemoryBarrier :: Type Source #

type FieldOptional ("srcAccessMask" :: Symbol) VkBufferMemoryBarrier :: Bool Source #

type FieldOffset ("srcAccessMask" :: Symbol) VkBufferMemoryBarrier :: Nat Source #

type FieldIsArray ("srcAccessMask" :: Symbol) VkBufferMemoryBarrier :: Bool Source #

HasField "srcQueueFamilyIndex" VkBufferMemoryBarrier Source # 

Associated Types

type FieldType ("srcQueueFamilyIndex" :: Symbol) VkBufferMemoryBarrier :: Type Source #

type FieldOptional ("srcQueueFamilyIndex" :: Symbol) VkBufferMemoryBarrier :: Bool Source #

type FieldOffset ("srcQueueFamilyIndex" :: Symbol) VkBufferMemoryBarrier :: Nat Source #

type FieldIsArray ("srcQueueFamilyIndex" :: Symbol) VkBufferMemoryBarrier :: Bool Source #

type StructFields VkBufferMemoryBarrier Source # 
type StructFields VkBufferMemoryBarrier = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "srcAccessMask" ((:) Symbol "dstAccessMask" ((:) Symbol "srcQueueFamilyIndex" ((:) Symbol "dstQueueFamilyIndex" ((:) Symbol "buffer" ((:) Symbol "offset" ((:) Symbol "size" ([] Symbol)))))))))
type CUnionType VkBufferMemoryBarrier Source # 
type ReturnedOnly VkBufferMemoryBarrier Source # 
type StructExtends VkBufferMemoryBarrier Source # 
type FieldType "buffer" VkBufferMemoryBarrier Source # 
type FieldType "dstAccessMask" VkBufferMemoryBarrier Source # 
type FieldType "dstQueueFamilyIndex" VkBufferMemoryBarrier Source # 
type FieldType "dstQueueFamilyIndex" VkBufferMemoryBarrier = Word32
type FieldType "offset" VkBufferMemoryBarrier Source # 
type FieldType "pNext" VkBufferMemoryBarrier Source # 
type FieldType "sType" VkBufferMemoryBarrier Source # 
type FieldType "size" VkBufferMemoryBarrier Source # 
type FieldType "srcAccessMask" VkBufferMemoryBarrier Source # 
type FieldType "srcQueueFamilyIndex" VkBufferMemoryBarrier Source # 
type FieldType "srcQueueFamilyIndex" VkBufferMemoryBarrier = Word32
type FieldOptional "buffer" VkBufferMemoryBarrier Source # 
type FieldOptional "dstAccessMask" VkBufferMemoryBarrier Source # 
type FieldOptional "dstQueueFamilyIndex" VkBufferMemoryBarrier Source # 
type FieldOptional "dstQueueFamilyIndex" VkBufferMemoryBarrier = False
type FieldOptional "offset" VkBufferMemoryBarrier Source # 
type FieldOptional "pNext" VkBufferMemoryBarrier Source # 
type FieldOptional "sType" VkBufferMemoryBarrier Source # 
type FieldOptional "size" VkBufferMemoryBarrier Source # 
type FieldOptional "srcAccessMask" VkBufferMemoryBarrier Source # 
type FieldOptional "srcQueueFamilyIndex" VkBufferMemoryBarrier Source # 
type FieldOptional "srcQueueFamilyIndex" VkBufferMemoryBarrier = False
type FieldOffset "buffer" VkBufferMemoryBarrier Source # 
type FieldOffset "dstAccessMask" VkBufferMemoryBarrier Source # 
type FieldOffset "dstAccessMask" VkBufferMemoryBarrier = 20
type FieldOffset "dstQueueFamilyIndex" VkBufferMemoryBarrier Source # 
type FieldOffset "dstQueueFamilyIndex" VkBufferMemoryBarrier = 28
type FieldOffset "offset" VkBufferMemoryBarrier Source # 
type FieldOffset "pNext" VkBufferMemoryBarrier Source # 
type FieldOffset "sType" VkBufferMemoryBarrier Source # 
type FieldOffset "size" VkBufferMemoryBarrier Source # 
type FieldOffset "srcAccessMask" VkBufferMemoryBarrier Source # 
type FieldOffset "srcAccessMask" VkBufferMemoryBarrier = 16
type FieldOffset "srcQueueFamilyIndex" VkBufferMemoryBarrier Source # 
type FieldOffset "srcQueueFamilyIndex" VkBufferMemoryBarrier = 24
type FieldIsArray "buffer" VkBufferMemoryBarrier Source # 
type FieldIsArray "dstAccessMask" VkBufferMemoryBarrier Source # 
type FieldIsArray "dstQueueFamilyIndex" VkBufferMemoryBarrier Source # 
type FieldIsArray "dstQueueFamilyIndex" VkBufferMemoryBarrier = False
type FieldIsArray "offset" VkBufferMemoryBarrier Source # 
type FieldIsArray "pNext" VkBufferMemoryBarrier Source # 
type FieldIsArray "sType" VkBufferMemoryBarrier Source # 
type FieldIsArray "size" VkBufferMemoryBarrier Source # 
type FieldIsArray "srcAccessMask" VkBufferMemoryBarrier Source # 
type FieldIsArray "srcQueueFamilyIndex" VkBufferMemoryBarrier Source # 
type FieldIsArray "srcQueueFamilyIndex" VkBufferMemoryBarrier = False

data VkBufferMemoryRequirementsInfo2 Source #

typedef struct VkBufferMemoryRequirementsInfo2 {
    VkStructureType sType;
    const void*                                                          pNext;
    VkBuffer                                                             buffer;
} VkBufferMemoryRequirementsInfo2;

VkBufferMemoryRequirementsInfo2 registry at www.khronos.org

Instances

Eq VkBufferMemoryRequirementsInfo2 Source # 
Ord VkBufferMemoryRequirementsInfo2 Source # 
Show VkBufferMemoryRequirementsInfo2 Source # 
Storable VkBufferMemoryRequirementsInfo2 Source # 
VulkanMarshalPrim VkBufferMemoryRequirementsInfo2 Source # 
VulkanMarshal VkBufferMemoryRequirementsInfo2 Source # 
CanWriteField "buffer" VkBufferMemoryRequirementsInfo2 Source # 
CanWriteField "pNext" VkBufferMemoryRequirementsInfo2 Source # 
CanWriteField "sType" VkBufferMemoryRequirementsInfo2 Source # 
CanReadField "buffer" VkBufferMemoryRequirementsInfo2 Source # 
CanReadField "pNext" VkBufferMemoryRequirementsInfo2 Source # 
CanReadField "sType" VkBufferMemoryRequirementsInfo2 Source # 
HasField "buffer" VkBufferMemoryRequirementsInfo2 Source # 
HasField "pNext" VkBufferMemoryRequirementsInfo2 Source # 
HasField "sType" VkBufferMemoryRequirementsInfo2 Source # 
type StructFields VkBufferMemoryRequirementsInfo2 Source # 
type StructFields VkBufferMemoryRequirementsInfo2 = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "buffer" ([] Symbol)))
type CUnionType VkBufferMemoryRequirementsInfo2 Source # 
type ReturnedOnly VkBufferMemoryRequirementsInfo2 Source # 
type StructExtends VkBufferMemoryRequirementsInfo2 Source # 
type FieldType "buffer" VkBufferMemoryRequirementsInfo2 Source # 
type FieldType "pNext" VkBufferMemoryRequirementsInfo2 Source # 
type FieldType "sType" VkBufferMemoryRequirementsInfo2 Source # 
type FieldOptional "buffer" VkBufferMemoryRequirementsInfo2 Source # 
type FieldOptional "pNext" VkBufferMemoryRequirementsInfo2 Source # 
type FieldOptional "sType" VkBufferMemoryRequirementsInfo2 Source # 
type FieldOffset "buffer" VkBufferMemoryRequirementsInfo2 Source # 
type FieldOffset "pNext" VkBufferMemoryRequirementsInfo2 Source # 
type FieldOffset "sType" VkBufferMemoryRequirementsInfo2 Source # 
type FieldIsArray "buffer" VkBufferMemoryRequirementsInfo2 Source # 
type FieldIsArray "pNext" VkBufferMemoryRequirementsInfo2 Source # 
type FieldIsArray "sType" VkBufferMemoryRequirementsInfo2 Source # 

data VkBufferViewCreateInfo Source #

typedef struct VkBufferViewCreateInfo {
    VkStructureType sType;
    const void*            pNext;
    VkBufferViewCreateFlagsflags;
    VkBuffer               buffer;
    VkFormat               format;
    VkDeviceSize           offset;
    VkDeviceSize           range;
} VkBufferViewCreateInfo;

VkBufferViewCreateInfo registry at www.khronos.org

Instances

Eq VkBufferViewCreateInfo Source # 
Ord VkBufferViewCreateInfo Source # 
Show VkBufferViewCreateInfo Source # 
Storable VkBufferViewCreateInfo Source # 
VulkanMarshalPrim VkBufferViewCreateInfo Source # 
VulkanMarshal VkBufferViewCreateInfo Source # 
CanWriteField "buffer" VkBufferViewCreateInfo Source # 
CanWriteField "flags" VkBufferViewCreateInfo Source # 
CanWriteField "format" VkBufferViewCreateInfo Source # 
CanWriteField "offset" VkBufferViewCreateInfo Source # 
CanWriteField "pNext" VkBufferViewCreateInfo Source # 
CanWriteField "range" VkBufferViewCreateInfo Source # 
CanWriteField "sType" VkBufferViewCreateInfo Source # 
CanReadField "buffer" VkBufferViewCreateInfo Source # 
CanReadField "flags" VkBufferViewCreateInfo Source # 
CanReadField "format" VkBufferViewCreateInfo Source # 
CanReadField "offset" VkBufferViewCreateInfo Source # 
CanReadField "pNext" VkBufferViewCreateInfo Source # 
CanReadField "range" VkBufferViewCreateInfo Source # 
CanReadField "sType" VkBufferViewCreateInfo Source # 
HasField "buffer" VkBufferViewCreateInfo Source # 
HasField "flags" VkBufferViewCreateInfo Source # 
HasField "format" VkBufferViewCreateInfo Source # 
HasField "offset" VkBufferViewCreateInfo Source # 
HasField "pNext" VkBufferViewCreateInfo Source # 
HasField "range" VkBufferViewCreateInfo Source # 
HasField "sType" VkBufferViewCreateInfo Source # 
type StructFields VkBufferViewCreateInfo Source # 
type StructFields VkBufferViewCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "buffer" ((:) Symbol "format" ((:) Symbol "offset" ((:) Symbol "range" ([] Symbol)))))))
type CUnionType VkBufferViewCreateInfo Source # 
type ReturnedOnly VkBufferViewCreateInfo Source # 
type StructExtends VkBufferViewCreateInfo Source # 
type FieldType "buffer" VkBufferViewCreateInfo Source # 
type FieldType "flags" VkBufferViewCreateInfo Source # 
type FieldType "format" VkBufferViewCreateInfo Source # 
type FieldType "offset" VkBufferViewCreateInfo Source # 
type FieldType "pNext" VkBufferViewCreateInfo Source # 
type FieldType "range" VkBufferViewCreateInfo Source # 
type FieldType "sType" VkBufferViewCreateInfo Source # 
type FieldOptional "buffer" VkBufferViewCreateInfo Source # 
type FieldOptional "flags" VkBufferViewCreateInfo Source # 
type FieldOptional "format" VkBufferViewCreateInfo Source # 
type FieldOptional "offset" VkBufferViewCreateInfo Source # 
type FieldOptional "pNext" VkBufferViewCreateInfo Source # 
type FieldOptional "range" VkBufferViewCreateInfo Source # 
type FieldOptional "sType" VkBufferViewCreateInfo Source # 
type FieldOffset "buffer" VkBufferViewCreateInfo Source # 
type FieldOffset "flags" VkBufferViewCreateInfo Source # 
type FieldOffset "format" VkBufferViewCreateInfo Source # 
type FieldOffset "offset" VkBufferViewCreateInfo Source # 
type FieldOffset "pNext" VkBufferViewCreateInfo Source # 
type FieldOffset "range" VkBufferViewCreateInfo Source # 
type FieldOffset "sType" VkBufferViewCreateInfo Source # 
type FieldIsArray "buffer" VkBufferViewCreateInfo Source # 
type FieldIsArray "flags" VkBufferViewCreateInfo Source # 
type FieldIsArray "format" VkBufferViewCreateInfo Source # 
type FieldIsArray "offset" VkBufferViewCreateInfo Source # 
type FieldIsArray "pNext" VkBufferViewCreateInfo Source # 
type FieldIsArray "range" VkBufferViewCreateInfo Source # 
type FieldIsArray "sType" VkBufferViewCreateInfo Source # 

type VkGetImageMemoryRequirements2 = "vkGetImageMemoryRequirements2" Source #

type HS_vkGetImageMemoryRequirements2 Source #

Arguments

 = VkDevice

device

-> Ptr VkImageMemoryRequirementsInfo2

pInfo

-> Ptr VkMemoryRequirements2

pMemoryRequirements

-> IO () 
void vkGetImageMemoryRequirements2
    ( VkDevice device
    , const VkImageMemoryRequirementsInfo2* pInfo
    , VkMemoryRequirements2* pMemoryRequirements
    )

vkGetImageMemoryRequirements2 registry at www.khronos.org

vkGetImageMemoryRequirements2 Source #

Arguments

:: VkDevice

device

-> Ptr VkImageMemoryRequirementsInfo2

pInfo

-> Ptr VkMemoryRequirements2

pMemoryRequirements

-> IO () 
void vkGetImageMemoryRequirements2
    ( VkDevice device
    , const VkImageMemoryRequirementsInfo2* pInfo
    , VkMemoryRequirements2* pMemoryRequirements
    )

vkGetImageMemoryRequirements2 registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetImageMemoryRequirements2 <- vkGetDeviceProc @VkGetImageMemoryRequirements2 vkDevice

or less efficient:

myGetImageMemoryRequirements2 <- vkGetProc @VkGetImageMemoryRequirements2

Note: vkGetImageMemoryRequirements2Unsafe and vkGetImageMemoryRequirements2Safe are the unsafe and safe FFI imports of this function, respectively. vkGetImageMemoryRequirements2 is an alias of vkGetImageMemoryRequirements2Unsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetImageMemoryRequirements2Safe.

vkGetImageMemoryRequirements2Unsafe Source #

Arguments

:: VkDevice

device

-> Ptr VkImageMemoryRequirementsInfo2

pInfo

-> Ptr VkMemoryRequirements2

pMemoryRequirements

-> IO () 
void vkGetImageMemoryRequirements2
    ( VkDevice device
    , const VkImageMemoryRequirementsInfo2* pInfo
    , VkMemoryRequirements2* pMemoryRequirements
    )

vkGetImageMemoryRequirements2 registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetImageMemoryRequirements2 <- vkGetDeviceProc @VkGetImageMemoryRequirements2 vkDevice

or less efficient:

myGetImageMemoryRequirements2 <- vkGetProc @VkGetImageMemoryRequirements2

Note: vkGetImageMemoryRequirements2Unsafe and vkGetImageMemoryRequirements2Safe are the unsafe and safe FFI imports of this function, respectively. vkGetImageMemoryRequirements2 is an alias of vkGetImageMemoryRequirements2Unsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetImageMemoryRequirements2Safe.

vkGetImageMemoryRequirements2Safe Source #

Arguments

:: VkDevice

device

-> Ptr VkImageMemoryRequirementsInfo2

pInfo

-> Ptr VkMemoryRequirements2

pMemoryRequirements

-> IO () 
void vkGetImageMemoryRequirements2
    ( VkDevice device
    , const VkImageMemoryRequirementsInfo2* pInfo
    , VkMemoryRequirements2* pMemoryRequirements
    )

vkGetImageMemoryRequirements2 registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetImageMemoryRequirements2 <- vkGetDeviceProc @VkGetImageMemoryRequirements2 vkDevice

or less efficient:

myGetImageMemoryRequirements2 <- vkGetProc @VkGetImageMemoryRequirements2

Note: vkGetImageMemoryRequirements2Unsafe and vkGetImageMemoryRequirements2Safe are the unsafe and safe FFI imports of this function, respectively. vkGetImageMemoryRequirements2 is an alias of vkGetImageMemoryRequirements2Unsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetImageMemoryRequirements2Safe.

type VkGetBufferMemoryRequirements2 = "vkGetBufferMemoryRequirements2" Source #

type HS_vkGetBufferMemoryRequirements2 Source #

Arguments

 = VkDevice

device

-> Ptr VkBufferMemoryRequirementsInfo2

pInfo

-> Ptr VkMemoryRequirements2

pMemoryRequirements

-> IO () 
void vkGetBufferMemoryRequirements2
    ( VkDevice device
    , const VkBufferMemoryRequirementsInfo2* pInfo
    , VkMemoryRequirements2* pMemoryRequirements
    )

vkGetBufferMemoryRequirements2 registry at www.khronos.org

vkGetBufferMemoryRequirements2 Source #

Arguments

:: VkDevice

device

-> Ptr VkBufferMemoryRequirementsInfo2

pInfo

-> Ptr VkMemoryRequirements2

pMemoryRequirements

-> IO () 
void vkGetBufferMemoryRequirements2
    ( VkDevice device
    , const VkBufferMemoryRequirementsInfo2* pInfo
    , VkMemoryRequirements2* pMemoryRequirements
    )

vkGetBufferMemoryRequirements2 registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetBufferMemoryRequirements2 <- vkGetDeviceProc @VkGetBufferMemoryRequirements2 vkDevice

or less efficient:

myGetBufferMemoryRequirements2 <- vkGetProc @VkGetBufferMemoryRequirements2

Note: vkGetBufferMemoryRequirements2Unsafe and vkGetBufferMemoryRequirements2Safe are the unsafe and safe FFI imports of this function, respectively. vkGetBufferMemoryRequirements2 is an alias of vkGetBufferMemoryRequirements2Unsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetBufferMemoryRequirements2Safe.

vkGetBufferMemoryRequirements2Unsafe Source #

Arguments

:: VkDevice

device

-> Ptr VkBufferMemoryRequirementsInfo2

pInfo

-> Ptr VkMemoryRequirements2

pMemoryRequirements

-> IO () 
void vkGetBufferMemoryRequirements2
    ( VkDevice device
    , const VkBufferMemoryRequirementsInfo2* pInfo
    , VkMemoryRequirements2* pMemoryRequirements
    )

vkGetBufferMemoryRequirements2 registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetBufferMemoryRequirements2 <- vkGetDeviceProc @VkGetBufferMemoryRequirements2 vkDevice

or less efficient:

myGetBufferMemoryRequirements2 <- vkGetProc @VkGetBufferMemoryRequirements2

Note: vkGetBufferMemoryRequirements2Unsafe and vkGetBufferMemoryRequirements2Safe are the unsafe and safe FFI imports of this function, respectively. vkGetBufferMemoryRequirements2 is an alias of vkGetBufferMemoryRequirements2Unsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetBufferMemoryRequirements2Safe.

vkGetBufferMemoryRequirements2Safe Source #

Arguments

:: VkDevice

device

-> Ptr VkBufferMemoryRequirementsInfo2

pInfo

-> Ptr VkMemoryRequirements2

pMemoryRequirements

-> IO () 
void vkGetBufferMemoryRequirements2
    ( VkDevice device
    , const VkBufferMemoryRequirementsInfo2* pInfo
    , VkMemoryRequirements2* pMemoryRequirements
    )

vkGetBufferMemoryRequirements2 registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetBufferMemoryRequirements2 <- vkGetDeviceProc @VkGetBufferMemoryRequirements2 vkDevice

or less efficient:

myGetBufferMemoryRequirements2 <- vkGetProc @VkGetBufferMemoryRequirements2

Note: vkGetBufferMemoryRequirements2Unsafe and vkGetBufferMemoryRequirements2Safe are the unsafe and safe FFI imports of this function, respectively. vkGetBufferMemoryRequirements2 is an alias of vkGetBufferMemoryRequirements2Unsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetBufferMemoryRequirements2Safe.

type VkGetImageSparseMemoryRequirements2 = "vkGetImageSparseMemoryRequirements2" Source #

type HS_vkGetImageSparseMemoryRequirements2 Source #

Arguments

 = VkDevice

device

-> Ptr VkImageSparseMemoryRequirementsInfo2

pInfo

-> Ptr Word32

pSparseMemoryRequirementCount

-> Ptr VkSparseImageMemoryRequirements2

pSparseMemoryRequirements

-> IO () 
void vkGetImageSparseMemoryRequirements2
    ( VkDevice device
    , const VkImageSparseMemoryRequirementsInfo2* pInfo
    , uint32_t* pSparseMemoryRequirementCount
    , VkSparseImageMemoryRequirements2* pSparseMemoryRequirements
    )

vkGetImageSparseMemoryRequirements2 registry at www.khronos.org

vkGetImageSparseMemoryRequirements2 Source #

Arguments

:: VkDevice

device

-> Ptr VkImageSparseMemoryRequirementsInfo2

pInfo

-> Ptr Word32

pSparseMemoryRequirementCount

-> Ptr VkSparseImageMemoryRequirements2

pSparseMemoryRequirements

-> IO () 
void vkGetImageSparseMemoryRequirements2
    ( VkDevice device
    , const VkImageSparseMemoryRequirementsInfo2* pInfo
    , uint32_t* pSparseMemoryRequirementCount
    , VkSparseImageMemoryRequirements2* pSparseMemoryRequirements
    )

vkGetImageSparseMemoryRequirements2 registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetImageSparseMemoryRequirements2 <- vkGetDeviceProc @VkGetImageSparseMemoryRequirements2 vkDevice

or less efficient:

myGetImageSparseMemoryRequirements2 <- vkGetProc @VkGetImageSparseMemoryRequirements2

Note: vkGetImageSparseMemoryRequirements2Unsafe and vkGetImageSparseMemoryRequirements2Safe are the unsafe and safe FFI imports of this function, respectively. vkGetImageSparseMemoryRequirements2 is an alias of vkGetImageSparseMemoryRequirements2Unsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetImageSparseMemoryRequirements2Safe.

vkGetImageSparseMemoryRequirements2Unsafe Source #

Arguments

:: VkDevice

device

-> Ptr VkImageSparseMemoryRequirementsInfo2

pInfo

-> Ptr Word32

pSparseMemoryRequirementCount

-> Ptr VkSparseImageMemoryRequirements2

pSparseMemoryRequirements

-> IO () 
void vkGetImageSparseMemoryRequirements2
    ( VkDevice device
    , const VkImageSparseMemoryRequirementsInfo2* pInfo
    , uint32_t* pSparseMemoryRequirementCount
    , VkSparseImageMemoryRequirements2* pSparseMemoryRequirements
    )

vkGetImageSparseMemoryRequirements2 registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetImageSparseMemoryRequirements2 <- vkGetDeviceProc @VkGetImageSparseMemoryRequirements2 vkDevice

or less efficient:

myGetImageSparseMemoryRequirements2 <- vkGetProc @VkGetImageSparseMemoryRequirements2

Note: vkGetImageSparseMemoryRequirements2Unsafe and vkGetImageSparseMemoryRequirements2Safe are the unsafe and safe FFI imports of this function, respectively. vkGetImageSparseMemoryRequirements2 is an alias of vkGetImageSparseMemoryRequirements2Unsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetImageSparseMemoryRequirements2Safe.

vkGetImageSparseMemoryRequirements2Safe Source #

Arguments

:: VkDevice

device

-> Ptr VkImageSparseMemoryRequirementsInfo2

pInfo

-> Ptr Word32

pSparseMemoryRequirementCount

-> Ptr VkSparseImageMemoryRequirements2

pSparseMemoryRequirements

-> IO () 
void vkGetImageSparseMemoryRequirements2
    ( VkDevice device
    , const VkImageSparseMemoryRequirementsInfo2* pInfo
    , uint32_t* pSparseMemoryRequirementCount
    , VkSparseImageMemoryRequirements2* pSparseMemoryRequirements
    )

vkGetImageSparseMemoryRequirements2 registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetImageSparseMemoryRequirements2 <- vkGetDeviceProc @VkGetImageSparseMemoryRequirements2 vkDevice

or less efficient:

myGetImageSparseMemoryRequirements2 <- vkGetProc @VkGetImageSparseMemoryRequirements2

Note: vkGetImageSparseMemoryRequirements2Unsafe and vkGetImageSparseMemoryRequirements2Safe are the unsafe and safe FFI imports of this function, respectively. vkGetImageSparseMemoryRequirements2 is an alias of vkGetImageSparseMemoryRequirements2Unsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetImageSparseMemoryRequirements2Safe.

Promoted from VK_KHR_get_physical_device_properties2

newtype VkFormat Source #

Vulkan format definitions

type = enum

VkFormat registry at www.khronos.org

Constructors

VkFormat Int32 

Instances

Bounded VkFormat Source # 
Enum VkFormat Source # 
Eq VkFormat Source # 
Data VkFormat Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkFormat -> c VkFormat #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkFormat #

toConstr :: VkFormat -> Constr #

dataTypeOf :: VkFormat -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkFormat) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkFormat) #

gmapT :: (forall b. Data b => b -> b) -> VkFormat -> VkFormat #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkFormat -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkFormat -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkFormat -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkFormat -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkFormat -> m VkFormat #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkFormat -> m VkFormat #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkFormat -> m VkFormat #

Num VkFormat Source # 
Ord VkFormat Source # 
Read VkFormat Source # 
Show VkFormat Source # 
Generic VkFormat Source # 

Associated Types

type Rep VkFormat :: * -> * #

Methods

from :: VkFormat -> Rep VkFormat x #

to :: Rep VkFormat x -> VkFormat #

Storable VkFormat Source # 
type Rep VkFormat Source # 
type Rep VkFormat = D1 (MetaData "VkFormat" "Graphics.Vulkan.Types.Enum.Format" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkFormat" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

newtype VkFormatFeatureBitmask a Source #

Instances

Bounded (VkFormatFeatureBitmask FlagMask) Source # 
Enum (VkFormatFeatureBitmask FlagMask) Source # 
Eq (VkFormatFeatureBitmask a) Source # 
Integral (VkFormatFeatureBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkFormatFeatureBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkFormatFeatureBitmask a -> c (VkFormatFeatureBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkFormatFeatureBitmask a) #

toConstr :: VkFormatFeatureBitmask a -> Constr #

dataTypeOf :: VkFormatFeatureBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkFormatFeatureBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkFormatFeatureBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkFormatFeatureBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkFormatFeatureBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkFormatFeatureBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkFormatFeatureBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkFormatFeatureBitmask a -> m (VkFormatFeatureBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkFormatFeatureBitmask a -> m (VkFormatFeatureBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkFormatFeatureBitmask a -> m (VkFormatFeatureBitmask a) #

Num (VkFormatFeatureBitmask FlagMask) Source # 
Ord (VkFormatFeatureBitmask a) Source # 
Read (VkFormatFeatureBitmask a) Source # 
Real (VkFormatFeatureBitmask FlagMask) Source # 
Show (VkFormatFeatureBitmask a) Source # 
Generic (VkFormatFeatureBitmask a) Source # 
Storable (VkFormatFeatureBitmask a) Source # 
Bits (VkFormatFeatureBitmask FlagMask) Source # 

Methods

(.&.) :: VkFormatFeatureBitmask FlagMask -> VkFormatFeatureBitmask FlagMask -> VkFormatFeatureBitmask FlagMask #

(.|.) :: VkFormatFeatureBitmask FlagMask -> VkFormatFeatureBitmask FlagMask -> VkFormatFeatureBitmask FlagMask #

xor :: VkFormatFeatureBitmask FlagMask -> VkFormatFeatureBitmask FlagMask -> VkFormatFeatureBitmask FlagMask #

complement :: VkFormatFeatureBitmask FlagMask -> VkFormatFeatureBitmask FlagMask #

shift :: VkFormatFeatureBitmask FlagMask -> Int -> VkFormatFeatureBitmask FlagMask #

rotate :: VkFormatFeatureBitmask FlagMask -> Int -> VkFormatFeatureBitmask FlagMask #

zeroBits :: VkFormatFeatureBitmask FlagMask #

bit :: Int -> VkFormatFeatureBitmask FlagMask #

setBit :: VkFormatFeatureBitmask FlagMask -> Int -> VkFormatFeatureBitmask FlagMask #

clearBit :: VkFormatFeatureBitmask FlagMask -> Int -> VkFormatFeatureBitmask FlagMask #

complementBit :: VkFormatFeatureBitmask FlagMask -> Int -> VkFormatFeatureBitmask FlagMask #

testBit :: VkFormatFeatureBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkFormatFeatureBitmask FlagMask -> Maybe Int #

bitSize :: VkFormatFeatureBitmask FlagMask -> Int #

isSigned :: VkFormatFeatureBitmask FlagMask -> Bool #

shiftL :: VkFormatFeatureBitmask FlagMask -> Int -> VkFormatFeatureBitmask FlagMask #

unsafeShiftL :: VkFormatFeatureBitmask FlagMask -> Int -> VkFormatFeatureBitmask FlagMask #

shiftR :: VkFormatFeatureBitmask FlagMask -> Int -> VkFormatFeatureBitmask FlagMask #

unsafeShiftR :: VkFormatFeatureBitmask FlagMask -> Int -> VkFormatFeatureBitmask FlagMask #

rotateL :: VkFormatFeatureBitmask FlagMask -> Int -> VkFormatFeatureBitmask FlagMask #

rotateR :: VkFormatFeatureBitmask FlagMask -> Int -> VkFormatFeatureBitmask FlagMask #

popCount :: VkFormatFeatureBitmask FlagMask -> Int #

FiniteBits (VkFormatFeatureBitmask FlagMask) Source # 
type Rep (VkFormatFeatureBitmask a) Source # 
type Rep (VkFormatFeatureBitmask a) = D1 (MetaData "VkFormatFeatureBitmask" "Graphics.Vulkan.Types.Enum.Format" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkFormatFeatureBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

pattern VK_FORMAT_FEATURE_SAMPLED_IMAGE_BIT :: forall a. VkFormatFeatureBitmask a Source #

Format can be used for sampled images (SAMPLED_IMAGE and COMBINED_IMAGE_SAMPLER descriptor types)

bitpos = 0

pattern VK_FORMAT_FEATURE_STORAGE_IMAGE_BIT :: forall a. VkFormatFeatureBitmask a Source #

Format can be used for storage images (STORAGE_IMAGE descriptor type)

bitpos = 1

pattern VK_FORMAT_FEATURE_STORAGE_IMAGE_ATOMIC_BIT :: forall a. VkFormatFeatureBitmask a Source #

Format supports atomic operations in case it is used for storage images

bitpos = 2

pattern VK_FORMAT_FEATURE_UNIFORM_TEXEL_BUFFER_BIT :: forall a. VkFormatFeatureBitmask a Source #

Format can be used for uniform texel buffers (TBOs)

bitpos = 3

pattern VK_FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_BIT :: forall a. VkFormatFeatureBitmask a Source #

Format can be used for storage texel buffers (IBOs)

bitpos = 4

pattern VK_FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_ATOMIC_BIT :: forall a. VkFormatFeatureBitmask a Source #

Format supports atomic operations in case it is used for storage texel buffers

bitpos = 5

pattern VK_FORMAT_FEATURE_VERTEX_BUFFER_BIT :: forall a. VkFormatFeatureBitmask a Source #

Format can be used for vertex buffers (VBOs)

bitpos = 6

pattern VK_FORMAT_FEATURE_COLOR_ATTACHMENT_BIT :: forall a. VkFormatFeatureBitmask a Source #

Format can be used for color attachment images

bitpos = 7

pattern VK_FORMAT_FEATURE_COLOR_ATTACHMENT_BLEND_BIT :: forall a. VkFormatFeatureBitmask a Source #

Format supports blending in case it is used for color attachment images

bitpos = 8

pattern VK_FORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT :: forall a. VkFormatFeatureBitmask a Source #

Format can be used for depth/stencil attachment images

bitpos = 9

pattern VK_FORMAT_FEATURE_BLIT_SRC_BIT :: forall a. VkFormatFeatureBitmask a Source #

Format can be used as the source image of blits with vkCmdBlitImage

bitpos = 10

pattern VK_FORMAT_FEATURE_BLIT_DST_BIT :: forall a. VkFormatFeatureBitmask a Source #

Format can be used as the destination image of blits with vkCmdBlitImage

bitpos = 11

pattern VK_FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT :: forall a. VkFormatFeatureBitmask a Source #

Format can be filtered with VK_FILTER_LINEAR when being sampled

bitpos = 12

data VkFormatProperties Source #

typedef struct VkFormatProperties {
    VkFormatFeatureFlags   linearTilingFeatures;
    VkFormatFeatureFlags   optimalTilingFeatures;
    VkFormatFeatureFlags   bufferFeatures;
} VkFormatProperties;

VkFormatProperties registry at www.khronos.org

Instances

Eq VkFormatProperties Source # 
Ord VkFormatProperties Source # 
Show VkFormatProperties Source # 
Storable VkFormatProperties Source # 
VulkanMarshalPrim VkFormatProperties Source # 
VulkanMarshal VkFormatProperties Source # 
CanWriteField "bufferFeatures" VkFormatProperties Source # 
CanWriteField "linearTilingFeatures" VkFormatProperties Source # 

Methods

writeField :: Ptr VkFormatProperties -> FieldType "linearTilingFeatures" VkFormatProperties -> IO () Source #

CanWriteField "optimalTilingFeatures" VkFormatProperties Source # 

Methods

writeField :: Ptr VkFormatProperties -> FieldType "optimalTilingFeatures" VkFormatProperties -> IO () Source #

CanReadField "bufferFeatures" VkFormatProperties Source # 
CanReadField "linearTilingFeatures" VkFormatProperties Source # 
CanReadField "optimalTilingFeatures" VkFormatProperties Source # 
HasField "bufferFeatures" VkFormatProperties Source # 

Associated Types

type FieldType ("bufferFeatures" :: Symbol) VkFormatProperties :: Type Source #

type FieldOptional ("bufferFeatures" :: Symbol) VkFormatProperties :: Bool Source #

type FieldOffset ("bufferFeatures" :: Symbol) VkFormatProperties :: Nat Source #

type FieldIsArray ("bufferFeatures" :: Symbol) VkFormatProperties :: Bool Source #

HasField "linearTilingFeatures" VkFormatProperties Source # 

Associated Types

type FieldType ("linearTilingFeatures" :: Symbol) VkFormatProperties :: Type Source #

type FieldOptional ("linearTilingFeatures" :: Symbol) VkFormatProperties :: Bool Source #

type FieldOffset ("linearTilingFeatures" :: Symbol) VkFormatProperties :: Nat Source #

type FieldIsArray ("linearTilingFeatures" :: Symbol) VkFormatProperties :: Bool Source #

HasField "optimalTilingFeatures" VkFormatProperties Source # 

Associated Types

type FieldType ("optimalTilingFeatures" :: Symbol) VkFormatProperties :: Type Source #

type FieldOptional ("optimalTilingFeatures" :: Symbol) VkFormatProperties :: Bool Source #

type FieldOffset ("optimalTilingFeatures" :: Symbol) VkFormatProperties :: Nat Source #

type FieldIsArray ("optimalTilingFeatures" :: Symbol) VkFormatProperties :: Bool Source #

type StructFields VkFormatProperties Source # 
type StructFields VkFormatProperties = (:) Symbol "linearTilingFeatures" ((:) Symbol "optimalTilingFeatures" ((:) Symbol "bufferFeatures" ([] Symbol)))
type CUnionType VkFormatProperties Source # 
type ReturnedOnly VkFormatProperties Source # 
type StructExtends VkFormatProperties Source # 
type FieldType "bufferFeatures" VkFormatProperties Source # 
type FieldType "linearTilingFeatures" VkFormatProperties Source # 
type FieldType "linearTilingFeatures" VkFormatProperties = VkFormatFeatureFlags
type FieldType "optimalTilingFeatures" VkFormatProperties Source # 
type FieldType "optimalTilingFeatures" VkFormatProperties = VkFormatFeatureFlags
type FieldOptional "bufferFeatures" VkFormatProperties Source # 
type FieldOptional "bufferFeatures" VkFormatProperties = True
type FieldOptional "linearTilingFeatures" VkFormatProperties Source # 
type FieldOptional "linearTilingFeatures" VkFormatProperties = True
type FieldOptional "optimalTilingFeatures" VkFormatProperties Source # 
type FieldOptional "optimalTilingFeatures" VkFormatProperties = True
type FieldOffset "bufferFeatures" VkFormatProperties Source # 
type FieldOffset "bufferFeatures" VkFormatProperties = 8
type FieldOffset "linearTilingFeatures" VkFormatProperties Source # 
type FieldOffset "linearTilingFeatures" VkFormatProperties = 0
type FieldOffset "optimalTilingFeatures" VkFormatProperties Source # 
type FieldOffset "optimalTilingFeatures" VkFormatProperties = 4
type FieldIsArray "bufferFeatures" VkFormatProperties Source # 
type FieldIsArray "bufferFeatures" VkFormatProperties = False
type FieldIsArray "linearTilingFeatures" VkFormatProperties Source # 
type FieldIsArray "linearTilingFeatures" VkFormatProperties = False
type FieldIsArray "optimalTilingFeatures" VkFormatProperties Source # 
type FieldIsArray "optimalTilingFeatures" VkFormatProperties = False

data VkFormatProperties2 Source #

typedef struct VkFormatProperties2 {
    VkStructureType sType;
    void*                            pNext;
    VkFormatProperties               formatProperties;
} VkFormatProperties2;

VkFormatProperties2 registry at www.khronos.org

Instances

Eq VkFormatProperties2 Source # 
Ord VkFormatProperties2 Source # 
Show VkFormatProperties2 Source # 
Storable VkFormatProperties2 Source # 
VulkanMarshalPrim VkFormatProperties2 Source # 
VulkanMarshal VkFormatProperties2 Source # 
CanWriteField "formatProperties" VkFormatProperties2 Source # 
CanWriteField "pNext" VkFormatProperties2 Source # 
CanWriteField "sType" VkFormatProperties2 Source # 
CanReadField "formatProperties" VkFormatProperties2 Source # 
CanReadField "pNext" VkFormatProperties2 Source # 
CanReadField "sType" VkFormatProperties2 Source # 
HasField "formatProperties" VkFormatProperties2 Source # 

Associated Types

type FieldType ("formatProperties" :: Symbol) VkFormatProperties2 :: Type Source #

type FieldOptional ("formatProperties" :: Symbol) VkFormatProperties2 :: Bool Source #

type FieldOffset ("formatProperties" :: Symbol) VkFormatProperties2 :: Nat Source #

type FieldIsArray ("formatProperties" :: Symbol) VkFormatProperties2 :: Bool Source #

HasField "pNext" VkFormatProperties2 Source # 
HasField "sType" VkFormatProperties2 Source # 
type StructFields VkFormatProperties2 Source # 
type StructFields VkFormatProperties2 = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "formatProperties" ([] Symbol)))
type CUnionType VkFormatProperties2 Source # 
type ReturnedOnly VkFormatProperties2 Source # 
type StructExtends VkFormatProperties2 Source # 
type FieldType "formatProperties" VkFormatProperties2 Source # 
type FieldType "pNext" VkFormatProperties2 Source # 
type FieldType "sType" VkFormatProperties2 Source # 
type FieldOptional "formatProperties" VkFormatProperties2 Source # 
type FieldOptional "formatProperties" VkFormatProperties2 = False
type FieldOptional "pNext" VkFormatProperties2 Source # 
type FieldOptional "sType" VkFormatProperties2 Source # 
type FieldOffset "formatProperties" VkFormatProperties2 Source # 
type FieldOffset "formatProperties" VkFormatProperties2 = 16
type FieldOffset "pNext" VkFormatProperties2 Source # 
type FieldOffset "sType" VkFormatProperties2 Source # 
type FieldIsArray "formatProperties" VkFormatProperties2 Source # 
type FieldIsArray "formatProperties" VkFormatProperties2 = False
type FieldIsArray "pNext" VkFormatProperties2 Source # 
type FieldIsArray "sType" VkFormatProperties2 Source # 

data VkQueueFamilyProperties Source #

typedef struct VkQueueFamilyProperties {
    VkQueueFlags           queueFlags;
    uint32_t               queueCount;
    uint32_t               timestampValidBits;
    VkExtent3D             minImageTransferGranularity;
} VkQueueFamilyProperties;

VkQueueFamilyProperties registry at www.khronos.org

Instances

Eq VkQueueFamilyProperties Source # 
Ord VkQueueFamilyProperties Source # 
Show VkQueueFamilyProperties Source # 
Storable VkQueueFamilyProperties Source # 
VulkanMarshalPrim VkQueueFamilyProperties Source # 
VulkanMarshal VkQueueFamilyProperties Source # 
CanWriteField "minImageTransferGranularity" VkQueueFamilyProperties Source # 

Methods

writeField :: Ptr VkQueueFamilyProperties -> FieldType "minImageTransferGranularity" VkQueueFamilyProperties -> IO () Source #

CanWriteField "queueCount" VkQueueFamilyProperties Source # 
CanWriteField "queueFlags" VkQueueFamilyProperties Source # 
CanWriteField "timestampValidBits" VkQueueFamilyProperties Source # 
CanReadField "minImageTransferGranularity" VkQueueFamilyProperties Source # 
CanReadField "queueCount" VkQueueFamilyProperties Source # 
CanReadField "queueFlags" VkQueueFamilyProperties Source # 
CanReadField "timestampValidBits" VkQueueFamilyProperties Source # 
HasField "minImageTransferGranularity" VkQueueFamilyProperties Source # 

Associated Types

type FieldType ("minImageTransferGranularity" :: Symbol) VkQueueFamilyProperties :: Type Source #

type FieldOptional ("minImageTransferGranularity" :: Symbol) VkQueueFamilyProperties :: Bool Source #

type FieldOffset ("minImageTransferGranularity" :: Symbol) VkQueueFamilyProperties :: Nat Source #

type FieldIsArray ("minImageTransferGranularity" :: Symbol) VkQueueFamilyProperties :: Bool Source #

HasField "queueCount" VkQueueFamilyProperties Source # 
HasField "queueFlags" VkQueueFamilyProperties Source # 
HasField "timestampValidBits" VkQueueFamilyProperties Source # 

Associated Types

type FieldType ("timestampValidBits" :: Symbol) VkQueueFamilyProperties :: Type Source #

type FieldOptional ("timestampValidBits" :: Symbol) VkQueueFamilyProperties :: Bool Source #

type FieldOffset ("timestampValidBits" :: Symbol) VkQueueFamilyProperties :: Nat Source #

type FieldIsArray ("timestampValidBits" :: Symbol) VkQueueFamilyProperties :: Bool Source #

type StructFields VkQueueFamilyProperties Source # 
type StructFields VkQueueFamilyProperties = (:) Symbol "queueFlags" ((:) Symbol "queueCount" ((:) Symbol "timestampValidBits" ((:) Symbol "minImageTransferGranularity" ([] Symbol))))
type CUnionType VkQueueFamilyProperties Source # 
type ReturnedOnly VkQueueFamilyProperties Source # 
type StructExtends VkQueueFamilyProperties Source # 
type FieldType "minImageTransferGranularity" VkQueueFamilyProperties Source # 
type FieldType "minImageTransferGranularity" VkQueueFamilyProperties = VkExtent3D
type FieldType "queueCount" VkQueueFamilyProperties Source # 
type FieldType "queueFlags" VkQueueFamilyProperties Source # 
type FieldType "timestampValidBits" VkQueueFamilyProperties Source # 
type FieldType "timestampValidBits" VkQueueFamilyProperties = Word32
type FieldOptional "minImageTransferGranularity" VkQueueFamilyProperties Source # 
type FieldOptional "minImageTransferGranularity" VkQueueFamilyProperties = False
type FieldOptional "queueCount" VkQueueFamilyProperties Source # 
type FieldOptional "queueFlags" VkQueueFamilyProperties Source # 
type FieldOptional "timestampValidBits" VkQueueFamilyProperties Source # 
type FieldOptional "timestampValidBits" VkQueueFamilyProperties = False
type FieldOffset "minImageTransferGranularity" VkQueueFamilyProperties Source # 
type FieldOffset "minImageTransferGranularity" VkQueueFamilyProperties = 12
type FieldOffset "queueCount" VkQueueFamilyProperties Source # 
type FieldOffset "queueCount" VkQueueFamilyProperties = 4
type FieldOffset "queueFlags" VkQueueFamilyProperties Source # 
type FieldOffset "queueFlags" VkQueueFamilyProperties = 0
type FieldOffset "timestampValidBits" VkQueueFamilyProperties Source # 
type FieldOffset "timestampValidBits" VkQueueFamilyProperties = 8
type FieldIsArray "minImageTransferGranularity" VkQueueFamilyProperties Source # 
type FieldIsArray "minImageTransferGranularity" VkQueueFamilyProperties = False
type FieldIsArray "queueCount" VkQueueFamilyProperties Source # 
type FieldIsArray "queueFlags" VkQueueFamilyProperties Source # 
type FieldIsArray "timestampValidBits" VkQueueFamilyProperties Source # 
type FieldIsArray "timestampValidBits" VkQueueFamilyProperties = False

data VkQueueFamilyProperties2 Source #

typedef struct VkQueueFamilyProperties2 {
    VkStructureType sType;
    void*                            pNext;
    VkQueueFamilyProperties          queueFamilyProperties;
} VkQueueFamilyProperties2;

VkQueueFamilyProperties2 registry at www.khronos.org

Instances

Eq VkQueueFamilyProperties2 Source # 
Ord VkQueueFamilyProperties2 Source # 
Show VkQueueFamilyProperties2 Source # 
Storable VkQueueFamilyProperties2 Source # 
VulkanMarshalPrim VkQueueFamilyProperties2 Source # 
VulkanMarshal VkQueueFamilyProperties2 Source # 
CanWriteField "pNext" VkQueueFamilyProperties2 Source # 
CanWriteField "queueFamilyProperties" VkQueueFamilyProperties2 Source # 
CanWriteField "sType" VkQueueFamilyProperties2 Source # 
CanReadField "pNext" VkQueueFamilyProperties2 Source # 
CanReadField "queueFamilyProperties" VkQueueFamilyProperties2 Source # 
CanReadField "sType" VkQueueFamilyProperties2 Source # 
HasField "pNext" VkQueueFamilyProperties2 Source # 
HasField "queueFamilyProperties" VkQueueFamilyProperties2 Source # 

Associated Types

type FieldType ("queueFamilyProperties" :: Symbol) VkQueueFamilyProperties2 :: Type Source #

type FieldOptional ("queueFamilyProperties" :: Symbol) VkQueueFamilyProperties2 :: Bool Source #

type FieldOffset ("queueFamilyProperties" :: Symbol) VkQueueFamilyProperties2 :: Nat Source #

type FieldIsArray ("queueFamilyProperties" :: Symbol) VkQueueFamilyProperties2 :: Bool Source #

HasField "sType" VkQueueFamilyProperties2 Source # 
type StructFields VkQueueFamilyProperties2 Source # 
type StructFields VkQueueFamilyProperties2 = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "queueFamilyProperties" ([] Symbol)))
type CUnionType VkQueueFamilyProperties2 Source # 
type ReturnedOnly VkQueueFamilyProperties2 Source # 
type StructExtends VkQueueFamilyProperties2 Source # 
type FieldType "pNext" VkQueueFamilyProperties2 Source # 
type FieldType "queueFamilyProperties" VkQueueFamilyProperties2 Source # 
type FieldType "sType" VkQueueFamilyProperties2 Source # 
type FieldOptional "pNext" VkQueueFamilyProperties2 Source # 
type FieldOptional "queueFamilyProperties" VkQueueFamilyProperties2 Source # 
type FieldOptional "queueFamilyProperties" VkQueueFamilyProperties2 = False
type FieldOptional "sType" VkQueueFamilyProperties2 Source # 
type FieldOffset "pNext" VkQueueFamilyProperties2 Source # 
type FieldOffset "queueFamilyProperties" VkQueueFamilyProperties2 Source # 
type FieldOffset "queueFamilyProperties" VkQueueFamilyProperties2 = 16
type FieldOffset "sType" VkQueueFamilyProperties2 Source # 
type FieldIsArray "pNext" VkQueueFamilyProperties2 Source # 
type FieldIsArray "queueFamilyProperties" VkQueueFamilyProperties2 Source # 
type FieldIsArray "queueFamilyProperties" VkQueueFamilyProperties2 = False
type FieldIsArray "sType" VkQueueFamilyProperties2 Source # 

newtype VkQueueBitmask a Source #

Constructors

VkQueueBitmask VkFlags 

Instances

Bounded (VkQueueBitmask FlagMask) Source # 
Enum (VkQueueBitmask FlagMask) Source # 
Eq (VkQueueBitmask a) Source # 
Integral (VkQueueBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkQueueBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkQueueBitmask a -> c (VkQueueBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkQueueBitmask a) #

toConstr :: VkQueueBitmask a -> Constr #

dataTypeOf :: VkQueueBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkQueueBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkQueueBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkQueueBitmask a -> VkQueueBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkQueueBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkQueueBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkQueueBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkQueueBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkQueueBitmask a -> m (VkQueueBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkQueueBitmask a -> m (VkQueueBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkQueueBitmask a -> m (VkQueueBitmask a) #

Num (VkQueueBitmask FlagMask) Source # 
Ord (VkQueueBitmask a) Source # 
Read (VkQueueBitmask a) Source # 
Real (VkQueueBitmask FlagMask) Source # 
Show (VkQueueBitmask a) Source # 
Generic (VkQueueBitmask a) Source # 

Associated Types

type Rep (VkQueueBitmask a) :: * -> * #

Storable (VkQueueBitmask a) Source # 
Bits (VkQueueBitmask FlagMask) Source # 
FiniteBits (VkQueueBitmask FlagMask) Source # 
type Rep (VkQueueBitmask a) Source # 
type Rep (VkQueueBitmask a) = D1 (MetaData "VkQueueBitmask" "Graphics.Vulkan.Types.Enum.Queue" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkQueueBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

pattern VK_QUEUE_GRAPHICS_BIT :: forall a. VkQueueBitmask a Source #

Queue supports graphics operations

bitpos = 0

pattern VK_QUEUE_COMPUTE_BIT :: forall a. VkQueueBitmask a Source #

Queue supports compute operations

bitpos = 1

pattern VK_QUEUE_TRANSFER_BIT :: forall a. VkQueueBitmask a Source #

Queue supports transfer operations

bitpos = 2

pattern VK_QUEUE_SPARSE_BINDING_BIT :: forall a. VkQueueBitmask a Source #

Queue supports sparse resource memory management operations

bitpos = 3

newtype VkQueueGlobalPriorityEXT Source #

Instances

Bounded VkQueueGlobalPriorityEXT Source # 
Enum VkQueueGlobalPriorityEXT Source # 
Eq VkQueueGlobalPriorityEXT Source # 
Data VkQueueGlobalPriorityEXT Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkQueueGlobalPriorityEXT -> c VkQueueGlobalPriorityEXT #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkQueueGlobalPriorityEXT #

toConstr :: VkQueueGlobalPriorityEXT -> Constr #

dataTypeOf :: VkQueueGlobalPriorityEXT -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkQueueGlobalPriorityEXT) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkQueueGlobalPriorityEXT) #

gmapT :: (forall b. Data b => b -> b) -> VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkQueueGlobalPriorityEXT -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkQueueGlobalPriorityEXT -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkQueueGlobalPriorityEXT -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkQueueGlobalPriorityEXT -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkQueueGlobalPriorityEXT -> m VkQueueGlobalPriorityEXT #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkQueueGlobalPriorityEXT -> m VkQueueGlobalPriorityEXT #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkQueueGlobalPriorityEXT -> m VkQueueGlobalPriorityEXT #

Num VkQueueGlobalPriorityEXT Source # 
Ord VkQueueGlobalPriorityEXT Source # 
Read VkQueueGlobalPriorityEXT Source # 
Show VkQueueGlobalPriorityEXT Source # 
Generic VkQueueGlobalPriorityEXT Source # 
Storable VkQueueGlobalPriorityEXT Source # 
type Rep VkQueueGlobalPriorityEXT Source # 
type Rep VkQueueGlobalPriorityEXT = D1 (MetaData "VkQueueGlobalPriorityEXT" "Graphics.Vulkan.Types.Enum.Queue" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkQueueGlobalPriorityEXT" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

type VkGetPhysicalDeviceFeatures2 = "vkGetPhysicalDeviceFeatures2" Source #

type HS_vkGetPhysicalDeviceFeatures2 Source #

Arguments

 = VkPhysicalDevice

physicalDevice

-> Ptr VkPhysicalDeviceFeatures2

pFeatures

-> IO () 
void vkGetPhysicalDeviceFeatures2
    ( VkPhysicalDevice physicalDevice
    , VkPhysicalDeviceFeatures2* pFeatures
    )

vkGetPhysicalDeviceFeatures2 registry at www.khronos.org

vkGetPhysicalDeviceFeatures2 Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> Ptr VkPhysicalDeviceFeatures2

pFeatures

-> IO () 
void vkGetPhysicalDeviceFeatures2
    ( VkPhysicalDevice physicalDevice
    , VkPhysicalDeviceFeatures2* pFeatures
    )

vkGetPhysicalDeviceFeatures2 registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetPhysicalDeviceFeatures2 <- vkGetInstanceProc @VkGetPhysicalDeviceFeatures2 vkInstance

or less efficient:

myGetPhysicalDeviceFeatures2 <- vkGetProc @VkGetPhysicalDeviceFeatures2

Note: vkGetPhysicalDeviceFeatures2Unsafe and vkGetPhysicalDeviceFeatures2Safe are the unsafe and safe FFI imports of this function, respectively. vkGetPhysicalDeviceFeatures2 is an alias of vkGetPhysicalDeviceFeatures2Unsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetPhysicalDeviceFeatures2Safe.

vkGetPhysicalDeviceFeatures2Unsafe Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> Ptr VkPhysicalDeviceFeatures2

pFeatures

-> IO () 
void vkGetPhysicalDeviceFeatures2
    ( VkPhysicalDevice physicalDevice
    , VkPhysicalDeviceFeatures2* pFeatures
    )

vkGetPhysicalDeviceFeatures2 registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetPhysicalDeviceFeatures2 <- vkGetInstanceProc @VkGetPhysicalDeviceFeatures2 vkInstance

or less efficient:

myGetPhysicalDeviceFeatures2 <- vkGetProc @VkGetPhysicalDeviceFeatures2

Note: vkGetPhysicalDeviceFeatures2Unsafe and vkGetPhysicalDeviceFeatures2Safe are the unsafe and safe FFI imports of this function, respectively. vkGetPhysicalDeviceFeatures2 is an alias of vkGetPhysicalDeviceFeatures2Unsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetPhysicalDeviceFeatures2Safe.

vkGetPhysicalDeviceFeatures2Safe Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> Ptr VkPhysicalDeviceFeatures2

pFeatures

-> IO () 
void vkGetPhysicalDeviceFeatures2
    ( VkPhysicalDevice physicalDevice
    , VkPhysicalDeviceFeatures2* pFeatures
    )

vkGetPhysicalDeviceFeatures2 registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetPhysicalDeviceFeatures2 <- vkGetInstanceProc @VkGetPhysicalDeviceFeatures2 vkInstance

or less efficient:

myGetPhysicalDeviceFeatures2 <- vkGetProc @VkGetPhysicalDeviceFeatures2

Note: vkGetPhysicalDeviceFeatures2Unsafe and vkGetPhysicalDeviceFeatures2Safe are the unsafe and safe FFI imports of this function, respectively. vkGetPhysicalDeviceFeatures2 is an alias of vkGetPhysicalDeviceFeatures2Unsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetPhysicalDeviceFeatures2Safe.

type VkGetPhysicalDeviceProperties2 = "vkGetPhysicalDeviceProperties2" Source #

type HS_vkGetPhysicalDeviceProperties2 Source #

Arguments

 = VkPhysicalDevice

physicalDevice

-> Ptr VkPhysicalDeviceProperties2

pProperties

-> IO () 
void vkGetPhysicalDeviceProperties2
    ( VkPhysicalDevice physicalDevice
    , VkPhysicalDeviceProperties2* pProperties
    )

vkGetPhysicalDeviceProperties2 registry at www.khronos.org

vkGetPhysicalDeviceProperties2 Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> Ptr VkPhysicalDeviceProperties2

pProperties

-> IO () 
void vkGetPhysicalDeviceProperties2
    ( VkPhysicalDevice physicalDevice
    , VkPhysicalDeviceProperties2* pProperties
    )

vkGetPhysicalDeviceProperties2 registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetPhysicalDeviceProperties2 <- vkGetInstanceProc @VkGetPhysicalDeviceProperties2 vkInstance

or less efficient:

myGetPhysicalDeviceProperties2 <- vkGetProc @VkGetPhysicalDeviceProperties2

Note: vkGetPhysicalDeviceProperties2Unsafe and vkGetPhysicalDeviceProperties2Safe are the unsafe and safe FFI imports of this function, respectively. vkGetPhysicalDeviceProperties2 is an alias of vkGetPhysicalDeviceProperties2Unsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetPhysicalDeviceProperties2Safe.

vkGetPhysicalDeviceProperties2Unsafe Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> Ptr VkPhysicalDeviceProperties2

pProperties

-> IO () 
void vkGetPhysicalDeviceProperties2
    ( VkPhysicalDevice physicalDevice
    , VkPhysicalDeviceProperties2* pProperties
    )

vkGetPhysicalDeviceProperties2 registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetPhysicalDeviceProperties2 <- vkGetInstanceProc @VkGetPhysicalDeviceProperties2 vkInstance

or less efficient:

myGetPhysicalDeviceProperties2 <- vkGetProc @VkGetPhysicalDeviceProperties2

Note: vkGetPhysicalDeviceProperties2Unsafe and vkGetPhysicalDeviceProperties2Safe are the unsafe and safe FFI imports of this function, respectively. vkGetPhysicalDeviceProperties2 is an alias of vkGetPhysicalDeviceProperties2Unsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetPhysicalDeviceProperties2Safe.

vkGetPhysicalDeviceProperties2Safe Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> Ptr VkPhysicalDeviceProperties2

pProperties

-> IO () 
void vkGetPhysicalDeviceProperties2
    ( VkPhysicalDevice physicalDevice
    , VkPhysicalDeviceProperties2* pProperties
    )

vkGetPhysicalDeviceProperties2 registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetPhysicalDeviceProperties2 <- vkGetInstanceProc @VkGetPhysicalDeviceProperties2 vkInstance

or less efficient:

myGetPhysicalDeviceProperties2 <- vkGetProc @VkGetPhysicalDeviceProperties2

Note: vkGetPhysicalDeviceProperties2Unsafe and vkGetPhysicalDeviceProperties2Safe are the unsafe and safe FFI imports of this function, respectively. vkGetPhysicalDeviceProperties2 is an alias of vkGetPhysicalDeviceProperties2Unsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetPhysicalDeviceProperties2Safe.

type VkGetPhysicalDeviceFormatProperties2 = "vkGetPhysicalDeviceFormatProperties2" Source #

type HS_vkGetPhysicalDeviceFormatProperties2 Source #

Arguments

 = VkPhysicalDevice

physicalDevice

-> VkFormat

format

-> Ptr VkFormatProperties2

pFormatProperties

-> IO () 
void vkGetPhysicalDeviceFormatProperties2
    ( VkPhysicalDevice physicalDevice
    , VkFormat format
    , VkFormatProperties2* pFormatProperties
    )

vkGetPhysicalDeviceFormatProperties2 registry at www.khronos.org

vkGetPhysicalDeviceFormatProperties2 Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> VkFormat

format

-> Ptr VkFormatProperties2

pFormatProperties

-> IO () 
void vkGetPhysicalDeviceFormatProperties2
    ( VkPhysicalDevice physicalDevice
    , VkFormat format
    , VkFormatProperties2* pFormatProperties
    )

vkGetPhysicalDeviceFormatProperties2 registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetPhysicalDeviceFormatProperties2 <- vkGetInstanceProc @VkGetPhysicalDeviceFormatProperties2 vkInstance

or less efficient:

myGetPhysicalDeviceFormatProperties2 <- vkGetProc @VkGetPhysicalDeviceFormatProperties2

Note: vkGetPhysicalDeviceFormatProperties2Unsafe and vkGetPhysicalDeviceFormatProperties2Safe are the unsafe and safe FFI imports of this function, respectively. vkGetPhysicalDeviceFormatProperties2 is an alias of vkGetPhysicalDeviceFormatProperties2Unsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetPhysicalDeviceFormatProperties2Safe.

vkGetPhysicalDeviceFormatProperties2Unsafe Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> VkFormat

format

-> Ptr VkFormatProperties2

pFormatProperties

-> IO () 
void vkGetPhysicalDeviceFormatProperties2
    ( VkPhysicalDevice physicalDevice
    , VkFormat format
    , VkFormatProperties2* pFormatProperties
    )

vkGetPhysicalDeviceFormatProperties2 registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetPhysicalDeviceFormatProperties2 <- vkGetInstanceProc @VkGetPhysicalDeviceFormatProperties2 vkInstance

or less efficient:

myGetPhysicalDeviceFormatProperties2 <- vkGetProc @VkGetPhysicalDeviceFormatProperties2

Note: vkGetPhysicalDeviceFormatProperties2Unsafe and vkGetPhysicalDeviceFormatProperties2Safe are the unsafe and safe FFI imports of this function, respectively. vkGetPhysicalDeviceFormatProperties2 is an alias of vkGetPhysicalDeviceFormatProperties2Unsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetPhysicalDeviceFormatProperties2Safe.

vkGetPhysicalDeviceFormatProperties2Safe Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> VkFormat

format

-> Ptr VkFormatProperties2

pFormatProperties

-> IO () 
void vkGetPhysicalDeviceFormatProperties2
    ( VkPhysicalDevice physicalDevice
    , VkFormat format
    , VkFormatProperties2* pFormatProperties
    )

vkGetPhysicalDeviceFormatProperties2 registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetPhysicalDeviceFormatProperties2 <- vkGetInstanceProc @VkGetPhysicalDeviceFormatProperties2 vkInstance

or less efficient:

myGetPhysicalDeviceFormatProperties2 <- vkGetProc @VkGetPhysicalDeviceFormatProperties2

Note: vkGetPhysicalDeviceFormatProperties2Unsafe and vkGetPhysicalDeviceFormatProperties2Safe are the unsafe and safe FFI imports of this function, respectively. vkGetPhysicalDeviceFormatProperties2 is an alias of vkGetPhysicalDeviceFormatProperties2Unsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetPhysicalDeviceFormatProperties2Safe.

type VkGetPhysicalDeviceImageFormatProperties2 = "vkGetPhysicalDeviceImageFormatProperties2" Source #

type HS_vkGetPhysicalDeviceImageFormatProperties2 Source #

Arguments

 = VkPhysicalDevice

physicalDevice

-> Ptr VkPhysicalDeviceImageFormatInfo2

pImageFormatInfo

-> Ptr VkImageFormatProperties2

pImageFormatProperties

-> IO VkResult 

Success codes: VK_SUCCESS.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY, VK_ERROR_FORMAT_NOT_SUPPORTED.

VkResult vkGetPhysicalDeviceImageFormatProperties2
    ( VkPhysicalDevice physicalDevice
    , const VkPhysicalDeviceImageFormatInfo2* pImageFormatInfo
    , VkImageFormatProperties2* pImageFormatProperties
    )

vkGetPhysicalDeviceImageFormatProperties2 registry at www.khronos.org

vkGetPhysicalDeviceImageFormatProperties2 Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> Ptr VkPhysicalDeviceImageFormatInfo2

pImageFormatInfo

-> Ptr VkImageFormatProperties2

pImageFormatProperties

-> IO VkResult 

Success codes: VK_SUCCESS.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY, VK_ERROR_FORMAT_NOT_SUPPORTED.

VkResult vkGetPhysicalDeviceImageFormatProperties2
    ( VkPhysicalDevice physicalDevice
    , const VkPhysicalDeviceImageFormatInfo2* pImageFormatInfo
    , VkImageFormatProperties2* pImageFormatProperties
    )

vkGetPhysicalDeviceImageFormatProperties2 registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetPhysicalDeviceImageFormatProperties2 <- vkGetInstanceProc @VkGetPhysicalDeviceImageFormatProperties2 vkInstance

or less efficient:

myGetPhysicalDeviceImageFormatProperties2 <- vkGetProc @VkGetPhysicalDeviceImageFormatProperties2

Note: vkGetPhysicalDeviceImageFormatProperties2Unsafe and vkGetPhysicalDeviceImageFormatProperties2Safe are the unsafe and safe FFI imports of this function, respectively. vkGetPhysicalDeviceImageFormatProperties2 is an alias of vkGetPhysicalDeviceImageFormatProperties2Unsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetPhysicalDeviceImageFormatProperties2Safe.

vkGetPhysicalDeviceImageFormatProperties2Unsafe Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> Ptr VkPhysicalDeviceImageFormatInfo2

pImageFormatInfo

-> Ptr VkImageFormatProperties2

pImageFormatProperties

-> IO VkResult 

Success codes: VK_SUCCESS.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY, VK_ERROR_FORMAT_NOT_SUPPORTED.

VkResult vkGetPhysicalDeviceImageFormatProperties2
    ( VkPhysicalDevice physicalDevice
    , const VkPhysicalDeviceImageFormatInfo2* pImageFormatInfo
    , VkImageFormatProperties2* pImageFormatProperties
    )

vkGetPhysicalDeviceImageFormatProperties2 registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetPhysicalDeviceImageFormatProperties2 <- vkGetInstanceProc @VkGetPhysicalDeviceImageFormatProperties2 vkInstance

or less efficient:

myGetPhysicalDeviceImageFormatProperties2 <- vkGetProc @VkGetPhysicalDeviceImageFormatProperties2

Note: vkGetPhysicalDeviceImageFormatProperties2Unsafe and vkGetPhysicalDeviceImageFormatProperties2Safe are the unsafe and safe FFI imports of this function, respectively. vkGetPhysicalDeviceImageFormatProperties2 is an alias of vkGetPhysicalDeviceImageFormatProperties2Unsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetPhysicalDeviceImageFormatProperties2Safe.

vkGetPhysicalDeviceImageFormatProperties2Safe Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> Ptr VkPhysicalDeviceImageFormatInfo2

pImageFormatInfo

-> Ptr VkImageFormatProperties2

pImageFormatProperties

-> IO VkResult 

Success codes: VK_SUCCESS.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY, VK_ERROR_FORMAT_NOT_SUPPORTED.

VkResult vkGetPhysicalDeviceImageFormatProperties2
    ( VkPhysicalDevice physicalDevice
    , const VkPhysicalDeviceImageFormatInfo2* pImageFormatInfo
    , VkImageFormatProperties2* pImageFormatProperties
    )

vkGetPhysicalDeviceImageFormatProperties2 registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetPhysicalDeviceImageFormatProperties2 <- vkGetInstanceProc @VkGetPhysicalDeviceImageFormatProperties2 vkInstance

or less efficient:

myGetPhysicalDeviceImageFormatProperties2 <- vkGetProc @VkGetPhysicalDeviceImageFormatProperties2

Note: vkGetPhysicalDeviceImageFormatProperties2Unsafe and vkGetPhysicalDeviceImageFormatProperties2Safe are the unsafe and safe FFI imports of this function, respectively. vkGetPhysicalDeviceImageFormatProperties2 is an alias of vkGetPhysicalDeviceImageFormatProperties2Unsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetPhysicalDeviceImageFormatProperties2Safe.

type VkGetPhysicalDeviceQueueFamilyProperties2 = "vkGetPhysicalDeviceQueueFamilyProperties2" Source #

type HS_vkGetPhysicalDeviceQueueFamilyProperties2 Source #

Arguments

 = VkPhysicalDevice

physicalDevice

-> Ptr Word32

pQueueFamilyPropertyCount

-> Ptr VkQueueFamilyProperties2

pQueueFamilyProperties

-> IO () 
void vkGetPhysicalDeviceQueueFamilyProperties2
    ( VkPhysicalDevice physicalDevice
    , uint32_t* pQueueFamilyPropertyCount
    , VkQueueFamilyProperties2* pQueueFamilyProperties
    )

vkGetPhysicalDeviceQueueFamilyProperties2 registry at www.khronos.org

vkGetPhysicalDeviceQueueFamilyProperties2 Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> Ptr Word32

pQueueFamilyPropertyCount

-> Ptr VkQueueFamilyProperties2

pQueueFamilyProperties

-> IO () 
void vkGetPhysicalDeviceQueueFamilyProperties2
    ( VkPhysicalDevice physicalDevice
    , uint32_t* pQueueFamilyPropertyCount
    , VkQueueFamilyProperties2* pQueueFamilyProperties
    )

vkGetPhysicalDeviceQueueFamilyProperties2 registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetPhysicalDeviceQueueFamilyProperties2 <- vkGetInstanceProc @VkGetPhysicalDeviceQueueFamilyProperties2 vkInstance

or less efficient:

myGetPhysicalDeviceQueueFamilyProperties2 <- vkGetProc @VkGetPhysicalDeviceQueueFamilyProperties2

Note: vkGetPhysicalDeviceQueueFamilyProperties2Unsafe and vkGetPhysicalDeviceQueueFamilyProperties2Safe are the unsafe and safe FFI imports of this function, respectively. vkGetPhysicalDeviceQueueFamilyProperties2 is an alias of vkGetPhysicalDeviceQueueFamilyProperties2Unsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetPhysicalDeviceQueueFamilyProperties2Safe.

vkGetPhysicalDeviceQueueFamilyProperties2Unsafe Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> Ptr Word32

pQueueFamilyPropertyCount

-> Ptr VkQueueFamilyProperties2

pQueueFamilyProperties

-> IO () 
void vkGetPhysicalDeviceQueueFamilyProperties2
    ( VkPhysicalDevice physicalDevice
    , uint32_t* pQueueFamilyPropertyCount
    , VkQueueFamilyProperties2* pQueueFamilyProperties
    )

vkGetPhysicalDeviceQueueFamilyProperties2 registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetPhysicalDeviceQueueFamilyProperties2 <- vkGetInstanceProc @VkGetPhysicalDeviceQueueFamilyProperties2 vkInstance

or less efficient:

myGetPhysicalDeviceQueueFamilyProperties2 <- vkGetProc @VkGetPhysicalDeviceQueueFamilyProperties2

Note: vkGetPhysicalDeviceQueueFamilyProperties2Unsafe and vkGetPhysicalDeviceQueueFamilyProperties2Safe are the unsafe and safe FFI imports of this function, respectively. vkGetPhysicalDeviceQueueFamilyProperties2 is an alias of vkGetPhysicalDeviceQueueFamilyProperties2Unsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetPhysicalDeviceQueueFamilyProperties2Safe.

vkGetPhysicalDeviceQueueFamilyProperties2Safe Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> Ptr Word32

pQueueFamilyPropertyCount

-> Ptr VkQueueFamilyProperties2

pQueueFamilyProperties

-> IO () 
void vkGetPhysicalDeviceQueueFamilyProperties2
    ( VkPhysicalDevice physicalDevice
    , uint32_t* pQueueFamilyPropertyCount
    , VkQueueFamilyProperties2* pQueueFamilyProperties
    )

vkGetPhysicalDeviceQueueFamilyProperties2 registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetPhysicalDeviceQueueFamilyProperties2 <- vkGetInstanceProc @VkGetPhysicalDeviceQueueFamilyProperties2 vkInstance

or less efficient:

myGetPhysicalDeviceQueueFamilyProperties2 <- vkGetProc @VkGetPhysicalDeviceQueueFamilyProperties2

Note: vkGetPhysicalDeviceQueueFamilyProperties2Unsafe and vkGetPhysicalDeviceQueueFamilyProperties2Safe are the unsafe and safe FFI imports of this function, respectively. vkGetPhysicalDeviceQueueFamilyProperties2 is an alias of vkGetPhysicalDeviceQueueFamilyProperties2Unsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetPhysicalDeviceQueueFamilyProperties2Safe.

type VkGetPhysicalDeviceMemoryProperties2 = "vkGetPhysicalDeviceMemoryProperties2" Source #

type HS_vkGetPhysicalDeviceMemoryProperties2 Source #

Arguments

 = VkPhysicalDevice

physicalDevice

-> Ptr VkPhysicalDeviceMemoryProperties2

pMemoryProperties

-> IO () 
void vkGetPhysicalDeviceMemoryProperties2
    ( VkPhysicalDevice physicalDevice
    , VkPhysicalDeviceMemoryProperties2* pMemoryProperties
    )

vkGetPhysicalDeviceMemoryProperties2 registry at www.khronos.org

vkGetPhysicalDeviceMemoryProperties2 Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> Ptr VkPhysicalDeviceMemoryProperties2

pMemoryProperties

-> IO () 
void vkGetPhysicalDeviceMemoryProperties2
    ( VkPhysicalDevice physicalDevice
    , VkPhysicalDeviceMemoryProperties2* pMemoryProperties
    )

vkGetPhysicalDeviceMemoryProperties2 registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetPhysicalDeviceMemoryProperties2 <- vkGetInstanceProc @VkGetPhysicalDeviceMemoryProperties2 vkInstance

or less efficient:

myGetPhysicalDeviceMemoryProperties2 <- vkGetProc @VkGetPhysicalDeviceMemoryProperties2

Note: vkGetPhysicalDeviceMemoryProperties2Unsafe and vkGetPhysicalDeviceMemoryProperties2Safe are the unsafe and safe FFI imports of this function, respectively. vkGetPhysicalDeviceMemoryProperties2 is an alias of vkGetPhysicalDeviceMemoryProperties2Unsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetPhysicalDeviceMemoryProperties2Safe.

vkGetPhysicalDeviceMemoryProperties2Unsafe Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> Ptr VkPhysicalDeviceMemoryProperties2

pMemoryProperties

-> IO () 
void vkGetPhysicalDeviceMemoryProperties2
    ( VkPhysicalDevice physicalDevice
    , VkPhysicalDeviceMemoryProperties2* pMemoryProperties
    )

vkGetPhysicalDeviceMemoryProperties2 registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetPhysicalDeviceMemoryProperties2 <- vkGetInstanceProc @VkGetPhysicalDeviceMemoryProperties2 vkInstance

or less efficient:

myGetPhysicalDeviceMemoryProperties2 <- vkGetProc @VkGetPhysicalDeviceMemoryProperties2

Note: vkGetPhysicalDeviceMemoryProperties2Unsafe and vkGetPhysicalDeviceMemoryProperties2Safe are the unsafe and safe FFI imports of this function, respectively. vkGetPhysicalDeviceMemoryProperties2 is an alias of vkGetPhysicalDeviceMemoryProperties2Unsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetPhysicalDeviceMemoryProperties2Safe.

vkGetPhysicalDeviceMemoryProperties2Safe Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> Ptr VkPhysicalDeviceMemoryProperties2

pMemoryProperties

-> IO () 
void vkGetPhysicalDeviceMemoryProperties2
    ( VkPhysicalDevice physicalDevice
    , VkPhysicalDeviceMemoryProperties2* pMemoryProperties
    )

vkGetPhysicalDeviceMemoryProperties2 registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetPhysicalDeviceMemoryProperties2 <- vkGetInstanceProc @VkGetPhysicalDeviceMemoryProperties2 vkInstance

or less efficient:

myGetPhysicalDeviceMemoryProperties2 <- vkGetProc @VkGetPhysicalDeviceMemoryProperties2

Note: vkGetPhysicalDeviceMemoryProperties2Unsafe and vkGetPhysicalDeviceMemoryProperties2Safe are the unsafe and safe FFI imports of this function, respectively. vkGetPhysicalDeviceMemoryProperties2 is an alias of vkGetPhysicalDeviceMemoryProperties2Unsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetPhysicalDeviceMemoryProperties2Safe.

type VkGetPhysicalDeviceSparseImageFormatProperties2 = "vkGetPhysicalDeviceSparseImageFormatProperties2" Source #

type HS_vkGetPhysicalDeviceSparseImageFormatProperties2 Source #

Arguments

 = VkPhysicalDevice

physicalDevice

-> Ptr VkPhysicalDeviceSparseImageFormatInfo2

pFormatInfo

-> Ptr Word32

pPropertyCount

-> Ptr VkSparseImageFormatProperties2

pProperties

-> IO () 
void vkGetPhysicalDeviceSparseImageFormatProperties2
    ( VkPhysicalDevice physicalDevice
    , const VkPhysicalDeviceSparseImageFormatInfo2* pFormatInfo
    , uint32_t* pPropertyCount
    , VkSparseImageFormatProperties2* pProperties
    )

vkGetPhysicalDeviceSparseImageFormatProperties2 registry at www.khronos.org

vkGetPhysicalDeviceSparseImageFormatProperties2 Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> Ptr VkPhysicalDeviceSparseImageFormatInfo2

pFormatInfo

-> Ptr Word32

pPropertyCount

-> Ptr VkSparseImageFormatProperties2

pProperties

-> IO () 
void vkGetPhysicalDeviceSparseImageFormatProperties2
    ( VkPhysicalDevice physicalDevice
    , const VkPhysicalDeviceSparseImageFormatInfo2* pFormatInfo
    , uint32_t* pPropertyCount
    , VkSparseImageFormatProperties2* pProperties
    )

vkGetPhysicalDeviceSparseImageFormatProperties2 registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetPhysicalDeviceSparseImageFormatProperties2 <- vkGetInstanceProc @VkGetPhysicalDeviceSparseImageFormatProperties2 vkInstance

or less efficient:

myGetPhysicalDeviceSparseImageFormatProperties2 <- vkGetProc @VkGetPhysicalDeviceSparseImageFormatProperties2

Note: vkGetPhysicalDeviceSparseImageFormatProperties2Unsafe and vkGetPhysicalDeviceSparseImageFormatProperties2Safe are the unsafe and safe FFI imports of this function, respectively. vkGetPhysicalDeviceSparseImageFormatProperties2 is an alias of vkGetPhysicalDeviceSparseImageFormatProperties2Unsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetPhysicalDeviceSparseImageFormatProperties2Safe.

vkGetPhysicalDeviceSparseImageFormatProperties2Unsafe Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> Ptr VkPhysicalDeviceSparseImageFormatInfo2

pFormatInfo

-> Ptr Word32

pPropertyCount

-> Ptr VkSparseImageFormatProperties2

pProperties

-> IO () 
void vkGetPhysicalDeviceSparseImageFormatProperties2
    ( VkPhysicalDevice physicalDevice
    , const VkPhysicalDeviceSparseImageFormatInfo2* pFormatInfo
    , uint32_t* pPropertyCount
    , VkSparseImageFormatProperties2* pProperties
    )

vkGetPhysicalDeviceSparseImageFormatProperties2 registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetPhysicalDeviceSparseImageFormatProperties2 <- vkGetInstanceProc @VkGetPhysicalDeviceSparseImageFormatProperties2 vkInstance

or less efficient:

myGetPhysicalDeviceSparseImageFormatProperties2 <- vkGetProc @VkGetPhysicalDeviceSparseImageFormatProperties2

Note: vkGetPhysicalDeviceSparseImageFormatProperties2Unsafe and vkGetPhysicalDeviceSparseImageFormatProperties2Safe are the unsafe and safe FFI imports of this function, respectively. vkGetPhysicalDeviceSparseImageFormatProperties2 is an alias of vkGetPhysicalDeviceSparseImageFormatProperties2Unsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetPhysicalDeviceSparseImageFormatProperties2Safe.

vkGetPhysicalDeviceSparseImageFormatProperties2Safe Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> Ptr VkPhysicalDeviceSparseImageFormatInfo2

pFormatInfo

-> Ptr Word32

pPropertyCount

-> Ptr VkSparseImageFormatProperties2

pProperties

-> IO () 
void vkGetPhysicalDeviceSparseImageFormatProperties2
    ( VkPhysicalDevice physicalDevice
    , const VkPhysicalDeviceSparseImageFormatInfo2* pFormatInfo
    , uint32_t* pPropertyCount
    , VkSparseImageFormatProperties2* pProperties
    )

vkGetPhysicalDeviceSparseImageFormatProperties2 registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetPhysicalDeviceSparseImageFormatProperties2 <- vkGetInstanceProc @VkGetPhysicalDeviceSparseImageFormatProperties2 vkInstance

or less efficient:

myGetPhysicalDeviceSparseImageFormatProperties2 <- vkGetProc @VkGetPhysicalDeviceSparseImageFormatProperties2

Note: vkGetPhysicalDeviceSparseImageFormatProperties2Unsafe and vkGetPhysicalDeviceSparseImageFormatProperties2Safe are the unsafe and safe FFI imports of this function, respectively. vkGetPhysicalDeviceSparseImageFormatProperties2 is an alias of vkGetPhysicalDeviceSparseImageFormatProperties2Unsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetPhysicalDeviceSparseImageFormatProperties2Safe.

Promoted from VK_KHR_maintenance1

#include "vk_platform.h"

type VkTrimCommandPool = "vkTrimCommandPool" Source #

type HS_vkTrimCommandPool Source #

Arguments

 = VkDevice

device

-> VkCommandPool

commandPool

-> VkCommandPoolTrimFlags

flags

-> IO () 
void vkTrimCommandPool
    ( VkDevice device
    , VkCommandPool commandPool
    , VkCommandPoolTrimFlags flags
    )

vkTrimCommandPool registry at www.khronos.org

vkTrimCommandPool Source #

Arguments

:: VkDevice

device

-> VkCommandPool

commandPool

-> VkCommandPoolTrimFlags

flags

-> IO () 
void vkTrimCommandPool
    ( VkDevice device
    , VkCommandPool commandPool
    , VkCommandPoolTrimFlags flags
    )

vkTrimCommandPool registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myTrimCommandPool <- vkGetDeviceProc @VkTrimCommandPool vkDevice

or less efficient:

myTrimCommandPool <- vkGetProc @VkTrimCommandPool

Note: vkTrimCommandPoolUnsafe and vkTrimCommandPoolSafe are the unsafe and safe FFI imports of this function, respectively. vkTrimCommandPool is an alias of vkTrimCommandPoolUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkTrimCommandPoolSafe.

vkTrimCommandPoolUnsafe Source #

Arguments

:: VkDevice

device

-> VkCommandPool

commandPool

-> VkCommandPoolTrimFlags

flags

-> IO () 
void vkTrimCommandPool
    ( VkDevice device
    , VkCommandPool commandPool
    , VkCommandPoolTrimFlags flags
    )

vkTrimCommandPool registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myTrimCommandPool <- vkGetDeviceProc @VkTrimCommandPool vkDevice

or less efficient:

myTrimCommandPool <- vkGetProc @VkTrimCommandPool

Note: vkTrimCommandPoolUnsafe and vkTrimCommandPoolSafe are the unsafe and safe FFI imports of this function, respectively. vkTrimCommandPool is an alias of vkTrimCommandPoolUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkTrimCommandPoolSafe.

vkTrimCommandPoolSafe Source #

Arguments

:: VkDevice

device

-> VkCommandPool

commandPool

-> VkCommandPoolTrimFlags

flags

-> IO () 
void vkTrimCommandPool
    ( VkDevice device
    , VkCommandPool commandPool
    , VkCommandPoolTrimFlags flags
    )

vkTrimCommandPool registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myTrimCommandPool <- vkGetDeviceProc @VkTrimCommandPool vkDevice

or less efficient:

myTrimCommandPool <- vkGetProc @VkTrimCommandPool

Note: vkTrimCommandPoolUnsafe and vkTrimCommandPoolSafe are the unsafe and safe FFI imports of this function, respectively. vkTrimCommandPool is an alias of vkTrimCommandPoolUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkTrimCommandPoolSafe.

pattern VK_FORMAT_FEATURE_TRANSFER_SRC_BIT :: VkFormatFeatureFlagBits Source #

Format can be used as the source image of image transfer commands

bitpos = 14

pattern VK_FORMAT_FEATURE_TRANSFER_DST_BIT :: VkFormatFeatureFlagBits Source #

Format can be used as the destination image of image transfer commands

bitpos = 15

pattern VK_IMAGE_CREATE_2D_ARRAY_COMPATIBLE_BIT :: VkImageCreateFlagBits Source #

The 3D image can be viewed as a 2D or 2D array image

bitpos = 5

Promoted from VK_KHR_maintenance2

newtype VkAccessBitmask a Source #

Constructors

VkAccessBitmask VkFlags 

Instances

Bounded (VkAccessBitmask FlagMask) Source # 
Enum (VkAccessBitmask FlagMask) Source # 
Eq (VkAccessBitmask a) Source # 
Integral (VkAccessBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkAccessBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkAccessBitmask a -> c (VkAccessBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkAccessBitmask a) #

toConstr :: VkAccessBitmask a -> Constr #

dataTypeOf :: VkAccessBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkAccessBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkAccessBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkAccessBitmask a -> VkAccessBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkAccessBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkAccessBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkAccessBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkAccessBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkAccessBitmask a -> m (VkAccessBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkAccessBitmask a -> m (VkAccessBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkAccessBitmask a -> m (VkAccessBitmask a) #

Num (VkAccessBitmask FlagMask) Source # 
Ord (VkAccessBitmask a) Source # 
Read (VkAccessBitmask a) Source # 
Real (VkAccessBitmask FlagMask) Source # 
Show (VkAccessBitmask a) Source # 
Generic (VkAccessBitmask a) Source # 

Associated Types

type Rep (VkAccessBitmask a) :: * -> * #

Storable (VkAccessBitmask a) Source # 
Bits (VkAccessBitmask FlagMask) Source # 
FiniteBits (VkAccessBitmask FlagMask) Source # 
type Rep (VkAccessBitmask a) Source # 
type Rep (VkAccessBitmask a) = D1 (MetaData "VkAccessBitmask" "Graphics.Vulkan.Types.Enum.AccessFlags" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkAccessBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

pattern VK_ACCESS_INDIRECT_COMMAND_READ_BIT :: forall a. VkAccessBitmask a Source #

Controls coherency of indirect command reads

bitpos = 0

pattern VK_ACCESS_INDEX_READ_BIT :: forall a. VkAccessBitmask a Source #

Controls coherency of index reads

bitpos = 1

pattern VK_ACCESS_VERTEX_ATTRIBUTE_READ_BIT :: forall a. VkAccessBitmask a Source #

Controls coherency of vertex attribute reads

bitpos = 2

pattern VK_ACCESS_UNIFORM_READ_BIT :: forall a. VkAccessBitmask a Source #

Controls coherency of uniform buffer reads

bitpos = 3

pattern VK_ACCESS_INPUT_ATTACHMENT_READ_BIT :: forall a. VkAccessBitmask a Source #

Controls coherency of input attachment reads

bitpos = 4

pattern VK_ACCESS_SHADER_READ_BIT :: forall a. VkAccessBitmask a Source #

Controls coherency of shader reads

bitpos = 5

pattern VK_ACCESS_SHADER_WRITE_BIT :: forall a. VkAccessBitmask a Source #

Controls coherency of shader writes

bitpos = 6

pattern VK_ACCESS_COLOR_ATTACHMENT_READ_BIT :: forall a. VkAccessBitmask a Source #

Controls coherency of color attachment reads

bitpos = 7

pattern VK_ACCESS_COLOR_ATTACHMENT_WRITE_BIT :: forall a. VkAccessBitmask a Source #

Controls coherency of color attachment writes

bitpos = 8

pattern VK_ACCESS_DEPTH_STENCIL_ATTACHMENT_READ_BIT :: forall a. VkAccessBitmask a Source #

Controls coherency of depth/stencil attachment reads

bitpos = 9

pattern VK_ACCESS_DEPTH_STENCIL_ATTACHMENT_WRITE_BIT :: forall a. VkAccessBitmask a Source #

Controls coherency of depth/stencil attachment writes

bitpos = 10

pattern VK_ACCESS_TRANSFER_READ_BIT :: forall a. VkAccessBitmask a Source #

Controls coherency of transfer reads

bitpos = 11

pattern VK_ACCESS_TRANSFER_WRITE_BIT :: forall a. VkAccessBitmask a Source #

Controls coherency of transfer writes

bitpos = 12

pattern VK_ACCESS_HOST_READ_BIT :: forall a. VkAccessBitmask a Source #

Controls coherency of host reads

bitpos = 13

pattern VK_ACCESS_HOST_WRITE_BIT :: forall a. VkAccessBitmask a Source #

Controls coherency of host writes

bitpos = 14

pattern VK_ACCESS_MEMORY_READ_BIT :: forall a. VkAccessBitmask a Source #

Controls coherency of memory reads

bitpos = 15

pattern VK_ACCESS_MEMORY_WRITE_BIT :: forall a. VkAccessBitmask a Source #

Controls coherency of memory writes

bitpos = 16

data VkAttachmentDescription Source #

typedef struct VkAttachmentDescription {
    VkAttachmentDescriptionFlags flags;
    VkFormat               format;
    VkSampleCountFlagBits  samples;
    VkAttachmentLoadOp     loadOp;
    VkAttachmentStoreOp    storeOp;
    VkAttachmentLoadOp     stencilLoadOp;
    VkAttachmentStoreOp    stencilStoreOp;
    VkImageLayout          initialLayout;
    VkImageLayout          finalLayout;
} VkAttachmentDescription;

VkAttachmentDescription registry at www.khronos.org

Instances

Eq VkAttachmentDescription Source # 
Ord VkAttachmentDescription Source # 
Show VkAttachmentDescription Source # 
Storable VkAttachmentDescription Source # 
VulkanMarshalPrim VkAttachmentDescription Source # 
VulkanMarshal VkAttachmentDescription Source # 
CanWriteField "finalLayout" VkAttachmentDescription Source # 
CanWriteField "flags" VkAttachmentDescription Source # 
CanWriteField "format" VkAttachmentDescription Source # 
CanWriteField "initialLayout" VkAttachmentDescription Source # 
CanWriteField "loadOp" VkAttachmentDescription Source # 
CanWriteField "samples" VkAttachmentDescription Source # 
CanWriteField "stencilLoadOp" VkAttachmentDescription Source # 
CanWriteField "stencilStoreOp" VkAttachmentDescription Source # 
CanWriteField "storeOp" VkAttachmentDescription Source # 
CanReadField "finalLayout" VkAttachmentDescription Source # 
CanReadField "flags" VkAttachmentDescription Source # 
CanReadField "format" VkAttachmentDescription Source # 
CanReadField "initialLayout" VkAttachmentDescription Source # 
CanReadField "loadOp" VkAttachmentDescription Source # 
CanReadField "samples" VkAttachmentDescription Source # 
CanReadField "stencilLoadOp" VkAttachmentDescription Source # 
CanReadField "stencilStoreOp" VkAttachmentDescription Source # 
CanReadField "storeOp" VkAttachmentDescription Source # 
HasField "finalLayout" VkAttachmentDescription Source # 
HasField "flags" VkAttachmentDescription Source # 
HasField "format" VkAttachmentDescription Source # 
HasField "initialLayout" VkAttachmentDescription Source # 

Associated Types

type FieldType ("initialLayout" :: Symbol) VkAttachmentDescription :: Type Source #

type FieldOptional ("initialLayout" :: Symbol) VkAttachmentDescription :: Bool Source #

type FieldOffset ("initialLayout" :: Symbol) VkAttachmentDescription :: Nat Source #

type FieldIsArray ("initialLayout" :: Symbol) VkAttachmentDescription :: Bool Source #

HasField "loadOp" VkAttachmentDescription Source # 
HasField "samples" VkAttachmentDescription Source # 
HasField "stencilLoadOp" VkAttachmentDescription Source # 

Associated Types

type FieldType ("stencilLoadOp" :: Symbol) VkAttachmentDescription :: Type Source #

type FieldOptional ("stencilLoadOp" :: Symbol) VkAttachmentDescription :: Bool Source #

type FieldOffset ("stencilLoadOp" :: Symbol) VkAttachmentDescription :: Nat Source #

type FieldIsArray ("stencilLoadOp" :: Symbol) VkAttachmentDescription :: Bool Source #

HasField "stencilStoreOp" VkAttachmentDescription Source # 

Associated Types

type FieldType ("stencilStoreOp" :: Symbol) VkAttachmentDescription :: Type Source #

type FieldOptional ("stencilStoreOp" :: Symbol) VkAttachmentDescription :: Bool Source #

type FieldOffset ("stencilStoreOp" :: Symbol) VkAttachmentDescription :: Nat Source #

type FieldIsArray ("stencilStoreOp" :: Symbol) VkAttachmentDescription :: Bool Source #

HasField "storeOp" VkAttachmentDescription Source # 
type StructFields VkAttachmentDescription Source # 
type StructFields VkAttachmentDescription = (:) Symbol "flags" ((:) Symbol "format" ((:) Symbol "samples" ((:) Symbol "loadOp" ((:) Symbol "storeOp" ((:) Symbol "stencilLoadOp" ((:) Symbol "stencilStoreOp" ((:) Symbol "initialLayout" ((:) Symbol "finalLayout" ([] Symbol)))))))))
type CUnionType VkAttachmentDescription Source # 
type ReturnedOnly VkAttachmentDescription Source # 
type StructExtends VkAttachmentDescription Source # 
type FieldType "finalLayout" VkAttachmentDescription Source # 
type FieldType "flags" VkAttachmentDescription Source # 
type FieldType "format" VkAttachmentDescription Source # 
type FieldType "initialLayout" VkAttachmentDescription Source # 
type FieldType "loadOp" VkAttachmentDescription Source # 
type FieldType "samples" VkAttachmentDescription Source # 
type FieldType "stencilLoadOp" VkAttachmentDescription Source # 
type FieldType "stencilStoreOp" VkAttachmentDescription Source # 
type FieldType "storeOp" VkAttachmentDescription Source # 
type FieldOptional "finalLayout" VkAttachmentDescription Source # 
type FieldOptional "flags" VkAttachmentDescription Source # 
type FieldOptional "format" VkAttachmentDescription Source # 
type FieldOptional "initialLayout" VkAttachmentDescription Source # 
type FieldOptional "loadOp" VkAttachmentDescription Source # 
type FieldOptional "samples" VkAttachmentDescription Source # 
type FieldOptional "stencilLoadOp" VkAttachmentDescription Source # 
type FieldOptional "stencilStoreOp" VkAttachmentDescription Source # 
type FieldOptional "storeOp" VkAttachmentDescription Source # 
type FieldOffset "finalLayout" VkAttachmentDescription Source # 
type FieldOffset "finalLayout" VkAttachmentDescription = 32
type FieldOffset "flags" VkAttachmentDescription Source # 
type FieldOffset "format" VkAttachmentDescription Source # 
type FieldOffset "initialLayout" VkAttachmentDescription Source # 
type FieldOffset "initialLayout" VkAttachmentDescription = 28
type FieldOffset "loadOp" VkAttachmentDescription Source # 
type FieldOffset "samples" VkAttachmentDescription Source # 
type FieldOffset "stencilLoadOp" VkAttachmentDescription Source # 
type FieldOffset "stencilLoadOp" VkAttachmentDescription = 20
type FieldOffset "stencilStoreOp" VkAttachmentDescription Source # 
type FieldOffset "stencilStoreOp" VkAttachmentDescription = 24
type FieldOffset "storeOp" VkAttachmentDescription Source # 
type FieldIsArray "finalLayout" VkAttachmentDescription Source # 
type FieldIsArray "flags" VkAttachmentDescription Source # 
type FieldIsArray "format" VkAttachmentDescription Source # 
type FieldIsArray "initialLayout" VkAttachmentDescription Source # 
type FieldIsArray "loadOp" VkAttachmentDescription Source # 
type FieldIsArray "samples" VkAttachmentDescription Source # 
type FieldIsArray "stencilLoadOp" VkAttachmentDescription Source # 
type FieldIsArray "stencilStoreOp" VkAttachmentDescription Source # 
type FieldIsArray "storeOp" VkAttachmentDescription Source # 

data VkAttachmentReference Source #

typedef struct VkAttachmentReference {
    uint32_t               attachment;
    VkImageLayout          layout;
} VkAttachmentReference;

VkAttachmentReference registry at www.khronos.org

Instances

Eq VkAttachmentReference Source # 
Ord VkAttachmentReference Source # 
Show VkAttachmentReference Source # 
Storable VkAttachmentReference Source # 
VulkanMarshalPrim VkAttachmentReference Source # 
VulkanMarshal VkAttachmentReference Source # 
CanWriteField "attachment" VkAttachmentReference Source # 
CanWriteField "layout" VkAttachmentReference Source # 
CanReadField "attachment" VkAttachmentReference Source # 
CanReadField "layout" VkAttachmentReference Source # 
HasField "attachment" VkAttachmentReference Source # 
HasField "layout" VkAttachmentReference Source # 
type StructFields VkAttachmentReference Source # 
type StructFields VkAttachmentReference = (:) Symbol "attachment" ((:) Symbol "layout" ([] Symbol))
type CUnionType VkAttachmentReference Source # 
type ReturnedOnly VkAttachmentReference Source # 
type StructExtends VkAttachmentReference Source # 
type FieldType "attachment" VkAttachmentReference Source # 
type FieldType "layout" VkAttachmentReference Source # 
type FieldOptional "attachment" VkAttachmentReference Source # 
type FieldOptional "layout" VkAttachmentReference Source # 
type FieldOffset "attachment" VkAttachmentReference Source # 
type FieldOffset "attachment" VkAttachmentReference = 0
type FieldOffset "layout" VkAttachmentReference Source # 
type FieldIsArray "attachment" VkAttachmentReference Source # 
type FieldIsArray "layout" VkAttachmentReference Source # 

data VkAttachmentSampleLocationsEXT Source #

typedef struct VkAttachmentSampleLocationsEXT {
    uint32_t                         attachmentIndex;
    VkSampleLocationsInfoEXT         sampleLocationsInfo;
} VkAttachmentSampleLocationsEXT;

VkAttachmentSampleLocationsEXT registry at www.khronos.org

Instances

Eq VkAttachmentSampleLocationsEXT Source # 
Ord VkAttachmentSampleLocationsEXT Source # 
Show VkAttachmentSampleLocationsEXT Source # 
Storable VkAttachmentSampleLocationsEXT Source # 
VulkanMarshalPrim VkAttachmentSampleLocationsEXT Source # 
VulkanMarshal VkAttachmentSampleLocationsEXT Source # 
CanWriteField "attachmentIndex" VkAttachmentSampleLocationsEXT Source # 
CanWriteField "sampleLocationsInfo" VkAttachmentSampleLocationsEXT Source # 
CanReadField "attachmentIndex" VkAttachmentSampleLocationsEXT Source # 
CanReadField "sampleLocationsInfo" VkAttachmentSampleLocationsEXT Source # 
HasField "attachmentIndex" VkAttachmentSampleLocationsEXT Source # 
HasField "sampleLocationsInfo" VkAttachmentSampleLocationsEXT Source # 

Associated Types

type FieldType ("sampleLocationsInfo" :: Symbol) VkAttachmentSampleLocationsEXT :: Type Source #

type FieldOptional ("sampleLocationsInfo" :: Symbol) VkAttachmentSampleLocationsEXT :: Bool Source #

type FieldOffset ("sampleLocationsInfo" :: Symbol) VkAttachmentSampleLocationsEXT :: Nat Source #

type FieldIsArray ("sampleLocationsInfo" :: Symbol) VkAttachmentSampleLocationsEXT :: Bool Source #

type StructFields VkAttachmentSampleLocationsEXT Source # 
type StructFields VkAttachmentSampleLocationsEXT = (:) Symbol "attachmentIndex" ((:) Symbol "sampleLocationsInfo" ([] Symbol))
type CUnionType VkAttachmentSampleLocationsEXT Source # 
type ReturnedOnly VkAttachmentSampleLocationsEXT Source # 
type StructExtends VkAttachmentSampleLocationsEXT Source # 
type FieldType "attachmentIndex" VkAttachmentSampleLocationsEXT Source # 
type FieldType "sampleLocationsInfo" VkAttachmentSampleLocationsEXT Source # 
type FieldOptional "attachmentIndex" VkAttachmentSampleLocationsEXT Source # 
type FieldOptional "sampleLocationsInfo" VkAttachmentSampleLocationsEXT Source # 
type FieldOffset "attachmentIndex" VkAttachmentSampleLocationsEXT Source # 
type FieldOffset "attachmentIndex" VkAttachmentSampleLocationsEXT = 0
type FieldOffset "sampleLocationsInfo" VkAttachmentSampleLocationsEXT Source # 
type FieldOffset "sampleLocationsInfo" VkAttachmentSampleLocationsEXT = 8
type FieldIsArray "attachmentIndex" VkAttachmentSampleLocationsEXT Source # 
type FieldIsArray "sampleLocationsInfo" VkAttachmentSampleLocationsEXT Source # 

newtype VkAttachmentDescriptionBitmask a Source #

Instances

Bounded (VkAttachmentDescriptionBitmask FlagMask) Source # 
Enum (VkAttachmentDescriptionBitmask FlagMask) Source # 
Eq (VkAttachmentDescriptionBitmask a) Source # 
Integral (VkAttachmentDescriptionBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkAttachmentDescriptionBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkAttachmentDescriptionBitmask a -> c (VkAttachmentDescriptionBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkAttachmentDescriptionBitmask a) #

toConstr :: VkAttachmentDescriptionBitmask a -> Constr #

dataTypeOf :: VkAttachmentDescriptionBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkAttachmentDescriptionBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkAttachmentDescriptionBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkAttachmentDescriptionBitmask a -> VkAttachmentDescriptionBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkAttachmentDescriptionBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkAttachmentDescriptionBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkAttachmentDescriptionBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkAttachmentDescriptionBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkAttachmentDescriptionBitmask a -> m (VkAttachmentDescriptionBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkAttachmentDescriptionBitmask a -> m (VkAttachmentDescriptionBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkAttachmentDescriptionBitmask a -> m (VkAttachmentDescriptionBitmask a) #

Num (VkAttachmentDescriptionBitmask FlagMask) Source # 
Ord (VkAttachmentDescriptionBitmask a) Source # 
Read (VkAttachmentDescriptionBitmask a) Source # 
Real (VkAttachmentDescriptionBitmask FlagMask) Source # 
Show (VkAttachmentDescriptionBitmask a) Source # 
Generic (VkAttachmentDescriptionBitmask a) Source # 
Storable (VkAttachmentDescriptionBitmask a) Source # 
Bits (VkAttachmentDescriptionBitmask FlagMask) Source # 

Methods

(.&.) :: VkAttachmentDescriptionBitmask FlagMask -> VkAttachmentDescriptionBitmask FlagMask -> VkAttachmentDescriptionBitmask FlagMask #

(.|.) :: VkAttachmentDescriptionBitmask FlagMask -> VkAttachmentDescriptionBitmask FlagMask -> VkAttachmentDescriptionBitmask FlagMask #

xor :: VkAttachmentDescriptionBitmask FlagMask -> VkAttachmentDescriptionBitmask FlagMask -> VkAttachmentDescriptionBitmask FlagMask #

complement :: VkAttachmentDescriptionBitmask FlagMask -> VkAttachmentDescriptionBitmask FlagMask #

shift :: VkAttachmentDescriptionBitmask FlagMask -> Int -> VkAttachmentDescriptionBitmask FlagMask #

rotate :: VkAttachmentDescriptionBitmask FlagMask -> Int -> VkAttachmentDescriptionBitmask FlagMask #

zeroBits :: VkAttachmentDescriptionBitmask FlagMask #

bit :: Int -> VkAttachmentDescriptionBitmask FlagMask #

setBit :: VkAttachmentDescriptionBitmask FlagMask -> Int -> VkAttachmentDescriptionBitmask FlagMask #

clearBit :: VkAttachmentDescriptionBitmask FlagMask -> Int -> VkAttachmentDescriptionBitmask FlagMask #

complementBit :: VkAttachmentDescriptionBitmask FlagMask -> Int -> VkAttachmentDescriptionBitmask FlagMask #

testBit :: VkAttachmentDescriptionBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkAttachmentDescriptionBitmask FlagMask -> Maybe Int #

bitSize :: VkAttachmentDescriptionBitmask FlagMask -> Int #

isSigned :: VkAttachmentDescriptionBitmask FlagMask -> Bool #

shiftL :: VkAttachmentDescriptionBitmask FlagMask -> Int -> VkAttachmentDescriptionBitmask FlagMask #

unsafeShiftL :: VkAttachmentDescriptionBitmask FlagMask -> Int -> VkAttachmentDescriptionBitmask FlagMask #

shiftR :: VkAttachmentDescriptionBitmask FlagMask -> Int -> VkAttachmentDescriptionBitmask FlagMask #

unsafeShiftR :: VkAttachmentDescriptionBitmask FlagMask -> Int -> VkAttachmentDescriptionBitmask FlagMask #

rotateL :: VkAttachmentDescriptionBitmask FlagMask -> Int -> VkAttachmentDescriptionBitmask FlagMask #

rotateR :: VkAttachmentDescriptionBitmask FlagMask -> Int -> VkAttachmentDescriptionBitmask FlagMask #

popCount :: VkAttachmentDescriptionBitmask FlagMask -> Int #

FiniteBits (VkAttachmentDescriptionBitmask FlagMask) Source # 
type Rep (VkAttachmentDescriptionBitmask a) Source # 
type Rep (VkAttachmentDescriptionBitmask a) = D1 (MetaData "VkAttachmentDescriptionBitmask" "Graphics.Vulkan.Types.Enum.Attachment" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkAttachmentDescriptionBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

pattern VK_ATTACHMENT_DESCRIPTION_MAY_ALIAS_BIT :: forall a. VkAttachmentDescriptionBitmask a Source #

The attachment may alias physical memory of another attachment in the same render pass

bitpos = 0

newtype VkAttachmentLoadOp Source #

Instances

Bounded VkAttachmentLoadOp Source # 
Enum VkAttachmentLoadOp Source # 
Eq VkAttachmentLoadOp Source # 
Data VkAttachmentLoadOp Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkAttachmentLoadOp -> c VkAttachmentLoadOp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkAttachmentLoadOp #

toConstr :: VkAttachmentLoadOp -> Constr #

dataTypeOf :: VkAttachmentLoadOp -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkAttachmentLoadOp) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkAttachmentLoadOp) #

gmapT :: (forall b. Data b => b -> b) -> VkAttachmentLoadOp -> VkAttachmentLoadOp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkAttachmentLoadOp -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkAttachmentLoadOp -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkAttachmentLoadOp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkAttachmentLoadOp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkAttachmentLoadOp -> m VkAttachmentLoadOp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkAttachmentLoadOp -> m VkAttachmentLoadOp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkAttachmentLoadOp -> m VkAttachmentLoadOp #

Num VkAttachmentLoadOp Source # 
Ord VkAttachmentLoadOp Source # 
Read VkAttachmentLoadOp Source # 
Show VkAttachmentLoadOp Source # 
Generic VkAttachmentLoadOp Source # 
Storable VkAttachmentLoadOp Source # 
type Rep VkAttachmentLoadOp Source # 
type Rep VkAttachmentLoadOp = D1 (MetaData "VkAttachmentLoadOp" "Graphics.Vulkan.Types.Enum.Attachment" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkAttachmentLoadOp" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

newtype VkAttachmentStoreOp Source #

Instances

Bounded VkAttachmentStoreOp Source # 
Enum VkAttachmentStoreOp Source # 
Eq VkAttachmentStoreOp Source # 
Data VkAttachmentStoreOp Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkAttachmentStoreOp -> c VkAttachmentStoreOp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkAttachmentStoreOp #

toConstr :: VkAttachmentStoreOp -> Constr #

dataTypeOf :: VkAttachmentStoreOp -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkAttachmentStoreOp) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkAttachmentStoreOp) #

gmapT :: (forall b. Data b => b -> b) -> VkAttachmentStoreOp -> VkAttachmentStoreOp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkAttachmentStoreOp -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkAttachmentStoreOp -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkAttachmentStoreOp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkAttachmentStoreOp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkAttachmentStoreOp -> m VkAttachmentStoreOp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkAttachmentStoreOp -> m VkAttachmentStoreOp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkAttachmentStoreOp -> m VkAttachmentStoreOp #

Num VkAttachmentStoreOp Source # 
Ord VkAttachmentStoreOp Source # 
Read VkAttachmentStoreOp Source # 
Show VkAttachmentStoreOp Source # 
Generic VkAttachmentStoreOp Source # 
Storable VkAttachmentStoreOp Source # 
type Rep VkAttachmentStoreOp Source # 
type Rep VkAttachmentStoreOp = D1 (MetaData "VkAttachmentStoreOp" "Graphics.Vulkan.Types.Enum.Attachment" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkAttachmentStoreOp" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

data VkComponentMapping Source #

typedef struct VkComponentMapping {
    VkComponentSwizzle r;
    VkComponentSwizzle g;
    VkComponentSwizzle b;
    VkComponentSwizzle a;
} VkComponentMapping;

VkComponentMapping registry at www.khronos.org

Instances

Eq VkComponentMapping Source # 
Ord VkComponentMapping Source # 
Show VkComponentMapping Source # 
Storable VkComponentMapping Source # 
VulkanMarshalPrim VkComponentMapping Source # 
VulkanMarshal VkComponentMapping Source # 
CanWriteField "a" VkComponentMapping Source # 
CanWriteField "b" VkComponentMapping Source # 
CanWriteField "g" VkComponentMapping Source # 
CanWriteField "r" VkComponentMapping Source # 
CanReadField "a" VkComponentMapping Source # 
CanReadField "b" VkComponentMapping Source # 
CanReadField "g" VkComponentMapping Source # 
CanReadField "r" VkComponentMapping Source # 
HasField "a" VkComponentMapping Source # 
HasField "b" VkComponentMapping Source # 
HasField "g" VkComponentMapping Source # 
HasField "r" VkComponentMapping Source # 
type StructFields VkComponentMapping Source # 
type StructFields VkComponentMapping = (:) Symbol "r" ((:) Symbol "g" ((:) Symbol "b" ((:) Symbol "a" ([] Symbol))))
type CUnionType VkComponentMapping Source # 
type ReturnedOnly VkComponentMapping Source # 
type StructExtends VkComponentMapping Source # 
type FieldType "a" VkComponentMapping Source # 
type FieldType "b" VkComponentMapping Source # 
type FieldType "g" VkComponentMapping Source # 
type FieldType "r" VkComponentMapping Source # 
type FieldOptional "a" VkComponentMapping Source # 
type FieldOptional "b" VkComponentMapping Source # 
type FieldOptional "g" VkComponentMapping Source # 
type FieldOptional "r" VkComponentMapping Source # 
type FieldOffset "a" VkComponentMapping Source # 
type FieldOffset "b" VkComponentMapping Source # 
type FieldOffset "g" VkComponentMapping Source # 
type FieldOffset "r" VkComponentMapping Source # 
type FieldIsArray "a" VkComponentMapping Source # 
type FieldIsArray "b" VkComponentMapping Source # 
type FieldIsArray "g" VkComponentMapping Source # 
type FieldIsArray "r" VkComponentMapping Source # 

newtype VkComponentSwizzle Source #

Instances

Bounded VkComponentSwizzle Source # 
Enum VkComponentSwizzle Source # 
Eq VkComponentSwizzle Source # 
Data VkComponentSwizzle Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkComponentSwizzle -> c VkComponentSwizzle #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkComponentSwizzle #

toConstr :: VkComponentSwizzle -> Constr #

dataTypeOf :: VkComponentSwizzle -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkComponentSwizzle) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkComponentSwizzle) #

gmapT :: (forall b. Data b => b -> b) -> VkComponentSwizzle -> VkComponentSwizzle #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkComponentSwizzle -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkComponentSwizzle -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkComponentSwizzle -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkComponentSwizzle -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkComponentSwizzle -> m VkComponentSwizzle #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkComponentSwizzle -> m VkComponentSwizzle #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkComponentSwizzle -> m VkComponentSwizzle #

Num VkComponentSwizzle Source # 
Ord VkComponentSwizzle Source # 
Read VkComponentSwizzle Source # 
Show VkComponentSwizzle Source # 
Generic VkComponentSwizzle Source # 
Storable VkComponentSwizzle Source # 
type Rep VkComponentSwizzle Source # 
type Rep VkComponentSwizzle = D1 (MetaData "VkComponentSwizzle" "Graphics.Vulkan.Types.Enum.ComponentSwizzle" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkComponentSwizzle" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

newtype VkDependencyBitmask a Source #

Instances

Bounded (VkDependencyBitmask FlagMask) Source # 
Enum (VkDependencyBitmask FlagMask) Source # 
Eq (VkDependencyBitmask a) Source # 
Integral (VkDependencyBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkDependencyBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkDependencyBitmask a -> c (VkDependencyBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkDependencyBitmask a) #

toConstr :: VkDependencyBitmask a -> Constr #

dataTypeOf :: VkDependencyBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkDependencyBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkDependencyBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkDependencyBitmask a -> VkDependencyBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkDependencyBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkDependencyBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkDependencyBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkDependencyBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkDependencyBitmask a -> m (VkDependencyBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkDependencyBitmask a -> m (VkDependencyBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkDependencyBitmask a -> m (VkDependencyBitmask a) #

Num (VkDependencyBitmask FlagMask) Source # 
Ord (VkDependencyBitmask a) Source # 
Read (VkDependencyBitmask a) Source # 
Real (VkDependencyBitmask FlagMask) Source # 
Show (VkDependencyBitmask a) Source # 
Generic (VkDependencyBitmask a) Source # 

Associated Types

type Rep (VkDependencyBitmask a) :: * -> * #

Storable (VkDependencyBitmask a) Source # 
Bits (VkDependencyBitmask FlagMask) Source # 

Methods

(.&.) :: VkDependencyBitmask FlagMask -> VkDependencyBitmask FlagMask -> VkDependencyBitmask FlagMask #

(.|.) :: VkDependencyBitmask FlagMask -> VkDependencyBitmask FlagMask -> VkDependencyBitmask FlagMask #

xor :: VkDependencyBitmask FlagMask -> VkDependencyBitmask FlagMask -> VkDependencyBitmask FlagMask #

complement :: VkDependencyBitmask FlagMask -> VkDependencyBitmask FlagMask #

shift :: VkDependencyBitmask FlagMask -> Int -> VkDependencyBitmask FlagMask #

rotate :: VkDependencyBitmask FlagMask -> Int -> VkDependencyBitmask FlagMask #

zeroBits :: VkDependencyBitmask FlagMask #

bit :: Int -> VkDependencyBitmask FlagMask #

setBit :: VkDependencyBitmask FlagMask -> Int -> VkDependencyBitmask FlagMask #

clearBit :: VkDependencyBitmask FlagMask -> Int -> VkDependencyBitmask FlagMask #

complementBit :: VkDependencyBitmask FlagMask -> Int -> VkDependencyBitmask FlagMask #

testBit :: VkDependencyBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkDependencyBitmask FlagMask -> Maybe Int #

bitSize :: VkDependencyBitmask FlagMask -> Int #

isSigned :: VkDependencyBitmask FlagMask -> Bool #

shiftL :: VkDependencyBitmask FlagMask -> Int -> VkDependencyBitmask FlagMask #

unsafeShiftL :: VkDependencyBitmask FlagMask -> Int -> VkDependencyBitmask FlagMask #

shiftR :: VkDependencyBitmask FlagMask -> Int -> VkDependencyBitmask FlagMask #

unsafeShiftR :: VkDependencyBitmask FlagMask -> Int -> VkDependencyBitmask FlagMask #

rotateL :: VkDependencyBitmask FlagMask -> Int -> VkDependencyBitmask FlagMask #

rotateR :: VkDependencyBitmask FlagMask -> Int -> VkDependencyBitmask FlagMask #

popCount :: VkDependencyBitmask FlagMask -> Int #

FiniteBits (VkDependencyBitmask FlagMask) Source # 
type Rep (VkDependencyBitmask a) Source # 
type Rep (VkDependencyBitmask a) = D1 (MetaData "VkDependencyBitmask" "Graphics.Vulkan.Types.Enum.DependencyFlags" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkDependencyBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

pattern VK_DEPENDENCY_BY_REGION_BIT :: forall a. VkDependencyBitmask a Source #

Dependency is per pixel region

bitpos = 0

data VkInputAttachmentAspectReference Source #

typedef struct VkInputAttachmentAspectReference {
    uint32_t                        subpass;
    uint32_t                        inputAttachmentIndex;
    VkImageAspectFlags              aspectMask;
} VkInputAttachmentAspectReference;

VkInputAttachmentAspectReference registry at www.khronos.org

Instances

Eq VkInputAttachmentAspectReference Source # 
Ord VkInputAttachmentAspectReference Source # 
Show VkInputAttachmentAspectReference Source # 
Storable VkInputAttachmentAspectReference Source # 
VulkanMarshalPrim VkInputAttachmentAspectReference Source # 
VulkanMarshal VkInputAttachmentAspectReference Source # 
CanWriteField "aspectMask" VkInputAttachmentAspectReference Source # 
CanWriteField "inputAttachmentIndex" VkInputAttachmentAspectReference Source # 
CanWriteField "subpass" VkInputAttachmentAspectReference Source # 
CanReadField "aspectMask" VkInputAttachmentAspectReference Source # 
CanReadField "inputAttachmentIndex" VkInputAttachmentAspectReference Source # 
CanReadField "subpass" VkInputAttachmentAspectReference Source # 
HasField "aspectMask" VkInputAttachmentAspectReference Source # 
HasField "inputAttachmentIndex" VkInputAttachmentAspectReference Source # 

Associated Types

type FieldType ("inputAttachmentIndex" :: Symbol) VkInputAttachmentAspectReference :: Type Source #

type FieldOptional ("inputAttachmentIndex" :: Symbol) VkInputAttachmentAspectReference :: Bool Source #

type FieldOffset ("inputAttachmentIndex" :: Symbol) VkInputAttachmentAspectReference :: Nat Source #

type FieldIsArray ("inputAttachmentIndex" :: Symbol) VkInputAttachmentAspectReference :: Bool Source #

HasField "subpass" VkInputAttachmentAspectReference Source # 
type StructFields VkInputAttachmentAspectReference Source # 
type StructFields VkInputAttachmentAspectReference = (:) Symbol "subpass" ((:) Symbol "inputAttachmentIndex" ((:) Symbol "aspectMask" ([] Symbol)))
type CUnionType VkInputAttachmentAspectReference Source # 
type ReturnedOnly VkInputAttachmentAspectReference Source # 
type StructExtends VkInputAttachmentAspectReference Source # 
type FieldType "aspectMask" VkInputAttachmentAspectReference Source # 
type FieldType "inputAttachmentIndex" VkInputAttachmentAspectReference Source # 
type FieldType "inputAttachmentIndex" VkInputAttachmentAspectReference = Word32
type FieldType "subpass" VkInputAttachmentAspectReference Source # 
type FieldOptional "aspectMask" VkInputAttachmentAspectReference Source # 
type FieldOptional "inputAttachmentIndex" VkInputAttachmentAspectReference Source # 
type FieldOptional "subpass" VkInputAttachmentAspectReference Source # 
type FieldOffset "aspectMask" VkInputAttachmentAspectReference Source # 
type FieldOffset "inputAttachmentIndex" VkInputAttachmentAspectReference Source # 
type FieldOffset "inputAttachmentIndex" VkInputAttachmentAspectReference = 4
type FieldOffset "subpass" VkInputAttachmentAspectReference Source # 
type FieldIsArray "aspectMask" VkInputAttachmentAspectReference Source # 
type FieldIsArray "inputAttachmentIndex" VkInputAttachmentAspectReference Source # 
type FieldIsArray "subpass" VkInputAttachmentAspectReference Source # 

data VkGraphicsPipelineCreateInfo Source #

typedef struct VkGraphicsPipelineCreateInfo {
    VkStructureType sType;
    const void*            pNext;
    VkPipelineCreateFlags  flags;
    uint32_t               stageCount;
    const VkPipelineShaderStageCreateInfo* pStages;
    const VkPipelineVertexInputStateCreateInfo* pVertexInputState;
    const VkPipelineInputAssemblyStateCreateInfo* pInputAssemblyState;
    const VkPipelineTessellationStateCreateInfo* pTessellationState;
    const VkPipelineViewportStateCreateInfo* pViewportState;
    const VkPipelineRasterizationStateCreateInfo* pRasterizationState;
    const VkPipelineMultisampleStateCreateInfo* pMultisampleState;
    const VkPipelineDepthStencilStateCreateInfo* pDepthStencilState;
    const VkPipelineColorBlendStateCreateInfo* pColorBlendState;
    const VkPipelineDynamicStateCreateInfo* pDynamicState;
    VkPipelineLayout       layout;
    VkRenderPass           renderPass;
    uint32_t               subpass;
    VkPipeline      basePipelineHandle;
    int32_t                basePipelineIndex;
} VkGraphicsPipelineCreateInfo;

VkGraphicsPipelineCreateInfo registry at www.khronos.org

Instances

Eq VkGraphicsPipelineCreateInfo Source # 
Ord VkGraphicsPipelineCreateInfo Source # 
Show VkGraphicsPipelineCreateInfo Source # 
Storable VkGraphicsPipelineCreateInfo Source # 
VulkanMarshalPrim VkGraphicsPipelineCreateInfo Source # 
VulkanMarshal VkGraphicsPipelineCreateInfo Source # 
CanWriteField "basePipelineHandle" VkGraphicsPipelineCreateInfo Source # 
CanWriteField "basePipelineIndex" VkGraphicsPipelineCreateInfo Source # 
CanWriteField "flags" VkGraphicsPipelineCreateInfo Source # 
CanWriteField "layout" VkGraphicsPipelineCreateInfo Source # 
CanWriteField "pColorBlendState" VkGraphicsPipelineCreateInfo Source # 
CanWriteField "pDepthStencilState" VkGraphicsPipelineCreateInfo Source # 
CanWriteField "pDynamicState" VkGraphicsPipelineCreateInfo Source # 
CanWriteField "pInputAssemblyState" VkGraphicsPipelineCreateInfo Source # 
CanWriteField "pMultisampleState" VkGraphicsPipelineCreateInfo Source # 
CanWriteField "pNext" VkGraphicsPipelineCreateInfo Source # 
CanWriteField "pRasterizationState" VkGraphicsPipelineCreateInfo Source # 
CanWriteField "pStages" VkGraphicsPipelineCreateInfo Source # 
CanWriteField "pTessellationState" VkGraphicsPipelineCreateInfo Source # 
CanWriteField "pVertexInputState" VkGraphicsPipelineCreateInfo Source # 
CanWriteField "pViewportState" VkGraphicsPipelineCreateInfo Source # 
CanWriteField "renderPass" VkGraphicsPipelineCreateInfo Source # 
CanWriteField "sType" VkGraphicsPipelineCreateInfo Source # 
CanWriteField "stageCount" VkGraphicsPipelineCreateInfo Source # 
CanWriteField "subpass" VkGraphicsPipelineCreateInfo Source # 
CanReadField "basePipelineHandle" VkGraphicsPipelineCreateInfo Source # 
CanReadField "basePipelineIndex" VkGraphicsPipelineCreateInfo Source # 
CanReadField "flags" VkGraphicsPipelineCreateInfo Source # 
CanReadField "layout" VkGraphicsPipelineCreateInfo Source # 
CanReadField "pColorBlendState" VkGraphicsPipelineCreateInfo Source # 
CanReadField "pDepthStencilState" VkGraphicsPipelineCreateInfo Source # 
CanReadField "pDynamicState" VkGraphicsPipelineCreateInfo Source # 
CanReadField "pInputAssemblyState" VkGraphicsPipelineCreateInfo Source # 
CanReadField "pMultisampleState" VkGraphicsPipelineCreateInfo Source # 
CanReadField "pNext" VkGraphicsPipelineCreateInfo Source # 
CanReadField "pRasterizationState" VkGraphicsPipelineCreateInfo Source # 
CanReadField "pStages" VkGraphicsPipelineCreateInfo Source # 
CanReadField "pTessellationState" VkGraphicsPipelineCreateInfo Source # 
CanReadField "pVertexInputState" VkGraphicsPipelineCreateInfo Source # 
CanReadField "pViewportState" VkGraphicsPipelineCreateInfo Source # 
CanReadField "renderPass" VkGraphicsPipelineCreateInfo Source # 
CanReadField "sType" VkGraphicsPipelineCreateInfo Source # 
CanReadField "stageCount" VkGraphicsPipelineCreateInfo Source # 
CanReadField "subpass" VkGraphicsPipelineCreateInfo Source # 
HasField "basePipelineHandle" VkGraphicsPipelineCreateInfo Source # 

Associated Types

type FieldType ("basePipelineHandle" :: Symbol) VkGraphicsPipelineCreateInfo :: Type Source #

type FieldOptional ("basePipelineHandle" :: Symbol) VkGraphicsPipelineCreateInfo :: Bool Source #

type FieldOffset ("basePipelineHandle" :: Symbol) VkGraphicsPipelineCreateInfo :: Nat Source #

type FieldIsArray ("basePipelineHandle" :: Symbol) VkGraphicsPipelineCreateInfo :: Bool Source #

HasField "basePipelineIndex" VkGraphicsPipelineCreateInfo Source # 

Associated Types

type FieldType ("basePipelineIndex" :: Symbol) VkGraphicsPipelineCreateInfo :: Type Source #

type FieldOptional ("basePipelineIndex" :: Symbol) VkGraphicsPipelineCreateInfo :: Bool Source #

type FieldOffset ("basePipelineIndex" :: Symbol) VkGraphicsPipelineCreateInfo :: Nat Source #

type FieldIsArray ("basePipelineIndex" :: Symbol) VkGraphicsPipelineCreateInfo :: Bool Source #

HasField "flags" VkGraphicsPipelineCreateInfo Source # 
HasField "layout" VkGraphicsPipelineCreateInfo Source # 
HasField "pColorBlendState" VkGraphicsPipelineCreateInfo Source # 

Associated Types

type FieldType ("pColorBlendState" :: Symbol) VkGraphicsPipelineCreateInfo :: Type Source #

type FieldOptional ("pColorBlendState" :: Symbol) VkGraphicsPipelineCreateInfo :: Bool Source #

type FieldOffset ("pColorBlendState" :: Symbol) VkGraphicsPipelineCreateInfo :: Nat Source #

type FieldIsArray ("pColorBlendState" :: Symbol) VkGraphicsPipelineCreateInfo :: Bool Source #

HasField "pDepthStencilState" VkGraphicsPipelineCreateInfo Source # 

Associated Types

type FieldType ("pDepthStencilState" :: Symbol) VkGraphicsPipelineCreateInfo :: Type Source #

type FieldOptional ("pDepthStencilState" :: Symbol) VkGraphicsPipelineCreateInfo :: Bool Source #

type FieldOffset ("pDepthStencilState" :: Symbol) VkGraphicsPipelineCreateInfo :: Nat Source #

type FieldIsArray ("pDepthStencilState" :: Symbol) VkGraphicsPipelineCreateInfo :: Bool Source #

HasField "pDynamicState" VkGraphicsPipelineCreateInfo Source # 
HasField "pInputAssemblyState" VkGraphicsPipelineCreateInfo Source # 

Associated Types

type FieldType ("pInputAssemblyState" :: Symbol) VkGraphicsPipelineCreateInfo :: Type Source #

type FieldOptional ("pInputAssemblyState" :: Symbol) VkGraphicsPipelineCreateInfo :: Bool Source #

type FieldOffset ("pInputAssemblyState" :: Symbol) VkGraphicsPipelineCreateInfo :: Nat Source #

type FieldIsArray ("pInputAssemblyState" :: Symbol) VkGraphicsPipelineCreateInfo :: Bool Source #

HasField "pMultisampleState" VkGraphicsPipelineCreateInfo Source # 

Associated Types

type FieldType ("pMultisampleState" :: Symbol) VkGraphicsPipelineCreateInfo :: Type Source #

type FieldOptional ("pMultisampleState" :: Symbol) VkGraphicsPipelineCreateInfo :: Bool Source #

type FieldOffset ("pMultisampleState" :: Symbol) VkGraphicsPipelineCreateInfo :: Nat Source #

type FieldIsArray ("pMultisampleState" :: Symbol) VkGraphicsPipelineCreateInfo :: Bool Source #

HasField "pNext" VkGraphicsPipelineCreateInfo Source # 
HasField "pRasterizationState" VkGraphicsPipelineCreateInfo Source # 

Associated Types

type FieldType ("pRasterizationState" :: Symbol) VkGraphicsPipelineCreateInfo :: Type Source #

type FieldOptional ("pRasterizationState" :: Symbol) VkGraphicsPipelineCreateInfo :: Bool Source #

type FieldOffset ("pRasterizationState" :: Symbol) VkGraphicsPipelineCreateInfo :: Nat Source #

type FieldIsArray ("pRasterizationState" :: Symbol) VkGraphicsPipelineCreateInfo :: Bool Source #

HasField "pStages" VkGraphicsPipelineCreateInfo Source # 
HasField "pTessellationState" VkGraphicsPipelineCreateInfo Source # 

Associated Types

type FieldType ("pTessellationState" :: Symbol) VkGraphicsPipelineCreateInfo :: Type Source #

type FieldOptional ("pTessellationState" :: Symbol) VkGraphicsPipelineCreateInfo :: Bool Source #

type FieldOffset ("pTessellationState" :: Symbol) VkGraphicsPipelineCreateInfo :: Nat Source #

type FieldIsArray ("pTessellationState" :: Symbol) VkGraphicsPipelineCreateInfo :: Bool Source #

HasField "pVertexInputState" VkGraphicsPipelineCreateInfo Source # 

Associated Types

type FieldType ("pVertexInputState" :: Symbol) VkGraphicsPipelineCreateInfo :: Type Source #

type FieldOptional ("pVertexInputState" :: Symbol) VkGraphicsPipelineCreateInfo :: Bool Source #

type FieldOffset ("pVertexInputState" :: Symbol) VkGraphicsPipelineCreateInfo :: Nat Source #

type FieldIsArray ("pVertexInputState" :: Symbol) VkGraphicsPipelineCreateInfo :: Bool Source #

HasField "pViewportState" VkGraphicsPipelineCreateInfo Source # 
HasField "renderPass" VkGraphicsPipelineCreateInfo Source # 
HasField "sType" VkGraphicsPipelineCreateInfo Source # 
HasField "stageCount" VkGraphicsPipelineCreateInfo Source # 
HasField "subpass" VkGraphicsPipelineCreateInfo Source # 
type StructFields VkGraphicsPipelineCreateInfo Source # 
type StructFields VkGraphicsPipelineCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "stageCount" ((:) Symbol "pStages" ((:) Symbol "pVertexInputState" ((:) Symbol "pInputAssemblyState" ((:) Symbol "pTessellationState" ((:) Symbol "pViewportState" ((:) Symbol "pRasterizationState" ((:) Symbol "pMultisampleState" ((:) Symbol "pDepthStencilState" ((:) Symbol "pColorBlendState" ((:) Symbol "pDynamicState" ((:) Symbol "layout" ((:) Symbol "renderPass" ((:) Symbol "subpass" ((:) Symbol "basePipelineHandle" ((:) Symbol "basePipelineIndex" ([] Symbol)))))))))))))))))))
type CUnionType VkGraphicsPipelineCreateInfo Source # 
type ReturnedOnly VkGraphicsPipelineCreateInfo Source # 
type StructExtends VkGraphicsPipelineCreateInfo Source # 
type FieldType "basePipelineHandle" VkGraphicsPipelineCreateInfo Source # 
type FieldType "basePipelineIndex" VkGraphicsPipelineCreateInfo Source # 
type FieldType "basePipelineIndex" VkGraphicsPipelineCreateInfo = Int32
type FieldType "flags" VkGraphicsPipelineCreateInfo Source # 
type FieldType "layout" VkGraphicsPipelineCreateInfo Source # 
type FieldType "pColorBlendState" VkGraphicsPipelineCreateInfo Source # 
type FieldType "pDepthStencilState" VkGraphicsPipelineCreateInfo Source # 
type FieldType "pDynamicState" VkGraphicsPipelineCreateInfo Source # 
type FieldType "pInputAssemblyState" VkGraphicsPipelineCreateInfo Source # 
type FieldType "pMultisampleState" VkGraphicsPipelineCreateInfo Source # 
type FieldType "pNext" VkGraphicsPipelineCreateInfo Source # 
type FieldType "pRasterizationState" VkGraphicsPipelineCreateInfo Source # 
type FieldType "pStages" VkGraphicsPipelineCreateInfo Source # 
type FieldType "pTessellationState" VkGraphicsPipelineCreateInfo Source # 
type FieldType "pVertexInputState" VkGraphicsPipelineCreateInfo Source # 
type FieldType "pViewportState" VkGraphicsPipelineCreateInfo Source # 
type FieldType "renderPass" VkGraphicsPipelineCreateInfo Source # 
type FieldType "sType" VkGraphicsPipelineCreateInfo Source # 
type FieldType "stageCount" VkGraphicsPipelineCreateInfo Source # 
type FieldType "subpass" VkGraphicsPipelineCreateInfo Source # 
type FieldOptional "basePipelineHandle" VkGraphicsPipelineCreateInfo Source # 
type FieldOptional "basePipelineHandle" VkGraphicsPipelineCreateInfo = True
type FieldOptional "basePipelineIndex" VkGraphicsPipelineCreateInfo Source # 
type FieldOptional "flags" VkGraphicsPipelineCreateInfo Source # 
type FieldOptional "layout" VkGraphicsPipelineCreateInfo Source # 
type FieldOptional "pColorBlendState" VkGraphicsPipelineCreateInfo Source # 
type FieldOptional "pDepthStencilState" VkGraphicsPipelineCreateInfo Source # 
type FieldOptional "pDepthStencilState" VkGraphicsPipelineCreateInfo = True
type FieldOptional "pDynamicState" VkGraphicsPipelineCreateInfo Source # 
type FieldOptional "pInputAssemblyState" VkGraphicsPipelineCreateInfo Source # 
type FieldOptional "pInputAssemblyState" VkGraphicsPipelineCreateInfo = False
type FieldOptional "pMultisampleState" VkGraphicsPipelineCreateInfo Source # 
type FieldOptional "pNext" VkGraphicsPipelineCreateInfo Source # 
type FieldOptional "pRasterizationState" VkGraphicsPipelineCreateInfo Source # 
type FieldOptional "pRasterizationState" VkGraphicsPipelineCreateInfo = False
type FieldOptional "pStages" VkGraphicsPipelineCreateInfo Source # 
type FieldOptional "pTessellationState" VkGraphicsPipelineCreateInfo Source # 
type FieldOptional "pTessellationState" VkGraphicsPipelineCreateInfo = True
type FieldOptional "pVertexInputState" VkGraphicsPipelineCreateInfo Source # 
type FieldOptional "pViewportState" VkGraphicsPipelineCreateInfo Source # 
type FieldOptional "renderPass" VkGraphicsPipelineCreateInfo Source # 
type FieldOptional "sType" VkGraphicsPipelineCreateInfo Source # 
type FieldOptional "stageCount" VkGraphicsPipelineCreateInfo Source # 
type FieldOptional "subpass" VkGraphicsPipelineCreateInfo Source # 
type FieldOffset "basePipelineHandle" VkGraphicsPipelineCreateInfo Source # 
type FieldOffset "basePipelineHandle" VkGraphicsPipelineCreateInfo = 128
type FieldOffset "basePipelineIndex" VkGraphicsPipelineCreateInfo Source # 
type FieldOffset "basePipelineIndex" VkGraphicsPipelineCreateInfo = 136
type FieldOffset "flags" VkGraphicsPipelineCreateInfo Source # 
type FieldOffset "layout" VkGraphicsPipelineCreateInfo Source # 
type FieldOffset "pColorBlendState" VkGraphicsPipelineCreateInfo Source # 
type FieldOffset "pColorBlendState" VkGraphicsPipelineCreateInfo = 88
type FieldOffset "pDepthStencilState" VkGraphicsPipelineCreateInfo Source # 
type FieldOffset "pDepthStencilState" VkGraphicsPipelineCreateInfo = 80
type FieldOffset "pDynamicState" VkGraphicsPipelineCreateInfo Source # 
type FieldOffset "pDynamicState" VkGraphicsPipelineCreateInfo = 96
type FieldOffset "pInputAssemblyState" VkGraphicsPipelineCreateInfo Source # 
type FieldOffset "pInputAssemblyState" VkGraphicsPipelineCreateInfo = 40
type FieldOffset "pMultisampleState" VkGraphicsPipelineCreateInfo Source # 
type FieldOffset "pMultisampleState" VkGraphicsPipelineCreateInfo = 72
type FieldOffset "pNext" VkGraphicsPipelineCreateInfo Source # 
type FieldOffset "pRasterizationState" VkGraphicsPipelineCreateInfo Source # 
type FieldOffset "pRasterizationState" VkGraphicsPipelineCreateInfo = 64
type FieldOffset "pStages" VkGraphicsPipelineCreateInfo Source # 
type FieldOffset "pTessellationState" VkGraphicsPipelineCreateInfo Source # 
type FieldOffset "pTessellationState" VkGraphicsPipelineCreateInfo = 48
type FieldOffset "pVertexInputState" VkGraphicsPipelineCreateInfo Source # 
type FieldOffset "pVertexInputState" VkGraphicsPipelineCreateInfo = 32
type FieldOffset "pViewportState" VkGraphicsPipelineCreateInfo Source # 
type FieldOffset "pViewportState" VkGraphicsPipelineCreateInfo = 56
type FieldOffset "renderPass" VkGraphicsPipelineCreateInfo Source # 
type FieldOffset "sType" VkGraphicsPipelineCreateInfo Source # 
type FieldOffset "stageCount" VkGraphicsPipelineCreateInfo Source # 
type FieldOffset "subpass" VkGraphicsPipelineCreateInfo Source # 
type FieldIsArray "basePipelineHandle" VkGraphicsPipelineCreateInfo Source # 
type FieldIsArray "basePipelineHandle" VkGraphicsPipelineCreateInfo = False
type FieldIsArray "basePipelineIndex" VkGraphicsPipelineCreateInfo Source # 
type FieldIsArray "flags" VkGraphicsPipelineCreateInfo Source # 
type FieldIsArray "layout" VkGraphicsPipelineCreateInfo Source # 
type FieldIsArray "pColorBlendState" VkGraphicsPipelineCreateInfo Source # 
type FieldIsArray "pDepthStencilState" VkGraphicsPipelineCreateInfo Source # 
type FieldIsArray "pDepthStencilState" VkGraphicsPipelineCreateInfo = False
type FieldIsArray "pDynamicState" VkGraphicsPipelineCreateInfo Source # 
type FieldIsArray "pInputAssemblyState" VkGraphicsPipelineCreateInfo Source # 
type FieldIsArray "pInputAssemblyState" VkGraphicsPipelineCreateInfo = False
type FieldIsArray "pMultisampleState" VkGraphicsPipelineCreateInfo Source # 
type FieldIsArray "pNext" VkGraphicsPipelineCreateInfo Source # 
type FieldIsArray "pRasterizationState" VkGraphicsPipelineCreateInfo Source # 
type FieldIsArray "pRasterizationState" VkGraphicsPipelineCreateInfo = False
type FieldIsArray "pStages" VkGraphicsPipelineCreateInfo Source # 
type FieldIsArray "pTessellationState" VkGraphicsPipelineCreateInfo Source # 
type FieldIsArray "pTessellationState" VkGraphicsPipelineCreateInfo = False
type FieldIsArray "pVertexInputState" VkGraphicsPipelineCreateInfo Source # 
type FieldIsArray "pViewportState" VkGraphicsPipelineCreateInfo Source # 
type FieldIsArray "renderPass" VkGraphicsPipelineCreateInfo Source # 
type FieldIsArray "sType" VkGraphicsPipelineCreateInfo Source # 
type FieldIsArray "stageCount" VkGraphicsPipelineCreateInfo Source # 
type FieldIsArray "subpass" VkGraphicsPipelineCreateInfo Source # 

data VkPipelineCacheCreateInfo Source #

typedef struct VkPipelineCacheCreateInfo {
    VkStructureType sType;
    const void*            pNext;
    VkPipelineCacheCreateFlags    flags;
    size_t                 initialDataSize;
    const void*            pInitialData;
} VkPipelineCacheCreateInfo;

VkPipelineCacheCreateInfo registry at www.khronos.org

Instances

Eq VkPipelineCacheCreateInfo Source # 
Ord VkPipelineCacheCreateInfo Source # 
Show VkPipelineCacheCreateInfo Source # 
Storable VkPipelineCacheCreateInfo Source # 
VulkanMarshalPrim VkPipelineCacheCreateInfo Source # 
VulkanMarshal VkPipelineCacheCreateInfo Source # 
CanWriteField "flags" VkPipelineCacheCreateInfo Source # 
CanWriteField "initialDataSize" VkPipelineCacheCreateInfo Source # 
CanWriteField "pInitialData" VkPipelineCacheCreateInfo Source # 
CanWriteField "pNext" VkPipelineCacheCreateInfo Source # 
CanWriteField "sType" VkPipelineCacheCreateInfo Source # 
CanReadField "flags" VkPipelineCacheCreateInfo Source # 
CanReadField "initialDataSize" VkPipelineCacheCreateInfo Source # 
CanReadField "pInitialData" VkPipelineCacheCreateInfo Source # 
CanReadField "pNext" VkPipelineCacheCreateInfo Source # 
CanReadField "sType" VkPipelineCacheCreateInfo Source # 
HasField "flags" VkPipelineCacheCreateInfo Source # 
HasField "initialDataSize" VkPipelineCacheCreateInfo Source # 

Associated Types

type FieldType ("initialDataSize" :: Symbol) VkPipelineCacheCreateInfo :: Type Source #

type FieldOptional ("initialDataSize" :: Symbol) VkPipelineCacheCreateInfo :: Bool Source #

type FieldOffset ("initialDataSize" :: Symbol) VkPipelineCacheCreateInfo :: Nat Source #

type FieldIsArray ("initialDataSize" :: Symbol) VkPipelineCacheCreateInfo :: Bool Source #

HasField "pInitialData" VkPipelineCacheCreateInfo Source # 
HasField "pNext" VkPipelineCacheCreateInfo Source # 
HasField "sType" VkPipelineCacheCreateInfo Source # 
type StructFields VkPipelineCacheCreateInfo Source # 
type StructFields VkPipelineCacheCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "initialDataSize" ((:) Symbol "pInitialData" ([] Symbol)))))
type CUnionType VkPipelineCacheCreateInfo Source # 
type ReturnedOnly VkPipelineCacheCreateInfo Source # 
type StructExtends VkPipelineCacheCreateInfo Source # 
type FieldType "flags" VkPipelineCacheCreateInfo Source # 
type FieldType "initialDataSize" VkPipelineCacheCreateInfo Source # 
type FieldType "initialDataSize" VkPipelineCacheCreateInfo = CSize
type FieldType "pInitialData" VkPipelineCacheCreateInfo Source # 
type FieldType "pNext" VkPipelineCacheCreateInfo Source # 
type FieldType "sType" VkPipelineCacheCreateInfo Source # 
type FieldOptional "flags" VkPipelineCacheCreateInfo Source # 
type FieldOptional "initialDataSize" VkPipelineCacheCreateInfo Source # 
type FieldOptional "pInitialData" VkPipelineCacheCreateInfo Source # 
type FieldOptional "pNext" VkPipelineCacheCreateInfo Source # 
type FieldOptional "sType" VkPipelineCacheCreateInfo Source # 
type FieldOffset "flags" VkPipelineCacheCreateInfo Source # 
type FieldOffset "initialDataSize" VkPipelineCacheCreateInfo Source # 
type FieldOffset "initialDataSize" VkPipelineCacheCreateInfo = 24
type FieldOffset "pInitialData" VkPipelineCacheCreateInfo Source # 
type FieldOffset "pInitialData" VkPipelineCacheCreateInfo = 32
type FieldOffset "pNext" VkPipelineCacheCreateInfo Source # 
type FieldOffset "sType" VkPipelineCacheCreateInfo Source # 
type FieldIsArray "flags" VkPipelineCacheCreateInfo Source # 
type FieldIsArray "initialDataSize" VkPipelineCacheCreateInfo Source # 
type FieldIsArray "pInitialData" VkPipelineCacheCreateInfo Source # 
type FieldIsArray "pNext" VkPipelineCacheCreateInfo Source # 
type FieldIsArray "sType" VkPipelineCacheCreateInfo Source # 

data VkPipelineColorBlendAdvancedStateCreateInfoEXT Source #

typedef struct VkPipelineColorBlendAdvancedStateCreateInfoEXT {
    VkStructureType sType;
    const void*            pNext;
    VkBool32               srcPremultiplied;
    VkBool32               dstPremultiplied;
    VkBlendOverlapEXT      blendOverlap;
} VkPipelineColorBlendAdvancedStateCreateInfoEXT;

VkPipelineColorBlendAdvancedStateCreateInfoEXT registry at www.khronos.org

Instances

Eq VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
Ord VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
Show VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
Storable VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
VulkanMarshalPrim VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
VulkanMarshal VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
CanWriteField "blendOverlap" VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
CanWriteField "dstPremultiplied" VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
CanWriteField "pNext" VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
CanWriteField "sType" VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
CanWriteField "srcPremultiplied" VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
CanReadField "blendOverlap" VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
CanReadField "dstPremultiplied" VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
CanReadField "pNext" VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
CanReadField "sType" VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
CanReadField "srcPremultiplied" VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
HasField "blendOverlap" VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
HasField "dstPremultiplied" VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
HasField "pNext" VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
HasField "sType" VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
HasField "srcPremultiplied" VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
type StructFields VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
type StructFields VkPipelineColorBlendAdvancedStateCreateInfoEXT = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "srcPremultiplied" ((:) Symbol "dstPremultiplied" ((:) Symbol "blendOverlap" ([] Symbol)))))
type CUnionType VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
type ReturnedOnly VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
type StructExtends VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
type FieldType "blendOverlap" VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
type FieldType "dstPremultiplied" VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
type FieldType "pNext" VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
type FieldType "sType" VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
type FieldType "srcPremultiplied" VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
type FieldOptional "blendOverlap" VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
type FieldOptional "dstPremultiplied" VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
type FieldOptional "pNext" VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
type FieldOptional "sType" VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
type FieldOptional "srcPremultiplied" VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
type FieldOffset "blendOverlap" VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
type FieldOffset "dstPremultiplied" VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
type FieldOffset "pNext" VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
type FieldOffset "sType" VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
type FieldOffset "srcPremultiplied" VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
type FieldIsArray "blendOverlap" VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
type FieldIsArray "dstPremultiplied" VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
type FieldIsArray "pNext" VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
type FieldIsArray "sType" VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 
type FieldIsArray "srcPremultiplied" VkPipelineColorBlendAdvancedStateCreateInfoEXT Source # 

data VkPipelineColorBlendAttachmentState Source #

typedef struct VkPipelineColorBlendAttachmentState {
    VkBool32               blendEnable;
    VkBlendFactor          srcColorBlendFactor;
    VkBlendFactor          dstColorBlendFactor;
    VkBlendOp              colorBlendOp;
    VkBlendFactor          srcAlphaBlendFactor;
    VkBlendFactor          dstAlphaBlendFactor;
    VkBlendOp              alphaBlendOp;
    VkColorComponentFlags  colorWriteMask;
} VkPipelineColorBlendAttachmentState;

VkPipelineColorBlendAttachmentState registry at www.khronos.org

Instances

Eq VkPipelineColorBlendAttachmentState Source # 
Ord VkPipelineColorBlendAttachmentState Source # 
Show VkPipelineColorBlendAttachmentState Source # 
Storable VkPipelineColorBlendAttachmentState Source # 
VulkanMarshalPrim VkPipelineColorBlendAttachmentState Source # 
VulkanMarshal VkPipelineColorBlendAttachmentState Source # 
CanWriteField "alphaBlendOp" VkPipelineColorBlendAttachmentState Source # 
CanWriteField "blendEnable" VkPipelineColorBlendAttachmentState Source # 
CanWriteField "colorBlendOp" VkPipelineColorBlendAttachmentState Source # 
CanWriteField "colorWriteMask" VkPipelineColorBlendAttachmentState Source # 
CanWriteField "dstAlphaBlendFactor" VkPipelineColorBlendAttachmentState Source # 
CanWriteField "dstColorBlendFactor" VkPipelineColorBlendAttachmentState Source # 
CanWriteField "srcAlphaBlendFactor" VkPipelineColorBlendAttachmentState Source # 
CanWriteField "srcColorBlendFactor" VkPipelineColorBlendAttachmentState Source # 
CanReadField "alphaBlendOp" VkPipelineColorBlendAttachmentState Source # 
CanReadField "blendEnable" VkPipelineColorBlendAttachmentState Source # 
CanReadField "colorBlendOp" VkPipelineColorBlendAttachmentState Source # 
CanReadField "colorWriteMask" VkPipelineColorBlendAttachmentState Source # 
CanReadField "dstAlphaBlendFactor" VkPipelineColorBlendAttachmentState Source # 
CanReadField "dstColorBlendFactor" VkPipelineColorBlendAttachmentState Source # 
CanReadField "srcAlphaBlendFactor" VkPipelineColorBlendAttachmentState Source # 
CanReadField "srcColorBlendFactor" VkPipelineColorBlendAttachmentState Source # 
HasField "alphaBlendOp" VkPipelineColorBlendAttachmentState Source # 
HasField "blendEnable" VkPipelineColorBlendAttachmentState Source # 
HasField "colorBlendOp" VkPipelineColorBlendAttachmentState Source # 
HasField "colorWriteMask" VkPipelineColorBlendAttachmentState Source # 
HasField "dstAlphaBlendFactor" VkPipelineColorBlendAttachmentState Source # 
HasField "dstColorBlendFactor" VkPipelineColorBlendAttachmentState Source # 
HasField "srcAlphaBlendFactor" VkPipelineColorBlendAttachmentState Source # 
HasField "srcColorBlendFactor" VkPipelineColorBlendAttachmentState Source # 
type StructFields VkPipelineColorBlendAttachmentState Source # 
type StructFields VkPipelineColorBlendAttachmentState = (:) Symbol "blendEnable" ((:) Symbol "srcColorBlendFactor" ((:) Symbol "dstColorBlendFactor" ((:) Symbol "colorBlendOp" ((:) Symbol "srcAlphaBlendFactor" ((:) Symbol "dstAlphaBlendFactor" ((:) Symbol "alphaBlendOp" ((:) Symbol "colorWriteMask" ([] Symbol))))))))
type CUnionType VkPipelineColorBlendAttachmentState Source # 
type ReturnedOnly VkPipelineColorBlendAttachmentState Source # 
type StructExtends VkPipelineColorBlendAttachmentState Source # 
type FieldType "alphaBlendOp" VkPipelineColorBlendAttachmentState Source # 
type FieldType "blendEnable" VkPipelineColorBlendAttachmentState Source # 
type FieldType "colorBlendOp" VkPipelineColorBlendAttachmentState Source # 
type FieldType "colorWriteMask" VkPipelineColorBlendAttachmentState Source # 
type FieldType "dstAlphaBlendFactor" VkPipelineColorBlendAttachmentState Source # 
type FieldType "dstColorBlendFactor" VkPipelineColorBlendAttachmentState Source # 
type FieldType "srcAlphaBlendFactor" VkPipelineColorBlendAttachmentState Source # 
type FieldType "srcColorBlendFactor" VkPipelineColorBlendAttachmentState Source # 
type FieldOptional "alphaBlendOp" VkPipelineColorBlendAttachmentState Source # 
type FieldOptional "blendEnable" VkPipelineColorBlendAttachmentState Source # 
type FieldOptional "colorBlendOp" VkPipelineColorBlendAttachmentState Source # 
type FieldOptional "colorWriteMask" VkPipelineColorBlendAttachmentState Source # 
type FieldOptional "dstAlphaBlendFactor" VkPipelineColorBlendAttachmentState Source # 
type FieldOptional "dstColorBlendFactor" VkPipelineColorBlendAttachmentState Source # 
type FieldOptional "srcAlphaBlendFactor" VkPipelineColorBlendAttachmentState Source # 
type FieldOptional "srcColorBlendFactor" VkPipelineColorBlendAttachmentState Source # 
type FieldOffset "alphaBlendOp" VkPipelineColorBlendAttachmentState Source # 
type FieldOffset "blendEnable" VkPipelineColorBlendAttachmentState Source # 
type FieldOffset "colorBlendOp" VkPipelineColorBlendAttachmentState Source # 
type FieldOffset "colorWriteMask" VkPipelineColorBlendAttachmentState Source # 
type FieldOffset "dstAlphaBlendFactor" VkPipelineColorBlendAttachmentState Source # 
type FieldOffset "dstAlphaBlendFactor" VkPipelineColorBlendAttachmentState = 20
type FieldOffset "dstColorBlendFactor" VkPipelineColorBlendAttachmentState Source # 
type FieldOffset "dstColorBlendFactor" VkPipelineColorBlendAttachmentState = 8
type FieldOffset "srcAlphaBlendFactor" VkPipelineColorBlendAttachmentState Source # 
type FieldOffset "srcAlphaBlendFactor" VkPipelineColorBlendAttachmentState = 16
type FieldOffset "srcColorBlendFactor" VkPipelineColorBlendAttachmentState Source # 
type FieldOffset "srcColorBlendFactor" VkPipelineColorBlendAttachmentState = 4
type FieldIsArray "alphaBlendOp" VkPipelineColorBlendAttachmentState Source # 
type FieldIsArray "blendEnable" VkPipelineColorBlendAttachmentState Source # 
type FieldIsArray "colorBlendOp" VkPipelineColorBlendAttachmentState Source # 
type FieldIsArray "colorWriteMask" VkPipelineColorBlendAttachmentState Source # 
type FieldIsArray "dstAlphaBlendFactor" VkPipelineColorBlendAttachmentState Source # 
type FieldIsArray "dstColorBlendFactor" VkPipelineColorBlendAttachmentState Source # 
type FieldIsArray "srcAlphaBlendFactor" VkPipelineColorBlendAttachmentState Source # 
type FieldIsArray "srcColorBlendFactor" VkPipelineColorBlendAttachmentState Source # 

data VkPipelineColorBlendStateCreateInfo Source #

typedef struct VkPipelineColorBlendStateCreateInfo {
    VkStructureType sType;
    const void*            pNext;
    VkPipelineColorBlendStateCreateFlags    flags;
    VkBool32               logicOpEnable;
    VkLogicOp              logicOp;
    uint32_t               attachmentCount;
    const VkPipelineColorBlendAttachmentState* pAttachments;
    float                  blendConstants[4];
} VkPipelineColorBlendStateCreateInfo;

VkPipelineColorBlendStateCreateInfo registry at www.khronos.org

Instances

Eq VkPipelineColorBlendStateCreateInfo Source # 
Ord VkPipelineColorBlendStateCreateInfo Source # 
Show VkPipelineColorBlendStateCreateInfo Source # 
Storable VkPipelineColorBlendStateCreateInfo Source # 
VulkanMarshalPrim VkPipelineColorBlendStateCreateInfo Source # 
VulkanMarshal VkPipelineColorBlendStateCreateInfo Source # 
CanWriteField "attachmentCount" VkPipelineColorBlendStateCreateInfo Source # 
CanWriteField "flags" VkPipelineColorBlendStateCreateInfo Source # 
CanWriteField "logicOp" VkPipelineColorBlendStateCreateInfo Source # 
CanWriteField "logicOpEnable" VkPipelineColorBlendStateCreateInfo Source # 
CanWriteField "pAttachments" VkPipelineColorBlendStateCreateInfo Source # 
CanWriteField "pNext" VkPipelineColorBlendStateCreateInfo Source # 
CanWriteField "sType" VkPipelineColorBlendStateCreateInfo Source # 
CanReadField "attachmentCount" VkPipelineColorBlendStateCreateInfo Source # 
CanReadField "flags" VkPipelineColorBlendStateCreateInfo Source # 
CanReadField "logicOp" VkPipelineColorBlendStateCreateInfo Source # 
CanReadField "logicOpEnable" VkPipelineColorBlendStateCreateInfo Source # 
CanReadField "pAttachments" VkPipelineColorBlendStateCreateInfo Source # 
CanReadField "pNext" VkPipelineColorBlendStateCreateInfo Source # 
CanReadField "sType" VkPipelineColorBlendStateCreateInfo Source # 
HasField "attachmentCount" VkPipelineColorBlendStateCreateInfo Source # 
HasField "blendConstants" VkPipelineColorBlendStateCreateInfo Source # 
HasField "flags" VkPipelineColorBlendStateCreateInfo Source # 
HasField "logicOp" VkPipelineColorBlendStateCreateInfo Source # 
HasField "logicOpEnable" VkPipelineColorBlendStateCreateInfo Source # 
HasField "pAttachments" VkPipelineColorBlendStateCreateInfo Source # 
HasField "pNext" VkPipelineColorBlendStateCreateInfo Source # 
HasField "sType" VkPipelineColorBlendStateCreateInfo Source # 
(KnownNat idx, IndexInBounds "blendConstants" idx VkPipelineColorBlendStateCreateInfo) => CanWriteFieldArray "blendConstants" idx VkPipelineColorBlendStateCreateInfo Source # 
(KnownNat idx, IndexInBounds "blendConstants" idx VkPipelineColorBlendStateCreateInfo) => CanReadFieldArray "blendConstants" idx VkPipelineColorBlendStateCreateInfo Source # 
type StructFields VkPipelineColorBlendStateCreateInfo Source # 
type StructFields VkPipelineColorBlendStateCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "logicOpEnable" ((:) Symbol "logicOp" ((:) Symbol "attachmentCount" ((:) Symbol "pAttachments" ((:) Symbol "blendConstants" ([] Symbol))))))))
type CUnionType VkPipelineColorBlendStateCreateInfo Source # 
type ReturnedOnly VkPipelineColorBlendStateCreateInfo Source # 
type StructExtends VkPipelineColorBlendStateCreateInfo Source # 
type FieldArrayLength "blendConstants" VkPipelineColorBlendStateCreateInfo Source # 
type FieldType "attachmentCount" VkPipelineColorBlendStateCreateInfo Source # 
type FieldType "blendConstants" VkPipelineColorBlendStateCreateInfo Source # 
type FieldType "flags" VkPipelineColorBlendStateCreateInfo Source # 
type FieldType "logicOp" VkPipelineColorBlendStateCreateInfo Source # 
type FieldType "logicOpEnable" VkPipelineColorBlendStateCreateInfo Source # 
type FieldType "pAttachments" VkPipelineColorBlendStateCreateInfo Source # 
type FieldType "pNext" VkPipelineColorBlendStateCreateInfo Source # 
type FieldType "sType" VkPipelineColorBlendStateCreateInfo Source # 
type FieldOptional "attachmentCount" VkPipelineColorBlendStateCreateInfo Source # 
type FieldOptional "blendConstants" VkPipelineColorBlendStateCreateInfo Source # 
type FieldOptional "flags" VkPipelineColorBlendStateCreateInfo Source # 
type FieldOptional "logicOp" VkPipelineColorBlendStateCreateInfo Source # 
type FieldOptional "logicOpEnable" VkPipelineColorBlendStateCreateInfo Source # 
type FieldOptional "pAttachments" VkPipelineColorBlendStateCreateInfo Source # 
type FieldOptional "pNext" VkPipelineColorBlendStateCreateInfo Source # 
type FieldOptional "sType" VkPipelineColorBlendStateCreateInfo Source # 
type FieldOffset "attachmentCount" VkPipelineColorBlendStateCreateInfo Source # 
type FieldOffset "blendConstants" VkPipelineColorBlendStateCreateInfo Source # 
type FieldOffset "flags" VkPipelineColorBlendStateCreateInfo Source # 
type FieldOffset "logicOp" VkPipelineColorBlendStateCreateInfo Source # 
type FieldOffset "logicOpEnable" VkPipelineColorBlendStateCreateInfo Source # 
type FieldOffset "pAttachments" VkPipelineColorBlendStateCreateInfo Source # 
type FieldOffset "pNext" VkPipelineColorBlendStateCreateInfo Source # 
type FieldOffset "sType" VkPipelineColorBlendStateCreateInfo Source # 
type FieldIsArray "attachmentCount" VkPipelineColorBlendStateCreateInfo Source # 
type FieldIsArray "blendConstants" VkPipelineColorBlendStateCreateInfo Source # 
type FieldIsArray "flags" VkPipelineColorBlendStateCreateInfo Source # 
type FieldIsArray "logicOp" VkPipelineColorBlendStateCreateInfo Source # 
type FieldIsArray "logicOpEnable" VkPipelineColorBlendStateCreateInfo Source # 
type FieldIsArray "pAttachments" VkPipelineColorBlendStateCreateInfo Source # 
type FieldIsArray "pNext" VkPipelineColorBlendStateCreateInfo Source # 
type FieldIsArray "sType" VkPipelineColorBlendStateCreateInfo Source # 

data VkPipelineCoverageModulationStateCreateInfoNV Source #

typedef struct VkPipelineCoverageModulationStateCreateInfoNV {
    VkStructureType sType;
    const void*                                                                      pNext;
    VkPipelineCoverageModulationStateCreateFlagsNV                   flags;
    VkCoverageModulationModeNV                                                       coverageModulationMode;
    VkBool32                                                                         coverageModulationTableEnable;
    uint32_t                                                                         coverageModulationTableCount;
    const float* pCoverageModulationTable;
} VkPipelineCoverageModulationStateCreateInfoNV;

VkPipelineCoverageModulationStateCreateInfoNV registry at www.khronos.org

Instances

Eq VkPipelineCoverageModulationStateCreateInfoNV Source # 
Ord VkPipelineCoverageModulationStateCreateInfoNV Source # 
Show VkPipelineCoverageModulationStateCreateInfoNV Source # 
Storable VkPipelineCoverageModulationStateCreateInfoNV Source # 
VulkanMarshalPrim VkPipelineCoverageModulationStateCreateInfoNV Source # 
VulkanMarshal VkPipelineCoverageModulationStateCreateInfoNV Source # 
CanWriteField "coverageModulationMode" VkPipelineCoverageModulationStateCreateInfoNV Source # 
CanWriteField "coverageModulationTableCount" VkPipelineCoverageModulationStateCreateInfoNV Source # 
CanWriteField "coverageModulationTableEnable" VkPipelineCoverageModulationStateCreateInfoNV Source # 
CanWriteField "flags" VkPipelineCoverageModulationStateCreateInfoNV Source # 
CanWriteField "pCoverageModulationTable" VkPipelineCoverageModulationStateCreateInfoNV Source # 
CanWriteField "pNext" VkPipelineCoverageModulationStateCreateInfoNV Source # 
CanWriteField "sType" VkPipelineCoverageModulationStateCreateInfoNV Source # 
CanReadField "coverageModulationMode" VkPipelineCoverageModulationStateCreateInfoNV Source # 
CanReadField "coverageModulationTableCount" VkPipelineCoverageModulationStateCreateInfoNV Source # 
CanReadField "coverageModulationTableEnable" VkPipelineCoverageModulationStateCreateInfoNV Source # 
CanReadField "flags" VkPipelineCoverageModulationStateCreateInfoNV Source # 
CanReadField "pCoverageModulationTable" VkPipelineCoverageModulationStateCreateInfoNV Source # 
CanReadField "pNext" VkPipelineCoverageModulationStateCreateInfoNV Source # 
CanReadField "sType" VkPipelineCoverageModulationStateCreateInfoNV Source # 
HasField "coverageModulationMode" VkPipelineCoverageModulationStateCreateInfoNV Source # 
HasField "coverageModulationTableCount" VkPipelineCoverageModulationStateCreateInfoNV Source # 

Associated Types

type FieldType ("coverageModulationTableCount" :: Symbol) VkPipelineCoverageModulationStateCreateInfoNV :: Type Source #

type FieldOptional ("coverageModulationTableCount" :: Symbol) VkPipelineCoverageModulationStateCreateInfoNV :: Bool Source #

type FieldOffset ("coverageModulationTableCount" :: Symbol) VkPipelineCoverageModulationStateCreateInfoNV :: Nat Source #

type FieldIsArray ("coverageModulationTableCount" :: Symbol) VkPipelineCoverageModulationStateCreateInfoNV :: Bool Source #

HasField "coverageModulationTableEnable" VkPipelineCoverageModulationStateCreateInfoNV Source # 

Associated Types

type FieldType ("coverageModulationTableEnable" :: Symbol) VkPipelineCoverageModulationStateCreateInfoNV :: Type Source #

type FieldOptional ("coverageModulationTableEnable" :: Symbol) VkPipelineCoverageModulationStateCreateInfoNV :: Bool Source #

type FieldOffset ("coverageModulationTableEnable" :: Symbol) VkPipelineCoverageModulationStateCreateInfoNV :: Nat Source #

type FieldIsArray ("coverageModulationTableEnable" :: Symbol) VkPipelineCoverageModulationStateCreateInfoNV :: Bool Source #

HasField "flags" VkPipelineCoverageModulationStateCreateInfoNV Source # 
HasField "pCoverageModulationTable" VkPipelineCoverageModulationStateCreateInfoNV Source # 
HasField "pNext" VkPipelineCoverageModulationStateCreateInfoNV Source # 
HasField "sType" VkPipelineCoverageModulationStateCreateInfoNV Source # 
type StructFields VkPipelineCoverageModulationStateCreateInfoNV Source # 
type StructFields VkPipelineCoverageModulationStateCreateInfoNV = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "coverageModulationMode" ((:) Symbol "coverageModulationTableEnable" ((:) Symbol "coverageModulationTableCount" ((:) Symbol "pCoverageModulationTable" ([] Symbol)))))))
type CUnionType VkPipelineCoverageModulationStateCreateInfoNV Source # 
type ReturnedOnly VkPipelineCoverageModulationStateCreateInfoNV Source # 
type StructExtends VkPipelineCoverageModulationStateCreateInfoNV Source # 
type FieldType "coverageModulationMode" VkPipelineCoverageModulationStateCreateInfoNV Source # 
type FieldType "coverageModulationTableCount" VkPipelineCoverageModulationStateCreateInfoNV Source # 
type FieldType "coverageModulationTableCount" VkPipelineCoverageModulationStateCreateInfoNV = Word32
type FieldType "coverageModulationTableEnable" VkPipelineCoverageModulationStateCreateInfoNV Source # 
type FieldType "flags" VkPipelineCoverageModulationStateCreateInfoNV Source # 
type FieldType "pCoverageModulationTable" VkPipelineCoverageModulationStateCreateInfoNV Source # 
type FieldType "pNext" VkPipelineCoverageModulationStateCreateInfoNV Source # 
type FieldType "sType" VkPipelineCoverageModulationStateCreateInfoNV Source # 
type FieldOptional "coverageModulationMode" VkPipelineCoverageModulationStateCreateInfoNV Source # 
type FieldOptional "coverageModulationTableCount" VkPipelineCoverageModulationStateCreateInfoNV Source # 
type FieldOptional "coverageModulationTableEnable" VkPipelineCoverageModulationStateCreateInfoNV Source # 
type FieldOptional "flags" VkPipelineCoverageModulationStateCreateInfoNV Source # 
type FieldOptional "pCoverageModulationTable" VkPipelineCoverageModulationStateCreateInfoNV Source # 
type FieldOptional "pNext" VkPipelineCoverageModulationStateCreateInfoNV Source # 
type FieldOptional "sType" VkPipelineCoverageModulationStateCreateInfoNV Source # 
type FieldOffset "coverageModulationMode" VkPipelineCoverageModulationStateCreateInfoNV Source # 
type FieldOffset "coverageModulationTableCount" VkPipelineCoverageModulationStateCreateInfoNV Source # 
type FieldOffset "coverageModulationTableCount" VkPipelineCoverageModulationStateCreateInfoNV = 28
type FieldOffset "coverageModulationTableEnable" VkPipelineCoverageModulationStateCreateInfoNV Source # 
type FieldOffset "coverageModulationTableEnable" VkPipelineCoverageModulationStateCreateInfoNV = 24
type FieldOffset "flags" VkPipelineCoverageModulationStateCreateInfoNV Source # 
type FieldOffset "pCoverageModulationTable" VkPipelineCoverageModulationStateCreateInfoNV Source # 
type FieldOffset "pCoverageModulationTable" VkPipelineCoverageModulationStateCreateInfoNV = 32
type FieldOffset "pNext" VkPipelineCoverageModulationStateCreateInfoNV Source # 
type FieldOffset "sType" VkPipelineCoverageModulationStateCreateInfoNV Source # 
type FieldIsArray "coverageModulationMode" VkPipelineCoverageModulationStateCreateInfoNV Source # 
type FieldIsArray "coverageModulationTableCount" VkPipelineCoverageModulationStateCreateInfoNV Source # 
type FieldIsArray "coverageModulationTableEnable" VkPipelineCoverageModulationStateCreateInfoNV Source # 
type FieldIsArray "flags" VkPipelineCoverageModulationStateCreateInfoNV Source # 
type FieldIsArray "pCoverageModulationTable" VkPipelineCoverageModulationStateCreateInfoNV Source # 
type FieldIsArray "pNext" VkPipelineCoverageModulationStateCreateInfoNV Source # 
type FieldIsArray "sType" VkPipelineCoverageModulationStateCreateInfoNV Source # 

data VkPipelineCoverageToColorStateCreateInfoNV Source #

typedef struct VkPipelineCoverageToColorStateCreateInfoNV {
    VkStructureType sType;
    const void*                                                                      pNext;
    VkPipelineCoverageToColorStateCreateFlagsNV                    flags;
    VkBool32                         coverageToColorEnable;
    uint32_t         coverageToColorLocation;
} VkPipelineCoverageToColorStateCreateInfoNV;

VkPipelineCoverageToColorStateCreateInfoNV registry at www.khronos.org

Instances

Eq VkPipelineCoverageToColorStateCreateInfoNV Source # 
Ord VkPipelineCoverageToColorStateCreateInfoNV Source # 
Show VkPipelineCoverageToColorStateCreateInfoNV Source # 
Storable VkPipelineCoverageToColorStateCreateInfoNV Source # 
VulkanMarshalPrim VkPipelineCoverageToColorStateCreateInfoNV Source # 
VulkanMarshal VkPipelineCoverageToColorStateCreateInfoNV Source # 
CanWriteField "coverageToColorEnable" VkPipelineCoverageToColorStateCreateInfoNV Source # 
CanWriteField "coverageToColorLocation" VkPipelineCoverageToColorStateCreateInfoNV Source # 
CanWriteField "flags" VkPipelineCoverageToColorStateCreateInfoNV Source # 
CanWriteField "pNext" VkPipelineCoverageToColorStateCreateInfoNV Source # 
CanWriteField "sType" VkPipelineCoverageToColorStateCreateInfoNV Source # 
CanReadField "coverageToColorEnable" VkPipelineCoverageToColorStateCreateInfoNV Source # 
CanReadField "coverageToColorLocation" VkPipelineCoverageToColorStateCreateInfoNV Source # 
CanReadField "flags" VkPipelineCoverageToColorStateCreateInfoNV Source # 
CanReadField "pNext" VkPipelineCoverageToColorStateCreateInfoNV Source # 
CanReadField "sType" VkPipelineCoverageToColorStateCreateInfoNV Source # 
HasField "coverageToColorEnable" VkPipelineCoverageToColorStateCreateInfoNV Source # 
HasField "coverageToColorLocation" VkPipelineCoverageToColorStateCreateInfoNV Source # 
HasField "flags" VkPipelineCoverageToColorStateCreateInfoNV Source # 
HasField "pNext" VkPipelineCoverageToColorStateCreateInfoNV Source # 
HasField "sType" VkPipelineCoverageToColorStateCreateInfoNV Source # 
type StructFields VkPipelineCoverageToColorStateCreateInfoNV Source # 
type StructFields VkPipelineCoverageToColorStateCreateInfoNV = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "coverageToColorEnable" ((:) Symbol "coverageToColorLocation" ([] Symbol)))))
type CUnionType VkPipelineCoverageToColorStateCreateInfoNV Source # 
type ReturnedOnly VkPipelineCoverageToColorStateCreateInfoNV Source # 
type StructExtends VkPipelineCoverageToColorStateCreateInfoNV Source # 
type FieldType "coverageToColorEnable" VkPipelineCoverageToColorStateCreateInfoNV Source # 
type FieldType "coverageToColorLocation" VkPipelineCoverageToColorStateCreateInfoNV Source # 
type FieldType "flags" VkPipelineCoverageToColorStateCreateInfoNV Source # 
type FieldType "pNext" VkPipelineCoverageToColorStateCreateInfoNV Source # 
type FieldType "sType" VkPipelineCoverageToColorStateCreateInfoNV Source # 
type FieldOptional "coverageToColorEnable" VkPipelineCoverageToColorStateCreateInfoNV Source # 
type FieldOptional "coverageToColorLocation" VkPipelineCoverageToColorStateCreateInfoNV Source # 
type FieldOptional "flags" VkPipelineCoverageToColorStateCreateInfoNV Source # 
type FieldOptional "pNext" VkPipelineCoverageToColorStateCreateInfoNV Source # 
type FieldOptional "sType" VkPipelineCoverageToColorStateCreateInfoNV Source # 
type FieldOffset "coverageToColorEnable" VkPipelineCoverageToColorStateCreateInfoNV Source # 
type FieldOffset "coverageToColorLocation" VkPipelineCoverageToColorStateCreateInfoNV Source # 
type FieldOffset "coverageToColorLocation" VkPipelineCoverageToColorStateCreateInfoNV = 24
type FieldOffset "flags" VkPipelineCoverageToColorStateCreateInfoNV Source # 
type FieldOffset "pNext" VkPipelineCoverageToColorStateCreateInfoNV Source # 
type FieldOffset "sType" VkPipelineCoverageToColorStateCreateInfoNV Source # 
type FieldIsArray "coverageToColorEnable" VkPipelineCoverageToColorStateCreateInfoNV Source # 
type FieldIsArray "coverageToColorLocation" VkPipelineCoverageToColorStateCreateInfoNV Source # 
type FieldIsArray "flags" VkPipelineCoverageToColorStateCreateInfoNV Source # 
type FieldIsArray "pNext" VkPipelineCoverageToColorStateCreateInfoNV Source # 
type FieldIsArray "sType" VkPipelineCoverageToColorStateCreateInfoNV Source # 

data VkPipelineDepthStencilStateCreateInfo Source #

typedef struct VkPipelineDepthStencilStateCreateInfo {
    VkStructureType sType;
    const void*            pNext;
    VkPipelineDepthStencilStateCreateFlags    flags;
    VkBool32               depthTestEnable;
    VkBool32               depthWriteEnable;
    VkCompareOp            depthCompareOp;
    VkBool32               depthBoundsTestEnable;
    VkBool32               stencilTestEnable;
    VkStencilOpState       front;
    VkStencilOpState       back;
    float                  minDepthBounds;
    float                  maxDepthBounds;
} VkPipelineDepthStencilStateCreateInfo;

VkPipelineDepthStencilStateCreateInfo registry at www.khronos.org

Instances

Eq VkPipelineDepthStencilStateCreateInfo Source # 
Ord VkPipelineDepthStencilStateCreateInfo Source # 
Show VkPipelineDepthStencilStateCreateInfo Source # 
Storable VkPipelineDepthStencilStateCreateInfo Source # 
VulkanMarshalPrim VkPipelineDepthStencilStateCreateInfo Source # 
VulkanMarshal VkPipelineDepthStencilStateCreateInfo Source # 
CanWriteField "back" VkPipelineDepthStencilStateCreateInfo Source # 
CanWriteField "depthBoundsTestEnable" VkPipelineDepthStencilStateCreateInfo Source # 
CanWriteField "depthCompareOp" VkPipelineDepthStencilStateCreateInfo Source # 
CanWriteField "depthTestEnable" VkPipelineDepthStencilStateCreateInfo Source # 
CanWriteField "depthWriteEnable" VkPipelineDepthStencilStateCreateInfo Source # 
CanWriteField "flags" VkPipelineDepthStencilStateCreateInfo Source # 
CanWriteField "front" VkPipelineDepthStencilStateCreateInfo Source # 
CanWriteField "maxDepthBounds" VkPipelineDepthStencilStateCreateInfo Source # 
CanWriteField "minDepthBounds" VkPipelineDepthStencilStateCreateInfo Source # 
CanWriteField "pNext" VkPipelineDepthStencilStateCreateInfo Source # 
CanWriteField "sType" VkPipelineDepthStencilStateCreateInfo Source # 
CanWriteField "stencilTestEnable" VkPipelineDepthStencilStateCreateInfo Source # 
CanReadField "back" VkPipelineDepthStencilStateCreateInfo Source # 
CanReadField "depthBoundsTestEnable" VkPipelineDepthStencilStateCreateInfo Source # 
CanReadField "depthCompareOp" VkPipelineDepthStencilStateCreateInfo Source # 
CanReadField "depthTestEnable" VkPipelineDepthStencilStateCreateInfo Source # 
CanReadField "depthWriteEnable" VkPipelineDepthStencilStateCreateInfo Source # 
CanReadField "flags" VkPipelineDepthStencilStateCreateInfo Source # 
CanReadField "front" VkPipelineDepthStencilStateCreateInfo Source # 
CanReadField "maxDepthBounds" VkPipelineDepthStencilStateCreateInfo Source # 
CanReadField "minDepthBounds" VkPipelineDepthStencilStateCreateInfo Source # 
CanReadField "pNext" VkPipelineDepthStencilStateCreateInfo Source # 
CanReadField "sType" VkPipelineDepthStencilStateCreateInfo Source # 
CanReadField "stencilTestEnable" VkPipelineDepthStencilStateCreateInfo Source # 
HasField "back" VkPipelineDepthStencilStateCreateInfo Source # 
HasField "depthBoundsTestEnable" VkPipelineDepthStencilStateCreateInfo Source # 

Associated Types

type FieldType ("depthBoundsTestEnable" :: Symbol) VkPipelineDepthStencilStateCreateInfo :: Type Source #

type FieldOptional ("depthBoundsTestEnable" :: Symbol) VkPipelineDepthStencilStateCreateInfo :: Bool Source #

type FieldOffset ("depthBoundsTestEnable" :: Symbol) VkPipelineDepthStencilStateCreateInfo :: Nat Source #

type FieldIsArray ("depthBoundsTestEnable" :: Symbol) VkPipelineDepthStencilStateCreateInfo :: Bool Source #

HasField "depthCompareOp" VkPipelineDepthStencilStateCreateInfo Source # 
HasField "depthTestEnable" VkPipelineDepthStencilStateCreateInfo Source # 
HasField "depthWriteEnable" VkPipelineDepthStencilStateCreateInfo Source # 
HasField "flags" VkPipelineDepthStencilStateCreateInfo Source # 
HasField "front" VkPipelineDepthStencilStateCreateInfo Source # 
HasField "maxDepthBounds" VkPipelineDepthStencilStateCreateInfo Source # 
HasField "minDepthBounds" VkPipelineDepthStencilStateCreateInfo Source # 
HasField "pNext" VkPipelineDepthStencilStateCreateInfo Source # 
HasField "sType" VkPipelineDepthStencilStateCreateInfo Source # 
HasField "stencilTestEnable" VkPipelineDepthStencilStateCreateInfo Source # 
type StructFields VkPipelineDepthStencilStateCreateInfo Source # 
type StructFields VkPipelineDepthStencilStateCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "depthTestEnable" ((:) Symbol "depthWriteEnable" ((:) Symbol "depthCompareOp" ((:) Symbol "depthBoundsTestEnable" ((:) Symbol "stencilTestEnable" ((:) Symbol "front" ((:) Symbol "back" ((:) Symbol "minDepthBounds" ((:) Symbol "maxDepthBounds" ([] Symbol))))))))))))
type CUnionType VkPipelineDepthStencilStateCreateInfo Source # 
type ReturnedOnly VkPipelineDepthStencilStateCreateInfo Source # 
type StructExtends VkPipelineDepthStencilStateCreateInfo Source # 
type FieldType "back" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldType "depthBoundsTestEnable" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldType "depthCompareOp" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldType "depthTestEnable" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldType "depthWriteEnable" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldType "flags" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldType "front" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldType "maxDepthBounds" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldType "minDepthBounds" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldType "pNext" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldType "sType" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldType "stencilTestEnable" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldOptional "back" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldOptional "depthBoundsTestEnable" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldOptional "depthCompareOp" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldOptional "depthTestEnable" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldOptional "depthWriteEnable" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldOptional "flags" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldOptional "front" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldOptional "maxDepthBounds" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldOptional "minDepthBounds" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldOptional "pNext" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldOptional "sType" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldOptional "stencilTestEnable" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldOffset "back" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldOffset "depthBoundsTestEnable" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldOffset "depthBoundsTestEnable" VkPipelineDepthStencilStateCreateInfo = 32
type FieldOffset "depthCompareOp" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldOffset "depthTestEnable" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldOffset "depthWriteEnable" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldOffset "flags" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldOffset "front" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldOffset "maxDepthBounds" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldOffset "minDepthBounds" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldOffset "pNext" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldOffset "sType" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldOffset "stencilTestEnable" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldIsArray "back" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldIsArray "depthBoundsTestEnable" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldIsArray "depthCompareOp" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldIsArray "depthTestEnable" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldIsArray "depthWriteEnable" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldIsArray "flags" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldIsArray "front" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldIsArray "maxDepthBounds" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldIsArray "minDepthBounds" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldIsArray "pNext" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldIsArray "sType" VkPipelineDepthStencilStateCreateInfo Source # 
type FieldIsArray "stencilTestEnable" VkPipelineDepthStencilStateCreateInfo Source # 

data VkPipelineDiscardRectangleStateCreateInfoEXT Source #

typedef struct VkPipelineDiscardRectangleStateCreateInfoEXT {
    VkStructureType sType;
    const void*                                                                      pNext;
    VkPipelineDiscardRectangleStateCreateFlagsEXT                    flags;
    VkDiscardRectangleModeEXT                                                        discardRectangleMode;
    uint32_t                                                         discardRectangleCount;
    const VkRect2D* pDiscardRectangles;
} VkPipelineDiscardRectangleStateCreateInfoEXT;

VkPipelineDiscardRectangleStateCreateInfoEXT registry at www.khronos.org

Instances

Eq VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
Ord VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
Show VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
Storable VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
VulkanMarshalPrim VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
VulkanMarshal VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
CanWriteField "discardRectangleCount" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
CanWriteField "discardRectangleMode" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
CanWriteField "flags" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
CanWriteField "pDiscardRectangles" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
CanWriteField "pNext" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
CanWriteField "sType" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
CanReadField "discardRectangleCount" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
CanReadField "discardRectangleMode" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
CanReadField "flags" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
CanReadField "pDiscardRectangles" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
CanReadField "pNext" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
CanReadField "sType" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
HasField "discardRectangleCount" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
HasField "discardRectangleMode" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
HasField "flags" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
HasField "pDiscardRectangles" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
HasField "pNext" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
HasField "sType" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
type StructFields VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
type StructFields VkPipelineDiscardRectangleStateCreateInfoEXT = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "discardRectangleMode" ((:) Symbol "discardRectangleCount" ((:) Symbol "pDiscardRectangles" ([] Symbol))))))
type CUnionType VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
type ReturnedOnly VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
type StructExtends VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
type FieldType "discardRectangleCount" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
type FieldType "discardRectangleMode" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
type FieldType "flags" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
type FieldType "pDiscardRectangles" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
type FieldType "pNext" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
type FieldType "sType" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
type FieldOptional "discardRectangleCount" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
type FieldOptional "discardRectangleMode" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
type FieldOptional "flags" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
type FieldOptional "pDiscardRectangles" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
type FieldOptional "pNext" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
type FieldOptional "sType" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
type FieldOffset "discardRectangleCount" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
type FieldOffset "discardRectangleMode" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
type FieldOffset "flags" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
type FieldOffset "pDiscardRectangles" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
type FieldOffset "pNext" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
type FieldOffset "sType" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
type FieldIsArray "discardRectangleCount" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
type FieldIsArray "discardRectangleMode" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
type FieldIsArray "flags" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
type FieldIsArray "pDiscardRectangles" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
type FieldIsArray "pNext" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 
type FieldIsArray "sType" VkPipelineDiscardRectangleStateCreateInfoEXT Source # 

data VkPipelineDynamicStateCreateInfo Source #

typedef struct VkPipelineDynamicStateCreateInfo {
    VkStructureType sType;
    const void*            pNext;
    VkPipelineDynamicStateCreateFlags    flags;
    uint32_t               dynamicStateCount;
    const VkDynamicState*  pDynamicStates;
} VkPipelineDynamicStateCreateInfo;

VkPipelineDynamicStateCreateInfo registry at www.khronos.org

Instances

Eq VkPipelineDynamicStateCreateInfo Source # 
Ord VkPipelineDynamicStateCreateInfo Source # 
Show VkPipelineDynamicStateCreateInfo Source # 
Storable VkPipelineDynamicStateCreateInfo Source # 
VulkanMarshalPrim VkPipelineDynamicStateCreateInfo Source # 
VulkanMarshal VkPipelineDynamicStateCreateInfo Source # 
CanWriteField "dynamicStateCount" VkPipelineDynamicStateCreateInfo Source # 
CanWriteField "flags" VkPipelineDynamicStateCreateInfo Source # 
CanWriteField "pDynamicStates" VkPipelineDynamicStateCreateInfo Source # 
CanWriteField "pNext" VkPipelineDynamicStateCreateInfo Source # 
CanWriteField "sType" VkPipelineDynamicStateCreateInfo Source # 
CanReadField "dynamicStateCount" VkPipelineDynamicStateCreateInfo Source # 
CanReadField "flags" VkPipelineDynamicStateCreateInfo Source # 
CanReadField "pDynamicStates" VkPipelineDynamicStateCreateInfo Source # 
CanReadField "pNext" VkPipelineDynamicStateCreateInfo Source # 
CanReadField "sType" VkPipelineDynamicStateCreateInfo Source # 
HasField "dynamicStateCount" VkPipelineDynamicStateCreateInfo Source # 
HasField "flags" VkPipelineDynamicStateCreateInfo Source # 
HasField "pDynamicStates" VkPipelineDynamicStateCreateInfo Source # 
HasField "pNext" VkPipelineDynamicStateCreateInfo Source # 
HasField "sType" VkPipelineDynamicStateCreateInfo Source # 
type StructFields VkPipelineDynamicStateCreateInfo Source # 
type StructFields VkPipelineDynamicStateCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "dynamicStateCount" ((:) Symbol "pDynamicStates" ([] Symbol)))))
type CUnionType VkPipelineDynamicStateCreateInfo Source # 
type ReturnedOnly VkPipelineDynamicStateCreateInfo Source # 
type StructExtends VkPipelineDynamicStateCreateInfo Source # 
type FieldType "dynamicStateCount" VkPipelineDynamicStateCreateInfo Source # 
type FieldType "flags" VkPipelineDynamicStateCreateInfo Source # 
type FieldType "pDynamicStates" VkPipelineDynamicStateCreateInfo Source # 
type FieldType "pNext" VkPipelineDynamicStateCreateInfo Source # 
type FieldType "sType" VkPipelineDynamicStateCreateInfo Source # 
type FieldOptional "dynamicStateCount" VkPipelineDynamicStateCreateInfo Source # 
type FieldOptional "flags" VkPipelineDynamicStateCreateInfo Source # 
type FieldOptional "pDynamicStates" VkPipelineDynamicStateCreateInfo Source # 
type FieldOptional "pNext" VkPipelineDynamicStateCreateInfo Source # 
type FieldOptional "sType" VkPipelineDynamicStateCreateInfo Source # 
type FieldOffset "dynamicStateCount" VkPipelineDynamicStateCreateInfo Source # 
type FieldOffset "dynamicStateCount" VkPipelineDynamicStateCreateInfo = 20
type FieldOffset "flags" VkPipelineDynamicStateCreateInfo Source # 
type FieldOffset "pDynamicStates" VkPipelineDynamicStateCreateInfo Source # 
type FieldOffset "pNext" VkPipelineDynamicStateCreateInfo Source # 
type FieldOffset "sType" VkPipelineDynamicStateCreateInfo Source # 
type FieldIsArray "dynamicStateCount" VkPipelineDynamicStateCreateInfo Source # 
type FieldIsArray "flags" VkPipelineDynamicStateCreateInfo Source # 
type FieldIsArray "pDynamicStates" VkPipelineDynamicStateCreateInfo Source # 
type FieldIsArray "pNext" VkPipelineDynamicStateCreateInfo Source # 
type FieldIsArray "sType" VkPipelineDynamicStateCreateInfo Source # 

data VkPipelineInputAssemblyStateCreateInfo Source #

typedef struct VkPipelineInputAssemblyStateCreateInfo {
    VkStructureType sType;
    const void*            pNext;
    VkPipelineInputAssemblyStateCreateFlags    flags;
    VkPrimitiveTopology    topology;
    VkBool32               primitiveRestartEnable;
} VkPipelineInputAssemblyStateCreateInfo;

VkPipelineInputAssemblyStateCreateInfo registry at www.khronos.org

Instances

Eq VkPipelineInputAssemblyStateCreateInfo Source # 
Ord VkPipelineInputAssemblyStateCreateInfo Source # 
Show VkPipelineInputAssemblyStateCreateInfo Source # 
Storable VkPipelineInputAssemblyStateCreateInfo Source # 
VulkanMarshalPrim VkPipelineInputAssemblyStateCreateInfo Source # 
VulkanMarshal VkPipelineInputAssemblyStateCreateInfo Source # 
CanWriteField "flags" VkPipelineInputAssemblyStateCreateInfo Source # 
CanWriteField "pNext" VkPipelineInputAssemblyStateCreateInfo Source # 
CanWriteField "primitiveRestartEnable" VkPipelineInputAssemblyStateCreateInfo Source # 
CanWriteField "sType" VkPipelineInputAssemblyStateCreateInfo Source # 
CanWriteField "topology" VkPipelineInputAssemblyStateCreateInfo Source # 
CanReadField "flags" VkPipelineInputAssemblyStateCreateInfo Source # 
CanReadField "pNext" VkPipelineInputAssemblyStateCreateInfo Source # 
CanReadField "primitiveRestartEnable" VkPipelineInputAssemblyStateCreateInfo Source # 
CanReadField "sType" VkPipelineInputAssemblyStateCreateInfo Source # 
CanReadField "topology" VkPipelineInputAssemblyStateCreateInfo Source # 
HasField "flags" VkPipelineInputAssemblyStateCreateInfo Source # 
HasField "pNext" VkPipelineInputAssemblyStateCreateInfo Source # 
HasField "primitiveRestartEnable" VkPipelineInputAssemblyStateCreateInfo Source # 

Associated Types

type FieldType ("primitiveRestartEnable" :: Symbol) VkPipelineInputAssemblyStateCreateInfo :: Type Source #

type FieldOptional ("primitiveRestartEnable" :: Symbol) VkPipelineInputAssemblyStateCreateInfo :: Bool Source #

type FieldOffset ("primitiveRestartEnable" :: Symbol) VkPipelineInputAssemblyStateCreateInfo :: Nat Source #

type FieldIsArray ("primitiveRestartEnable" :: Symbol) VkPipelineInputAssemblyStateCreateInfo :: Bool Source #

HasField "sType" VkPipelineInputAssemblyStateCreateInfo Source # 
HasField "topology" VkPipelineInputAssemblyStateCreateInfo Source # 
type StructFields VkPipelineInputAssemblyStateCreateInfo Source # 
type StructFields VkPipelineInputAssemblyStateCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "topology" ((:) Symbol "primitiveRestartEnable" ([] Symbol)))))
type CUnionType VkPipelineInputAssemblyStateCreateInfo Source # 
type ReturnedOnly VkPipelineInputAssemblyStateCreateInfo Source # 
type StructExtends VkPipelineInputAssemblyStateCreateInfo Source # 
type FieldType "flags" VkPipelineInputAssemblyStateCreateInfo Source # 
type FieldType "pNext" VkPipelineInputAssemblyStateCreateInfo Source # 
type FieldType "primitiveRestartEnable" VkPipelineInputAssemblyStateCreateInfo Source # 
type FieldType "sType" VkPipelineInputAssemblyStateCreateInfo Source # 
type FieldType "topology" VkPipelineInputAssemblyStateCreateInfo Source # 
type FieldOptional "flags" VkPipelineInputAssemblyStateCreateInfo Source # 
type FieldOptional "pNext" VkPipelineInputAssemblyStateCreateInfo Source # 
type FieldOptional "primitiveRestartEnable" VkPipelineInputAssemblyStateCreateInfo Source # 
type FieldOptional "sType" VkPipelineInputAssemblyStateCreateInfo Source # 
type FieldOptional "topology" VkPipelineInputAssemblyStateCreateInfo Source # 
type FieldOffset "flags" VkPipelineInputAssemblyStateCreateInfo Source # 
type FieldOffset "pNext" VkPipelineInputAssemblyStateCreateInfo Source # 
type FieldOffset "primitiveRestartEnable" VkPipelineInputAssemblyStateCreateInfo Source # 
type FieldOffset "primitiveRestartEnable" VkPipelineInputAssemblyStateCreateInfo = 24
type FieldOffset "sType" VkPipelineInputAssemblyStateCreateInfo Source # 
type FieldOffset "topology" VkPipelineInputAssemblyStateCreateInfo Source # 
type FieldIsArray "flags" VkPipelineInputAssemblyStateCreateInfo Source # 
type FieldIsArray "pNext" VkPipelineInputAssemblyStateCreateInfo Source # 
type FieldIsArray "primitiveRestartEnable" VkPipelineInputAssemblyStateCreateInfo Source # 
type FieldIsArray "sType" VkPipelineInputAssemblyStateCreateInfo Source # 
type FieldIsArray "topology" VkPipelineInputAssemblyStateCreateInfo Source # 

data VkPipelineLayoutCreateInfo Source #

typedef struct VkPipelineLayoutCreateInfo {
    VkStructureType sType;
    const void*            pNext;
    VkPipelineLayoutCreateFlags    flags;
    uint32_t               setLayoutCount;
    const VkDescriptorSetLayout* pSetLayouts;
    uint32_t               pushConstantRangeCount;
    const VkPushConstantRange* pPushConstantRanges;
} VkPipelineLayoutCreateInfo;

VkPipelineLayoutCreateInfo registry at www.khronos.org

Instances

Eq VkPipelineLayoutCreateInfo Source # 
Ord VkPipelineLayoutCreateInfo Source # 
Show VkPipelineLayoutCreateInfo Source # 
Storable VkPipelineLayoutCreateInfo Source # 
VulkanMarshalPrim VkPipelineLayoutCreateInfo Source # 
VulkanMarshal VkPipelineLayoutCreateInfo Source # 
CanWriteField "flags" VkPipelineLayoutCreateInfo Source # 
CanWriteField "pNext" VkPipelineLayoutCreateInfo Source # 
CanWriteField "pPushConstantRanges" VkPipelineLayoutCreateInfo Source # 
CanWriteField "pSetLayouts" VkPipelineLayoutCreateInfo Source # 
CanWriteField "pushConstantRangeCount" VkPipelineLayoutCreateInfo Source # 
CanWriteField "sType" VkPipelineLayoutCreateInfo Source # 
CanWriteField "setLayoutCount" VkPipelineLayoutCreateInfo Source # 
CanReadField "flags" VkPipelineLayoutCreateInfo Source # 
CanReadField "pNext" VkPipelineLayoutCreateInfo Source # 
CanReadField "pPushConstantRanges" VkPipelineLayoutCreateInfo Source # 
CanReadField "pSetLayouts" VkPipelineLayoutCreateInfo Source # 
CanReadField "pushConstantRangeCount" VkPipelineLayoutCreateInfo Source # 
CanReadField "sType" VkPipelineLayoutCreateInfo Source # 
CanReadField "setLayoutCount" VkPipelineLayoutCreateInfo Source # 
HasField "flags" VkPipelineLayoutCreateInfo Source # 
HasField "pNext" VkPipelineLayoutCreateInfo Source # 
HasField "pPushConstantRanges" VkPipelineLayoutCreateInfo Source # 

Associated Types

type FieldType ("pPushConstantRanges" :: Symbol) VkPipelineLayoutCreateInfo :: Type Source #

type FieldOptional ("pPushConstantRanges" :: Symbol) VkPipelineLayoutCreateInfo :: Bool Source #

type FieldOffset ("pPushConstantRanges" :: Symbol) VkPipelineLayoutCreateInfo :: Nat Source #

type FieldIsArray ("pPushConstantRanges" :: Symbol) VkPipelineLayoutCreateInfo :: Bool Source #

HasField "pSetLayouts" VkPipelineLayoutCreateInfo Source # 
HasField "pushConstantRangeCount" VkPipelineLayoutCreateInfo Source # 

Associated Types

type FieldType ("pushConstantRangeCount" :: Symbol) VkPipelineLayoutCreateInfo :: Type Source #

type FieldOptional ("pushConstantRangeCount" :: Symbol) VkPipelineLayoutCreateInfo :: Bool Source #

type FieldOffset ("pushConstantRangeCount" :: Symbol) VkPipelineLayoutCreateInfo :: Nat Source #

type FieldIsArray ("pushConstantRangeCount" :: Symbol) VkPipelineLayoutCreateInfo :: Bool Source #

HasField "sType" VkPipelineLayoutCreateInfo Source # 
HasField "setLayoutCount" VkPipelineLayoutCreateInfo Source # 

Associated Types

type FieldType ("setLayoutCount" :: Symbol) VkPipelineLayoutCreateInfo :: Type Source #

type FieldOptional ("setLayoutCount" :: Symbol) VkPipelineLayoutCreateInfo :: Bool Source #

type FieldOffset ("setLayoutCount" :: Symbol) VkPipelineLayoutCreateInfo :: Nat Source #

type FieldIsArray ("setLayoutCount" :: Symbol) VkPipelineLayoutCreateInfo :: Bool Source #

type StructFields VkPipelineLayoutCreateInfo Source # 
type StructFields VkPipelineLayoutCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "setLayoutCount" ((:) Symbol "pSetLayouts" ((:) Symbol "pushConstantRangeCount" ((:) Symbol "pPushConstantRanges" ([] Symbol)))))))
type CUnionType VkPipelineLayoutCreateInfo Source # 
type ReturnedOnly VkPipelineLayoutCreateInfo Source # 
type StructExtends VkPipelineLayoutCreateInfo Source # 
type FieldType "flags" VkPipelineLayoutCreateInfo Source # 
type FieldType "pNext" VkPipelineLayoutCreateInfo Source # 
type FieldType "pPushConstantRanges" VkPipelineLayoutCreateInfo Source # 
type FieldType "pSetLayouts" VkPipelineLayoutCreateInfo Source # 
type FieldType "pushConstantRangeCount" VkPipelineLayoutCreateInfo Source # 
type FieldType "pushConstantRangeCount" VkPipelineLayoutCreateInfo = Word32
type FieldType "sType" VkPipelineLayoutCreateInfo Source # 
type FieldType "setLayoutCount" VkPipelineLayoutCreateInfo Source # 
type FieldOptional "flags" VkPipelineLayoutCreateInfo Source # 
type FieldOptional "pNext" VkPipelineLayoutCreateInfo Source # 
type FieldOptional "pPushConstantRanges" VkPipelineLayoutCreateInfo Source # 
type FieldOptional "pPushConstantRanges" VkPipelineLayoutCreateInfo = False
type FieldOptional "pSetLayouts" VkPipelineLayoutCreateInfo Source # 
type FieldOptional "pushConstantRangeCount" VkPipelineLayoutCreateInfo Source # 
type FieldOptional "pushConstantRangeCount" VkPipelineLayoutCreateInfo = True
type FieldOptional "sType" VkPipelineLayoutCreateInfo Source # 
type FieldOptional "setLayoutCount" VkPipelineLayoutCreateInfo Source # 
type FieldOffset "flags" VkPipelineLayoutCreateInfo Source # 
type FieldOffset "pNext" VkPipelineLayoutCreateInfo Source # 
type FieldOffset "pPushConstantRanges" VkPipelineLayoutCreateInfo Source # 
type FieldOffset "pPushConstantRanges" VkPipelineLayoutCreateInfo = 40
type FieldOffset "pSetLayouts" VkPipelineLayoutCreateInfo Source # 
type FieldOffset "pSetLayouts" VkPipelineLayoutCreateInfo = 24
type FieldOffset "pushConstantRangeCount" VkPipelineLayoutCreateInfo Source # 
type FieldOffset "pushConstantRangeCount" VkPipelineLayoutCreateInfo = 32
type FieldOffset "sType" VkPipelineLayoutCreateInfo Source # 
type FieldOffset "setLayoutCount" VkPipelineLayoutCreateInfo Source # 
type FieldOffset "setLayoutCount" VkPipelineLayoutCreateInfo = 20
type FieldIsArray "flags" VkPipelineLayoutCreateInfo Source # 
type FieldIsArray "pNext" VkPipelineLayoutCreateInfo Source # 
type FieldIsArray "pPushConstantRanges" VkPipelineLayoutCreateInfo Source # 
type FieldIsArray "pPushConstantRanges" VkPipelineLayoutCreateInfo = False
type FieldIsArray "pSetLayouts" VkPipelineLayoutCreateInfo Source # 
type FieldIsArray "pushConstantRangeCount" VkPipelineLayoutCreateInfo Source # 
type FieldIsArray "pushConstantRangeCount" VkPipelineLayoutCreateInfo = False
type FieldIsArray "sType" VkPipelineLayoutCreateInfo Source # 
type FieldIsArray "setLayoutCount" VkPipelineLayoutCreateInfo Source # 

data VkPipelineMultisampleStateCreateInfo Source #

typedef struct VkPipelineMultisampleStateCreateInfo {
    VkStructureType sType;
    const void*            pNext;
    VkPipelineMultisampleStateCreateFlags    flags;
    VkSampleCountFlagBits  rasterizationSamples;
    VkBool32               sampleShadingEnable;
    float                  minSampleShading;
    const VkSampleMask*    pSampleMask;
    VkBool32               alphaToCoverageEnable;
    VkBool32               alphaToOneEnable;
} VkPipelineMultisampleStateCreateInfo;

VkPipelineMultisampleStateCreateInfo registry at www.khronos.org

Instances

Eq VkPipelineMultisampleStateCreateInfo Source # 
Ord VkPipelineMultisampleStateCreateInfo Source # 
Show VkPipelineMultisampleStateCreateInfo Source # 
Storable VkPipelineMultisampleStateCreateInfo Source # 
VulkanMarshalPrim VkPipelineMultisampleStateCreateInfo Source # 
VulkanMarshal VkPipelineMultisampleStateCreateInfo Source # 
CanWriteField "alphaToCoverageEnable" VkPipelineMultisampleStateCreateInfo Source # 
CanWriteField "alphaToOneEnable" VkPipelineMultisampleStateCreateInfo Source # 
CanWriteField "flags" VkPipelineMultisampleStateCreateInfo Source # 
CanWriteField "minSampleShading" VkPipelineMultisampleStateCreateInfo Source # 
CanWriteField "pNext" VkPipelineMultisampleStateCreateInfo Source # 
CanWriteField "pSampleMask" VkPipelineMultisampleStateCreateInfo Source # 
CanWriteField "rasterizationSamples" VkPipelineMultisampleStateCreateInfo Source # 
CanWriteField "sType" VkPipelineMultisampleStateCreateInfo Source # 
CanWriteField "sampleShadingEnable" VkPipelineMultisampleStateCreateInfo Source # 
CanReadField "alphaToCoverageEnable" VkPipelineMultisampleStateCreateInfo Source # 
CanReadField "alphaToOneEnable" VkPipelineMultisampleStateCreateInfo Source # 
CanReadField "flags" VkPipelineMultisampleStateCreateInfo Source # 
CanReadField "minSampleShading" VkPipelineMultisampleStateCreateInfo Source # 
CanReadField "pNext" VkPipelineMultisampleStateCreateInfo Source # 
CanReadField "pSampleMask" VkPipelineMultisampleStateCreateInfo Source # 
CanReadField "rasterizationSamples" VkPipelineMultisampleStateCreateInfo Source # 
CanReadField "sType" VkPipelineMultisampleStateCreateInfo Source # 
CanReadField "sampleShadingEnable" VkPipelineMultisampleStateCreateInfo Source # 
HasField "alphaToCoverageEnable" VkPipelineMultisampleStateCreateInfo Source # 

Associated Types

type FieldType ("alphaToCoverageEnable" :: Symbol) VkPipelineMultisampleStateCreateInfo :: Type Source #

type FieldOptional ("alphaToCoverageEnable" :: Symbol) VkPipelineMultisampleStateCreateInfo :: Bool Source #

type FieldOffset ("alphaToCoverageEnable" :: Symbol) VkPipelineMultisampleStateCreateInfo :: Nat Source #

type FieldIsArray ("alphaToCoverageEnable" :: Symbol) VkPipelineMultisampleStateCreateInfo :: Bool Source #

HasField "alphaToOneEnable" VkPipelineMultisampleStateCreateInfo Source # 
HasField "flags" VkPipelineMultisampleStateCreateInfo Source # 
HasField "minSampleShading" VkPipelineMultisampleStateCreateInfo Source # 
HasField "pNext" VkPipelineMultisampleStateCreateInfo Source # 
HasField "pSampleMask" VkPipelineMultisampleStateCreateInfo Source # 
HasField "rasterizationSamples" VkPipelineMultisampleStateCreateInfo Source # 
HasField "sType" VkPipelineMultisampleStateCreateInfo Source # 
HasField "sampleShadingEnable" VkPipelineMultisampleStateCreateInfo Source # 
type StructFields VkPipelineMultisampleStateCreateInfo Source # 
type StructFields VkPipelineMultisampleStateCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "rasterizationSamples" ((:) Symbol "sampleShadingEnable" ((:) Symbol "minSampleShading" ((:) Symbol "pSampleMask" ((:) Symbol "alphaToCoverageEnable" ((:) Symbol "alphaToOneEnable" ([] Symbol)))))))))
type CUnionType VkPipelineMultisampleStateCreateInfo Source # 
type ReturnedOnly VkPipelineMultisampleStateCreateInfo Source # 
type StructExtends VkPipelineMultisampleStateCreateInfo Source # 
type FieldType "alphaToCoverageEnable" VkPipelineMultisampleStateCreateInfo Source # 
type FieldType "alphaToOneEnable" VkPipelineMultisampleStateCreateInfo Source # 
type FieldType "flags" VkPipelineMultisampleStateCreateInfo Source # 
type FieldType "minSampleShading" VkPipelineMultisampleStateCreateInfo Source # 
type FieldType "pNext" VkPipelineMultisampleStateCreateInfo Source # 
type FieldType "pSampleMask" VkPipelineMultisampleStateCreateInfo Source # 
type FieldType "rasterizationSamples" VkPipelineMultisampleStateCreateInfo Source # 
type FieldType "sType" VkPipelineMultisampleStateCreateInfo Source # 
type FieldType "sampleShadingEnable" VkPipelineMultisampleStateCreateInfo Source # 
type FieldOptional "alphaToCoverageEnable" VkPipelineMultisampleStateCreateInfo Source # 
type FieldOptional "alphaToOneEnable" VkPipelineMultisampleStateCreateInfo Source # 
type FieldOptional "flags" VkPipelineMultisampleStateCreateInfo Source # 
type FieldOptional "minSampleShading" VkPipelineMultisampleStateCreateInfo Source # 
type FieldOptional "pNext" VkPipelineMultisampleStateCreateInfo Source # 
type FieldOptional "pSampleMask" VkPipelineMultisampleStateCreateInfo Source # 
type FieldOptional "rasterizationSamples" VkPipelineMultisampleStateCreateInfo Source # 
type FieldOptional "sType" VkPipelineMultisampleStateCreateInfo Source # 
type FieldOptional "sampleShadingEnable" VkPipelineMultisampleStateCreateInfo Source # 
type FieldOffset "alphaToCoverageEnable" VkPipelineMultisampleStateCreateInfo Source # 
type FieldOffset "alphaToCoverageEnable" VkPipelineMultisampleStateCreateInfo = 40
type FieldOffset "alphaToOneEnable" VkPipelineMultisampleStateCreateInfo Source # 
type FieldOffset "flags" VkPipelineMultisampleStateCreateInfo Source # 
type FieldOffset "minSampleShading" VkPipelineMultisampleStateCreateInfo Source # 
type FieldOffset "pNext" VkPipelineMultisampleStateCreateInfo Source # 
type FieldOffset "pSampleMask" VkPipelineMultisampleStateCreateInfo Source # 
type FieldOffset "rasterizationSamples" VkPipelineMultisampleStateCreateInfo Source # 
type FieldOffset "rasterizationSamples" VkPipelineMultisampleStateCreateInfo = 20
type FieldOffset "sType" VkPipelineMultisampleStateCreateInfo Source # 
type FieldOffset "sampleShadingEnable" VkPipelineMultisampleStateCreateInfo Source # 
type FieldOffset "sampleShadingEnable" VkPipelineMultisampleStateCreateInfo = 24
type FieldIsArray "alphaToCoverageEnable" VkPipelineMultisampleStateCreateInfo Source # 
type FieldIsArray "alphaToOneEnable" VkPipelineMultisampleStateCreateInfo Source # 
type FieldIsArray "flags" VkPipelineMultisampleStateCreateInfo Source # 
type FieldIsArray "minSampleShading" VkPipelineMultisampleStateCreateInfo Source # 
type FieldIsArray "pNext" VkPipelineMultisampleStateCreateInfo Source # 
type FieldIsArray "pSampleMask" VkPipelineMultisampleStateCreateInfo Source # 
type FieldIsArray "rasterizationSamples" VkPipelineMultisampleStateCreateInfo Source # 
type FieldIsArray "sType" VkPipelineMultisampleStateCreateInfo Source # 
type FieldIsArray "sampleShadingEnable" VkPipelineMultisampleStateCreateInfo Source # 

data VkPipelineRasterizationConservativeStateCreateInfoEXT Source #

typedef struct VkPipelineRasterizationConservativeStateCreateInfoEXT {
    VkStructureType sType;
    const void*                                                                      pNext;
    VkPipelineRasterizationConservativeStateCreateFlagsEXT           flags;
    VkConservativeRasterizationModeEXT                                               conservativeRasterizationMode;
    float                                                                            extraPrimitiveOverestimationSize;
} VkPipelineRasterizationConservativeStateCreateInfoEXT;

VkPipelineRasterizationConservativeStateCreateInfoEXT registry at www.khronos.org

Instances

Eq VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
Ord VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
Show VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
Storable VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
VulkanMarshalPrim VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
VulkanMarshal VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
CanWriteField "conservativeRasterizationMode" VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
CanWriteField "extraPrimitiveOverestimationSize" VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
CanWriteField "flags" VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
CanWriteField "pNext" VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
CanWriteField "sType" VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
CanReadField "conservativeRasterizationMode" VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
CanReadField "extraPrimitiveOverestimationSize" VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
CanReadField "flags" VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
CanReadField "pNext" VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
CanReadField "sType" VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
HasField "conservativeRasterizationMode" VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
HasField "extraPrimitiveOverestimationSize" VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 

Associated Types

type FieldType ("extraPrimitiveOverestimationSize" :: Symbol) VkPipelineRasterizationConservativeStateCreateInfoEXT :: Type Source #

type FieldOptional ("extraPrimitiveOverestimationSize" :: Symbol) VkPipelineRasterizationConservativeStateCreateInfoEXT :: Bool Source #

type FieldOffset ("extraPrimitiveOverestimationSize" :: Symbol) VkPipelineRasterizationConservativeStateCreateInfoEXT :: Nat Source #

type FieldIsArray ("extraPrimitiveOverestimationSize" :: Symbol) VkPipelineRasterizationConservativeStateCreateInfoEXT :: Bool Source #

HasField "flags" VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
HasField "pNext" VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
HasField "sType" VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
type StructFields VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
type StructFields VkPipelineRasterizationConservativeStateCreateInfoEXT = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "conservativeRasterizationMode" ((:) Symbol "extraPrimitiveOverestimationSize" ([] Symbol)))))
type CUnionType VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
type ReturnedOnly VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
type StructExtends VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
type FieldType "conservativeRasterizationMode" VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
type FieldType "extraPrimitiveOverestimationSize" VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
type FieldType "flags" VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
type FieldType "pNext" VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
type FieldType "sType" VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
type FieldOptional "conservativeRasterizationMode" VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
type FieldOptional "extraPrimitiveOverestimationSize" VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
type FieldOptional "flags" VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
type FieldOptional "pNext" VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
type FieldOptional "sType" VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
type FieldOffset "conservativeRasterizationMode" VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
type FieldOffset "conservativeRasterizationMode" VkPipelineRasterizationConservativeStateCreateInfoEXT = 20
type FieldOffset "extraPrimitiveOverestimationSize" VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
type FieldOffset "extraPrimitiveOverestimationSize" VkPipelineRasterizationConservativeStateCreateInfoEXT = 24
type FieldOffset "flags" VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
type FieldOffset "pNext" VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
type FieldOffset "sType" VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
type FieldIsArray "conservativeRasterizationMode" VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
type FieldIsArray "extraPrimitiveOverestimationSize" VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
type FieldIsArray "flags" VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
type FieldIsArray "pNext" VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 
type FieldIsArray "sType" VkPipelineRasterizationConservativeStateCreateInfoEXT Source # 

data VkPipelineRasterizationStateCreateInfo Source #

typedef struct VkPipelineRasterizationStateCreateInfo {
    VkStructureType sType;
    const void* pNext;
    VkPipelineRasterizationStateCreateFlags    flags;
    VkBool32               depthClampEnable;
    VkBool32               rasterizerDiscardEnable;
    VkPolygonMode          polygonMode;
    VkCullModeFlags        cullMode;
    VkFrontFace            frontFace;
    VkBool32               depthBiasEnable;
    float                  depthBiasConstantFactor;
    float                  depthBiasClamp;
    float                  depthBiasSlopeFactor;
    float                  lineWidth;
} VkPipelineRasterizationStateCreateInfo;

VkPipelineRasterizationStateCreateInfo registry at www.khronos.org

Instances

Eq VkPipelineRasterizationStateCreateInfo Source # 
Ord VkPipelineRasterizationStateCreateInfo Source # 
Show VkPipelineRasterizationStateCreateInfo Source # 
Storable VkPipelineRasterizationStateCreateInfo Source # 
VulkanMarshalPrim VkPipelineRasterizationStateCreateInfo Source # 
VulkanMarshal VkPipelineRasterizationStateCreateInfo Source # 
CanWriteField "cullMode" VkPipelineRasterizationStateCreateInfo Source # 
CanWriteField "depthBiasClamp" VkPipelineRasterizationStateCreateInfo Source # 
CanWriteField "depthBiasConstantFactor" VkPipelineRasterizationStateCreateInfo Source # 
CanWriteField "depthBiasEnable" VkPipelineRasterizationStateCreateInfo Source # 
CanWriteField "depthBiasSlopeFactor" VkPipelineRasterizationStateCreateInfo Source # 
CanWriteField "depthClampEnable" VkPipelineRasterizationStateCreateInfo Source # 
CanWriteField "flags" VkPipelineRasterizationStateCreateInfo Source # 
CanWriteField "frontFace" VkPipelineRasterizationStateCreateInfo Source # 
CanWriteField "lineWidth" VkPipelineRasterizationStateCreateInfo Source # 
CanWriteField "pNext" VkPipelineRasterizationStateCreateInfo Source # 
CanWriteField "polygonMode" VkPipelineRasterizationStateCreateInfo Source # 
CanWriteField "rasterizerDiscardEnable" VkPipelineRasterizationStateCreateInfo Source # 
CanWriteField "sType" VkPipelineRasterizationStateCreateInfo Source # 
CanReadField "cullMode" VkPipelineRasterizationStateCreateInfo Source # 
CanReadField "depthBiasClamp" VkPipelineRasterizationStateCreateInfo Source # 
CanReadField "depthBiasConstantFactor" VkPipelineRasterizationStateCreateInfo Source # 
CanReadField "depthBiasEnable" VkPipelineRasterizationStateCreateInfo Source # 
CanReadField "depthBiasSlopeFactor" VkPipelineRasterizationStateCreateInfo Source # 
CanReadField "depthClampEnable" VkPipelineRasterizationStateCreateInfo Source # 
CanReadField "flags" VkPipelineRasterizationStateCreateInfo Source # 
CanReadField "frontFace" VkPipelineRasterizationStateCreateInfo Source # 
CanReadField "lineWidth" VkPipelineRasterizationStateCreateInfo Source # 
CanReadField "pNext" VkPipelineRasterizationStateCreateInfo Source # 
CanReadField "polygonMode" VkPipelineRasterizationStateCreateInfo Source # 
CanReadField "rasterizerDiscardEnable" VkPipelineRasterizationStateCreateInfo Source # 
CanReadField "sType" VkPipelineRasterizationStateCreateInfo Source # 
HasField "cullMode" VkPipelineRasterizationStateCreateInfo Source # 
HasField "depthBiasClamp" VkPipelineRasterizationStateCreateInfo Source # 
HasField "depthBiasConstantFactor" VkPipelineRasterizationStateCreateInfo Source # 

Associated Types

type FieldType ("depthBiasConstantFactor" :: Symbol) VkPipelineRasterizationStateCreateInfo :: Type Source #

type FieldOptional ("depthBiasConstantFactor" :: Symbol) VkPipelineRasterizationStateCreateInfo :: Bool Source #

type FieldOffset ("depthBiasConstantFactor" :: Symbol) VkPipelineRasterizationStateCreateInfo :: Nat Source #

type FieldIsArray ("depthBiasConstantFactor" :: Symbol) VkPipelineRasterizationStateCreateInfo :: Bool Source #

HasField "depthBiasEnable" VkPipelineRasterizationStateCreateInfo Source # 
HasField "depthBiasSlopeFactor" VkPipelineRasterizationStateCreateInfo Source # 
HasField "depthClampEnable" VkPipelineRasterizationStateCreateInfo Source # 
HasField "flags" VkPipelineRasterizationStateCreateInfo Source # 
HasField "frontFace" VkPipelineRasterizationStateCreateInfo Source # 
HasField "lineWidth" VkPipelineRasterizationStateCreateInfo Source # 
HasField "pNext" VkPipelineRasterizationStateCreateInfo Source # 
HasField "polygonMode" VkPipelineRasterizationStateCreateInfo Source # 
HasField "rasterizerDiscardEnable" VkPipelineRasterizationStateCreateInfo Source # 

Associated Types

type FieldType ("rasterizerDiscardEnable" :: Symbol) VkPipelineRasterizationStateCreateInfo :: Type Source #

type FieldOptional ("rasterizerDiscardEnable" :: Symbol) VkPipelineRasterizationStateCreateInfo :: Bool Source #

type FieldOffset ("rasterizerDiscardEnable" :: Symbol) VkPipelineRasterizationStateCreateInfo :: Nat Source #

type FieldIsArray ("rasterizerDiscardEnable" :: Symbol) VkPipelineRasterizationStateCreateInfo :: Bool Source #

HasField "sType" VkPipelineRasterizationStateCreateInfo Source # 
type StructFields VkPipelineRasterizationStateCreateInfo Source # 
type StructFields VkPipelineRasterizationStateCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "depthClampEnable" ((:) Symbol "rasterizerDiscardEnable" ((:) Symbol "polygonMode" ((:) Symbol "cullMode" ((:) Symbol "frontFace" ((:) Symbol "depthBiasEnable" ((:) Symbol "depthBiasConstantFactor" ((:) Symbol "depthBiasClamp" ((:) Symbol "depthBiasSlopeFactor" ((:) Symbol "lineWidth" ([] Symbol)))))))))))))
type CUnionType VkPipelineRasterizationStateCreateInfo Source # 
type ReturnedOnly VkPipelineRasterizationStateCreateInfo Source # 
type StructExtends VkPipelineRasterizationStateCreateInfo Source # 
type FieldType "cullMode" VkPipelineRasterizationStateCreateInfo Source # 
type FieldType "depthBiasClamp" VkPipelineRasterizationStateCreateInfo Source # 
type FieldType "depthBiasConstantFactor" VkPipelineRasterizationStateCreateInfo Source # 
type FieldType "depthBiasConstantFactor" VkPipelineRasterizationStateCreateInfo = Float
type FieldType "depthBiasEnable" VkPipelineRasterizationStateCreateInfo Source # 
type FieldType "depthBiasSlopeFactor" VkPipelineRasterizationStateCreateInfo Source # 
type FieldType "depthClampEnable" VkPipelineRasterizationStateCreateInfo Source # 
type FieldType "flags" VkPipelineRasterizationStateCreateInfo Source # 
type FieldType "frontFace" VkPipelineRasterizationStateCreateInfo Source # 
type FieldType "lineWidth" VkPipelineRasterizationStateCreateInfo Source # 
type FieldType "pNext" VkPipelineRasterizationStateCreateInfo Source # 
type FieldType "polygonMode" VkPipelineRasterizationStateCreateInfo Source # 
type FieldType "rasterizerDiscardEnable" VkPipelineRasterizationStateCreateInfo Source # 
type FieldType "sType" VkPipelineRasterizationStateCreateInfo Source # 
type FieldOptional "cullMode" VkPipelineRasterizationStateCreateInfo Source # 
type FieldOptional "depthBiasClamp" VkPipelineRasterizationStateCreateInfo Source # 
type FieldOptional "depthBiasConstantFactor" VkPipelineRasterizationStateCreateInfo Source # 
type FieldOptional "depthBiasEnable" VkPipelineRasterizationStateCreateInfo Source # 
type FieldOptional "depthBiasSlopeFactor" VkPipelineRasterizationStateCreateInfo Source # 
type FieldOptional "depthClampEnable" VkPipelineRasterizationStateCreateInfo Source # 
type FieldOptional "flags" VkPipelineRasterizationStateCreateInfo Source # 
type FieldOptional "frontFace" VkPipelineRasterizationStateCreateInfo Source # 
type FieldOptional "lineWidth" VkPipelineRasterizationStateCreateInfo Source # 
type FieldOptional "pNext" VkPipelineRasterizationStateCreateInfo Source # 
type FieldOptional "polygonMode" VkPipelineRasterizationStateCreateInfo Source # 
type FieldOptional "rasterizerDiscardEnable" VkPipelineRasterizationStateCreateInfo Source # 
type FieldOptional "sType" VkPipelineRasterizationStateCreateInfo Source # 
type FieldOffset "cullMode" VkPipelineRasterizationStateCreateInfo Source # 
type FieldOffset "depthBiasClamp" VkPipelineRasterizationStateCreateInfo Source # 
type FieldOffset "depthBiasConstantFactor" VkPipelineRasterizationStateCreateInfo Source # 
type FieldOffset "depthBiasConstantFactor" VkPipelineRasterizationStateCreateInfo = 44
type FieldOffset "depthBiasEnable" VkPipelineRasterizationStateCreateInfo Source # 
type FieldOffset "depthBiasSlopeFactor" VkPipelineRasterizationStateCreateInfo Source # 
type FieldOffset "depthBiasSlopeFactor" VkPipelineRasterizationStateCreateInfo = 52
type FieldOffset "depthClampEnable" VkPipelineRasterizationStateCreateInfo Source # 
type FieldOffset "flags" VkPipelineRasterizationStateCreateInfo Source # 
type FieldOffset "frontFace" VkPipelineRasterizationStateCreateInfo Source # 
type FieldOffset "lineWidth" VkPipelineRasterizationStateCreateInfo Source # 
type FieldOffset "pNext" VkPipelineRasterizationStateCreateInfo Source # 
type FieldOffset "polygonMode" VkPipelineRasterizationStateCreateInfo Source # 
type FieldOffset "rasterizerDiscardEnable" VkPipelineRasterizationStateCreateInfo Source # 
type FieldOffset "rasterizerDiscardEnable" VkPipelineRasterizationStateCreateInfo = 24
type FieldOffset "sType" VkPipelineRasterizationStateCreateInfo Source # 
type FieldIsArray "cullMode" VkPipelineRasterizationStateCreateInfo Source # 
type FieldIsArray "depthBiasClamp" VkPipelineRasterizationStateCreateInfo Source # 
type FieldIsArray "depthBiasConstantFactor" VkPipelineRasterizationStateCreateInfo Source # 
type FieldIsArray "depthBiasEnable" VkPipelineRasterizationStateCreateInfo Source # 
type FieldIsArray "depthBiasSlopeFactor" VkPipelineRasterizationStateCreateInfo Source # 
type FieldIsArray "depthClampEnable" VkPipelineRasterizationStateCreateInfo Source # 
type FieldIsArray "flags" VkPipelineRasterizationStateCreateInfo Source # 
type FieldIsArray "frontFace" VkPipelineRasterizationStateCreateInfo Source # 
type FieldIsArray "lineWidth" VkPipelineRasterizationStateCreateInfo Source # 
type FieldIsArray "pNext" VkPipelineRasterizationStateCreateInfo Source # 
type FieldIsArray "polygonMode" VkPipelineRasterizationStateCreateInfo Source # 
type FieldIsArray "rasterizerDiscardEnable" VkPipelineRasterizationStateCreateInfo Source # 
type FieldIsArray "sType" VkPipelineRasterizationStateCreateInfo Source # 

data VkPipelineRasterizationStateRasterizationOrderAMD Source #

typedef struct VkPipelineRasterizationStateRasterizationOrderAMD {
    VkStructureType sType;
    const void*                      pNext;
    VkRasterizationOrderAMD          rasterizationOrder;
} VkPipelineRasterizationStateRasterizationOrderAMD;

VkPipelineRasterizationStateRasterizationOrderAMD registry at www.khronos.org

Instances

Eq VkPipelineRasterizationStateRasterizationOrderAMD Source # 
Ord VkPipelineRasterizationStateRasterizationOrderAMD Source # 
Show VkPipelineRasterizationStateRasterizationOrderAMD Source # 
Storable VkPipelineRasterizationStateRasterizationOrderAMD Source # 
VulkanMarshalPrim VkPipelineRasterizationStateRasterizationOrderAMD Source # 
VulkanMarshal VkPipelineRasterizationStateRasterizationOrderAMD Source # 
CanWriteField "pNext" VkPipelineRasterizationStateRasterizationOrderAMD Source # 
CanWriteField "rasterizationOrder" VkPipelineRasterizationStateRasterizationOrderAMD Source # 
CanWriteField "sType" VkPipelineRasterizationStateRasterizationOrderAMD Source # 
CanReadField "pNext" VkPipelineRasterizationStateRasterizationOrderAMD Source # 
CanReadField "rasterizationOrder" VkPipelineRasterizationStateRasterizationOrderAMD Source # 
CanReadField "sType" VkPipelineRasterizationStateRasterizationOrderAMD Source # 
HasField "pNext" VkPipelineRasterizationStateRasterizationOrderAMD Source # 
HasField "rasterizationOrder" VkPipelineRasterizationStateRasterizationOrderAMD Source # 
HasField "sType" VkPipelineRasterizationStateRasterizationOrderAMD Source # 
type StructFields VkPipelineRasterizationStateRasterizationOrderAMD Source # 
type StructFields VkPipelineRasterizationStateRasterizationOrderAMD = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "rasterizationOrder" ([] Symbol)))
type CUnionType VkPipelineRasterizationStateRasterizationOrderAMD Source # 
type ReturnedOnly VkPipelineRasterizationStateRasterizationOrderAMD Source # 
type StructExtends VkPipelineRasterizationStateRasterizationOrderAMD Source # 
type FieldType "pNext" VkPipelineRasterizationStateRasterizationOrderAMD Source # 
type FieldType "rasterizationOrder" VkPipelineRasterizationStateRasterizationOrderAMD Source # 
type FieldType "sType" VkPipelineRasterizationStateRasterizationOrderAMD Source # 
type FieldOptional "pNext" VkPipelineRasterizationStateRasterizationOrderAMD Source # 
type FieldOptional "rasterizationOrder" VkPipelineRasterizationStateRasterizationOrderAMD Source # 
type FieldOptional "sType" VkPipelineRasterizationStateRasterizationOrderAMD Source # 
type FieldOffset "pNext" VkPipelineRasterizationStateRasterizationOrderAMD Source # 
type FieldOffset "rasterizationOrder" VkPipelineRasterizationStateRasterizationOrderAMD Source # 
type FieldOffset "sType" VkPipelineRasterizationStateRasterizationOrderAMD Source # 
type FieldIsArray "pNext" VkPipelineRasterizationStateRasterizationOrderAMD Source # 
type FieldIsArray "rasterizationOrder" VkPipelineRasterizationStateRasterizationOrderAMD Source # 
type FieldIsArray "sType" VkPipelineRasterizationStateRasterizationOrderAMD Source # 

data VkPipelineSampleLocationsStateCreateInfoEXT Source #

typedef struct VkPipelineSampleLocationsStateCreateInfoEXT {
    VkStructureType sType;
    const void*                      pNext;
    VkBool32                         sampleLocationsEnable;
    VkSampleLocationsInfoEXT         sampleLocationsInfo;
} VkPipelineSampleLocationsStateCreateInfoEXT;

VkPipelineSampleLocationsStateCreateInfoEXT registry at www.khronos.org

Instances

Eq VkPipelineSampleLocationsStateCreateInfoEXT Source # 
Ord VkPipelineSampleLocationsStateCreateInfoEXT Source # 
Show VkPipelineSampleLocationsStateCreateInfoEXT Source # 
Storable VkPipelineSampleLocationsStateCreateInfoEXT Source # 
VulkanMarshalPrim VkPipelineSampleLocationsStateCreateInfoEXT Source # 
VulkanMarshal VkPipelineSampleLocationsStateCreateInfoEXT Source # 
CanWriteField "pNext" VkPipelineSampleLocationsStateCreateInfoEXT Source # 
CanWriteField "sType" VkPipelineSampleLocationsStateCreateInfoEXT Source # 
CanWriteField "sampleLocationsEnable" VkPipelineSampleLocationsStateCreateInfoEXT Source # 
CanWriteField "sampleLocationsInfo" VkPipelineSampleLocationsStateCreateInfoEXT Source # 
CanReadField "pNext" VkPipelineSampleLocationsStateCreateInfoEXT Source # 
CanReadField "sType" VkPipelineSampleLocationsStateCreateInfoEXT Source # 
CanReadField "sampleLocationsEnable" VkPipelineSampleLocationsStateCreateInfoEXT Source # 
CanReadField "sampleLocationsInfo" VkPipelineSampleLocationsStateCreateInfoEXT Source # 
HasField "pNext" VkPipelineSampleLocationsStateCreateInfoEXT Source # 
HasField "sType" VkPipelineSampleLocationsStateCreateInfoEXT Source # 
HasField "sampleLocationsEnable" VkPipelineSampleLocationsStateCreateInfoEXT Source # 
HasField "sampleLocationsInfo" VkPipelineSampleLocationsStateCreateInfoEXT Source # 
type StructFields VkPipelineSampleLocationsStateCreateInfoEXT Source # 
type StructFields VkPipelineSampleLocationsStateCreateInfoEXT = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "sampleLocationsEnable" ((:) Symbol "sampleLocationsInfo" ([] Symbol))))
type CUnionType VkPipelineSampleLocationsStateCreateInfoEXT Source # 
type ReturnedOnly VkPipelineSampleLocationsStateCreateInfoEXT Source # 
type StructExtends VkPipelineSampleLocationsStateCreateInfoEXT Source # 
type FieldType "pNext" VkPipelineSampleLocationsStateCreateInfoEXT Source # 
type FieldType "sType" VkPipelineSampleLocationsStateCreateInfoEXT Source # 
type FieldType "sampleLocationsEnable" VkPipelineSampleLocationsStateCreateInfoEXT Source # 
type FieldType "sampleLocationsInfo" VkPipelineSampleLocationsStateCreateInfoEXT Source # 
type FieldOptional "pNext" VkPipelineSampleLocationsStateCreateInfoEXT Source # 
type FieldOptional "sType" VkPipelineSampleLocationsStateCreateInfoEXT Source # 
type FieldOptional "sampleLocationsEnable" VkPipelineSampleLocationsStateCreateInfoEXT Source # 
type FieldOptional "sampleLocationsInfo" VkPipelineSampleLocationsStateCreateInfoEXT Source # 
type FieldOffset "pNext" VkPipelineSampleLocationsStateCreateInfoEXT Source # 
type FieldOffset "sType" VkPipelineSampleLocationsStateCreateInfoEXT Source # 
type FieldOffset "sampleLocationsEnable" VkPipelineSampleLocationsStateCreateInfoEXT Source # 
type FieldOffset "sampleLocationsInfo" VkPipelineSampleLocationsStateCreateInfoEXT Source # 
type FieldIsArray "pNext" VkPipelineSampleLocationsStateCreateInfoEXT Source # 
type FieldIsArray "sType" VkPipelineSampleLocationsStateCreateInfoEXT Source # 
type FieldIsArray "sampleLocationsEnable" VkPipelineSampleLocationsStateCreateInfoEXT Source # 
type FieldIsArray "sampleLocationsInfo" VkPipelineSampleLocationsStateCreateInfoEXT Source # 

data VkPipelineShaderStageCreateInfo Source #

typedef struct VkPipelineShaderStageCreateInfo {
    VkStructureType sType;
    const void*            pNext;
    VkPipelineShaderStageCreateFlags    flags;
    VkShaderStageFlagBits  stage;
    VkShaderModule         module;
    const char*            pName;
    const VkSpecializationInfo* pSpecializationInfo;
} VkPipelineShaderStageCreateInfo;

VkPipelineShaderStageCreateInfo registry at www.khronos.org

Instances

Eq VkPipelineShaderStageCreateInfo Source # 
Ord VkPipelineShaderStageCreateInfo Source # 
Show VkPipelineShaderStageCreateInfo Source # 
Storable VkPipelineShaderStageCreateInfo Source # 
VulkanMarshalPrim VkPipelineShaderStageCreateInfo Source # 
VulkanMarshal VkPipelineShaderStageCreateInfo Source # 
CanWriteField "flags" VkPipelineShaderStageCreateInfo Source # 
CanWriteField "module" VkPipelineShaderStageCreateInfo Source # 
CanWriteField "pName" VkPipelineShaderStageCreateInfo Source # 
CanWriteField "pNext" VkPipelineShaderStageCreateInfo Source # 
CanWriteField "pSpecializationInfo" VkPipelineShaderStageCreateInfo Source # 
CanWriteField "sType" VkPipelineShaderStageCreateInfo Source # 
CanWriteField "stage" VkPipelineShaderStageCreateInfo Source # 
CanReadField "flags" VkPipelineShaderStageCreateInfo Source # 
CanReadField "module" VkPipelineShaderStageCreateInfo Source # 
CanReadField "pName" VkPipelineShaderStageCreateInfo Source # 
CanReadField "pNext" VkPipelineShaderStageCreateInfo Source # 
CanReadField "pSpecializationInfo" VkPipelineShaderStageCreateInfo Source # 
CanReadField "sType" VkPipelineShaderStageCreateInfo Source # 
CanReadField "stage" VkPipelineShaderStageCreateInfo Source # 
HasField "flags" VkPipelineShaderStageCreateInfo Source # 
HasField "module" VkPipelineShaderStageCreateInfo Source # 
HasField "pName" VkPipelineShaderStageCreateInfo Source # 
HasField "pNext" VkPipelineShaderStageCreateInfo Source # 
HasField "pSpecializationInfo" VkPipelineShaderStageCreateInfo Source # 

Associated Types

type FieldType ("pSpecializationInfo" :: Symbol) VkPipelineShaderStageCreateInfo :: Type Source #

type FieldOptional ("pSpecializationInfo" :: Symbol) VkPipelineShaderStageCreateInfo :: Bool Source #

type FieldOffset ("pSpecializationInfo" :: Symbol) VkPipelineShaderStageCreateInfo :: Nat Source #

type FieldIsArray ("pSpecializationInfo" :: Symbol) VkPipelineShaderStageCreateInfo :: Bool Source #

HasField "sType" VkPipelineShaderStageCreateInfo Source # 
HasField "stage" VkPipelineShaderStageCreateInfo Source # 
type StructFields VkPipelineShaderStageCreateInfo Source # 
type StructFields VkPipelineShaderStageCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "stage" ((:) Symbol "module" ((:) Symbol "pName" ((:) Symbol "pSpecializationInfo" ([] Symbol)))))))
type CUnionType VkPipelineShaderStageCreateInfo Source # 
type ReturnedOnly VkPipelineShaderStageCreateInfo Source # 
type StructExtends VkPipelineShaderStageCreateInfo Source # 
type FieldType "flags" VkPipelineShaderStageCreateInfo Source # 
type FieldType "module" VkPipelineShaderStageCreateInfo Source # 
type FieldType "pName" VkPipelineShaderStageCreateInfo Source # 
type FieldType "pNext" VkPipelineShaderStageCreateInfo Source # 
type FieldType "pSpecializationInfo" VkPipelineShaderStageCreateInfo Source # 
type FieldType "sType" VkPipelineShaderStageCreateInfo Source # 
type FieldType "stage" VkPipelineShaderStageCreateInfo Source # 
type FieldOptional "flags" VkPipelineShaderStageCreateInfo Source # 
type FieldOptional "module" VkPipelineShaderStageCreateInfo Source # 
type FieldOptional "pName" VkPipelineShaderStageCreateInfo Source # 
type FieldOptional "pNext" VkPipelineShaderStageCreateInfo Source # 
type FieldOptional "pSpecializationInfo" VkPipelineShaderStageCreateInfo Source # 
type FieldOptional "sType" VkPipelineShaderStageCreateInfo Source # 
type FieldOptional "stage" VkPipelineShaderStageCreateInfo Source # 
type FieldOffset "flags" VkPipelineShaderStageCreateInfo Source # 
type FieldOffset "module" VkPipelineShaderStageCreateInfo Source # 
type FieldOffset "pName" VkPipelineShaderStageCreateInfo Source # 
type FieldOffset "pNext" VkPipelineShaderStageCreateInfo Source # 
type FieldOffset "pSpecializationInfo" VkPipelineShaderStageCreateInfo Source # 
type FieldOffset "pSpecializationInfo" VkPipelineShaderStageCreateInfo = 40
type FieldOffset "sType" VkPipelineShaderStageCreateInfo Source # 
type FieldOffset "stage" VkPipelineShaderStageCreateInfo Source # 
type FieldIsArray "flags" VkPipelineShaderStageCreateInfo Source # 
type FieldIsArray "module" VkPipelineShaderStageCreateInfo Source # 
type FieldIsArray "pName" VkPipelineShaderStageCreateInfo Source # 
type FieldIsArray "pNext" VkPipelineShaderStageCreateInfo Source # 
type FieldIsArray "pSpecializationInfo" VkPipelineShaderStageCreateInfo Source # 
type FieldIsArray "sType" VkPipelineShaderStageCreateInfo Source # 
type FieldIsArray "stage" VkPipelineShaderStageCreateInfo Source # 

data VkPipelineTessellationDomainOriginStateCreateInfo Source #

typedef struct VkPipelineTessellationDomainOriginStateCreateInfo {
    VkStructureType sType;
    const void*                      pNext;
    VkTessellationDomainOrigin    domainOrigin;
} VkPipelineTessellationDomainOriginStateCreateInfo;

VkPipelineTessellationDomainOriginStateCreateInfo registry at www.khronos.org

Instances

Eq VkPipelineTessellationDomainOriginStateCreateInfo Source # 
Ord VkPipelineTessellationDomainOriginStateCreateInfo Source # 
Show VkPipelineTessellationDomainOriginStateCreateInfo Source # 
Storable VkPipelineTessellationDomainOriginStateCreateInfo Source # 
VulkanMarshalPrim VkPipelineTessellationDomainOriginStateCreateInfo Source # 
VulkanMarshal VkPipelineTessellationDomainOriginStateCreateInfo Source # 
CanWriteField "domainOrigin" VkPipelineTessellationDomainOriginStateCreateInfo Source # 
CanWriteField "pNext" VkPipelineTessellationDomainOriginStateCreateInfo Source # 
CanWriteField "sType" VkPipelineTessellationDomainOriginStateCreateInfo Source # 
CanReadField "domainOrigin" VkPipelineTessellationDomainOriginStateCreateInfo Source # 
CanReadField "pNext" VkPipelineTessellationDomainOriginStateCreateInfo Source # 
CanReadField "sType" VkPipelineTessellationDomainOriginStateCreateInfo Source # 
HasField "domainOrigin" VkPipelineTessellationDomainOriginStateCreateInfo Source # 
HasField "pNext" VkPipelineTessellationDomainOriginStateCreateInfo Source # 
HasField "sType" VkPipelineTessellationDomainOriginStateCreateInfo Source # 
type StructFields VkPipelineTessellationDomainOriginStateCreateInfo Source # 
type StructFields VkPipelineTessellationDomainOriginStateCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "domainOrigin" ([] Symbol)))
type CUnionType VkPipelineTessellationDomainOriginStateCreateInfo Source # 
type ReturnedOnly VkPipelineTessellationDomainOriginStateCreateInfo Source # 
type StructExtends VkPipelineTessellationDomainOriginStateCreateInfo Source # 
type FieldType "domainOrigin" VkPipelineTessellationDomainOriginStateCreateInfo Source # 
type FieldType "pNext" VkPipelineTessellationDomainOriginStateCreateInfo Source # 
type FieldType "sType" VkPipelineTessellationDomainOriginStateCreateInfo Source # 
type FieldOptional "domainOrigin" VkPipelineTessellationDomainOriginStateCreateInfo Source # 
type FieldOptional "pNext" VkPipelineTessellationDomainOriginStateCreateInfo Source # 
type FieldOptional "sType" VkPipelineTessellationDomainOriginStateCreateInfo Source # 
type FieldOffset "domainOrigin" VkPipelineTessellationDomainOriginStateCreateInfo Source # 
type FieldOffset "pNext" VkPipelineTessellationDomainOriginStateCreateInfo Source # 
type FieldOffset "sType" VkPipelineTessellationDomainOriginStateCreateInfo Source # 
type FieldIsArray "domainOrigin" VkPipelineTessellationDomainOriginStateCreateInfo Source # 
type FieldIsArray "pNext" VkPipelineTessellationDomainOriginStateCreateInfo Source # 
type FieldIsArray "sType" VkPipelineTessellationDomainOriginStateCreateInfo Source # 

data VkPipelineTessellationStateCreateInfo Source #

typedef struct VkPipelineTessellationStateCreateInfo {
    VkStructureType sType;
    const void*            pNext;
    VkPipelineTessellationStateCreateFlags    flags;
    uint32_t               patchControlPoints;
} VkPipelineTessellationStateCreateInfo;

VkPipelineTessellationStateCreateInfo registry at www.khronos.org

Instances

Eq VkPipelineTessellationStateCreateInfo Source # 
Ord VkPipelineTessellationStateCreateInfo Source # 
Show VkPipelineTessellationStateCreateInfo Source # 
Storable VkPipelineTessellationStateCreateInfo Source # 
VulkanMarshalPrim VkPipelineTessellationStateCreateInfo Source # 
VulkanMarshal VkPipelineTessellationStateCreateInfo Source # 
CanWriteField "flags" VkPipelineTessellationStateCreateInfo Source # 
CanWriteField "pNext" VkPipelineTessellationStateCreateInfo Source # 
CanWriteField "patchControlPoints" VkPipelineTessellationStateCreateInfo Source # 
CanWriteField "sType" VkPipelineTessellationStateCreateInfo Source # 
CanReadField "flags" VkPipelineTessellationStateCreateInfo Source # 
CanReadField "pNext" VkPipelineTessellationStateCreateInfo Source # 
CanReadField "patchControlPoints" VkPipelineTessellationStateCreateInfo Source # 
CanReadField "sType" VkPipelineTessellationStateCreateInfo Source # 
HasField "flags" VkPipelineTessellationStateCreateInfo Source # 
HasField "pNext" VkPipelineTessellationStateCreateInfo Source # 
HasField "patchControlPoints" VkPipelineTessellationStateCreateInfo Source # 
HasField "sType" VkPipelineTessellationStateCreateInfo Source # 
type StructFields VkPipelineTessellationStateCreateInfo Source # 
type StructFields VkPipelineTessellationStateCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "patchControlPoints" ([] Symbol))))
type CUnionType VkPipelineTessellationStateCreateInfo Source # 
type ReturnedOnly VkPipelineTessellationStateCreateInfo Source # 
type StructExtends VkPipelineTessellationStateCreateInfo Source # 
type FieldType "flags" VkPipelineTessellationStateCreateInfo Source # 
type FieldType "pNext" VkPipelineTessellationStateCreateInfo Source # 
type FieldType "patchControlPoints" VkPipelineTessellationStateCreateInfo Source # 
type FieldType "sType" VkPipelineTessellationStateCreateInfo Source # 
type FieldOptional "flags" VkPipelineTessellationStateCreateInfo Source # 
type FieldOptional "pNext" VkPipelineTessellationStateCreateInfo Source # 
type FieldOptional "patchControlPoints" VkPipelineTessellationStateCreateInfo Source # 
type FieldOptional "sType" VkPipelineTessellationStateCreateInfo Source # 
type FieldOffset "flags" VkPipelineTessellationStateCreateInfo Source # 
type FieldOffset "pNext" VkPipelineTessellationStateCreateInfo Source # 
type FieldOffset "patchControlPoints" VkPipelineTessellationStateCreateInfo Source # 
type FieldOffset "patchControlPoints" VkPipelineTessellationStateCreateInfo = 20
type FieldOffset "sType" VkPipelineTessellationStateCreateInfo Source # 
type FieldIsArray "flags" VkPipelineTessellationStateCreateInfo Source # 
type FieldIsArray "pNext" VkPipelineTessellationStateCreateInfo Source # 
type FieldIsArray "patchControlPoints" VkPipelineTessellationStateCreateInfo Source # 
type FieldIsArray "sType" VkPipelineTessellationStateCreateInfo Source # 

data VkPipelineVertexInputDivisorStateCreateInfoEXT Source #

typedef struct VkPipelineVertexInputDivisorStateCreateInfoEXT {
    VkStructureType sType;
    const void*                         pNext;
    uint32_t                            vertexBindingDivisorCount;
    const VkVertexInputBindingDivisorDescriptionEXT*      pVertexBindingDivisors;
} VkPipelineVertexInputDivisorStateCreateInfoEXT;

VkPipelineVertexInputDivisorStateCreateInfoEXT registry at www.khronos.org

Instances

Eq VkPipelineVertexInputDivisorStateCreateInfoEXT Source # 
Ord VkPipelineVertexInputDivisorStateCreateInfoEXT Source # 
Show VkPipelineVertexInputDivisorStateCreateInfoEXT Source # 
Storable VkPipelineVertexInputDivisorStateCreateInfoEXT Source # 
VulkanMarshalPrim VkPipelineVertexInputDivisorStateCreateInfoEXT Source # 
VulkanMarshal VkPipelineVertexInputDivisorStateCreateInfoEXT Source # 
CanWriteField "pNext" VkPipelineVertexInputDivisorStateCreateInfoEXT Source # 
CanWriteField "pVertexBindingDivisors" VkPipelineVertexInputDivisorStateCreateInfoEXT Source # 
CanWriteField "sType" VkPipelineVertexInputDivisorStateCreateInfoEXT Source # 
CanWriteField "vertexBindingDivisorCount" VkPipelineVertexInputDivisorStateCreateInfoEXT Source # 
CanReadField "pNext" VkPipelineVertexInputDivisorStateCreateInfoEXT Source # 
CanReadField "pVertexBindingDivisors" VkPipelineVertexInputDivisorStateCreateInfoEXT Source # 
CanReadField "sType" VkPipelineVertexInputDivisorStateCreateInfoEXT Source # 
CanReadField "vertexBindingDivisorCount" VkPipelineVertexInputDivisorStateCreateInfoEXT Source # 
HasField "pNext" VkPipelineVertexInputDivisorStateCreateInfoEXT Source # 
HasField "pVertexBindingDivisors" VkPipelineVertexInputDivisorStateCreateInfoEXT Source # 
HasField "sType" VkPipelineVertexInputDivisorStateCreateInfoEXT Source # 
HasField "vertexBindingDivisorCount" VkPipelineVertexInputDivisorStateCreateInfoEXT Source # 
type StructFields VkPipelineVertexInputDivisorStateCreateInfoEXT Source # 
type StructFields VkPipelineVertexInputDivisorStateCreateInfoEXT = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "vertexBindingDivisorCount" ((:) Symbol "pVertexBindingDivisors" ([] Symbol))))
type CUnionType VkPipelineVertexInputDivisorStateCreateInfoEXT Source # 
type ReturnedOnly VkPipelineVertexInputDivisorStateCreateInfoEXT Source # 
type StructExtends VkPipelineVertexInputDivisorStateCreateInfoEXT Source # 
type FieldType "pNext" VkPipelineVertexInputDivisorStateCreateInfoEXT Source # 
type FieldType "pVertexBindingDivisors" VkPipelineVertexInputDivisorStateCreateInfoEXT Source # 
type FieldType "sType" VkPipelineVertexInputDivisorStateCreateInfoEXT Source # 
type FieldType "vertexBindingDivisorCount" VkPipelineVertexInputDivisorStateCreateInfoEXT Source # 
type FieldOptional "pNext" VkPipelineVertexInputDivisorStateCreateInfoEXT Source # 
type FieldOptional "pVertexBindingDivisors" VkPipelineVertexInputDivisorStateCreateInfoEXT Source # 
type FieldOptional "sType" VkPipelineVertexInputDivisorStateCreateInfoEXT Source # 
type FieldOptional "vertexBindingDivisorCount" VkPipelineVertexInputDivisorStateCreateInfoEXT Source # 
type FieldOffset "pNext" VkPipelineVertexInputDivisorStateCreateInfoEXT Source # 
type FieldOffset "pVertexBindingDivisors" VkPipelineVertexInputDivisorStateCreateInfoEXT Source # 
type FieldOffset "sType" VkPipelineVertexInputDivisorStateCreateInfoEXT Source # 
type FieldOffset "vertexBindingDivisorCount" VkPipelineVertexInputDivisorStateCreateInfoEXT Source # 
type FieldOffset "vertexBindingDivisorCount" VkPipelineVertexInputDivisorStateCreateInfoEXT = 16
type FieldIsArray "pNext" VkPipelineVertexInputDivisorStateCreateInfoEXT Source # 
type FieldIsArray "pVertexBindingDivisors" VkPipelineVertexInputDivisorStateCreateInfoEXT Source # 
type FieldIsArray "sType" VkPipelineVertexInputDivisorStateCreateInfoEXT Source # 
type FieldIsArray "vertexBindingDivisorCount" VkPipelineVertexInputDivisorStateCreateInfoEXT Source # 

data VkPipelineVertexInputStateCreateInfo Source #

typedef struct VkPipelineVertexInputStateCreateInfo {
    VkStructureType sType;
    const void*            pNext;
    VkPipelineVertexInputStateCreateFlags    flags;
    uint32_t               vertexBindingDescriptionCount;
    const VkVertexInputBindingDescription* pVertexBindingDescriptions;
    uint32_t               vertexAttributeDescriptionCount;
    const VkVertexInputAttributeDescription* pVertexAttributeDescriptions;
} VkPipelineVertexInputStateCreateInfo;

VkPipelineVertexInputStateCreateInfo registry at www.khronos.org

Instances

Eq VkPipelineVertexInputStateCreateInfo Source # 
Ord VkPipelineVertexInputStateCreateInfo Source # 
Show VkPipelineVertexInputStateCreateInfo Source # 
Storable VkPipelineVertexInputStateCreateInfo Source # 
VulkanMarshalPrim VkPipelineVertexInputStateCreateInfo Source # 
VulkanMarshal VkPipelineVertexInputStateCreateInfo Source # 
CanWriteField "flags" VkPipelineVertexInputStateCreateInfo Source # 
CanWriteField "pNext" VkPipelineVertexInputStateCreateInfo Source # 
CanWriteField "pVertexAttributeDescriptions" VkPipelineVertexInputStateCreateInfo Source # 
CanWriteField "pVertexBindingDescriptions" VkPipelineVertexInputStateCreateInfo Source # 
CanWriteField "sType" VkPipelineVertexInputStateCreateInfo Source # 
CanWriteField "vertexAttributeDescriptionCount" VkPipelineVertexInputStateCreateInfo Source # 
CanWriteField "vertexBindingDescriptionCount" VkPipelineVertexInputStateCreateInfo Source # 
CanReadField "flags" VkPipelineVertexInputStateCreateInfo Source # 
CanReadField "pNext" VkPipelineVertexInputStateCreateInfo Source # 
CanReadField "pVertexAttributeDescriptions" VkPipelineVertexInputStateCreateInfo Source # 
CanReadField "pVertexBindingDescriptions" VkPipelineVertexInputStateCreateInfo Source # 
CanReadField "sType" VkPipelineVertexInputStateCreateInfo Source # 
CanReadField "vertexAttributeDescriptionCount" VkPipelineVertexInputStateCreateInfo Source # 
CanReadField "vertexBindingDescriptionCount" VkPipelineVertexInputStateCreateInfo Source # 
HasField "flags" VkPipelineVertexInputStateCreateInfo Source # 
HasField "pNext" VkPipelineVertexInputStateCreateInfo Source # 
HasField "pVertexAttributeDescriptions" VkPipelineVertexInputStateCreateInfo Source # 

Associated Types

type FieldType ("pVertexAttributeDescriptions" :: Symbol) VkPipelineVertexInputStateCreateInfo :: Type Source #

type FieldOptional ("pVertexAttributeDescriptions" :: Symbol) VkPipelineVertexInputStateCreateInfo :: Bool Source #

type FieldOffset ("pVertexAttributeDescriptions" :: Symbol) VkPipelineVertexInputStateCreateInfo :: Nat Source #

type FieldIsArray ("pVertexAttributeDescriptions" :: Symbol) VkPipelineVertexInputStateCreateInfo :: Bool Source #

HasField "pVertexBindingDescriptions" VkPipelineVertexInputStateCreateInfo Source # 

Associated Types

type FieldType ("pVertexBindingDescriptions" :: Symbol) VkPipelineVertexInputStateCreateInfo :: Type Source #

type FieldOptional ("pVertexBindingDescriptions" :: Symbol) VkPipelineVertexInputStateCreateInfo :: Bool Source #

type FieldOffset ("pVertexBindingDescriptions" :: Symbol) VkPipelineVertexInputStateCreateInfo :: Nat Source #

type FieldIsArray ("pVertexBindingDescriptions" :: Symbol) VkPipelineVertexInputStateCreateInfo :: Bool Source #

HasField "sType" VkPipelineVertexInputStateCreateInfo Source # 
HasField "vertexAttributeDescriptionCount" VkPipelineVertexInputStateCreateInfo Source # 

Associated Types

type FieldType ("vertexAttributeDescriptionCount" :: Symbol) VkPipelineVertexInputStateCreateInfo :: Type Source #

type FieldOptional ("vertexAttributeDescriptionCount" :: Symbol) VkPipelineVertexInputStateCreateInfo :: Bool Source #

type FieldOffset ("vertexAttributeDescriptionCount" :: Symbol) VkPipelineVertexInputStateCreateInfo :: Nat Source #

type FieldIsArray ("vertexAttributeDescriptionCount" :: Symbol) VkPipelineVertexInputStateCreateInfo :: Bool Source #

HasField "vertexBindingDescriptionCount" VkPipelineVertexInputStateCreateInfo Source # 

Associated Types

type FieldType ("vertexBindingDescriptionCount" :: Symbol) VkPipelineVertexInputStateCreateInfo :: Type Source #

type FieldOptional ("vertexBindingDescriptionCount" :: Symbol) VkPipelineVertexInputStateCreateInfo :: Bool Source #

type FieldOffset ("vertexBindingDescriptionCount" :: Symbol) VkPipelineVertexInputStateCreateInfo :: Nat Source #

type FieldIsArray ("vertexBindingDescriptionCount" :: Symbol) VkPipelineVertexInputStateCreateInfo :: Bool Source #

type StructFields VkPipelineVertexInputStateCreateInfo Source # 
type StructFields VkPipelineVertexInputStateCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "vertexBindingDescriptionCount" ((:) Symbol "pVertexBindingDescriptions" ((:) Symbol "vertexAttributeDescriptionCount" ((:) Symbol "pVertexAttributeDescriptions" ([] Symbol)))))))
type CUnionType VkPipelineVertexInputStateCreateInfo Source # 
type ReturnedOnly VkPipelineVertexInputStateCreateInfo Source # 
type StructExtends VkPipelineVertexInputStateCreateInfo Source # 
type FieldType "flags" VkPipelineVertexInputStateCreateInfo Source # 
type FieldType "pNext" VkPipelineVertexInputStateCreateInfo Source # 
type FieldType "pVertexAttributeDescriptions" VkPipelineVertexInputStateCreateInfo Source # 
type FieldType "pVertexBindingDescriptions" VkPipelineVertexInputStateCreateInfo Source # 
type FieldType "sType" VkPipelineVertexInputStateCreateInfo Source # 
type FieldType "vertexAttributeDescriptionCount" VkPipelineVertexInputStateCreateInfo Source # 
type FieldType "vertexAttributeDescriptionCount" VkPipelineVertexInputStateCreateInfo = Word32
type FieldType "vertexBindingDescriptionCount" VkPipelineVertexInputStateCreateInfo Source # 
type FieldType "vertexBindingDescriptionCount" VkPipelineVertexInputStateCreateInfo = Word32
type FieldOptional "flags" VkPipelineVertexInputStateCreateInfo Source # 
type FieldOptional "pNext" VkPipelineVertexInputStateCreateInfo Source # 
type FieldOptional "pVertexAttributeDescriptions" VkPipelineVertexInputStateCreateInfo Source # 
type FieldOptional "pVertexAttributeDescriptions" VkPipelineVertexInputStateCreateInfo = False
type FieldOptional "pVertexBindingDescriptions" VkPipelineVertexInputStateCreateInfo Source # 
type FieldOptional "pVertexBindingDescriptions" VkPipelineVertexInputStateCreateInfo = False
type FieldOptional "sType" VkPipelineVertexInputStateCreateInfo Source # 
type FieldOptional "vertexAttributeDescriptionCount" VkPipelineVertexInputStateCreateInfo Source # 
type FieldOptional "vertexAttributeDescriptionCount" VkPipelineVertexInputStateCreateInfo = True
type FieldOptional "vertexBindingDescriptionCount" VkPipelineVertexInputStateCreateInfo Source # 
type FieldOptional "vertexBindingDescriptionCount" VkPipelineVertexInputStateCreateInfo = True
type FieldOffset "flags" VkPipelineVertexInputStateCreateInfo Source # 
type FieldOffset "pNext" VkPipelineVertexInputStateCreateInfo Source # 
type FieldOffset "pVertexAttributeDescriptions" VkPipelineVertexInputStateCreateInfo Source # 
type FieldOffset "pVertexAttributeDescriptions" VkPipelineVertexInputStateCreateInfo = 40
type FieldOffset "pVertexBindingDescriptions" VkPipelineVertexInputStateCreateInfo Source # 
type FieldOffset "pVertexBindingDescriptions" VkPipelineVertexInputStateCreateInfo = 24
type FieldOffset "sType" VkPipelineVertexInputStateCreateInfo Source # 
type FieldOffset "vertexAttributeDescriptionCount" VkPipelineVertexInputStateCreateInfo Source # 
type FieldOffset "vertexAttributeDescriptionCount" VkPipelineVertexInputStateCreateInfo = 32
type FieldOffset "vertexBindingDescriptionCount" VkPipelineVertexInputStateCreateInfo Source # 
type FieldOffset "vertexBindingDescriptionCount" VkPipelineVertexInputStateCreateInfo = 20
type FieldIsArray "flags" VkPipelineVertexInputStateCreateInfo Source # 
type FieldIsArray "pNext" VkPipelineVertexInputStateCreateInfo Source # 
type FieldIsArray "pVertexAttributeDescriptions" VkPipelineVertexInputStateCreateInfo Source # 
type FieldIsArray "pVertexAttributeDescriptions" VkPipelineVertexInputStateCreateInfo = False
type FieldIsArray "pVertexBindingDescriptions" VkPipelineVertexInputStateCreateInfo Source # 
type FieldIsArray "pVertexBindingDescriptions" VkPipelineVertexInputStateCreateInfo = False
type FieldIsArray "sType" VkPipelineVertexInputStateCreateInfo Source # 
type FieldIsArray "vertexAttributeDescriptionCount" VkPipelineVertexInputStateCreateInfo Source # 
type FieldIsArray "vertexAttributeDescriptionCount" VkPipelineVertexInputStateCreateInfo = False
type FieldIsArray "vertexBindingDescriptionCount" VkPipelineVertexInputStateCreateInfo Source # 
type FieldIsArray "vertexBindingDescriptionCount" VkPipelineVertexInputStateCreateInfo = False

data VkPipelineViewportStateCreateInfo Source #

typedef struct VkPipelineViewportStateCreateInfo {
    VkStructureType sType;
    const void*            pNext;
    VkPipelineViewportStateCreateFlags    flags;
    uint32_t               viewportCount;
    const VkViewport*      pViewports;
    uint32_t               scissorCount;
    const VkRect2D*        pScissors;
} VkPipelineViewportStateCreateInfo;

VkPipelineViewportStateCreateInfo registry at www.khronos.org

Instances

Eq VkPipelineViewportStateCreateInfo Source # 
Ord VkPipelineViewportStateCreateInfo Source # 
Show VkPipelineViewportStateCreateInfo Source # 
Storable VkPipelineViewportStateCreateInfo Source # 
VulkanMarshalPrim VkPipelineViewportStateCreateInfo Source # 
VulkanMarshal VkPipelineViewportStateCreateInfo Source # 
CanWriteField "flags" VkPipelineViewportStateCreateInfo Source # 
CanWriteField "pNext" VkPipelineViewportStateCreateInfo Source # 
CanWriteField "pScissors" VkPipelineViewportStateCreateInfo Source # 
CanWriteField "pViewports" VkPipelineViewportStateCreateInfo Source # 
CanWriteField "sType" VkPipelineViewportStateCreateInfo Source # 
CanWriteField "scissorCount" VkPipelineViewportStateCreateInfo Source # 
CanWriteField "viewportCount" VkPipelineViewportStateCreateInfo Source # 
CanReadField "flags" VkPipelineViewportStateCreateInfo Source # 
CanReadField "pNext" VkPipelineViewportStateCreateInfo Source # 
CanReadField "pScissors" VkPipelineViewportStateCreateInfo Source # 
CanReadField "pViewports" VkPipelineViewportStateCreateInfo Source # 
CanReadField "sType" VkPipelineViewportStateCreateInfo Source # 
CanReadField "scissorCount" VkPipelineViewportStateCreateInfo Source # 
CanReadField "viewportCount" VkPipelineViewportStateCreateInfo Source # 
HasField "flags" VkPipelineViewportStateCreateInfo Source # 
HasField "pNext" VkPipelineViewportStateCreateInfo Source # 
HasField "pScissors" VkPipelineViewportStateCreateInfo Source # 
HasField "pViewports" VkPipelineViewportStateCreateInfo Source # 
HasField "sType" VkPipelineViewportStateCreateInfo Source # 
HasField "scissorCount" VkPipelineViewportStateCreateInfo Source # 
HasField "viewportCount" VkPipelineViewportStateCreateInfo Source # 
type StructFields VkPipelineViewportStateCreateInfo Source # 
type StructFields VkPipelineViewportStateCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "viewportCount" ((:) Symbol "pViewports" ((:) Symbol "scissorCount" ((:) Symbol "pScissors" ([] Symbol)))))))
type CUnionType VkPipelineViewportStateCreateInfo Source # 
type ReturnedOnly VkPipelineViewportStateCreateInfo Source # 
type StructExtends VkPipelineViewportStateCreateInfo Source # 
type FieldType "flags" VkPipelineViewportStateCreateInfo Source # 
type FieldType "pNext" VkPipelineViewportStateCreateInfo Source # 
type FieldType "pScissors" VkPipelineViewportStateCreateInfo Source # 
type FieldType "pViewports" VkPipelineViewportStateCreateInfo Source # 
type FieldType "sType" VkPipelineViewportStateCreateInfo Source # 
type FieldType "scissorCount" VkPipelineViewportStateCreateInfo Source # 
type FieldType "viewportCount" VkPipelineViewportStateCreateInfo Source # 
type FieldOptional "flags" VkPipelineViewportStateCreateInfo Source # 
type FieldOptional "pNext" VkPipelineViewportStateCreateInfo Source # 
type FieldOptional "pScissors" VkPipelineViewportStateCreateInfo Source # 
type FieldOptional "pViewports" VkPipelineViewportStateCreateInfo Source # 
type FieldOptional "sType" VkPipelineViewportStateCreateInfo Source # 
type FieldOptional "scissorCount" VkPipelineViewportStateCreateInfo Source # 
type FieldOptional "viewportCount" VkPipelineViewportStateCreateInfo Source # 
type FieldOffset "flags" VkPipelineViewportStateCreateInfo Source # 
type FieldOffset "pNext" VkPipelineViewportStateCreateInfo Source # 
type FieldOffset "pScissors" VkPipelineViewportStateCreateInfo Source # 
type FieldOffset "pViewports" VkPipelineViewportStateCreateInfo Source # 
type FieldOffset "sType" VkPipelineViewportStateCreateInfo Source # 
type FieldOffset "scissorCount" VkPipelineViewportStateCreateInfo Source # 
type FieldOffset "viewportCount" VkPipelineViewportStateCreateInfo Source # 
type FieldIsArray "flags" VkPipelineViewportStateCreateInfo Source # 
type FieldIsArray "pNext" VkPipelineViewportStateCreateInfo Source # 
type FieldIsArray "pScissors" VkPipelineViewportStateCreateInfo Source # 
type FieldIsArray "pViewports" VkPipelineViewportStateCreateInfo Source # 
type FieldIsArray "sType" VkPipelineViewportStateCreateInfo Source # 
type FieldIsArray "scissorCount" VkPipelineViewportStateCreateInfo Source # 
type FieldIsArray "viewportCount" VkPipelineViewportStateCreateInfo Source # 

data VkPipelineViewportSwizzleStateCreateInfoNV Source #

typedef struct VkPipelineViewportSwizzleStateCreateInfoNV {
    VkStructureType sType;
    const void*            pNext;
    VkPipelineViewportSwizzleStateCreateFlagsNV    flags;
    uint32_t               viewportCount;
    const VkViewportSwizzleNV*      pViewportSwizzles;
} VkPipelineViewportSwizzleStateCreateInfoNV;

VkPipelineViewportSwizzleStateCreateInfoNV registry at www.khronos.org

Instances

Eq VkPipelineViewportSwizzleStateCreateInfoNV Source # 
Ord VkPipelineViewportSwizzleStateCreateInfoNV Source # 
Show VkPipelineViewportSwizzleStateCreateInfoNV Source # 
Storable VkPipelineViewportSwizzleStateCreateInfoNV Source # 
VulkanMarshalPrim VkPipelineViewportSwizzleStateCreateInfoNV Source # 
VulkanMarshal VkPipelineViewportSwizzleStateCreateInfoNV Source # 
CanWriteField "flags" VkPipelineViewportSwizzleStateCreateInfoNV Source # 
CanWriteField "pNext" VkPipelineViewportSwizzleStateCreateInfoNV Source # 
CanWriteField "pViewportSwizzles" VkPipelineViewportSwizzleStateCreateInfoNV Source # 
CanWriteField "sType" VkPipelineViewportSwizzleStateCreateInfoNV Source # 
CanWriteField "viewportCount" VkPipelineViewportSwizzleStateCreateInfoNV Source # 
CanReadField "flags" VkPipelineViewportSwizzleStateCreateInfoNV Source # 
CanReadField "pNext" VkPipelineViewportSwizzleStateCreateInfoNV Source # 
CanReadField "pViewportSwizzles" VkPipelineViewportSwizzleStateCreateInfoNV Source # 
CanReadField "sType" VkPipelineViewportSwizzleStateCreateInfoNV Source # 
CanReadField "viewportCount" VkPipelineViewportSwizzleStateCreateInfoNV Source # 
HasField "flags" VkPipelineViewportSwizzleStateCreateInfoNV Source # 
HasField "pNext" VkPipelineViewportSwizzleStateCreateInfoNV Source # 
HasField "pViewportSwizzles" VkPipelineViewportSwizzleStateCreateInfoNV Source # 
HasField "sType" VkPipelineViewportSwizzleStateCreateInfoNV Source # 
HasField "viewportCount" VkPipelineViewportSwizzleStateCreateInfoNV Source # 
type StructFields VkPipelineViewportSwizzleStateCreateInfoNV Source # 
type StructFields VkPipelineViewportSwizzleStateCreateInfoNV = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "viewportCount" ((:) Symbol "pViewportSwizzles" ([] Symbol)))))
type CUnionType VkPipelineViewportSwizzleStateCreateInfoNV Source # 
type ReturnedOnly VkPipelineViewportSwizzleStateCreateInfoNV Source # 
type StructExtends VkPipelineViewportSwizzleStateCreateInfoNV Source # 
type FieldType "flags" VkPipelineViewportSwizzleStateCreateInfoNV Source # 
type FieldType "pNext" VkPipelineViewportSwizzleStateCreateInfoNV Source # 
type FieldType "pViewportSwizzles" VkPipelineViewportSwizzleStateCreateInfoNV Source # 
type FieldType "sType" VkPipelineViewportSwizzleStateCreateInfoNV Source # 
type FieldType "viewportCount" VkPipelineViewportSwizzleStateCreateInfoNV Source # 
type FieldOptional "flags" VkPipelineViewportSwizzleStateCreateInfoNV Source # 
type FieldOptional "pNext" VkPipelineViewportSwizzleStateCreateInfoNV Source # 
type FieldOptional "pViewportSwizzles" VkPipelineViewportSwizzleStateCreateInfoNV Source # 
type FieldOptional "sType" VkPipelineViewportSwizzleStateCreateInfoNV Source # 
type FieldOptional "viewportCount" VkPipelineViewportSwizzleStateCreateInfoNV Source # 
type FieldOffset "flags" VkPipelineViewportSwizzleStateCreateInfoNV Source # 
type FieldOffset "pNext" VkPipelineViewportSwizzleStateCreateInfoNV Source # 
type FieldOffset "pViewportSwizzles" VkPipelineViewportSwizzleStateCreateInfoNV Source # 
type FieldOffset "sType" VkPipelineViewportSwizzleStateCreateInfoNV Source # 
type FieldOffset "viewportCount" VkPipelineViewportSwizzleStateCreateInfoNV Source # 
type FieldIsArray "flags" VkPipelineViewportSwizzleStateCreateInfoNV Source # 
type FieldIsArray "pNext" VkPipelineViewportSwizzleStateCreateInfoNV Source # 
type FieldIsArray "pViewportSwizzles" VkPipelineViewportSwizzleStateCreateInfoNV Source # 
type FieldIsArray "sType" VkPipelineViewportSwizzleStateCreateInfoNV Source # 
type FieldIsArray "viewportCount" VkPipelineViewportSwizzleStateCreateInfoNV Source # 

data VkPipelineViewportWScalingStateCreateInfoNV Source #

typedef struct VkPipelineViewportWScalingStateCreateInfoNV {
    VkStructureType sType;
    const void*                      pNext;
    VkBool32               viewportWScalingEnable;
    uint32_t               viewportCount;
    const VkViewportWScalingNV*      pViewportWScalings;
} VkPipelineViewportWScalingStateCreateInfoNV;

VkPipelineViewportWScalingStateCreateInfoNV registry at www.khronos.org

Instances

Eq VkPipelineViewportWScalingStateCreateInfoNV Source # 
Ord VkPipelineViewportWScalingStateCreateInfoNV Source # 
Show VkPipelineViewportWScalingStateCreateInfoNV Source # 
Storable VkPipelineViewportWScalingStateCreateInfoNV Source # 
VulkanMarshalPrim VkPipelineViewportWScalingStateCreateInfoNV Source # 
VulkanMarshal VkPipelineViewportWScalingStateCreateInfoNV Source # 
CanWriteField "pNext" VkPipelineViewportWScalingStateCreateInfoNV Source # 
CanWriteField "pViewportWScalings" VkPipelineViewportWScalingStateCreateInfoNV Source # 
CanWriteField "sType" VkPipelineViewportWScalingStateCreateInfoNV Source # 
CanWriteField "viewportCount" VkPipelineViewportWScalingStateCreateInfoNV Source # 
CanWriteField "viewportWScalingEnable" VkPipelineViewportWScalingStateCreateInfoNV Source # 
CanReadField "pNext" VkPipelineViewportWScalingStateCreateInfoNV Source # 
CanReadField "pViewportWScalings" VkPipelineViewportWScalingStateCreateInfoNV Source # 
CanReadField "sType" VkPipelineViewportWScalingStateCreateInfoNV Source # 
CanReadField "viewportCount" VkPipelineViewportWScalingStateCreateInfoNV Source # 
CanReadField "viewportWScalingEnable" VkPipelineViewportWScalingStateCreateInfoNV Source # 
HasField "pNext" VkPipelineViewportWScalingStateCreateInfoNV Source # 
HasField "pViewportWScalings" VkPipelineViewportWScalingStateCreateInfoNV Source # 
HasField "sType" VkPipelineViewportWScalingStateCreateInfoNV Source # 
HasField "viewportCount" VkPipelineViewportWScalingStateCreateInfoNV Source # 
HasField "viewportWScalingEnable" VkPipelineViewportWScalingStateCreateInfoNV Source # 
type StructFields VkPipelineViewportWScalingStateCreateInfoNV Source # 
type StructFields VkPipelineViewportWScalingStateCreateInfoNV = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "viewportWScalingEnable" ((:) Symbol "viewportCount" ((:) Symbol "pViewportWScalings" ([] Symbol)))))
type CUnionType VkPipelineViewportWScalingStateCreateInfoNV Source # 
type ReturnedOnly VkPipelineViewportWScalingStateCreateInfoNV Source # 
type StructExtends VkPipelineViewportWScalingStateCreateInfoNV Source # 
type FieldType "pNext" VkPipelineViewportWScalingStateCreateInfoNV Source # 
type FieldType "pViewportWScalings" VkPipelineViewportWScalingStateCreateInfoNV Source # 
type FieldType "sType" VkPipelineViewportWScalingStateCreateInfoNV Source # 
type FieldType "viewportCount" VkPipelineViewportWScalingStateCreateInfoNV Source # 
type FieldType "viewportWScalingEnable" VkPipelineViewportWScalingStateCreateInfoNV Source # 
type FieldOptional "pNext" VkPipelineViewportWScalingStateCreateInfoNV Source # 
type FieldOptional "pViewportWScalings" VkPipelineViewportWScalingStateCreateInfoNV Source # 
type FieldOptional "sType" VkPipelineViewportWScalingStateCreateInfoNV Source # 
type FieldOptional "viewportCount" VkPipelineViewportWScalingStateCreateInfoNV Source # 
type FieldOptional "viewportWScalingEnable" VkPipelineViewportWScalingStateCreateInfoNV Source # 
type FieldOffset "pNext" VkPipelineViewportWScalingStateCreateInfoNV Source # 
type FieldOffset "pViewportWScalings" VkPipelineViewportWScalingStateCreateInfoNV Source # 
type FieldOffset "sType" VkPipelineViewportWScalingStateCreateInfoNV Source # 
type FieldOffset "viewportCount" VkPipelineViewportWScalingStateCreateInfoNV Source # 
type FieldOffset "viewportWScalingEnable" VkPipelineViewportWScalingStateCreateInfoNV Source # 
type FieldOffset "viewportWScalingEnable" VkPipelineViewportWScalingStateCreateInfoNV = 16
type FieldIsArray "pNext" VkPipelineViewportWScalingStateCreateInfoNV Source # 
type FieldIsArray "pViewportWScalings" VkPipelineViewportWScalingStateCreateInfoNV Source # 
type FieldIsArray "sType" VkPipelineViewportWScalingStateCreateInfoNV Source # 
type FieldIsArray "viewportCount" VkPipelineViewportWScalingStateCreateInfoNV Source # 
type FieldIsArray "viewportWScalingEnable" VkPipelineViewportWScalingStateCreateInfoNV Source # 

newtype VkPointClippingBehavior Source #

Instances

Bounded VkPointClippingBehavior Source # 
Enum VkPointClippingBehavior Source # 
Eq VkPointClippingBehavior Source # 
Data VkPointClippingBehavior Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkPointClippingBehavior -> c VkPointClippingBehavior #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkPointClippingBehavior #

toConstr :: VkPointClippingBehavior -> Constr #

dataTypeOf :: VkPointClippingBehavior -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkPointClippingBehavior) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkPointClippingBehavior) #

gmapT :: (forall b. Data b => b -> b) -> VkPointClippingBehavior -> VkPointClippingBehavior #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkPointClippingBehavior -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkPointClippingBehavior -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkPointClippingBehavior -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkPointClippingBehavior -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkPointClippingBehavior -> m VkPointClippingBehavior #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPointClippingBehavior -> m VkPointClippingBehavior #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPointClippingBehavior -> m VkPointClippingBehavior #

Num VkPointClippingBehavior Source # 
Ord VkPointClippingBehavior Source # 
Read VkPointClippingBehavior Source # 
Show VkPointClippingBehavior Source # 
Generic VkPointClippingBehavior Source # 
Storable VkPointClippingBehavior Source # 
type Rep VkPointClippingBehavior Source # 
type Rep VkPointClippingBehavior = D1 (MetaData "VkPointClippingBehavior" "Graphics.Vulkan.Types.Enum.PointClippingBehavior" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkPointClippingBehavior" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

newtype VkPointClippingBehaviorKHR Source #

Instances

Bounded VkPointClippingBehaviorKHR Source # 
Enum VkPointClippingBehaviorKHR Source # 
Eq VkPointClippingBehaviorKHR Source # 
Integral VkPointClippingBehaviorKHR Source # 
Data VkPointClippingBehaviorKHR Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkPointClippingBehaviorKHR -> c VkPointClippingBehaviorKHR #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkPointClippingBehaviorKHR #

toConstr :: VkPointClippingBehaviorKHR -> Constr #

dataTypeOf :: VkPointClippingBehaviorKHR -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkPointClippingBehaviorKHR) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkPointClippingBehaviorKHR) #

gmapT :: (forall b. Data b => b -> b) -> VkPointClippingBehaviorKHR -> VkPointClippingBehaviorKHR #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkPointClippingBehaviorKHR -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkPointClippingBehaviorKHR -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkPointClippingBehaviorKHR -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkPointClippingBehaviorKHR -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkPointClippingBehaviorKHR -> m VkPointClippingBehaviorKHR #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPointClippingBehaviorKHR -> m VkPointClippingBehaviorKHR #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkPointClippingBehaviorKHR -> m VkPointClippingBehaviorKHR #

Num VkPointClippingBehaviorKHR Source # 
Ord VkPointClippingBehaviorKHR Source # 
Read VkPointClippingBehaviorKHR Source # 
Real VkPointClippingBehaviorKHR Source # 
Show VkPointClippingBehaviorKHR Source # 
Generic VkPointClippingBehaviorKHR Source # 
Storable VkPointClippingBehaviorKHR Source # 
Bits VkPointClippingBehaviorKHR Source # 

Methods

(.&.) :: VkPointClippingBehaviorKHR -> VkPointClippingBehaviorKHR -> VkPointClippingBehaviorKHR #

(.|.) :: VkPointClippingBehaviorKHR -> VkPointClippingBehaviorKHR -> VkPointClippingBehaviorKHR #

xor :: VkPointClippingBehaviorKHR -> VkPointClippingBehaviorKHR -> VkPointClippingBehaviorKHR #

complement :: VkPointClippingBehaviorKHR -> VkPointClippingBehaviorKHR #

shift :: VkPointClippingBehaviorKHR -> Int -> VkPointClippingBehaviorKHR #

rotate :: VkPointClippingBehaviorKHR -> Int -> VkPointClippingBehaviorKHR #

zeroBits :: VkPointClippingBehaviorKHR #

bit :: Int -> VkPointClippingBehaviorKHR #

setBit :: VkPointClippingBehaviorKHR -> Int -> VkPointClippingBehaviorKHR #

clearBit :: VkPointClippingBehaviorKHR -> Int -> VkPointClippingBehaviorKHR #

complementBit :: VkPointClippingBehaviorKHR -> Int -> VkPointClippingBehaviorKHR #

testBit :: VkPointClippingBehaviorKHR -> Int -> Bool #

bitSizeMaybe :: VkPointClippingBehaviorKHR -> Maybe Int #

bitSize :: VkPointClippingBehaviorKHR -> Int #

isSigned :: VkPointClippingBehaviorKHR -> Bool #

shiftL :: VkPointClippingBehaviorKHR -> Int -> VkPointClippingBehaviorKHR #

unsafeShiftL :: VkPointClippingBehaviorKHR -> Int -> VkPointClippingBehaviorKHR #

shiftR :: VkPointClippingBehaviorKHR -> Int -> VkPointClippingBehaviorKHR #

unsafeShiftR :: VkPointClippingBehaviorKHR -> Int -> VkPointClippingBehaviorKHR #

rotateL :: VkPointClippingBehaviorKHR -> Int -> VkPointClippingBehaviorKHR #

rotateR :: VkPointClippingBehaviorKHR -> Int -> VkPointClippingBehaviorKHR #

popCount :: VkPointClippingBehaviorKHR -> Int #

FiniteBits VkPointClippingBehaviorKHR Source # 
type Rep VkPointClippingBehaviorKHR Source # 
type Rep VkPointClippingBehaviorKHR = D1 (MetaData "VkPointClippingBehaviorKHR" "Graphics.Vulkan.Types.Enum.PointClippingBehavior" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkPointClippingBehaviorKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

data VkSubpassDependency Source #

typedef struct VkSubpassDependency {
    uint32_t               srcSubpass;
    uint32_t               dstSubpass;
    VkPipelineStageFlags   srcStageMask;
    VkPipelineStageFlags   dstStageMask;
    VkAccessFlags          srcAccessMask;
    VkAccessFlags          dstAccessMask;
    VkDependencyFlags      dependencyFlags;
} VkSubpassDependency;

VkSubpassDependency registry at www.khronos.org

Instances

Eq VkSubpassDependency Source # 
Ord VkSubpassDependency Source # 
Show VkSubpassDependency Source # 
Storable VkSubpassDependency Source # 
VulkanMarshalPrim VkSubpassDependency Source # 
VulkanMarshal VkSubpassDependency Source # 
CanWriteField "dependencyFlags" VkSubpassDependency Source # 
CanWriteField "dstAccessMask" VkSubpassDependency Source # 
CanWriteField "dstStageMask" VkSubpassDependency Source # 
CanWriteField "dstSubpass" VkSubpassDependency Source # 
CanWriteField "srcAccessMask" VkSubpassDependency Source # 
CanWriteField "srcStageMask" VkSubpassDependency Source # 
CanWriteField "srcSubpass" VkSubpassDependency Source # 
CanReadField "dependencyFlags" VkSubpassDependency Source # 
CanReadField "dstAccessMask" VkSubpassDependency Source # 
CanReadField "dstStageMask" VkSubpassDependency Source # 
CanReadField "dstSubpass" VkSubpassDependency Source # 
CanReadField "srcAccessMask" VkSubpassDependency Source # 
CanReadField "srcStageMask" VkSubpassDependency Source # 
CanReadField "srcSubpass" VkSubpassDependency Source # 
HasField "dependencyFlags" VkSubpassDependency Source # 

Associated Types

type FieldType ("dependencyFlags" :: Symbol) VkSubpassDependency :: Type Source #

type FieldOptional ("dependencyFlags" :: Symbol) VkSubpassDependency :: Bool Source #

type FieldOffset ("dependencyFlags" :: Symbol) VkSubpassDependency :: Nat Source #

type FieldIsArray ("dependencyFlags" :: Symbol) VkSubpassDependency :: Bool Source #

HasField "dstAccessMask" VkSubpassDependency Source # 

Associated Types

type FieldType ("dstAccessMask" :: Symbol) VkSubpassDependency :: Type Source #

type FieldOptional ("dstAccessMask" :: Symbol) VkSubpassDependency :: Bool Source #

type FieldOffset ("dstAccessMask" :: Symbol) VkSubpassDependency :: Nat Source #

type FieldIsArray ("dstAccessMask" :: Symbol) VkSubpassDependency :: Bool Source #

HasField "dstStageMask" VkSubpassDependency Source # 

Associated Types

type FieldType ("dstStageMask" :: Symbol) VkSubpassDependency :: Type Source #

type FieldOptional ("dstStageMask" :: Symbol) VkSubpassDependency :: Bool Source #

type FieldOffset ("dstStageMask" :: Symbol) VkSubpassDependency :: Nat Source #

type FieldIsArray ("dstStageMask" :: Symbol) VkSubpassDependency :: Bool Source #

HasField "dstSubpass" VkSubpassDependency Source # 

Associated Types

type FieldType ("dstSubpass" :: Symbol) VkSubpassDependency :: Type Source #

type FieldOptional ("dstSubpass" :: Symbol) VkSubpassDependency :: Bool Source #

type FieldOffset ("dstSubpass" :: Symbol) VkSubpassDependency :: Nat Source #

type FieldIsArray ("dstSubpass" :: Symbol) VkSubpassDependency :: Bool Source #

HasField "srcAccessMask" VkSubpassDependency Source # 

Associated Types

type FieldType ("srcAccessMask" :: Symbol) VkSubpassDependency :: Type Source #

type FieldOptional ("srcAccessMask" :: Symbol) VkSubpassDependency :: Bool Source #

type FieldOffset ("srcAccessMask" :: Symbol) VkSubpassDependency :: Nat Source #

type FieldIsArray ("srcAccessMask" :: Symbol) VkSubpassDependency :: Bool Source #

HasField "srcStageMask" VkSubpassDependency Source # 

Associated Types

type FieldType ("srcStageMask" :: Symbol) VkSubpassDependency :: Type Source #

type FieldOptional ("srcStageMask" :: Symbol) VkSubpassDependency :: Bool Source #

type FieldOffset ("srcStageMask" :: Symbol) VkSubpassDependency :: Nat Source #

type FieldIsArray ("srcStageMask" :: Symbol) VkSubpassDependency :: Bool Source #

HasField "srcSubpass" VkSubpassDependency Source # 

Associated Types

type FieldType ("srcSubpass" :: Symbol) VkSubpassDependency :: Type Source #

type FieldOptional ("srcSubpass" :: Symbol) VkSubpassDependency :: Bool Source #

type FieldOffset ("srcSubpass" :: Symbol) VkSubpassDependency :: Nat Source #

type FieldIsArray ("srcSubpass" :: Symbol) VkSubpassDependency :: Bool Source #

type StructFields VkSubpassDependency Source # 
type StructFields VkSubpassDependency = (:) Symbol "srcSubpass" ((:) Symbol "dstSubpass" ((:) Symbol "srcStageMask" ((:) Symbol "dstStageMask" ((:) Symbol "srcAccessMask" ((:) Symbol "dstAccessMask" ((:) Symbol "dependencyFlags" ([] Symbol)))))))
type CUnionType VkSubpassDependency Source # 
type ReturnedOnly VkSubpassDependency Source # 
type StructExtends VkSubpassDependency Source # 
type FieldType "dependencyFlags" VkSubpassDependency Source # 
type FieldType "dstAccessMask" VkSubpassDependency Source # 
type FieldType "dstStageMask" VkSubpassDependency Source # 
type FieldType "dstSubpass" VkSubpassDependency Source # 
type FieldType "srcAccessMask" VkSubpassDependency Source # 
type FieldType "srcStageMask" VkSubpassDependency Source # 
type FieldType "srcSubpass" VkSubpassDependency Source # 
type FieldOptional "dependencyFlags" VkSubpassDependency Source # 
type FieldOptional "dependencyFlags" VkSubpassDependency = True
type FieldOptional "dstAccessMask" VkSubpassDependency Source # 
type FieldOptional "dstAccessMask" VkSubpassDependency = True
type FieldOptional "dstStageMask" VkSubpassDependency Source # 
type FieldOptional "dstSubpass" VkSubpassDependency Source # 
type FieldOptional "srcAccessMask" VkSubpassDependency Source # 
type FieldOptional "srcAccessMask" VkSubpassDependency = True
type FieldOptional "srcStageMask" VkSubpassDependency Source # 
type FieldOptional "srcSubpass" VkSubpassDependency Source # 
type FieldOffset "dependencyFlags" VkSubpassDependency Source # 
type FieldOffset "dependencyFlags" VkSubpassDependency = 24
type FieldOffset "dstAccessMask" VkSubpassDependency Source # 
type FieldOffset "dstAccessMask" VkSubpassDependency = 20
type FieldOffset "dstStageMask" VkSubpassDependency Source # 
type FieldOffset "dstStageMask" VkSubpassDependency = 12
type FieldOffset "dstSubpass" VkSubpassDependency Source # 
type FieldOffset "dstSubpass" VkSubpassDependency = 4
type FieldOffset "srcAccessMask" VkSubpassDependency Source # 
type FieldOffset "srcAccessMask" VkSubpassDependency = 16
type FieldOffset "srcStageMask" VkSubpassDependency Source # 
type FieldOffset "srcStageMask" VkSubpassDependency = 8
type FieldOffset "srcSubpass" VkSubpassDependency Source # 
type FieldOffset "srcSubpass" VkSubpassDependency = 0
type FieldIsArray "dependencyFlags" VkSubpassDependency Source # 
type FieldIsArray "dependencyFlags" VkSubpassDependency = False
type FieldIsArray "dstAccessMask" VkSubpassDependency Source # 
type FieldIsArray "dstAccessMask" VkSubpassDependency = False
type FieldIsArray "dstStageMask" VkSubpassDependency Source # 
type FieldIsArray "dstStageMask" VkSubpassDependency = False
type FieldIsArray "dstSubpass" VkSubpassDependency Source # 
type FieldIsArray "srcAccessMask" VkSubpassDependency Source # 
type FieldIsArray "srcAccessMask" VkSubpassDependency = False
type FieldIsArray "srcStageMask" VkSubpassDependency Source # 
type FieldIsArray "srcStageMask" VkSubpassDependency = False
type FieldIsArray "srcSubpass" VkSubpassDependency Source # 

data VkSubpassDescription Source #

typedef struct VkSubpassDescription {
    VkSubpassDescriptionFlags flags;
    VkPipelineBindPoint    pipelineBindPoint;
    uint32_t               inputAttachmentCount;
    const VkAttachmentReference* pInputAttachments;
    uint32_t               colorAttachmentCount;
    const VkAttachmentReference* pColorAttachments;
    const VkAttachmentReference* pResolveAttachments;
    const VkAttachmentReference* pDepthStencilAttachment;
    uint32_t               preserveAttachmentCount;
    const uint32_t* pPreserveAttachments;
} VkSubpassDescription;

VkSubpassDescription registry at www.khronos.org

Instances

Eq VkSubpassDescription Source # 
Ord VkSubpassDescription Source # 
Show VkSubpassDescription Source # 
Storable VkSubpassDescription Source # 
VulkanMarshalPrim VkSubpassDescription Source # 
VulkanMarshal VkSubpassDescription Source # 
CanWriteField "colorAttachmentCount" VkSubpassDescription Source # 

Methods

writeField :: Ptr VkSubpassDescription -> FieldType "colorAttachmentCount" VkSubpassDescription -> IO () Source #

CanWriteField "flags" VkSubpassDescription Source # 
CanWriteField "inputAttachmentCount" VkSubpassDescription Source # 

Methods

writeField :: Ptr VkSubpassDescription -> FieldType "inputAttachmentCount" VkSubpassDescription -> IO () Source #

CanWriteField "pColorAttachments" VkSubpassDescription Source # 
CanWriteField "pDepthStencilAttachment" VkSubpassDescription Source # 

Methods

writeField :: Ptr VkSubpassDescription -> FieldType "pDepthStencilAttachment" VkSubpassDescription -> IO () Source #

CanWriteField "pInputAttachments" VkSubpassDescription Source # 
CanWriteField "pPreserveAttachments" VkSubpassDescription Source # 

Methods

writeField :: Ptr VkSubpassDescription -> FieldType "pPreserveAttachments" VkSubpassDescription -> IO () Source #

CanWriteField "pResolveAttachments" VkSubpassDescription Source # 

Methods

writeField :: Ptr VkSubpassDescription -> FieldType "pResolveAttachments" VkSubpassDescription -> IO () Source #

CanWriteField "pipelineBindPoint" VkSubpassDescription Source # 
CanWriteField "preserveAttachmentCount" VkSubpassDescription Source # 

Methods

writeField :: Ptr VkSubpassDescription -> FieldType "preserveAttachmentCount" VkSubpassDescription -> IO () Source #

CanReadField "colorAttachmentCount" VkSubpassDescription Source # 
CanReadField "flags" VkSubpassDescription Source # 
CanReadField "inputAttachmentCount" VkSubpassDescription Source # 
CanReadField "pColorAttachments" VkSubpassDescription Source # 
CanReadField "pDepthStencilAttachment" VkSubpassDescription Source # 
CanReadField "pInputAttachments" VkSubpassDescription Source # 
CanReadField "pPreserveAttachments" VkSubpassDescription Source # 
CanReadField "pResolveAttachments" VkSubpassDescription Source # 
CanReadField "pipelineBindPoint" VkSubpassDescription Source # 
CanReadField "preserveAttachmentCount" VkSubpassDescription Source # 
HasField "colorAttachmentCount" VkSubpassDescription Source # 

Associated Types

type FieldType ("colorAttachmentCount" :: Symbol) VkSubpassDescription :: Type Source #

type FieldOptional ("colorAttachmentCount" :: Symbol) VkSubpassDescription :: Bool Source #

type FieldOffset ("colorAttachmentCount" :: Symbol) VkSubpassDescription :: Nat Source #

type FieldIsArray ("colorAttachmentCount" :: Symbol) VkSubpassDescription :: Bool Source #

HasField "flags" VkSubpassDescription Source # 
HasField "inputAttachmentCount" VkSubpassDescription Source # 

Associated Types

type FieldType ("inputAttachmentCount" :: Symbol) VkSubpassDescription :: Type Source #

type FieldOptional ("inputAttachmentCount" :: Symbol) VkSubpassDescription :: Bool Source #

type FieldOffset ("inputAttachmentCount" :: Symbol) VkSubpassDescription :: Nat Source #

type FieldIsArray ("inputAttachmentCount" :: Symbol) VkSubpassDescription :: Bool Source #

HasField "pColorAttachments" VkSubpassDescription Source # 

Associated Types

type FieldType ("pColorAttachments" :: Symbol) VkSubpassDescription :: Type Source #

type FieldOptional ("pColorAttachments" :: Symbol) VkSubpassDescription :: Bool Source #

type FieldOffset ("pColorAttachments" :: Symbol) VkSubpassDescription :: Nat Source #

type FieldIsArray ("pColorAttachments" :: Symbol) VkSubpassDescription :: Bool Source #

HasField "pDepthStencilAttachment" VkSubpassDescription Source # 

Associated Types

type FieldType ("pDepthStencilAttachment" :: Symbol) VkSubpassDescription :: Type Source #

type FieldOptional ("pDepthStencilAttachment" :: Symbol) VkSubpassDescription :: Bool Source #

type FieldOffset ("pDepthStencilAttachment" :: Symbol) VkSubpassDescription :: Nat Source #

type FieldIsArray ("pDepthStencilAttachment" :: Symbol) VkSubpassDescription :: Bool Source #

HasField "pInputAttachments" VkSubpassDescription Source # 

Associated Types

type FieldType ("pInputAttachments" :: Symbol) VkSubpassDescription :: Type Source #

type FieldOptional ("pInputAttachments" :: Symbol) VkSubpassDescription :: Bool Source #

type FieldOffset ("pInputAttachments" :: Symbol) VkSubpassDescription :: Nat Source #

type FieldIsArray ("pInputAttachments" :: Symbol) VkSubpassDescription :: Bool Source #

HasField "pPreserveAttachments" VkSubpassDescription Source # 

Associated Types

type FieldType ("pPreserveAttachments" :: Symbol) VkSubpassDescription :: Type Source #

type FieldOptional ("pPreserveAttachments" :: Symbol) VkSubpassDescription :: Bool Source #

type FieldOffset ("pPreserveAttachments" :: Symbol) VkSubpassDescription :: Nat Source #

type FieldIsArray ("pPreserveAttachments" :: Symbol) VkSubpassDescription :: Bool Source #

HasField "pResolveAttachments" VkSubpassDescription Source # 

Associated Types

type FieldType ("pResolveAttachments" :: Symbol) VkSubpassDescription :: Type Source #

type FieldOptional ("pResolveAttachments" :: Symbol) VkSubpassDescription :: Bool Source #

type FieldOffset ("pResolveAttachments" :: Symbol) VkSubpassDescription :: Nat Source #

type FieldIsArray ("pResolveAttachments" :: Symbol) VkSubpassDescription :: Bool Source #

HasField "pipelineBindPoint" VkSubpassDescription Source # 

Associated Types

type FieldType ("pipelineBindPoint" :: Symbol) VkSubpassDescription :: Type Source #

type FieldOptional ("pipelineBindPoint" :: Symbol) VkSubpassDescription :: Bool Source #

type FieldOffset ("pipelineBindPoint" :: Symbol) VkSubpassDescription :: Nat Source #

type FieldIsArray ("pipelineBindPoint" :: Symbol) VkSubpassDescription :: Bool Source #

HasField "preserveAttachmentCount" VkSubpassDescription Source # 

Associated Types

type FieldType ("preserveAttachmentCount" :: Symbol) VkSubpassDescription :: Type Source #

type FieldOptional ("preserveAttachmentCount" :: Symbol) VkSubpassDescription :: Bool Source #

type FieldOffset ("preserveAttachmentCount" :: Symbol) VkSubpassDescription :: Nat Source #

type FieldIsArray ("preserveAttachmentCount" :: Symbol) VkSubpassDescription :: Bool Source #

type StructFields VkSubpassDescription Source # 
type StructFields VkSubpassDescription = (:) Symbol "flags" ((:) Symbol "pipelineBindPoint" ((:) Symbol "inputAttachmentCount" ((:) Symbol "pInputAttachments" ((:) Symbol "colorAttachmentCount" ((:) Symbol "pColorAttachments" ((:) Symbol "pResolveAttachments" ((:) Symbol "pDepthStencilAttachment" ((:) Symbol "preserveAttachmentCount" ((:) Symbol "pPreserveAttachments" ([] Symbol))))))))))
type CUnionType VkSubpassDescription Source # 
type ReturnedOnly VkSubpassDescription Source # 
type StructExtends VkSubpassDescription Source # 
type FieldType "colorAttachmentCount" VkSubpassDescription Source # 
type FieldType "colorAttachmentCount" VkSubpassDescription = Word32
type FieldType "flags" VkSubpassDescription Source # 
type FieldType "inputAttachmentCount" VkSubpassDescription Source # 
type FieldType "inputAttachmentCount" VkSubpassDescription = Word32
type FieldType "pColorAttachments" VkSubpassDescription Source # 
type FieldType "pDepthStencilAttachment" VkSubpassDescription Source # 
type FieldType "pDepthStencilAttachment" VkSubpassDescription = Ptr VkAttachmentReference
type FieldType "pInputAttachments" VkSubpassDescription Source # 
type FieldType "pPreserveAttachments" VkSubpassDescription Source # 
type FieldType "pPreserveAttachments" VkSubpassDescription = Ptr Word32
type FieldType "pResolveAttachments" VkSubpassDescription Source # 
type FieldType "pipelineBindPoint" VkSubpassDescription Source # 
type FieldType "preserveAttachmentCount" VkSubpassDescription Source # 
type FieldType "preserveAttachmentCount" VkSubpassDescription = Word32
type FieldOptional "colorAttachmentCount" VkSubpassDescription Source # 
type FieldOptional "colorAttachmentCount" VkSubpassDescription = True
type FieldOptional "flags" VkSubpassDescription Source # 
type FieldOptional "inputAttachmentCount" VkSubpassDescription Source # 
type FieldOptional "inputAttachmentCount" VkSubpassDescription = True
type FieldOptional "pColorAttachments" VkSubpassDescription Source # 
type FieldOptional "pColorAttachments" VkSubpassDescription = False
type FieldOptional "pDepthStencilAttachment" VkSubpassDescription Source # 
type FieldOptional "pDepthStencilAttachment" VkSubpassDescription = True
type FieldOptional "pInputAttachments" VkSubpassDescription Source # 
type FieldOptional "pInputAttachments" VkSubpassDescription = False
type FieldOptional "pPreserveAttachments" VkSubpassDescription Source # 
type FieldOptional "pPreserveAttachments" VkSubpassDescription = False
type FieldOptional "pResolveAttachments" VkSubpassDescription Source # 
type FieldOptional "pResolveAttachments" VkSubpassDescription = True
type FieldOptional "pipelineBindPoint" VkSubpassDescription Source # 
type FieldOptional "pipelineBindPoint" VkSubpassDescription = False
type FieldOptional "preserveAttachmentCount" VkSubpassDescription Source # 
type FieldOptional "preserveAttachmentCount" VkSubpassDescription = True
type FieldOffset "colorAttachmentCount" VkSubpassDescription Source # 
type FieldOffset "colorAttachmentCount" VkSubpassDescription = 24
type FieldOffset "flags" VkSubpassDescription Source # 
type FieldOffset "inputAttachmentCount" VkSubpassDescription Source # 
type FieldOffset "inputAttachmentCount" VkSubpassDescription = 8
type FieldOffset "pColorAttachments" VkSubpassDescription Source # 
type FieldOffset "pColorAttachments" VkSubpassDescription = 32
type FieldOffset "pDepthStencilAttachment" VkSubpassDescription Source # 
type FieldOffset "pDepthStencilAttachment" VkSubpassDescription = 48
type FieldOffset "pInputAttachments" VkSubpassDescription Source # 
type FieldOffset "pInputAttachments" VkSubpassDescription = 16
type FieldOffset "pPreserveAttachments" VkSubpassDescription Source # 
type FieldOffset "pPreserveAttachments" VkSubpassDescription = 64
type FieldOffset "pResolveAttachments" VkSubpassDescription Source # 
type FieldOffset "pResolveAttachments" VkSubpassDescription = 40
type FieldOffset "pipelineBindPoint" VkSubpassDescription Source # 
type FieldOffset "pipelineBindPoint" VkSubpassDescription = 4
type FieldOffset "preserveAttachmentCount" VkSubpassDescription Source # 
type FieldOffset "preserveAttachmentCount" VkSubpassDescription = 56
type FieldIsArray "colorAttachmentCount" VkSubpassDescription Source # 
type FieldIsArray "colorAttachmentCount" VkSubpassDescription = False
type FieldIsArray "flags" VkSubpassDescription Source # 
type FieldIsArray "inputAttachmentCount" VkSubpassDescription Source # 
type FieldIsArray "inputAttachmentCount" VkSubpassDescription = False
type FieldIsArray "pColorAttachments" VkSubpassDescription Source # 
type FieldIsArray "pColorAttachments" VkSubpassDescription = False
type FieldIsArray "pDepthStencilAttachment" VkSubpassDescription Source # 
type FieldIsArray "pDepthStencilAttachment" VkSubpassDescription = False
type FieldIsArray "pInputAttachments" VkSubpassDescription Source # 
type FieldIsArray "pInputAttachments" VkSubpassDescription = False
type FieldIsArray "pPreserveAttachments" VkSubpassDescription Source # 
type FieldIsArray "pPreserveAttachments" VkSubpassDescription = False
type FieldIsArray "pResolveAttachments" VkSubpassDescription Source # 
type FieldIsArray "pResolveAttachments" VkSubpassDescription = False
type FieldIsArray "pipelineBindPoint" VkSubpassDescription Source # 
type FieldIsArray "pipelineBindPoint" VkSubpassDescription = False
type FieldIsArray "preserveAttachmentCount" VkSubpassDescription Source # 
type FieldIsArray "preserveAttachmentCount" VkSubpassDescription = False

data VkSubpassSampleLocationsEXT Source #

typedef struct VkSubpassSampleLocationsEXT {
    uint32_t                         subpassIndex;
    VkSampleLocationsInfoEXT         sampleLocationsInfo;
} VkSubpassSampleLocationsEXT;

VkSubpassSampleLocationsEXT registry at www.khronos.org

Instances

Eq VkSubpassSampleLocationsEXT Source # 
Ord VkSubpassSampleLocationsEXT Source # 
Show VkSubpassSampleLocationsEXT Source # 
Storable VkSubpassSampleLocationsEXT Source # 
VulkanMarshalPrim VkSubpassSampleLocationsEXT Source # 
VulkanMarshal VkSubpassSampleLocationsEXT Source # 
CanWriteField "sampleLocationsInfo" VkSubpassSampleLocationsEXT Source # 
CanWriteField "subpassIndex" VkSubpassSampleLocationsEXT Source # 
CanReadField "sampleLocationsInfo" VkSubpassSampleLocationsEXT Source # 
CanReadField "subpassIndex" VkSubpassSampleLocationsEXT Source # 
HasField "sampleLocationsInfo" VkSubpassSampleLocationsEXT Source # 

Associated Types

type FieldType ("sampleLocationsInfo" :: Symbol) VkSubpassSampleLocationsEXT :: Type Source #

type FieldOptional ("sampleLocationsInfo" :: Symbol) VkSubpassSampleLocationsEXT :: Bool Source #

type FieldOffset ("sampleLocationsInfo" :: Symbol) VkSubpassSampleLocationsEXT :: Nat Source #

type FieldIsArray ("sampleLocationsInfo" :: Symbol) VkSubpassSampleLocationsEXT :: Bool Source #

HasField "subpassIndex" VkSubpassSampleLocationsEXT Source # 
type StructFields VkSubpassSampleLocationsEXT Source # 
type StructFields VkSubpassSampleLocationsEXT = (:) Symbol "subpassIndex" ((:) Symbol "sampleLocationsInfo" ([] Symbol))
type CUnionType VkSubpassSampleLocationsEXT Source # 
type ReturnedOnly VkSubpassSampleLocationsEXT Source # 
type StructExtends VkSubpassSampleLocationsEXT Source # 
type FieldType "sampleLocationsInfo" VkSubpassSampleLocationsEXT Source # 
type FieldType "subpassIndex" VkSubpassSampleLocationsEXT Source # 
type FieldOptional "sampleLocationsInfo" VkSubpassSampleLocationsEXT Source # 
type FieldOptional "sampleLocationsInfo" VkSubpassSampleLocationsEXT = False
type FieldOptional "subpassIndex" VkSubpassSampleLocationsEXT Source # 
type FieldOffset "sampleLocationsInfo" VkSubpassSampleLocationsEXT Source # 
type FieldOffset "sampleLocationsInfo" VkSubpassSampleLocationsEXT = 8
type FieldOffset "subpassIndex" VkSubpassSampleLocationsEXT Source # 
type FieldIsArray "sampleLocationsInfo" VkSubpassSampleLocationsEXT Source # 
type FieldIsArray "sampleLocationsInfo" VkSubpassSampleLocationsEXT = False
type FieldIsArray "subpassIndex" VkSubpassSampleLocationsEXT Source # 

newtype VkSubpassContents Source #

Constructors

VkSubpassContents Int32 

Instances

Bounded VkSubpassContents Source # 
Enum VkSubpassContents Source # 
Eq VkSubpassContents Source # 
Data VkSubpassContents Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkSubpassContents -> c VkSubpassContents #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkSubpassContents #

toConstr :: VkSubpassContents -> Constr #

dataTypeOf :: VkSubpassContents -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkSubpassContents) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkSubpassContents) #

gmapT :: (forall b. Data b => b -> b) -> VkSubpassContents -> VkSubpassContents #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkSubpassContents -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkSubpassContents -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkSubpassContents -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkSubpassContents -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkSubpassContents -> m VkSubpassContents #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSubpassContents -> m VkSubpassContents #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSubpassContents -> m VkSubpassContents #

Num VkSubpassContents Source # 
Ord VkSubpassContents Source # 
Read VkSubpassContents Source # 
Show VkSubpassContents Source # 
Generic VkSubpassContents Source # 
Storable VkSubpassContents Source # 
type Rep VkSubpassContents Source # 
type Rep VkSubpassContents = D1 (MetaData "VkSubpassContents" "Graphics.Vulkan.Types.Enum.Subpass" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkSubpassContents" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

newtype VkSubpassDescriptionBitmask a Source #

Instances

Bounded (VkSubpassDescriptionBitmask FlagMask) Source # 
Enum (VkSubpassDescriptionBitmask FlagMask) Source # 
Eq (VkSubpassDescriptionBitmask a) Source # 
Integral (VkSubpassDescriptionBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkSubpassDescriptionBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkSubpassDescriptionBitmask a -> c (VkSubpassDescriptionBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkSubpassDescriptionBitmask a) #

toConstr :: VkSubpassDescriptionBitmask a -> Constr #

dataTypeOf :: VkSubpassDescriptionBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkSubpassDescriptionBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkSubpassDescriptionBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkSubpassDescriptionBitmask a -> VkSubpassDescriptionBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkSubpassDescriptionBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkSubpassDescriptionBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkSubpassDescriptionBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkSubpassDescriptionBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkSubpassDescriptionBitmask a -> m (VkSubpassDescriptionBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSubpassDescriptionBitmask a -> m (VkSubpassDescriptionBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSubpassDescriptionBitmask a -> m (VkSubpassDescriptionBitmask a) #

Num (VkSubpassDescriptionBitmask FlagMask) Source # 
Ord (VkSubpassDescriptionBitmask a) Source # 
Read (VkSubpassDescriptionBitmask a) Source # 
Real (VkSubpassDescriptionBitmask FlagMask) Source # 
Show (VkSubpassDescriptionBitmask a) Source # 
Generic (VkSubpassDescriptionBitmask a) Source # 
Storable (VkSubpassDescriptionBitmask a) Source # 
Bits (VkSubpassDescriptionBitmask FlagMask) Source # 

Methods

(.&.) :: VkSubpassDescriptionBitmask FlagMask -> VkSubpassDescriptionBitmask FlagMask -> VkSubpassDescriptionBitmask FlagMask #

(.|.) :: VkSubpassDescriptionBitmask FlagMask -> VkSubpassDescriptionBitmask FlagMask -> VkSubpassDescriptionBitmask FlagMask #

xor :: VkSubpassDescriptionBitmask FlagMask -> VkSubpassDescriptionBitmask FlagMask -> VkSubpassDescriptionBitmask FlagMask #

complement :: VkSubpassDescriptionBitmask FlagMask -> VkSubpassDescriptionBitmask FlagMask #

shift :: VkSubpassDescriptionBitmask FlagMask -> Int -> VkSubpassDescriptionBitmask FlagMask #

rotate :: VkSubpassDescriptionBitmask FlagMask -> Int -> VkSubpassDescriptionBitmask FlagMask #

zeroBits :: VkSubpassDescriptionBitmask FlagMask #

bit :: Int -> VkSubpassDescriptionBitmask FlagMask #

setBit :: VkSubpassDescriptionBitmask FlagMask -> Int -> VkSubpassDescriptionBitmask FlagMask #

clearBit :: VkSubpassDescriptionBitmask FlagMask -> Int -> VkSubpassDescriptionBitmask FlagMask #

complementBit :: VkSubpassDescriptionBitmask FlagMask -> Int -> VkSubpassDescriptionBitmask FlagMask #

testBit :: VkSubpassDescriptionBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkSubpassDescriptionBitmask FlagMask -> Maybe Int #

bitSize :: VkSubpassDescriptionBitmask FlagMask -> Int #

isSigned :: VkSubpassDescriptionBitmask FlagMask -> Bool #

shiftL :: VkSubpassDescriptionBitmask FlagMask -> Int -> VkSubpassDescriptionBitmask FlagMask #

unsafeShiftL :: VkSubpassDescriptionBitmask FlagMask -> Int -> VkSubpassDescriptionBitmask FlagMask #

shiftR :: VkSubpassDescriptionBitmask FlagMask -> Int -> VkSubpassDescriptionBitmask FlagMask #

unsafeShiftR :: VkSubpassDescriptionBitmask FlagMask -> Int -> VkSubpassDescriptionBitmask FlagMask #

rotateL :: VkSubpassDescriptionBitmask FlagMask -> Int -> VkSubpassDescriptionBitmask FlagMask #

rotateR :: VkSubpassDescriptionBitmask FlagMask -> Int -> VkSubpassDescriptionBitmask FlagMask #

popCount :: VkSubpassDescriptionBitmask FlagMask -> Int #

FiniteBits (VkSubpassDescriptionBitmask FlagMask) Source # 
type Rep (VkSubpassDescriptionBitmask a) Source # 
type Rep (VkSubpassDescriptionBitmask a) = D1 (MetaData "VkSubpassDescriptionBitmask" "Graphics.Vulkan.Types.Enum.Subpass" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkSubpassDescriptionBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkTessellationDomainOrigin Source #

Instances

Bounded VkTessellationDomainOrigin Source # 
Enum VkTessellationDomainOrigin Source # 
Eq VkTessellationDomainOrigin Source # 
Data VkTessellationDomainOrigin Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkTessellationDomainOrigin -> c VkTessellationDomainOrigin #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkTessellationDomainOrigin #

toConstr :: VkTessellationDomainOrigin -> Constr #

dataTypeOf :: VkTessellationDomainOrigin -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkTessellationDomainOrigin) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkTessellationDomainOrigin) #

gmapT :: (forall b. Data b => b -> b) -> VkTessellationDomainOrigin -> VkTessellationDomainOrigin #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkTessellationDomainOrigin -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkTessellationDomainOrigin -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkTessellationDomainOrigin -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkTessellationDomainOrigin -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkTessellationDomainOrigin -> m VkTessellationDomainOrigin #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkTessellationDomainOrigin -> m VkTessellationDomainOrigin #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkTessellationDomainOrigin -> m VkTessellationDomainOrigin #

Num VkTessellationDomainOrigin Source # 
Ord VkTessellationDomainOrigin Source # 
Read VkTessellationDomainOrigin Source # 
Show VkTessellationDomainOrigin Source # 
Generic VkTessellationDomainOrigin Source # 
Storable VkTessellationDomainOrigin Source # 
type Rep VkTessellationDomainOrigin Source # 
type Rep VkTessellationDomainOrigin = D1 (MetaData "VkTessellationDomainOrigin" "Graphics.Vulkan.Types.Enum.TessellationDomainOrigin" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkTessellationDomainOrigin" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

newtype VkTessellationDomainOriginKHR Source #

Instances

Bounded VkTessellationDomainOriginKHR Source # 
Enum VkTessellationDomainOriginKHR Source # 
Eq VkTessellationDomainOriginKHR Source # 
Integral VkTessellationDomainOriginKHR Source # 
Data VkTessellationDomainOriginKHR Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkTessellationDomainOriginKHR -> c VkTessellationDomainOriginKHR #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkTessellationDomainOriginKHR #

toConstr :: VkTessellationDomainOriginKHR -> Constr #

dataTypeOf :: VkTessellationDomainOriginKHR -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkTessellationDomainOriginKHR) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkTessellationDomainOriginKHR) #

gmapT :: (forall b. Data b => b -> b) -> VkTessellationDomainOriginKHR -> VkTessellationDomainOriginKHR #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkTessellationDomainOriginKHR -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkTessellationDomainOriginKHR -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkTessellationDomainOriginKHR -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkTessellationDomainOriginKHR -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkTessellationDomainOriginKHR -> m VkTessellationDomainOriginKHR #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkTessellationDomainOriginKHR -> m VkTessellationDomainOriginKHR #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkTessellationDomainOriginKHR -> m VkTessellationDomainOriginKHR #

Num VkTessellationDomainOriginKHR Source # 
Ord VkTessellationDomainOriginKHR Source # 
Read VkTessellationDomainOriginKHR Source # 
Real VkTessellationDomainOriginKHR Source # 
Show VkTessellationDomainOriginKHR Source # 
Generic VkTessellationDomainOriginKHR Source # 
Storable VkTessellationDomainOriginKHR Source # 
Bits VkTessellationDomainOriginKHR Source # 

Methods

(.&.) :: VkTessellationDomainOriginKHR -> VkTessellationDomainOriginKHR -> VkTessellationDomainOriginKHR #

(.|.) :: VkTessellationDomainOriginKHR -> VkTessellationDomainOriginKHR -> VkTessellationDomainOriginKHR #

xor :: VkTessellationDomainOriginKHR -> VkTessellationDomainOriginKHR -> VkTessellationDomainOriginKHR #

complement :: VkTessellationDomainOriginKHR -> VkTessellationDomainOriginKHR #

shift :: VkTessellationDomainOriginKHR -> Int -> VkTessellationDomainOriginKHR #

rotate :: VkTessellationDomainOriginKHR -> Int -> VkTessellationDomainOriginKHR #

zeroBits :: VkTessellationDomainOriginKHR #

bit :: Int -> VkTessellationDomainOriginKHR #

setBit :: VkTessellationDomainOriginKHR -> Int -> VkTessellationDomainOriginKHR #

clearBit :: VkTessellationDomainOriginKHR -> Int -> VkTessellationDomainOriginKHR #

complementBit :: VkTessellationDomainOriginKHR -> Int -> VkTessellationDomainOriginKHR #

testBit :: VkTessellationDomainOriginKHR -> Int -> Bool #

bitSizeMaybe :: VkTessellationDomainOriginKHR -> Maybe Int #

bitSize :: VkTessellationDomainOriginKHR -> Int #

isSigned :: VkTessellationDomainOriginKHR -> Bool #

shiftL :: VkTessellationDomainOriginKHR -> Int -> VkTessellationDomainOriginKHR #

unsafeShiftL :: VkTessellationDomainOriginKHR -> Int -> VkTessellationDomainOriginKHR #

shiftR :: VkTessellationDomainOriginKHR -> Int -> VkTessellationDomainOriginKHR #

unsafeShiftR :: VkTessellationDomainOriginKHR -> Int -> VkTessellationDomainOriginKHR #

rotateL :: VkTessellationDomainOriginKHR -> Int -> VkTessellationDomainOriginKHR #

rotateR :: VkTessellationDomainOriginKHR -> Int -> VkTessellationDomainOriginKHR #

popCount :: VkTessellationDomainOriginKHR -> Int #

FiniteBits VkTessellationDomainOriginKHR Source # 
type Rep VkTessellationDomainOriginKHR Source # 
type Rep VkTessellationDomainOriginKHR = D1 (MetaData "VkTessellationDomainOriginKHR" "Graphics.Vulkan.Types.Enum.TessellationDomainOrigin" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkTessellationDomainOriginKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

Promoted from VK_KHR_multiview

#include "vk_platform.h"

Promoted from VK_KHR_variable_pointers

#include "vk_platform.h"

Originally based on VK_KHR_protected_memory (extension 146), which was never published; thus the mystifying large value= numbers below. These are not aliased since they weren't actually promoted from an extension.

data VkProtectedSubmitInfo Source #

typedef struct VkProtectedSubmitInfo {
    VkStructureType sType;
    const void*                     pNext;
    VkBool32                        protectedSubmit;
} VkProtectedSubmitInfo;

VkProtectedSubmitInfo registry at www.khronos.org

Instances

Eq VkProtectedSubmitInfo Source # 
Ord VkProtectedSubmitInfo Source # 
Show VkProtectedSubmitInfo Source # 
Storable VkProtectedSubmitInfo Source # 
VulkanMarshalPrim VkProtectedSubmitInfo Source # 
VulkanMarshal VkProtectedSubmitInfo Source # 
CanWriteField "pNext" VkProtectedSubmitInfo Source # 
CanWriteField "protectedSubmit" VkProtectedSubmitInfo Source # 
CanWriteField "sType" VkProtectedSubmitInfo Source # 
CanReadField "pNext" VkProtectedSubmitInfo Source # 
CanReadField "protectedSubmit" VkProtectedSubmitInfo Source # 
CanReadField "sType" VkProtectedSubmitInfo Source # 
HasField "pNext" VkProtectedSubmitInfo Source # 
HasField "protectedSubmit" VkProtectedSubmitInfo Source # 

Associated Types

type FieldType ("protectedSubmit" :: Symbol) VkProtectedSubmitInfo :: Type Source #

type FieldOptional ("protectedSubmit" :: Symbol) VkProtectedSubmitInfo :: Bool Source #

type FieldOffset ("protectedSubmit" :: Symbol) VkProtectedSubmitInfo :: Nat Source #

type FieldIsArray ("protectedSubmit" :: Symbol) VkProtectedSubmitInfo :: Bool Source #

HasField "sType" VkProtectedSubmitInfo Source # 
type StructFields VkProtectedSubmitInfo Source # 
type StructFields VkProtectedSubmitInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "protectedSubmit" ([] Symbol)))
type CUnionType VkProtectedSubmitInfo Source # 
type ReturnedOnly VkProtectedSubmitInfo Source # 
type StructExtends VkProtectedSubmitInfo Source # 
type FieldType "pNext" VkProtectedSubmitInfo Source # 
type FieldType "protectedSubmit" VkProtectedSubmitInfo Source # 
type FieldType "protectedSubmit" VkProtectedSubmitInfo = VkBool32
type FieldType "sType" VkProtectedSubmitInfo Source # 
type FieldOptional "pNext" VkProtectedSubmitInfo Source # 
type FieldOptional "protectedSubmit" VkProtectedSubmitInfo Source # 
type FieldOptional "protectedSubmit" VkProtectedSubmitInfo = False
type FieldOptional "sType" VkProtectedSubmitInfo Source # 
type FieldOffset "pNext" VkProtectedSubmitInfo Source # 
type FieldOffset "protectedSubmit" VkProtectedSubmitInfo Source # 
type FieldOffset "protectedSubmit" VkProtectedSubmitInfo = 16
type FieldOffset "sType" VkProtectedSubmitInfo Source # 
type FieldIsArray "pNext" VkProtectedSubmitInfo Source # 
type FieldIsArray "protectedSubmit" VkProtectedSubmitInfo Source # 
type FieldIsArray "protectedSubmit" VkProtectedSubmitInfo = False
type FieldIsArray "sType" VkProtectedSubmitInfo Source # 

type VkGetDeviceQueue2 = "vkGetDeviceQueue2" Source #

type HS_vkGetDeviceQueue2 Source #

Arguments

 = VkDevice

device

-> Ptr VkDeviceQueueInfo2

pQueueInfo

-> Ptr VkQueue

pQueue

-> IO () 
void vkGetDeviceQueue2
    ( VkDevice device
    , const VkDeviceQueueInfo2* pQueueInfo
    , VkQueue* pQueue
    )

vkGetDeviceQueue2 registry at www.khronos.org

vkGetDeviceQueue2 Source #

Arguments

:: VkDevice

device

-> Ptr VkDeviceQueueInfo2

pQueueInfo

-> Ptr VkQueue

pQueue

-> IO () 
void vkGetDeviceQueue2
    ( VkDevice device
    , const VkDeviceQueueInfo2* pQueueInfo
    , VkQueue* pQueue
    )

vkGetDeviceQueue2 registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetDeviceQueue2 <- vkGetDeviceProc @VkGetDeviceQueue2 vkDevice

or less efficient:

myGetDeviceQueue2 <- vkGetProc @VkGetDeviceQueue2

Note: vkGetDeviceQueue2Unsafe and vkGetDeviceQueue2Safe are the unsafe and safe FFI imports of this function, respectively. vkGetDeviceQueue2 is an alias of vkGetDeviceQueue2Unsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetDeviceQueue2Safe.

vkGetDeviceQueue2Unsafe Source #

Arguments

:: VkDevice

device

-> Ptr VkDeviceQueueInfo2

pQueueInfo

-> Ptr VkQueue

pQueue

-> IO () 
void vkGetDeviceQueue2
    ( VkDevice device
    , const VkDeviceQueueInfo2* pQueueInfo
    , VkQueue* pQueue
    )

vkGetDeviceQueue2 registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetDeviceQueue2 <- vkGetDeviceProc @VkGetDeviceQueue2 vkDevice

or less efficient:

myGetDeviceQueue2 <- vkGetProc @VkGetDeviceQueue2

Note: vkGetDeviceQueue2Unsafe and vkGetDeviceQueue2Safe are the unsafe and safe FFI imports of this function, respectively. vkGetDeviceQueue2 is an alias of vkGetDeviceQueue2Unsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetDeviceQueue2Safe.

vkGetDeviceQueue2Safe Source #

Arguments

:: VkDevice

device

-> Ptr VkDeviceQueueInfo2

pQueueInfo

-> Ptr VkQueue

pQueue

-> IO () 
void vkGetDeviceQueue2
    ( VkDevice device
    , const VkDeviceQueueInfo2* pQueueInfo
    , VkQueue* pQueue
    )

vkGetDeviceQueue2 registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetDeviceQueue2 <- vkGetDeviceProc @VkGetDeviceQueue2 vkDevice

or less efficient:

myGetDeviceQueue2 <- vkGetProc @VkGetDeviceQueue2

Note: vkGetDeviceQueue2Unsafe and vkGetDeviceQueue2Safe are the unsafe and safe FFI imports of this function, respectively. vkGetDeviceQueue2 is an alias of vkGetDeviceQueue2Unsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetDeviceQueue2Safe.

pattern VK_QUEUE_PROTECTED_BIT :: VkQueueFlagBits Source #

Queues may support protected operations

bitpos = 4

pattern VK_DEVICE_QUEUE_CREATE_PROTECTED_BIT :: VkDeviceQueueCreateFlagBits Source #

Queue is a protected-capable device queue

bitpos = 0

pattern VK_MEMORY_PROPERTY_PROTECTED_BIT :: VkMemoryPropertyFlagBits Source #

Memory is protected

bitpos = 5

pattern VK_BUFFER_CREATE_PROTECTED_BIT :: VkBufferCreateFlagBits Source #

Buffer requires protected memory

bitpos = 3

pattern VK_IMAGE_CREATE_PROTECTED_BIT :: VkImageCreateFlagBits Source #

Image requires protected memory

bitpos = 11

pattern VK_COMMAND_POOL_CREATE_PROTECTED_BIT :: VkCommandPoolCreateFlagBits Source #

Command buffers allocated from pool are protected command buffers

bitpos = 2

Promoted from VK_KHR_sampler_ycbcr_conversion

newtype VkBorderColor Source #

Constructors

VkBorderColor Int32 

Instances

Bounded VkBorderColor Source # 
Enum VkBorderColor Source # 
Eq VkBorderColor Source # 
Data VkBorderColor Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkBorderColor -> c VkBorderColor #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkBorderColor #

toConstr :: VkBorderColor -> Constr #

dataTypeOf :: VkBorderColor -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkBorderColor) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkBorderColor) #

gmapT :: (forall b. Data b => b -> b) -> VkBorderColor -> VkBorderColor #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkBorderColor -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkBorderColor -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkBorderColor -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkBorderColor -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkBorderColor -> m VkBorderColor #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkBorderColor -> m VkBorderColor #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkBorderColor -> m VkBorderColor #

Num VkBorderColor Source # 
Ord VkBorderColor Source # 
Read VkBorderColor Source # 
Show VkBorderColor Source # 
Generic VkBorderColor Source # 

Associated Types

type Rep VkBorderColor :: * -> * #

Storable VkBorderColor Source # 
type Rep VkBorderColor Source # 
type Rep VkBorderColor = D1 (MetaData "VkBorderColor" "Graphics.Vulkan.Types.Enum.BorderColor" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkBorderColor" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

newtype VkChromaLocation Source #

Constructors

VkChromaLocation Int32 

Instances

Bounded VkChromaLocation Source # 
Enum VkChromaLocation Source # 
Eq VkChromaLocation Source # 
Data VkChromaLocation Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkChromaLocation -> c VkChromaLocation #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkChromaLocation #

toConstr :: VkChromaLocation -> Constr #

dataTypeOf :: VkChromaLocation -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkChromaLocation) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkChromaLocation) #

gmapT :: (forall b. Data b => b -> b) -> VkChromaLocation -> VkChromaLocation #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkChromaLocation -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkChromaLocation -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkChromaLocation -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkChromaLocation -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkChromaLocation -> m VkChromaLocation #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkChromaLocation -> m VkChromaLocation #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkChromaLocation -> m VkChromaLocation #

Num VkChromaLocation Source # 
Ord VkChromaLocation Source # 
Read VkChromaLocation Source # 
Show VkChromaLocation Source # 
Generic VkChromaLocation Source # 
Storable VkChromaLocation Source # 
type Rep VkChromaLocation Source # 
type Rep VkChromaLocation = D1 (MetaData "VkChromaLocation" "Graphics.Vulkan.Types.Enum.ChromaLocation" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkChromaLocation" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

newtype VkChromaLocationKHR Source #

Instances

Bounded VkChromaLocationKHR Source # 
Enum VkChromaLocationKHR Source # 
Eq VkChromaLocationKHR Source # 
Integral VkChromaLocationKHR Source # 
Data VkChromaLocationKHR Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkChromaLocationKHR -> c VkChromaLocationKHR #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkChromaLocationKHR #

toConstr :: VkChromaLocationKHR -> Constr #

dataTypeOf :: VkChromaLocationKHR -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkChromaLocationKHR) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkChromaLocationKHR) #

gmapT :: (forall b. Data b => b -> b) -> VkChromaLocationKHR -> VkChromaLocationKHR #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkChromaLocationKHR -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkChromaLocationKHR -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkChromaLocationKHR -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkChromaLocationKHR -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkChromaLocationKHR -> m VkChromaLocationKHR #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkChromaLocationKHR -> m VkChromaLocationKHR #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkChromaLocationKHR -> m VkChromaLocationKHR #

Num VkChromaLocationKHR Source # 
Ord VkChromaLocationKHR Source # 
Read VkChromaLocationKHR Source # 
Real VkChromaLocationKHR Source # 
Show VkChromaLocationKHR Source # 
Generic VkChromaLocationKHR Source # 
Storable VkChromaLocationKHR Source # 
Bits VkChromaLocationKHR Source # 
FiniteBits VkChromaLocationKHR Source # 
type Rep VkChromaLocationKHR Source # 
type Rep VkChromaLocationKHR = D1 (MetaData "VkChromaLocationKHR" "Graphics.Vulkan.Types.Enum.ChromaLocation" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkChromaLocationKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkCompareOp Source #

Constructors

VkCompareOp Int32 

Instances

Bounded VkCompareOp Source # 
Enum VkCompareOp Source # 
Eq VkCompareOp Source # 
Data VkCompareOp Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkCompareOp -> c VkCompareOp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkCompareOp #

toConstr :: VkCompareOp -> Constr #

dataTypeOf :: VkCompareOp -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkCompareOp) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkCompareOp) #

gmapT :: (forall b. Data b => b -> b) -> VkCompareOp -> VkCompareOp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkCompareOp -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkCompareOp -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkCompareOp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkCompareOp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkCompareOp -> m VkCompareOp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkCompareOp -> m VkCompareOp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkCompareOp -> m VkCompareOp #

Num VkCompareOp Source # 
Ord VkCompareOp Source # 
Read VkCompareOp Source # 
Show VkCompareOp Source # 
Generic VkCompareOp Source # 

Associated Types

type Rep VkCompareOp :: * -> * #

Storable VkCompareOp Source # 
type Rep VkCompareOp Source # 
type Rep VkCompareOp = D1 (MetaData "VkCompareOp" "Graphics.Vulkan.Types.Enum.CompareOp" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkCompareOp" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

newtype VkFilter Source #

Constructors

VkFilter Int32 

Instances

Bounded VkFilter Source # 
Enum VkFilter Source # 
Eq VkFilter Source # 
Data VkFilter Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkFilter -> c VkFilter #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkFilter #

toConstr :: VkFilter -> Constr #

dataTypeOf :: VkFilter -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkFilter) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkFilter) #

gmapT :: (forall b. Data b => b -> b) -> VkFilter -> VkFilter #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkFilter -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkFilter -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkFilter -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkFilter -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkFilter -> m VkFilter #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkFilter -> m VkFilter #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkFilter -> m VkFilter #

Num VkFilter Source # 
Ord VkFilter Source # 
Read VkFilter Source # 
Show VkFilter Source # 
Generic VkFilter Source # 

Associated Types

type Rep VkFilter :: * -> * #

Methods

from :: VkFilter -> Rep VkFilter x #

to :: Rep VkFilter x -> VkFilter #

Storable VkFilter Source # 
type Rep VkFilter Source # 
type Rep VkFilter = D1 (MetaData "VkFilter" "Graphics.Vulkan.Types.Enum.Filter" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkFilter" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

newtype VkSamplerAddressMode Source #

Instances

Bounded VkSamplerAddressMode Source # 
Enum VkSamplerAddressMode Source # 
Eq VkSamplerAddressMode Source # 
Data VkSamplerAddressMode Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkSamplerAddressMode -> c VkSamplerAddressMode #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkSamplerAddressMode #

toConstr :: VkSamplerAddressMode -> Constr #

dataTypeOf :: VkSamplerAddressMode -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkSamplerAddressMode) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkSamplerAddressMode) #

gmapT :: (forall b. Data b => b -> b) -> VkSamplerAddressMode -> VkSamplerAddressMode #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkSamplerAddressMode -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkSamplerAddressMode -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkSamplerAddressMode -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkSamplerAddressMode -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkSamplerAddressMode -> m VkSamplerAddressMode #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSamplerAddressMode -> m VkSamplerAddressMode #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSamplerAddressMode -> m VkSamplerAddressMode #

Num VkSamplerAddressMode Source # 
Ord VkSamplerAddressMode Source # 
Read VkSamplerAddressMode Source # 
Show VkSamplerAddressMode Source # 
Generic VkSamplerAddressMode Source # 
Storable VkSamplerAddressMode Source # 
type Rep VkSamplerAddressMode Source # 
type Rep VkSamplerAddressMode = D1 (MetaData "VkSamplerAddressMode" "Graphics.Vulkan.Types.Enum.Sampler" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkSamplerAddressMode" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

newtype VkSamplerCreateFlagBits Source #

Instances

Bounded VkSamplerCreateFlagBits Source # 
Enum VkSamplerCreateFlagBits Source # 
Eq VkSamplerCreateFlagBits Source # 
Integral VkSamplerCreateFlagBits Source # 
Data VkSamplerCreateFlagBits Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkSamplerCreateFlagBits -> c VkSamplerCreateFlagBits #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkSamplerCreateFlagBits #

toConstr :: VkSamplerCreateFlagBits -> Constr #

dataTypeOf :: VkSamplerCreateFlagBits -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkSamplerCreateFlagBits) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkSamplerCreateFlagBits) #

gmapT :: (forall b. Data b => b -> b) -> VkSamplerCreateFlagBits -> VkSamplerCreateFlagBits #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkSamplerCreateFlagBits -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkSamplerCreateFlagBits -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkSamplerCreateFlagBits -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkSamplerCreateFlagBits -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkSamplerCreateFlagBits -> m VkSamplerCreateFlagBits #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSamplerCreateFlagBits -> m VkSamplerCreateFlagBits #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSamplerCreateFlagBits -> m VkSamplerCreateFlagBits #

Num VkSamplerCreateFlagBits Source # 
Ord VkSamplerCreateFlagBits Source # 
Read VkSamplerCreateFlagBits Source # 
Real VkSamplerCreateFlagBits Source # 
Show VkSamplerCreateFlagBits Source # 
Generic VkSamplerCreateFlagBits Source # 
Storable VkSamplerCreateFlagBits Source # 
Bits VkSamplerCreateFlagBits Source # 
FiniteBits VkSamplerCreateFlagBits Source # 
type Rep VkSamplerCreateFlagBits Source # 
type Rep VkSamplerCreateFlagBits = D1 (MetaData "VkSamplerCreateFlagBits" "Graphics.Vulkan.Types.Enum.Sampler" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkSamplerCreateFlagBits" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkSamplerMipmapMode Source #

Instances

Bounded VkSamplerMipmapMode Source # 
Enum VkSamplerMipmapMode Source # 
Eq VkSamplerMipmapMode Source # 
Data VkSamplerMipmapMode Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkSamplerMipmapMode -> c VkSamplerMipmapMode #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkSamplerMipmapMode #

toConstr :: VkSamplerMipmapMode -> Constr #

dataTypeOf :: VkSamplerMipmapMode -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkSamplerMipmapMode) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkSamplerMipmapMode) #

gmapT :: (forall b. Data b => b -> b) -> VkSamplerMipmapMode -> VkSamplerMipmapMode #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkSamplerMipmapMode -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkSamplerMipmapMode -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkSamplerMipmapMode -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkSamplerMipmapMode -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkSamplerMipmapMode -> m VkSamplerMipmapMode #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSamplerMipmapMode -> m VkSamplerMipmapMode #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSamplerMipmapMode -> m VkSamplerMipmapMode #

Num VkSamplerMipmapMode Source # 
Ord VkSamplerMipmapMode Source # 
Read VkSamplerMipmapMode Source # 
Show VkSamplerMipmapMode Source # 
Generic VkSamplerMipmapMode Source # 
Storable VkSamplerMipmapMode Source # 
type Rep VkSamplerMipmapMode Source # 
type Rep VkSamplerMipmapMode = D1 (MetaData "VkSamplerMipmapMode" "Graphics.Vulkan.Types.Enum.Sampler" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkSamplerMipmapMode" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

pattern VK_SAMPLER_MIPMAP_MODE_NEAREST :: VkSamplerMipmapMode Source #

Choose nearest mip level

pattern VK_SAMPLER_MIPMAP_MODE_LINEAR :: VkSamplerMipmapMode Source #

Linear filter between mip levels

newtype VkSamplerReductionModeEXT Source #

Instances

Bounded VkSamplerReductionModeEXT Source # 
Enum VkSamplerReductionModeEXT Source # 
Eq VkSamplerReductionModeEXT Source # 
Data VkSamplerReductionModeEXT Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkSamplerReductionModeEXT -> c VkSamplerReductionModeEXT #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkSamplerReductionModeEXT #

toConstr :: VkSamplerReductionModeEXT -> Constr #

dataTypeOf :: VkSamplerReductionModeEXT -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkSamplerReductionModeEXT) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkSamplerReductionModeEXT) #

gmapT :: (forall b. Data b => b -> b) -> VkSamplerReductionModeEXT -> VkSamplerReductionModeEXT #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkSamplerReductionModeEXT -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkSamplerReductionModeEXT -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkSamplerReductionModeEXT -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkSamplerReductionModeEXT -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkSamplerReductionModeEXT -> m VkSamplerReductionModeEXT #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSamplerReductionModeEXT -> m VkSamplerReductionModeEXT #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSamplerReductionModeEXT -> m VkSamplerReductionModeEXT #

Num VkSamplerReductionModeEXT Source # 
Ord VkSamplerReductionModeEXT Source # 
Read VkSamplerReductionModeEXT Source # 
Show VkSamplerReductionModeEXT Source # 
Generic VkSamplerReductionModeEXT Source # 
Storable VkSamplerReductionModeEXT Source # 
type Rep VkSamplerReductionModeEXT Source # 
type Rep VkSamplerReductionModeEXT = D1 (MetaData "VkSamplerReductionModeEXT" "Graphics.Vulkan.Types.Enum.Sampler" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkSamplerReductionModeEXT" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

newtype VkSamplerYcbcrModelConversion Source #

Instances

Bounded VkSamplerYcbcrModelConversion Source # 
Enum VkSamplerYcbcrModelConversion Source # 
Eq VkSamplerYcbcrModelConversion Source # 
Data VkSamplerYcbcrModelConversion Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkSamplerYcbcrModelConversion -> c VkSamplerYcbcrModelConversion #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkSamplerYcbcrModelConversion #

toConstr :: VkSamplerYcbcrModelConversion -> Constr #

dataTypeOf :: VkSamplerYcbcrModelConversion -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkSamplerYcbcrModelConversion) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkSamplerYcbcrModelConversion) #

gmapT :: (forall b. Data b => b -> b) -> VkSamplerYcbcrModelConversion -> VkSamplerYcbcrModelConversion #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkSamplerYcbcrModelConversion -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkSamplerYcbcrModelConversion -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkSamplerYcbcrModelConversion -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkSamplerYcbcrModelConversion -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkSamplerYcbcrModelConversion -> m VkSamplerYcbcrModelConversion #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSamplerYcbcrModelConversion -> m VkSamplerYcbcrModelConversion #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSamplerYcbcrModelConversion -> m VkSamplerYcbcrModelConversion #

Num VkSamplerYcbcrModelConversion Source # 
Ord VkSamplerYcbcrModelConversion Source # 
Read VkSamplerYcbcrModelConversion Source # 
Show VkSamplerYcbcrModelConversion Source # 
Generic VkSamplerYcbcrModelConversion Source # 
Storable VkSamplerYcbcrModelConversion Source # 
type Rep VkSamplerYcbcrModelConversion Source # 
type Rep VkSamplerYcbcrModelConversion = D1 (MetaData "VkSamplerYcbcrModelConversion" "Graphics.Vulkan.Types.Enum.Sampler" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkSamplerYcbcrModelConversion" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

newtype VkSamplerYcbcrModelConversionKHR Source #

Instances

Bounded VkSamplerYcbcrModelConversionKHR Source # 
Enum VkSamplerYcbcrModelConversionKHR Source # 
Eq VkSamplerYcbcrModelConversionKHR Source # 
Integral VkSamplerYcbcrModelConversionKHR Source # 
Data VkSamplerYcbcrModelConversionKHR Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkSamplerYcbcrModelConversionKHR -> c VkSamplerYcbcrModelConversionKHR #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkSamplerYcbcrModelConversionKHR #

toConstr :: VkSamplerYcbcrModelConversionKHR -> Constr #

dataTypeOf :: VkSamplerYcbcrModelConversionKHR -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkSamplerYcbcrModelConversionKHR) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkSamplerYcbcrModelConversionKHR) #

gmapT :: (forall b. Data b => b -> b) -> VkSamplerYcbcrModelConversionKHR -> VkSamplerYcbcrModelConversionKHR #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkSamplerYcbcrModelConversionKHR -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkSamplerYcbcrModelConversionKHR -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkSamplerYcbcrModelConversionKHR -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkSamplerYcbcrModelConversionKHR -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkSamplerYcbcrModelConversionKHR -> m VkSamplerYcbcrModelConversionKHR #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSamplerYcbcrModelConversionKHR -> m VkSamplerYcbcrModelConversionKHR #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSamplerYcbcrModelConversionKHR -> m VkSamplerYcbcrModelConversionKHR #

Num VkSamplerYcbcrModelConversionKHR Source # 
Ord VkSamplerYcbcrModelConversionKHR Source # 
Read VkSamplerYcbcrModelConversionKHR Source # 
Real VkSamplerYcbcrModelConversionKHR Source # 
Show VkSamplerYcbcrModelConversionKHR Source # 
Generic VkSamplerYcbcrModelConversionKHR Source # 
Storable VkSamplerYcbcrModelConversionKHR Source # 
Bits VkSamplerYcbcrModelConversionKHR Source # 

Methods

(.&.) :: VkSamplerYcbcrModelConversionKHR -> VkSamplerYcbcrModelConversionKHR -> VkSamplerYcbcrModelConversionKHR #

(.|.) :: VkSamplerYcbcrModelConversionKHR -> VkSamplerYcbcrModelConversionKHR -> VkSamplerYcbcrModelConversionKHR #

xor :: VkSamplerYcbcrModelConversionKHR -> VkSamplerYcbcrModelConversionKHR -> VkSamplerYcbcrModelConversionKHR #

complement :: VkSamplerYcbcrModelConversionKHR -> VkSamplerYcbcrModelConversionKHR #

shift :: VkSamplerYcbcrModelConversionKHR -> Int -> VkSamplerYcbcrModelConversionKHR #

rotate :: VkSamplerYcbcrModelConversionKHR -> Int -> VkSamplerYcbcrModelConversionKHR #

zeroBits :: VkSamplerYcbcrModelConversionKHR #

bit :: Int -> VkSamplerYcbcrModelConversionKHR #

setBit :: VkSamplerYcbcrModelConversionKHR -> Int -> VkSamplerYcbcrModelConversionKHR #

clearBit :: VkSamplerYcbcrModelConversionKHR -> Int -> VkSamplerYcbcrModelConversionKHR #

complementBit :: VkSamplerYcbcrModelConversionKHR -> Int -> VkSamplerYcbcrModelConversionKHR #

testBit :: VkSamplerYcbcrModelConversionKHR -> Int -> Bool #

bitSizeMaybe :: VkSamplerYcbcrModelConversionKHR -> Maybe Int #

bitSize :: VkSamplerYcbcrModelConversionKHR -> Int #

isSigned :: VkSamplerYcbcrModelConversionKHR -> Bool #

shiftL :: VkSamplerYcbcrModelConversionKHR -> Int -> VkSamplerYcbcrModelConversionKHR #

unsafeShiftL :: VkSamplerYcbcrModelConversionKHR -> Int -> VkSamplerYcbcrModelConversionKHR #

shiftR :: VkSamplerYcbcrModelConversionKHR -> Int -> VkSamplerYcbcrModelConversionKHR #

unsafeShiftR :: VkSamplerYcbcrModelConversionKHR -> Int -> VkSamplerYcbcrModelConversionKHR #

rotateL :: VkSamplerYcbcrModelConversionKHR -> Int -> VkSamplerYcbcrModelConversionKHR #

rotateR :: VkSamplerYcbcrModelConversionKHR -> Int -> VkSamplerYcbcrModelConversionKHR #

popCount :: VkSamplerYcbcrModelConversionKHR -> Int #

FiniteBits VkSamplerYcbcrModelConversionKHR Source # 
type Rep VkSamplerYcbcrModelConversionKHR Source # 
type Rep VkSamplerYcbcrModelConversionKHR = D1 (MetaData "VkSamplerYcbcrModelConversionKHR" "Graphics.Vulkan.Types.Enum.Sampler" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkSamplerYcbcrModelConversionKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkSamplerYcbcrRange Source #

Instances

Bounded VkSamplerYcbcrRange Source # 
Enum VkSamplerYcbcrRange Source # 
Eq VkSamplerYcbcrRange Source # 
Data VkSamplerYcbcrRange Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkSamplerYcbcrRange -> c VkSamplerYcbcrRange #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkSamplerYcbcrRange #

toConstr :: VkSamplerYcbcrRange -> Constr #

dataTypeOf :: VkSamplerYcbcrRange -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkSamplerYcbcrRange) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkSamplerYcbcrRange) #

gmapT :: (forall b. Data b => b -> b) -> VkSamplerYcbcrRange -> VkSamplerYcbcrRange #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkSamplerYcbcrRange -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkSamplerYcbcrRange -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkSamplerYcbcrRange -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkSamplerYcbcrRange -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkSamplerYcbcrRange -> m VkSamplerYcbcrRange #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSamplerYcbcrRange -> m VkSamplerYcbcrRange #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSamplerYcbcrRange -> m VkSamplerYcbcrRange #

Num VkSamplerYcbcrRange Source # 
Ord VkSamplerYcbcrRange Source # 
Read VkSamplerYcbcrRange Source # 
Show VkSamplerYcbcrRange Source # 
Generic VkSamplerYcbcrRange Source # 
Storable VkSamplerYcbcrRange Source # 
type Rep VkSamplerYcbcrRange Source # 
type Rep VkSamplerYcbcrRange = D1 (MetaData "VkSamplerYcbcrRange" "Graphics.Vulkan.Types.Enum.Sampler" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkSamplerYcbcrRange" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

pattern VK_SAMPLER_YCBCR_RANGE_ITU_FULL :: VkSamplerYcbcrRange Source #

Luma 0..1 maps to 0..255, chroma -0.5..0.5 to 1..255 (clamped)

pattern VK_SAMPLER_YCBCR_RANGE_ITU_NARROW :: VkSamplerYcbcrRange Source #

Luma 0..1 maps to 16..235, chroma -0.5..0.5 to 16..240

newtype VkSamplerYcbcrRangeKHR Source #

Instances

Bounded VkSamplerYcbcrRangeKHR Source # 
Enum VkSamplerYcbcrRangeKHR Source # 
Eq VkSamplerYcbcrRangeKHR Source # 
Integral VkSamplerYcbcrRangeKHR Source # 
Data VkSamplerYcbcrRangeKHR Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkSamplerYcbcrRangeKHR -> c VkSamplerYcbcrRangeKHR #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkSamplerYcbcrRangeKHR #

toConstr :: VkSamplerYcbcrRangeKHR -> Constr #

dataTypeOf :: VkSamplerYcbcrRangeKHR -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkSamplerYcbcrRangeKHR) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkSamplerYcbcrRangeKHR) #

gmapT :: (forall b. Data b => b -> b) -> VkSamplerYcbcrRangeKHR -> VkSamplerYcbcrRangeKHR #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkSamplerYcbcrRangeKHR -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkSamplerYcbcrRangeKHR -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkSamplerYcbcrRangeKHR -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkSamplerYcbcrRangeKHR -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkSamplerYcbcrRangeKHR -> m VkSamplerYcbcrRangeKHR #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSamplerYcbcrRangeKHR -> m VkSamplerYcbcrRangeKHR #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSamplerYcbcrRangeKHR -> m VkSamplerYcbcrRangeKHR #

Num VkSamplerYcbcrRangeKHR Source # 
Ord VkSamplerYcbcrRangeKHR Source # 
Read VkSamplerYcbcrRangeKHR Source # 
Real VkSamplerYcbcrRangeKHR Source # 
Show VkSamplerYcbcrRangeKHR Source # 
Generic VkSamplerYcbcrRangeKHR Source # 
Storable VkSamplerYcbcrRangeKHR Source # 
Bits VkSamplerYcbcrRangeKHR Source # 
FiniteBits VkSamplerYcbcrRangeKHR Source # 
type Rep VkSamplerYcbcrRangeKHR Source # 
type Rep VkSamplerYcbcrRangeKHR = D1 (MetaData "VkSamplerYcbcrRangeKHR" "Graphics.Vulkan.Types.Enum.Sampler" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkSamplerYcbcrRangeKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

data VkSamplerCreateInfo Source #

typedef struct VkSamplerCreateInfo {
    VkStructureType sType;
    const void*            pNext;
    VkSamplerCreateFlags   flags;
    VkFilter               magFilter;
    VkFilter               minFilter;
    VkSamplerMipmapMode    mipmapMode;
    VkSamplerAddressMode   addressModeU;
    VkSamplerAddressMode   addressModeV;
    VkSamplerAddressMode   addressModeW;
    float                  mipLodBias;
    VkBool32               anisotropyEnable;
    float                  maxAnisotropy;
    VkBool32               compareEnable;
    VkCompareOp            compareOp;
    float                  minLod;
    float                  maxLod;
    VkBorderColor          borderColor;
    VkBool32               unnormalizedCoordinates;
} VkSamplerCreateInfo;

VkSamplerCreateInfo registry at www.khronos.org

Instances

Eq VkSamplerCreateInfo Source # 
Ord VkSamplerCreateInfo Source # 
Show VkSamplerCreateInfo Source # 
Storable VkSamplerCreateInfo Source # 
VulkanMarshalPrim VkSamplerCreateInfo Source # 
VulkanMarshal VkSamplerCreateInfo Source # 
CanWriteField "addressModeU" VkSamplerCreateInfo Source # 
CanWriteField "addressModeV" VkSamplerCreateInfo Source # 
CanWriteField "addressModeW" VkSamplerCreateInfo Source # 
CanWriteField "anisotropyEnable" VkSamplerCreateInfo Source # 
CanWriteField "borderColor" VkSamplerCreateInfo Source # 
CanWriteField "compareEnable" VkSamplerCreateInfo Source # 
CanWriteField "compareOp" VkSamplerCreateInfo Source # 
CanWriteField "flags" VkSamplerCreateInfo Source # 
CanWriteField "magFilter" VkSamplerCreateInfo Source # 
CanWriteField "maxAnisotropy" VkSamplerCreateInfo Source # 
CanWriteField "maxLod" VkSamplerCreateInfo Source # 
CanWriteField "minFilter" VkSamplerCreateInfo Source # 
CanWriteField "minLod" VkSamplerCreateInfo Source # 
CanWriteField "mipLodBias" VkSamplerCreateInfo Source # 
CanWriteField "mipmapMode" VkSamplerCreateInfo Source # 
CanWriteField "pNext" VkSamplerCreateInfo Source # 
CanWriteField "sType" VkSamplerCreateInfo Source # 
CanWriteField "unnormalizedCoordinates" VkSamplerCreateInfo Source # 

Methods

writeField :: Ptr VkSamplerCreateInfo -> FieldType "unnormalizedCoordinates" VkSamplerCreateInfo -> IO () Source #

CanReadField "addressModeU" VkSamplerCreateInfo Source # 
CanReadField "addressModeV" VkSamplerCreateInfo Source # 
CanReadField "addressModeW" VkSamplerCreateInfo Source # 
CanReadField "anisotropyEnable" VkSamplerCreateInfo Source # 
CanReadField "borderColor" VkSamplerCreateInfo Source # 
CanReadField "compareEnable" VkSamplerCreateInfo Source # 
CanReadField "compareOp" VkSamplerCreateInfo Source # 
CanReadField "flags" VkSamplerCreateInfo Source # 
CanReadField "magFilter" VkSamplerCreateInfo Source # 
CanReadField "maxAnisotropy" VkSamplerCreateInfo Source # 
CanReadField "maxLod" VkSamplerCreateInfo Source # 
CanReadField "minFilter" VkSamplerCreateInfo Source # 
CanReadField "minLod" VkSamplerCreateInfo Source # 
CanReadField "mipLodBias" VkSamplerCreateInfo Source # 
CanReadField "mipmapMode" VkSamplerCreateInfo Source # 
CanReadField "pNext" VkSamplerCreateInfo Source # 
CanReadField "sType" VkSamplerCreateInfo Source # 
CanReadField "unnormalizedCoordinates" VkSamplerCreateInfo Source # 
HasField "addressModeU" VkSamplerCreateInfo Source # 

Associated Types

type FieldType ("addressModeU" :: Symbol) VkSamplerCreateInfo :: Type Source #

type FieldOptional ("addressModeU" :: Symbol) VkSamplerCreateInfo :: Bool Source #

type FieldOffset ("addressModeU" :: Symbol) VkSamplerCreateInfo :: Nat Source #

type FieldIsArray ("addressModeU" :: Symbol) VkSamplerCreateInfo :: Bool Source #

HasField "addressModeV" VkSamplerCreateInfo Source # 

Associated Types

type FieldType ("addressModeV" :: Symbol) VkSamplerCreateInfo :: Type Source #

type FieldOptional ("addressModeV" :: Symbol) VkSamplerCreateInfo :: Bool Source #

type FieldOffset ("addressModeV" :: Symbol) VkSamplerCreateInfo :: Nat Source #

type FieldIsArray ("addressModeV" :: Symbol) VkSamplerCreateInfo :: Bool Source #

HasField "addressModeW" VkSamplerCreateInfo Source # 

Associated Types

type FieldType ("addressModeW" :: Symbol) VkSamplerCreateInfo :: Type Source #

type FieldOptional ("addressModeW" :: Symbol) VkSamplerCreateInfo :: Bool Source #

type FieldOffset ("addressModeW" :: Symbol) VkSamplerCreateInfo :: Nat Source #

type FieldIsArray ("addressModeW" :: Symbol) VkSamplerCreateInfo :: Bool Source #

HasField "anisotropyEnable" VkSamplerCreateInfo Source # 

Associated Types

type FieldType ("anisotropyEnable" :: Symbol) VkSamplerCreateInfo :: Type Source #

type FieldOptional ("anisotropyEnable" :: Symbol) VkSamplerCreateInfo :: Bool Source #

type FieldOffset ("anisotropyEnable" :: Symbol) VkSamplerCreateInfo :: Nat Source #

type FieldIsArray ("anisotropyEnable" :: Symbol) VkSamplerCreateInfo :: Bool Source #

HasField "borderColor" VkSamplerCreateInfo Source # 

Associated Types

type FieldType ("borderColor" :: Symbol) VkSamplerCreateInfo :: Type Source #

type FieldOptional ("borderColor" :: Symbol) VkSamplerCreateInfo :: Bool Source #

type FieldOffset ("borderColor" :: Symbol) VkSamplerCreateInfo :: Nat Source #

type FieldIsArray ("borderColor" :: Symbol) VkSamplerCreateInfo :: Bool Source #

HasField "compareEnable" VkSamplerCreateInfo Source # 

Associated Types

type FieldType ("compareEnable" :: Symbol) VkSamplerCreateInfo :: Type Source #

type FieldOptional ("compareEnable" :: Symbol) VkSamplerCreateInfo :: Bool Source #

type FieldOffset ("compareEnable" :: Symbol) VkSamplerCreateInfo :: Nat Source #

type FieldIsArray ("compareEnable" :: Symbol) VkSamplerCreateInfo :: Bool Source #

HasField "compareOp" VkSamplerCreateInfo Source # 

Associated Types

type FieldType ("compareOp" :: Symbol) VkSamplerCreateInfo :: Type Source #

type FieldOptional ("compareOp" :: Symbol) VkSamplerCreateInfo :: Bool Source #

type FieldOffset ("compareOp" :: Symbol) VkSamplerCreateInfo :: Nat Source #

type FieldIsArray ("compareOp" :: Symbol) VkSamplerCreateInfo :: Bool Source #

HasField "flags" VkSamplerCreateInfo Source # 
HasField "magFilter" VkSamplerCreateInfo Source # 

Associated Types

type FieldType ("magFilter" :: Symbol) VkSamplerCreateInfo :: Type Source #

type FieldOptional ("magFilter" :: Symbol) VkSamplerCreateInfo :: Bool Source #

type FieldOffset ("magFilter" :: Symbol) VkSamplerCreateInfo :: Nat Source #

type FieldIsArray ("magFilter" :: Symbol) VkSamplerCreateInfo :: Bool Source #

HasField "maxAnisotropy" VkSamplerCreateInfo Source # 

Associated Types

type FieldType ("maxAnisotropy" :: Symbol) VkSamplerCreateInfo :: Type Source #

type FieldOptional ("maxAnisotropy" :: Symbol) VkSamplerCreateInfo :: Bool Source #

type FieldOffset ("maxAnisotropy" :: Symbol) VkSamplerCreateInfo :: Nat Source #

type FieldIsArray ("maxAnisotropy" :: Symbol) VkSamplerCreateInfo :: Bool Source #

HasField "maxLod" VkSamplerCreateInfo Source # 
HasField "minFilter" VkSamplerCreateInfo Source # 

Associated Types

type FieldType ("minFilter" :: Symbol) VkSamplerCreateInfo :: Type Source #

type FieldOptional ("minFilter" :: Symbol) VkSamplerCreateInfo :: Bool Source #

type FieldOffset ("minFilter" :: Symbol) VkSamplerCreateInfo :: Nat Source #

type FieldIsArray ("minFilter" :: Symbol) VkSamplerCreateInfo :: Bool Source #

HasField "minLod" VkSamplerCreateInfo Source # 
HasField "mipLodBias" VkSamplerCreateInfo Source # 

Associated Types

type FieldType ("mipLodBias" :: Symbol) VkSamplerCreateInfo :: Type Source #

type FieldOptional ("mipLodBias" :: Symbol) VkSamplerCreateInfo :: Bool Source #

type FieldOffset ("mipLodBias" :: Symbol) VkSamplerCreateInfo :: Nat Source #

type FieldIsArray ("mipLodBias" :: Symbol) VkSamplerCreateInfo :: Bool Source #

HasField "mipmapMode" VkSamplerCreateInfo Source # 

Associated Types

type FieldType ("mipmapMode" :: Symbol) VkSamplerCreateInfo :: Type Source #

type FieldOptional ("mipmapMode" :: Symbol) VkSamplerCreateInfo :: Bool Source #

type FieldOffset ("mipmapMode" :: Symbol) VkSamplerCreateInfo :: Nat Source #

type FieldIsArray ("mipmapMode" :: Symbol) VkSamplerCreateInfo :: Bool Source #

HasField "pNext" VkSamplerCreateInfo Source # 
HasField "sType" VkSamplerCreateInfo Source # 
HasField "unnormalizedCoordinates" VkSamplerCreateInfo Source # 

Associated Types

type FieldType ("unnormalizedCoordinates" :: Symbol) VkSamplerCreateInfo :: Type Source #

type FieldOptional ("unnormalizedCoordinates" :: Symbol) VkSamplerCreateInfo :: Bool Source #

type FieldOffset ("unnormalizedCoordinates" :: Symbol) VkSamplerCreateInfo :: Nat Source #

type FieldIsArray ("unnormalizedCoordinates" :: Symbol) VkSamplerCreateInfo :: Bool Source #

type StructFields VkSamplerCreateInfo Source # 
type StructFields VkSamplerCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "magFilter" ((:) Symbol "minFilter" ((:) Symbol "mipmapMode" ((:) Symbol "addressModeU" ((:) Symbol "addressModeV" ((:) Symbol "addressModeW" ((:) Symbol "mipLodBias" ((:) Symbol "anisotropyEnable" ((:) Symbol "maxAnisotropy" ((:) Symbol "compareEnable" ((:) Symbol "compareOp" ((:) Symbol "minLod" ((:) Symbol "maxLod" ((:) Symbol "borderColor" ((:) Symbol "unnormalizedCoordinates" ([] Symbol))))))))))))))))))
type CUnionType VkSamplerCreateInfo Source # 
type ReturnedOnly VkSamplerCreateInfo Source # 
type StructExtends VkSamplerCreateInfo Source # 
type FieldType "addressModeU" VkSamplerCreateInfo Source # 
type FieldType "addressModeV" VkSamplerCreateInfo Source # 
type FieldType "addressModeW" VkSamplerCreateInfo Source # 
type FieldType "anisotropyEnable" VkSamplerCreateInfo Source # 
type FieldType "anisotropyEnable" VkSamplerCreateInfo = VkBool32
type FieldType "borderColor" VkSamplerCreateInfo Source # 
type FieldType "compareEnable" VkSamplerCreateInfo Source # 
type FieldType "compareEnable" VkSamplerCreateInfo = VkBool32
type FieldType "compareOp" VkSamplerCreateInfo Source # 
type FieldType "flags" VkSamplerCreateInfo Source # 
type FieldType "magFilter" VkSamplerCreateInfo Source # 
type FieldType "maxAnisotropy" VkSamplerCreateInfo Source # 
type FieldType "maxAnisotropy" VkSamplerCreateInfo = Float
type FieldType "maxLod" VkSamplerCreateInfo Source # 
type FieldType "minFilter" VkSamplerCreateInfo Source # 
type FieldType "minLod" VkSamplerCreateInfo Source # 
type FieldType "mipLodBias" VkSamplerCreateInfo Source # 
type FieldType "mipLodBias" VkSamplerCreateInfo = Float
type FieldType "mipmapMode" VkSamplerCreateInfo Source # 
type FieldType "pNext" VkSamplerCreateInfo Source # 
type FieldType "sType" VkSamplerCreateInfo Source # 
type FieldType "unnormalizedCoordinates" VkSamplerCreateInfo Source # 
type FieldType "unnormalizedCoordinates" VkSamplerCreateInfo = VkBool32
type FieldOptional "addressModeU" VkSamplerCreateInfo Source # 
type FieldOptional "addressModeV" VkSamplerCreateInfo Source # 
type FieldOptional "addressModeW" VkSamplerCreateInfo Source # 
type FieldOptional "anisotropyEnable" VkSamplerCreateInfo Source # 
type FieldOptional "anisotropyEnable" VkSamplerCreateInfo = False
type FieldOptional "borderColor" VkSamplerCreateInfo Source # 
type FieldOptional "compareEnable" VkSamplerCreateInfo Source # 
type FieldOptional "compareEnable" VkSamplerCreateInfo = False
type FieldOptional "compareOp" VkSamplerCreateInfo Source # 
type FieldOptional "flags" VkSamplerCreateInfo Source # 
type FieldOptional "magFilter" VkSamplerCreateInfo Source # 
type FieldOptional "maxAnisotropy" VkSamplerCreateInfo Source # 
type FieldOptional "maxAnisotropy" VkSamplerCreateInfo = False
type FieldOptional "maxLod" VkSamplerCreateInfo Source # 
type FieldOptional "minFilter" VkSamplerCreateInfo Source # 
type FieldOptional "minLod" VkSamplerCreateInfo Source # 
type FieldOptional "mipLodBias" VkSamplerCreateInfo Source # 
type FieldOptional "mipmapMode" VkSamplerCreateInfo Source # 
type FieldOptional "pNext" VkSamplerCreateInfo Source # 
type FieldOptional "sType" VkSamplerCreateInfo Source # 
type FieldOptional "unnormalizedCoordinates" VkSamplerCreateInfo Source # 
type FieldOptional "unnormalizedCoordinates" VkSamplerCreateInfo = False
type FieldOffset "addressModeU" VkSamplerCreateInfo Source # 
type FieldOffset "addressModeU" VkSamplerCreateInfo = 32
type FieldOffset "addressModeV" VkSamplerCreateInfo Source # 
type FieldOffset "addressModeV" VkSamplerCreateInfo = 36
type FieldOffset "addressModeW" VkSamplerCreateInfo Source # 
type FieldOffset "addressModeW" VkSamplerCreateInfo = 40
type FieldOffset "anisotropyEnable" VkSamplerCreateInfo Source # 
type FieldOffset "anisotropyEnable" VkSamplerCreateInfo = 48
type FieldOffset "borderColor" VkSamplerCreateInfo Source # 
type FieldOffset "borderColor" VkSamplerCreateInfo = 72
type FieldOffset "compareEnable" VkSamplerCreateInfo Source # 
type FieldOffset "compareEnable" VkSamplerCreateInfo = 56
type FieldOffset "compareOp" VkSamplerCreateInfo Source # 
type FieldOffset "compareOp" VkSamplerCreateInfo = 60
type FieldOffset "flags" VkSamplerCreateInfo Source # 
type FieldOffset "magFilter" VkSamplerCreateInfo Source # 
type FieldOffset "magFilter" VkSamplerCreateInfo = 20
type FieldOffset "maxAnisotropy" VkSamplerCreateInfo Source # 
type FieldOffset "maxAnisotropy" VkSamplerCreateInfo = 52
type FieldOffset "maxLod" VkSamplerCreateInfo Source # 
type FieldOffset "maxLod" VkSamplerCreateInfo = 68
type FieldOffset "minFilter" VkSamplerCreateInfo Source # 
type FieldOffset "minFilter" VkSamplerCreateInfo = 24
type FieldOffset "minLod" VkSamplerCreateInfo Source # 
type FieldOffset "minLod" VkSamplerCreateInfo = 64
type FieldOffset "mipLodBias" VkSamplerCreateInfo Source # 
type FieldOffset "mipLodBias" VkSamplerCreateInfo = 44
type FieldOffset "mipmapMode" VkSamplerCreateInfo Source # 
type FieldOffset "mipmapMode" VkSamplerCreateInfo = 28
type FieldOffset "pNext" VkSamplerCreateInfo Source # 
type FieldOffset "sType" VkSamplerCreateInfo Source # 
type FieldOffset "unnormalizedCoordinates" VkSamplerCreateInfo Source # 
type FieldOffset "unnormalizedCoordinates" VkSamplerCreateInfo = 76
type FieldIsArray "addressModeU" VkSamplerCreateInfo Source # 
type FieldIsArray "addressModeU" VkSamplerCreateInfo = False
type FieldIsArray "addressModeV" VkSamplerCreateInfo Source # 
type FieldIsArray "addressModeV" VkSamplerCreateInfo = False
type FieldIsArray "addressModeW" VkSamplerCreateInfo Source # 
type FieldIsArray "addressModeW" VkSamplerCreateInfo = False
type FieldIsArray "anisotropyEnable" VkSamplerCreateInfo Source # 
type FieldIsArray "anisotropyEnable" VkSamplerCreateInfo = False
type FieldIsArray "borderColor" VkSamplerCreateInfo Source # 
type FieldIsArray "compareEnable" VkSamplerCreateInfo Source # 
type FieldIsArray "compareEnable" VkSamplerCreateInfo = False
type FieldIsArray "compareOp" VkSamplerCreateInfo Source # 
type FieldIsArray "flags" VkSamplerCreateInfo Source # 
type FieldIsArray "magFilter" VkSamplerCreateInfo Source # 
type FieldIsArray "maxAnisotropy" VkSamplerCreateInfo Source # 
type FieldIsArray "maxAnisotropy" VkSamplerCreateInfo = False
type FieldIsArray "maxLod" VkSamplerCreateInfo Source # 
type FieldIsArray "minFilter" VkSamplerCreateInfo Source # 
type FieldIsArray "minLod" VkSamplerCreateInfo Source # 
type FieldIsArray "mipLodBias" VkSamplerCreateInfo Source # 
type FieldIsArray "mipmapMode" VkSamplerCreateInfo Source # 
type FieldIsArray "pNext" VkSamplerCreateInfo Source # 
type FieldIsArray "sType" VkSamplerCreateInfo Source # 
type FieldIsArray "unnormalizedCoordinates" VkSamplerCreateInfo Source # 
type FieldIsArray "unnormalizedCoordinates" VkSamplerCreateInfo = False

data VkSamplerReductionModeCreateInfoEXT Source #

typedef struct VkSamplerReductionModeCreateInfoEXT {
    VkStructureType sType;
    const void*            pNext;
    VkSamplerReductionModeEXT reductionMode;
} VkSamplerReductionModeCreateInfoEXT;

VkSamplerReductionModeCreateInfoEXT registry at www.khronos.org

Instances

Eq VkSamplerReductionModeCreateInfoEXT Source # 
Ord VkSamplerReductionModeCreateInfoEXT Source # 
Show VkSamplerReductionModeCreateInfoEXT Source # 
Storable VkSamplerReductionModeCreateInfoEXT Source # 
VulkanMarshalPrim VkSamplerReductionModeCreateInfoEXT Source # 
VulkanMarshal VkSamplerReductionModeCreateInfoEXT Source # 
CanWriteField "pNext" VkSamplerReductionModeCreateInfoEXT Source # 
CanWriteField "reductionMode" VkSamplerReductionModeCreateInfoEXT Source # 
CanWriteField "sType" VkSamplerReductionModeCreateInfoEXT Source # 
CanReadField "pNext" VkSamplerReductionModeCreateInfoEXT Source # 
CanReadField "reductionMode" VkSamplerReductionModeCreateInfoEXT Source # 
CanReadField "sType" VkSamplerReductionModeCreateInfoEXT Source # 
HasField "pNext" VkSamplerReductionModeCreateInfoEXT Source # 
HasField "reductionMode" VkSamplerReductionModeCreateInfoEXT Source # 
HasField "sType" VkSamplerReductionModeCreateInfoEXT Source # 
type StructFields VkSamplerReductionModeCreateInfoEXT Source # 
type StructFields VkSamplerReductionModeCreateInfoEXT = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "reductionMode" ([] Symbol)))
type CUnionType VkSamplerReductionModeCreateInfoEXT Source # 
type ReturnedOnly VkSamplerReductionModeCreateInfoEXT Source # 
type StructExtends VkSamplerReductionModeCreateInfoEXT Source # 
type FieldType "pNext" VkSamplerReductionModeCreateInfoEXT Source # 
type FieldType "reductionMode" VkSamplerReductionModeCreateInfoEXT Source # 
type FieldType "sType" VkSamplerReductionModeCreateInfoEXT Source # 
type FieldOptional "pNext" VkSamplerReductionModeCreateInfoEXT Source # 
type FieldOptional "reductionMode" VkSamplerReductionModeCreateInfoEXT Source # 
type FieldOptional "sType" VkSamplerReductionModeCreateInfoEXT Source # 
type FieldOffset "pNext" VkSamplerReductionModeCreateInfoEXT Source # 
type FieldOffset "reductionMode" VkSamplerReductionModeCreateInfoEXT Source # 
type FieldOffset "sType" VkSamplerReductionModeCreateInfoEXT Source # 
type FieldIsArray "pNext" VkSamplerReductionModeCreateInfoEXT Source # 
type FieldIsArray "reductionMode" VkSamplerReductionModeCreateInfoEXT Source # 
type FieldIsArray "sType" VkSamplerReductionModeCreateInfoEXT Source # 

data VkSamplerYcbcrConversionCreateInfo Source #

typedef struct VkSamplerYcbcrConversionCreateInfo {
    VkStructureType sType;
    const void*                      pNext;
    VkFormat                         format;
    VkSamplerYcbcrModelConversion ycbcrModel;
    VkSamplerYcbcrRange           ycbcrRange;
    VkComponentMapping               components;
    VkChromaLocation              xChromaOffset;
    VkChromaLocation              yChromaOffset;
    VkFilter                         chromaFilter;
    VkBool32                         forceExplicitReconstruction;
} VkSamplerYcbcrConversionCreateInfo;

VkSamplerYcbcrConversionCreateInfo registry at www.khronos.org

Instances

Eq VkSamplerYcbcrConversionCreateInfo Source # 
Ord VkSamplerYcbcrConversionCreateInfo Source # 
Show VkSamplerYcbcrConversionCreateInfo Source # 
Storable VkSamplerYcbcrConversionCreateInfo Source # 
VulkanMarshalPrim VkSamplerYcbcrConversionCreateInfo Source # 
VulkanMarshal VkSamplerYcbcrConversionCreateInfo Source # 
CanWriteField "chromaFilter" VkSamplerYcbcrConversionCreateInfo Source # 
CanWriteField "components" VkSamplerYcbcrConversionCreateInfo Source # 
CanWriteField "forceExplicitReconstruction" VkSamplerYcbcrConversionCreateInfo Source # 
CanWriteField "format" VkSamplerYcbcrConversionCreateInfo Source # 
CanWriteField "pNext" VkSamplerYcbcrConversionCreateInfo Source # 
CanWriteField "sType" VkSamplerYcbcrConversionCreateInfo Source # 
CanWriteField "xChromaOffset" VkSamplerYcbcrConversionCreateInfo Source # 
CanWriteField "yChromaOffset" VkSamplerYcbcrConversionCreateInfo Source # 
CanWriteField "ycbcrModel" VkSamplerYcbcrConversionCreateInfo Source # 
CanWriteField "ycbcrRange" VkSamplerYcbcrConversionCreateInfo Source # 
CanReadField "chromaFilter" VkSamplerYcbcrConversionCreateInfo Source # 
CanReadField "components" VkSamplerYcbcrConversionCreateInfo Source # 
CanReadField "forceExplicitReconstruction" VkSamplerYcbcrConversionCreateInfo Source # 
CanReadField "format" VkSamplerYcbcrConversionCreateInfo Source # 
CanReadField "pNext" VkSamplerYcbcrConversionCreateInfo Source # 
CanReadField "sType" VkSamplerYcbcrConversionCreateInfo Source # 
CanReadField "xChromaOffset" VkSamplerYcbcrConversionCreateInfo Source # 
CanReadField "yChromaOffset" VkSamplerYcbcrConversionCreateInfo Source # 
CanReadField "ycbcrModel" VkSamplerYcbcrConversionCreateInfo Source # 
CanReadField "ycbcrRange" VkSamplerYcbcrConversionCreateInfo Source # 
HasField "chromaFilter" VkSamplerYcbcrConversionCreateInfo Source # 
HasField "components" VkSamplerYcbcrConversionCreateInfo Source # 
HasField "forceExplicitReconstruction" VkSamplerYcbcrConversionCreateInfo Source # 

Associated Types

type FieldType ("forceExplicitReconstruction" :: Symbol) VkSamplerYcbcrConversionCreateInfo :: Type Source #

type FieldOptional ("forceExplicitReconstruction" :: Symbol) VkSamplerYcbcrConversionCreateInfo :: Bool Source #

type FieldOffset ("forceExplicitReconstruction" :: Symbol) VkSamplerYcbcrConversionCreateInfo :: Nat Source #

type FieldIsArray ("forceExplicitReconstruction" :: Symbol) VkSamplerYcbcrConversionCreateInfo :: Bool Source #

HasField "format" VkSamplerYcbcrConversionCreateInfo Source # 
HasField "pNext" VkSamplerYcbcrConversionCreateInfo Source # 
HasField "sType" VkSamplerYcbcrConversionCreateInfo Source # 
HasField "xChromaOffset" VkSamplerYcbcrConversionCreateInfo Source # 
HasField "yChromaOffset" VkSamplerYcbcrConversionCreateInfo Source # 
HasField "ycbcrModel" VkSamplerYcbcrConversionCreateInfo Source # 
HasField "ycbcrRange" VkSamplerYcbcrConversionCreateInfo Source # 
type StructFields VkSamplerYcbcrConversionCreateInfo Source # 
type StructFields VkSamplerYcbcrConversionCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "format" ((:) Symbol "ycbcrModel" ((:) Symbol "ycbcrRange" ((:) Symbol "components" ((:) Symbol "xChromaOffset" ((:) Symbol "yChromaOffset" ((:) Symbol "chromaFilter" ((:) Symbol "forceExplicitReconstruction" ([] Symbol))))))))))
type CUnionType VkSamplerYcbcrConversionCreateInfo Source # 
type ReturnedOnly VkSamplerYcbcrConversionCreateInfo Source # 
type StructExtends VkSamplerYcbcrConversionCreateInfo Source # 
type FieldType "chromaFilter" VkSamplerYcbcrConversionCreateInfo Source # 
type FieldType "components" VkSamplerYcbcrConversionCreateInfo Source # 
type FieldType "forceExplicitReconstruction" VkSamplerYcbcrConversionCreateInfo Source # 
type FieldType "forceExplicitReconstruction" VkSamplerYcbcrConversionCreateInfo = VkBool32
type FieldType "format" VkSamplerYcbcrConversionCreateInfo Source # 
type FieldType "pNext" VkSamplerYcbcrConversionCreateInfo Source # 
type FieldType "sType" VkSamplerYcbcrConversionCreateInfo Source # 
type FieldType "xChromaOffset" VkSamplerYcbcrConversionCreateInfo Source # 
type FieldType "yChromaOffset" VkSamplerYcbcrConversionCreateInfo Source # 
type FieldType "ycbcrModel" VkSamplerYcbcrConversionCreateInfo Source # 
type FieldType "ycbcrRange" VkSamplerYcbcrConversionCreateInfo Source # 
type FieldOptional "chromaFilter" VkSamplerYcbcrConversionCreateInfo Source # 
type FieldOptional "components" VkSamplerYcbcrConversionCreateInfo Source # 
type FieldOptional "forceExplicitReconstruction" VkSamplerYcbcrConversionCreateInfo Source # 
type FieldOptional "forceExplicitReconstruction" VkSamplerYcbcrConversionCreateInfo = False
type FieldOptional "format" VkSamplerYcbcrConversionCreateInfo Source # 
type FieldOptional "pNext" VkSamplerYcbcrConversionCreateInfo Source # 
type FieldOptional "sType" VkSamplerYcbcrConversionCreateInfo Source # 
type FieldOptional "xChromaOffset" VkSamplerYcbcrConversionCreateInfo Source # 
type FieldOptional "yChromaOffset" VkSamplerYcbcrConversionCreateInfo Source # 
type FieldOptional "ycbcrModel" VkSamplerYcbcrConversionCreateInfo Source # 
type FieldOptional "ycbcrRange" VkSamplerYcbcrConversionCreateInfo Source # 
type FieldOffset "chromaFilter" VkSamplerYcbcrConversionCreateInfo Source # 
type FieldOffset "components" VkSamplerYcbcrConversionCreateInfo Source # 
type FieldOffset "forceExplicitReconstruction" VkSamplerYcbcrConversionCreateInfo Source # 
type FieldOffset "forceExplicitReconstruction" VkSamplerYcbcrConversionCreateInfo = 56
type FieldOffset "format" VkSamplerYcbcrConversionCreateInfo Source # 
type FieldOffset "pNext" VkSamplerYcbcrConversionCreateInfo Source # 
type FieldOffset "sType" VkSamplerYcbcrConversionCreateInfo Source # 
type FieldOffset "xChromaOffset" VkSamplerYcbcrConversionCreateInfo Source # 
type FieldOffset "yChromaOffset" VkSamplerYcbcrConversionCreateInfo Source # 
type FieldOffset "ycbcrModel" VkSamplerYcbcrConversionCreateInfo Source # 
type FieldOffset "ycbcrRange" VkSamplerYcbcrConversionCreateInfo Source # 
type FieldIsArray "chromaFilter" VkSamplerYcbcrConversionCreateInfo Source # 
type FieldIsArray "components" VkSamplerYcbcrConversionCreateInfo Source # 
type FieldIsArray "forceExplicitReconstruction" VkSamplerYcbcrConversionCreateInfo Source # 
type FieldIsArray "forceExplicitReconstruction" VkSamplerYcbcrConversionCreateInfo = False
type FieldIsArray "format" VkSamplerYcbcrConversionCreateInfo Source # 
type FieldIsArray "pNext" VkSamplerYcbcrConversionCreateInfo Source # 
type FieldIsArray "sType" VkSamplerYcbcrConversionCreateInfo Source # 
type FieldIsArray "xChromaOffset" VkSamplerYcbcrConversionCreateInfo Source # 
type FieldIsArray "yChromaOffset" VkSamplerYcbcrConversionCreateInfo Source # 
type FieldIsArray "ycbcrModel" VkSamplerYcbcrConversionCreateInfo Source # 
type FieldIsArray "ycbcrRange" VkSamplerYcbcrConversionCreateInfo Source # 

data VkSamplerYcbcrConversionImageFormatProperties Source #

typedef struct VkSamplerYcbcrConversionImageFormatProperties {
    VkStructureType sType;
    void*      pNext;
    uint32_t                         combinedImageSamplerDescriptorCount;
} VkSamplerYcbcrConversionImageFormatProperties;

VkSamplerYcbcrConversionImageFormatProperties registry at www.khronos.org

Instances

Eq VkSamplerYcbcrConversionImageFormatProperties Source # 
Ord VkSamplerYcbcrConversionImageFormatProperties Source # 
Show VkSamplerYcbcrConversionImageFormatProperties Source # 
Storable VkSamplerYcbcrConversionImageFormatProperties Source # 
VulkanMarshalPrim VkSamplerYcbcrConversionImageFormatProperties Source # 
VulkanMarshal VkSamplerYcbcrConversionImageFormatProperties Source # 
CanWriteField "combinedImageSamplerDescriptorCount" VkSamplerYcbcrConversionImageFormatProperties Source # 
CanWriteField "pNext" VkSamplerYcbcrConversionImageFormatProperties Source # 
CanWriteField "sType" VkSamplerYcbcrConversionImageFormatProperties Source # 
CanReadField "combinedImageSamplerDescriptorCount" VkSamplerYcbcrConversionImageFormatProperties Source # 
CanReadField "pNext" VkSamplerYcbcrConversionImageFormatProperties Source # 
CanReadField "sType" VkSamplerYcbcrConversionImageFormatProperties Source # 
HasField "combinedImageSamplerDescriptorCount" VkSamplerYcbcrConversionImageFormatProperties Source # 

Associated Types

type FieldType ("combinedImageSamplerDescriptorCount" :: Symbol) VkSamplerYcbcrConversionImageFormatProperties :: Type Source #

type FieldOptional ("combinedImageSamplerDescriptorCount" :: Symbol) VkSamplerYcbcrConversionImageFormatProperties :: Bool Source #

type FieldOffset ("combinedImageSamplerDescriptorCount" :: Symbol) VkSamplerYcbcrConversionImageFormatProperties :: Nat Source #

type FieldIsArray ("combinedImageSamplerDescriptorCount" :: Symbol) VkSamplerYcbcrConversionImageFormatProperties :: Bool Source #

HasField "pNext" VkSamplerYcbcrConversionImageFormatProperties Source # 
HasField "sType" VkSamplerYcbcrConversionImageFormatProperties Source # 
type StructFields VkSamplerYcbcrConversionImageFormatProperties Source # 
type StructFields VkSamplerYcbcrConversionImageFormatProperties = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "combinedImageSamplerDescriptorCount" ([] Symbol)))
type CUnionType VkSamplerYcbcrConversionImageFormatProperties Source # 
type ReturnedOnly VkSamplerYcbcrConversionImageFormatProperties Source # 
type StructExtends VkSamplerYcbcrConversionImageFormatProperties Source # 
type FieldType "combinedImageSamplerDescriptorCount" VkSamplerYcbcrConversionImageFormatProperties Source # 
type FieldType "combinedImageSamplerDescriptorCount" VkSamplerYcbcrConversionImageFormatProperties = Word32
type FieldType "pNext" VkSamplerYcbcrConversionImageFormatProperties Source # 
type FieldType "sType" VkSamplerYcbcrConversionImageFormatProperties Source # 
type FieldOptional "combinedImageSamplerDescriptorCount" VkSamplerYcbcrConversionImageFormatProperties Source # 
type FieldOptional "combinedImageSamplerDescriptorCount" VkSamplerYcbcrConversionImageFormatProperties = False
type FieldOptional "pNext" VkSamplerYcbcrConversionImageFormatProperties Source # 
type FieldOptional "sType" VkSamplerYcbcrConversionImageFormatProperties Source # 
type FieldOffset "combinedImageSamplerDescriptorCount" VkSamplerYcbcrConversionImageFormatProperties Source # 
type FieldOffset "combinedImageSamplerDescriptorCount" VkSamplerYcbcrConversionImageFormatProperties = 16
type FieldOffset "pNext" VkSamplerYcbcrConversionImageFormatProperties Source # 
type FieldOffset "sType" VkSamplerYcbcrConversionImageFormatProperties Source # 
type FieldIsArray "combinedImageSamplerDescriptorCount" VkSamplerYcbcrConversionImageFormatProperties Source # 
type FieldIsArray "combinedImageSamplerDescriptorCount" VkSamplerYcbcrConversionImageFormatProperties = False
type FieldIsArray "pNext" VkSamplerYcbcrConversionImageFormatProperties Source # 
type FieldIsArray "sType" VkSamplerYcbcrConversionImageFormatProperties Source # 

data VkSamplerYcbcrConversionInfo Source #

typedef struct VkSamplerYcbcrConversionInfo {
    VkStructureType sType;
    const void*                      pNext;
    VkSamplerYcbcrConversion      conversion;
} VkSamplerYcbcrConversionInfo;

VkSamplerYcbcrConversionInfo registry at www.khronos.org

Instances

Eq VkSamplerYcbcrConversionInfo Source # 
Ord VkSamplerYcbcrConversionInfo Source # 
Show VkSamplerYcbcrConversionInfo Source # 
Storable VkSamplerYcbcrConversionInfo Source # 
VulkanMarshalPrim VkSamplerYcbcrConversionInfo Source # 
VulkanMarshal VkSamplerYcbcrConversionInfo Source # 
CanWriteField "conversion" VkSamplerYcbcrConversionInfo Source # 
CanWriteField "pNext" VkSamplerYcbcrConversionInfo Source # 
CanWriteField "sType" VkSamplerYcbcrConversionInfo Source # 
CanReadField "conversion" VkSamplerYcbcrConversionInfo Source # 
CanReadField "pNext" VkSamplerYcbcrConversionInfo Source # 
CanReadField "sType" VkSamplerYcbcrConversionInfo Source # 
HasField "conversion" VkSamplerYcbcrConversionInfo Source # 
HasField "pNext" VkSamplerYcbcrConversionInfo Source # 
HasField "sType" VkSamplerYcbcrConversionInfo Source # 
type StructFields VkSamplerYcbcrConversionInfo Source # 
type StructFields VkSamplerYcbcrConversionInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "conversion" ([] Symbol)))
type CUnionType VkSamplerYcbcrConversionInfo Source # 
type ReturnedOnly VkSamplerYcbcrConversionInfo Source # 
type StructExtends VkSamplerYcbcrConversionInfo Source # 
type FieldType "conversion" VkSamplerYcbcrConversionInfo Source # 
type FieldType "pNext" VkSamplerYcbcrConversionInfo Source # 
type FieldType "sType" VkSamplerYcbcrConversionInfo Source # 
type FieldOptional "conversion" VkSamplerYcbcrConversionInfo Source # 
type FieldOptional "pNext" VkSamplerYcbcrConversionInfo Source # 
type FieldOptional "sType" VkSamplerYcbcrConversionInfo Source # 
type FieldOffset "conversion" VkSamplerYcbcrConversionInfo Source # 
type FieldOffset "pNext" VkSamplerYcbcrConversionInfo Source # 
type FieldOffset "sType" VkSamplerYcbcrConversionInfo Source # 
type FieldIsArray "conversion" VkSamplerYcbcrConversionInfo Source # 
type FieldIsArray "pNext" VkSamplerYcbcrConversionInfo Source # 
type FieldIsArray "sType" VkSamplerYcbcrConversionInfo Source # 

type VkCreateSamplerYcbcrConversion = "vkCreateSamplerYcbcrConversion" Source #

type HS_vkCreateSamplerYcbcrConversion Source #

Arguments

 = VkDevice

device

-> Ptr VkSamplerYcbcrConversionCreateInfo

pCreateInfo

-> Ptr VkAllocationCallbacks

pAllocator

-> Ptr VkSamplerYcbcrConversion

pYcbcrConversion

-> IO VkResult 

Success codes: VK_SUCCESS.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY.

VkResult vkCreateSamplerYcbcrConversion
    ( VkDevice device
    , const VkSamplerYcbcrConversionCreateInfo* pCreateInfo
    , const VkAllocationCallbacks* pAllocator
    , VkSamplerYcbcrConversion* pYcbcrConversion
    )

vkCreateSamplerYcbcrConversion registry at www.khronos.org

vkCreateSamplerYcbcrConversion Source #

Arguments

:: VkDevice

device

-> Ptr VkSamplerYcbcrConversionCreateInfo

pCreateInfo

-> Ptr VkAllocationCallbacks

pAllocator

-> Ptr VkSamplerYcbcrConversion

pYcbcrConversion

-> IO VkResult 

Success codes: VK_SUCCESS.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY.

VkResult vkCreateSamplerYcbcrConversion
    ( VkDevice device
    , const VkSamplerYcbcrConversionCreateInfo* pCreateInfo
    , const VkAllocationCallbacks* pAllocator
    , VkSamplerYcbcrConversion* pYcbcrConversion
    )

vkCreateSamplerYcbcrConversion registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myCreateSamplerYcbcrConversion <- vkGetDeviceProc @VkCreateSamplerYcbcrConversion vkDevice

or less efficient:

myCreateSamplerYcbcrConversion <- vkGetProc @VkCreateSamplerYcbcrConversion

Note: vkCreateSamplerYcbcrConversionUnsafe and vkCreateSamplerYcbcrConversionSafe are the unsafe and safe FFI imports of this function, respectively. vkCreateSamplerYcbcrConversion is an alias of vkCreateSamplerYcbcrConversionUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkCreateSamplerYcbcrConversionSafe.

vkCreateSamplerYcbcrConversionUnsafe Source #

Arguments

:: VkDevice

device

-> Ptr VkSamplerYcbcrConversionCreateInfo

pCreateInfo

-> Ptr VkAllocationCallbacks

pAllocator

-> Ptr VkSamplerYcbcrConversion

pYcbcrConversion

-> IO VkResult 

Success codes: VK_SUCCESS.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY.

VkResult vkCreateSamplerYcbcrConversion
    ( VkDevice device
    , const VkSamplerYcbcrConversionCreateInfo* pCreateInfo
    , const VkAllocationCallbacks* pAllocator
    , VkSamplerYcbcrConversion* pYcbcrConversion
    )

vkCreateSamplerYcbcrConversion registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myCreateSamplerYcbcrConversion <- vkGetDeviceProc @VkCreateSamplerYcbcrConversion vkDevice

or less efficient:

myCreateSamplerYcbcrConversion <- vkGetProc @VkCreateSamplerYcbcrConversion

Note: vkCreateSamplerYcbcrConversionUnsafe and vkCreateSamplerYcbcrConversionSafe are the unsafe and safe FFI imports of this function, respectively. vkCreateSamplerYcbcrConversion is an alias of vkCreateSamplerYcbcrConversionUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkCreateSamplerYcbcrConversionSafe.

vkCreateSamplerYcbcrConversionSafe Source #

Arguments

:: VkDevice

device

-> Ptr VkSamplerYcbcrConversionCreateInfo

pCreateInfo

-> Ptr VkAllocationCallbacks

pAllocator

-> Ptr VkSamplerYcbcrConversion

pYcbcrConversion

-> IO VkResult 

Success codes: VK_SUCCESS.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY.

VkResult vkCreateSamplerYcbcrConversion
    ( VkDevice device
    , const VkSamplerYcbcrConversionCreateInfo* pCreateInfo
    , const VkAllocationCallbacks* pAllocator
    , VkSamplerYcbcrConversion* pYcbcrConversion
    )

vkCreateSamplerYcbcrConversion registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myCreateSamplerYcbcrConversion <- vkGetDeviceProc @VkCreateSamplerYcbcrConversion vkDevice

or less efficient:

myCreateSamplerYcbcrConversion <- vkGetProc @VkCreateSamplerYcbcrConversion

Note: vkCreateSamplerYcbcrConversionUnsafe and vkCreateSamplerYcbcrConversionSafe are the unsafe and safe FFI imports of this function, respectively. vkCreateSamplerYcbcrConversion is an alias of vkCreateSamplerYcbcrConversionUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkCreateSamplerYcbcrConversionSafe.

type VkDestroySamplerYcbcrConversion = "vkDestroySamplerYcbcrConversion" Source #

type HS_vkDestroySamplerYcbcrConversion Source #

Arguments

 = VkDevice

device

-> VkSamplerYcbcrConversion

ycbcrConversion

-> Ptr VkAllocationCallbacks

pAllocator

-> IO () 
void vkDestroySamplerYcbcrConversion
    ( VkDevice device
    , VkSamplerYcbcrConversion ycbcrConversion
    , const VkAllocationCallbacks* pAllocator
    )

vkDestroySamplerYcbcrConversion registry at www.khronos.org

vkDestroySamplerYcbcrConversion Source #

Arguments

:: VkDevice

device

-> VkSamplerYcbcrConversion

ycbcrConversion

-> Ptr VkAllocationCallbacks

pAllocator

-> IO () 
void vkDestroySamplerYcbcrConversion
    ( VkDevice device
    , VkSamplerYcbcrConversion ycbcrConversion
    , const VkAllocationCallbacks* pAllocator
    )

vkDestroySamplerYcbcrConversion registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myDestroySamplerYcbcrConversion <- vkGetDeviceProc @VkDestroySamplerYcbcrConversion vkDevice

or less efficient:

myDestroySamplerYcbcrConversion <- vkGetProc @VkDestroySamplerYcbcrConversion

Note: vkDestroySamplerYcbcrConversionUnsafe and vkDestroySamplerYcbcrConversionSafe are the unsafe and safe FFI imports of this function, respectively. vkDestroySamplerYcbcrConversion is an alias of vkDestroySamplerYcbcrConversionUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkDestroySamplerYcbcrConversionSafe.

vkDestroySamplerYcbcrConversionUnsafe Source #

Arguments

:: VkDevice

device

-> VkSamplerYcbcrConversion

ycbcrConversion

-> Ptr VkAllocationCallbacks

pAllocator

-> IO () 
void vkDestroySamplerYcbcrConversion
    ( VkDevice device
    , VkSamplerYcbcrConversion ycbcrConversion
    , const VkAllocationCallbacks* pAllocator
    )

vkDestroySamplerYcbcrConversion registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myDestroySamplerYcbcrConversion <- vkGetDeviceProc @VkDestroySamplerYcbcrConversion vkDevice

or less efficient:

myDestroySamplerYcbcrConversion <- vkGetProc @VkDestroySamplerYcbcrConversion

Note: vkDestroySamplerYcbcrConversionUnsafe and vkDestroySamplerYcbcrConversionSafe are the unsafe and safe FFI imports of this function, respectively. vkDestroySamplerYcbcrConversion is an alias of vkDestroySamplerYcbcrConversionUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkDestroySamplerYcbcrConversionSafe.

vkDestroySamplerYcbcrConversionSafe Source #

Arguments

:: VkDevice

device

-> VkSamplerYcbcrConversion

ycbcrConversion

-> Ptr VkAllocationCallbacks

pAllocator

-> IO () 
void vkDestroySamplerYcbcrConversion
    ( VkDevice device
    , VkSamplerYcbcrConversion ycbcrConversion
    , const VkAllocationCallbacks* pAllocator
    )

vkDestroySamplerYcbcrConversion registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myDestroySamplerYcbcrConversion <- vkGetDeviceProc @VkDestroySamplerYcbcrConversion vkDevice

or less efficient:

myDestroySamplerYcbcrConversion <- vkGetProc @VkDestroySamplerYcbcrConversion

Note: vkDestroySamplerYcbcrConversionUnsafe and vkDestroySamplerYcbcrConversionSafe are the unsafe and safe FFI imports of this function, respectively. vkDestroySamplerYcbcrConversion is an alias of vkDestroySamplerYcbcrConversionUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkDestroySamplerYcbcrConversionSafe.

newtype VkInternalAllocationType Source #

Instances

Bounded VkInternalAllocationType Source # 
Enum VkInternalAllocationType Source # 
Eq VkInternalAllocationType Source # 
Data VkInternalAllocationType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkInternalAllocationType -> c VkInternalAllocationType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkInternalAllocationType #

toConstr :: VkInternalAllocationType -> Constr #

dataTypeOf :: VkInternalAllocationType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkInternalAllocationType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkInternalAllocationType) #

gmapT :: (forall b. Data b => b -> b) -> VkInternalAllocationType -> VkInternalAllocationType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkInternalAllocationType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkInternalAllocationType -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkInternalAllocationType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkInternalAllocationType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkInternalAllocationType -> m VkInternalAllocationType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkInternalAllocationType -> m VkInternalAllocationType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkInternalAllocationType -> m VkInternalAllocationType #

Num VkInternalAllocationType Source # 
Ord VkInternalAllocationType Source # 
Read VkInternalAllocationType Source # 
Show VkInternalAllocationType Source # 
Generic VkInternalAllocationType Source # 
Storable VkInternalAllocationType Source # 
type Rep VkInternalAllocationType Source # 
type Rep VkInternalAllocationType = D1 (MetaData "VkInternalAllocationType" "Graphics.Vulkan.Types.Enum.InternalAllocationType" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkInternalAllocationType" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

newtype VkSystemAllocationScope Source #

Instances

Bounded VkSystemAllocationScope Source # 
Enum VkSystemAllocationScope Source # 
Eq VkSystemAllocationScope Source # 
Data VkSystemAllocationScope Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkSystemAllocationScope -> c VkSystemAllocationScope #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkSystemAllocationScope #

toConstr :: VkSystemAllocationScope -> Constr #

dataTypeOf :: VkSystemAllocationScope -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkSystemAllocationScope) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkSystemAllocationScope) #

gmapT :: (forall b. Data b => b -> b) -> VkSystemAllocationScope -> VkSystemAllocationScope #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkSystemAllocationScope -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkSystemAllocationScope -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkSystemAllocationScope -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkSystemAllocationScope -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkSystemAllocationScope -> m VkSystemAllocationScope #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSystemAllocationScope -> m VkSystemAllocationScope #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSystemAllocationScope -> m VkSystemAllocationScope #

Num VkSystemAllocationScope Source # 
Ord VkSystemAllocationScope Source # 
Read VkSystemAllocationScope Source # 
Show VkSystemAllocationScope Source # 
Generic VkSystemAllocationScope Source # 
Storable VkSystemAllocationScope Source # 
type Rep VkSystemAllocationScope Source # 
type Rep VkSystemAllocationScope = D1 (MetaData "VkSystemAllocationScope" "Graphics.Vulkan.Types.Enum.SystemAllocationScope" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkSystemAllocationScope" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

type PFN_vkAllocationFunction = FunPtr HS_vkAllocationFunction Source #

typedef void* (VKAPI_PTR *PFN_vkAllocationFunction)(
    void*                                       pUserData,
    size_t                                      size,
    size_t                                      alignment,
    VkSystemAllocationScope                     allocationScope);

newVkAllocationFunction :: HS_vkAllocationFunction -> IO PFN_vkAllocationFunction Source #

Wrap haskell function into C-callable FunPtr. Note, you need to free resources after using it.

type PFN_vkDebugReportCallbackEXT = FunPtr HS_vkDebugReportCallbackEXT Source #

typedef VkBool32 (VKAPI_PTR *PFN_vkDebugReportCallbackEXT)(
    VkDebugReportFlagsEXT                       flags,
    VkDebugReportObjectTypeEXT                  objectType,
    uint64_t                                    object,
    size_t                                      location,
    int32_t                                     messageCode,
    const char*                                 pLayerPrefix,
    const char*                                 pMessage,
    void*                                       pUserData);

newVkDebugReportCallbackEXT :: HS_vkDebugReportCallbackEXT -> IO PFN_vkDebugReportCallbackEXT Source #

Wrap haskell function into C-callable FunPtr. Note, you need to free resources after using it.

type PFN_vkDebugUtilsMessengerCallbackEXT = FunPtr HS_vkDebugUtilsMessengerCallbackEXT Source #

typedef VkBool32 (VKAPI_PTR *PFN_vkDebugUtilsMessengerCallbackEXT)(
    VkDebugUtilsMessageSeverityFlagBitsEXT           messageSeverity,
    VkDebugUtilsMessageTypeFlagsEXT                  messageType,
    const VkDebugUtilsMessengerCallbackDataEXT*      pCallbackData,
    void*                                            pUserData);

newVkDebugUtilsMessengerCallbackEXT :: HS_vkDebugUtilsMessengerCallbackEXT -> IO PFN_vkDebugUtilsMessengerCallbackEXT Source #

Wrap haskell function into C-callable FunPtr. Note, you need to free resources after using it.

type PFN_vkFreeFunction = FunPtr HS_vkFreeFunction Source #

typedef void (VKAPI_PTR *PFN_vkFreeFunction)(
    void*                                       pUserData,
    void*                                       pMemory);

newVkFreeFunction :: HS_vkFreeFunction -> IO PFN_vkFreeFunction Source #

Wrap haskell function into C-callable FunPtr. Note, you need to free resources after using it.

type PFN_vkInternalAllocationNotification = FunPtr HS_vkInternalAllocationNotification Source #

typedef void (VKAPI_PTR *PFN_vkInternalAllocationNotification)(
    void*                                       pUserData,
    size_t                                      size,
    VkInternalAllocationType                    allocationType,
    VkSystemAllocationScope                     allocationScope);

newVkInternalAllocationNotification :: HS_vkInternalAllocationNotification -> IO PFN_vkInternalAllocationNotification Source #

Wrap haskell function into C-callable FunPtr. Note, you need to free resources after using it.

type PFN_vkInternalFreeNotification = FunPtr HS_vkInternalFreeNotification Source #

typedef void (VKAPI_PTR *PFN_vkInternalFreeNotification)(
    void*                                       pUserData,
    size_t                                      size,
    VkInternalAllocationType                    allocationType,
    VkSystemAllocationScope                     allocationScope);

newVkInternalFreeNotification :: HS_vkInternalFreeNotification -> IO PFN_vkInternalFreeNotification Source #

Wrap haskell function into C-callable FunPtr. Note, you need to free resources after using it.

type PFN_vkReallocationFunction = FunPtr HS_vkReallocationFunction Source #

typedef void* (VKAPI_PTR *PFN_vkReallocationFunction)(
    void*                                       pUserData,
    void*                                       pOriginal,
    size_t                                      size,
    size_t                                      alignment,
    VkSystemAllocationScope                     allocationScope);

newVkReallocationFunction :: HS_vkReallocationFunction -> IO PFN_vkReallocationFunction Source #

Wrap haskell function into C-callable FunPtr. Note, you need to free resources after using it.

type PFN_vkVoidFunction = FunPtr HS_vkVoidFunction Source #

typedef void (VKAPI_PTR *PFN_vkVoidFunction)(void);

newVkVoidFunction :: HS_vkVoidFunction -> IO PFN_vkVoidFunction Source #

Wrap haskell function into C-callable FunPtr. Note, you need to free resources after using it.

data VkAllocationCallbacks Source #

typedef struct VkAllocationCallbacks {
    void*           pUserData;
    PFN_vkAllocationFunction   pfnAllocation;
    PFN_vkReallocationFunction pfnReallocation;
    PFN_vkFreeFunction    pfnFree;
    PFN_vkInternalAllocationNotification pfnInternalAllocation;
    PFN_vkInternalFreeNotification pfnInternalFree;
} VkAllocationCallbacks;

VkAllocationCallbacks registry at www.khronos.org

Instances

Eq VkAllocationCallbacks Source # 
Ord VkAllocationCallbacks Source # 
Show VkAllocationCallbacks Source # 
Storable VkAllocationCallbacks Source # 
VulkanMarshalPrim VkAllocationCallbacks Source # 
VulkanMarshal VkAllocationCallbacks Source # 
CanWriteField "pUserData" VkAllocationCallbacks Source # 
CanWriteField "pfnAllocation" VkAllocationCallbacks Source # 
CanWriteField "pfnFree" VkAllocationCallbacks Source # 
CanWriteField "pfnInternalAllocation" VkAllocationCallbacks Source # 

Methods

writeField :: Ptr VkAllocationCallbacks -> FieldType "pfnInternalAllocation" VkAllocationCallbacks -> IO () Source #

CanWriteField "pfnInternalFree" VkAllocationCallbacks Source # 
CanWriteField "pfnReallocation" VkAllocationCallbacks Source # 
CanReadField "pUserData" VkAllocationCallbacks Source # 
CanReadField "pfnAllocation" VkAllocationCallbacks Source # 
CanReadField "pfnFree" VkAllocationCallbacks Source # 
CanReadField "pfnInternalAllocation" VkAllocationCallbacks Source # 
CanReadField "pfnInternalFree" VkAllocationCallbacks Source # 
CanReadField "pfnReallocation" VkAllocationCallbacks Source # 
HasField "pUserData" VkAllocationCallbacks Source # 
HasField "pfnAllocation" VkAllocationCallbacks Source # 

Associated Types

type FieldType ("pfnAllocation" :: Symbol) VkAllocationCallbacks :: Type Source #

type FieldOptional ("pfnAllocation" :: Symbol) VkAllocationCallbacks :: Bool Source #

type FieldOffset ("pfnAllocation" :: Symbol) VkAllocationCallbacks :: Nat Source #

type FieldIsArray ("pfnAllocation" :: Symbol) VkAllocationCallbacks :: Bool Source #

HasField "pfnFree" VkAllocationCallbacks Source # 
HasField "pfnInternalAllocation" VkAllocationCallbacks Source # 

Associated Types

type FieldType ("pfnInternalAllocation" :: Symbol) VkAllocationCallbacks :: Type Source #

type FieldOptional ("pfnInternalAllocation" :: Symbol) VkAllocationCallbacks :: Bool Source #

type FieldOffset ("pfnInternalAllocation" :: Symbol) VkAllocationCallbacks :: Nat Source #

type FieldIsArray ("pfnInternalAllocation" :: Symbol) VkAllocationCallbacks :: Bool Source #

HasField "pfnInternalFree" VkAllocationCallbacks Source # 

Associated Types

type FieldType ("pfnInternalFree" :: Symbol) VkAllocationCallbacks :: Type Source #

type FieldOptional ("pfnInternalFree" :: Symbol) VkAllocationCallbacks :: Bool Source #

type FieldOffset ("pfnInternalFree" :: Symbol) VkAllocationCallbacks :: Nat Source #

type FieldIsArray ("pfnInternalFree" :: Symbol) VkAllocationCallbacks :: Bool Source #

HasField "pfnReallocation" VkAllocationCallbacks Source # 

Associated Types

type FieldType ("pfnReallocation" :: Symbol) VkAllocationCallbacks :: Type Source #

type FieldOptional ("pfnReallocation" :: Symbol) VkAllocationCallbacks :: Bool Source #

type FieldOffset ("pfnReallocation" :: Symbol) VkAllocationCallbacks :: Nat Source #

type FieldIsArray ("pfnReallocation" :: Symbol) VkAllocationCallbacks :: Bool Source #

type StructFields VkAllocationCallbacks Source # 
type StructFields VkAllocationCallbacks = (:) Symbol "pUserData" ((:) Symbol "pfnAllocation" ((:) Symbol "pfnReallocation" ((:) Symbol "pfnFree" ((:) Symbol "pfnInternalAllocation" ((:) Symbol "pfnInternalFree" ([] Symbol))))))
type CUnionType VkAllocationCallbacks Source # 
type ReturnedOnly VkAllocationCallbacks Source # 
type StructExtends VkAllocationCallbacks Source # 
type FieldType "pUserData" VkAllocationCallbacks Source # 
type FieldType "pfnAllocation" VkAllocationCallbacks Source # 
type FieldType "pfnFree" VkAllocationCallbacks Source # 
type FieldType "pfnInternalAllocation" VkAllocationCallbacks Source # 
type FieldType "pfnInternalFree" VkAllocationCallbacks Source # 
type FieldType "pfnReallocation" VkAllocationCallbacks Source # 
type FieldOptional "pUserData" VkAllocationCallbacks Source # 
type FieldOptional "pfnAllocation" VkAllocationCallbacks Source # 
type FieldOptional "pfnFree" VkAllocationCallbacks Source # 
type FieldOptional "pfnInternalAllocation" VkAllocationCallbacks Source # 
type FieldOptional "pfnInternalAllocation" VkAllocationCallbacks = True
type FieldOptional "pfnInternalFree" VkAllocationCallbacks Source # 
type FieldOptional "pfnInternalFree" VkAllocationCallbacks = True
type FieldOptional "pfnReallocation" VkAllocationCallbacks Source # 
type FieldOptional "pfnReallocation" VkAllocationCallbacks = False
type FieldOffset "pUserData" VkAllocationCallbacks Source # 
type FieldOffset "pUserData" VkAllocationCallbacks = 0
type FieldOffset "pfnAllocation" VkAllocationCallbacks Source # 
type FieldOffset "pfnAllocation" VkAllocationCallbacks = 8
type FieldOffset "pfnFree" VkAllocationCallbacks Source # 
type FieldOffset "pfnInternalAllocation" VkAllocationCallbacks Source # 
type FieldOffset "pfnInternalAllocation" VkAllocationCallbacks = 32
type FieldOffset "pfnInternalFree" VkAllocationCallbacks Source # 
type FieldOffset "pfnInternalFree" VkAllocationCallbacks = 40
type FieldOffset "pfnReallocation" VkAllocationCallbacks Source # 
type FieldOffset "pfnReallocation" VkAllocationCallbacks = 16
type FieldIsArray "pUserData" VkAllocationCallbacks Source # 
type FieldIsArray "pfnAllocation" VkAllocationCallbacks Source # 
type FieldIsArray "pfnFree" VkAllocationCallbacks Source # 
type FieldIsArray "pfnInternalAllocation" VkAllocationCallbacks Source # 
type FieldIsArray "pfnInternalAllocation" VkAllocationCallbacks = False
type FieldIsArray "pfnInternalFree" VkAllocationCallbacks Source # 
type FieldIsArray "pfnInternalFree" VkAllocationCallbacks = False
type FieldIsArray "pfnReallocation" VkAllocationCallbacks Source # 
type FieldIsArray "pfnReallocation" VkAllocationCallbacks = False

pattern VK_FORMAT_FEATURE_MIDPOINT_CHROMA_SAMPLES_BIT :: VkFormatFeatureFlagBits Source #

Format can have midpoint rather than cosited chroma samples

bitpos = 17

pattern VK_FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_LINEAR_FILTER_BIT :: VkFormatFeatureFlagBits Source #

Format can be used with linear filtering whilst color conversion is enabled

bitpos = 18

pattern VK_FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_SEPARATE_RECONSTRUCTION_FILTER_BIT :: VkFormatFeatureFlagBits Source #

Format can have different chroma, min and mag filters

bitpos = 19

pattern VK_FORMAT_FEATURE_DISJOINT_BIT :: VkFormatFeatureFlagBits Source #

Format supports disjoint planes

bitpos = 22

pattern VK_FORMAT_FEATURE_COSITED_CHROMA_SAMPLES_BIT :: VkFormatFeatureFlagBits Source #

Format can have cosited rather than midpoint chroma samples

bitpos = 23

Promoted from VK_KHR_descriptor_update_template

newtype VkDescriptorBindingBitmaskEXT a Source #

Instances

Bounded (VkDescriptorBindingBitmaskEXT FlagMask) Source # 
Enum (VkDescriptorBindingBitmaskEXT FlagMask) Source # 
Eq (VkDescriptorBindingBitmaskEXT a) Source # 
Integral (VkDescriptorBindingBitmaskEXT FlagMask) Source # 
Typeable FlagType a => Data (VkDescriptorBindingBitmaskEXT a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkDescriptorBindingBitmaskEXT a -> c (VkDescriptorBindingBitmaskEXT a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkDescriptorBindingBitmaskEXT a) #

toConstr :: VkDescriptorBindingBitmaskEXT a -> Constr #

dataTypeOf :: VkDescriptorBindingBitmaskEXT a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkDescriptorBindingBitmaskEXT a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkDescriptorBindingBitmaskEXT a)) #

gmapT :: (forall b. Data b => b -> b) -> VkDescriptorBindingBitmaskEXT a -> VkDescriptorBindingBitmaskEXT a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkDescriptorBindingBitmaskEXT a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkDescriptorBindingBitmaskEXT a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkDescriptorBindingBitmaskEXT a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkDescriptorBindingBitmaskEXT a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkDescriptorBindingBitmaskEXT a -> m (VkDescriptorBindingBitmaskEXT a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkDescriptorBindingBitmaskEXT a -> m (VkDescriptorBindingBitmaskEXT a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkDescriptorBindingBitmaskEXT a -> m (VkDescriptorBindingBitmaskEXT a) #

Num (VkDescriptorBindingBitmaskEXT FlagMask) Source # 
Ord (VkDescriptorBindingBitmaskEXT a) Source # 
Read (VkDescriptorBindingBitmaskEXT a) Source # 
Real (VkDescriptorBindingBitmaskEXT FlagMask) Source # 
Show (VkDescriptorBindingBitmaskEXT a) Source # 
Generic (VkDescriptorBindingBitmaskEXT a) Source # 
Storable (VkDescriptorBindingBitmaskEXT a) Source # 
Bits (VkDescriptorBindingBitmaskEXT FlagMask) Source # 

Methods

(.&.) :: VkDescriptorBindingBitmaskEXT FlagMask -> VkDescriptorBindingBitmaskEXT FlagMask -> VkDescriptorBindingBitmaskEXT FlagMask #

(.|.) :: VkDescriptorBindingBitmaskEXT FlagMask -> VkDescriptorBindingBitmaskEXT FlagMask -> VkDescriptorBindingBitmaskEXT FlagMask #

xor :: VkDescriptorBindingBitmaskEXT FlagMask -> VkDescriptorBindingBitmaskEXT FlagMask -> VkDescriptorBindingBitmaskEXT FlagMask #

complement :: VkDescriptorBindingBitmaskEXT FlagMask -> VkDescriptorBindingBitmaskEXT FlagMask #

shift :: VkDescriptorBindingBitmaskEXT FlagMask -> Int -> VkDescriptorBindingBitmaskEXT FlagMask #

rotate :: VkDescriptorBindingBitmaskEXT FlagMask -> Int -> VkDescriptorBindingBitmaskEXT FlagMask #

zeroBits :: VkDescriptorBindingBitmaskEXT FlagMask #

bit :: Int -> VkDescriptorBindingBitmaskEXT FlagMask #

setBit :: VkDescriptorBindingBitmaskEXT FlagMask -> Int -> VkDescriptorBindingBitmaskEXT FlagMask #

clearBit :: VkDescriptorBindingBitmaskEXT FlagMask -> Int -> VkDescriptorBindingBitmaskEXT FlagMask #

complementBit :: VkDescriptorBindingBitmaskEXT FlagMask -> Int -> VkDescriptorBindingBitmaskEXT FlagMask #

testBit :: VkDescriptorBindingBitmaskEXT FlagMask -> Int -> Bool #

bitSizeMaybe :: VkDescriptorBindingBitmaskEXT FlagMask -> Maybe Int #

bitSize :: VkDescriptorBindingBitmaskEXT FlagMask -> Int #

isSigned :: VkDescriptorBindingBitmaskEXT FlagMask -> Bool #

shiftL :: VkDescriptorBindingBitmaskEXT FlagMask -> Int -> VkDescriptorBindingBitmaskEXT FlagMask #

unsafeShiftL :: VkDescriptorBindingBitmaskEXT FlagMask -> Int -> VkDescriptorBindingBitmaskEXT FlagMask #

shiftR :: VkDescriptorBindingBitmaskEXT FlagMask -> Int -> VkDescriptorBindingBitmaskEXT FlagMask #

unsafeShiftR :: VkDescriptorBindingBitmaskEXT FlagMask -> Int -> VkDescriptorBindingBitmaskEXT FlagMask #

rotateL :: VkDescriptorBindingBitmaskEXT FlagMask -> Int -> VkDescriptorBindingBitmaskEXT FlagMask #

rotateR :: VkDescriptorBindingBitmaskEXT FlagMask -> Int -> VkDescriptorBindingBitmaskEXT FlagMask #

popCount :: VkDescriptorBindingBitmaskEXT FlagMask -> Int #

FiniteBits (VkDescriptorBindingBitmaskEXT FlagMask) Source # 
type Rep (VkDescriptorBindingBitmaskEXT a) Source # 
type Rep (VkDescriptorBindingBitmaskEXT a) = D1 (MetaData "VkDescriptorBindingBitmaskEXT" "Graphics.Vulkan.Types.Enum.Descriptor" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkDescriptorBindingBitmaskEXT" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkDescriptorPoolCreateBitmask a Source #

Instances

Bounded (VkDescriptorPoolCreateBitmask FlagMask) Source # 
Enum (VkDescriptorPoolCreateBitmask FlagMask) Source # 
Eq (VkDescriptorPoolCreateBitmask a) Source # 
Integral (VkDescriptorPoolCreateBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkDescriptorPoolCreateBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkDescriptorPoolCreateBitmask a -> c (VkDescriptorPoolCreateBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkDescriptorPoolCreateBitmask a) #

toConstr :: VkDescriptorPoolCreateBitmask a -> Constr #

dataTypeOf :: VkDescriptorPoolCreateBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkDescriptorPoolCreateBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkDescriptorPoolCreateBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkDescriptorPoolCreateBitmask a -> VkDescriptorPoolCreateBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkDescriptorPoolCreateBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkDescriptorPoolCreateBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkDescriptorPoolCreateBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkDescriptorPoolCreateBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkDescriptorPoolCreateBitmask a -> m (VkDescriptorPoolCreateBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkDescriptorPoolCreateBitmask a -> m (VkDescriptorPoolCreateBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkDescriptorPoolCreateBitmask a -> m (VkDescriptorPoolCreateBitmask a) #

Num (VkDescriptorPoolCreateBitmask FlagMask) Source # 
Ord (VkDescriptorPoolCreateBitmask a) Source # 
Read (VkDescriptorPoolCreateBitmask a) Source # 
Real (VkDescriptorPoolCreateBitmask FlagMask) Source # 
Show (VkDescriptorPoolCreateBitmask a) Source # 
Generic (VkDescriptorPoolCreateBitmask a) Source # 
Storable (VkDescriptorPoolCreateBitmask a) Source # 
Bits (VkDescriptorPoolCreateBitmask FlagMask) Source # 

Methods

(.&.) :: VkDescriptorPoolCreateBitmask FlagMask -> VkDescriptorPoolCreateBitmask FlagMask -> VkDescriptorPoolCreateBitmask FlagMask #

(.|.) :: VkDescriptorPoolCreateBitmask FlagMask -> VkDescriptorPoolCreateBitmask FlagMask -> VkDescriptorPoolCreateBitmask FlagMask #

xor :: VkDescriptorPoolCreateBitmask FlagMask -> VkDescriptorPoolCreateBitmask FlagMask -> VkDescriptorPoolCreateBitmask FlagMask #

complement :: VkDescriptorPoolCreateBitmask FlagMask -> VkDescriptorPoolCreateBitmask FlagMask #

shift :: VkDescriptorPoolCreateBitmask FlagMask -> Int -> VkDescriptorPoolCreateBitmask FlagMask #

rotate :: VkDescriptorPoolCreateBitmask FlagMask -> Int -> VkDescriptorPoolCreateBitmask FlagMask #

zeroBits :: VkDescriptorPoolCreateBitmask FlagMask #

bit :: Int -> VkDescriptorPoolCreateBitmask FlagMask #

setBit :: VkDescriptorPoolCreateBitmask FlagMask -> Int -> VkDescriptorPoolCreateBitmask FlagMask #

clearBit :: VkDescriptorPoolCreateBitmask FlagMask -> Int -> VkDescriptorPoolCreateBitmask FlagMask #

complementBit :: VkDescriptorPoolCreateBitmask FlagMask -> Int -> VkDescriptorPoolCreateBitmask FlagMask #

testBit :: VkDescriptorPoolCreateBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkDescriptorPoolCreateBitmask FlagMask -> Maybe Int #

bitSize :: VkDescriptorPoolCreateBitmask FlagMask -> Int #

isSigned :: VkDescriptorPoolCreateBitmask FlagMask -> Bool #

shiftL :: VkDescriptorPoolCreateBitmask FlagMask -> Int -> VkDescriptorPoolCreateBitmask FlagMask #

unsafeShiftL :: VkDescriptorPoolCreateBitmask FlagMask -> Int -> VkDescriptorPoolCreateBitmask FlagMask #

shiftR :: VkDescriptorPoolCreateBitmask FlagMask -> Int -> VkDescriptorPoolCreateBitmask FlagMask #

unsafeShiftR :: VkDescriptorPoolCreateBitmask FlagMask -> Int -> VkDescriptorPoolCreateBitmask FlagMask #

rotateL :: VkDescriptorPoolCreateBitmask FlagMask -> Int -> VkDescriptorPoolCreateBitmask FlagMask #

rotateR :: VkDescriptorPoolCreateBitmask FlagMask -> Int -> VkDescriptorPoolCreateBitmask FlagMask #

popCount :: VkDescriptorPoolCreateBitmask FlagMask -> Int #

FiniteBits (VkDescriptorPoolCreateBitmask FlagMask) Source # 
type Rep (VkDescriptorPoolCreateBitmask a) Source # 
type Rep (VkDescriptorPoolCreateBitmask a) = D1 (MetaData "VkDescriptorPoolCreateBitmask" "Graphics.Vulkan.Types.Enum.Descriptor" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkDescriptorPoolCreateBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

pattern VK_DESCRIPTOR_POOL_CREATE_FREE_DESCRIPTOR_SET_BIT :: forall a. VkDescriptorPoolCreateBitmask a Source #

Descriptor sets may be freed individually

bitpos = 0

newtype VkDescriptorSetLayoutCreateBitmask a Source #

Instances

Bounded (VkDescriptorSetLayoutCreateBitmask FlagMask) Source # 
Enum (VkDescriptorSetLayoutCreateBitmask FlagMask) Source # 
Eq (VkDescriptorSetLayoutCreateBitmask a) Source # 
Integral (VkDescriptorSetLayoutCreateBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkDescriptorSetLayoutCreateBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkDescriptorSetLayoutCreateBitmask a -> c (VkDescriptorSetLayoutCreateBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkDescriptorSetLayoutCreateBitmask a) #

toConstr :: VkDescriptorSetLayoutCreateBitmask a -> Constr #

dataTypeOf :: VkDescriptorSetLayoutCreateBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkDescriptorSetLayoutCreateBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkDescriptorSetLayoutCreateBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkDescriptorSetLayoutCreateBitmask a -> VkDescriptorSetLayoutCreateBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkDescriptorSetLayoutCreateBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkDescriptorSetLayoutCreateBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkDescriptorSetLayoutCreateBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkDescriptorSetLayoutCreateBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkDescriptorSetLayoutCreateBitmask a -> m (VkDescriptorSetLayoutCreateBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkDescriptorSetLayoutCreateBitmask a -> m (VkDescriptorSetLayoutCreateBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkDescriptorSetLayoutCreateBitmask a -> m (VkDescriptorSetLayoutCreateBitmask a) #

Num (VkDescriptorSetLayoutCreateBitmask FlagMask) Source # 
Ord (VkDescriptorSetLayoutCreateBitmask a) Source # 
Read (VkDescriptorSetLayoutCreateBitmask a) Source # 
Real (VkDescriptorSetLayoutCreateBitmask FlagMask) Source # 
Show (VkDescriptorSetLayoutCreateBitmask a) Source # 
Generic (VkDescriptorSetLayoutCreateBitmask a) Source # 
Storable (VkDescriptorSetLayoutCreateBitmask a) Source # 
Bits (VkDescriptorSetLayoutCreateBitmask FlagMask) Source # 

Methods

(.&.) :: VkDescriptorSetLayoutCreateBitmask FlagMask -> VkDescriptorSetLayoutCreateBitmask FlagMask -> VkDescriptorSetLayoutCreateBitmask FlagMask #

(.|.) :: VkDescriptorSetLayoutCreateBitmask FlagMask -> VkDescriptorSetLayoutCreateBitmask FlagMask -> VkDescriptorSetLayoutCreateBitmask FlagMask #

xor :: VkDescriptorSetLayoutCreateBitmask FlagMask -> VkDescriptorSetLayoutCreateBitmask FlagMask -> VkDescriptorSetLayoutCreateBitmask FlagMask #

complement :: VkDescriptorSetLayoutCreateBitmask FlagMask -> VkDescriptorSetLayoutCreateBitmask FlagMask #

shift :: VkDescriptorSetLayoutCreateBitmask FlagMask -> Int -> VkDescriptorSetLayoutCreateBitmask FlagMask #

rotate :: VkDescriptorSetLayoutCreateBitmask FlagMask -> Int -> VkDescriptorSetLayoutCreateBitmask FlagMask #

zeroBits :: VkDescriptorSetLayoutCreateBitmask FlagMask #

bit :: Int -> VkDescriptorSetLayoutCreateBitmask FlagMask #

setBit :: VkDescriptorSetLayoutCreateBitmask FlagMask -> Int -> VkDescriptorSetLayoutCreateBitmask FlagMask #

clearBit :: VkDescriptorSetLayoutCreateBitmask FlagMask -> Int -> VkDescriptorSetLayoutCreateBitmask FlagMask #

complementBit :: VkDescriptorSetLayoutCreateBitmask FlagMask -> Int -> VkDescriptorSetLayoutCreateBitmask FlagMask #

testBit :: VkDescriptorSetLayoutCreateBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkDescriptorSetLayoutCreateBitmask FlagMask -> Maybe Int #

bitSize :: VkDescriptorSetLayoutCreateBitmask FlagMask -> Int #

isSigned :: VkDescriptorSetLayoutCreateBitmask FlagMask -> Bool #

shiftL :: VkDescriptorSetLayoutCreateBitmask FlagMask -> Int -> VkDescriptorSetLayoutCreateBitmask FlagMask #

unsafeShiftL :: VkDescriptorSetLayoutCreateBitmask FlagMask -> Int -> VkDescriptorSetLayoutCreateBitmask FlagMask #

shiftR :: VkDescriptorSetLayoutCreateBitmask FlagMask -> Int -> VkDescriptorSetLayoutCreateBitmask FlagMask #

unsafeShiftR :: VkDescriptorSetLayoutCreateBitmask FlagMask -> Int -> VkDescriptorSetLayoutCreateBitmask FlagMask #

rotateL :: VkDescriptorSetLayoutCreateBitmask FlagMask -> Int -> VkDescriptorSetLayoutCreateBitmask FlagMask #

rotateR :: VkDescriptorSetLayoutCreateBitmask FlagMask -> Int -> VkDescriptorSetLayoutCreateBitmask FlagMask #

popCount :: VkDescriptorSetLayoutCreateBitmask FlagMask -> Int #

FiniteBits (VkDescriptorSetLayoutCreateBitmask FlagMask) Source # 
type Rep (VkDescriptorSetLayoutCreateBitmask a) Source # 
type Rep (VkDescriptorSetLayoutCreateBitmask a) = D1 (MetaData "VkDescriptorSetLayoutCreateBitmask" "Graphics.Vulkan.Types.Enum.Descriptor" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkDescriptorSetLayoutCreateBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkDescriptorType Source #

Constructors

VkDescriptorType Int32 

Instances

Bounded VkDescriptorType Source # 
Enum VkDescriptorType Source # 
Eq VkDescriptorType Source # 
Data VkDescriptorType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkDescriptorType -> c VkDescriptorType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkDescriptorType #

toConstr :: VkDescriptorType -> Constr #

dataTypeOf :: VkDescriptorType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkDescriptorType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkDescriptorType) #

gmapT :: (forall b. Data b => b -> b) -> VkDescriptorType -> VkDescriptorType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkDescriptorType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkDescriptorType -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkDescriptorType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkDescriptorType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkDescriptorType -> m VkDescriptorType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkDescriptorType -> m VkDescriptorType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkDescriptorType -> m VkDescriptorType #

Num VkDescriptorType Source # 
Ord VkDescriptorType Source # 
Read VkDescriptorType Source # 
Show VkDescriptorType Source # 
Generic VkDescriptorType Source # 
Storable VkDescriptorType Source # 
type Rep VkDescriptorType Source # 
type Rep VkDescriptorType = D1 (MetaData "VkDescriptorType" "Graphics.Vulkan.Types.Enum.Descriptor" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkDescriptorType" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

newtype VkDescriptorUpdateTemplateType Source #

Instances

Bounded VkDescriptorUpdateTemplateType Source # 
Enum VkDescriptorUpdateTemplateType Source # 
Eq VkDescriptorUpdateTemplateType Source # 
Data VkDescriptorUpdateTemplateType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkDescriptorUpdateTemplateType -> c VkDescriptorUpdateTemplateType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkDescriptorUpdateTemplateType #

toConstr :: VkDescriptorUpdateTemplateType -> Constr #

dataTypeOf :: VkDescriptorUpdateTemplateType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkDescriptorUpdateTemplateType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkDescriptorUpdateTemplateType) #

gmapT :: (forall b. Data b => b -> b) -> VkDescriptorUpdateTemplateType -> VkDescriptorUpdateTemplateType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkDescriptorUpdateTemplateType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkDescriptorUpdateTemplateType -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkDescriptorUpdateTemplateType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkDescriptorUpdateTemplateType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkDescriptorUpdateTemplateType -> m VkDescriptorUpdateTemplateType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkDescriptorUpdateTemplateType -> m VkDescriptorUpdateTemplateType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkDescriptorUpdateTemplateType -> m VkDescriptorUpdateTemplateType #

Num VkDescriptorUpdateTemplateType Source # 
Ord VkDescriptorUpdateTemplateType Source # 
Read VkDescriptorUpdateTemplateType Source # 
Show VkDescriptorUpdateTemplateType Source # 
Generic VkDescriptorUpdateTemplateType Source # 
Storable VkDescriptorUpdateTemplateType Source # 
type Rep VkDescriptorUpdateTemplateType Source # 
type Rep VkDescriptorUpdateTemplateType = D1 (MetaData "VkDescriptorUpdateTemplateType" "Graphics.Vulkan.Types.Enum.Descriptor" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkDescriptorUpdateTemplateType" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

pattern VK_DESCRIPTOR_UPDATE_TEMPLATE_TYPE_DESCRIPTOR_SET :: VkDescriptorUpdateTemplateType Source #

Create descriptor update template for descriptor set updates

newtype VkDescriptorUpdateTemplateTypeKHR Source #

Instances

Bounded VkDescriptorUpdateTemplateTypeKHR Source # 
Enum VkDescriptorUpdateTemplateTypeKHR Source # 
Eq VkDescriptorUpdateTemplateTypeKHR Source # 
Integral VkDescriptorUpdateTemplateTypeKHR Source # 
Data VkDescriptorUpdateTemplateTypeKHR Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkDescriptorUpdateTemplateTypeKHR -> c VkDescriptorUpdateTemplateTypeKHR #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkDescriptorUpdateTemplateTypeKHR #

toConstr :: VkDescriptorUpdateTemplateTypeKHR -> Constr #

dataTypeOf :: VkDescriptorUpdateTemplateTypeKHR -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkDescriptorUpdateTemplateTypeKHR) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkDescriptorUpdateTemplateTypeKHR) #

gmapT :: (forall b. Data b => b -> b) -> VkDescriptorUpdateTemplateTypeKHR -> VkDescriptorUpdateTemplateTypeKHR #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkDescriptorUpdateTemplateTypeKHR -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkDescriptorUpdateTemplateTypeKHR -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkDescriptorUpdateTemplateTypeKHR -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkDescriptorUpdateTemplateTypeKHR -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkDescriptorUpdateTemplateTypeKHR -> m VkDescriptorUpdateTemplateTypeKHR #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkDescriptorUpdateTemplateTypeKHR -> m VkDescriptorUpdateTemplateTypeKHR #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkDescriptorUpdateTemplateTypeKHR -> m VkDescriptorUpdateTemplateTypeKHR #

Num VkDescriptorUpdateTemplateTypeKHR Source # 
Ord VkDescriptorUpdateTemplateTypeKHR Source # 
Read VkDescriptorUpdateTemplateTypeKHR Source # 
Real VkDescriptorUpdateTemplateTypeKHR Source # 
Show VkDescriptorUpdateTemplateTypeKHR Source # 
Generic VkDescriptorUpdateTemplateTypeKHR Source # 
Storable VkDescriptorUpdateTemplateTypeKHR Source # 
Bits VkDescriptorUpdateTemplateTypeKHR Source # 

Methods

(.&.) :: VkDescriptorUpdateTemplateTypeKHR -> VkDescriptorUpdateTemplateTypeKHR -> VkDescriptorUpdateTemplateTypeKHR #

(.|.) :: VkDescriptorUpdateTemplateTypeKHR -> VkDescriptorUpdateTemplateTypeKHR -> VkDescriptorUpdateTemplateTypeKHR #

xor :: VkDescriptorUpdateTemplateTypeKHR -> VkDescriptorUpdateTemplateTypeKHR -> VkDescriptorUpdateTemplateTypeKHR #

complement :: VkDescriptorUpdateTemplateTypeKHR -> VkDescriptorUpdateTemplateTypeKHR #

shift :: VkDescriptorUpdateTemplateTypeKHR -> Int -> VkDescriptorUpdateTemplateTypeKHR #

rotate :: VkDescriptorUpdateTemplateTypeKHR -> Int -> VkDescriptorUpdateTemplateTypeKHR #

zeroBits :: VkDescriptorUpdateTemplateTypeKHR #

bit :: Int -> VkDescriptorUpdateTemplateTypeKHR #

setBit :: VkDescriptorUpdateTemplateTypeKHR -> Int -> VkDescriptorUpdateTemplateTypeKHR #

clearBit :: VkDescriptorUpdateTemplateTypeKHR -> Int -> VkDescriptorUpdateTemplateTypeKHR #

complementBit :: VkDescriptorUpdateTemplateTypeKHR -> Int -> VkDescriptorUpdateTemplateTypeKHR #

testBit :: VkDescriptorUpdateTemplateTypeKHR -> Int -> Bool #

bitSizeMaybe :: VkDescriptorUpdateTemplateTypeKHR -> Maybe Int #

bitSize :: VkDescriptorUpdateTemplateTypeKHR -> Int #

isSigned :: VkDescriptorUpdateTemplateTypeKHR -> Bool #

shiftL :: VkDescriptorUpdateTemplateTypeKHR -> Int -> VkDescriptorUpdateTemplateTypeKHR #

unsafeShiftL :: VkDescriptorUpdateTemplateTypeKHR -> Int -> VkDescriptorUpdateTemplateTypeKHR #

shiftR :: VkDescriptorUpdateTemplateTypeKHR -> Int -> VkDescriptorUpdateTemplateTypeKHR #

unsafeShiftR :: VkDescriptorUpdateTemplateTypeKHR -> Int -> VkDescriptorUpdateTemplateTypeKHR #

rotateL :: VkDescriptorUpdateTemplateTypeKHR -> Int -> VkDescriptorUpdateTemplateTypeKHR #

rotateR :: VkDescriptorUpdateTemplateTypeKHR -> Int -> VkDescriptorUpdateTemplateTypeKHR #

popCount :: VkDescriptorUpdateTemplateTypeKHR -> Int #

FiniteBits VkDescriptorUpdateTemplateTypeKHR Source # 
type Rep VkDescriptorUpdateTemplateTypeKHR Source # 
type Rep VkDescriptorUpdateTemplateTypeKHR = D1 (MetaData "VkDescriptorUpdateTemplateTypeKHR" "Graphics.Vulkan.Types.Enum.Descriptor" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkDescriptorUpdateTemplateTypeKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

data VkDescriptorBufferInfo Source #

typedef struct VkDescriptorBufferInfo {
    VkBuffer               buffer;
    VkDeviceSize           offset;
    VkDeviceSize           range;
} VkDescriptorBufferInfo;

VkDescriptorBufferInfo registry at www.khronos.org

Instances

Eq VkDescriptorBufferInfo Source # 
Ord VkDescriptorBufferInfo Source # 
Show VkDescriptorBufferInfo Source # 
Storable VkDescriptorBufferInfo Source # 
VulkanMarshalPrim VkDescriptorBufferInfo Source # 
VulkanMarshal VkDescriptorBufferInfo Source # 
CanWriteField "buffer" VkDescriptorBufferInfo Source # 
CanWriteField "offset" VkDescriptorBufferInfo Source # 
CanWriteField "range" VkDescriptorBufferInfo Source # 
CanReadField "buffer" VkDescriptorBufferInfo Source # 
CanReadField "offset" VkDescriptorBufferInfo Source # 
CanReadField "range" VkDescriptorBufferInfo Source # 
HasField "buffer" VkDescriptorBufferInfo Source # 
HasField "offset" VkDescriptorBufferInfo Source # 
HasField "range" VkDescriptorBufferInfo Source # 
type StructFields VkDescriptorBufferInfo Source # 
type StructFields VkDescriptorBufferInfo = (:) Symbol "buffer" ((:) Symbol "offset" ((:) Symbol "range" ([] Symbol)))
type CUnionType VkDescriptorBufferInfo Source # 
type ReturnedOnly VkDescriptorBufferInfo Source # 
type StructExtends VkDescriptorBufferInfo Source # 
type FieldType "buffer" VkDescriptorBufferInfo Source # 
type FieldType "offset" VkDescriptorBufferInfo Source # 
type FieldType "range" VkDescriptorBufferInfo Source # 
type FieldOptional "buffer" VkDescriptorBufferInfo Source # 
type FieldOptional "offset" VkDescriptorBufferInfo Source # 
type FieldOptional "range" VkDescriptorBufferInfo Source # 
type FieldOffset "buffer" VkDescriptorBufferInfo Source # 
type FieldOffset "offset" VkDescriptorBufferInfo Source # 
type FieldOffset "range" VkDescriptorBufferInfo Source # 
type FieldIsArray "buffer" VkDescriptorBufferInfo Source # 
type FieldIsArray "offset" VkDescriptorBufferInfo Source # 
type FieldIsArray "range" VkDescriptorBufferInfo Source # 

data VkDescriptorImageInfo Source #

typedef struct VkDescriptorImageInfo {
    VkSampler       sampler;
    VkImageView     imageView;
    VkImageLayout   imageLayout;
} VkDescriptorImageInfo;

VkDescriptorImageInfo registry at www.khronos.org

Instances

Eq VkDescriptorImageInfo Source # 
Ord VkDescriptorImageInfo Source # 
Show VkDescriptorImageInfo Source # 
Storable VkDescriptorImageInfo Source # 
VulkanMarshalPrim VkDescriptorImageInfo Source # 
VulkanMarshal VkDescriptorImageInfo Source # 
CanWriteField "imageLayout" VkDescriptorImageInfo Source # 
CanWriteField "imageView" VkDescriptorImageInfo Source # 
CanWriteField "sampler" VkDescriptorImageInfo Source # 
CanReadField "imageLayout" VkDescriptorImageInfo Source # 
CanReadField "imageView" VkDescriptorImageInfo Source # 
CanReadField "sampler" VkDescriptorImageInfo Source # 
HasField "imageLayout" VkDescriptorImageInfo Source # 

Associated Types

type FieldType ("imageLayout" :: Symbol) VkDescriptorImageInfo :: Type Source #

type FieldOptional ("imageLayout" :: Symbol) VkDescriptorImageInfo :: Bool Source #

type FieldOffset ("imageLayout" :: Symbol) VkDescriptorImageInfo :: Nat Source #

type FieldIsArray ("imageLayout" :: Symbol) VkDescriptorImageInfo :: Bool Source #

HasField "imageView" VkDescriptorImageInfo Source # 
HasField "sampler" VkDescriptorImageInfo Source # 
type StructFields VkDescriptorImageInfo Source # 
type StructFields VkDescriptorImageInfo = (:) Symbol "sampler" ((:) Symbol "imageView" ((:) Symbol "imageLayout" ([] Symbol)))
type CUnionType VkDescriptorImageInfo Source # 
type ReturnedOnly VkDescriptorImageInfo Source # 
type StructExtends VkDescriptorImageInfo Source # 
type FieldType "imageLayout" VkDescriptorImageInfo Source # 
type FieldType "imageView" VkDescriptorImageInfo Source # 
type FieldType "sampler" VkDescriptorImageInfo Source # 
type FieldOptional "imageLayout" VkDescriptorImageInfo Source # 
type FieldOptional "imageView" VkDescriptorImageInfo Source # 
type FieldOptional "sampler" VkDescriptorImageInfo Source # 
type FieldOffset "imageLayout" VkDescriptorImageInfo Source # 
type FieldOffset "imageLayout" VkDescriptorImageInfo = 16
type FieldOffset "imageView" VkDescriptorImageInfo Source # 
type FieldOffset "imageView" VkDescriptorImageInfo = 8
type FieldOffset "sampler" VkDescriptorImageInfo Source # 
type FieldIsArray "imageLayout" VkDescriptorImageInfo Source # 
type FieldIsArray "imageView" VkDescriptorImageInfo Source # 
type FieldIsArray "sampler" VkDescriptorImageInfo Source # 

data VkDescriptorPoolCreateInfo Source #

typedef struct VkDescriptorPoolCreateInfo {
    VkStructureType sType;
    const void*            pNext;
    VkDescriptorPoolCreateFlags  flags;
    uint32_t               maxSets;
    uint32_t               poolSizeCount;
    const VkDescriptorPoolSize* pPoolSizes;
} VkDescriptorPoolCreateInfo;

VkDescriptorPoolCreateInfo registry at www.khronos.org

Instances

Eq VkDescriptorPoolCreateInfo Source # 
Ord VkDescriptorPoolCreateInfo Source # 
Show VkDescriptorPoolCreateInfo Source # 
Storable VkDescriptorPoolCreateInfo Source # 
VulkanMarshalPrim VkDescriptorPoolCreateInfo Source # 
VulkanMarshal VkDescriptorPoolCreateInfo Source # 
CanWriteField "flags" VkDescriptorPoolCreateInfo Source # 
CanWriteField "maxSets" VkDescriptorPoolCreateInfo Source # 
CanWriteField "pNext" VkDescriptorPoolCreateInfo Source # 
CanWriteField "pPoolSizes" VkDescriptorPoolCreateInfo Source # 
CanWriteField "poolSizeCount" VkDescriptorPoolCreateInfo Source # 
CanWriteField "sType" VkDescriptorPoolCreateInfo Source # 
CanReadField "flags" VkDescriptorPoolCreateInfo Source # 
CanReadField "maxSets" VkDescriptorPoolCreateInfo Source # 
CanReadField "pNext" VkDescriptorPoolCreateInfo Source # 
CanReadField "pPoolSizes" VkDescriptorPoolCreateInfo Source # 
CanReadField "poolSizeCount" VkDescriptorPoolCreateInfo Source # 
CanReadField "sType" VkDescriptorPoolCreateInfo Source # 
HasField "flags" VkDescriptorPoolCreateInfo Source # 
HasField "maxSets" VkDescriptorPoolCreateInfo Source # 
HasField "pNext" VkDescriptorPoolCreateInfo Source # 
HasField "pPoolSizes" VkDescriptorPoolCreateInfo Source # 
HasField "poolSizeCount" VkDescriptorPoolCreateInfo Source # 
HasField "sType" VkDescriptorPoolCreateInfo Source # 
type StructFields VkDescriptorPoolCreateInfo Source # 
type StructFields VkDescriptorPoolCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "maxSets" ((:) Symbol "poolSizeCount" ((:) Symbol "pPoolSizes" ([] Symbol))))))
type CUnionType VkDescriptorPoolCreateInfo Source # 
type ReturnedOnly VkDescriptorPoolCreateInfo Source # 
type StructExtends VkDescriptorPoolCreateInfo Source # 
type FieldType "flags" VkDescriptorPoolCreateInfo Source # 
type FieldType "maxSets" VkDescriptorPoolCreateInfo Source # 
type FieldType "pNext" VkDescriptorPoolCreateInfo Source # 
type FieldType "pPoolSizes" VkDescriptorPoolCreateInfo Source # 
type FieldType "poolSizeCount" VkDescriptorPoolCreateInfo Source # 
type FieldType "sType" VkDescriptorPoolCreateInfo Source # 
type FieldOptional "flags" VkDescriptorPoolCreateInfo Source # 
type FieldOptional "maxSets" VkDescriptorPoolCreateInfo Source # 
type FieldOptional "pNext" VkDescriptorPoolCreateInfo Source # 
type FieldOptional "pPoolSizes" VkDescriptorPoolCreateInfo Source # 
type FieldOptional "poolSizeCount" VkDescriptorPoolCreateInfo Source # 
type FieldOptional "sType" VkDescriptorPoolCreateInfo Source # 
type FieldOffset "flags" VkDescriptorPoolCreateInfo Source # 
type FieldOffset "maxSets" VkDescriptorPoolCreateInfo Source # 
type FieldOffset "pNext" VkDescriptorPoolCreateInfo Source # 
type FieldOffset "pPoolSizes" VkDescriptorPoolCreateInfo Source # 
type FieldOffset "poolSizeCount" VkDescriptorPoolCreateInfo Source # 
type FieldOffset "poolSizeCount" VkDescriptorPoolCreateInfo = 24
type FieldOffset "sType" VkDescriptorPoolCreateInfo Source # 
type FieldIsArray "flags" VkDescriptorPoolCreateInfo Source # 
type FieldIsArray "maxSets" VkDescriptorPoolCreateInfo Source # 
type FieldIsArray "pNext" VkDescriptorPoolCreateInfo Source # 
type FieldIsArray "pPoolSizes" VkDescriptorPoolCreateInfo Source # 
type FieldIsArray "poolSizeCount" VkDescriptorPoolCreateInfo Source # 
type FieldIsArray "sType" VkDescriptorPoolCreateInfo Source # 

data VkDescriptorPoolSize Source #

typedef struct VkDescriptorPoolSize {
    VkDescriptorType       type;
    uint32_t               descriptorCount;
} VkDescriptorPoolSize;

VkDescriptorPoolSize registry at www.khronos.org

Instances

Eq VkDescriptorPoolSize Source # 
Ord VkDescriptorPoolSize Source # 
Show VkDescriptorPoolSize Source # 
Storable VkDescriptorPoolSize Source # 
VulkanMarshalPrim VkDescriptorPoolSize Source # 
VulkanMarshal VkDescriptorPoolSize Source # 
CanWriteField "descriptorCount" VkDescriptorPoolSize Source # 
CanWriteField "type" VkDescriptorPoolSize Source # 
CanReadField "descriptorCount" VkDescriptorPoolSize Source # 
CanReadField "type" VkDescriptorPoolSize Source # 
HasField "descriptorCount" VkDescriptorPoolSize Source # 

Associated Types

type FieldType ("descriptorCount" :: Symbol) VkDescriptorPoolSize :: Type Source #

type FieldOptional ("descriptorCount" :: Symbol) VkDescriptorPoolSize :: Bool Source #

type FieldOffset ("descriptorCount" :: Symbol) VkDescriptorPoolSize :: Nat Source #

type FieldIsArray ("descriptorCount" :: Symbol) VkDescriptorPoolSize :: Bool Source #

HasField "type" VkDescriptorPoolSize Source # 
type StructFields VkDescriptorPoolSize Source # 
type StructFields VkDescriptorPoolSize = (:) Symbol "type" ((:) Symbol "descriptorCount" ([] Symbol))
type CUnionType VkDescriptorPoolSize Source # 
type ReturnedOnly VkDescriptorPoolSize Source # 
type StructExtends VkDescriptorPoolSize Source # 
type FieldType "descriptorCount" VkDescriptorPoolSize Source # 
type FieldType "descriptorCount" VkDescriptorPoolSize = Word32
type FieldType "type" VkDescriptorPoolSize Source # 
type FieldOptional "descriptorCount" VkDescriptorPoolSize Source # 
type FieldOptional "descriptorCount" VkDescriptorPoolSize = False
type FieldOptional "type" VkDescriptorPoolSize Source # 
type FieldOffset "descriptorCount" VkDescriptorPoolSize Source # 
type FieldOffset "descriptorCount" VkDescriptorPoolSize = 4
type FieldOffset "type" VkDescriptorPoolSize Source # 
type FieldIsArray "descriptorCount" VkDescriptorPoolSize Source # 
type FieldIsArray "descriptorCount" VkDescriptorPoolSize = False
type FieldIsArray "type" VkDescriptorPoolSize Source # 

data VkDescriptorSetAllocateInfo Source #

typedef struct VkDescriptorSetAllocateInfo {
    VkStructureType sType;
    const void*            pNext;
    VkDescriptorPool       descriptorPool;
    uint32_t               descriptorSetCount;
    const VkDescriptorSetLayout* pSetLayouts;
} VkDescriptorSetAllocateInfo;

VkDescriptorSetAllocateInfo registry at www.khronos.org

Instances

Eq VkDescriptorSetAllocateInfo Source # 
Ord VkDescriptorSetAllocateInfo Source # 
Show VkDescriptorSetAllocateInfo Source # 
Storable VkDescriptorSetAllocateInfo Source # 
VulkanMarshalPrim VkDescriptorSetAllocateInfo Source # 
VulkanMarshal VkDescriptorSetAllocateInfo Source # 
CanWriteField "descriptorPool" VkDescriptorSetAllocateInfo Source # 
CanWriteField "descriptorSetCount" VkDescriptorSetAllocateInfo Source # 
CanWriteField "pNext" VkDescriptorSetAllocateInfo Source # 
CanWriteField "pSetLayouts" VkDescriptorSetAllocateInfo Source # 
CanWriteField "sType" VkDescriptorSetAllocateInfo Source # 
CanReadField "descriptorPool" VkDescriptorSetAllocateInfo Source # 
CanReadField "descriptorSetCount" VkDescriptorSetAllocateInfo Source # 
CanReadField "pNext" VkDescriptorSetAllocateInfo Source # 
CanReadField "pSetLayouts" VkDescriptorSetAllocateInfo Source # 
CanReadField "sType" VkDescriptorSetAllocateInfo Source # 
HasField "descriptorPool" VkDescriptorSetAllocateInfo Source # 
HasField "descriptorSetCount" VkDescriptorSetAllocateInfo Source # 

Associated Types

type FieldType ("descriptorSetCount" :: Symbol) VkDescriptorSetAllocateInfo :: Type Source #

type FieldOptional ("descriptorSetCount" :: Symbol) VkDescriptorSetAllocateInfo :: Bool Source #

type FieldOffset ("descriptorSetCount" :: Symbol) VkDescriptorSetAllocateInfo :: Nat Source #

type FieldIsArray ("descriptorSetCount" :: Symbol) VkDescriptorSetAllocateInfo :: Bool Source #

HasField "pNext" VkDescriptorSetAllocateInfo Source # 
HasField "pSetLayouts" VkDescriptorSetAllocateInfo Source # 
HasField "sType" VkDescriptorSetAllocateInfo Source # 
type StructFields VkDescriptorSetAllocateInfo Source # 
type StructFields VkDescriptorSetAllocateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "descriptorPool" ((:) Symbol "descriptorSetCount" ((:) Symbol "pSetLayouts" ([] Symbol)))))
type CUnionType VkDescriptorSetAllocateInfo Source # 
type ReturnedOnly VkDescriptorSetAllocateInfo Source # 
type StructExtends VkDescriptorSetAllocateInfo Source # 
type FieldType "descriptorPool" VkDescriptorSetAllocateInfo Source # 
type FieldType "descriptorSetCount" VkDescriptorSetAllocateInfo Source # 
type FieldType "descriptorSetCount" VkDescriptorSetAllocateInfo = Word32
type FieldType "pNext" VkDescriptorSetAllocateInfo Source # 
type FieldType "pSetLayouts" VkDescriptorSetAllocateInfo Source # 
type FieldType "sType" VkDescriptorSetAllocateInfo Source # 
type FieldOptional "descriptorPool" VkDescriptorSetAllocateInfo Source # 
type FieldOptional "descriptorSetCount" VkDescriptorSetAllocateInfo Source # 
type FieldOptional "descriptorSetCount" VkDescriptorSetAllocateInfo = False
type FieldOptional "pNext" VkDescriptorSetAllocateInfo Source # 
type FieldOptional "pSetLayouts" VkDescriptorSetAllocateInfo Source # 
type FieldOptional "sType" VkDescriptorSetAllocateInfo Source # 
type FieldOffset "descriptorPool" VkDescriptorSetAllocateInfo Source # 
type FieldOffset "descriptorPool" VkDescriptorSetAllocateInfo = 16
type FieldOffset "descriptorSetCount" VkDescriptorSetAllocateInfo Source # 
type FieldOffset "descriptorSetCount" VkDescriptorSetAllocateInfo = 24
type FieldOffset "pNext" VkDescriptorSetAllocateInfo Source # 
type FieldOffset "pSetLayouts" VkDescriptorSetAllocateInfo Source # 
type FieldOffset "sType" VkDescriptorSetAllocateInfo Source # 
type FieldIsArray "descriptorPool" VkDescriptorSetAllocateInfo Source # 
type FieldIsArray "descriptorSetCount" VkDescriptorSetAllocateInfo Source # 
type FieldIsArray "descriptorSetCount" VkDescriptorSetAllocateInfo = False
type FieldIsArray "pNext" VkDescriptorSetAllocateInfo Source # 
type FieldIsArray "pSetLayouts" VkDescriptorSetAllocateInfo Source # 
type FieldIsArray "sType" VkDescriptorSetAllocateInfo Source # 

data VkDescriptorSetLayoutBinding Source #

typedef struct VkDescriptorSetLayoutBinding {
    uint32_t               binding;
    VkDescriptorType       descriptorType;
    uint32_t descriptorCount;
    VkShaderStageFlags     stageFlags;
    const VkSampler*       pImmutableSamplers;
} VkDescriptorSetLayoutBinding;

VkDescriptorSetLayoutBinding registry at www.khronos.org

Instances

Eq VkDescriptorSetLayoutBinding Source # 
Ord VkDescriptorSetLayoutBinding Source # 
Show VkDescriptorSetLayoutBinding Source # 
Storable VkDescriptorSetLayoutBinding Source # 
VulkanMarshalPrim VkDescriptorSetLayoutBinding Source # 
VulkanMarshal VkDescriptorSetLayoutBinding Source # 
CanWriteField "binding" VkDescriptorSetLayoutBinding Source # 
CanWriteField "descriptorCount" VkDescriptorSetLayoutBinding Source # 
CanWriteField "descriptorType" VkDescriptorSetLayoutBinding Source # 
CanWriteField "pImmutableSamplers" VkDescriptorSetLayoutBinding Source # 
CanWriteField "stageFlags" VkDescriptorSetLayoutBinding Source # 
CanReadField "binding" VkDescriptorSetLayoutBinding Source # 
CanReadField "descriptorCount" VkDescriptorSetLayoutBinding Source # 
CanReadField "descriptorType" VkDescriptorSetLayoutBinding Source # 
CanReadField "pImmutableSamplers" VkDescriptorSetLayoutBinding Source # 
CanReadField "stageFlags" VkDescriptorSetLayoutBinding Source # 
HasField "binding" VkDescriptorSetLayoutBinding Source # 
HasField "descriptorCount" VkDescriptorSetLayoutBinding Source # 

Associated Types

type FieldType ("descriptorCount" :: Symbol) VkDescriptorSetLayoutBinding :: Type Source #

type FieldOptional ("descriptorCount" :: Symbol) VkDescriptorSetLayoutBinding :: Bool Source #

type FieldOffset ("descriptorCount" :: Symbol) VkDescriptorSetLayoutBinding :: Nat Source #

type FieldIsArray ("descriptorCount" :: Symbol) VkDescriptorSetLayoutBinding :: Bool Source #

HasField "descriptorType" VkDescriptorSetLayoutBinding Source # 
HasField "pImmutableSamplers" VkDescriptorSetLayoutBinding Source # 

Associated Types

type FieldType ("pImmutableSamplers" :: Symbol) VkDescriptorSetLayoutBinding :: Type Source #

type FieldOptional ("pImmutableSamplers" :: Symbol) VkDescriptorSetLayoutBinding :: Bool Source #

type FieldOffset ("pImmutableSamplers" :: Symbol) VkDescriptorSetLayoutBinding :: Nat Source #

type FieldIsArray ("pImmutableSamplers" :: Symbol) VkDescriptorSetLayoutBinding :: Bool Source #

HasField "stageFlags" VkDescriptorSetLayoutBinding Source # 
type StructFields VkDescriptorSetLayoutBinding Source # 
type StructFields VkDescriptorSetLayoutBinding = (:) Symbol "binding" ((:) Symbol "descriptorType" ((:) Symbol "descriptorCount" ((:) Symbol "stageFlags" ((:) Symbol "pImmutableSamplers" ([] Symbol)))))
type CUnionType VkDescriptorSetLayoutBinding Source # 
type ReturnedOnly VkDescriptorSetLayoutBinding Source # 
type StructExtends VkDescriptorSetLayoutBinding Source # 
type FieldType "binding" VkDescriptorSetLayoutBinding Source # 
type FieldType "descriptorCount" VkDescriptorSetLayoutBinding Source # 
type FieldType "descriptorType" VkDescriptorSetLayoutBinding Source # 
type FieldType "pImmutableSamplers" VkDescriptorSetLayoutBinding Source # 
type FieldType "stageFlags" VkDescriptorSetLayoutBinding Source # 
type FieldOptional "binding" VkDescriptorSetLayoutBinding Source # 
type FieldOptional "descriptorCount" VkDescriptorSetLayoutBinding Source # 
type FieldOptional "descriptorType" VkDescriptorSetLayoutBinding Source # 
type FieldOptional "pImmutableSamplers" VkDescriptorSetLayoutBinding Source # 
type FieldOptional "pImmutableSamplers" VkDescriptorSetLayoutBinding = True
type FieldOptional "stageFlags" VkDescriptorSetLayoutBinding Source # 
type FieldOffset "binding" VkDescriptorSetLayoutBinding Source # 
type FieldOffset "descriptorCount" VkDescriptorSetLayoutBinding Source # 
type FieldOffset "descriptorCount" VkDescriptorSetLayoutBinding = 8
type FieldOffset "descriptorType" VkDescriptorSetLayoutBinding Source # 
type FieldOffset "descriptorType" VkDescriptorSetLayoutBinding = 4
type FieldOffset "pImmutableSamplers" VkDescriptorSetLayoutBinding Source # 
type FieldOffset "pImmutableSamplers" VkDescriptorSetLayoutBinding = 16
type FieldOffset "stageFlags" VkDescriptorSetLayoutBinding Source # 
type FieldIsArray "binding" VkDescriptorSetLayoutBinding Source # 
type FieldIsArray "descriptorCount" VkDescriptorSetLayoutBinding Source # 
type FieldIsArray "descriptorType" VkDescriptorSetLayoutBinding Source # 
type FieldIsArray "pImmutableSamplers" VkDescriptorSetLayoutBinding Source # 
type FieldIsArray "pImmutableSamplers" VkDescriptorSetLayoutBinding = False
type FieldIsArray "stageFlags" VkDescriptorSetLayoutBinding Source # 

data VkDescriptorSetLayoutBindingFlagsCreateInfoEXT Source #

typedef struct VkDescriptorSetLayoutBindingFlagsCreateInfoEXT {
    VkStructureType sType;
    const void*            pNext;
    uint32_t               bindingCount;
    const VkDescriptorBindingFlagsEXT* pBindingFlags;
} VkDescriptorSetLayoutBindingFlagsCreateInfoEXT;

VkDescriptorSetLayoutBindingFlagsCreateInfoEXT registry at www.khronos.org

Instances

Eq VkDescriptorSetLayoutBindingFlagsCreateInfoEXT Source # 
Ord VkDescriptorSetLayoutBindingFlagsCreateInfoEXT Source # 
Show VkDescriptorSetLayoutBindingFlagsCreateInfoEXT Source # 
Storable VkDescriptorSetLayoutBindingFlagsCreateInfoEXT Source # 
VulkanMarshalPrim VkDescriptorSetLayoutBindingFlagsCreateInfoEXT Source # 
VulkanMarshal VkDescriptorSetLayoutBindingFlagsCreateInfoEXT Source # 
CanWriteField "bindingCount" VkDescriptorSetLayoutBindingFlagsCreateInfoEXT Source # 
CanWriteField "pBindingFlags" VkDescriptorSetLayoutBindingFlagsCreateInfoEXT Source # 
CanWriteField "pNext" VkDescriptorSetLayoutBindingFlagsCreateInfoEXT Source # 
CanWriteField "sType" VkDescriptorSetLayoutBindingFlagsCreateInfoEXT Source # 
CanReadField "bindingCount" VkDescriptorSetLayoutBindingFlagsCreateInfoEXT Source # 
CanReadField "pBindingFlags" VkDescriptorSetLayoutBindingFlagsCreateInfoEXT Source # 
CanReadField "pNext" VkDescriptorSetLayoutBindingFlagsCreateInfoEXT Source # 
CanReadField "sType" VkDescriptorSetLayoutBindingFlagsCreateInfoEXT Source # 
HasField "bindingCount" VkDescriptorSetLayoutBindingFlagsCreateInfoEXT Source # 
HasField "pBindingFlags" VkDescriptorSetLayoutBindingFlagsCreateInfoEXT Source # 
HasField "pNext" VkDescriptorSetLayoutBindingFlagsCreateInfoEXT Source # 
HasField "sType" VkDescriptorSetLayoutBindingFlagsCreateInfoEXT Source # 
type StructFields VkDescriptorSetLayoutBindingFlagsCreateInfoEXT Source # 
type StructFields VkDescriptorSetLayoutBindingFlagsCreateInfoEXT = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "bindingCount" ((:) Symbol "pBindingFlags" ([] Symbol))))
type CUnionType VkDescriptorSetLayoutBindingFlagsCreateInfoEXT Source # 
type ReturnedOnly VkDescriptorSetLayoutBindingFlagsCreateInfoEXT Source # 
type StructExtends VkDescriptorSetLayoutBindingFlagsCreateInfoEXT Source # 
type FieldType "bindingCount" VkDescriptorSetLayoutBindingFlagsCreateInfoEXT Source # 
type FieldType "pBindingFlags" VkDescriptorSetLayoutBindingFlagsCreateInfoEXT Source # 
type FieldType "pNext" VkDescriptorSetLayoutBindingFlagsCreateInfoEXT Source # 
type FieldType "sType" VkDescriptorSetLayoutBindingFlagsCreateInfoEXT Source # 
type FieldOptional "bindingCount" VkDescriptorSetLayoutBindingFlagsCreateInfoEXT Source # 
type FieldOptional "pBindingFlags" VkDescriptorSetLayoutBindingFlagsCreateInfoEXT Source # 
type FieldOptional "pNext" VkDescriptorSetLayoutBindingFlagsCreateInfoEXT Source # 
type FieldOptional "sType" VkDescriptorSetLayoutBindingFlagsCreateInfoEXT Source # 
type FieldOffset "bindingCount" VkDescriptorSetLayoutBindingFlagsCreateInfoEXT Source # 
type FieldOffset "pBindingFlags" VkDescriptorSetLayoutBindingFlagsCreateInfoEXT Source # 
type FieldOffset "pNext" VkDescriptorSetLayoutBindingFlagsCreateInfoEXT Source # 
type FieldOffset "sType" VkDescriptorSetLayoutBindingFlagsCreateInfoEXT Source # 
type FieldIsArray "bindingCount" VkDescriptorSetLayoutBindingFlagsCreateInfoEXT Source # 
type FieldIsArray "pBindingFlags" VkDescriptorSetLayoutBindingFlagsCreateInfoEXT Source # 
type FieldIsArray "pNext" VkDescriptorSetLayoutBindingFlagsCreateInfoEXT Source # 
type FieldIsArray "sType" VkDescriptorSetLayoutBindingFlagsCreateInfoEXT Source # 

data VkDescriptorSetLayoutCreateInfo Source #

typedef struct VkDescriptorSetLayoutCreateInfo {
    VkStructureType sType;
    const void*            pNext;
    VkDescriptorSetLayoutCreateFlags    flags;
    uint32_t               bindingCount;
    const VkDescriptorSetLayoutBinding* pBindings;
} VkDescriptorSetLayoutCreateInfo;

VkDescriptorSetLayoutCreateInfo registry at www.khronos.org

Instances

Eq VkDescriptorSetLayoutCreateInfo Source # 
Ord VkDescriptorSetLayoutCreateInfo Source # 
Show VkDescriptorSetLayoutCreateInfo Source # 
Storable VkDescriptorSetLayoutCreateInfo Source # 
VulkanMarshalPrim VkDescriptorSetLayoutCreateInfo Source # 
VulkanMarshal VkDescriptorSetLayoutCreateInfo Source # 
CanWriteField "bindingCount" VkDescriptorSetLayoutCreateInfo Source # 
CanWriteField "flags" VkDescriptorSetLayoutCreateInfo Source # 
CanWriteField "pBindings" VkDescriptorSetLayoutCreateInfo Source # 
CanWriteField "pNext" VkDescriptorSetLayoutCreateInfo Source # 
CanWriteField "sType" VkDescriptorSetLayoutCreateInfo Source # 
CanReadField "bindingCount" VkDescriptorSetLayoutCreateInfo Source # 
CanReadField "flags" VkDescriptorSetLayoutCreateInfo Source # 
CanReadField "pBindings" VkDescriptorSetLayoutCreateInfo Source # 
CanReadField "pNext" VkDescriptorSetLayoutCreateInfo Source # 
CanReadField "sType" VkDescriptorSetLayoutCreateInfo Source # 
HasField "bindingCount" VkDescriptorSetLayoutCreateInfo Source # 
HasField "flags" VkDescriptorSetLayoutCreateInfo Source # 
HasField "pBindings" VkDescriptorSetLayoutCreateInfo Source # 
HasField "pNext" VkDescriptorSetLayoutCreateInfo Source # 
HasField "sType" VkDescriptorSetLayoutCreateInfo Source # 
type StructFields VkDescriptorSetLayoutCreateInfo Source # 
type StructFields VkDescriptorSetLayoutCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "bindingCount" ((:) Symbol "pBindings" ([] Symbol)))))
type CUnionType VkDescriptorSetLayoutCreateInfo Source # 
type ReturnedOnly VkDescriptorSetLayoutCreateInfo Source # 
type StructExtends VkDescriptorSetLayoutCreateInfo Source # 
type FieldType "bindingCount" VkDescriptorSetLayoutCreateInfo Source # 
type FieldType "flags" VkDescriptorSetLayoutCreateInfo Source # 
type FieldType "pBindings" VkDescriptorSetLayoutCreateInfo Source # 
type FieldType "pNext" VkDescriptorSetLayoutCreateInfo Source # 
type FieldType "sType" VkDescriptorSetLayoutCreateInfo Source # 
type FieldOptional "bindingCount" VkDescriptorSetLayoutCreateInfo Source # 
type FieldOptional "flags" VkDescriptorSetLayoutCreateInfo Source # 
type FieldOptional "pBindings" VkDescriptorSetLayoutCreateInfo Source # 
type FieldOptional "pNext" VkDescriptorSetLayoutCreateInfo Source # 
type FieldOptional "sType" VkDescriptorSetLayoutCreateInfo Source # 
type FieldOffset "bindingCount" VkDescriptorSetLayoutCreateInfo Source # 
type FieldOffset "flags" VkDescriptorSetLayoutCreateInfo Source # 
type FieldOffset "pBindings" VkDescriptorSetLayoutCreateInfo Source # 
type FieldOffset "pNext" VkDescriptorSetLayoutCreateInfo Source # 
type FieldOffset "sType" VkDescriptorSetLayoutCreateInfo Source # 
type FieldIsArray "bindingCount" VkDescriptorSetLayoutCreateInfo Source # 
type FieldIsArray "flags" VkDescriptorSetLayoutCreateInfo Source # 
type FieldIsArray "pBindings" VkDescriptorSetLayoutCreateInfo Source # 
type FieldIsArray "pNext" VkDescriptorSetLayoutCreateInfo Source # 
type FieldIsArray "sType" VkDescriptorSetLayoutCreateInfo Source # 

data VkDescriptorSetLayoutSupport Source #

typedef struct VkDescriptorSetLayoutSupport {
    VkStructureType sType;
    void*            pNext;
    VkBool32         supported;
} VkDescriptorSetLayoutSupport;

VkDescriptorSetLayoutSupport registry at www.khronos.org

Instances

Eq VkDescriptorSetLayoutSupport Source # 
Ord VkDescriptorSetLayoutSupport Source # 
Show VkDescriptorSetLayoutSupport Source # 
Storable VkDescriptorSetLayoutSupport Source # 
VulkanMarshalPrim VkDescriptorSetLayoutSupport Source # 
VulkanMarshal VkDescriptorSetLayoutSupport Source # 
CanWriteField "pNext" VkDescriptorSetLayoutSupport Source # 
CanWriteField "sType" VkDescriptorSetLayoutSupport Source # 
CanWriteField "supported" VkDescriptorSetLayoutSupport Source # 
CanReadField "pNext" VkDescriptorSetLayoutSupport Source # 
CanReadField "sType" VkDescriptorSetLayoutSupport Source # 
CanReadField "supported" VkDescriptorSetLayoutSupport Source # 
HasField "pNext" VkDescriptorSetLayoutSupport Source # 
HasField "sType" VkDescriptorSetLayoutSupport Source # 
HasField "supported" VkDescriptorSetLayoutSupport Source # 
type StructFields VkDescriptorSetLayoutSupport Source # 
type StructFields VkDescriptorSetLayoutSupport = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "supported" ([] Symbol)))
type CUnionType VkDescriptorSetLayoutSupport Source # 
type ReturnedOnly VkDescriptorSetLayoutSupport Source # 
type StructExtends VkDescriptorSetLayoutSupport Source # 
type FieldType "pNext" VkDescriptorSetLayoutSupport Source # 
type FieldType "sType" VkDescriptorSetLayoutSupport Source # 
type FieldType "supported" VkDescriptorSetLayoutSupport Source # 
type FieldOptional "pNext" VkDescriptorSetLayoutSupport Source # 
type FieldOptional "sType" VkDescriptorSetLayoutSupport Source # 
type FieldOptional "supported" VkDescriptorSetLayoutSupport Source # 
type FieldOffset "pNext" VkDescriptorSetLayoutSupport Source # 
type FieldOffset "sType" VkDescriptorSetLayoutSupport Source # 
type FieldOffset "supported" VkDescriptorSetLayoutSupport Source # 
type FieldIsArray "pNext" VkDescriptorSetLayoutSupport Source # 
type FieldIsArray "sType" VkDescriptorSetLayoutSupport Source # 
type FieldIsArray "supported" VkDescriptorSetLayoutSupport Source # 

data VkDescriptorSetVariableDescriptorCountAllocateInfoEXT Source #

typedef struct VkDescriptorSetVariableDescriptorCountAllocateInfoEXT {
    VkStructureType sType;
    const void*            pNext;
    uint32_t               descriptorSetCount;
    const uint32_t* pDescriptorCounts;
} VkDescriptorSetVariableDescriptorCountAllocateInfoEXT;

VkDescriptorSetVariableDescriptorCountAllocateInfoEXT registry at www.khronos.org

Instances

Eq VkDescriptorSetVariableDescriptorCountAllocateInfoEXT Source # 
Ord VkDescriptorSetVariableDescriptorCountAllocateInfoEXT Source # 
Show VkDescriptorSetVariableDescriptorCountAllocateInfoEXT Source # 
Storable VkDescriptorSetVariableDescriptorCountAllocateInfoEXT Source # 
VulkanMarshalPrim VkDescriptorSetVariableDescriptorCountAllocateInfoEXT Source # 
VulkanMarshal VkDescriptorSetVariableDescriptorCountAllocateInfoEXT Source # 
CanWriteField "descriptorSetCount" VkDescriptorSetVariableDescriptorCountAllocateInfoEXT Source # 
CanWriteField "pDescriptorCounts" VkDescriptorSetVariableDescriptorCountAllocateInfoEXT Source # 
CanWriteField "pNext" VkDescriptorSetVariableDescriptorCountAllocateInfoEXT Source # 
CanWriteField "sType" VkDescriptorSetVariableDescriptorCountAllocateInfoEXT Source # 
CanReadField "descriptorSetCount" VkDescriptorSetVariableDescriptorCountAllocateInfoEXT Source # 
CanReadField "pDescriptorCounts" VkDescriptorSetVariableDescriptorCountAllocateInfoEXT Source # 
CanReadField "pNext" VkDescriptorSetVariableDescriptorCountAllocateInfoEXT Source # 
CanReadField "sType" VkDescriptorSetVariableDescriptorCountAllocateInfoEXT Source # 
HasField "descriptorSetCount" VkDescriptorSetVariableDescriptorCountAllocateInfoEXT Source # 
HasField "pDescriptorCounts" VkDescriptorSetVariableDescriptorCountAllocateInfoEXT Source # 
HasField "pNext" VkDescriptorSetVariableDescriptorCountAllocateInfoEXT Source # 
HasField "sType" VkDescriptorSetVariableDescriptorCountAllocateInfoEXT Source # 
type StructFields VkDescriptorSetVariableDescriptorCountAllocateInfoEXT Source # 
type StructFields VkDescriptorSetVariableDescriptorCountAllocateInfoEXT = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "descriptorSetCount" ((:) Symbol "pDescriptorCounts" ([] Symbol))))
type CUnionType VkDescriptorSetVariableDescriptorCountAllocateInfoEXT Source # 
type ReturnedOnly VkDescriptorSetVariableDescriptorCountAllocateInfoEXT Source # 
type StructExtends VkDescriptorSetVariableDescriptorCountAllocateInfoEXT Source # 
type FieldType "descriptorSetCount" VkDescriptorSetVariableDescriptorCountAllocateInfoEXT Source # 
type FieldType "pDescriptorCounts" VkDescriptorSetVariableDescriptorCountAllocateInfoEXT Source # 
type FieldType "pNext" VkDescriptorSetVariableDescriptorCountAllocateInfoEXT Source # 
type FieldType "sType" VkDescriptorSetVariableDescriptorCountAllocateInfoEXT Source # 
type FieldOptional "descriptorSetCount" VkDescriptorSetVariableDescriptorCountAllocateInfoEXT Source # 
type FieldOptional "pDescriptorCounts" VkDescriptorSetVariableDescriptorCountAllocateInfoEXT Source # 
type FieldOptional "pNext" VkDescriptorSetVariableDescriptorCountAllocateInfoEXT Source # 
type FieldOptional "sType" VkDescriptorSetVariableDescriptorCountAllocateInfoEXT Source # 
type FieldOffset "descriptorSetCount" VkDescriptorSetVariableDescriptorCountAllocateInfoEXT Source # 
type FieldOffset "pDescriptorCounts" VkDescriptorSetVariableDescriptorCountAllocateInfoEXT Source # 
type FieldOffset "pNext" VkDescriptorSetVariableDescriptorCountAllocateInfoEXT Source # 
type FieldOffset "sType" VkDescriptorSetVariableDescriptorCountAllocateInfoEXT Source # 
type FieldIsArray "descriptorSetCount" VkDescriptorSetVariableDescriptorCountAllocateInfoEXT Source # 
type FieldIsArray "pDescriptorCounts" VkDescriptorSetVariableDescriptorCountAllocateInfoEXT Source # 
type FieldIsArray "pNext" VkDescriptorSetVariableDescriptorCountAllocateInfoEXT Source # 
type FieldIsArray "sType" VkDescriptorSetVariableDescriptorCountAllocateInfoEXT Source # 

data VkDescriptorSetVariableDescriptorCountLayoutSupportEXT Source #

typedef struct VkDescriptorSetVariableDescriptorCountLayoutSupportEXT {
    VkStructureType sType;
    void*            pNext;
    uint32_t         maxVariableDescriptorCount;
} VkDescriptorSetVariableDescriptorCountLayoutSupportEXT;

VkDescriptorSetVariableDescriptorCountLayoutSupportEXT registry at www.khronos.org

Instances

Eq VkDescriptorSetVariableDescriptorCountLayoutSupportEXT Source # 
Ord VkDescriptorSetVariableDescriptorCountLayoutSupportEXT Source # 
Show VkDescriptorSetVariableDescriptorCountLayoutSupportEXT Source # 
Storable VkDescriptorSetVariableDescriptorCountLayoutSupportEXT Source # 
VulkanMarshalPrim VkDescriptorSetVariableDescriptorCountLayoutSupportEXT Source # 
VulkanMarshal VkDescriptorSetVariableDescriptorCountLayoutSupportEXT Source # 
CanWriteField "maxVariableDescriptorCount" VkDescriptorSetVariableDescriptorCountLayoutSupportEXT Source # 
CanWriteField "pNext" VkDescriptorSetVariableDescriptorCountLayoutSupportEXT Source # 
CanWriteField "sType" VkDescriptorSetVariableDescriptorCountLayoutSupportEXT Source # 
CanReadField "maxVariableDescriptorCount" VkDescriptorSetVariableDescriptorCountLayoutSupportEXT Source # 
CanReadField "pNext" VkDescriptorSetVariableDescriptorCountLayoutSupportEXT Source # 
CanReadField "sType" VkDescriptorSetVariableDescriptorCountLayoutSupportEXT Source # 
HasField "maxVariableDescriptorCount" VkDescriptorSetVariableDescriptorCountLayoutSupportEXT Source # 
HasField "pNext" VkDescriptorSetVariableDescriptorCountLayoutSupportEXT Source # 
HasField "sType" VkDescriptorSetVariableDescriptorCountLayoutSupportEXT Source # 
type StructFields VkDescriptorSetVariableDescriptorCountLayoutSupportEXT Source # 
type StructFields VkDescriptorSetVariableDescriptorCountLayoutSupportEXT = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "maxVariableDescriptorCount" ([] Symbol)))
type CUnionType VkDescriptorSetVariableDescriptorCountLayoutSupportEXT Source # 
type ReturnedOnly VkDescriptorSetVariableDescriptorCountLayoutSupportEXT Source # 
type StructExtends VkDescriptorSetVariableDescriptorCountLayoutSupportEXT Source # 
type FieldType "maxVariableDescriptorCount" VkDescriptorSetVariableDescriptorCountLayoutSupportEXT Source # 
type FieldType "pNext" VkDescriptorSetVariableDescriptorCountLayoutSupportEXT Source # 
type FieldType "sType" VkDescriptorSetVariableDescriptorCountLayoutSupportEXT Source # 
type FieldOptional "maxVariableDescriptorCount" VkDescriptorSetVariableDescriptorCountLayoutSupportEXT Source # 
type FieldOptional "pNext" VkDescriptorSetVariableDescriptorCountLayoutSupportEXT Source # 
type FieldOptional "sType" VkDescriptorSetVariableDescriptorCountLayoutSupportEXT Source # 
type FieldOffset "maxVariableDescriptorCount" VkDescriptorSetVariableDescriptorCountLayoutSupportEXT Source # 
type FieldOffset "pNext" VkDescriptorSetVariableDescriptorCountLayoutSupportEXT Source # 
type FieldOffset "sType" VkDescriptorSetVariableDescriptorCountLayoutSupportEXT Source # 
type FieldIsArray "maxVariableDescriptorCount" VkDescriptorSetVariableDescriptorCountLayoutSupportEXT Source # 
type FieldIsArray "pNext" VkDescriptorSetVariableDescriptorCountLayoutSupportEXT Source # 
type FieldIsArray "sType" VkDescriptorSetVariableDescriptorCountLayoutSupportEXT Source # 

data VkDescriptorUpdateTemplateCreateInfo Source #

typedef struct VkDescriptorUpdateTemplateCreateInfo {
    VkStructureType sType;
    void*                                   pNext;
    VkDescriptorUpdateTemplateCreateFlags    flags;
    uint32_t                 descriptorUpdateEntryCount;
    const VkDescriptorUpdateTemplateEntry* pDescriptorUpdateEntries;
    VkDescriptorUpdateTemplateType templateType;
    VkDescriptorSetLayout descriptorSetLayout;
    VkPipelineBindPoint pipelineBindPoint;
    VkPipelineLayoutpipelineLayout;
    uint32_t set;
} VkDescriptorUpdateTemplateCreateInfo;

VkDescriptorUpdateTemplateCreateInfo registry at www.khronos.org

Instances

Eq VkDescriptorUpdateTemplateCreateInfo Source # 
Ord VkDescriptorUpdateTemplateCreateInfo Source # 
Show VkDescriptorUpdateTemplateCreateInfo Source # 
Storable VkDescriptorUpdateTemplateCreateInfo Source # 
VulkanMarshalPrim VkDescriptorUpdateTemplateCreateInfo Source # 
VulkanMarshal VkDescriptorUpdateTemplateCreateInfo Source # 
CanWriteField "descriptorSetLayout" VkDescriptorUpdateTemplateCreateInfo Source # 
CanWriteField "descriptorUpdateEntryCount" VkDescriptorUpdateTemplateCreateInfo Source # 
CanWriteField "flags" VkDescriptorUpdateTemplateCreateInfo Source # 
CanWriteField "pDescriptorUpdateEntries" VkDescriptorUpdateTemplateCreateInfo Source # 
CanWriteField "pNext" VkDescriptorUpdateTemplateCreateInfo Source # 
CanWriteField "pipelineBindPoint" VkDescriptorUpdateTemplateCreateInfo Source # 
CanWriteField "pipelineLayout" VkDescriptorUpdateTemplateCreateInfo Source # 
CanWriteField "sType" VkDescriptorUpdateTemplateCreateInfo Source # 
CanWriteField "set" VkDescriptorUpdateTemplateCreateInfo Source # 
CanWriteField "templateType" VkDescriptorUpdateTemplateCreateInfo Source # 
CanReadField "descriptorSetLayout" VkDescriptorUpdateTemplateCreateInfo Source # 
CanReadField "descriptorUpdateEntryCount" VkDescriptorUpdateTemplateCreateInfo Source # 
CanReadField "flags" VkDescriptorUpdateTemplateCreateInfo Source # 
CanReadField "pDescriptorUpdateEntries" VkDescriptorUpdateTemplateCreateInfo Source # 
CanReadField "pNext" VkDescriptorUpdateTemplateCreateInfo Source # 
CanReadField "pipelineBindPoint" VkDescriptorUpdateTemplateCreateInfo Source # 
CanReadField "pipelineLayout" VkDescriptorUpdateTemplateCreateInfo Source # 
CanReadField "sType" VkDescriptorUpdateTemplateCreateInfo Source # 
CanReadField "set" VkDescriptorUpdateTemplateCreateInfo Source # 
CanReadField "templateType" VkDescriptorUpdateTemplateCreateInfo Source # 
HasField "descriptorSetLayout" VkDescriptorUpdateTemplateCreateInfo Source # 
HasField "descriptorUpdateEntryCount" VkDescriptorUpdateTemplateCreateInfo Source # 

Associated Types

type FieldType ("descriptorUpdateEntryCount" :: Symbol) VkDescriptorUpdateTemplateCreateInfo :: Type Source #

type FieldOptional ("descriptorUpdateEntryCount" :: Symbol) VkDescriptorUpdateTemplateCreateInfo :: Bool Source #

type FieldOffset ("descriptorUpdateEntryCount" :: Symbol) VkDescriptorUpdateTemplateCreateInfo :: Nat Source #

type FieldIsArray ("descriptorUpdateEntryCount" :: Symbol) VkDescriptorUpdateTemplateCreateInfo :: Bool Source #

HasField "flags" VkDescriptorUpdateTemplateCreateInfo Source # 
HasField "pDescriptorUpdateEntries" VkDescriptorUpdateTemplateCreateInfo Source # 

Associated Types

type FieldType ("pDescriptorUpdateEntries" :: Symbol) VkDescriptorUpdateTemplateCreateInfo :: Type Source #

type FieldOptional ("pDescriptorUpdateEntries" :: Symbol) VkDescriptorUpdateTemplateCreateInfo :: Bool Source #

type FieldOffset ("pDescriptorUpdateEntries" :: Symbol) VkDescriptorUpdateTemplateCreateInfo :: Nat Source #

type FieldIsArray ("pDescriptorUpdateEntries" :: Symbol) VkDescriptorUpdateTemplateCreateInfo :: Bool Source #

HasField "pNext" VkDescriptorUpdateTemplateCreateInfo Source # 
HasField "pipelineBindPoint" VkDescriptorUpdateTemplateCreateInfo Source # 
HasField "pipelineLayout" VkDescriptorUpdateTemplateCreateInfo Source # 
HasField "sType" VkDescriptorUpdateTemplateCreateInfo Source # 
HasField "set" VkDescriptorUpdateTemplateCreateInfo Source # 
HasField "templateType" VkDescriptorUpdateTemplateCreateInfo Source # 
type StructFields VkDescriptorUpdateTemplateCreateInfo Source # 
type StructFields VkDescriptorUpdateTemplateCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "descriptorUpdateEntryCount" ((:) Symbol "pDescriptorUpdateEntries" ((:) Symbol "templateType" ((:) Symbol "descriptorSetLayout" ((:) Symbol "pipelineBindPoint" ((:) Symbol "pipelineLayout" ((:) Symbol "set" ([] Symbol))))))))))
type CUnionType VkDescriptorUpdateTemplateCreateInfo Source # 
type ReturnedOnly VkDescriptorUpdateTemplateCreateInfo Source # 
type StructExtends VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldType "descriptorSetLayout" VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldType "descriptorUpdateEntryCount" VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldType "descriptorUpdateEntryCount" VkDescriptorUpdateTemplateCreateInfo = Word32
type FieldType "flags" VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldType "pDescriptorUpdateEntries" VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldType "pNext" VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldType "pipelineBindPoint" VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldType "pipelineLayout" VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldType "sType" VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldType "set" VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldType "templateType" VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldOptional "descriptorSetLayout" VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldOptional "descriptorUpdateEntryCount" VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldOptional "descriptorUpdateEntryCount" VkDescriptorUpdateTemplateCreateInfo = False
type FieldOptional "flags" VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldOptional "pDescriptorUpdateEntries" VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldOptional "pDescriptorUpdateEntries" VkDescriptorUpdateTemplateCreateInfo = False
type FieldOptional "pNext" VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldOptional "pipelineBindPoint" VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldOptional "pipelineLayout" VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldOptional "sType" VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldOptional "set" VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldOptional "templateType" VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldOffset "descriptorSetLayout" VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldOffset "descriptorSetLayout" VkDescriptorUpdateTemplateCreateInfo = 40
type FieldOffset "descriptorUpdateEntryCount" VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldOffset "descriptorUpdateEntryCount" VkDescriptorUpdateTemplateCreateInfo = 20
type FieldOffset "flags" VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldOffset "pDescriptorUpdateEntries" VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldOffset "pDescriptorUpdateEntries" VkDescriptorUpdateTemplateCreateInfo = 24
type FieldOffset "pNext" VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldOffset "pipelineBindPoint" VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldOffset "pipelineLayout" VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldOffset "sType" VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldOffset "set" VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldOffset "templateType" VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldIsArray "descriptorSetLayout" VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldIsArray "descriptorUpdateEntryCount" VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldIsArray "descriptorUpdateEntryCount" VkDescriptorUpdateTemplateCreateInfo = False
type FieldIsArray "flags" VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldIsArray "pDescriptorUpdateEntries" VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldIsArray "pDescriptorUpdateEntries" VkDescriptorUpdateTemplateCreateInfo = False
type FieldIsArray "pNext" VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldIsArray "pipelineBindPoint" VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldIsArray "pipelineLayout" VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldIsArray "sType" VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldIsArray "set" VkDescriptorUpdateTemplateCreateInfo Source # 
type FieldIsArray "templateType" VkDescriptorUpdateTemplateCreateInfo Source # 

data VkDescriptorUpdateTemplateEntry Source #

typedef struct VkDescriptorUpdateTemplateEntry {
    uint32_t                         dstBinding;
    uint32_t                         dstArrayElement;
    uint32_t                         descriptorCount;
    VkDescriptorType                 descriptorType;
    size_t                           offset;
    size_t                           stride;
} VkDescriptorUpdateTemplateEntry;

VkDescriptorUpdateTemplateEntry registry at www.khronos.org

Instances

Eq VkDescriptorUpdateTemplateEntry Source # 
Ord VkDescriptorUpdateTemplateEntry Source # 
Show VkDescriptorUpdateTemplateEntry Source # 
Storable VkDescriptorUpdateTemplateEntry Source # 
VulkanMarshalPrim VkDescriptorUpdateTemplateEntry Source # 
VulkanMarshal VkDescriptorUpdateTemplateEntry Source # 
CanWriteField "descriptorCount" VkDescriptorUpdateTemplateEntry Source # 
CanWriteField "descriptorType" VkDescriptorUpdateTemplateEntry Source # 
CanWriteField "dstArrayElement" VkDescriptorUpdateTemplateEntry Source # 
CanWriteField "dstBinding" VkDescriptorUpdateTemplateEntry Source # 
CanWriteField "offset" VkDescriptorUpdateTemplateEntry Source # 
CanWriteField "stride" VkDescriptorUpdateTemplateEntry Source # 
CanReadField "descriptorCount" VkDescriptorUpdateTemplateEntry Source # 
CanReadField "descriptorType" VkDescriptorUpdateTemplateEntry Source # 
CanReadField "dstArrayElement" VkDescriptorUpdateTemplateEntry Source # 
CanReadField "dstBinding" VkDescriptorUpdateTemplateEntry Source # 
CanReadField "offset" VkDescriptorUpdateTemplateEntry Source # 
CanReadField "stride" VkDescriptorUpdateTemplateEntry Source # 
HasField "descriptorCount" VkDescriptorUpdateTemplateEntry Source # 
HasField "descriptorType" VkDescriptorUpdateTemplateEntry Source # 
HasField "dstArrayElement" VkDescriptorUpdateTemplateEntry Source # 
HasField "dstBinding" VkDescriptorUpdateTemplateEntry Source # 
HasField "offset" VkDescriptorUpdateTemplateEntry Source # 
HasField "stride" VkDescriptorUpdateTemplateEntry Source # 
type StructFields VkDescriptorUpdateTemplateEntry Source # 
type StructFields VkDescriptorUpdateTemplateEntry = (:) Symbol "dstBinding" ((:) Symbol "dstArrayElement" ((:) Symbol "descriptorCount" ((:) Symbol "descriptorType" ((:) Symbol "offset" ((:) Symbol "stride" ([] Symbol))))))
type CUnionType VkDescriptorUpdateTemplateEntry Source # 
type ReturnedOnly VkDescriptorUpdateTemplateEntry Source # 
type StructExtends VkDescriptorUpdateTemplateEntry Source # 
type FieldType "descriptorCount" VkDescriptorUpdateTemplateEntry Source # 
type FieldType "descriptorType" VkDescriptorUpdateTemplateEntry Source # 
type FieldType "dstArrayElement" VkDescriptorUpdateTemplateEntry Source # 
type FieldType "dstBinding" VkDescriptorUpdateTemplateEntry Source # 
type FieldType "offset" VkDescriptorUpdateTemplateEntry Source # 
type FieldType "stride" VkDescriptorUpdateTemplateEntry Source # 
type FieldOptional "descriptorCount" VkDescriptorUpdateTemplateEntry Source # 
type FieldOptional "descriptorType" VkDescriptorUpdateTemplateEntry Source # 
type FieldOptional "dstArrayElement" VkDescriptorUpdateTemplateEntry Source # 
type FieldOptional "dstBinding" VkDescriptorUpdateTemplateEntry Source # 
type FieldOptional "offset" VkDescriptorUpdateTemplateEntry Source # 
type FieldOptional "stride" VkDescriptorUpdateTemplateEntry Source # 
type FieldOffset "descriptorCount" VkDescriptorUpdateTemplateEntry Source # 
type FieldOffset "descriptorCount" VkDescriptorUpdateTemplateEntry = 8
type FieldOffset "descriptorType" VkDescriptorUpdateTemplateEntry Source # 
type FieldOffset "descriptorType" VkDescriptorUpdateTemplateEntry = 12
type FieldOffset "dstArrayElement" VkDescriptorUpdateTemplateEntry Source # 
type FieldOffset "dstArrayElement" VkDescriptorUpdateTemplateEntry = 4
type FieldOffset "dstBinding" VkDescriptorUpdateTemplateEntry Source # 
type FieldOffset "offset" VkDescriptorUpdateTemplateEntry Source # 
type FieldOffset "stride" VkDescriptorUpdateTemplateEntry Source # 
type FieldIsArray "descriptorCount" VkDescriptorUpdateTemplateEntry Source # 
type FieldIsArray "descriptorType" VkDescriptorUpdateTemplateEntry Source # 
type FieldIsArray "dstArrayElement" VkDescriptorUpdateTemplateEntry Source # 
type FieldIsArray "dstBinding" VkDescriptorUpdateTemplateEntry Source # 
type FieldIsArray "offset" VkDescriptorUpdateTemplateEntry Source # 
type FieldIsArray "stride" VkDescriptorUpdateTemplateEntry Source # 

type VkCreateDescriptorUpdateTemplate = "vkCreateDescriptorUpdateTemplate" Source #

type HS_vkCreateDescriptorUpdateTemplate Source #

Arguments

 = VkDevice

device

-> Ptr VkDescriptorUpdateTemplateCreateInfo

pCreateInfo

-> Ptr VkAllocationCallbacks

pAllocator

-> Ptr VkDescriptorUpdateTemplate

pDescriptorUpdateTemplate

-> IO VkResult 

Success codes: VK_SUCCESS.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY.

VkResult vkCreateDescriptorUpdateTemplate
    ( VkDevice device
    , const VkDescriptorUpdateTemplateCreateInfo* pCreateInfo
    , const VkAllocationCallbacks* pAllocator
    , VkDescriptorUpdateTemplate* pDescriptorUpdateTemplate
    )

vkCreateDescriptorUpdateTemplate registry at www.khronos.org

vkCreateDescriptorUpdateTemplate Source #

Arguments

:: VkDevice

device

-> Ptr VkDescriptorUpdateTemplateCreateInfo

pCreateInfo

-> Ptr VkAllocationCallbacks

pAllocator

-> Ptr VkDescriptorUpdateTemplate

pDescriptorUpdateTemplate

-> IO VkResult 

Success codes: VK_SUCCESS.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY.

VkResult vkCreateDescriptorUpdateTemplate
    ( VkDevice device
    , const VkDescriptorUpdateTemplateCreateInfo* pCreateInfo
    , const VkAllocationCallbacks* pAllocator
    , VkDescriptorUpdateTemplate* pDescriptorUpdateTemplate
    )

vkCreateDescriptorUpdateTemplate registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myCreateDescriptorUpdateTemplate <- vkGetDeviceProc @VkCreateDescriptorUpdateTemplate vkDevice

or less efficient:

myCreateDescriptorUpdateTemplate <- vkGetProc @VkCreateDescriptorUpdateTemplate

Note: vkCreateDescriptorUpdateTemplateUnsafe and vkCreateDescriptorUpdateTemplateSafe are the unsafe and safe FFI imports of this function, respectively. vkCreateDescriptorUpdateTemplate is an alias of vkCreateDescriptorUpdateTemplateUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkCreateDescriptorUpdateTemplateSafe.

vkCreateDescriptorUpdateTemplateUnsafe Source #

Arguments

:: VkDevice

device

-> Ptr VkDescriptorUpdateTemplateCreateInfo

pCreateInfo

-> Ptr VkAllocationCallbacks

pAllocator

-> Ptr VkDescriptorUpdateTemplate

pDescriptorUpdateTemplate

-> IO VkResult 

Success codes: VK_SUCCESS.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY.

VkResult vkCreateDescriptorUpdateTemplate
    ( VkDevice device
    , const VkDescriptorUpdateTemplateCreateInfo* pCreateInfo
    , const VkAllocationCallbacks* pAllocator
    , VkDescriptorUpdateTemplate* pDescriptorUpdateTemplate
    )

vkCreateDescriptorUpdateTemplate registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myCreateDescriptorUpdateTemplate <- vkGetDeviceProc @VkCreateDescriptorUpdateTemplate vkDevice

or less efficient:

myCreateDescriptorUpdateTemplate <- vkGetProc @VkCreateDescriptorUpdateTemplate

Note: vkCreateDescriptorUpdateTemplateUnsafe and vkCreateDescriptorUpdateTemplateSafe are the unsafe and safe FFI imports of this function, respectively. vkCreateDescriptorUpdateTemplate is an alias of vkCreateDescriptorUpdateTemplateUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkCreateDescriptorUpdateTemplateSafe.

vkCreateDescriptorUpdateTemplateSafe Source #

Arguments

:: VkDevice

device

-> Ptr VkDescriptorUpdateTemplateCreateInfo

pCreateInfo

-> Ptr VkAllocationCallbacks

pAllocator

-> Ptr VkDescriptorUpdateTemplate

pDescriptorUpdateTemplate

-> IO VkResult 

Success codes: VK_SUCCESS.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY.

VkResult vkCreateDescriptorUpdateTemplate
    ( VkDevice device
    , const VkDescriptorUpdateTemplateCreateInfo* pCreateInfo
    , const VkAllocationCallbacks* pAllocator
    , VkDescriptorUpdateTemplate* pDescriptorUpdateTemplate
    )

vkCreateDescriptorUpdateTemplate registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myCreateDescriptorUpdateTemplate <- vkGetDeviceProc @VkCreateDescriptorUpdateTemplate vkDevice

or less efficient:

myCreateDescriptorUpdateTemplate <- vkGetProc @VkCreateDescriptorUpdateTemplate

Note: vkCreateDescriptorUpdateTemplateUnsafe and vkCreateDescriptorUpdateTemplateSafe are the unsafe and safe FFI imports of this function, respectively. vkCreateDescriptorUpdateTemplate is an alias of vkCreateDescriptorUpdateTemplateUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkCreateDescriptorUpdateTemplateSafe.

type VkDestroyDescriptorUpdateTemplate = "vkDestroyDescriptorUpdateTemplate" Source #

type HS_vkDestroyDescriptorUpdateTemplate Source #

Arguments

 = VkDevice

device

-> VkDescriptorUpdateTemplate

descriptorUpdateTemplate

-> Ptr VkAllocationCallbacks

pAllocator

-> IO () 
void vkDestroyDescriptorUpdateTemplate
    ( VkDevice device
    , VkDescriptorUpdateTemplate descriptorUpdateTemplate
    , const VkAllocationCallbacks* pAllocator
    )

vkDestroyDescriptorUpdateTemplate registry at www.khronos.org

vkDestroyDescriptorUpdateTemplate Source #

Arguments

:: VkDevice

device

-> VkDescriptorUpdateTemplate

descriptorUpdateTemplate

-> Ptr VkAllocationCallbacks

pAllocator

-> IO () 
void vkDestroyDescriptorUpdateTemplate
    ( VkDevice device
    , VkDescriptorUpdateTemplate descriptorUpdateTemplate
    , const VkAllocationCallbacks* pAllocator
    )

vkDestroyDescriptorUpdateTemplate registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myDestroyDescriptorUpdateTemplate <- vkGetDeviceProc @VkDestroyDescriptorUpdateTemplate vkDevice

or less efficient:

myDestroyDescriptorUpdateTemplate <- vkGetProc @VkDestroyDescriptorUpdateTemplate

Note: vkDestroyDescriptorUpdateTemplateUnsafe and vkDestroyDescriptorUpdateTemplateSafe are the unsafe and safe FFI imports of this function, respectively. vkDestroyDescriptorUpdateTemplate is an alias of vkDestroyDescriptorUpdateTemplateUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkDestroyDescriptorUpdateTemplateSafe.

vkDestroyDescriptorUpdateTemplateUnsafe Source #

Arguments

:: VkDevice

device

-> VkDescriptorUpdateTemplate

descriptorUpdateTemplate

-> Ptr VkAllocationCallbacks

pAllocator

-> IO () 
void vkDestroyDescriptorUpdateTemplate
    ( VkDevice device
    , VkDescriptorUpdateTemplate descriptorUpdateTemplate
    , const VkAllocationCallbacks* pAllocator
    )

vkDestroyDescriptorUpdateTemplate registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myDestroyDescriptorUpdateTemplate <- vkGetDeviceProc @VkDestroyDescriptorUpdateTemplate vkDevice

or less efficient:

myDestroyDescriptorUpdateTemplate <- vkGetProc @VkDestroyDescriptorUpdateTemplate

Note: vkDestroyDescriptorUpdateTemplateUnsafe and vkDestroyDescriptorUpdateTemplateSafe are the unsafe and safe FFI imports of this function, respectively. vkDestroyDescriptorUpdateTemplate is an alias of vkDestroyDescriptorUpdateTemplateUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkDestroyDescriptorUpdateTemplateSafe.

vkDestroyDescriptorUpdateTemplateSafe Source #

Arguments

:: VkDevice

device

-> VkDescriptorUpdateTemplate

descriptorUpdateTemplate

-> Ptr VkAllocationCallbacks

pAllocator

-> IO () 
void vkDestroyDescriptorUpdateTemplate
    ( VkDevice device
    , VkDescriptorUpdateTemplate descriptorUpdateTemplate
    , const VkAllocationCallbacks* pAllocator
    )

vkDestroyDescriptorUpdateTemplate registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myDestroyDescriptorUpdateTemplate <- vkGetDeviceProc @VkDestroyDescriptorUpdateTemplate vkDevice

or less efficient:

myDestroyDescriptorUpdateTemplate <- vkGetProc @VkDestroyDescriptorUpdateTemplate

Note: vkDestroyDescriptorUpdateTemplateUnsafe and vkDestroyDescriptorUpdateTemplateSafe are the unsafe and safe FFI imports of this function, respectively. vkDestroyDescriptorUpdateTemplate is an alias of vkDestroyDescriptorUpdateTemplateUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkDestroyDescriptorUpdateTemplateSafe.

type VkUpdateDescriptorSetWithTemplate = "vkUpdateDescriptorSetWithTemplate" Source #

type HS_vkUpdateDescriptorSetWithTemplate Source #

Arguments

 = VkDevice

device

-> VkDescriptorSet

descriptorSet

-> VkDescriptorUpdateTemplate

descriptorUpdateTemplate

-> Ptr Void

pData

-> IO () 
void vkUpdateDescriptorSetWithTemplate
    ( VkDevice device
    , VkDescriptorSet descriptorSet
    , VkDescriptorUpdateTemplate descriptorUpdateTemplate
    , const void* pData
    )

vkUpdateDescriptorSetWithTemplate registry at www.khronos.org

vkUpdateDescriptorSetWithTemplate Source #

Arguments

:: VkDevice

device

-> VkDescriptorSet

descriptorSet

-> VkDescriptorUpdateTemplate

descriptorUpdateTemplate

-> Ptr Void

pData

-> IO () 
void vkUpdateDescriptorSetWithTemplate
    ( VkDevice device
    , VkDescriptorSet descriptorSet
    , VkDescriptorUpdateTemplate descriptorUpdateTemplate
    , const void* pData
    )

vkUpdateDescriptorSetWithTemplate registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myUpdateDescriptorSetWithTemplate <- vkGetDeviceProc @VkUpdateDescriptorSetWithTemplate vkDevice

or less efficient:

myUpdateDescriptorSetWithTemplate <- vkGetProc @VkUpdateDescriptorSetWithTemplate

Note: vkUpdateDescriptorSetWithTemplateUnsafe and vkUpdateDescriptorSetWithTemplateSafe are the unsafe and safe FFI imports of this function, respectively. vkUpdateDescriptorSetWithTemplate is an alias of vkUpdateDescriptorSetWithTemplateUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkUpdateDescriptorSetWithTemplateSafe.

vkUpdateDescriptorSetWithTemplateUnsafe Source #

Arguments

:: VkDevice

device

-> VkDescriptorSet

descriptorSet

-> VkDescriptorUpdateTemplate

descriptorUpdateTemplate

-> Ptr Void

pData

-> IO () 
void vkUpdateDescriptorSetWithTemplate
    ( VkDevice device
    , VkDescriptorSet descriptorSet
    , VkDescriptorUpdateTemplate descriptorUpdateTemplate
    , const void* pData
    )

vkUpdateDescriptorSetWithTemplate registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myUpdateDescriptorSetWithTemplate <- vkGetDeviceProc @VkUpdateDescriptorSetWithTemplate vkDevice

or less efficient:

myUpdateDescriptorSetWithTemplate <- vkGetProc @VkUpdateDescriptorSetWithTemplate

Note: vkUpdateDescriptorSetWithTemplateUnsafe and vkUpdateDescriptorSetWithTemplateSafe are the unsafe and safe FFI imports of this function, respectively. vkUpdateDescriptorSetWithTemplate is an alias of vkUpdateDescriptorSetWithTemplateUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkUpdateDescriptorSetWithTemplateSafe.

vkUpdateDescriptorSetWithTemplateSafe Source #

Arguments

:: VkDevice

device

-> VkDescriptorSet

descriptorSet

-> VkDescriptorUpdateTemplate

descriptorUpdateTemplate

-> Ptr Void

pData

-> IO () 
void vkUpdateDescriptorSetWithTemplate
    ( VkDevice device
    , VkDescriptorSet descriptorSet
    , VkDescriptorUpdateTemplate descriptorUpdateTemplate
    , const void* pData
    )

vkUpdateDescriptorSetWithTemplate registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myUpdateDescriptorSetWithTemplate <- vkGetDeviceProc @VkUpdateDescriptorSetWithTemplate vkDevice

or less efficient:

myUpdateDescriptorSetWithTemplate <- vkGetProc @VkUpdateDescriptorSetWithTemplate

Note: vkUpdateDescriptorSetWithTemplateUnsafe and vkUpdateDescriptorSetWithTemplateSafe are the unsafe and safe FFI imports of this function, respectively. vkUpdateDescriptorSetWithTemplate is an alias of vkUpdateDescriptorSetWithTemplateUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkUpdateDescriptorSetWithTemplateSafe.

Promoted from VK_KHR_external_memory_capabilities

newtype VkBufferCreateBitmask a Source #

Instances

Bounded (VkBufferCreateBitmask FlagMask) Source # 
Enum (VkBufferCreateBitmask FlagMask) Source # 
Eq (VkBufferCreateBitmask a) Source # 
Integral (VkBufferCreateBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkBufferCreateBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkBufferCreateBitmask a -> c (VkBufferCreateBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkBufferCreateBitmask a) #

toConstr :: VkBufferCreateBitmask a -> Constr #

dataTypeOf :: VkBufferCreateBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkBufferCreateBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkBufferCreateBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkBufferCreateBitmask a -> VkBufferCreateBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkBufferCreateBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkBufferCreateBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkBufferCreateBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkBufferCreateBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkBufferCreateBitmask a -> m (VkBufferCreateBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkBufferCreateBitmask a -> m (VkBufferCreateBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkBufferCreateBitmask a -> m (VkBufferCreateBitmask a) #

Num (VkBufferCreateBitmask FlagMask) Source # 
Ord (VkBufferCreateBitmask a) Source # 
Read (VkBufferCreateBitmask a) Source # 
Real (VkBufferCreateBitmask FlagMask) Source # 
Show (VkBufferCreateBitmask a) Source # 
Generic (VkBufferCreateBitmask a) Source # 
Storable (VkBufferCreateBitmask a) Source # 
Bits (VkBufferCreateBitmask FlagMask) Source # 

Methods

(.&.) :: VkBufferCreateBitmask FlagMask -> VkBufferCreateBitmask FlagMask -> VkBufferCreateBitmask FlagMask #

(.|.) :: VkBufferCreateBitmask FlagMask -> VkBufferCreateBitmask FlagMask -> VkBufferCreateBitmask FlagMask #

xor :: VkBufferCreateBitmask FlagMask -> VkBufferCreateBitmask FlagMask -> VkBufferCreateBitmask FlagMask #

complement :: VkBufferCreateBitmask FlagMask -> VkBufferCreateBitmask FlagMask #

shift :: VkBufferCreateBitmask FlagMask -> Int -> VkBufferCreateBitmask FlagMask #

rotate :: VkBufferCreateBitmask FlagMask -> Int -> VkBufferCreateBitmask FlagMask #

zeroBits :: VkBufferCreateBitmask FlagMask #

bit :: Int -> VkBufferCreateBitmask FlagMask #

setBit :: VkBufferCreateBitmask FlagMask -> Int -> VkBufferCreateBitmask FlagMask #

clearBit :: VkBufferCreateBitmask FlagMask -> Int -> VkBufferCreateBitmask FlagMask #

complementBit :: VkBufferCreateBitmask FlagMask -> Int -> VkBufferCreateBitmask FlagMask #

testBit :: VkBufferCreateBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkBufferCreateBitmask FlagMask -> Maybe Int #

bitSize :: VkBufferCreateBitmask FlagMask -> Int #

isSigned :: VkBufferCreateBitmask FlagMask -> Bool #

shiftL :: VkBufferCreateBitmask FlagMask -> Int -> VkBufferCreateBitmask FlagMask #

unsafeShiftL :: VkBufferCreateBitmask FlagMask -> Int -> VkBufferCreateBitmask FlagMask #

shiftR :: VkBufferCreateBitmask FlagMask -> Int -> VkBufferCreateBitmask FlagMask #

unsafeShiftR :: VkBufferCreateBitmask FlagMask -> Int -> VkBufferCreateBitmask FlagMask #

rotateL :: VkBufferCreateBitmask FlagMask -> Int -> VkBufferCreateBitmask FlagMask #

rotateR :: VkBufferCreateBitmask FlagMask -> Int -> VkBufferCreateBitmask FlagMask #

popCount :: VkBufferCreateBitmask FlagMask -> Int #

FiniteBits (VkBufferCreateBitmask FlagMask) Source # 
type Rep (VkBufferCreateBitmask a) Source # 
type Rep (VkBufferCreateBitmask a) = D1 (MetaData "VkBufferCreateBitmask" "Graphics.Vulkan.Types.Enum.Buffer" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkBufferCreateBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

pattern VK_BUFFER_CREATE_SPARSE_BINDING_BIT :: forall a. VkBufferCreateBitmask a Source #

Buffer should support sparse backing

bitpos = 0

pattern VK_BUFFER_CREATE_SPARSE_RESIDENCY_BIT :: forall a. VkBufferCreateBitmask a Source #

Buffer should support sparse backing with partial residency

bitpos = 1

pattern VK_BUFFER_CREATE_SPARSE_ALIASED_BIT :: forall a. VkBufferCreateBitmask a Source #

Buffer should support constent data access to physical memory ranges mapped into multiple locations of sparse buffers

bitpos = 2

newtype VkBufferUsageBitmask a Source #

Instances

Bounded (VkBufferUsageBitmask FlagMask) Source # 
Enum (VkBufferUsageBitmask FlagMask) Source # 
Eq (VkBufferUsageBitmask a) Source # 
Integral (VkBufferUsageBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkBufferUsageBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkBufferUsageBitmask a -> c (VkBufferUsageBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkBufferUsageBitmask a) #

toConstr :: VkBufferUsageBitmask a -> Constr #

dataTypeOf :: VkBufferUsageBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkBufferUsageBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkBufferUsageBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkBufferUsageBitmask a -> VkBufferUsageBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkBufferUsageBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkBufferUsageBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkBufferUsageBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkBufferUsageBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkBufferUsageBitmask a -> m (VkBufferUsageBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkBufferUsageBitmask a -> m (VkBufferUsageBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkBufferUsageBitmask a -> m (VkBufferUsageBitmask a) #

Num (VkBufferUsageBitmask FlagMask) Source # 
Ord (VkBufferUsageBitmask a) Source # 
Read (VkBufferUsageBitmask a) Source # 
Real (VkBufferUsageBitmask FlagMask) Source # 
Show (VkBufferUsageBitmask a) Source # 
Generic (VkBufferUsageBitmask a) Source # 
Storable (VkBufferUsageBitmask a) Source # 
Bits (VkBufferUsageBitmask FlagMask) Source # 

Methods

(.&.) :: VkBufferUsageBitmask FlagMask -> VkBufferUsageBitmask FlagMask -> VkBufferUsageBitmask FlagMask #

(.|.) :: VkBufferUsageBitmask FlagMask -> VkBufferUsageBitmask FlagMask -> VkBufferUsageBitmask FlagMask #

xor :: VkBufferUsageBitmask FlagMask -> VkBufferUsageBitmask FlagMask -> VkBufferUsageBitmask FlagMask #

complement :: VkBufferUsageBitmask FlagMask -> VkBufferUsageBitmask FlagMask #

shift :: VkBufferUsageBitmask FlagMask -> Int -> VkBufferUsageBitmask FlagMask #

rotate :: VkBufferUsageBitmask FlagMask -> Int -> VkBufferUsageBitmask FlagMask #

zeroBits :: VkBufferUsageBitmask FlagMask #

bit :: Int -> VkBufferUsageBitmask FlagMask #

setBit :: VkBufferUsageBitmask FlagMask -> Int -> VkBufferUsageBitmask FlagMask #

clearBit :: VkBufferUsageBitmask FlagMask -> Int -> VkBufferUsageBitmask FlagMask #

complementBit :: VkBufferUsageBitmask FlagMask -> Int -> VkBufferUsageBitmask FlagMask #

testBit :: VkBufferUsageBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkBufferUsageBitmask FlagMask -> Maybe Int #

bitSize :: VkBufferUsageBitmask FlagMask -> Int #

isSigned :: VkBufferUsageBitmask FlagMask -> Bool #

shiftL :: VkBufferUsageBitmask FlagMask -> Int -> VkBufferUsageBitmask FlagMask #

unsafeShiftL :: VkBufferUsageBitmask FlagMask -> Int -> VkBufferUsageBitmask FlagMask #

shiftR :: VkBufferUsageBitmask FlagMask -> Int -> VkBufferUsageBitmask FlagMask #

unsafeShiftR :: VkBufferUsageBitmask FlagMask -> Int -> VkBufferUsageBitmask FlagMask #

rotateL :: VkBufferUsageBitmask FlagMask -> Int -> VkBufferUsageBitmask FlagMask #

rotateR :: VkBufferUsageBitmask FlagMask -> Int -> VkBufferUsageBitmask FlagMask #

popCount :: VkBufferUsageBitmask FlagMask -> Int #

FiniteBits (VkBufferUsageBitmask FlagMask) Source # 
type Rep (VkBufferUsageBitmask a) Source # 
type Rep (VkBufferUsageBitmask a) = D1 (MetaData "VkBufferUsageBitmask" "Graphics.Vulkan.Types.Enum.Buffer" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkBufferUsageBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

pattern VK_BUFFER_USAGE_TRANSFER_SRC_BIT :: forall a. VkBufferUsageBitmask a Source #

Can be used as a source of transfer operations

bitpos = 0

pattern VK_BUFFER_USAGE_TRANSFER_DST_BIT :: forall a. VkBufferUsageBitmask a Source #

Can be used as a destination of transfer operations

bitpos = 1

pattern VK_BUFFER_USAGE_UNIFORM_TEXEL_BUFFER_BIT :: forall a. VkBufferUsageBitmask a Source #

Can be used as TBO

bitpos = 2

pattern VK_BUFFER_USAGE_STORAGE_TEXEL_BUFFER_BIT :: forall a. VkBufferUsageBitmask a Source #

Can be used as IBO

bitpos = 3

pattern VK_BUFFER_USAGE_UNIFORM_BUFFER_BIT :: forall a. VkBufferUsageBitmask a Source #

Can be used as UBO

bitpos = 4

pattern VK_BUFFER_USAGE_STORAGE_BUFFER_BIT :: forall a. VkBufferUsageBitmask a Source #

Can be used as SSBO

bitpos = 5

pattern VK_BUFFER_USAGE_INDEX_BUFFER_BIT :: forall a. VkBufferUsageBitmask a Source #

Can be used as source of fixed-function index fetch (index buffer)

bitpos = 6

pattern VK_BUFFER_USAGE_VERTEX_BUFFER_BIT :: forall a. VkBufferUsageBitmask a Source #

Can be used as source of fixed-function vertex fetch (VBO)

bitpos = 7

pattern VK_BUFFER_USAGE_INDIRECT_BUFFER_BIT :: forall a. VkBufferUsageBitmask a Source #

Can be the source of indirect parameters (e.g. indirect buffer, parameter buffer)

bitpos = 8

newtype VkBufferViewCreateFlagBits Source #

Instances

Bounded VkBufferViewCreateFlagBits Source # 
Enum VkBufferViewCreateFlagBits Source # 
Eq VkBufferViewCreateFlagBits Source # 
Integral VkBufferViewCreateFlagBits Source # 
Data VkBufferViewCreateFlagBits Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkBufferViewCreateFlagBits -> c VkBufferViewCreateFlagBits #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkBufferViewCreateFlagBits #

toConstr :: VkBufferViewCreateFlagBits -> Constr #

dataTypeOf :: VkBufferViewCreateFlagBits -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkBufferViewCreateFlagBits) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkBufferViewCreateFlagBits) #

gmapT :: (forall b. Data b => b -> b) -> VkBufferViewCreateFlagBits -> VkBufferViewCreateFlagBits #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkBufferViewCreateFlagBits -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkBufferViewCreateFlagBits -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkBufferViewCreateFlagBits -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkBufferViewCreateFlagBits -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkBufferViewCreateFlagBits -> m VkBufferViewCreateFlagBits #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkBufferViewCreateFlagBits -> m VkBufferViewCreateFlagBits #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkBufferViewCreateFlagBits -> m VkBufferViewCreateFlagBits #

Num VkBufferViewCreateFlagBits Source # 
Ord VkBufferViewCreateFlagBits Source # 
Read VkBufferViewCreateFlagBits Source # 
Real VkBufferViewCreateFlagBits Source # 
Show VkBufferViewCreateFlagBits Source # 
Generic VkBufferViewCreateFlagBits Source # 
Storable VkBufferViewCreateFlagBits Source # 
Bits VkBufferViewCreateFlagBits Source # 

Methods

(.&.) :: VkBufferViewCreateFlagBits -> VkBufferViewCreateFlagBits -> VkBufferViewCreateFlagBits #

(.|.) :: VkBufferViewCreateFlagBits -> VkBufferViewCreateFlagBits -> VkBufferViewCreateFlagBits #

xor :: VkBufferViewCreateFlagBits -> VkBufferViewCreateFlagBits -> VkBufferViewCreateFlagBits #

complement :: VkBufferViewCreateFlagBits -> VkBufferViewCreateFlagBits #

shift :: VkBufferViewCreateFlagBits -> Int -> VkBufferViewCreateFlagBits #

rotate :: VkBufferViewCreateFlagBits -> Int -> VkBufferViewCreateFlagBits #

zeroBits :: VkBufferViewCreateFlagBits #

bit :: Int -> VkBufferViewCreateFlagBits #

setBit :: VkBufferViewCreateFlagBits -> Int -> VkBufferViewCreateFlagBits #

clearBit :: VkBufferViewCreateFlagBits -> Int -> VkBufferViewCreateFlagBits #

complementBit :: VkBufferViewCreateFlagBits -> Int -> VkBufferViewCreateFlagBits #

testBit :: VkBufferViewCreateFlagBits -> Int -> Bool #

bitSizeMaybe :: VkBufferViewCreateFlagBits -> Maybe Int #

bitSize :: VkBufferViewCreateFlagBits -> Int #

isSigned :: VkBufferViewCreateFlagBits -> Bool #

shiftL :: VkBufferViewCreateFlagBits -> Int -> VkBufferViewCreateFlagBits #

unsafeShiftL :: VkBufferViewCreateFlagBits -> Int -> VkBufferViewCreateFlagBits #

shiftR :: VkBufferViewCreateFlagBits -> Int -> VkBufferViewCreateFlagBits #

unsafeShiftR :: VkBufferViewCreateFlagBits -> Int -> VkBufferViewCreateFlagBits #

rotateL :: VkBufferViewCreateFlagBits -> Int -> VkBufferViewCreateFlagBits #

rotateR :: VkBufferViewCreateFlagBits -> Int -> VkBufferViewCreateFlagBits #

popCount :: VkBufferViewCreateFlagBits -> Int #

FiniteBits VkBufferViewCreateFlagBits Source # 
type Rep VkBufferViewCreateFlagBits Source # 
type Rep VkBufferViewCreateFlagBits = D1 (MetaData "VkBufferViewCreateFlagBits" "Graphics.Vulkan.Types.Enum.Buffer" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkBufferViewCreateFlagBits" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

data VkExternalBufferProperties Source #

typedef struct VkExternalBufferProperties {
    VkStructureType sType;
    void*                            pNext;
    VkExternalMemoryProperties    externalMemoryProperties;
} VkExternalBufferProperties;

VkExternalBufferProperties registry at www.khronos.org

Instances

Eq VkExternalBufferProperties Source # 
Ord VkExternalBufferProperties Source # 
Show VkExternalBufferProperties Source # 
Storable VkExternalBufferProperties Source # 
VulkanMarshalPrim VkExternalBufferProperties Source # 
VulkanMarshal VkExternalBufferProperties Source # 
CanWriteField "externalMemoryProperties" VkExternalBufferProperties Source # 
CanWriteField "pNext" VkExternalBufferProperties Source # 
CanWriteField "sType" VkExternalBufferProperties Source # 
CanReadField "externalMemoryProperties" VkExternalBufferProperties Source # 
CanReadField "pNext" VkExternalBufferProperties Source # 
CanReadField "sType" VkExternalBufferProperties Source # 
HasField "externalMemoryProperties" VkExternalBufferProperties Source # 

Associated Types

type FieldType ("externalMemoryProperties" :: Symbol) VkExternalBufferProperties :: Type Source #

type FieldOptional ("externalMemoryProperties" :: Symbol) VkExternalBufferProperties :: Bool Source #

type FieldOffset ("externalMemoryProperties" :: Symbol) VkExternalBufferProperties :: Nat Source #

type FieldIsArray ("externalMemoryProperties" :: Symbol) VkExternalBufferProperties :: Bool Source #

HasField "pNext" VkExternalBufferProperties Source # 
HasField "sType" VkExternalBufferProperties Source # 
type StructFields VkExternalBufferProperties Source # 
type StructFields VkExternalBufferProperties = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "externalMemoryProperties" ([] Symbol)))
type CUnionType VkExternalBufferProperties Source # 
type ReturnedOnly VkExternalBufferProperties Source # 
type StructExtends VkExternalBufferProperties Source # 
type FieldType "externalMemoryProperties" VkExternalBufferProperties Source # 
type FieldType "pNext" VkExternalBufferProperties Source # 
type FieldType "sType" VkExternalBufferProperties Source # 
type FieldOptional "externalMemoryProperties" VkExternalBufferProperties Source # 
type FieldOptional "externalMemoryProperties" VkExternalBufferProperties = False
type FieldOptional "pNext" VkExternalBufferProperties Source # 
type FieldOptional "sType" VkExternalBufferProperties Source # 
type FieldOffset "externalMemoryProperties" VkExternalBufferProperties Source # 
type FieldOffset "externalMemoryProperties" VkExternalBufferProperties = 16
type FieldOffset "pNext" VkExternalBufferProperties Source # 
type FieldOffset "sType" VkExternalBufferProperties Source # 
type FieldIsArray "externalMemoryProperties" VkExternalBufferProperties Source # 
type FieldIsArray "externalMemoryProperties" VkExternalBufferProperties = False
type FieldIsArray "pNext" VkExternalBufferProperties Source # 
type FieldIsArray "sType" VkExternalBufferProperties Source # 

data VkExternalFenceProperties Source #

typedef struct VkExternalFenceProperties {
    VkStructureType sType;
    void*                            pNext;
    VkExternalFenceHandleTypeFlags exportFromImportedHandleTypes;
    VkExternalFenceHandleTypeFlags compatibleHandleTypes;
    VkExternalFenceFeatureFlags externalFenceFeatures;
} VkExternalFenceProperties;

VkExternalFenceProperties registry at www.khronos.org

Instances

Eq VkExternalFenceProperties Source # 
Ord VkExternalFenceProperties Source # 
Show VkExternalFenceProperties Source # 
Storable VkExternalFenceProperties Source # 
VulkanMarshalPrim VkExternalFenceProperties Source # 
VulkanMarshal VkExternalFenceProperties Source # 
CanWriteField "compatibleHandleTypes" VkExternalFenceProperties Source # 
CanWriteField "exportFromImportedHandleTypes" VkExternalFenceProperties Source # 

Methods

writeField :: Ptr VkExternalFenceProperties -> FieldType "exportFromImportedHandleTypes" VkExternalFenceProperties -> IO () Source #

CanWriteField "externalFenceFeatures" VkExternalFenceProperties Source # 
CanWriteField "pNext" VkExternalFenceProperties Source # 
CanWriteField "sType" VkExternalFenceProperties Source # 
CanReadField "compatibleHandleTypes" VkExternalFenceProperties Source # 
CanReadField "exportFromImportedHandleTypes" VkExternalFenceProperties Source # 
CanReadField "externalFenceFeatures" VkExternalFenceProperties Source # 
CanReadField "pNext" VkExternalFenceProperties Source # 
CanReadField "sType" VkExternalFenceProperties Source # 
HasField "compatibleHandleTypes" VkExternalFenceProperties Source # 

Associated Types

type FieldType ("compatibleHandleTypes" :: Symbol) VkExternalFenceProperties :: Type Source #

type FieldOptional ("compatibleHandleTypes" :: Symbol) VkExternalFenceProperties :: Bool Source #

type FieldOffset ("compatibleHandleTypes" :: Symbol) VkExternalFenceProperties :: Nat Source #

type FieldIsArray ("compatibleHandleTypes" :: Symbol) VkExternalFenceProperties :: Bool Source #

HasField "exportFromImportedHandleTypes" VkExternalFenceProperties Source # 

Associated Types

type FieldType ("exportFromImportedHandleTypes" :: Symbol) VkExternalFenceProperties :: Type Source #

type FieldOptional ("exportFromImportedHandleTypes" :: Symbol) VkExternalFenceProperties :: Bool Source #

type FieldOffset ("exportFromImportedHandleTypes" :: Symbol) VkExternalFenceProperties :: Nat Source #

type FieldIsArray ("exportFromImportedHandleTypes" :: Symbol) VkExternalFenceProperties :: Bool Source #

HasField "externalFenceFeatures" VkExternalFenceProperties Source # 

Associated Types

type FieldType ("externalFenceFeatures" :: Symbol) VkExternalFenceProperties :: Type Source #

type FieldOptional ("externalFenceFeatures" :: Symbol) VkExternalFenceProperties :: Bool Source #

type FieldOffset ("externalFenceFeatures" :: Symbol) VkExternalFenceProperties :: Nat Source #

type FieldIsArray ("externalFenceFeatures" :: Symbol) VkExternalFenceProperties :: Bool Source #

HasField "pNext" VkExternalFenceProperties Source # 
HasField "sType" VkExternalFenceProperties Source # 
type StructFields VkExternalFenceProperties Source # 
type StructFields VkExternalFenceProperties = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "exportFromImportedHandleTypes" ((:) Symbol "compatibleHandleTypes" ((:) Symbol "externalFenceFeatures" ([] Symbol)))))
type CUnionType VkExternalFenceProperties Source # 
type ReturnedOnly VkExternalFenceProperties Source # 
type StructExtends VkExternalFenceProperties Source # 
type FieldType "compatibleHandleTypes" VkExternalFenceProperties Source # 
type FieldType "exportFromImportedHandleTypes" VkExternalFenceProperties Source # 
type FieldType "externalFenceFeatures" VkExternalFenceProperties Source # 
type FieldType "pNext" VkExternalFenceProperties Source # 
type FieldType "sType" VkExternalFenceProperties Source # 
type FieldOptional "compatibleHandleTypes" VkExternalFenceProperties Source # 
type FieldOptional "compatibleHandleTypes" VkExternalFenceProperties = False
type FieldOptional "exportFromImportedHandleTypes" VkExternalFenceProperties Source # 
type FieldOptional "exportFromImportedHandleTypes" VkExternalFenceProperties = False
type FieldOptional "externalFenceFeatures" VkExternalFenceProperties Source # 
type FieldOptional "externalFenceFeatures" VkExternalFenceProperties = True
type FieldOptional "pNext" VkExternalFenceProperties Source # 
type FieldOptional "sType" VkExternalFenceProperties Source # 
type FieldOffset "compatibleHandleTypes" VkExternalFenceProperties Source # 
type FieldOffset "compatibleHandleTypes" VkExternalFenceProperties = 20
type FieldOffset "exportFromImportedHandleTypes" VkExternalFenceProperties Source # 
type FieldOffset "exportFromImportedHandleTypes" VkExternalFenceProperties = 16
type FieldOffset "externalFenceFeatures" VkExternalFenceProperties Source # 
type FieldOffset "externalFenceFeatures" VkExternalFenceProperties = 24
type FieldOffset "pNext" VkExternalFenceProperties Source # 
type FieldOffset "sType" VkExternalFenceProperties Source # 
type FieldIsArray "compatibleHandleTypes" VkExternalFenceProperties Source # 
type FieldIsArray "compatibleHandleTypes" VkExternalFenceProperties = False
type FieldIsArray "exportFromImportedHandleTypes" VkExternalFenceProperties Source # 
type FieldIsArray "exportFromImportedHandleTypes" VkExternalFenceProperties = False
type FieldIsArray "externalFenceFeatures" VkExternalFenceProperties Source # 
type FieldIsArray "externalFenceFeatures" VkExternalFenceProperties = False
type FieldIsArray "pNext" VkExternalFenceProperties Source # 
type FieldIsArray "sType" VkExternalFenceProperties Source # 

data VkExternalImageFormatProperties Source #

typedef struct VkExternalImageFormatProperties {
    VkStructureType sType;
    void*                            pNext;
    VkExternalMemoryProperties externalMemoryProperties;
} VkExternalImageFormatProperties;

VkExternalImageFormatProperties registry at www.khronos.org

Instances

Eq VkExternalImageFormatProperties Source # 
Ord VkExternalImageFormatProperties Source # 
Show VkExternalImageFormatProperties Source # 
Storable VkExternalImageFormatProperties Source # 
VulkanMarshalPrim VkExternalImageFormatProperties Source # 
VulkanMarshal VkExternalImageFormatProperties Source # 
CanWriteField "externalMemoryProperties" VkExternalImageFormatProperties Source # 
CanWriteField "pNext" VkExternalImageFormatProperties Source # 
CanWriteField "sType" VkExternalImageFormatProperties Source # 
CanReadField "externalMemoryProperties" VkExternalImageFormatProperties Source # 
CanReadField "pNext" VkExternalImageFormatProperties Source # 
CanReadField "sType" VkExternalImageFormatProperties Source # 
HasField "externalMemoryProperties" VkExternalImageFormatProperties Source # 

Associated Types

type FieldType ("externalMemoryProperties" :: Symbol) VkExternalImageFormatProperties :: Type Source #

type FieldOptional ("externalMemoryProperties" :: Symbol) VkExternalImageFormatProperties :: Bool Source #

type FieldOffset ("externalMemoryProperties" :: Symbol) VkExternalImageFormatProperties :: Nat Source #

type FieldIsArray ("externalMemoryProperties" :: Symbol) VkExternalImageFormatProperties :: Bool Source #

HasField "pNext" VkExternalImageFormatProperties Source # 
HasField "sType" VkExternalImageFormatProperties Source # 
type StructFields VkExternalImageFormatProperties Source # 
type StructFields VkExternalImageFormatProperties = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "externalMemoryProperties" ([] Symbol)))
type CUnionType VkExternalImageFormatProperties Source # 
type ReturnedOnly VkExternalImageFormatProperties Source # 
type StructExtends VkExternalImageFormatProperties Source # 
type FieldType "externalMemoryProperties" VkExternalImageFormatProperties Source # 
type FieldType "pNext" VkExternalImageFormatProperties Source # 
type FieldType "sType" VkExternalImageFormatProperties Source # 
type FieldOptional "externalMemoryProperties" VkExternalImageFormatProperties Source # 
type FieldOptional "externalMemoryProperties" VkExternalImageFormatProperties = False
type FieldOptional "pNext" VkExternalImageFormatProperties Source # 
type FieldOptional "sType" VkExternalImageFormatProperties Source # 
type FieldOffset "externalMemoryProperties" VkExternalImageFormatProperties Source # 
type FieldOffset "externalMemoryProperties" VkExternalImageFormatProperties = 16
type FieldOffset "pNext" VkExternalImageFormatProperties Source # 
type FieldOffset "sType" VkExternalImageFormatProperties Source # 
type FieldIsArray "externalMemoryProperties" VkExternalImageFormatProperties Source # 
type FieldIsArray "externalMemoryProperties" VkExternalImageFormatProperties = False
type FieldIsArray "pNext" VkExternalImageFormatProperties Source # 
type FieldIsArray "sType" VkExternalImageFormatProperties Source # 

data VkExternalImageFormatPropertiesNV Source #

typedef struct VkExternalImageFormatPropertiesNV {
    VkImageFormatProperties          imageFormatProperties;
    VkExternalMemoryFeatureFlagsNV   externalMemoryFeatures;
    VkExternalMemoryHandleTypeFlagsNV exportFromImportedHandleTypes;
    VkExternalMemoryHandleTypeFlagsNV compatibleHandleTypes;
} VkExternalImageFormatPropertiesNV;

VkExternalImageFormatPropertiesNV registry at www.khronos.org

Instances

Eq VkExternalImageFormatPropertiesNV Source # 
Ord VkExternalImageFormatPropertiesNV Source # 
Show VkExternalImageFormatPropertiesNV Source # 
Storable VkExternalImageFormatPropertiesNV Source # 
VulkanMarshalPrim VkExternalImageFormatPropertiesNV Source # 
VulkanMarshal VkExternalImageFormatPropertiesNV Source # 
CanWriteField "compatibleHandleTypes" VkExternalImageFormatPropertiesNV Source # 
CanWriteField "exportFromImportedHandleTypes" VkExternalImageFormatPropertiesNV Source # 
CanWriteField "externalMemoryFeatures" VkExternalImageFormatPropertiesNV Source # 
CanWriteField "imageFormatProperties" VkExternalImageFormatPropertiesNV Source # 
CanReadField "compatibleHandleTypes" VkExternalImageFormatPropertiesNV Source # 
CanReadField "exportFromImportedHandleTypes" VkExternalImageFormatPropertiesNV Source # 
CanReadField "externalMemoryFeatures" VkExternalImageFormatPropertiesNV Source # 
CanReadField "imageFormatProperties" VkExternalImageFormatPropertiesNV Source # 
HasField "compatibleHandleTypes" VkExternalImageFormatPropertiesNV Source # 

Associated Types

type FieldType ("compatibleHandleTypes" :: Symbol) VkExternalImageFormatPropertiesNV :: Type Source #

type FieldOptional ("compatibleHandleTypes" :: Symbol) VkExternalImageFormatPropertiesNV :: Bool Source #

type FieldOffset ("compatibleHandleTypes" :: Symbol) VkExternalImageFormatPropertiesNV :: Nat Source #

type FieldIsArray ("compatibleHandleTypes" :: Symbol) VkExternalImageFormatPropertiesNV :: Bool Source #

HasField "exportFromImportedHandleTypes" VkExternalImageFormatPropertiesNV Source # 

Associated Types

type FieldType ("exportFromImportedHandleTypes" :: Symbol) VkExternalImageFormatPropertiesNV :: Type Source #

type FieldOptional ("exportFromImportedHandleTypes" :: Symbol) VkExternalImageFormatPropertiesNV :: Bool Source #

type FieldOffset ("exportFromImportedHandleTypes" :: Symbol) VkExternalImageFormatPropertiesNV :: Nat Source #

type FieldIsArray ("exportFromImportedHandleTypes" :: Symbol) VkExternalImageFormatPropertiesNV :: Bool Source #

HasField "externalMemoryFeatures" VkExternalImageFormatPropertiesNV Source # 

Associated Types

type FieldType ("externalMemoryFeatures" :: Symbol) VkExternalImageFormatPropertiesNV :: Type Source #

type FieldOptional ("externalMemoryFeatures" :: Symbol) VkExternalImageFormatPropertiesNV :: Bool Source #

type FieldOffset ("externalMemoryFeatures" :: Symbol) VkExternalImageFormatPropertiesNV :: Nat Source #

type FieldIsArray ("externalMemoryFeatures" :: Symbol) VkExternalImageFormatPropertiesNV :: Bool Source #

HasField "imageFormatProperties" VkExternalImageFormatPropertiesNV Source # 

Associated Types

type FieldType ("imageFormatProperties" :: Symbol) VkExternalImageFormatPropertiesNV :: Type Source #

type FieldOptional ("imageFormatProperties" :: Symbol) VkExternalImageFormatPropertiesNV :: Bool Source #

type FieldOffset ("imageFormatProperties" :: Symbol) VkExternalImageFormatPropertiesNV :: Nat Source #

type FieldIsArray ("imageFormatProperties" :: Symbol) VkExternalImageFormatPropertiesNV :: Bool Source #

type StructFields VkExternalImageFormatPropertiesNV Source # 
type StructFields VkExternalImageFormatPropertiesNV = (:) Symbol "imageFormatProperties" ((:) Symbol "externalMemoryFeatures" ((:) Symbol "exportFromImportedHandleTypes" ((:) Symbol "compatibleHandleTypes" ([] Symbol))))
type CUnionType VkExternalImageFormatPropertiesNV Source # 
type ReturnedOnly VkExternalImageFormatPropertiesNV Source # 
type StructExtends VkExternalImageFormatPropertiesNV Source # 
type FieldType "compatibleHandleTypes" VkExternalImageFormatPropertiesNV Source # 
type FieldType "exportFromImportedHandleTypes" VkExternalImageFormatPropertiesNV Source # 
type FieldType "externalMemoryFeatures" VkExternalImageFormatPropertiesNV Source # 
type FieldType "imageFormatProperties" VkExternalImageFormatPropertiesNV Source # 
type FieldOptional "compatibleHandleTypes" VkExternalImageFormatPropertiesNV Source # 
type FieldOptional "exportFromImportedHandleTypes" VkExternalImageFormatPropertiesNV Source # 
type FieldOptional "exportFromImportedHandleTypes" VkExternalImageFormatPropertiesNV = True
type FieldOptional "externalMemoryFeatures" VkExternalImageFormatPropertiesNV Source # 
type FieldOptional "externalMemoryFeatures" VkExternalImageFormatPropertiesNV = True
type FieldOptional "imageFormatProperties" VkExternalImageFormatPropertiesNV Source # 
type FieldOffset "compatibleHandleTypes" VkExternalImageFormatPropertiesNV Source # 
type FieldOffset "compatibleHandleTypes" VkExternalImageFormatPropertiesNV = 40
type FieldOffset "exportFromImportedHandleTypes" VkExternalImageFormatPropertiesNV Source # 
type FieldOffset "exportFromImportedHandleTypes" VkExternalImageFormatPropertiesNV = 36
type FieldOffset "externalMemoryFeatures" VkExternalImageFormatPropertiesNV Source # 
type FieldOffset "externalMemoryFeatures" VkExternalImageFormatPropertiesNV = 32
type FieldOffset "imageFormatProperties" VkExternalImageFormatPropertiesNV Source # 
type FieldOffset "imageFormatProperties" VkExternalImageFormatPropertiesNV = 0
type FieldIsArray "compatibleHandleTypes" VkExternalImageFormatPropertiesNV Source # 
type FieldIsArray "exportFromImportedHandleTypes" VkExternalImageFormatPropertiesNV Source # 
type FieldIsArray "exportFromImportedHandleTypes" VkExternalImageFormatPropertiesNV = False
type FieldIsArray "externalMemoryFeatures" VkExternalImageFormatPropertiesNV Source # 
type FieldIsArray "externalMemoryFeatures" VkExternalImageFormatPropertiesNV = False
type FieldIsArray "imageFormatProperties" VkExternalImageFormatPropertiesNV Source # 

data VkExternalMemoryBufferCreateInfo Source #

typedef struct VkExternalMemoryBufferCreateInfo {
    VkStructureType sType;
    const void*                      pNext;
    VkExternalMemoryHandleTypeFlags handleTypes;
} VkExternalMemoryBufferCreateInfo;

VkExternalMemoryBufferCreateInfo registry at www.khronos.org

Instances

Eq VkExternalMemoryBufferCreateInfo Source # 
Ord VkExternalMemoryBufferCreateInfo Source # 
Show VkExternalMemoryBufferCreateInfo Source # 
Storable VkExternalMemoryBufferCreateInfo Source # 
VulkanMarshalPrim VkExternalMemoryBufferCreateInfo Source # 
VulkanMarshal VkExternalMemoryBufferCreateInfo Source # 
CanWriteField "handleTypes" VkExternalMemoryBufferCreateInfo Source # 
CanWriteField "pNext" VkExternalMemoryBufferCreateInfo Source # 
CanWriteField "sType" VkExternalMemoryBufferCreateInfo Source # 
CanReadField "handleTypes" VkExternalMemoryBufferCreateInfo Source # 
CanReadField "pNext" VkExternalMemoryBufferCreateInfo Source # 
CanReadField "sType" VkExternalMemoryBufferCreateInfo Source # 
HasField "handleTypes" VkExternalMemoryBufferCreateInfo Source # 
HasField "pNext" VkExternalMemoryBufferCreateInfo Source # 
HasField "sType" VkExternalMemoryBufferCreateInfo Source # 
type StructFields VkExternalMemoryBufferCreateInfo Source # 
type StructFields VkExternalMemoryBufferCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "handleTypes" ([] Symbol)))
type CUnionType VkExternalMemoryBufferCreateInfo Source # 
type ReturnedOnly VkExternalMemoryBufferCreateInfo Source # 
type StructExtends VkExternalMemoryBufferCreateInfo Source # 
type FieldType "handleTypes" VkExternalMemoryBufferCreateInfo Source # 
type FieldType "pNext" VkExternalMemoryBufferCreateInfo Source # 
type FieldType "sType" VkExternalMemoryBufferCreateInfo Source # 
type FieldOptional "handleTypes" VkExternalMemoryBufferCreateInfo Source # 
type FieldOptional "pNext" VkExternalMemoryBufferCreateInfo Source # 
type FieldOptional "sType" VkExternalMemoryBufferCreateInfo Source # 
type FieldOffset "handleTypes" VkExternalMemoryBufferCreateInfo Source # 
type FieldOffset "pNext" VkExternalMemoryBufferCreateInfo Source # 
type FieldOffset "sType" VkExternalMemoryBufferCreateInfo Source # 
type FieldIsArray "handleTypes" VkExternalMemoryBufferCreateInfo Source # 
type FieldIsArray "pNext" VkExternalMemoryBufferCreateInfo Source # 
type FieldIsArray "sType" VkExternalMemoryBufferCreateInfo Source # 

data VkExternalMemoryImageCreateInfo Source #

typedef struct VkExternalMemoryImageCreateInfo {
    VkStructureType sType;
    const void*                      pNext;
    VkExternalMemoryHandleTypeFlags handleTypes;
} VkExternalMemoryImageCreateInfo;

VkExternalMemoryImageCreateInfo registry at www.khronos.org

Instances

Eq VkExternalMemoryImageCreateInfo Source # 
Ord VkExternalMemoryImageCreateInfo Source # 
Show VkExternalMemoryImageCreateInfo Source # 
Storable VkExternalMemoryImageCreateInfo Source # 
VulkanMarshalPrim VkExternalMemoryImageCreateInfo Source # 
VulkanMarshal VkExternalMemoryImageCreateInfo Source # 
CanWriteField "handleTypes" VkExternalMemoryImageCreateInfo Source # 
CanWriteField "pNext" VkExternalMemoryImageCreateInfo Source # 
CanWriteField "sType" VkExternalMemoryImageCreateInfo Source # 
CanReadField "handleTypes" VkExternalMemoryImageCreateInfo Source # 
CanReadField "pNext" VkExternalMemoryImageCreateInfo Source # 
CanReadField "sType" VkExternalMemoryImageCreateInfo Source # 
HasField "handleTypes" VkExternalMemoryImageCreateInfo Source # 
HasField "pNext" VkExternalMemoryImageCreateInfo Source # 
HasField "sType" VkExternalMemoryImageCreateInfo Source # 
type StructFields VkExternalMemoryImageCreateInfo Source # 
type StructFields VkExternalMemoryImageCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "handleTypes" ([] Symbol)))
type CUnionType VkExternalMemoryImageCreateInfo Source # 
type ReturnedOnly VkExternalMemoryImageCreateInfo Source # 
type StructExtends VkExternalMemoryImageCreateInfo Source # 
type FieldType "handleTypes" VkExternalMemoryImageCreateInfo Source # 
type FieldType "pNext" VkExternalMemoryImageCreateInfo Source # 
type FieldType "sType" VkExternalMemoryImageCreateInfo Source # 
type FieldOptional "handleTypes" VkExternalMemoryImageCreateInfo Source # 
type FieldOptional "pNext" VkExternalMemoryImageCreateInfo Source # 
type FieldOptional "sType" VkExternalMemoryImageCreateInfo Source # 
type FieldOffset "handleTypes" VkExternalMemoryImageCreateInfo Source # 
type FieldOffset "pNext" VkExternalMemoryImageCreateInfo Source # 
type FieldOffset "sType" VkExternalMemoryImageCreateInfo Source # 
type FieldIsArray "handleTypes" VkExternalMemoryImageCreateInfo Source # 
type FieldIsArray "pNext" VkExternalMemoryImageCreateInfo Source # 
type FieldIsArray "sType" VkExternalMemoryImageCreateInfo Source # 

data VkExternalMemoryImageCreateInfoNV Source #

typedef struct VkExternalMemoryImageCreateInfoNV {
    VkStructureType sType;
    const void*                      pNext;
    VkExternalMemoryHandleTypeFlagsNV handleTypes;
} VkExternalMemoryImageCreateInfoNV;

VkExternalMemoryImageCreateInfoNV registry at www.khronos.org

Instances

Eq VkExternalMemoryImageCreateInfoNV Source # 
Ord VkExternalMemoryImageCreateInfoNV Source # 
Show VkExternalMemoryImageCreateInfoNV Source # 
Storable VkExternalMemoryImageCreateInfoNV Source # 
VulkanMarshalPrim VkExternalMemoryImageCreateInfoNV Source # 
VulkanMarshal VkExternalMemoryImageCreateInfoNV Source # 
CanWriteField "handleTypes" VkExternalMemoryImageCreateInfoNV Source # 
CanWriteField "pNext" VkExternalMemoryImageCreateInfoNV Source # 
CanWriteField "sType" VkExternalMemoryImageCreateInfoNV Source # 
CanReadField "handleTypes" VkExternalMemoryImageCreateInfoNV Source # 
CanReadField "pNext" VkExternalMemoryImageCreateInfoNV Source # 
CanReadField "sType" VkExternalMemoryImageCreateInfoNV Source # 
HasField "handleTypes" VkExternalMemoryImageCreateInfoNV Source # 
HasField "pNext" VkExternalMemoryImageCreateInfoNV Source # 
HasField "sType" VkExternalMemoryImageCreateInfoNV Source # 
type StructFields VkExternalMemoryImageCreateInfoNV Source # 
type StructFields VkExternalMemoryImageCreateInfoNV = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "handleTypes" ([] Symbol)))
type CUnionType VkExternalMemoryImageCreateInfoNV Source # 
type ReturnedOnly VkExternalMemoryImageCreateInfoNV Source # 
type StructExtends VkExternalMemoryImageCreateInfoNV Source # 
type FieldType "handleTypes" VkExternalMemoryImageCreateInfoNV Source # 
type FieldType "pNext" VkExternalMemoryImageCreateInfoNV Source # 
type FieldType "sType" VkExternalMemoryImageCreateInfoNV Source # 
type FieldOptional "handleTypes" VkExternalMemoryImageCreateInfoNV Source # 
type FieldOptional "pNext" VkExternalMemoryImageCreateInfoNV Source # 
type FieldOptional "sType" VkExternalMemoryImageCreateInfoNV Source # 
type FieldOffset "handleTypes" VkExternalMemoryImageCreateInfoNV Source # 
type FieldOffset "pNext" VkExternalMemoryImageCreateInfoNV Source # 
type FieldOffset "sType" VkExternalMemoryImageCreateInfoNV Source # 
type FieldIsArray "handleTypes" VkExternalMemoryImageCreateInfoNV Source # 
type FieldIsArray "pNext" VkExternalMemoryImageCreateInfoNV Source # 
type FieldIsArray "sType" VkExternalMemoryImageCreateInfoNV Source # 

data VkExternalMemoryProperties Source #

typedef struct VkExternalMemoryProperties {
    VkExternalMemoryFeatureFlags  externalMemoryFeatures;
    VkExternalMemoryHandleTypeFlags exportFromImportedHandleTypes;
    VkExternalMemoryHandleTypeFlags compatibleHandleTypes;
} VkExternalMemoryProperties;

VkExternalMemoryProperties registry at www.khronos.org

Instances

Eq VkExternalMemoryProperties Source # 
Ord VkExternalMemoryProperties Source # 
Show VkExternalMemoryProperties Source # 
Storable VkExternalMemoryProperties Source # 
VulkanMarshalPrim VkExternalMemoryProperties Source # 
VulkanMarshal VkExternalMemoryProperties Source # 
CanWriteField "compatibleHandleTypes" VkExternalMemoryProperties Source # 
CanWriteField "exportFromImportedHandleTypes" VkExternalMemoryProperties Source # 

Methods

writeField :: Ptr VkExternalMemoryProperties -> FieldType "exportFromImportedHandleTypes" VkExternalMemoryProperties -> IO () Source #

CanWriteField "externalMemoryFeatures" VkExternalMemoryProperties Source # 
CanReadField "compatibleHandleTypes" VkExternalMemoryProperties Source # 
CanReadField "exportFromImportedHandleTypes" VkExternalMemoryProperties Source # 
CanReadField "externalMemoryFeatures" VkExternalMemoryProperties Source # 
HasField "compatibleHandleTypes" VkExternalMemoryProperties Source # 

Associated Types

type FieldType ("compatibleHandleTypes" :: Symbol) VkExternalMemoryProperties :: Type Source #

type FieldOptional ("compatibleHandleTypes" :: Symbol) VkExternalMemoryProperties :: Bool Source #

type FieldOffset ("compatibleHandleTypes" :: Symbol) VkExternalMemoryProperties :: Nat Source #

type FieldIsArray ("compatibleHandleTypes" :: Symbol) VkExternalMemoryProperties :: Bool Source #

HasField "exportFromImportedHandleTypes" VkExternalMemoryProperties Source # 

Associated Types

type FieldType ("exportFromImportedHandleTypes" :: Symbol) VkExternalMemoryProperties :: Type Source #

type FieldOptional ("exportFromImportedHandleTypes" :: Symbol) VkExternalMemoryProperties :: Bool Source #

type FieldOffset ("exportFromImportedHandleTypes" :: Symbol) VkExternalMemoryProperties :: Nat Source #

type FieldIsArray ("exportFromImportedHandleTypes" :: Symbol) VkExternalMemoryProperties :: Bool Source #

HasField "externalMemoryFeatures" VkExternalMemoryProperties Source # 

Associated Types

type FieldType ("externalMemoryFeatures" :: Symbol) VkExternalMemoryProperties :: Type Source #

type FieldOptional ("externalMemoryFeatures" :: Symbol) VkExternalMemoryProperties :: Bool Source #

type FieldOffset ("externalMemoryFeatures" :: Symbol) VkExternalMemoryProperties :: Nat Source #

type FieldIsArray ("externalMemoryFeatures" :: Symbol) VkExternalMemoryProperties :: Bool Source #

type StructFields VkExternalMemoryProperties Source # 
type StructFields VkExternalMemoryProperties = (:) Symbol "externalMemoryFeatures" ((:) Symbol "exportFromImportedHandleTypes" ((:) Symbol "compatibleHandleTypes" ([] Symbol)))
type CUnionType VkExternalMemoryProperties Source # 
type ReturnedOnly VkExternalMemoryProperties Source # 
type StructExtends VkExternalMemoryProperties Source # 
type FieldType "compatibleHandleTypes" VkExternalMemoryProperties Source # 
type FieldType "exportFromImportedHandleTypes" VkExternalMemoryProperties Source # 
type FieldType "externalMemoryFeatures" VkExternalMemoryProperties Source # 
type FieldOptional "compatibleHandleTypes" VkExternalMemoryProperties Source # 
type FieldOptional "compatibleHandleTypes" VkExternalMemoryProperties = False
type FieldOptional "exportFromImportedHandleTypes" VkExternalMemoryProperties Source # 
type FieldOptional "exportFromImportedHandleTypes" VkExternalMemoryProperties = True
type FieldOptional "externalMemoryFeatures" VkExternalMemoryProperties Source # 
type FieldOptional "externalMemoryFeatures" VkExternalMemoryProperties = False
type FieldOffset "compatibleHandleTypes" VkExternalMemoryProperties Source # 
type FieldOffset "compatibleHandleTypes" VkExternalMemoryProperties = 8
type FieldOffset "exportFromImportedHandleTypes" VkExternalMemoryProperties Source # 
type FieldOffset "exportFromImportedHandleTypes" VkExternalMemoryProperties = 4
type FieldOffset "externalMemoryFeatures" VkExternalMemoryProperties Source # 
type FieldOffset "externalMemoryFeatures" VkExternalMemoryProperties = 0
type FieldIsArray "compatibleHandleTypes" VkExternalMemoryProperties Source # 
type FieldIsArray "compatibleHandleTypes" VkExternalMemoryProperties = False
type FieldIsArray "exportFromImportedHandleTypes" VkExternalMemoryProperties Source # 
type FieldIsArray "exportFromImportedHandleTypes" VkExternalMemoryProperties = False
type FieldIsArray "externalMemoryFeatures" VkExternalMemoryProperties Source # 
type FieldIsArray "externalMemoryFeatures" VkExternalMemoryProperties = False

data VkExternalSemaphoreProperties Source #

typedef struct VkExternalSemaphoreProperties {
    VkStructureType sType;
    void*                            pNext;
    VkExternalSemaphoreHandleTypeFlags exportFromImportedHandleTypes;
    VkExternalSemaphoreHandleTypeFlags compatibleHandleTypes;
    VkExternalSemaphoreFeatureFlags externalSemaphoreFeatures;
} VkExternalSemaphoreProperties;

VkExternalSemaphoreProperties registry at www.khronos.org

Instances

Eq VkExternalSemaphoreProperties Source # 
Ord VkExternalSemaphoreProperties Source # 
Show VkExternalSemaphoreProperties Source # 
Storable VkExternalSemaphoreProperties Source # 
VulkanMarshalPrim VkExternalSemaphoreProperties Source # 
VulkanMarshal VkExternalSemaphoreProperties Source # 
CanWriteField "compatibleHandleTypes" VkExternalSemaphoreProperties Source # 
CanWriteField "exportFromImportedHandleTypes" VkExternalSemaphoreProperties Source # 
CanWriteField "externalSemaphoreFeatures" VkExternalSemaphoreProperties Source # 
CanWriteField "pNext" VkExternalSemaphoreProperties Source # 
CanWriteField "sType" VkExternalSemaphoreProperties Source # 
CanReadField "compatibleHandleTypes" VkExternalSemaphoreProperties Source # 
CanReadField "exportFromImportedHandleTypes" VkExternalSemaphoreProperties Source # 
CanReadField "externalSemaphoreFeatures" VkExternalSemaphoreProperties Source # 
CanReadField "pNext" VkExternalSemaphoreProperties Source # 
CanReadField "sType" VkExternalSemaphoreProperties Source # 
HasField "compatibleHandleTypes" VkExternalSemaphoreProperties Source # 

Associated Types

type FieldType ("compatibleHandleTypes" :: Symbol) VkExternalSemaphoreProperties :: Type Source #

type FieldOptional ("compatibleHandleTypes" :: Symbol) VkExternalSemaphoreProperties :: Bool Source #

type FieldOffset ("compatibleHandleTypes" :: Symbol) VkExternalSemaphoreProperties :: Nat Source #

type FieldIsArray ("compatibleHandleTypes" :: Symbol) VkExternalSemaphoreProperties :: Bool Source #

HasField "exportFromImportedHandleTypes" VkExternalSemaphoreProperties Source # 

Associated Types

type FieldType ("exportFromImportedHandleTypes" :: Symbol) VkExternalSemaphoreProperties :: Type Source #

type FieldOptional ("exportFromImportedHandleTypes" :: Symbol) VkExternalSemaphoreProperties :: Bool Source #

type FieldOffset ("exportFromImportedHandleTypes" :: Symbol) VkExternalSemaphoreProperties :: Nat Source #

type FieldIsArray ("exportFromImportedHandleTypes" :: Symbol) VkExternalSemaphoreProperties :: Bool Source #

HasField "externalSemaphoreFeatures" VkExternalSemaphoreProperties Source # 

Associated Types

type FieldType ("externalSemaphoreFeatures" :: Symbol) VkExternalSemaphoreProperties :: Type Source #

type FieldOptional ("externalSemaphoreFeatures" :: Symbol) VkExternalSemaphoreProperties :: Bool Source #

type FieldOffset ("externalSemaphoreFeatures" :: Symbol) VkExternalSemaphoreProperties :: Nat Source #

type FieldIsArray ("externalSemaphoreFeatures" :: Symbol) VkExternalSemaphoreProperties :: Bool Source #

HasField "pNext" VkExternalSemaphoreProperties Source # 
HasField "sType" VkExternalSemaphoreProperties Source # 
type StructFields VkExternalSemaphoreProperties Source # 
type StructFields VkExternalSemaphoreProperties = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "exportFromImportedHandleTypes" ((:) Symbol "compatibleHandleTypes" ((:) Symbol "externalSemaphoreFeatures" ([] Symbol)))))
type CUnionType VkExternalSemaphoreProperties Source # 
type ReturnedOnly VkExternalSemaphoreProperties Source # 
type StructExtends VkExternalSemaphoreProperties Source # 
type FieldType "compatibleHandleTypes" VkExternalSemaphoreProperties Source # 
type FieldType "exportFromImportedHandleTypes" VkExternalSemaphoreProperties Source # 
type FieldType "externalSemaphoreFeatures" VkExternalSemaphoreProperties Source # 
type FieldType "pNext" VkExternalSemaphoreProperties Source # 
type FieldType "sType" VkExternalSemaphoreProperties Source # 
type FieldOptional "compatibleHandleTypes" VkExternalSemaphoreProperties Source # 
type FieldOptional "compatibleHandleTypes" VkExternalSemaphoreProperties = False
type FieldOptional "exportFromImportedHandleTypes" VkExternalSemaphoreProperties Source # 
type FieldOptional "exportFromImportedHandleTypes" VkExternalSemaphoreProperties = False
type FieldOptional "externalSemaphoreFeatures" VkExternalSemaphoreProperties Source # 
type FieldOptional "externalSemaphoreFeatures" VkExternalSemaphoreProperties = True
type FieldOptional "pNext" VkExternalSemaphoreProperties Source # 
type FieldOptional "sType" VkExternalSemaphoreProperties Source # 
type FieldOffset "compatibleHandleTypes" VkExternalSemaphoreProperties Source # 
type FieldOffset "compatibleHandleTypes" VkExternalSemaphoreProperties = 20
type FieldOffset "exportFromImportedHandleTypes" VkExternalSemaphoreProperties Source # 
type FieldOffset "exportFromImportedHandleTypes" VkExternalSemaphoreProperties = 16
type FieldOffset "externalSemaphoreFeatures" VkExternalSemaphoreProperties Source # 
type FieldOffset "externalSemaphoreFeatures" VkExternalSemaphoreProperties = 24
type FieldOffset "pNext" VkExternalSemaphoreProperties Source # 
type FieldOffset "sType" VkExternalSemaphoreProperties Source # 
type FieldIsArray "compatibleHandleTypes" VkExternalSemaphoreProperties Source # 
type FieldIsArray "compatibleHandleTypes" VkExternalSemaphoreProperties = False
type FieldIsArray "exportFromImportedHandleTypes" VkExternalSemaphoreProperties Source # 
type FieldIsArray "exportFromImportedHandleTypes" VkExternalSemaphoreProperties = False
type FieldIsArray "externalSemaphoreFeatures" VkExternalSemaphoreProperties Source # 
type FieldIsArray "externalSemaphoreFeatures" VkExternalSemaphoreProperties = False
type FieldIsArray "pNext" VkExternalSemaphoreProperties Source # 
type FieldIsArray "sType" VkExternalSemaphoreProperties Source # 

newtype VkExternalFenceFeatureFlagBitsKHR Source #

Instances

Bounded VkExternalFenceFeatureFlagBitsKHR Source # 
Enum VkExternalFenceFeatureFlagBitsKHR Source # 
Eq VkExternalFenceFeatureFlagBitsKHR Source # 
Integral VkExternalFenceFeatureFlagBitsKHR Source # 
Data VkExternalFenceFeatureFlagBitsKHR Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkExternalFenceFeatureFlagBitsKHR -> c VkExternalFenceFeatureFlagBitsKHR #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkExternalFenceFeatureFlagBitsKHR #

toConstr :: VkExternalFenceFeatureFlagBitsKHR -> Constr #

dataTypeOf :: VkExternalFenceFeatureFlagBitsKHR -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkExternalFenceFeatureFlagBitsKHR) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkExternalFenceFeatureFlagBitsKHR) #

gmapT :: (forall b. Data b => b -> b) -> VkExternalFenceFeatureFlagBitsKHR -> VkExternalFenceFeatureFlagBitsKHR #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkExternalFenceFeatureFlagBitsKHR -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkExternalFenceFeatureFlagBitsKHR -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkExternalFenceFeatureFlagBitsKHR -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkExternalFenceFeatureFlagBitsKHR -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkExternalFenceFeatureFlagBitsKHR -> m VkExternalFenceFeatureFlagBitsKHR #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkExternalFenceFeatureFlagBitsKHR -> m VkExternalFenceFeatureFlagBitsKHR #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkExternalFenceFeatureFlagBitsKHR -> m VkExternalFenceFeatureFlagBitsKHR #

Num VkExternalFenceFeatureFlagBitsKHR Source # 
Ord VkExternalFenceFeatureFlagBitsKHR Source # 
Read VkExternalFenceFeatureFlagBitsKHR Source # 
Real VkExternalFenceFeatureFlagBitsKHR Source # 
Show VkExternalFenceFeatureFlagBitsKHR Source # 
Generic VkExternalFenceFeatureFlagBitsKHR Source # 
Storable VkExternalFenceFeatureFlagBitsKHR Source # 
Bits VkExternalFenceFeatureFlagBitsKHR Source # 

Methods

(.&.) :: VkExternalFenceFeatureFlagBitsKHR -> VkExternalFenceFeatureFlagBitsKHR -> VkExternalFenceFeatureFlagBitsKHR #

(.|.) :: VkExternalFenceFeatureFlagBitsKHR -> VkExternalFenceFeatureFlagBitsKHR -> VkExternalFenceFeatureFlagBitsKHR #

xor :: VkExternalFenceFeatureFlagBitsKHR -> VkExternalFenceFeatureFlagBitsKHR -> VkExternalFenceFeatureFlagBitsKHR #

complement :: VkExternalFenceFeatureFlagBitsKHR -> VkExternalFenceFeatureFlagBitsKHR #

shift :: VkExternalFenceFeatureFlagBitsKHR -> Int -> VkExternalFenceFeatureFlagBitsKHR #

rotate :: VkExternalFenceFeatureFlagBitsKHR -> Int -> VkExternalFenceFeatureFlagBitsKHR #

zeroBits :: VkExternalFenceFeatureFlagBitsKHR #

bit :: Int -> VkExternalFenceFeatureFlagBitsKHR #

setBit :: VkExternalFenceFeatureFlagBitsKHR -> Int -> VkExternalFenceFeatureFlagBitsKHR #

clearBit :: VkExternalFenceFeatureFlagBitsKHR -> Int -> VkExternalFenceFeatureFlagBitsKHR #

complementBit :: VkExternalFenceFeatureFlagBitsKHR -> Int -> VkExternalFenceFeatureFlagBitsKHR #

testBit :: VkExternalFenceFeatureFlagBitsKHR -> Int -> Bool #

bitSizeMaybe :: VkExternalFenceFeatureFlagBitsKHR -> Maybe Int #

bitSize :: VkExternalFenceFeatureFlagBitsKHR -> Int #

isSigned :: VkExternalFenceFeatureFlagBitsKHR -> Bool #

shiftL :: VkExternalFenceFeatureFlagBitsKHR -> Int -> VkExternalFenceFeatureFlagBitsKHR #

unsafeShiftL :: VkExternalFenceFeatureFlagBitsKHR -> Int -> VkExternalFenceFeatureFlagBitsKHR #

shiftR :: VkExternalFenceFeatureFlagBitsKHR -> Int -> VkExternalFenceFeatureFlagBitsKHR #

unsafeShiftR :: VkExternalFenceFeatureFlagBitsKHR -> Int -> VkExternalFenceFeatureFlagBitsKHR #

rotateL :: VkExternalFenceFeatureFlagBitsKHR -> Int -> VkExternalFenceFeatureFlagBitsKHR #

rotateR :: VkExternalFenceFeatureFlagBitsKHR -> Int -> VkExternalFenceFeatureFlagBitsKHR #

popCount :: VkExternalFenceFeatureFlagBitsKHR -> Int #

FiniteBits VkExternalFenceFeatureFlagBitsKHR Source # 
type Rep VkExternalFenceFeatureFlagBitsKHR Source # 
type Rep VkExternalFenceFeatureFlagBitsKHR = D1 (MetaData "VkExternalFenceFeatureFlagBitsKHR" "Graphics.Vulkan.Types.Enum.External" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkExternalFenceFeatureFlagBitsKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkExternalFenceFeatureBitmask a Source #

Instances

Bounded (VkExternalFenceFeatureBitmask FlagMask) Source # 
Enum (VkExternalFenceFeatureBitmask FlagMask) Source # 
Eq (VkExternalFenceFeatureBitmask a) Source # 
Integral (VkExternalFenceFeatureBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkExternalFenceFeatureBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkExternalFenceFeatureBitmask a -> c (VkExternalFenceFeatureBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkExternalFenceFeatureBitmask a) #

toConstr :: VkExternalFenceFeatureBitmask a -> Constr #

dataTypeOf :: VkExternalFenceFeatureBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkExternalFenceFeatureBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkExternalFenceFeatureBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkExternalFenceFeatureBitmask a -> VkExternalFenceFeatureBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkExternalFenceFeatureBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkExternalFenceFeatureBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkExternalFenceFeatureBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkExternalFenceFeatureBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkExternalFenceFeatureBitmask a -> m (VkExternalFenceFeatureBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkExternalFenceFeatureBitmask a -> m (VkExternalFenceFeatureBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkExternalFenceFeatureBitmask a -> m (VkExternalFenceFeatureBitmask a) #

Num (VkExternalFenceFeatureBitmask FlagMask) Source # 
Ord (VkExternalFenceFeatureBitmask a) Source # 
Read (VkExternalFenceFeatureBitmask a) Source # 
Real (VkExternalFenceFeatureBitmask FlagMask) Source # 
Show (VkExternalFenceFeatureBitmask a) Source # 
Generic (VkExternalFenceFeatureBitmask a) Source # 
Storable (VkExternalFenceFeatureBitmask a) Source # 
Bits (VkExternalFenceFeatureBitmask FlagMask) Source # 

Methods

(.&.) :: VkExternalFenceFeatureBitmask FlagMask -> VkExternalFenceFeatureBitmask FlagMask -> VkExternalFenceFeatureBitmask FlagMask #

(.|.) :: VkExternalFenceFeatureBitmask FlagMask -> VkExternalFenceFeatureBitmask FlagMask -> VkExternalFenceFeatureBitmask FlagMask #

xor :: VkExternalFenceFeatureBitmask FlagMask -> VkExternalFenceFeatureBitmask FlagMask -> VkExternalFenceFeatureBitmask FlagMask #

complement :: VkExternalFenceFeatureBitmask FlagMask -> VkExternalFenceFeatureBitmask FlagMask #

shift :: VkExternalFenceFeatureBitmask FlagMask -> Int -> VkExternalFenceFeatureBitmask FlagMask #

rotate :: VkExternalFenceFeatureBitmask FlagMask -> Int -> VkExternalFenceFeatureBitmask FlagMask #

zeroBits :: VkExternalFenceFeatureBitmask FlagMask #

bit :: Int -> VkExternalFenceFeatureBitmask FlagMask #

setBit :: VkExternalFenceFeatureBitmask FlagMask -> Int -> VkExternalFenceFeatureBitmask FlagMask #

clearBit :: VkExternalFenceFeatureBitmask FlagMask -> Int -> VkExternalFenceFeatureBitmask FlagMask #

complementBit :: VkExternalFenceFeatureBitmask FlagMask -> Int -> VkExternalFenceFeatureBitmask FlagMask #

testBit :: VkExternalFenceFeatureBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkExternalFenceFeatureBitmask FlagMask -> Maybe Int #

bitSize :: VkExternalFenceFeatureBitmask FlagMask -> Int #

isSigned :: VkExternalFenceFeatureBitmask FlagMask -> Bool #

shiftL :: VkExternalFenceFeatureBitmask FlagMask -> Int -> VkExternalFenceFeatureBitmask FlagMask #

unsafeShiftL :: VkExternalFenceFeatureBitmask FlagMask -> Int -> VkExternalFenceFeatureBitmask FlagMask #

shiftR :: VkExternalFenceFeatureBitmask FlagMask -> Int -> VkExternalFenceFeatureBitmask FlagMask #

unsafeShiftR :: VkExternalFenceFeatureBitmask FlagMask -> Int -> VkExternalFenceFeatureBitmask FlagMask #

rotateL :: VkExternalFenceFeatureBitmask FlagMask -> Int -> VkExternalFenceFeatureBitmask FlagMask #

rotateR :: VkExternalFenceFeatureBitmask FlagMask -> Int -> VkExternalFenceFeatureBitmask FlagMask #

popCount :: VkExternalFenceFeatureBitmask FlagMask -> Int #

FiniteBits (VkExternalFenceFeatureBitmask FlagMask) Source # 
type Rep (VkExternalFenceFeatureBitmask a) Source # 
type Rep (VkExternalFenceFeatureBitmask a) = D1 (MetaData "VkExternalFenceFeatureBitmask" "Graphics.Vulkan.Types.Enum.External" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkExternalFenceFeatureBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkExternalFenceHandleTypeFlagBitsKHR Source #

Instances

Bounded VkExternalFenceHandleTypeFlagBitsKHR Source # 
Enum VkExternalFenceHandleTypeFlagBitsKHR Source # 
Eq VkExternalFenceHandleTypeFlagBitsKHR Source # 
Integral VkExternalFenceHandleTypeFlagBitsKHR Source # 
Data VkExternalFenceHandleTypeFlagBitsKHR Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkExternalFenceHandleTypeFlagBitsKHR -> c VkExternalFenceHandleTypeFlagBitsKHR #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkExternalFenceHandleTypeFlagBitsKHR #

toConstr :: VkExternalFenceHandleTypeFlagBitsKHR -> Constr #

dataTypeOf :: VkExternalFenceHandleTypeFlagBitsKHR -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkExternalFenceHandleTypeFlagBitsKHR) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkExternalFenceHandleTypeFlagBitsKHR) #

gmapT :: (forall b. Data b => b -> b) -> VkExternalFenceHandleTypeFlagBitsKHR -> VkExternalFenceHandleTypeFlagBitsKHR #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkExternalFenceHandleTypeFlagBitsKHR -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkExternalFenceHandleTypeFlagBitsKHR -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkExternalFenceHandleTypeFlagBitsKHR -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkExternalFenceHandleTypeFlagBitsKHR -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkExternalFenceHandleTypeFlagBitsKHR -> m VkExternalFenceHandleTypeFlagBitsKHR #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkExternalFenceHandleTypeFlagBitsKHR -> m VkExternalFenceHandleTypeFlagBitsKHR #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkExternalFenceHandleTypeFlagBitsKHR -> m VkExternalFenceHandleTypeFlagBitsKHR #

Num VkExternalFenceHandleTypeFlagBitsKHR Source # 
Ord VkExternalFenceHandleTypeFlagBitsKHR Source # 
Read VkExternalFenceHandleTypeFlagBitsKHR Source # 
Real VkExternalFenceHandleTypeFlagBitsKHR Source # 
Show VkExternalFenceHandleTypeFlagBitsKHR Source # 
Generic VkExternalFenceHandleTypeFlagBitsKHR Source # 
Storable VkExternalFenceHandleTypeFlagBitsKHR Source # 
Bits VkExternalFenceHandleTypeFlagBitsKHR Source # 

Methods

(.&.) :: VkExternalFenceHandleTypeFlagBitsKHR -> VkExternalFenceHandleTypeFlagBitsKHR -> VkExternalFenceHandleTypeFlagBitsKHR #

(.|.) :: VkExternalFenceHandleTypeFlagBitsKHR -> VkExternalFenceHandleTypeFlagBitsKHR -> VkExternalFenceHandleTypeFlagBitsKHR #

xor :: VkExternalFenceHandleTypeFlagBitsKHR -> VkExternalFenceHandleTypeFlagBitsKHR -> VkExternalFenceHandleTypeFlagBitsKHR #

complement :: VkExternalFenceHandleTypeFlagBitsKHR -> VkExternalFenceHandleTypeFlagBitsKHR #

shift :: VkExternalFenceHandleTypeFlagBitsKHR -> Int -> VkExternalFenceHandleTypeFlagBitsKHR #

rotate :: VkExternalFenceHandleTypeFlagBitsKHR -> Int -> VkExternalFenceHandleTypeFlagBitsKHR #

zeroBits :: VkExternalFenceHandleTypeFlagBitsKHR #

bit :: Int -> VkExternalFenceHandleTypeFlagBitsKHR #

setBit :: VkExternalFenceHandleTypeFlagBitsKHR -> Int -> VkExternalFenceHandleTypeFlagBitsKHR #

clearBit :: VkExternalFenceHandleTypeFlagBitsKHR -> Int -> VkExternalFenceHandleTypeFlagBitsKHR #

complementBit :: VkExternalFenceHandleTypeFlagBitsKHR -> Int -> VkExternalFenceHandleTypeFlagBitsKHR #

testBit :: VkExternalFenceHandleTypeFlagBitsKHR -> Int -> Bool #

bitSizeMaybe :: VkExternalFenceHandleTypeFlagBitsKHR -> Maybe Int #

bitSize :: VkExternalFenceHandleTypeFlagBitsKHR -> Int #

isSigned :: VkExternalFenceHandleTypeFlagBitsKHR -> Bool #

shiftL :: VkExternalFenceHandleTypeFlagBitsKHR -> Int -> VkExternalFenceHandleTypeFlagBitsKHR #

unsafeShiftL :: VkExternalFenceHandleTypeFlagBitsKHR -> Int -> VkExternalFenceHandleTypeFlagBitsKHR #

shiftR :: VkExternalFenceHandleTypeFlagBitsKHR -> Int -> VkExternalFenceHandleTypeFlagBitsKHR #

unsafeShiftR :: VkExternalFenceHandleTypeFlagBitsKHR -> Int -> VkExternalFenceHandleTypeFlagBitsKHR #

rotateL :: VkExternalFenceHandleTypeFlagBitsKHR -> Int -> VkExternalFenceHandleTypeFlagBitsKHR #

rotateR :: VkExternalFenceHandleTypeFlagBitsKHR -> Int -> VkExternalFenceHandleTypeFlagBitsKHR #

popCount :: VkExternalFenceHandleTypeFlagBitsKHR -> Int #

FiniteBits VkExternalFenceHandleTypeFlagBitsKHR Source # 
type Rep VkExternalFenceHandleTypeFlagBitsKHR Source # 
type Rep VkExternalFenceHandleTypeFlagBitsKHR = D1 (MetaData "VkExternalFenceHandleTypeFlagBitsKHR" "Graphics.Vulkan.Types.Enum.External" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkExternalFenceHandleTypeFlagBitsKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkExternalFenceHandleTypeBitmask a Source #

Instances

Bounded (VkExternalFenceHandleTypeBitmask FlagMask) Source # 
Enum (VkExternalFenceHandleTypeBitmask FlagMask) Source # 
Eq (VkExternalFenceHandleTypeBitmask a) Source # 
Integral (VkExternalFenceHandleTypeBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkExternalFenceHandleTypeBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkExternalFenceHandleTypeBitmask a -> c (VkExternalFenceHandleTypeBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkExternalFenceHandleTypeBitmask a) #

toConstr :: VkExternalFenceHandleTypeBitmask a -> Constr #

dataTypeOf :: VkExternalFenceHandleTypeBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkExternalFenceHandleTypeBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkExternalFenceHandleTypeBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkExternalFenceHandleTypeBitmask a -> VkExternalFenceHandleTypeBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkExternalFenceHandleTypeBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkExternalFenceHandleTypeBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkExternalFenceHandleTypeBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkExternalFenceHandleTypeBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkExternalFenceHandleTypeBitmask a -> m (VkExternalFenceHandleTypeBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkExternalFenceHandleTypeBitmask a -> m (VkExternalFenceHandleTypeBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkExternalFenceHandleTypeBitmask a -> m (VkExternalFenceHandleTypeBitmask a) #

Num (VkExternalFenceHandleTypeBitmask FlagMask) Source # 
Ord (VkExternalFenceHandleTypeBitmask a) Source # 
Read (VkExternalFenceHandleTypeBitmask a) Source # 
Real (VkExternalFenceHandleTypeBitmask FlagMask) Source # 
Show (VkExternalFenceHandleTypeBitmask a) Source # 
Generic (VkExternalFenceHandleTypeBitmask a) Source # 
Storable (VkExternalFenceHandleTypeBitmask a) Source # 
Bits (VkExternalFenceHandleTypeBitmask FlagMask) Source # 

Methods

(.&.) :: VkExternalFenceHandleTypeBitmask FlagMask -> VkExternalFenceHandleTypeBitmask FlagMask -> VkExternalFenceHandleTypeBitmask FlagMask #

(.|.) :: VkExternalFenceHandleTypeBitmask FlagMask -> VkExternalFenceHandleTypeBitmask FlagMask -> VkExternalFenceHandleTypeBitmask FlagMask #

xor :: VkExternalFenceHandleTypeBitmask FlagMask -> VkExternalFenceHandleTypeBitmask FlagMask -> VkExternalFenceHandleTypeBitmask FlagMask #

complement :: VkExternalFenceHandleTypeBitmask FlagMask -> VkExternalFenceHandleTypeBitmask FlagMask #

shift :: VkExternalFenceHandleTypeBitmask FlagMask -> Int -> VkExternalFenceHandleTypeBitmask FlagMask #

rotate :: VkExternalFenceHandleTypeBitmask FlagMask -> Int -> VkExternalFenceHandleTypeBitmask FlagMask #

zeroBits :: VkExternalFenceHandleTypeBitmask FlagMask #

bit :: Int -> VkExternalFenceHandleTypeBitmask FlagMask #

setBit :: VkExternalFenceHandleTypeBitmask FlagMask -> Int -> VkExternalFenceHandleTypeBitmask FlagMask #

clearBit :: VkExternalFenceHandleTypeBitmask FlagMask -> Int -> VkExternalFenceHandleTypeBitmask FlagMask #

complementBit :: VkExternalFenceHandleTypeBitmask FlagMask -> Int -> VkExternalFenceHandleTypeBitmask FlagMask #

testBit :: VkExternalFenceHandleTypeBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkExternalFenceHandleTypeBitmask FlagMask -> Maybe Int #

bitSize :: VkExternalFenceHandleTypeBitmask FlagMask -> Int #

isSigned :: VkExternalFenceHandleTypeBitmask FlagMask -> Bool #

shiftL :: VkExternalFenceHandleTypeBitmask FlagMask -> Int -> VkExternalFenceHandleTypeBitmask FlagMask #

unsafeShiftL :: VkExternalFenceHandleTypeBitmask FlagMask -> Int -> VkExternalFenceHandleTypeBitmask FlagMask #

shiftR :: VkExternalFenceHandleTypeBitmask FlagMask -> Int -> VkExternalFenceHandleTypeBitmask FlagMask #

unsafeShiftR :: VkExternalFenceHandleTypeBitmask FlagMask -> Int -> VkExternalFenceHandleTypeBitmask FlagMask #

rotateL :: VkExternalFenceHandleTypeBitmask FlagMask -> Int -> VkExternalFenceHandleTypeBitmask FlagMask #

rotateR :: VkExternalFenceHandleTypeBitmask FlagMask -> Int -> VkExternalFenceHandleTypeBitmask FlagMask #

popCount :: VkExternalFenceHandleTypeBitmask FlagMask -> Int #

FiniteBits (VkExternalFenceHandleTypeBitmask FlagMask) Source # 
type Rep (VkExternalFenceHandleTypeBitmask a) Source # 
type Rep (VkExternalFenceHandleTypeBitmask a) = D1 (MetaData "VkExternalFenceHandleTypeBitmask" "Graphics.Vulkan.Types.Enum.External" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkExternalFenceHandleTypeBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkExternalMemoryFeatureFlagBitsKHR Source #

Instances

Bounded VkExternalMemoryFeatureFlagBitsKHR Source # 
Enum VkExternalMemoryFeatureFlagBitsKHR Source # 
Eq VkExternalMemoryFeatureFlagBitsKHR Source # 
Integral VkExternalMemoryFeatureFlagBitsKHR Source # 
Data VkExternalMemoryFeatureFlagBitsKHR Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkExternalMemoryFeatureFlagBitsKHR -> c VkExternalMemoryFeatureFlagBitsKHR #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkExternalMemoryFeatureFlagBitsKHR #

toConstr :: VkExternalMemoryFeatureFlagBitsKHR -> Constr #

dataTypeOf :: VkExternalMemoryFeatureFlagBitsKHR -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkExternalMemoryFeatureFlagBitsKHR) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkExternalMemoryFeatureFlagBitsKHR) #

gmapT :: (forall b. Data b => b -> b) -> VkExternalMemoryFeatureFlagBitsKHR -> VkExternalMemoryFeatureFlagBitsKHR #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkExternalMemoryFeatureFlagBitsKHR -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkExternalMemoryFeatureFlagBitsKHR -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkExternalMemoryFeatureFlagBitsKHR -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkExternalMemoryFeatureFlagBitsKHR -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkExternalMemoryFeatureFlagBitsKHR -> m VkExternalMemoryFeatureFlagBitsKHR #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkExternalMemoryFeatureFlagBitsKHR -> m VkExternalMemoryFeatureFlagBitsKHR #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkExternalMemoryFeatureFlagBitsKHR -> m VkExternalMemoryFeatureFlagBitsKHR #

Num VkExternalMemoryFeatureFlagBitsKHR Source # 
Ord VkExternalMemoryFeatureFlagBitsKHR Source # 
Read VkExternalMemoryFeatureFlagBitsKHR Source # 
Real VkExternalMemoryFeatureFlagBitsKHR Source # 
Show VkExternalMemoryFeatureFlagBitsKHR Source # 
Generic VkExternalMemoryFeatureFlagBitsKHR Source # 
Storable VkExternalMemoryFeatureFlagBitsKHR Source # 
Bits VkExternalMemoryFeatureFlagBitsKHR Source # 

Methods

(.&.) :: VkExternalMemoryFeatureFlagBitsKHR -> VkExternalMemoryFeatureFlagBitsKHR -> VkExternalMemoryFeatureFlagBitsKHR #

(.|.) :: VkExternalMemoryFeatureFlagBitsKHR -> VkExternalMemoryFeatureFlagBitsKHR -> VkExternalMemoryFeatureFlagBitsKHR #

xor :: VkExternalMemoryFeatureFlagBitsKHR -> VkExternalMemoryFeatureFlagBitsKHR -> VkExternalMemoryFeatureFlagBitsKHR #

complement :: VkExternalMemoryFeatureFlagBitsKHR -> VkExternalMemoryFeatureFlagBitsKHR #

shift :: VkExternalMemoryFeatureFlagBitsKHR -> Int -> VkExternalMemoryFeatureFlagBitsKHR #

rotate :: VkExternalMemoryFeatureFlagBitsKHR -> Int -> VkExternalMemoryFeatureFlagBitsKHR #

zeroBits :: VkExternalMemoryFeatureFlagBitsKHR #

bit :: Int -> VkExternalMemoryFeatureFlagBitsKHR #

setBit :: VkExternalMemoryFeatureFlagBitsKHR -> Int -> VkExternalMemoryFeatureFlagBitsKHR #

clearBit :: VkExternalMemoryFeatureFlagBitsKHR -> Int -> VkExternalMemoryFeatureFlagBitsKHR #

complementBit :: VkExternalMemoryFeatureFlagBitsKHR -> Int -> VkExternalMemoryFeatureFlagBitsKHR #

testBit :: VkExternalMemoryFeatureFlagBitsKHR -> Int -> Bool #

bitSizeMaybe :: VkExternalMemoryFeatureFlagBitsKHR -> Maybe Int #

bitSize :: VkExternalMemoryFeatureFlagBitsKHR -> Int #

isSigned :: VkExternalMemoryFeatureFlagBitsKHR -> Bool #

shiftL :: VkExternalMemoryFeatureFlagBitsKHR -> Int -> VkExternalMemoryFeatureFlagBitsKHR #

unsafeShiftL :: VkExternalMemoryFeatureFlagBitsKHR -> Int -> VkExternalMemoryFeatureFlagBitsKHR #

shiftR :: VkExternalMemoryFeatureFlagBitsKHR -> Int -> VkExternalMemoryFeatureFlagBitsKHR #

unsafeShiftR :: VkExternalMemoryFeatureFlagBitsKHR -> Int -> VkExternalMemoryFeatureFlagBitsKHR #

rotateL :: VkExternalMemoryFeatureFlagBitsKHR -> Int -> VkExternalMemoryFeatureFlagBitsKHR #

rotateR :: VkExternalMemoryFeatureFlagBitsKHR -> Int -> VkExternalMemoryFeatureFlagBitsKHR #

popCount :: VkExternalMemoryFeatureFlagBitsKHR -> Int #

FiniteBits VkExternalMemoryFeatureFlagBitsKHR Source # 
type Rep VkExternalMemoryFeatureFlagBitsKHR Source # 
type Rep VkExternalMemoryFeatureFlagBitsKHR = D1 (MetaData "VkExternalMemoryFeatureFlagBitsKHR" "Graphics.Vulkan.Types.Enum.External" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkExternalMemoryFeatureFlagBitsKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkExternalMemoryFeatureBitmask a Source #

Instances

Bounded (VkExternalMemoryFeatureBitmask FlagMask) Source # 
Enum (VkExternalMemoryFeatureBitmask FlagMask) Source # 
Eq (VkExternalMemoryFeatureBitmask a) Source # 
Integral (VkExternalMemoryFeatureBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkExternalMemoryFeatureBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkExternalMemoryFeatureBitmask a -> c (VkExternalMemoryFeatureBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkExternalMemoryFeatureBitmask a) #

toConstr :: VkExternalMemoryFeatureBitmask a -> Constr #

dataTypeOf :: VkExternalMemoryFeatureBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkExternalMemoryFeatureBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkExternalMemoryFeatureBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkExternalMemoryFeatureBitmask a -> VkExternalMemoryFeatureBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkExternalMemoryFeatureBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkExternalMemoryFeatureBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkExternalMemoryFeatureBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkExternalMemoryFeatureBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkExternalMemoryFeatureBitmask a -> m (VkExternalMemoryFeatureBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkExternalMemoryFeatureBitmask a -> m (VkExternalMemoryFeatureBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkExternalMemoryFeatureBitmask a -> m (VkExternalMemoryFeatureBitmask a) #

Num (VkExternalMemoryFeatureBitmask FlagMask) Source # 
Ord (VkExternalMemoryFeatureBitmask a) Source # 
Read (VkExternalMemoryFeatureBitmask a) Source # 
Real (VkExternalMemoryFeatureBitmask FlagMask) Source # 
Show (VkExternalMemoryFeatureBitmask a) Source # 
Generic (VkExternalMemoryFeatureBitmask a) Source # 
Storable (VkExternalMemoryFeatureBitmask a) Source # 
Bits (VkExternalMemoryFeatureBitmask FlagMask) Source # 

Methods

(.&.) :: VkExternalMemoryFeatureBitmask FlagMask -> VkExternalMemoryFeatureBitmask FlagMask -> VkExternalMemoryFeatureBitmask FlagMask #

(.|.) :: VkExternalMemoryFeatureBitmask FlagMask -> VkExternalMemoryFeatureBitmask FlagMask -> VkExternalMemoryFeatureBitmask FlagMask #

xor :: VkExternalMemoryFeatureBitmask FlagMask -> VkExternalMemoryFeatureBitmask FlagMask -> VkExternalMemoryFeatureBitmask FlagMask #

complement :: VkExternalMemoryFeatureBitmask FlagMask -> VkExternalMemoryFeatureBitmask FlagMask #

shift :: VkExternalMemoryFeatureBitmask FlagMask -> Int -> VkExternalMemoryFeatureBitmask FlagMask #

rotate :: VkExternalMemoryFeatureBitmask FlagMask -> Int -> VkExternalMemoryFeatureBitmask FlagMask #

zeroBits :: VkExternalMemoryFeatureBitmask FlagMask #

bit :: Int -> VkExternalMemoryFeatureBitmask FlagMask #

setBit :: VkExternalMemoryFeatureBitmask FlagMask -> Int -> VkExternalMemoryFeatureBitmask FlagMask #

clearBit :: VkExternalMemoryFeatureBitmask FlagMask -> Int -> VkExternalMemoryFeatureBitmask FlagMask #

complementBit :: VkExternalMemoryFeatureBitmask FlagMask -> Int -> VkExternalMemoryFeatureBitmask FlagMask #

testBit :: VkExternalMemoryFeatureBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkExternalMemoryFeatureBitmask FlagMask -> Maybe Int #

bitSize :: VkExternalMemoryFeatureBitmask FlagMask -> Int #

isSigned :: VkExternalMemoryFeatureBitmask FlagMask -> Bool #

shiftL :: VkExternalMemoryFeatureBitmask FlagMask -> Int -> VkExternalMemoryFeatureBitmask FlagMask #

unsafeShiftL :: VkExternalMemoryFeatureBitmask FlagMask -> Int -> VkExternalMemoryFeatureBitmask FlagMask #

shiftR :: VkExternalMemoryFeatureBitmask FlagMask -> Int -> VkExternalMemoryFeatureBitmask FlagMask #

unsafeShiftR :: VkExternalMemoryFeatureBitmask FlagMask -> Int -> VkExternalMemoryFeatureBitmask FlagMask #

rotateL :: VkExternalMemoryFeatureBitmask FlagMask -> Int -> VkExternalMemoryFeatureBitmask FlagMask #

rotateR :: VkExternalMemoryFeatureBitmask FlagMask -> Int -> VkExternalMemoryFeatureBitmask FlagMask #

popCount :: VkExternalMemoryFeatureBitmask FlagMask -> Int #

FiniteBits (VkExternalMemoryFeatureBitmask FlagMask) Source # 
type Rep (VkExternalMemoryFeatureBitmask a) Source # 
type Rep (VkExternalMemoryFeatureBitmask a) = D1 (MetaData "VkExternalMemoryFeatureBitmask" "Graphics.Vulkan.Types.Enum.External" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkExternalMemoryFeatureBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkExternalMemoryFeatureBitmaskNV a Source #

Instances

Bounded (VkExternalMemoryFeatureBitmaskNV FlagMask) Source # 
Enum (VkExternalMemoryFeatureBitmaskNV FlagMask) Source # 
Eq (VkExternalMemoryFeatureBitmaskNV a) Source # 
Integral (VkExternalMemoryFeatureBitmaskNV FlagMask) Source # 
Typeable FlagType a => Data (VkExternalMemoryFeatureBitmaskNV a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkExternalMemoryFeatureBitmaskNV a -> c (VkExternalMemoryFeatureBitmaskNV a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkExternalMemoryFeatureBitmaskNV a) #

toConstr :: VkExternalMemoryFeatureBitmaskNV a -> Constr #

dataTypeOf :: VkExternalMemoryFeatureBitmaskNV a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkExternalMemoryFeatureBitmaskNV a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkExternalMemoryFeatureBitmaskNV a)) #

gmapT :: (forall b. Data b => b -> b) -> VkExternalMemoryFeatureBitmaskNV a -> VkExternalMemoryFeatureBitmaskNV a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkExternalMemoryFeatureBitmaskNV a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkExternalMemoryFeatureBitmaskNV a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkExternalMemoryFeatureBitmaskNV a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkExternalMemoryFeatureBitmaskNV a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkExternalMemoryFeatureBitmaskNV a -> m (VkExternalMemoryFeatureBitmaskNV a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkExternalMemoryFeatureBitmaskNV a -> m (VkExternalMemoryFeatureBitmaskNV a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkExternalMemoryFeatureBitmaskNV a -> m (VkExternalMemoryFeatureBitmaskNV a) #

Num (VkExternalMemoryFeatureBitmaskNV FlagMask) Source # 
Ord (VkExternalMemoryFeatureBitmaskNV a) Source # 
Read (VkExternalMemoryFeatureBitmaskNV a) Source # 
Real (VkExternalMemoryFeatureBitmaskNV FlagMask) Source # 
Show (VkExternalMemoryFeatureBitmaskNV a) Source # 
Generic (VkExternalMemoryFeatureBitmaskNV a) Source # 
Storable (VkExternalMemoryFeatureBitmaskNV a) Source # 
Bits (VkExternalMemoryFeatureBitmaskNV FlagMask) Source # 

Methods

(.&.) :: VkExternalMemoryFeatureBitmaskNV FlagMask -> VkExternalMemoryFeatureBitmaskNV FlagMask -> VkExternalMemoryFeatureBitmaskNV FlagMask #

(.|.) :: VkExternalMemoryFeatureBitmaskNV FlagMask -> VkExternalMemoryFeatureBitmaskNV FlagMask -> VkExternalMemoryFeatureBitmaskNV FlagMask #

xor :: VkExternalMemoryFeatureBitmaskNV FlagMask -> VkExternalMemoryFeatureBitmaskNV FlagMask -> VkExternalMemoryFeatureBitmaskNV FlagMask #

complement :: VkExternalMemoryFeatureBitmaskNV FlagMask -> VkExternalMemoryFeatureBitmaskNV FlagMask #

shift :: VkExternalMemoryFeatureBitmaskNV FlagMask -> Int -> VkExternalMemoryFeatureBitmaskNV FlagMask #

rotate :: VkExternalMemoryFeatureBitmaskNV FlagMask -> Int -> VkExternalMemoryFeatureBitmaskNV FlagMask #

zeroBits :: VkExternalMemoryFeatureBitmaskNV FlagMask #

bit :: Int -> VkExternalMemoryFeatureBitmaskNV FlagMask #

setBit :: VkExternalMemoryFeatureBitmaskNV FlagMask -> Int -> VkExternalMemoryFeatureBitmaskNV FlagMask #

clearBit :: VkExternalMemoryFeatureBitmaskNV FlagMask -> Int -> VkExternalMemoryFeatureBitmaskNV FlagMask #

complementBit :: VkExternalMemoryFeatureBitmaskNV FlagMask -> Int -> VkExternalMemoryFeatureBitmaskNV FlagMask #

testBit :: VkExternalMemoryFeatureBitmaskNV FlagMask -> Int -> Bool #

bitSizeMaybe :: VkExternalMemoryFeatureBitmaskNV FlagMask -> Maybe Int #

bitSize :: VkExternalMemoryFeatureBitmaskNV FlagMask -> Int #

isSigned :: VkExternalMemoryFeatureBitmaskNV FlagMask -> Bool #

shiftL :: VkExternalMemoryFeatureBitmaskNV FlagMask -> Int -> VkExternalMemoryFeatureBitmaskNV FlagMask #

unsafeShiftL :: VkExternalMemoryFeatureBitmaskNV FlagMask -> Int -> VkExternalMemoryFeatureBitmaskNV FlagMask #

shiftR :: VkExternalMemoryFeatureBitmaskNV FlagMask -> Int -> VkExternalMemoryFeatureBitmaskNV FlagMask #

unsafeShiftR :: VkExternalMemoryFeatureBitmaskNV FlagMask -> Int -> VkExternalMemoryFeatureBitmaskNV FlagMask #

rotateL :: VkExternalMemoryFeatureBitmaskNV FlagMask -> Int -> VkExternalMemoryFeatureBitmaskNV FlagMask #

rotateR :: VkExternalMemoryFeatureBitmaskNV FlagMask -> Int -> VkExternalMemoryFeatureBitmaskNV FlagMask #

popCount :: VkExternalMemoryFeatureBitmaskNV FlagMask -> Int #

FiniteBits (VkExternalMemoryFeatureBitmaskNV FlagMask) Source # 
type Rep (VkExternalMemoryFeatureBitmaskNV a) Source # 
type Rep (VkExternalMemoryFeatureBitmaskNV a) = D1 (MetaData "VkExternalMemoryFeatureBitmaskNV" "Graphics.Vulkan.Types.Enum.External" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkExternalMemoryFeatureBitmaskNV" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkExternalMemoryHandleTypeFlagBitsKHR Source #

Instances

Bounded VkExternalMemoryHandleTypeFlagBitsKHR Source # 
Enum VkExternalMemoryHandleTypeFlagBitsKHR Source # 
Eq VkExternalMemoryHandleTypeFlagBitsKHR Source # 
Integral VkExternalMemoryHandleTypeFlagBitsKHR Source # 
Data VkExternalMemoryHandleTypeFlagBitsKHR Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkExternalMemoryHandleTypeFlagBitsKHR -> c VkExternalMemoryHandleTypeFlagBitsKHR #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkExternalMemoryHandleTypeFlagBitsKHR #

toConstr :: VkExternalMemoryHandleTypeFlagBitsKHR -> Constr #

dataTypeOf :: VkExternalMemoryHandleTypeFlagBitsKHR -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkExternalMemoryHandleTypeFlagBitsKHR) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkExternalMemoryHandleTypeFlagBitsKHR) #

gmapT :: (forall b. Data b => b -> b) -> VkExternalMemoryHandleTypeFlagBitsKHR -> VkExternalMemoryHandleTypeFlagBitsKHR #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkExternalMemoryHandleTypeFlagBitsKHR -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkExternalMemoryHandleTypeFlagBitsKHR -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkExternalMemoryHandleTypeFlagBitsKHR -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkExternalMemoryHandleTypeFlagBitsKHR -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkExternalMemoryHandleTypeFlagBitsKHR -> m VkExternalMemoryHandleTypeFlagBitsKHR #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkExternalMemoryHandleTypeFlagBitsKHR -> m VkExternalMemoryHandleTypeFlagBitsKHR #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkExternalMemoryHandleTypeFlagBitsKHR -> m VkExternalMemoryHandleTypeFlagBitsKHR #

Num VkExternalMemoryHandleTypeFlagBitsKHR Source # 
Ord VkExternalMemoryHandleTypeFlagBitsKHR Source # 
Read VkExternalMemoryHandleTypeFlagBitsKHR Source # 
Real VkExternalMemoryHandleTypeFlagBitsKHR Source # 
Show VkExternalMemoryHandleTypeFlagBitsKHR Source # 
Generic VkExternalMemoryHandleTypeFlagBitsKHR Source # 
Storable VkExternalMemoryHandleTypeFlagBitsKHR Source # 
Bits VkExternalMemoryHandleTypeFlagBitsKHR Source # 

Methods

(.&.) :: VkExternalMemoryHandleTypeFlagBitsKHR -> VkExternalMemoryHandleTypeFlagBitsKHR -> VkExternalMemoryHandleTypeFlagBitsKHR #

(.|.) :: VkExternalMemoryHandleTypeFlagBitsKHR -> VkExternalMemoryHandleTypeFlagBitsKHR -> VkExternalMemoryHandleTypeFlagBitsKHR #

xor :: VkExternalMemoryHandleTypeFlagBitsKHR -> VkExternalMemoryHandleTypeFlagBitsKHR -> VkExternalMemoryHandleTypeFlagBitsKHR #

complement :: VkExternalMemoryHandleTypeFlagBitsKHR -> VkExternalMemoryHandleTypeFlagBitsKHR #

shift :: VkExternalMemoryHandleTypeFlagBitsKHR -> Int -> VkExternalMemoryHandleTypeFlagBitsKHR #

rotate :: VkExternalMemoryHandleTypeFlagBitsKHR -> Int -> VkExternalMemoryHandleTypeFlagBitsKHR #

zeroBits :: VkExternalMemoryHandleTypeFlagBitsKHR #

bit :: Int -> VkExternalMemoryHandleTypeFlagBitsKHR #

setBit :: VkExternalMemoryHandleTypeFlagBitsKHR -> Int -> VkExternalMemoryHandleTypeFlagBitsKHR #

clearBit :: VkExternalMemoryHandleTypeFlagBitsKHR -> Int -> VkExternalMemoryHandleTypeFlagBitsKHR #

complementBit :: VkExternalMemoryHandleTypeFlagBitsKHR -> Int -> VkExternalMemoryHandleTypeFlagBitsKHR #

testBit :: VkExternalMemoryHandleTypeFlagBitsKHR -> Int -> Bool #

bitSizeMaybe :: VkExternalMemoryHandleTypeFlagBitsKHR -> Maybe Int #

bitSize :: VkExternalMemoryHandleTypeFlagBitsKHR -> Int #

isSigned :: VkExternalMemoryHandleTypeFlagBitsKHR -> Bool #

shiftL :: VkExternalMemoryHandleTypeFlagBitsKHR -> Int -> VkExternalMemoryHandleTypeFlagBitsKHR #

unsafeShiftL :: VkExternalMemoryHandleTypeFlagBitsKHR -> Int -> VkExternalMemoryHandleTypeFlagBitsKHR #

shiftR :: VkExternalMemoryHandleTypeFlagBitsKHR -> Int -> VkExternalMemoryHandleTypeFlagBitsKHR #

unsafeShiftR :: VkExternalMemoryHandleTypeFlagBitsKHR -> Int -> VkExternalMemoryHandleTypeFlagBitsKHR #

rotateL :: VkExternalMemoryHandleTypeFlagBitsKHR -> Int -> VkExternalMemoryHandleTypeFlagBitsKHR #

rotateR :: VkExternalMemoryHandleTypeFlagBitsKHR -> Int -> VkExternalMemoryHandleTypeFlagBitsKHR #

popCount :: VkExternalMemoryHandleTypeFlagBitsKHR -> Int #

FiniteBits VkExternalMemoryHandleTypeFlagBitsKHR Source # 
type Rep VkExternalMemoryHandleTypeFlagBitsKHR Source # 
type Rep VkExternalMemoryHandleTypeFlagBitsKHR = D1 (MetaData "VkExternalMemoryHandleTypeFlagBitsKHR" "Graphics.Vulkan.Types.Enum.External" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkExternalMemoryHandleTypeFlagBitsKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkExternalMemoryHandleTypeBitmask a Source #

Instances

Bounded (VkExternalMemoryHandleTypeBitmask FlagMask) Source # 
Enum (VkExternalMemoryHandleTypeBitmask FlagMask) Source # 
Eq (VkExternalMemoryHandleTypeBitmask a) Source # 
Integral (VkExternalMemoryHandleTypeBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkExternalMemoryHandleTypeBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkExternalMemoryHandleTypeBitmask a -> c (VkExternalMemoryHandleTypeBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkExternalMemoryHandleTypeBitmask a) #

toConstr :: VkExternalMemoryHandleTypeBitmask a -> Constr #

dataTypeOf :: VkExternalMemoryHandleTypeBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkExternalMemoryHandleTypeBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkExternalMemoryHandleTypeBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkExternalMemoryHandleTypeBitmask a -> VkExternalMemoryHandleTypeBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkExternalMemoryHandleTypeBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkExternalMemoryHandleTypeBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkExternalMemoryHandleTypeBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkExternalMemoryHandleTypeBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkExternalMemoryHandleTypeBitmask a -> m (VkExternalMemoryHandleTypeBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkExternalMemoryHandleTypeBitmask a -> m (VkExternalMemoryHandleTypeBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkExternalMemoryHandleTypeBitmask a -> m (VkExternalMemoryHandleTypeBitmask a) #

Num (VkExternalMemoryHandleTypeBitmask FlagMask) Source # 
Ord (VkExternalMemoryHandleTypeBitmask a) Source # 
Read (VkExternalMemoryHandleTypeBitmask a) Source # 
Real (VkExternalMemoryHandleTypeBitmask FlagMask) Source # 
Show (VkExternalMemoryHandleTypeBitmask a) Source # 
Generic (VkExternalMemoryHandleTypeBitmask a) Source # 
Storable (VkExternalMemoryHandleTypeBitmask a) Source # 
Bits (VkExternalMemoryHandleTypeBitmask FlagMask) Source # 

Methods

(.&.) :: VkExternalMemoryHandleTypeBitmask FlagMask -> VkExternalMemoryHandleTypeBitmask FlagMask -> VkExternalMemoryHandleTypeBitmask FlagMask #

(.|.) :: VkExternalMemoryHandleTypeBitmask FlagMask -> VkExternalMemoryHandleTypeBitmask FlagMask -> VkExternalMemoryHandleTypeBitmask FlagMask #

xor :: VkExternalMemoryHandleTypeBitmask FlagMask -> VkExternalMemoryHandleTypeBitmask FlagMask -> VkExternalMemoryHandleTypeBitmask FlagMask #

complement :: VkExternalMemoryHandleTypeBitmask FlagMask -> VkExternalMemoryHandleTypeBitmask FlagMask #

shift :: VkExternalMemoryHandleTypeBitmask FlagMask -> Int -> VkExternalMemoryHandleTypeBitmask FlagMask #

rotate :: VkExternalMemoryHandleTypeBitmask FlagMask -> Int -> VkExternalMemoryHandleTypeBitmask FlagMask #

zeroBits :: VkExternalMemoryHandleTypeBitmask FlagMask #

bit :: Int -> VkExternalMemoryHandleTypeBitmask FlagMask #

setBit :: VkExternalMemoryHandleTypeBitmask FlagMask -> Int -> VkExternalMemoryHandleTypeBitmask FlagMask #

clearBit :: VkExternalMemoryHandleTypeBitmask FlagMask -> Int -> VkExternalMemoryHandleTypeBitmask FlagMask #

complementBit :: VkExternalMemoryHandleTypeBitmask FlagMask -> Int -> VkExternalMemoryHandleTypeBitmask FlagMask #

testBit :: VkExternalMemoryHandleTypeBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkExternalMemoryHandleTypeBitmask FlagMask -> Maybe Int #

bitSize :: VkExternalMemoryHandleTypeBitmask FlagMask -> Int #

isSigned :: VkExternalMemoryHandleTypeBitmask FlagMask -> Bool #

shiftL :: VkExternalMemoryHandleTypeBitmask FlagMask -> Int -> VkExternalMemoryHandleTypeBitmask FlagMask #

unsafeShiftL :: VkExternalMemoryHandleTypeBitmask FlagMask -> Int -> VkExternalMemoryHandleTypeBitmask FlagMask #

shiftR :: VkExternalMemoryHandleTypeBitmask FlagMask -> Int -> VkExternalMemoryHandleTypeBitmask FlagMask #

unsafeShiftR :: VkExternalMemoryHandleTypeBitmask FlagMask -> Int -> VkExternalMemoryHandleTypeBitmask FlagMask #

rotateL :: VkExternalMemoryHandleTypeBitmask FlagMask -> Int -> VkExternalMemoryHandleTypeBitmask FlagMask #

rotateR :: VkExternalMemoryHandleTypeBitmask FlagMask -> Int -> VkExternalMemoryHandleTypeBitmask FlagMask #

popCount :: VkExternalMemoryHandleTypeBitmask FlagMask -> Int #

FiniteBits (VkExternalMemoryHandleTypeBitmask FlagMask) Source # 
type Rep (VkExternalMemoryHandleTypeBitmask a) Source # 
type Rep (VkExternalMemoryHandleTypeBitmask a) = D1 (MetaData "VkExternalMemoryHandleTypeBitmask" "Graphics.Vulkan.Types.Enum.External" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkExternalMemoryHandleTypeBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkExternalMemoryHandleTypeBitmaskNV a Source #

Instances

Bounded (VkExternalMemoryHandleTypeBitmaskNV FlagMask) Source # 
Enum (VkExternalMemoryHandleTypeBitmaskNV FlagMask) Source # 
Eq (VkExternalMemoryHandleTypeBitmaskNV a) Source # 
Integral (VkExternalMemoryHandleTypeBitmaskNV FlagMask) Source # 
Typeable FlagType a => Data (VkExternalMemoryHandleTypeBitmaskNV a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkExternalMemoryHandleTypeBitmaskNV a -> c (VkExternalMemoryHandleTypeBitmaskNV a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkExternalMemoryHandleTypeBitmaskNV a) #

toConstr :: VkExternalMemoryHandleTypeBitmaskNV a -> Constr #

dataTypeOf :: VkExternalMemoryHandleTypeBitmaskNV a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkExternalMemoryHandleTypeBitmaskNV a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkExternalMemoryHandleTypeBitmaskNV a)) #

gmapT :: (forall b. Data b => b -> b) -> VkExternalMemoryHandleTypeBitmaskNV a -> VkExternalMemoryHandleTypeBitmaskNV a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkExternalMemoryHandleTypeBitmaskNV a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkExternalMemoryHandleTypeBitmaskNV a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkExternalMemoryHandleTypeBitmaskNV a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkExternalMemoryHandleTypeBitmaskNV a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkExternalMemoryHandleTypeBitmaskNV a -> m (VkExternalMemoryHandleTypeBitmaskNV a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkExternalMemoryHandleTypeBitmaskNV a -> m (VkExternalMemoryHandleTypeBitmaskNV a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkExternalMemoryHandleTypeBitmaskNV a -> m (VkExternalMemoryHandleTypeBitmaskNV a) #

Num (VkExternalMemoryHandleTypeBitmaskNV FlagMask) Source # 
Ord (VkExternalMemoryHandleTypeBitmaskNV a) Source # 
Read (VkExternalMemoryHandleTypeBitmaskNV a) Source # 
Real (VkExternalMemoryHandleTypeBitmaskNV FlagMask) Source # 
Show (VkExternalMemoryHandleTypeBitmaskNV a) Source # 
Generic (VkExternalMemoryHandleTypeBitmaskNV a) Source # 
Storable (VkExternalMemoryHandleTypeBitmaskNV a) Source # 
Bits (VkExternalMemoryHandleTypeBitmaskNV FlagMask) Source # 

Methods

(.&.) :: VkExternalMemoryHandleTypeBitmaskNV FlagMask -> VkExternalMemoryHandleTypeBitmaskNV FlagMask -> VkExternalMemoryHandleTypeBitmaskNV FlagMask #

(.|.) :: VkExternalMemoryHandleTypeBitmaskNV FlagMask -> VkExternalMemoryHandleTypeBitmaskNV FlagMask -> VkExternalMemoryHandleTypeBitmaskNV FlagMask #

xor :: VkExternalMemoryHandleTypeBitmaskNV FlagMask -> VkExternalMemoryHandleTypeBitmaskNV FlagMask -> VkExternalMemoryHandleTypeBitmaskNV FlagMask #

complement :: VkExternalMemoryHandleTypeBitmaskNV FlagMask -> VkExternalMemoryHandleTypeBitmaskNV FlagMask #

shift :: VkExternalMemoryHandleTypeBitmaskNV FlagMask -> Int -> VkExternalMemoryHandleTypeBitmaskNV FlagMask #

rotate :: VkExternalMemoryHandleTypeBitmaskNV FlagMask -> Int -> VkExternalMemoryHandleTypeBitmaskNV FlagMask #

zeroBits :: VkExternalMemoryHandleTypeBitmaskNV FlagMask #

bit :: Int -> VkExternalMemoryHandleTypeBitmaskNV FlagMask #

setBit :: VkExternalMemoryHandleTypeBitmaskNV FlagMask -> Int -> VkExternalMemoryHandleTypeBitmaskNV FlagMask #

clearBit :: VkExternalMemoryHandleTypeBitmaskNV FlagMask -> Int -> VkExternalMemoryHandleTypeBitmaskNV FlagMask #

complementBit :: VkExternalMemoryHandleTypeBitmaskNV FlagMask -> Int -> VkExternalMemoryHandleTypeBitmaskNV FlagMask #

testBit :: VkExternalMemoryHandleTypeBitmaskNV FlagMask -> Int -> Bool #

bitSizeMaybe :: VkExternalMemoryHandleTypeBitmaskNV FlagMask -> Maybe Int #

bitSize :: VkExternalMemoryHandleTypeBitmaskNV FlagMask -> Int #

isSigned :: VkExternalMemoryHandleTypeBitmaskNV FlagMask -> Bool #

shiftL :: VkExternalMemoryHandleTypeBitmaskNV FlagMask -> Int -> VkExternalMemoryHandleTypeBitmaskNV FlagMask #

unsafeShiftL :: VkExternalMemoryHandleTypeBitmaskNV FlagMask -> Int -> VkExternalMemoryHandleTypeBitmaskNV FlagMask #

shiftR :: VkExternalMemoryHandleTypeBitmaskNV FlagMask -> Int -> VkExternalMemoryHandleTypeBitmaskNV FlagMask #

unsafeShiftR :: VkExternalMemoryHandleTypeBitmaskNV FlagMask -> Int -> VkExternalMemoryHandleTypeBitmaskNV FlagMask #

rotateL :: VkExternalMemoryHandleTypeBitmaskNV FlagMask -> Int -> VkExternalMemoryHandleTypeBitmaskNV FlagMask #

rotateR :: VkExternalMemoryHandleTypeBitmaskNV FlagMask -> Int -> VkExternalMemoryHandleTypeBitmaskNV FlagMask #

popCount :: VkExternalMemoryHandleTypeBitmaskNV FlagMask -> Int #

FiniteBits (VkExternalMemoryHandleTypeBitmaskNV FlagMask) Source # 
type Rep (VkExternalMemoryHandleTypeBitmaskNV a) Source # 
type Rep (VkExternalMemoryHandleTypeBitmaskNV a) = D1 (MetaData "VkExternalMemoryHandleTypeBitmaskNV" "Graphics.Vulkan.Types.Enum.External" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkExternalMemoryHandleTypeBitmaskNV" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkExternalSemaphoreFeatureFlagBitsKHR Source #

Instances

Bounded VkExternalSemaphoreFeatureFlagBitsKHR Source # 
Enum VkExternalSemaphoreFeatureFlagBitsKHR Source # 
Eq VkExternalSemaphoreFeatureFlagBitsKHR Source # 
Integral VkExternalSemaphoreFeatureFlagBitsKHR Source # 
Data VkExternalSemaphoreFeatureFlagBitsKHR Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkExternalSemaphoreFeatureFlagBitsKHR -> c VkExternalSemaphoreFeatureFlagBitsKHR #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkExternalSemaphoreFeatureFlagBitsKHR #

toConstr :: VkExternalSemaphoreFeatureFlagBitsKHR -> Constr #

dataTypeOf :: VkExternalSemaphoreFeatureFlagBitsKHR -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkExternalSemaphoreFeatureFlagBitsKHR) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkExternalSemaphoreFeatureFlagBitsKHR) #

gmapT :: (forall b. Data b => b -> b) -> VkExternalSemaphoreFeatureFlagBitsKHR -> VkExternalSemaphoreFeatureFlagBitsKHR #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkExternalSemaphoreFeatureFlagBitsKHR -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkExternalSemaphoreFeatureFlagBitsKHR -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkExternalSemaphoreFeatureFlagBitsKHR -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkExternalSemaphoreFeatureFlagBitsKHR -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkExternalSemaphoreFeatureFlagBitsKHR -> m VkExternalSemaphoreFeatureFlagBitsKHR #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkExternalSemaphoreFeatureFlagBitsKHR -> m VkExternalSemaphoreFeatureFlagBitsKHR #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkExternalSemaphoreFeatureFlagBitsKHR -> m VkExternalSemaphoreFeatureFlagBitsKHR #

Num VkExternalSemaphoreFeatureFlagBitsKHR Source # 
Ord VkExternalSemaphoreFeatureFlagBitsKHR Source # 
Read VkExternalSemaphoreFeatureFlagBitsKHR Source # 
Real VkExternalSemaphoreFeatureFlagBitsKHR Source # 
Show VkExternalSemaphoreFeatureFlagBitsKHR Source # 
Generic VkExternalSemaphoreFeatureFlagBitsKHR Source # 
Storable VkExternalSemaphoreFeatureFlagBitsKHR Source # 
Bits VkExternalSemaphoreFeatureFlagBitsKHR Source # 

Methods

(.&.) :: VkExternalSemaphoreFeatureFlagBitsKHR -> VkExternalSemaphoreFeatureFlagBitsKHR -> VkExternalSemaphoreFeatureFlagBitsKHR #

(.|.) :: VkExternalSemaphoreFeatureFlagBitsKHR -> VkExternalSemaphoreFeatureFlagBitsKHR -> VkExternalSemaphoreFeatureFlagBitsKHR #

xor :: VkExternalSemaphoreFeatureFlagBitsKHR -> VkExternalSemaphoreFeatureFlagBitsKHR -> VkExternalSemaphoreFeatureFlagBitsKHR #

complement :: VkExternalSemaphoreFeatureFlagBitsKHR -> VkExternalSemaphoreFeatureFlagBitsKHR #

shift :: VkExternalSemaphoreFeatureFlagBitsKHR -> Int -> VkExternalSemaphoreFeatureFlagBitsKHR #

rotate :: VkExternalSemaphoreFeatureFlagBitsKHR -> Int -> VkExternalSemaphoreFeatureFlagBitsKHR #

zeroBits :: VkExternalSemaphoreFeatureFlagBitsKHR #

bit :: Int -> VkExternalSemaphoreFeatureFlagBitsKHR #

setBit :: VkExternalSemaphoreFeatureFlagBitsKHR -> Int -> VkExternalSemaphoreFeatureFlagBitsKHR #

clearBit :: VkExternalSemaphoreFeatureFlagBitsKHR -> Int -> VkExternalSemaphoreFeatureFlagBitsKHR #

complementBit :: VkExternalSemaphoreFeatureFlagBitsKHR -> Int -> VkExternalSemaphoreFeatureFlagBitsKHR #

testBit :: VkExternalSemaphoreFeatureFlagBitsKHR -> Int -> Bool #

bitSizeMaybe :: VkExternalSemaphoreFeatureFlagBitsKHR -> Maybe Int #

bitSize :: VkExternalSemaphoreFeatureFlagBitsKHR -> Int #

isSigned :: VkExternalSemaphoreFeatureFlagBitsKHR -> Bool #

shiftL :: VkExternalSemaphoreFeatureFlagBitsKHR -> Int -> VkExternalSemaphoreFeatureFlagBitsKHR #

unsafeShiftL :: VkExternalSemaphoreFeatureFlagBitsKHR -> Int -> VkExternalSemaphoreFeatureFlagBitsKHR #

shiftR :: VkExternalSemaphoreFeatureFlagBitsKHR -> Int -> VkExternalSemaphoreFeatureFlagBitsKHR #

unsafeShiftR :: VkExternalSemaphoreFeatureFlagBitsKHR -> Int -> VkExternalSemaphoreFeatureFlagBitsKHR #

rotateL :: VkExternalSemaphoreFeatureFlagBitsKHR -> Int -> VkExternalSemaphoreFeatureFlagBitsKHR #

rotateR :: VkExternalSemaphoreFeatureFlagBitsKHR -> Int -> VkExternalSemaphoreFeatureFlagBitsKHR #

popCount :: VkExternalSemaphoreFeatureFlagBitsKHR -> Int #

FiniteBits VkExternalSemaphoreFeatureFlagBitsKHR Source # 
type Rep VkExternalSemaphoreFeatureFlagBitsKHR Source # 
type Rep VkExternalSemaphoreFeatureFlagBitsKHR = D1 (MetaData "VkExternalSemaphoreFeatureFlagBitsKHR" "Graphics.Vulkan.Types.Enum.External" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkExternalSemaphoreFeatureFlagBitsKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkExternalSemaphoreFeatureBitmask a Source #

Instances

Bounded (VkExternalSemaphoreFeatureBitmask FlagMask) Source # 
Enum (VkExternalSemaphoreFeatureBitmask FlagMask) Source # 
Eq (VkExternalSemaphoreFeatureBitmask a) Source # 
Integral (VkExternalSemaphoreFeatureBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkExternalSemaphoreFeatureBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkExternalSemaphoreFeatureBitmask a -> c (VkExternalSemaphoreFeatureBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkExternalSemaphoreFeatureBitmask a) #

toConstr :: VkExternalSemaphoreFeatureBitmask a -> Constr #

dataTypeOf :: VkExternalSemaphoreFeatureBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkExternalSemaphoreFeatureBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkExternalSemaphoreFeatureBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkExternalSemaphoreFeatureBitmask a -> VkExternalSemaphoreFeatureBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkExternalSemaphoreFeatureBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkExternalSemaphoreFeatureBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkExternalSemaphoreFeatureBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkExternalSemaphoreFeatureBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkExternalSemaphoreFeatureBitmask a -> m (VkExternalSemaphoreFeatureBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkExternalSemaphoreFeatureBitmask a -> m (VkExternalSemaphoreFeatureBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkExternalSemaphoreFeatureBitmask a -> m (VkExternalSemaphoreFeatureBitmask a) #

Num (VkExternalSemaphoreFeatureBitmask FlagMask) Source # 
Ord (VkExternalSemaphoreFeatureBitmask a) Source # 
Read (VkExternalSemaphoreFeatureBitmask a) Source # 
Real (VkExternalSemaphoreFeatureBitmask FlagMask) Source # 
Show (VkExternalSemaphoreFeatureBitmask a) Source # 
Generic (VkExternalSemaphoreFeatureBitmask a) Source # 
Storable (VkExternalSemaphoreFeatureBitmask a) Source # 
Bits (VkExternalSemaphoreFeatureBitmask FlagMask) Source # 

Methods

(.&.) :: VkExternalSemaphoreFeatureBitmask FlagMask -> VkExternalSemaphoreFeatureBitmask FlagMask -> VkExternalSemaphoreFeatureBitmask FlagMask #

(.|.) :: VkExternalSemaphoreFeatureBitmask FlagMask -> VkExternalSemaphoreFeatureBitmask FlagMask -> VkExternalSemaphoreFeatureBitmask FlagMask #

xor :: VkExternalSemaphoreFeatureBitmask FlagMask -> VkExternalSemaphoreFeatureBitmask FlagMask -> VkExternalSemaphoreFeatureBitmask FlagMask #

complement :: VkExternalSemaphoreFeatureBitmask FlagMask -> VkExternalSemaphoreFeatureBitmask FlagMask #

shift :: VkExternalSemaphoreFeatureBitmask FlagMask -> Int -> VkExternalSemaphoreFeatureBitmask FlagMask #

rotate :: VkExternalSemaphoreFeatureBitmask FlagMask -> Int -> VkExternalSemaphoreFeatureBitmask FlagMask #

zeroBits :: VkExternalSemaphoreFeatureBitmask FlagMask #

bit :: Int -> VkExternalSemaphoreFeatureBitmask FlagMask #

setBit :: VkExternalSemaphoreFeatureBitmask FlagMask -> Int -> VkExternalSemaphoreFeatureBitmask FlagMask #

clearBit :: VkExternalSemaphoreFeatureBitmask FlagMask -> Int -> VkExternalSemaphoreFeatureBitmask FlagMask #

complementBit :: VkExternalSemaphoreFeatureBitmask FlagMask -> Int -> VkExternalSemaphoreFeatureBitmask FlagMask #

testBit :: VkExternalSemaphoreFeatureBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkExternalSemaphoreFeatureBitmask FlagMask -> Maybe Int #

bitSize :: VkExternalSemaphoreFeatureBitmask FlagMask -> Int #

isSigned :: VkExternalSemaphoreFeatureBitmask FlagMask -> Bool #

shiftL :: VkExternalSemaphoreFeatureBitmask FlagMask -> Int -> VkExternalSemaphoreFeatureBitmask FlagMask #

unsafeShiftL :: VkExternalSemaphoreFeatureBitmask FlagMask -> Int -> VkExternalSemaphoreFeatureBitmask FlagMask #

shiftR :: VkExternalSemaphoreFeatureBitmask FlagMask -> Int -> VkExternalSemaphoreFeatureBitmask FlagMask #

unsafeShiftR :: VkExternalSemaphoreFeatureBitmask FlagMask -> Int -> VkExternalSemaphoreFeatureBitmask FlagMask #

rotateL :: VkExternalSemaphoreFeatureBitmask FlagMask -> Int -> VkExternalSemaphoreFeatureBitmask FlagMask #

rotateR :: VkExternalSemaphoreFeatureBitmask FlagMask -> Int -> VkExternalSemaphoreFeatureBitmask FlagMask #

popCount :: VkExternalSemaphoreFeatureBitmask FlagMask -> Int #

FiniteBits (VkExternalSemaphoreFeatureBitmask FlagMask) Source # 
type Rep (VkExternalSemaphoreFeatureBitmask a) Source # 
type Rep (VkExternalSemaphoreFeatureBitmask a) = D1 (MetaData "VkExternalSemaphoreFeatureBitmask" "Graphics.Vulkan.Types.Enum.External" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkExternalSemaphoreFeatureBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkExternalSemaphoreHandleTypeFlagBitsKHR Source #

Instances

Bounded VkExternalSemaphoreHandleTypeFlagBitsKHR Source # 
Enum VkExternalSemaphoreHandleTypeFlagBitsKHR Source # 
Eq VkExternalSemaphoreHandleTypeFlagBitsKHR Source # 
Integral VkExternalSemaphoreHandleTypeFlagBitsKHR Source # 
Data VkExternalSemaphoreHandleTypeFlagBitsKHR Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkExternalSemaphoreHandleTypeFlagBitsKHR -> c VkExternalSemaphoreHandleTypeFlagBitsKHR #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkExternalSemaphoreHandleTypeFlagBitsKHR #

toConstr :: VkExternalSemaphoreHandleTypeFlagBitsKHR -> Constr #

dataTypeOf :: VkExternalSemaphoreHandleTypeFlagBitsKHR -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkExternalSemaphoreHandleTypeFlagBitsKHR) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkExternalSemaphoreHandleTypeFlagBitsKHR) #

gmapT :: (forall b. Data b => b -> b) -> VkExternalSemaphoreHandleTypeFlagBitsKHR -> VkExternalSemaphoreHandleTypeFlagBitsKHR #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkExternalSemaphoreHandleTypeFlagBitsKHR -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkExternalSemaphoreHandleTypeFlagBitsKHR -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkExternalSemaphoreHandleTypeFlagBitsKHR -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkExternalSemaphoreHandleTypeFlagBitsKHR -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkExternalSemaphoreHandleTypeFlagBitsKHR -> m VkExternalSemaphoreHandleTypeFlagBitsKHR #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkExternalSemaphoreHandleTypeFlagBitsKHR -> m VkExternalSemaphoreHandleTypeFlagBitsKHR #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkExternalSemaphoreHandleTypeFlagBitsKHR -> m VkExternalSemaphoreHandleTypeFlagBitsKHR #

Num VkExternalSemaphoreHandleTypeFlagBitsKHR Source # 
Ord VkExternalSemaphoreHandleTypeFlagBitsKHR Source # 
Read VkExternalSemaphoreHandleTypeFlagBitsKHR Source # 
Real VkExternalSemaphoreHandleTypeFlagBitsKHR Source # 
Show VkExternalSemaphoreHandleTypeFlagBitsKHR Source # 
Generic VkExternalSemaphoreHandleTypeFlagBitsKHR Source # 
Storable VkExternalSemaphoreHandleTypeFlagBitsKHR Source # 
Bits VkExternalSemaphoreHandleTypeFlagBitsKHR Source # 

Methods

(.&.) :: VkExternalSemaphoreHandleTypeFlagBitsKHR -> VkExternalSemaphoreHandleTypeFlagBitsKHR -> VkExternalSemaphoreHandleTypeFlagBitsKHR #

(.|.) :: VkExternalSemaphoreHandleTypeFlagBitsKHR -> VkExternalSemaphoreHandleTypeFlagBitsKHR -> VkExternalSemaphoreHandleTypeFlagBitsKHR #

xor :: VkExternalSemaphoreHandleTypeFlagBitsKHR -> VkExternalSemaphoreHandleTypeFlagBitsKHR -> VkExternalSemaphoreHandleTypeFlagBitsKHR #

complement :: VkExternalSemaphoreHandleTypeFlagBitsKHR -> VkExternalSemaphoreHandleTypeFlagBitsKHR #

shift :: VkExternalSemaphoreHandleTypeFlagBitsKHR -> Int -> VkExternalSemaphoreHandleTypeFlagBitsKHR #

rotate :: VkExternalSemaphoreHandleTypeFlagBitsKHR -> Int -> VkExternalSemaphoreHandleTypeFlagBitsKHR #

zeroBits :: VkExternalSemaphoreHandleTypeFlagBitsKHR #

bit :: Int -> VkExternalSemaphoreHandleTypeFlagBitsKHR #

setBit :: VkExternalSemaphoreHandleTypeFlagBitsKHR -> Int -> VkExternalSemaphoreHandleTypeFlagBitsKHR #

clearBit :: VkExternalSemaphoreHandleTypeFlagBitsKHR -> Int -> VkExternalSemaphoreHandleTypeFlagBitsKHR #

complementBit :: VkExternalSemaphoreHandleTypeFlagBitsKHR -> Int -> VkExternalSemaphoreHandleTypeFlagBitsKHR #

testBit :: VkExternalSemaphoreHandleTypeFlagBitsKHR -> Int -> Bool #

bitSizeMaybe :: VkExternalSemaphoreHandleTypeFlagBitsKHR -> Maybe Int #

bitSize :: VkExternalSemaphoreHandleTypeFlagBitsKHR -> Int #

isSigned :: VkExternalSemaphoreHandleTypeFlagBitsKHR -> Bool #

shiftL :: VkExternalSemaphoreHandleTypeFlagBitsKHR -> Int -> VkExternalSemaphoreHandleTypeFlagBitsKHR #

unsafeShiftL :: VkExternalSemaphoreHandleTypeFlagBitsKHR -> Int -> VkExternalSemaphoreHandleTypeFlagBitsKHR #

shiftR :: VkExternalSemaphoreHandleTypeFlagBitsKHR -> Int -> VkExternalSemaphoreHandleTypeFlagBitsKHR #

unsafeShiftR :: VkExternalSemaphoreHandleTypeFlagBitsKHR -> Int -> VkExternalSemaphoreHandleTypeFlagBitsKHR #

rotateL :: VkExternalSemaphoreHandleTypeFlagBitsKHR -> Int -> VkExternalSemaphoreHandleTypeFlagBitsKHR #

rotateR :: VkExternalSemaphoreHandleTypeFlagBitsKHR -> Int -> VkExternalSemaphoreHandleTypeFlagBitsKHR #

popCount :: VkExternalSemaphoreHandleTypeFlagBitsKHR -> Int #

FiniteBits VkExternalSemaphoreHandleTypeFlagBitsKHR Source # 
type Rep VkExternalSemaphoreHandleTypeFlagBitsKHR Source # 
type Rep VkExternalSemaphoreHandleTypeFlagBitsKHR = D1 (MetaData "VkExternalSemaphoreHandleTypeFlagBitsKHR" "Graphics.Vulkan.Types.Enum.External" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkExternalSemaphoreHandleTypeFlagBitsKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkExternalSemaphoreHandleTypeBitmask a Source #

Instances

Bounded (VkExternalSemaphoreHandleTypeBitmask FlagMask) Source # 
Enum (VkExternalSemaphoreHandleTypeBitmask FlagMask) Source # 
Eq (VkExternalSemaphoreHandleTypeBitmask a) Source # 
Integral (VkExternalSemaphoreHandleTypeBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkExternalSemaphoreHandleTypeBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkExternalSemaphoreHandleTypeBitmask a -> c (VkExternalSemaphoreHandleTypeBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkExternalSemaphoreHandleTypeBitmask a) #

toConstr :: VkExternalSemaphoreHandleTypeBitmask a -> Constr #

dataTypeOf :: VkExternalSemaphoreHandleTypeBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkExternalSemaphoreHandleTypeBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkExternalSemaphoreHandleTypeBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkExternalSemaphoreHandleTypeBitmask a -> VkExternalSemaphoreHandleTypeBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkExternalSemaphoreHandleTypeBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkExternalSemaphoreHandleTypeBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkExternalSemaphoreHandleTypeBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkExternalSemaphoreHandleTypeBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkExternalSemaphoreHandleTypeBitmask a -> m (VkExternalSemaphoreHandleTypeBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkExternalSemaphoreHandleTypeBitmask a -> m (VkExternalSemaphoreHandleTypeBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkExternalSemaphoreHandleTypeBitmask a -> m (VkExternalSemaphoreHandleTypeBitmask a) #

Num (VkExternalSemaphoreHandleTypeBitmask FlagMask) Source # 
Ord (VkExternalSemaphoreHandleTypeBitmask a) Source # 
Read (VkExternalSemaphoreHandleTypeBitmask a) Source # 
Real (VkExternalSemaphoreHandleTypeBitmask FlagMask) Source # 
Show (VkExternalSemaphoreHandleTypeBitmask a) Source # 
Generic (VkExternalSemaphoreHandleTypeBitmask a) Source # 
Storable (VkExternalSemaphoreHandleTypeBitmask a) Source # 
Bits (VkExternalSemaphoreHandleTypeBitmask FlagMask) Source # 

Methods

(.&.) :: VkExternalSemaphoreHandleTypeBitmask FlagMask -> VkExternalSemaphoreHandleTypeBitmask FlagMask -> VkExternalSemaphoreHandleTypeBitmask FlagMask #

(.|.) :: VkExternalSemaphoreHandleTypeBitmask FlagMask -> VkExternalSemaphoreHandleTypeBitmask FlagMask -> VkExternalSemaphoreHandleTypeBitmask FlagMask #

xor :: VkExternalSemaphoreHandleTypeBitmask FlagMask -> VkExternalSemaphoreHandleTypeBitmask FlagMask -> VkExternalSemaphoreHandleTypeBitmask FlagMask #

complement :: VkExternalSemaphoreHandleTypeBitmask FlagMask -> VkExternalSemaphoreHandleTypeBitmask FlagMask #

shift :: VkExternalSemaphoreHandleTypeBitmask FlagMask -> Int -> VkExternalSemaphoreHandleTypeBitmask FlagMask #

rotate :: VkExternalSemaphoreHandleTypeBitmask FlagMask -> Int -> VkExternalSemaphoreHandleTypeBitmask FlagMask #

zeroBits :: VkExternalSemaphoreHandleTypeBitmask FlagMask #

bit :: Int -> VkExternalSemaphoreHandleTypeBitmask FlagMask #

setBit :: VkExternalSemaphoreHandleTypeBitmask FlagMask -> Int -> VkExternalSemaphoreHandleTypeBitmask FlagMask #

clearBit :: VkExternalSemaphoreHandleTypeBitmask FlagMask -> Int -> VkExternalSemaphoreHandleTypeBitmask FlagMask #

complementBit :: VkExternalSemaphoreHandleTypeBitmask FlagMask -> Int -> VkExternalSemaphoreHandleTypeBitmask FlagMask #

testBit :: VkExternalSemaphoreHandleTypeBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkExternalSemaphoreHandleTypeBitmask FlagMask -> Maybe Int #

bitSize :: VkExternalSemaphoreHandleTypeBitmask FlagMask -> Int #

isSigned :: VkExternalSemaphoreHandleTypeBitmask FlagMask -> Bool #

shiftL :: VkExternalSemaphoreHandleTypeBitmask FlagMask -> Int -> VkExternalSemaphoreHandleTypeBitmask FlagMask #

unsafeShiftL :: VkExternalSemaphoreHandleTypeBitmask FlagMask -> Int -> VkExternalSemaphoreHandleTypeBitmask FlagMask #

shiftR :: VkExternalSemaphoreHandleTypeBitmask FlagMask -> Int -> VkExternalSemaphoreHandleTypeBitmask FlagMask #

unsafeShiftR :: VkExternalSemaphoreHandleTypeBitmask FlagMask -> Int -> VkExternalSemaphoreHandleTypeBitmask FlagMask #

rotateL :: VkExternalSemaphoreHandleTypeBitmask FlagMask -> Int -> VkExternalSemaphoreHandleTypeBitmask FlagMask #

rotateR :: VkExternalSemaphoreHandleTypeBitmask FlagMask -> Int -> VkExternalSemaphoreHandleTypeBitmask FlagMask #

popCount :: VkExternalSemaphoreHandleTypeBitmask FlagMask -> Int #

FiniteBits (VkExternalSemaphoreHandleTypeBitmask FlagMask) Source # 
type Rep (VkExternalSemaphoreHandleTypeBitmask a) Source # 
type Rep (VkExternalSemaphoreHandleTypeBitmask a) = D1 (MetaData "VkExternalSemaphoreHandleTypeBitmask" "Graphics.Vulkan.Types.Enum.External" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkExternalSemaphoreHandleTypeBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

type VkGetPhysicalDeviceExternalBufferProperties = "vkGetPhysicalDeviceExternalBufferProperties" Source #

type HS_vkGetPhysicalDeviceExternalBufferProperties Source #

Arguments

 = VkPhysicalDevice

physicalDevice

-> Ptr VkPhysicalDeviceExternalBufferInfo

pExternalBufferInfo

-> Ptr VkExternalBufferProperties

pExternalBufferProperties

-> IO () 
void vkGetPhysicalDeviceExternalBufferProperties
    ( VkPhysicalDevice physicalDevice
    , const VkPhysicalDeviceExternalBufferInfo* pExternalBufferInfo
    , VkExternalBufferProperties* pExternalBufferProperties
    )

vkGetPhysicalDeviceExternalBufferProperties registry at www.khronos.org

vkGetPhysicalDeviceExternalBufferProperties Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> Ptr VkPhysicalDeviceExternalBufferInfo

pExternalBufferInfo

-> Ptr VkExternalBufferProperties

pExternalBufferProperties

-> IO () 
void vkGetPhysicalDeviceExternalBufferProperties
    ( VkPhysicalDevice physicalDevice
    , const VkPhysicalDeviceExternalBufferInfo* pExternalBufferInfo
    , VkExternalBufferProperties* pExternalBufferProperties
    )

vkGetPhysicalDeviceExternalBufferProperties registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetPhysicalDeviceExternalBufferProperties <- vkGetInstanceProc @VkGetPhysicalDeviceExternalBufferProperties vkInstance

or less efficient:

myGetPhysicalDeviceExternalBufferProperties <- vkGetProc @VkGetPhysicalDeviceExternalBufferProperties

Note: vkGetPhysicalDeviceExternalBufferPropertiesUnsafe and vkGetPhysicalDeviceExternalBufferPropertiesSafe are the unsafe and safe FFI imports of this function, respectively. vkGetPhysicalDeviceExternalBufferProperties is an alias of vkGetPhysicalDeviceExternalBufferPropertiesUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetPhysicalDeviceExternalBufferPropertiesSafe.

vkGetPhysicalDeviceExternalBufferPropertiesUnsafe Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> Ptr VkPhysicalDeviceExternalBufferInfo

pExternalBufferInfo

-> Ptr VkExternalBufferProperties

pExternalBufferProperties

-> IO () 
void vkGetPhysicalDeviceExternalBufferProperties
    ( VkPhysicalDevice physicalDevice
    , const VkPhysicalDeviceExternalBufferInfo* pExternalBufferInfo
    , VkExternalBufferProperties* pExternalBufferProperties
    )

vkGetPhysicalDeviceExternalBufferProperties registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetPhysicalDeviceExternalBufferProperties <- vkGetInstanceProc @VkGetPhysicalDeviceExternalBufferProperties vkInstance

or less efficient:

myGetPhysicalDeviceExternalBufferProperties <- vkGetProc @VkGetPhysicalDeviceExternalBufferProperties

Note: vkGetPhysicalDeviceExternalBufferPropertiesUnsafe and vkGetPhysicalDeviceExternalBufferPropertiesSafe are the unsafe and safe FFI imports of this function, respectively. vkGetPhysicalDeviceExternalBufferProperties is an alias of vkGetPhysicalDeviceExternalBufferPropertiesUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetPhysicalDeviceExternalBufferPropertiesSafe.

vkGetPhysicalDeviceExternalBufferPropertiesSafe Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> Ptr VkPhysicalDeviceExternalBufferInfo

pExternalBufferInfo

-> Ptr VkExternalBufferProperties

pExternalBufferProperties

-> IO () 
void vkGetPhysicalDeviceExternalBufferProperties
    ( VkPhysicalDevice physicalDevice
    , const VkPhysicalDeviceExternalBufferInfo* pExternalBufferInfo
    , VkExternalBufferProperties* pExternalBufferProperties
    )

vkGetPhysicalDeviceExternalBufferProperties registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetPhysicalDeviceExternalBufferProperties <- vkGetInstanceProc @VkGetPhysicalDeviceExternalBufferProperties vkInstance

or less efficient:

myGetPhysicalDeviceExternalBufferProperties <- vkGetProc @VkGetPhysicalDeviceExternalBufferProperties

Note: vkGetPhysicalDeviceExternalBufferPropertiesUnsafe and vkGetPhysicalDeviceExternalBufferPropertiesSafe are the unsafe and safe FFI imports of this function, respectively. vkGetPhysicalDeviceExternalBufferProperties is an alias of vkGetPhysicalDeviceExternalBufferPropertiesUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetPhysicalDeviceExternalBufferPropertiesSafe.

pattern VK_LUID_SIZE :: forall a. (Num a, Eq a) => a Source #

Promoted from VK_KHR_external_memory

data VkExportFenceCreateInfo Source #

typedef struct VkExportFenceCreateInfo {
    VkStructureType sType;
    const void*                      pNext;
    VkExternalFenceHandleTypeFlags handleTypes;
} VkExportFenceCreateInfo;

VkExportFenceCreateInfo registry at www.khronos.org

Instances

Eq VkExportFenceCreateInfo Source # 
Ord VkExportFenceCreateInfo Source # 
Show VkExportFenceCreateInfo Source # 
Storable VkExportFenceCreateInfo Source # 
VulkanMarshalPrim VkExportFenceCreateInfo Source # 
VulkanMarshal VkExportFenceCreateInfo Source # 
CanWriteField "handleTypes" VkExportFenceCreateInfo Source # 
CanWriteField "pNext" VkExportFenceCreateInfo Source # 
CanWriteField "sType" VkExportFenceCreateInfo Source # 
CanReadField "handleTypes" VkExportFenceCreateInfo Source # 
CanReadField "pNext" VkExportFenceCreateInfo Source # 
CanReadField "sType" VkExportFenceCreateInfo Source # 
HasField "handleTypes" VkExportFenceCreateInfo Source # 
HasField "pNext" VkExportFenceCreateInfo Source # 
HasField "sType" VkExportFenceCreateInfo Source # 
type StructFields VkExportFenceCreateInfo Source # 
type StructFields VkExportFenceCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "handleTypes" ([] Symbol)))
type CUnionType VkExportFenceCreateInfo Source # 
type ReturnedOnly VkExportFenceCreateInfo Source # 
type StructExtends VkExportFenceCreateInfo Source # 
type FieldType "handleTypes" VkExportFenceCreateInfo Source # 
type FieldType "pNext" VkExportFenceCreateInfo Source # 
type FieldType "sType" VkExportFenceCreateInfo Source # 
type FieldOptional "handleTypes" VkExportFenceCreateInfo Source # 
type FieldOptional "pNext" VkExportFenceCreateInfo Source # 
type FieldOptional "sType" VkExportFenceCreateInfo Source # 
type FieldOffset "handleTypes" VkExportFenceCreateInfo Source # 
type FieldOffset "handleTypes" VkExportFenceCreateInfo = 16
type FieldOffset "pNext" VkExportFenceCreateInfo Source # 
type FieldOffset "sType" VkExportFenceCreateInfo Source # 
type FieldIsArray "handleTypes" VkExportFenceCreateInfo Source # 
type FieldIsArray "pNext" VkExportFenceCreateInfo Source # 
type FieldIsArray "sType" VkExportFenceCreateInfo Source # 

data VkExportMemoryAllocateInfo Source #

typedef struct VkExportMemoryAllocateInfo {
    VkStructureType sType;
    const void*                      pNext;
    VkExternalMemoryHandleTypeFlags handleTypes;
} VkExportMemoryAllocateInfo;

VkExportMemoryAllocateInfo registry at www.khronos.org

Instances

Eq VkExportMemoryAllocateInfo Source # 
Ord VkExportMemoryAllocateInfo Source # 
Show VkExportMemoryAllocateInfo Source # 
Storable VkExportMemoryAllocateInfo Source # 
VulkanMarshalPrim VkExportMemoryAllocateInfo Source # 
VulkanMarshal VkExportMemoryAllocateInfo Source # 
CanWriteField "handleTypes" VkExportMemoryAllocateInfo Source # 
CanWriteField "pNext" VkExportMemoryAllocateInfo Source # 
CanWriteField "sType" VkExportMemoryAllocateInfo Source # 
CanReadField "handleTypes" VkExportMemoryAllocateInfo Source # 
CanReadField "pNext" VkExportMemoryAllocateInfo Source # 
CanReadField "sType" VkExportMemoryAllocateInfo Source # 
HasField "handleTypes" VkExportMemoryAllocateInfo Source # 
HasField "pNext" VkExportMemoryAllocateInfo Source # 
HasField "sType" VkExportMemoryAllocateInfo Source # 
type StructFields VkExportMemoryAllocateInfo Source # 
type StructFields VkExportMemoryAllocateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "handleTypes" ([] Symbol)))
type CUnionType VkExportMemoryAllocateInfo Source # 
type ReturnedOnly VkExportMemoryAllocateInfo Source # 
type StructExtends VkExportMemoryAllocateInfo Source # 
type FieldType "handleTypes" VkExportMemoryAllocateInfo Source # 
type FieldType "pNext" VkExportMemoryAllocateInfo Source # 
type FieldType "sType" VkExportMemoryAllocateInfo Source # 
type FieldOptional "handleTypes" VkExportMemoryAllocateInfo Source # 
type FieldOptional "pNext" VkExportMemoryAllocateInfo Source # 
type FieldOptional "sType" VkExportMemoryAllocateInfo Source # 
type FieldOffset "handleTypes" VkExportMemoryAllocateInfo Source # 
type FieldOffset "handleTypes" VkExportMemoryAllocateInfo = 16
type FieldOffset "pNext" VkExportMemoryAllocateInfo Source # 
type FieldOffset "sType" VkExportMemoryAllocateInfo Source # 
type FieldIsArray "handleTypes" VkExportMemoryAllocateInfo Source # 
type FieldIsArray "pNext" VkExportMemoryAllocateInfo Source # 
type FieldIsArray "sType" VkExportMemoryAllocateInfo Source # 

data VkExportMemoryAllocateInfoNV Source #

typedef struct VkExportMemoryAllocateInfoNV {
    VkStructureType sType;
    const void*                      pNext;
    VkExternalMemoryHandleTypeFlagsNV handleTypes;
} VkExportMemoryAllocateInfoNV;

VkExportMemoryAllocateInfoNV registry at www.khronos.org

Instances

Eq VkExportMemoryAllocateInfoNV Source # 
Ord VkExportMemoryAllocateInfoNV Source # 
Show VkExportMemoryAllocateInfoNV Source # 
Storable VkExportMemoryAllocateInfoNV Source # 
VulkanMarshalPrim VkExportMemoryAllocateInfoNV Source # 
VulkanMarshal VkExportMemoryAllocateInfoNV Source # 
CanWriteField "handleTypes" VkExportMemoryAllocateInfoNV Source # 
CanWriteField "pNext" VkExportMemoryAllocateInfoNV Source # 
CanWriteField "sType" VkExportMemoryAllocateInfoNV Source # 
CanReadField "handleTypes" VkExportMemoryAllocateInfoNV Source # 
CanReadField "pNext" VkExportMemoryAllocateInfoNV Source # 
CanReadField "sType" VkExportMemoryAllocateInfoNV Source # 
HasField "handleTypes" VkExportMemoryAllocateInfoNV Source # 
HasField "pNext" VkExportMemoryAllocateInfoNV Source # 
HasField "sType" VkExportMemoryAllocateInfoNV Source # 
type StructFields VkExportMemoryAllocateInfoNV Source # 
type StructFields VkExportMemoryAllocateInfoNV = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "handleTypes" ([] Symbol)))
type CUnionType VkExportMemoryAllocateInfoNV Source # 
type ReturnedOnly VkExportMemoryAllocateInfoNV Source # 
type StructExtends VkExportMemoryAllocateInfoNV Source # 
type FieldType "handleTypes" VkExportMemoryAllocateInfoNV Source # 
type FieldType "pNext" VkExportMemoryAllocateInfoNV Source # 
type FieldType "sType" VkExportMemoryAllocateInfoNV Source # 
type FieldOptional "handleTypes" VkExportMemoryAllocateInfoNV Source # 
type FieldOptional "pNext" VkExportMemoryAllocateInfoNV Source # 
type FieldOptional "sType" VkExportMemoryAllocateInfoNV Source # 
type FieldOffset "handleTypes" VkExportMemoryAllocateInfoNV Source # 
type FieldOffset "pNext" VkExportMemoryAllocateInfoNV Source # 
type FieldOffset "sType" VkExportMemoryAllocateInfoNV Source # 
type FieldIsArray "handleTypes" VkExportMemoryAllocateInfoNV Source # 
type FieldIsArray "pNext" VkExportMemoryAllocateInfoNV Source # 
type FieldIsArray "sType" VkExportMemoryAllocateInfoNV Source # 

data VkExportSemaphoreCreateInfo Source #

typedef struct VkExportSemaphoreCreateInfo {
    VkStructureType sType;
    const void*                      pNext;
    VkExternalSemaphoreHandleTypeFlags handleTypes;
} VkExportSemaphoreCreateInfo;

VkExportSemaphoreCreateInfo registry at www.khronos.org

Instances

Eq VkExportSemaphoreCreateInfo Source # 
Ord VkExportSemaphoreCreateInfo Source # 
Show VkExportSemaphoreCreateInfo Source # 
Storable VkExportSemaphoreCreateInfo Source # 
VulkanMarshalPrim VkExportSemaphoreCreateInfo Source # 
VulkanMarshal VkExportSemaphoreCreateInfo Source # 
CanWriteField "handleTypes" VkExportSemaphoreCreateInfo Source # 
CanWriteField "pNext" VkExportSemaphoreCreateInfo Source # 
CanWriteField "sType" VkExportSemaphoreCreateInfo Source # 
CanReadField "handleTypes" VkExportSemaphoreCreateInfo Source # 
CanReadField "pNext" VkExportSemaphoreCreateInfo Source # 
CanReadField "sType" VkExportSemaphoreCreateInfo Source # 
HasField "handleTypes" VkExportSemaphoreCreateInfo Source # 
HasField "pNext" VkExportSemaphoreCreateInfo Source # 
HasField "sType" VkExportSemaphoreCreateInfo Source # 
type StructFields VkExportSemaphoreCreateInfo Source # 
type StructFields VkExportSemaphoreCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "handleTypes" ([] Symbol)))
type CUnionType VkExportSemaphoreCreateInfo Source # 
type ReturnedOnly VkExportSemaphoreCreateInfo Source # 
type StructExtends VkExportSemaphoreCreateInfo Source # 
type FieldType "handleTypes" VkExportSemaphoreCreateInfo Source # 
type FieldType "pNext" VkExportSemaphoreCreateInfo Source # 
type FieldType "sType" VkExportSemaphoreCreateInfo Source # 
type FieldOptional "handleTypes" VkExportSemaphoreCreateInfo Source # 
type FieldOptional "pNext" VkExportSemaphoreCreateInfo Source # 
type FieldOptional "sType" VkExportSemaphoreCreateInfo Source # 
type FieldOffset "handleTypes" VkExportSemaphoreCreateInfo Source # 
type FieldOffset "pNext" VkExportSemaphoreCreateInfo Source # 
type FieldOffset "sType" VkExportSemaphoreCreateInfo Source # 
type FieldIsArray "handleTypes" VkExportSemaphoreCreateInfo Source # 
type FieldIsArray "pNext" VkExportSemaphoreCreateInfo Source # 
type FieldIsArray "sType" VkExportSemaphoreCreateInfo Source # 

newtype VkSharingMode Source #

Constructors

VkSharingMode Int32 

Instances

Bounded VkSharingMode Source # 
Enum VkSharingMode Source # 
Eq VkSharingMode Source # 
Data VkSharingMode Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkSharingMode -> c VkSharingMode #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkSharingMode #

toConstr :: VkSharingMode -> Constr #

dataTypeOf :: VkSharingMode -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkSharingMode) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkSharingMode) #

gmapT :: (forall b. Data b => b -> b) -> VkSharingMode -> VkSharingMode #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkSharingMode -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkSharingMode -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkSharingMode -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkSharingMode -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkSharingMode -> m VkSharingMode #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSharingMode -> m VkSharingMode #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSharingMode -> m VkSharingMode #

Num VkSharingMode Source # 
Ord VkSharingMode Source # 
Read VkSharingMode Source # 
Show VkSharingMode Source # 
Generic VkSharingMode Source # 

Associated Types

type Rep VkSharingMode :: * -> * #

Storable VkSharingMode Source # 
type Rep VkSharingMode Source # 
type Rep VkSharingMode = D1 (MetaData "VkSharingMode" "Graphics.Vulkan.Types.Enum.SharingMode" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkSharingMode" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

Promoted from VK_KHR_external_fence_capabilities

#include "vk_platform.h"

type VkGetPhysicalDeviceExternalFenceProperties = "vkGetPhysicalDeviceExternalFenceProperties" Source #

type HS_vkGetPhysicalDeviceExternalFenceProperties Source #

Arguments

 = VkPhysicalDevice

physicalDevice

-> Ptr VkPhysicalDeviceExternalFenceInfo

pExternalFenceInfo

-> Ptr VkExternalFenceProperties

pExternalFenceProperties

-> IO () 
void vkGetPhysicalDeviceExternalFenceProperties
    ( VkPhysicalDevice physicalDevice
    , const VkPhysicalDeviceExternalFenceInfo* pExternalFenceInfo
    , VkExternalFenceProperties* pExternalFenceProperties
    )

vkGetPhysicalDeviceExternalFenceProperties registry at www.khronos.org

vkGetPhysicalDeviceExternalFenceProperties Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> Ptr VkPhysicalDeviceExternalFenceInfo

pExternalFenceInfo

-> Ptr VkExternalFenceProperties

pExternalFenceProperties

-> IO () 
void vkGetPhysicalDeviceExternalFenceProperties
    ( VkPhysicalDevice physicalDevice
    , const VkPhysicalDeviceExternalFenceInfo* pExternalFenceInfo
    , VkExternalFenceProperties* pExternalFenceProperties
    )

vkGetPhysicalDeviceExternalFenceProperties registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetPhysicalDeviceExternalFenceProperties <- vkGetInstanceProc @VkGetPhysicalDeviceExternalFenceProperties vkInstance

or less efficient:

myGetPhysicalDeviceExternalFenceProperties <- vkGetProc @VkGetPhysicalDeviceExternalFenceProperties

Note: vkGetPhysicalDeviceExternalFencePropertiesUnsafe and vkGetPhysicalDeviceExternalFencePropertiesSafe are the unsafe and safe FFI imports of this function, respectively. vkGetPhysicalDeviceExternalFenceProperties is an alias of vkGetPhysicalDeviceExternalFencePropertiesUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetPhysicalDeviceExternalFencePropertiesSafe.

vkGetPhysicalDeviceExternalFencePropertiesUnsafe Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> Ptr VkPhysicalDeviceExternalFenceInfo

pExternalFenceInfo

-> Ptr VkExternalFenceProperties

pExternalFenceProperties

-> IO () 
void vkGetPhysicalDeviceExternalFenceProperties
    ( VkPhysicalDevice physicalDevice
    , const VkPhysicalDeviceExternalFenceInfo* pExternalFenceInfo
    , VkExternalFenceProperties* pExternalFenceProperties
    )

vkGetPhysicalDeviceExternalFenceProperties registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetPhysicalDeviceExternalFenceProperties <- vkGetInstanceProc @VkGetPhysicalDeviceExternalFenceProperties vkInstance

or less efficient:

myGetPhysicalDeviceExternalFenceProperties <- vkGetProc @VkGetPhysicalDeviceExternalFenceProperties

Note: vkGetPhysicalDeviceExternalFencePropertiesUnsafe and vkGetPhysicalDeviceExternalFencePropertiesSafe are the unsafe and safe FFI imports of this function, respectively. vkGetPhysicalDeviceExternalFenceProperties is an alias of vkGetPhysicalDeviceExternalFencePropertiesUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetPhysicalDeviceExternalFencePropertiesSafe.

vkGetPhysicalDeviceExternalFencePropertiesSafe Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> Ptr VkPhysicalDeviceExternalFenceInfo

pExternalFenceInfo

-> Ptr VkExternalFenceProperties

pExternalFenceProperties

-> IO () 
void vkGetPhysicalDeviceExternalFenceProperties
    ( VkPhysicalDevice physicalDevice
    , const VkPhysicalDeviceExternalFenceInfo* pExternalFenceInfo
    , VkExternalFenceProperties* pExternalFenceProperties
    )

vkGetPhysicalDeviceExternalFenceProperties registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetPhysicalDeviceExternalFenceProperties <- vkGetInstanceProc @VkGetPhysicalDeviceExternalFenceProperties vkInstance

or less efficient:

myGetPhysicalDeviceExternalFenceProperties <- vkGetProc @VkGetPhysicalDeviceExternalFenceProperties

Note: vkGetPhysicalDeviceExternalFencePropertiesUnsafe and vkGetPhysicalDeviceExternalFencePropertiesSafe are the unsafe and safe FFI imports of this function, respectively. vkGetPhysicalDeviceExternalFenceProperties is an alias of vkGetPhysicalDeviceExternalFencePropertiesUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetPhysicalDeviceExternalFencePropertiesSafe.

Promoted from VK_KHR_external_fence

newtype VkFenceCreateBitmask a Source #

Instances

Bounded (VkFenceCreateBitmask FlagMask) Source # 
Enum (VkFenceCreateBitmask FlagMask) Source # 
Eq (VkFenceCreateBitmask a) Source # 
Integral (VkFenceCreateBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkFenceCreateBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkFenceCreateBitmask a -> c (VkFenceCreateBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkFenceCreateBitmask a) #

toConstr :: VkFenceCreateBitmask a -> Constr #

dataTypeOf :: VkFenceCreateBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkFenceCreateBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkFenceCreateBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkFenceCreateBitmask a -> VkFenceCreateBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkFenceCreateBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkFenceCreateBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkFenceCreateBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkFenceCreateBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkFenceCreateBitmask a -> m (VkFenceCreateBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkFenceCreateBitmask a -> m (VkFenceCreateBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkFenceCreateBitmask a -> m (VkFenceCreateBitmask a) #

Num (VkFenceCreateBitmask FlagMask) Source # 
Ord (VkFenceCreateBitmask a) Source # 
Read (VkFenceCreateBitmask a) Source # 
Real (VkFenceCreateBitmask FlagMask) Source # 
Show (VkFenceCreateBitmask a) Source # 
Generic (VkFenceCreateBitmask a) Source # 
Storable (VkFenceCreateBitmask a) Source # 
Bits (VkFenceCreateBitmask FlagMask) Source # 

Methods

(.&.) :: VkFenceCreateBitmask FlagMask -> VkFenceCreateBitmask FlagMask -> VkFenceCreateBitmask FlagMask #

(.|.) :: VkFenceCreateBitmask FlagMask -> VkFenceCreateBitmask FlagMask -> VkFenceCreateBitmask FlagMask #

xor :: VkFenceCreateBitmask FlagMask -> VkFenceCreateBitmask FlagMask -> VkFenceCreateBitmask FlagMask #

complement :: VkFenceCreateBitmask FlagMask -> VkFenceCreateBitmask FlagMask #

shift :: VkFenceCreateBitmask FlagMask -> Int -> VkFenceCreateBitmask FlagMask #

rotate :: VkFenceCreateBitmask FlagMask -> Int -> VkFenceCreateBitmask FlagMask #

zeroBits :: VkFenceCreateBitmask FlagMask #

bit :: Int -> VkFenceCreateBitmask FlagMask #

setBit :: VkFenceCreateBitmask FlagMask -> Int -> VkFenceCreateBitmask FlagMask #

clearBit :: VkFenceCreateBitmask FlagMask -> Int -> VkFenceCreateBitmask FlagMask #

complementBit :: VkFenceCreateBitmask FlagMask -> Int -> VkFenceCreateBitmask FlagMask #

testBit :: VkFenceCreateBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkFenceCreateBitmask FlagMask -> Maybe Int #

bitSize :: VkFenceCreateBitmask FlagMask -> Int #

isSigned :: VkFenceCreateBitmask FlagMask -> Bool #

shiftL :: VkFenceCreateBitmask FlagMask -> Int -> VkFenceCreateBitmask FlagMask #

unsafeShiftL :: VkFenceCreateBitmask FlagMask -> Int -> VkFenceCreateBitmask FlagMask #

shiftR :: VkFenceCreateBitmask FlagMask -> Int -> VkFenceCreateBitmask FlagMask #

unsafeShiftR :: VkFenceCreateBitmask FlagMask -> Int -> VkFenceCreateBitmask FlagMask #

rotateL :: VkFenceCreateBitmask FlagMask -> Int -> VkFenceCreateBitmask FlagMask #

rotateR :: VkFenceCreateBitmask FlagMask -> Int -> VkFenceCreateBitmask FlagMask #

popCount :: VkFenceCreateBitmask FlagMask -> Int #

FiniteBits (VkFenceCreateBitmask FlagMask) Source # 
type Rep (VkFenceCreateBitmask a) Source # 
type Rep (VkFenceCreateBitmask a) = D1 (MetaData "VkFenceCreateBitmask" "Graphics.Vulkan.Types.Enum.Fence" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkFenceCreateBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkFenceImportFlagBitsKHR Source #

Instances

Bounded VkFenceImportFlagBitsKHR Source # 
Enum VkFenceImportFlagBitsKHR Source # 
Eq VkFenceImportFlagBitsKHR Source # 
Integral VkFenceImportFlagBitsKHR Source # 
Data VkFenceImportFlagBitsKHR Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkFenceImportFlagBitsKHR -> c VkFenceImportFlagBitsKHR #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkFenceImportFlagBitsKHR #

toConstr :: VkFenceImportFlagBitsKHR -> Constr #

dataTypeOf :: VkFenceImportFlagBitsKHR -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkFenceImportFlagBitsKHR) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkFenceImportFlagBitsKHR) #

gmapT :: (forall b. Data b => b -> b) -> VkFenceImportFlagBitsKHR -> VkFenceImportFlagBitsKHR #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkFenceImportFlagBitsKHR -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkFenceImportFlagBitsKHR -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkFenceImportFlagBitsKHR -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkFenceImportFlagBitsKHR -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkFenceImportFlagBitsKHR -> m VkFenceImportFlagBitsKHR #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkFenceImportFlagBitsKHR -> m VkFenceImportFlagBitsKHR #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkFenceImportFlagBitsKHR -> m VkFenceImportFlagBitsKHR #

Num VkFenceImportFlagBitsKHR Source # 
Ord VkFenceImportFlagBitsKHR Source # 
Read VkFenceImportFlagBitsKHR Source # 
Real VkFenceImportFlagBitsKHR Source # 
Show VkFenceImportFlagBitsKHR Source # 
Generic VkFenceImportFlagBitsKHR Source # 
Storable VkFenceImportFlagBitsKHR Source # 
Bits VkFenceImportFlagBitsKHR Source # 
FiniteBits VkFenceImportFlagBitsKHR Source # 
type Rep VkFenceImportFlagBitsKHR Source # 
type Rep VkFenceImportFlagBitsKHR = D1 (MetaData "VkFenceImportFlagBitsKHR" "Graphics.Vulkan.Types.Enum.Fence" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkFenceImportFlagBitsKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkFenceImportBitmask a Source #

Instances

Bounded (VkFenceImportBitmask FlagMask) Source # 
Enum (VkFenceImportBitmask FlagMask) Source # 
Eq (VkFenceImportBitmask a) Source # 
Integral (VkFenceImportBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkFenceImportBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkFenceImportBitmask a -> c (VkFenceImportBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkFenceImportBitmask a) #

toConstr :: VkFenceImportBitmask a -> Constr #

dataTypeOf :: VkFenceImportBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkFenceImportBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkFenceImportBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkFenceImportBitmask a -> VkFenceImportBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkFenceImportBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkFenceImportBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkFenceImportBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkFenceImportBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkFenceImportBitmask a -> m (VkFenceImportBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkFenceImportBitmask a -> m (VkFenceImportBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkFenceImportBitmask a -> m (VkFenceImportBitmask a) #

Num (VkFenceImportBitmask FlagMask) Source # 
Ord (VkFenceImportBitmask a) Source # 
Read (VkFenceImportBitmask a) Source # 
Real (VkFenceImportBitmask FlagMask) Source # 
Show (VkFenceImportBitmask a) Source # 
Generic (VkFenceImportBitmask a) Source # 
Storable (VkFenceImportBitmask a) Source # 
Bits (VkFenceImportBitmask FlagMask) Source # 

Methods

(.&.) :: VkFenceImportBitmask FlagMask -> VkFenceImportBitmask FlagMask -> VkFenceImportBitmask FlagMask #

(.|.) :: VkFenceImportBitmask FlagMask -> VkFenceImportBitmask FlagMask -> VkFenceImportBitmask FlagMask #

xor :: VkFenceImportBitmask FlagMask -> VkFenceImportBitmask FlagMask -> VkFenceImportBitmask FlagMask #

complement :: VkFenceImportBitmask FlagMask -> VkFenceImportBitmask FlagMask #

shift :: VkFenceImportBitmask FlagMask -> Int -> VkFenceImportBitmask FlagMask #

rotate :: VkFenceImportBitmask FlagMask -> Int -> VkFenceImportBitmask FlagMask #

zeroBits :: VkFenceImportBitmask FlagMask #

bit :: Int -> VkFenceImportBitmask FlagMask #

setBit :: VkFenceImportBitmask FlagMask -> Int -> VkFenceImportBitmask FlagMask #

clearBit :: VkFenceImportBitmask FlagMask -> Int -> VkFenceImportBitmask FlagMask #

complementBit :: VkFenceImportBitmask FlagMask -> Int -> VkFenceImportBitmask FlagMask #

testBit :: VkFenceImportBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkFenceImportBitmask FlagMask -> Maybe Int #

bitSize :: VkFenceImportBitmask FlagMask -> Int #

isSigned :: VkFenceImportBitmask FlagMask -> Bool #

shiftL :: VkFenceImportBitmask FlagMask -> Int -> VkFenceImportBitmask FlagMask #

unsafeShiftL :: VkFenceImportBitmask FlagMask -> Int -> VkFenceImportBitmask FlagMask #

shiftR :: VkFenceImportBitmask FlagMask -> Int -> VkFenceImportBitmask FlagMask #

unsafeShiftR :: VkFenceImportBitmask FlagMask -> Int -> VkFenceImportBitmask FlagMask #

rotateL :: VkFenceImportBitmask FlagMask -> Int -> VkFenceImportBitmask FlagMask #

rotateR :: VkFenceImportBitmask FlagMask -> Int -> VkFenceImportBitmask FlagMask #

popCount :: VkFenceImportBitmask FlagMask -> Int #

FiniteBits (VkFenceImportBitmask FlagMask) Source # 
type Rep (VkFenceImportBitmask a) Source # 
type Rep (VkFenceImportBitmask a) = D1 (MetaData "VkFenceImportBitmask" "Graphics.Vulkan.Types.Enum.Fence" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkFenceImportBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

data VkFenceCreateInfo Source #

typedef struct VkFenceCreateInfo {
    VkStructureType sType;
    const void*            pNext;
    VkFenceCreateFlags     flags;
} VkFenceCreateInfo;

VkFenceCreateInfo registry at www.khronos.org

Instances

Eq VkFenceCreateInfo Source # 
Ord VkFenceCreateInfo Source # 
Show VkFenceCreateInfo Source # 
Storable VkFenceCreateInfo Source # 
VulkanMarshalPrim VkFenceCreateInfo Source # 
VulkanMarshal VkFenceCreateInfo Source # 
CanWriteField "flags" VkFenceCreateInfo Source # 
CanWriteField "pNext" VkFenceCreateInfo Source # 
CanWriteField "sType" VkFenceCreateInfo Source # 
CanReadField "flags" VkFenceCreateInfo Source # 
CanReadField "pNext" VkFenceCreateInfo Source # 
CanReadField "sType" VkFenceCreateInfo Source # 
HasField "flags" VkFenceCreateInfo Source # 
HasField "pNext" VkFenceCreateInfo Source # 
HasField "sType" VkFenceCreateInfo Source # 
type StructFields VkFenceCreateInfo Source # 
type StructFields VkFenceCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ([] Symbol)))
type CUnionType VkFenceCreateInfo Source # 
type ReturnedOnly VkFenceCreateInfo Source # 
type StructExtends VkFenceCreateInfo Source # 
type FieldType "flags" VkFenceCreateInfo Source # 
type FieldType "pNext" VkFenceCreateInfo Source # 
type FieldType "sType" VkFenceCreateInfo Source # 
type FieldOptional "flags" VkFenceCreateInfo Source # 
type FieldOptional "pNext" VkFenceCreateInfo Source # 
type FieldOptional "sType" VkFenceCreateInfo Source # 
type FieldOffset "flags" VkFenceCreateInfo Source # 
type FieldOffset "flags" VkFenceCreateInfo = 16
type FieldOffset "pNext" VkFenceCreateInfo Source # 
type FieldOffset "sType" VkFenceCreateInfo Source # 
type FieldIsArray "flags" VkFenceCreateInfo Source # 
type FieldIsArray "pNext" VkFenceCreateInfo Source # 
type FieldIsArray "sType" VkFenceCreateInfo Source # 

data VkFenceGetFdInfoKHR Source #

typedef struct VkFenceGetFdInfoKHR {
    VkStructureType sType;
    const void*                            pNext;
    VkFence                                fence;
    VkExternalFenceHandleTypeFlagBits   handleType;
} VkFenceGetFdInfoKHR;

VkFenceGetFdInfoKHR registry at www.khronos.org

Instances

Eq VkFenceGetFdInfoKHR Source # 
Ord VkFenceGetFdInfoKHR Source # 
Show VkFenceGetFdInfoKHR Source # 
Storable VkFenceGetFdInfoKHR Source # 
VulkanMarshalPrim VkFenceGetFdInfoKHR Source # 
VulkanMarshal VkFenceGetFdInfoKHR Source # 
CanWriteField "fence" VkFenceGetFdInfoKHR Source # 
CanWriteField "handleType" VkFenceGetFdInfoKHR Source # 
CanWriteField "pNext" VkFenceGetFdInfoKHR Source # 
CanWriteField "sType" VkFenceGetFdInfoKHR Source # 
CanReadField "fence" VkFenceGetFdInfoKHR Source # 
CanReadField "handleType" VkFenceGetFdInfoKHR Source # 
CanReadField "pNext" VkFenceGetFdInfoKHR Source # 
CanReadField "sType" VkFenceGetFdInfoKHR Source # 
HasField "fence" VkFenceGetFdInfoKHR Source # 
HasField "handleType" VkFenceGetFdInfoKHR Source # 

Associated Types

type FieldType ("handleType" :: Symbol) VkFenceGetFdInfoKHR :: Type Source #

type FieldOptional ("handleType" :: Symbol) VkFenceGetFdInfoKHR :: Bool Source #

type FieldOffset ("handleType" :: Symbol) VkFenceGetFdInfoKHR :: Nat Source #

type FieldIsArray ("handleType" :: Symbol) VkFenceGetFdInfoKHR :: Bool Source #

HasField "pNext" VkFenceGetFdInfoKHR Source # 
HasField "sType" VkFenceGetFdInfoKHR Source # 
type StructFields VkFenceGetFdInfoKHR Source # 
type StructFields VkFenceGetFdInfoKHR = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "fence" ((:) Symbol "handleType" ([] Symbol))))
type CUnionType VkFenceGetFdInfoKHR Source # 
type ReturnedOnly VkFenceGetFdInfoKHR Source # 
type StructExtends VkFenceGetFdInfoKHR Source # 
type FieldType "fence" VkFenceGetFdInfoKHR Source # 
type FieldType "handleType" VkFenceGetFdInfoKHR Source # 
type FieldType "pNext" VkFenceGetFdInfoKHR Source # 
type FieldType "sType" VkFenceGetFdInfoKHR Source # 
type FieldOptional "fence" VkFenceGetFdInfoKHR Source # 
type FieldOptional "handleType" VkFenceGetFdInfoKHR Source # 
type FieldOptional "pNext" VkFenceGetFdInfoKHR Source # 
type FieldOptional "sType" VkFenceGetFdInfoKHR Source # 
type FieldOffset "fence" VkFenceGetFdInfoKHR Source # 
type FieldOffset "handleType" VkFenceGetFdInfoKHR Source # 
type FieldOffset "handleType" VkFenceGetFdInfoKHR = 24
type FieldOffset "pNext" VkFenceGetFdInfoKHR Source # 
type FieldOffset "sType" VkFenceGetFdInfoKHR Source # 
type FieldIsArray "fence" VkFenceGetFdInfoKHR Source # 
type FieldIsArray "handleType" VkFenceGetFdInfoKHR Source # 
type FieldIsArray "pNext" VkFenceGetFdInfoKHR Source # 
type FieldIsArray "sType" VkFenceGetFdInfoKHR Source # 

Promoted from VK_KHR_external_semaphore

data VkSemaphoreCreateInfo Source #

typedef struct VkSemaphoreCreateInfo {
    VkStructureType sType;
    const void*            pNext;
    VkSemaphoreCreateFlags flags;
} VkSemaphoreCreateInfo;

VkSemaphoreCreateInfo registry at www.khronos.org

Instances

Eq VkSemaphoreCreateInfo Source # 
Ord VkSemaphoreCreateInfo Source # 
Show VkSemaphoreCreateInfo Source # 
Storable VkSemaphoreCreateInfo Source # 
VulkanMarshalPrim VkSemaphoreCreateInfo Source # 
VulkanMarshal VkSemaphoreCreateInfo Source # 
CanWriteField "flags" VkSemaphoreCreateInfo Source # 
CanWriteField "pNext" VkSemaphoreCreateInfo Source # 
CanWriteField "sType" VkSemaphoreCreateInfo Source # 
CanReadField "flags" VkSemaphoreCreateInfo Source # 
CanReadField "pNext" VkSemaphoreCreateInfo Source # 
CanReadField "sType" VkSemaphoreCreateInfo Source # 
HasField "flags" VkSemaphoreCreateInfo Source # 
HasField "pNext" VkSemaphoreCreateInfo Source # 
HasField "sType" VkSemaphoreCreateInfo Source # 
type StructFields VkSemaphoreCreateInfo Source # 
type StructFields VkSemaphoreCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ([] Symbol)))
type CUnionType VkSemaphoreCreateInfo Source # 
type ReturnedOnly VkSemaphoreCreateInfo Source # 
type StructExtends VkSemaphoreCreateInfo Source # 
type FieldType "flags" VkSemaphoreCreateInfo Source # 
type FieldType "pNext" VkSemaphoreCreateInfo Source # 
type FieldType "sType" VkSemaphoreCreateInfo Source # 
type FieldOptional "flags" VkSemaphoreCreateInfo Source # 
type FieldOptional "pNext" VkSemaphoreCreateInfo Source # 
type FieldOptional "sType" VkSemaphoreCreateInfo Source # 
type FieldOffset "flags" VkSemaphoreCreateInfo Source # 
type FieldOffset "pNext" VkSemaphoreCreateInfo Source # 
type FieldOffset "sType" VkSemaphoreCreateInfo Source # 
type FieldIsArray "flags" VkSemaphoreCreateInfo Source # 
type FieldIsArray "pNext" VkSemaphoreCreateInfo Source # 
type FieldIsArray "sType" VkSemaphoreCreateInfo Source # 

data VkSemaphoreGetFdInfoKHR Source #

typedef struct VkSemaphoreGetFdInfoKHR {
    VkStructureType sType;
    const void*                      pNext;
    VkSemaphore                      semaphore;
    VkExternalSemaphoreHandleTypeFlagBits handleType;
} VkSemaphoreGetFdInfoKHR;

VkSemaphoreGetFdInfoKHR registry at www.khronos.org

Instances

Eq VkSemaphoreGetFdInfoKHR Source # 
Ord VkSemaphoreGetFdInfoKHR Source # 
Show VkSemaphoreGetFdInfoKHR Source # 
Storable VkSemaphoreGetFdInfoKHR Source # 
VulkanMarshalPrim VkSemaphoreGetFdInfoKHR Source # 
VulkanMarshal VkSemaphoreGetFdInfoKHR Source # 
CanWriteField "handleType" VkSemaphoreGetFdInfoKHR Source # 
CanWriteField "pNext" VkSemaphoreGetFdInfoKHR Source # 
CanWriteField "sType" VkSemaphoreGetFdInfoKHR Source # 
CanWriteField "semaphore" VkSemaphoreGetFdInfoKHR Source # 
CanReadField "handleType" VkSemaphoreGetFdInfoKHR Source # 
CanReadField "pNext" VkSemaphoreGetFdInfoKHR Source # 
CanReadField "sType" VkSemaphoreGetFdInfoKHR Source # 
CanReadField "semaphore" VkSemaphoreGetFdInfoKHR Source # 
HasField "handleType" VkSemaphoreGetFdInfoKHR Source # 
HasField "pNext" VkSemaphoreGetFdInfoKHR Source # 
HasField "sType" VkSemaphoreGetFdInfoKHR Source # 
HasField "semaphore" VkSemaphoreGetFdInfoKHR Source # 
type StructFields VkSemaphoreGetFdInfoKHR Source # 
type StructFields VkSemaphoreGetFdInfoKHR = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "semaphore" ((:) Symbol "handleType" ([] Symbol))))
type CUnionType VkSemaphoreGetFdInfoKHR Source # 
type ReturnedOnly VkSemaphoreGetFdInfoKHR Source # 
type StructExtends VkSemaphoreGetFdInfoKHR Source # 
type FieldType "handleType" VkSemaphoreGetFdInfoKHR Source # 
type FieldType "pNext" VkSemaphoreGetFdInfoKHR Source # 
type FieldType "sType" VkSemaphoreGetFdInfoKHR Source # 
type FieldType "semaphore" VkSemaphoreGetFdInfoKHR Source # 
type FieldOptional "handleType" VkSemaphoreGetFdInfoKHR Source # 
type FieldOptional "pNext" VkSemaphoreGetFdInfoKHR Source # 
type FieldOptional "sType" VkSemaphoreGetFdInfoKHR Source # 
type FieldOptional "semaphore" VkSemaphoreGetFdInfoKHR Source # 
type FieldOffset "handleType" VkSemaphoreGetFdInfoKHR Source # 
type FieldOffset "handleType" VkSemaphoreGetFdInfoKHR = 24
type FieldOffset "pNext" VkSemaphoreGetFdInfoKHR Source # 
type FieldOffset "sType" VkSemaphoreGetFdInfoKHR Source # 
type FieldOffset "semaphore" VkSemaphoreGetFdInfoKHR Source # 
type FieldOffset "semaphore" VkSemaphoreGetFdInfoKHR = 16
type FieldIsArray "handleType" VkSemaphoreGetFdInfoKHR Source # 
type FieldIsArray "pNext" VkSemaphoreGetFdInfoKHR Source # 
type FieldIsArray "sType" VkSemaphoreGetFdInfoKHR Source # 
type FieldIsArray "semaphore" VkSemaphoreGetFdInfoKHR Source # 

newtype VkSemaphoreImportFlagBitsKHR Source #

Instances

Bounded VkSemaphoreImportFlagBitsKHR Source # 
Enum VkSemaphoreImportFlagBitsKHR Source # 
Eq VkSemaphoreImportFlagBitsKHR Source # 
Integral VkSemaphoreImportFlagBitsKHR Source # 
Data VkSemaphoreImportFlagBitsKHR Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkSemaphoreImportFlagBitsKHR -> c VkSemaphoreImportFlagBitsKHR #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VkSemaphoreImportFlagBitsKHR #

toConstr :: VkSemaphoreImportFlagBitsKHR -> Constr #

dataTypeOf :: VkSemaphoreImportFlagBitsKHR -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VkSemaphoreImportFlagBitsKHR) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkSemaphoreImportFlagBitsKHR) #

gmapT :: (forall b. Data b => b -> b) -> VkSemaphoreImportFlagBitsKHR -> VkSemaphoreImportFlagBitsKHR #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkSemaphoreImportFlagBitsKHR -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkSemaphoreImportFlagBitsKHR -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkSemaphoreImportFlagBitsKHR -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkSemaphoreImportFlagBitsKHR -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkSemaphoreImportFlagBitsKHR -> m VkSemaphoreImportFlagBitsKHR #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSemaphoreImportFlagBitsKHR -> m VkSemaphoreImportFlagBitsKHR #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSemaphoreImportFlagBitsKHR -> m VkSemaphoreImportFlagBitsKHR #

Num VkSemaphoreImportFlagBitsKHR Source # 
Ord VkSemaphoreImportFlagBitsKHR Source # 
Read VkSemaphoreImportFlagBitsKHR Source # 
Real VkSemaphoreImportFlagBitsKHR Source # 
Show VkSemaphoreImportFlagBitsKHR Source # 
Generic VkSemaphoreImportFlagBitsKHR Source # 
Storable VkSemaphoreImportFlagBitsKHR Source # 
Bits VkSemaphoreImportFlagBitsKHR Source # 

Methods

(.&.) :: VkSemaphoreImportFlagBitsKHR -> VkSemaphoreImportFlagBitsKHR -> VkSemaphoreImportFlagBitsKHR #

(.|.) :: VkSemaphoreImportFlagBitsKHR -> VkSemaphoreImportFlagBitsKHR -> VkSemaphoreImportFlagBitsKHR #

xor :: VkSemaphoreImportFlagBitsKHR -> VkSemaphoreImportFlagBitsKHR -> VkSemaphoreImportFlagBitsKHR #

complement :: VkSemaphoreImportFlagBitsKHR -> VkSemaphoreImportFlagBitsKHR #

shift :: VkSemaphoreImportFlagBitsKHR -> Int -> VkSemaphoreImportFlagBitsKHR #

rotate :: VkSemaphoreImportFlagBitsKHR -> Int -> VkSemaphoreImportFlagBitsKHR #

zeroBits :: VkSemaphoreImportFlagBitsKHR #

bit :: Int -> VkSemaphoreImportFlagBitsKHR #

setBit :: VkSemaphoreImportFlagBitsKHR -> Int -> VkSemaphoreImportFlagBitsKHR #

clearBit :: VkSemaphoreImportFlagBitsKHR -> Int -> VkSemaphoreImportFlagBitsKHR #

complementBit :: VkSemaphoreImportFlagBitsKHR -> Int -> VkSemaphoreImportFlagBitsKHR #

testBit :: VkSemaphoreImportFlagBitsKHR -> Int -> Bool #

bitSizeMaybe :: VkSemaphoreImportFlagBitsKHR -> Maybe Int #

bitSize :: VkSemaphoreImportFlagBitsKHR -> Int #

isSigned :: VkSemaphoreImportFlagBitsKHR -> Bool #

shiftL :: VkSemaphoreImportFlagBitsKHR -> Int -> VkSemaphoreImportFlagBitsKHR #

unsafeShiftL :: VkSemaphoreImportFlagBitsKHR -> Int -> VkSemaphoreImportFlagBitsKHR #

shiftR :: VkSemaphoreImportFlagBitsKHR -> Int -> VkSemaphoreImportFlagBitsKHR #

unsafeShiftR :: VkSemaphoreImportFlagBitsKHR -> Int -> VkSemaphoreImportFlagBitsKHR #

rotateL :: VkSemaphoreImportFlagBitsKHR -> Int -> VkSemaphoreImportFlagBitsKHR #

rotateR :: VkSemaphoreImportFlagBitsKHR -> Int -> VkSemaphoreImportFlagBitsKHR #

popCount :: VkSemaphoreImportFlagBitsKHR -> Int #

FiniteBits VkSemaphoreImportFlagBitsKHR Source # 
type Rep VkSemaphoreImportFlagBitsKHR Source # 
type Rep VkSemaphoreImportFlagBitsKHR = D1 (MetaData "VkSemaphoreImportFlagBitsKHR" "Graphics.Vulkan.Types.Enum.SemaphoreImportFlag" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkSemaphoreImportFlagBitsKHR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

newtype VkSemaphoreImportBitmask a Source #

Instances

Bounded (VkSemaphoreImportBitmask FlagMask) Source # 
Enum (VkSemaphoreImportBitmask FlagMask) Source # 
Eq (VkSemaphoreImportBitmask a) Source # 
Integral (VkSemaphoreImportBitmask FlagMask) Source # 
Typeable FlagType a => Data (VkSemaphoreImportBitmask a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VkSemaphoreImportBitmask a -> c (VkSemaphoreImportBitmask a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VkSemaphoreImportBitmask a) #

toConstr :: VkSemaphoreImportBitmask a -> Constr #

dataTypeOf :: VkSemaphoreImportBitmask a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VkSemaphoreImportBitmask a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VkSemaphoreImportBitmask a)) #

gmapT :: (forall b. Data b => b -> b) -> VkSemaphoreImportBitmask a -> VkSemaphoreImportBitmask a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VkSemaphoreImportBitmask a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VkSemaphoreImportBitmask a -> r #

gmapQ :: (forall d. Data d => d -> u) -> VkSemaphoreImportBitmask a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VkSemaphoreImportBitmask a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VkSemaphoreImportBitmask a -> m (VkSemaphoreImportBitmask a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSemaphoreImportBitmask a -> m (VkSemaphoreImportBitmask a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VkSemaphoreImportBitmask a -> m (VkSemaphoreImportBitmask a) #

Num (VkSemaphoreImportBitmask FlagMask) Source # 
Ord (VkSemaphoreImportBitmask a) Source # 
Read (VkSemaphoreImportBitmask a) Source # 
Real (VkSemaphoreImportBitmask FlagMask) Source # 
Show (VkSemaphoreImportBitmask a) Source # 
Generic (VkSemaphoreImportBitmask a) Source # 
Storable (VkSemaphoreImportBitmask a) Source # 
Bits (VkSemaphoreImportBitmask FlagMask) Source # 

Methods

(.&.) :: VkSemaphoreImportBitmask FlagMask -> VkSemaphoreImportBitmask FlagMask -> VkSemaphoreImportBitmask FlagMask #

(.|.) :: VkSemaphoreImportBitmask FlagMask -> VkSemaphoreImportBitmask FlagMask -> VkSemaphoreImportBitmask FlagMask #

xor :: VkSemaphoreImportBitmask FlagMask -> VkSemaphoreImportBitmask FlagMask -> VkSemaphoreImportBitmask FlagMask #

complement :: VkSemaphoreImportBitmask FlagMask -> VkSemaphoreImportBitmask FlagMask #

shift :: VkSemaphoreImportBitmask FlagMask -> Int -> VkSemaphoreImportBitmask FlagMask #

rotate :: VkSemaphoreImportBitmask FlagMask -> Int -> VkSemaphoreImportBitmask FlagMask #

zeroBits :: VkSemaphoreImportBitmask FlagMask #

bit :: Int -> VkSemaphoreImportBitmask FlagMask #

setBit :: VkSemaphoreImportBitmask FlagMask -> Int -> VkSemaphoreImportBitmask FlagMask #

clearBit :: VkSemaphoreImportBitmask FlagMask -> Int -> VkSemaphoreImportBitmask FlagMask #

complementBit :: VkSemaphoreImportBitmask FlagMask -> Int -> VkSemaphoreImportBitmask FlagMask #

testBit :: VkSemaphoreImportBitmask FlagMask -> Int -> Bool #

bitSizeMaybe :: VkSemaphoreImportBitmask FlagMask -> Maybe Int #

bitSize :: VkSemaphoreImportBitmask FlagMask -> Int #

isSigned :: VkSemaphoreImportBitmask FlagMask -> Bool #

shiftL :: VkSemaphoreImportBitmask FlagMask -> Int -> VkSemaphoreImportBitmask FlagMask #

unsafeShiftL :: VkSemaphoreImportBitmask FlagMask -> Int -> VkSemaphoreImportBitmask FlagMask #

shiftR :: VkSemaphoreImportBitmask FlagMask -> Int -> VkSemaphoreImportBitmask FlagMask #

unsafeShiftR :: VkSemaphoreImportBitmask FlagMask -> Int -> VkSemaphoreImportBitmask FlagMask #

rotateL :: VkSemaphoreImportBitmask FlagMask -> Int -> VkSemaphoreImportBitmask FlagMask #

rotateR :: VkSemaphoreImportBitmask FlagMask -> Int -> VkSemaphoreImportBitmask FlagMask #

popCount :: VkSemaphoreImportBitmask FlagMask -> Int #

FiniteBits (VkSemaphoreImportBitmask FlagMask) Source # 
type Rep (VkSemaphoreImportBitmask a) Source # 
type Rep (VkSemaphoreImportBitmask a) = D1 (MetaData "VkSemaphoreImportBitmask" "Graphics.Vulkan.Types.Enum.SemaphoreImportFlag" "vulkan-api-1.1.3.0-FHhzd5k5VLu5phG4JhXQzZ" True) (C1 (MetaCons "VkSemaphoreImportBitmask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VkFlags)))

Promoted from VK_KHR_external_semaphore_capabilities

#include "vk_platform.h"

type VkGetPhysicalDeviceExternalSemaphoreProperties = "vkGetPhysicalDeviceExternalSemaphoreProperties" Source #

type HS_vkGetPhysicalDeviceExternalSemaphoreProperties Source #

Arguments

 = VkPhysicalDevice

physicalDevice

-> Ptr VkPhysicalDeviceExternalSemaphoreInfo

pExternalSemaphoreInfo

-> Ptr VkExternalSemaphoreProperties

pExternalSemaphoreProperties

-> IO () 
void vkGetPhysicalDeviceExternalSemaphoreProperties
    ( VkPhysicalDevice physicalDevice
    , const VkPhysicalDeviceExternalSemaphoreInfo* pExternalSemaphoreInfo
    , VkExternalSemaphoreProperties* pExternalSemaphoreProperties
    )

vkGetPhysicalDeviceExternalSemaphoreProperties registry at www.khronos.org

vkGetPhysicalDeviceExternalSemaphoreProperties Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> Ptr VkPhysicalDeviceExternalSemaphoreInfo

pExternalSemaphoreInfo

-> Ptr VkExternalSemaphoreProperties

pExternalSemaphoreProperties

-> IO () 
void vkGetPhysicalDeviceExternalSemaphoreProperties
    ( VkPhysicalDevice physicalDevice
    , const VkPhysicalDeviceExternalSemaphoreInfo* pExternalSemaphoreInfo
    , VkExternalSemaphoreProperties* pExternalSemaphoreProperties
    )

vkGetPhysicalDeviceExternalSemaphoreProperties registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetPhysicalDeviceExternalSemaphoreProperties <- vkGetInstanceProc @VkGetPhysicalDeviceExternalSemaphoreProperties vkInstance

or less efficient:

myGetPhysicalDeviceExternalSemaphoreProperties <- vkGetProc @VkGetPhysicalDeviceExternalSemaphoreProperties

Note: vkGetPhysicalDeviceExternalSemaphorePropertiesUnsafe and vkGetPhysicalDeviceExternalSemaphorePropertiesSafe are the unsafe and safe FFI imports of this function, respectively. vkGetPhysicalDeviceExternalSemaphoreProperties is an alias of vkGetPhysicalDeviceExternalSemaphorePropertiesUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetPhysicalDeviceExternalSemaphorePropertiesSafe.

vkGetPhysicalDeviceExternalSemaphorePropertiesUnsafe Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> Ptr VkPhysicalDeviceExternalSemaphoreInfo

pExternalSemaphoreInfo

-> Ptr VkExternalSemaphoreProperties

pExternalSemaphoreProperties

-> IO () 
void vkGetPhysicalDeviceExternalSemaphoreProperties
    ( VkPhysicalDevice physicalDevice
    , const VkPhysicalDeviceExternalSemaphoreInfo* pExternalSemaphoreInfo
    , VkExternalSemaphoreProperties* pExternalSemaphoreProperties
    )

vkGetPhysicalDeviceExternalSemaphoreProperties registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetPhysicalDeviceExternalSemaphoreProperties <- vkGetInstanceProc @VkGetPhysicalDeviceExternalSemaphoreProperties vkInstance

or less efficient:

myGetPhysicalDeviceExternalSemaphoreProperties <- vkGetProc @VkGetPhysicalDeviceExternalSemaphoreProperties

Note: vkGetPhysicalDeviceExternalSemaphorePropertiesUnsafe and vkGetPhysicalDeviceExternalSemaphorePropertiesSafe are the unsafe and safe FFI imports of this function, respectively. vkGetPhysicalDeviceExternalSemaphoreProperties is an alias of vkGetPhysicalDeviceExternalSemaphorePropertiesUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetPhysicalDeviceExternalSemaphorePropertiesSafe.

vkGetPhysicalDeviceExternalSemaphorePropertiesSafe Source #

Arguments

:: VkPhysicalDevice

physicalDevice

-> Ptr VkPhysicalDeviceExternalSemaphoreInfo

pExternalSemaphoreInfo

-> Ptr VkExternalSemaphoreProperties

pExternalSemaphoreProperties

-> IO () 
void vkGetPhysicalDeviceExternalSemaphoreProperties
    ( VkPhysicalDevice physicalDevice
    , const VkPhysicalDeviceExternalSemaphoreInfo* pExternalSemaphoreInfo
    , VkExternalSemaphoreProperties* pExternalSemaphoreProperties
    )

vkGetPhysicalDeviceExternalSemaphoreProperties registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetPhysicalDeviceExternalSemaphoreProperties <- vkGetInstanceProc @VkGetPhysicalDeviceExternalSemaphoreProperties vkInstance

or less efficient:

myGetPhysicalDeviceExternalSemaphoreProperties <- vkGetProc @VkGetPhysicalDeviceExternalSemaphoreProperties

Note: vkGetPhysicalDeviceExternalSemaphorePropertiesUnsafe and vkGetPhysicalDeviceExternalSemaphorePropertiesSafe are the unsafe and safe FFI imports of this function, respectively. vkGetPhysicalDeviceExternalSemaphoreProperties is an alias of vkGetPhysicalDeviceExternalSemaphorePropertiesUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetPhysicalDeviceExternalSemaphorePropertiesSafe.

Promoted from VK_KHR_maintenance3

#include "vk_platform.h"

type VkGetDescriptorSetLayoutSupport = "vkGetDescriptorSetLayoutSupport" Source #

type HS_vkGetDescriptorSetLayoutSupport Source #

Arguments

 = VkDevice

device

-> Ptr VkDescriptorSetLayoutCreateInfo

pCreateInfo

-> Ptr VkDescriptorSetLayoutSupport

pSupport

-> IO () 
void vkGetDescriptorSetLayoutSupport
    ( VkDevice device
    , const VkDescriptorSetLayoutCreateInfo* pCreateInfo
    , VkDescriptorSetLayoutSupport* pSupport
    )

vkGetDescriptorSetLayoutSupport registry at www.khronos.org

vkGetDescriptorSetLayoutSupport Source #

Arguments

:: VkDevice

device

-> Ptr VkDescriptorSetLayoutCreateInfo

pCreateInfo

-> Ptr VkDescriptorSetLayoutSupport

pSupport

-> IO () 
void vkGetDescriptorSetLayoutSupport
    ( VkDevice device
    , const VkDescriptorSetLayoutCreateInfo* pCreateInfo
    , VkDescriptorSetLayoutSupport* pSupport
    )

vkGetDescriptorSetLayoutSupport registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetDescriptorSetLayoutSupport <- vkGetDeviceProc @VkGetDescriptorSetLayoutSupport vkDevice

or less efficient:

myGetDescriptorSetLayoutSupport <- vkGetProc @VkGetDescriptorSetLayoutSupport

Note: vkGetDescriptorSetLayoutSupportUnsafe and vkGetDescriptorSetLayoutSupportSafe are the unsafe and safe FFI imports of this function, respectively. vkGetDescriptorSetLayoutSupport is an alias of vkGetDescriptorSetLayoutSupportUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetDescriptorSetLayoutSupportSafe.

vkGetDescriptorSetLayoutSupportUnsafe Source #

Arguments

:: VkDevice

device

-> Ptr VkDescriptorSetLayoutCreateInfo

pCreateInfo

-> Ptr VkDescriptorSetLayoutSupport

pSupport

-> IO () 
void vkGetDescriptorSetLayoutSupport
    ( VkDevice device
    , const VkDescriptorSetLayoutCreateInfo* pCreateInfo
    , VkDescriptorSetLayoutSupport* pSupport
    )

vkGetDescriptorSetLayoutSupport registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetDescriptorSetLayoutSupport <- vkGetDeviceProc @VkGetDescriptorSetLayoutSupport vkDevice

or less efficient:

myGetDescriptorSetLayoutSupport <- vkGetProc @VkGetDescriptorSetLayoutSupport

Note: vkGetDescriptorSetLayoutSupportUnsafe and vkGetDescriptorSetLayoutSupportSafe are the unsafe and safe FFI imports of this function, respectively. vkGetDescriptorSetLayoutSupport is an alias of vkGetDescriptorSetLayoutSupportUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetDescriptorSetLayoutSupportSafe.

vkGetDescriptorSetLayoutSupportSafe Source #

Arguments

:: VkDevice

device

-> Ptr VkDescriptorSetLayoutCreateInfo

pCreateInfo

-> Ptr VkDescriptorSetLayoutSupport

pSupport

-> IO () 
void vkGetDescriptorSetLayoutSupport
    ( VkDevice device
    , const VkDescriptorSetLayoutCreateInfo* pCreateInfo
    , VkDescriptorSetLayoutSupport* pSupport
    )

vkGetDescriptorSetLayoutSupport registry at www.khronos.org

Note: When useNativeFFI-1-1 cabal flag is enabled, this function is linked statically as a foreign import call to C Vulkan loader. Otherwise, it is looked up dynamically at runtime using dlsym-like machinery (platform-dependent).

Independently of the flag setting, you can lookup the function manually at runtime:

myGetDescriptorSetLayoutSupport <- vkGetDeviceProc @VkGetDescriptorSetLayoutSupport vkDevice

or less efficient:

myGetDescriptorSetLayoutSupport <- vkGetProc @VkGetDescriptorSetLayoutSupport

Note: vkGetDescriptorSetLayoutSupportUnsafe and vkGetDescriptorSetLayoutSupportSafe are the unsafe and safe FFI imports of this function, respectively. vkGetDescriptorSetLayoutSupport is an alias of vkGetDescriptorSetLayoutSupportUnsafe when the useUnsafeFFIDefault cabal flag is enabled; otherwise, it is an alias of vkGetDescriptorSetLayoutSupportSafe.

Promoted from VK_KHR_shader_draw_parameters, with a feature support query added

#include "vk_platform.h"

Orphan instances

VulkanProc "vkBindBufferMemory2" Source # 

Associated Types

type VkProcType ("vkBindBufferMemory2" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkBindBufferMemory2") -> VkProcType "vkBindBufferMemory2" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkBindBufferMemory2") -> VkProcType "vkBindBufferMemory2" Source #

VulkanProc "vkBindImageMemory2" Source # 

Associated Types

type VkProcType ("vkBindImageMemory2" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkBindImageMemory2") -> VkProcType "vkBindImageMemory2" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkBindImageMemory2") -> VkProcType "vkBindImageMemory2" Source #

VulkanProc "vkCmdDispatchBase" Source # 

Associated Types

type VkProcType ("vkCmdDispatchBase" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkCmdDispatchBase") -> VkProcType "vkCmdDispatchBase" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkCmdDispatchBase") -> VkProcType "vkCmdDispatchBase" Source #

VulkanProc "vkCmdSetDeviceMask" Source # 

Associated Types

type VkProcType ("vkCmdSetDeviceMask" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkCmdSetDeviceMask") -> VkProcType "vkCmdSetDeviceMask" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkCmdSetDeviceMask") -> VkProcType "vkCmdSetDeviceMask" Source #

VulkanProc "vkCreateDescriptorUpdateTemplate" Source # 

Associated Types

type VkProcType ("vkCreateDescriptorUpdateTemplate" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkCreateDescriptorUpdateTemplate") -> VkProcType "vkCreateDescriptorUpdateTemplate" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkCreateDescriptorUpdateTemplate") -> VkProcType "vkCreateDescriptorUpdateTemplate" Source #

VulkanProc "vkCreateSamplerYcbcrConversion" Source # 

Associated Types

type VkProcType ("vkCreateSamplerYcbcrConversion" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkCreateSamplerYcbcrConversion") -> VkProcType "vkCreateSamplerYcbcrConversion" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkCreateSamplerYcbcrConversion") -> VkProcType "vkCreateSamplerYcbcrConversion" Source #

VulkanProc "vkDestroyDescriptorUpdateTemplate" Source # 

Associated Types

type VkProcType ("vkDestroyDescriptorUpdateTemplate" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkDestroyDescriptorUpdateTemplate") -> VkProcType "vkDestroyDescriptorUpdateTemplate" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkDestroyDescriptorUpdateTemplate") -> VkProcType "vkDestroyDescriptorUpdateTemplate" Source #

VulkanProc "vkDestroySamplerYcbcrConversion" Source # 

Associated Types

type VkProcType ("vkDestroySamplerYcbcrConversion" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkDestroySamplerYcbcrConversion") -> VkProcType "vkDestroySamplerYcbcrConversion" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkDestroySamplerYcbcrConversion") -> VkProcType "vkDestroySamplerYcbcrConversion" Source #

VulkanProc "vkEnumerateInstanceVersion" Source # 

Associated Types

type VkProcType ("vkEnumerateInstanceVersion" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkEnumerateInstanceVersion") -> VkProcType "vkEnumerateInstanceVersion" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkEnumerateInstanceVersion") -> VkProcType "vkEnumerateInstanceVersion" Source #

VulkanProc "vkEnumeratePhysicalDeviceGroups" Source # 

Associated Types

type VkProcType ("vkEnumeratePhysicalDeviceGroups" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkEnumeratePhysicalDeviceGroups") -> VkProcType "vkEnumeratePhysicalDeviceGroups" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkEnumeratePhysicalDeviceGroups") -> VkProcType "vkEnumeratePhysicalDeviceGroups" Source #

VulkanProc "vkGetBufferMemoryRequirements2" Source # 

Associated Types

type VkProcType ("vkGetBufferMemoryRequirements2" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkGetBufferMemoryRequirements2") -> VkProcType "vkGetBufferMemoryRequirements2" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkGetBufferMemoryRequirements2") -> VkProcType "vkGetBufferMemoryRequirements2" Source #

VulkanProc "vkGetDescriptorSetLayoutSupport" Source # 

Associated Types

type VkProcType ("vkGetDescriptorSetLayoutSupport" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkGetDescriptorSetLayoutSupport") -> VkProcType "vkGetDescriptorSetLayoutSupport" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkGetDescriptorSetLayoutSupport") -> VkProcType "vkGetDescriptorSetLayoutSupport" Source #

VulkanProc "vkGetDeviceGroupPeerMemoryFeatures" Source # 

Associated Types

type VkProcType ("vkGetDeviceGroupPeerMemoryFeatures" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkGetDeviceGroupPeerMemoryFeatures") -> VkProcType "vkGetDeviceGroupPeerMemoryFeatures" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkGetDeviceGroupPeerMemoryFeatures") -> VkProcType "vkGetDeviceGroupPeerMemoryFeatures" Source #

VulkanProc "vkGetDeviceQueue2" Source # 

Associated Types

type VkProcType ("vkGetDeviceQueue2" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkGetDeviceQueue2") -> VkProcType "vkGetDeviceQueue2" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkGetDeviceQueue2") -> VkProcType "vkGetDeviceQueue2" Source #

VulkanProc "vkGetImageMemoryRequirements2" Source # 

Associated Types

type VkProcType ("vkGetImageMemoryRequirements2" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkGetImageMemoryRequirements2") -> VkProcType "vkGetImageMemoryRequirements2" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkGetImageMemoryRequirements2") -> VkProcType "vkGetImageMemoryRequirements2" Source #

VulkanProc "vkGetImageSparseMemoryRequirements2" Source # 

Associated Types

type VkProcType ("vkGetImageSparseMemoryRequirements2" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkGetImageSparseMemoryRequirements2") -> VkProcType "vkGetImageSparseMemoryRequirements2" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkGetImageSparseMemoryRequirements2") -> VkProcType "vkGetImageSparseMemoryRequirements2" Source #

VulkanProc "vkGetPhysicalDeviceExternalBufferProperties" Source # 

Associated Types

type VkProcType ("vkGetPhysicalDeviceExternalBufferProperties" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkGetPhysicalDeviceExternalBufferProperties") -> VkProcType "vkGetPhysicalDeviceExternalBufferProperties" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkGetPhysicalDeviceExternalBufferProperties") -> VkProcType "vkGetPhysicalDeviceExternalBufferProperties" Source #

VulkanProc "vkGetPhysicalDeviceExternalFenceProperties" Source # 

Associated Types

type VkProcType ("vkGetPhysicalDeviceExternalFenceProperties" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkGetPhysicalDeviceExternalFenceProperties") -> VkProcType "vkGetPhysicalDeviceExternalFenceProperties" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkGetPhysicalDeviceExternalFenceProperties") -> VkProcType "vkGetPhysicalDeviceExternalFenceProperties" Source #

VulkanProc "vkGetPhysicalDeviceExternalSemaphoreProperties" Source # 

Associated Types

type VkProcType ("vkGetPhysicalDeviceExternalSemaphoreProperties" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkGetPhysicalDeviceExternalSemaphoreProperties") -> VkProcType "vkGetPhysicalDeviceExternalSemaphoreProperties" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkGetPhysicalDeviceExternalSemaphoreProperties") -> VkProcType "vkGetPhysicalDeviceExternalSemaphoreProperties" Source #

VulkanProc "vkGetPhysicalDeviceFeatures2" Source # 

Associated Types

type VkProcType ("vkGetPhysicalDeviceFeatures2" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkGetPhysicalDeviceFeatures2") -> VkProcType "vkGetPhysicalDeviceFeatures2" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkGetPhysicalDeviceFeatures2") -> VkProcType "vkGetPhysicalDeviceFeatures2" Source #

VulkanProc "vkGetPhysicalDeviceFormatProperties2" Source # 

Associated Types

type VkProcType ("vkGetPhysicalDeviceFormatProperties2" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkGetPhysicalDeviceFormatProperties2") -> VkProcType "vkGetPhysicalDeviceFormatProperties2" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkGetPhysicalDeviceFormatProperties2") -> VkProcType "vkGetPhysicalDeviceFormatProperties2" Source #

VulkanProc "vkGetPhysicalDeviceImageFormatProperties2" Source # 

Associated Types

type VkProcType ("vkGetPhysicalDeviceImageFormatProperties2" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkGetPhysicalDeviceImageFormatProperties2") -> VkProcType "vkGetPhysicalDeviceImageFormatProperties2" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkGetPhysicalDeviceImageFormatProperties2") -> VkProcType "vkGetPhysicalDeviceImageFormatProperties2" Source #

VulkanProc "vkGetPhysicalDeviceMemoryProperties2" Source # 

Associated Types

type VkProcType ("vkGetPhysicalDeviceMemoryProperties2" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkGetPhysicalDeviceMemoryProperties2") -> VkProcType "vkGetPhysicalDeviceMemoryProperties2" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkGetPhysicalDeviceMemoryProperties2") -> VkProcType "vkGetPhysicalDeviceMemoryProperties2" Source #

VulkanProc "vkGetPhysicalDeviceProperties2" Source # 

Associated Types

type VkProcType ("vkGetPhysicalDeviceProperties2" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkGetPhysicalDeviceProperties2") -> VkProcType "vkGetPhysicalDeviceProperties2" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkGetPhysicalDeviceProperties2") -> VkProcType "vkGetPhysicalDeviceProperties2" Source #

VulkanProc "vkGetPhysicalDeviceQueueFamilyProperties2" Source # 

Associated Types

type VkProcType ("vkGetPhysicalDeviceQueueFamilyProperties2" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkGetPhysicalDeviceQueueFamilyProperties2") -> VkProcType "vkGetPhysicalDeviceQueueFamilyProperties2" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkGetPhysicalDeviceQueueFamilyProperties2") -> VkProcType "vkGetPhysicalDeviceQueueFamilyProperties2" Source #

VulkanProc "vkGetPhysicalDeviceSparseImageFormatProperties2" Source # 

Associated Types

type VkProcType ("vkGetPhysicalDeviceSparseImageFormatProperties2" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkGetPhysicalDeviceSparseImageFormatProperties2") -> VkProcType "vkGetPhysicalDeviceSparseImageFormatProperties2" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkGetPhysicalDeviceSparseImageFormatProperties2") -> VkProcType "vkGetPhysicalDeviceSparseImageFormatProperties2" Source #

VulkanProc "vkTrimCommandPool" Source # 

Associated Types

type VkProcType ("vkTrimCommandPool" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkTrimCommandPool") -> VkProcType "vkTrimCommandPool" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkTrimCommandPool") -> VkProcType "vkTrimCommandPool" Source #

VulkanProc "vkUpdateDescriptorSetWithTemplate" Source # 

Associated Types

type VkProcType ("vkUpdateDescriptorSetWithTemplate" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkUpdateDescriptorSetWithTemplate") -> VkProcType "vkUpdateDescriptorSetWithTemplate" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkUpdateDescriptorSetWithTemplate") -> VkProcType "vkUpdateDescriptorSetWithTemplate" Source #