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

Safe HaskellNone
LanguageHaskell2010

Graphics.Vulkan.Ext.VK_NVX_device_generated_commands

Contents

Synopsis

Vulkan extension: VK_NVX_device_generated_commands

supported: vulkan

contact: Christoph Kubisch pixeljetstream@

author: NVX

type: device

Extension number: 87

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 VkCmdProcessCommandsInfoNVX Source #

typedef struct VkCmdProcessCommandsInfoNVX {
    VkStructureType sType;
    const void*                      pNext;
    VkObjectTableNVX                                         objectTable;
    VkIndirectCommandsLayoutNVX                              indirectCommandsLayout;
    uint32_t                                                 indirectCommandsTokenCount;
    const VkIndirectCommandsTokenNVX*       pIndirectCommandsTokens;
    uint32_t                                                 maxSequencesCount;
    VkCommandBuffer                          targetCommandBuffer;
    VkBuffer                                 sequencesCountBuffer;
    VkDeviceSize                             sequencesCountOffset;
    VkBuffer                                 sequencesIndexBuffer;
    VkDeviceSize                             sequencesIndexOffset;
} VkCmdProcessCommandsInfoNVX;

VkCmdProcessCommandsInfoNVX registry at www.khronos.org

Instances

Eq VkCmdProcessCommandsInfoNVX Source # 
Ord VkCmdProcessCommandsInfoNVX Source # 
Show VkCmdProcessCommandsInfoNVX Source # 
Storable VkCmdProcessCommandsInfoNVX Source # 
VulkanMarshalPrim VkCmdProcessCommandsInfoNVX Source # 
VulkanMarshal VkCmdProcessCommandsInfoNVX Source # 
CanWriteField "indirectCommandsLayout" VkCmdProcessCommandsInfoNVX Source # 
CanWriteField "indirectCommandsTokenCount" VkCmdProcessCommandsInfoNVX Source # 
CanWriteField "maxSequencesCount" VkCmdProcessCommandsInfoNVX Source # 
CanWriteField "objectTable" VkCmdProcessCommandsInfoNVX Source # 
CanWriteField "pIndirectCommandsTokens" VkCmdProcessCommandsInfoNVX Source # 
CanWriteField "pNext" VkCmdProcessCommandsInfoNVX Source # 
CanWriteField "sType" VkCmdProcessCommandsInfoNVX Source # 
CanWriteField "sequencesCountBuffer" VkCmdProcessCommandsInfoNVX Source # 
CanWriteField "sequencesCountOffset" VkCmdProcessCommandsInfoNVX Source # 
CanWriteField "sequencesIndexBuffer" VkCmdProcessCommandsInfoNVX Source # 
CanWriteField "sequencesIndexOffset" VkCmdProcessCommandsInfoNVX Source # 
CanWriteField "targetCommandBuffer" VkCmdProcessCommandsInfoNVX Source # 
CanReadField "indirectCommandsLayout" VkCmdProcessCommandsInfoNVX Source # 
CanReadField "indirectCommandsTokenCount" VkCmdProcessCommandsInfoNVX Source # 
CanReadField "maxSequencesCount" VkCmdProcessCommandsInfoNVX Source # 
CanReadField "objectTable" VkCmdProcessCommandsInfoNVX Source # 
CanReadField "pIndirectCommandsTokens" VkCmdProcessCommandsInfoNVX Source # 
CanReadField "pNext" VkCmdProcessCommandsInfoNVX Source # 
CanReadField "sType" VkCmdProcessCommandsInfoNVX Source # 
CanReadField "sequencesCountBuffer" VkCmdProcessCommandsInfoNVX Source # 
CanReadField "sequencesCountOffset" VkCmdProcessCommandsInfoNVX Source # 
CanReadField "sequencesIndexBuffer" VkCmdProcessCommandsInfoNVX Source # 
CanReadField "sequencesIndexOffset" VkCmdProcessCommandsInfoNVX Source # 
CanReadField "targetCommandBuffer" VkCmdProcessCommandsInfoNVX Source # 
HasField "indirectCommandsLayout" VkCmdProcessCommandsInfoNVX Source # 

Associated Types

type FieldType ("indirectCommandsLayout" :: Symbol) VkCmdProcessCommandsInfoNVX :: Type Source #

type FieldOptional ("indirectCommandsLayout" :: Symbol) VkCmdProcessCommandsInfoNVX :: Bool Source #

type FieldOffset ("indirectCommandsLayout" :: Symbol) VkCmdProcessCommandsInfoNVX :: Nat Source #

type FieldIsArray ("indirectCommandsLayout" :: Symbol) VkCmdProcessCommandsInfoNVX :: Bool Source #

HasField "indirectCommandsTokenCount" VkCmdProcessCommandsInfoNVX Source # 

Associated Types

type FieldType ("indirectCommandsTokenCount" :: Symbol) VkCmdProcessCommandsInfoNVX :: Type Source #

type FieldOptional ("indirectCommandsTokenCount" :: Symbol) VkCmdProcessCommandsInfoNVX :: Bool Source #

type FieldOffset ("indirectCommandsTokenCount" :: Symbol) VkCmdProcessCommandsInfoNVX :: Nat Source #

type FieldIsArray ("indirectCommandsTokenCount" :: Symbol) VkCmdProcessCommandsInfoNVX :: Bool Source #

HasField "maxSequencesCount" VkCmdProcessCommandsInfoNVX Source # 

Associated Types

type FieldType ("maxSequencesCount" :: Symbol) VkCmdProcessCommandsInfoNVX :: Type Source #

type FieldOptional ("maxSequencesCount" :: Symbol) VkCmdProcessCommandsInfoNVX :: Bool Source #

type FieldOffset ("maxSequencesCount" :: Symbol) VkCmdProcessCommandsInfoNVX :: Nat Source #

type FieldIsArray ("maxSequencesCount" :: Symbol) VkCmdProcessCommandsInfoNVX :: Bool Source #

HasField "objectTable" VkCmdProcessCommandsInfoNVX Source # 
HasField "pIndirectCommandsTokens" VkCmdProcessCommandsInfoNVX Source # 

Associated Types

type FieldType ("pIndirectCommandsTokens" :: Symbol) VkCmdProcessCommandsInfoNVX :: Type Source #

type FieldOptional ("pIndirectCommandsTokens" :: Symbol) VkCmdProcessCommandsInfoNVX :: Bool Source #

type FieldOffset ("pIndirectCommandsTokens" :: Symbol) VkCmdProcessCommandsInfoNVX :: Nat Source #

type FieldIsArray ("pIndirectCommandsTokens" :: Symbol) VkCmdProcessCommandsInfoNVX :: Bool Source #

HasField "pNext" VkCmdProcessCommandsInfoNVX Source # 
HasField "sType" VkCmdProcessCommandsInfoNVX Source # 
HasField "sequencesCountBuffer" VkCmdProcessCommandsInfoNVX Source # 

Associated Types

type FieldType ("sequencesCountBuffer" :: Symbol) VkCmdProcessCommandsInfoNVX :: Type Source #

type FieldOptional ("sequencesCountBuffer" :: Symbol) VkCmdProcessCommandsInfoNVX :: Bool Source #

type FieldOffset ("sequencesCountBuffer" :: Symbol) VkCmdProcessCommandsInfoNVX :: Nat Source #

type FieldIsArray ("sequencesCountBuffer" :: Symbol) VkCmdProcessCommandsInfoNVX :: Bool Source #

HasField "sequencesCountOffset" VkCmdProcessCommandsInfoNVX Source # 

Associated Types

type FieldType ("sequencesCountOffset" :: Symbol) VkCmdProcessCommandsInfoNVX :: Type Source #

type FieldOptional ("sequencesCountOffset" :: Symbol) VkCmdProcessCommandsInfoNVX :: Bool Source #

type FieldOffset ("sequencesCountOffset" :: Symbol) VkCmdProcessCommandsInfoNVX :: Nat Source #

type FieldIsArray ("sequencesCountOffset" :: Symbol) VkCmdProcessCommandsInfoNVX :: Bool Source #

HasField "sequencesIndexBuffer" VkCmdProcessCommandsInfoNVX Source # 

Associated Types

type FieldType ("sequencesIndexBuffer" :: Symbol) VkCmdProcessCommandsInfoNVX :: Type Source #

type FieldOptional ("sequencesIndexBuffer" :: Symbol) VkCmdProcessCommandsInfoNVX :: Bool Source #

type FieldOffset ("sequencesIndexBuffer" :: Symbol) VkCmdProcessCommandsInfoNVX :: Nat Source #

type FieldIsArray ("sequencesIndexBuffer" :: Symbol) VkCmdProcessCommandsInfoNVX :: Bool Source #

HasField "sequencesIndexOffset" VkCmdProcessCommandsInfoNVX Source # 

Associated Types

type FieldType ("sequencesIndexOffset" :: Symbol) VkCmdProcessCommandsInfoNVX :: Type Source #

type FieldOptional ("sequencesIndexOffset" :: Symbol) VkCmdProcessCommandsInfoNVX :: Bool Source #

type FieldOffset ("sequencesIndexOffset" :: Symbol) VkCmdProcessCommandsInfoNVX :: Nat Source #

type FieldIsArray ("sequencesIndexOffset" :: Symbol) VkCmdProcessCommandsInfoNVX :: Bool Source #

HasField "targetCommandBuffer" VkCmdProcessCommandsInfoNVX Source # 

Associated Types

type FieldType ("targetCommandBuffer" :: Symbol) VkCmdProcessCommandsInfoNVX :: Type Source #

type FieldOptional ("targetCommandBuffer" :: Symbol) VkCmdProcessCommandsInfoNVX :: Bool Source #

type FieldOffset ("targetCommandBuffer" :: Symbol) VkCmdProcessCommandsInfoNVX :: Nat Source #

type FieldIsArray ("targetCommandBuffer" :: Symbol) VkCmdProcessCommandsInfoNVX :: Bool Source #

type StructFields VkCmdProcessCommandsInfoNVX Source # 
type StructFields VkCmdProcessCommandsInfoNVX = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "objectTable" ((:) Symbol "indirectCommandsLayout" ((:) Symbol "indirectCommandsTokenCount" ((:) Symbol "pIndirectCommandsTokens" ((:) Symbol "maxSequencesCount" ((:) Symbol "targetCommandBuffer" ((:) Symbol "sequencesCountBuffer" ((:) Symbol "sequencesCountOffset" ((:) Symbol "sequencesIndexBuffer" ((:) Symbol "sequencesIndexOffset" ([] Symbol))))))))))))
type CUnionType VkCmdProcessCommandsInfoNVX Source # 
type ReturnedOnly VkCmdProcessCommandsInfoNVX Source # 
type StructExtends VkCmdProcessCommandsInfoNVX Source # 
type FieldType "indirectCommandsLayout" VkCmdProcessCommandsInfoNVX Source # 
type FieldType "indirectCommandsTokenCount" VkCmdProcessCommandsInfoNVX Source # 
type FieldType "indirectCommandsTokenCount" VkCmdProcessCommandsInfoNVX = Word32
type FieldType "maxSequencesCount" VkCmdProcessCommandsInfoNVX Source # 
type FieldType "maxSequencesCount" VkCmdProcessCommandsInfoNVX = Word32
type FieldType "objectTable" VkCmdProcessCommandsInfoNVX Source # 
type FieldType "pIndirectCommandsTokens" VkCmdProcessCommandsInfoNVX Source # 
type FieldType "pNext" VkCmdProcessCommandsInfoNVX Source # 
type FieldType "sType" VkCmdProcessCommandsInfoNVX Source # 
type FieldType "sequencesCountBuffer" VkCmdProcessCommandsInfoNVX Source # 
type FieldType "sequencesCountBuffer" VkCmdProcessCommandsInfoNVX = VkBuffer
type FieldType "sequencesCountOffset" VkCmdProcessCommandsInfoNVX Source # 
type FieldType "sequencesCountOffset" VkCmdProcessCommandsInfoNVX = VkDeviceSize
type FieldType "sequencesIndexBuffer" VkCmdProcessCommandsInfoNVX Source # 
type FieldType "sequencesIndexBuffer" VkCmdProcessCommandsInfoNVX = VkBuffer
type FieldType "sequencesIndexOffset" VkCmdProcessCommandsInfoNVX Source # 
type FieldType "sequencesIndexOffset" VkCmdProcessCommandsInfoNVX = VkDeviceSize
type FieldType "targetCommandBuffer" VkCmdProcessCommandsInfoNVX Source # 
type FieldOptional "indirectCommandsLayout" VkCmdProcessCommandsInfoNVX Source # 
type FieldOptional "indirectCommandsLayout" VkCmdProcessCommandsInfoNVX = False
type FieldOptional "indirectCommandsTokenCount" VkCmdProcessCommandsInfoNVX Source # 
type FieldOptional "indirectCommandsTokenCount" VkCmdProcessCommandsInfoNVX = False
type FieldOptional "maxSequencesCount" VkCmdProcessCommandsInfoNVX Source # 
type FieldOptional "objectTable" VkCmdProcessCommandsInfoNVX Source # 
type FieldOptional "pIndirectCommandsTokens" VkCmdProcessCommandsInfoNVX Source # 
type FieldOptional "pIndirectCommandsTokens" VkCmdProcessCommandsInfoNVX = False
type FieldOptional "pNext" VkCmdProcessCommandsInfoNVX Source # 
type FieldOptional "sType" VkCmdProcessCommandsInfoNVX Source # 
type FieldOptional "sequencesCountBuffer" VkCmdProcessCommandsInfoNVX Source # 
type FieldOptional "sequencesCountBuffer" VkCmdProcessCommandsInfoNVX = True
type FieldOptional "sequencesCountOffset" VkCmdProcessCommandsInfoNVX Source # 
type FieldOptional "sequencesCountOffset" VkCmdProcessCommandsInfoNVX = True
type FieldOptional "sequencesIndexBuffer" VkCmdProcessCommandsInfoNVX Source # 
type FieldOptional "sequencesIndexBuffer" VkCmdProcessCommandsInfoNVX = True
type FieldOptional "sequencesIndexOffset" VkCmdProcessCommandsInfoNVX Source # 
type FieldOptional "sequencesIndexOffset" VkCmdProcessCommandsInfoNVX = True
type FieldOptional "targetCommandBuffer" VkCmdProcessCommandsInfoNVX Source # 
type FieldOptional "targetCommandBuffer" VkCmdProcessCommandsInfoNVX = True
type FieldOffset "indirectCommandsLayout" VkCmdProcessCommandsInfoNVX Source # 
type FieldOffset "indirectCommandsLayout" VkCmdProcessCommandsInfoNVX = 24
type FieldOffset "indirectCommandsTokenCount" VkCmdProcessCommandsInfoNVX Source # 
type FieldOffset "indirectCommandsTokenCount" VkCmdProcessCommandsInfoNVX = 32
type FieldOffset "maxSequencesCount" VkCmdProcessCommandsInfoNVX Source # 
type FieldOffset "maxSequencesCount" VkCmdProcessCommandsInfoNVX = 48
type FieldOffset "objectTable" VkCmdProcessCommandsInfoNVX Source # 
type FieldOffset "pIndirectCommandsTokens" VkCmdProcessCommandsInfoNVX Source # 
type FieldOffset "pIndirectCommandsTokens" VkCmdProcessCommandsInfoNVX = 40
type FieldOffset "pNext" VkCmdProcessCommandsInfoNVX Source # 
type FieldOffset "sType" VkCmdProcessCommandsInfoNVX Source # 
type FieldOffset "sequencesCountBuffer" VkCmdProcessCommandsInfoNVX Source # 
type FieldOffset "sequencesCountBuffer" VkCmdProcessCommandsInfoNVX = 64
type FieldOffset "sequencesCountOffset" VkCmdProcessCommandsInfoNVX Source # 
type FieldOffset "sequencesCountOffset" VkCmdProcessCommandsInfoNVX = 72
type FieldOffset "sequencesIndexBuffer" VkCmdProcessCommandsInfoNVX Source # 
type FieldOffset "sequencesIndexBuffer" VkCmdProcessCommandsInfoNVX = 80
type FieldOffset "sequencesIndexOffset" VkCmdProcessCommandsInfoNVX Source # 
type FieldOffset "sequencesIndexOffset" VkCmdProcessCommandsInfoNVX = 88
type FieldOffset "targetCommandBuffer" VkCmdProcessCommandsInfoNVX Source # 
type FieldOffset "targetCommandBuffer" VkCmdProcessCommandsInfoNVX = 56
type FieldIsArray "indirectCommandsLayout" VkCmdProcessCommandsInfoNVX Source # 
type FieldIsArray "indirectCommandsLayout" VkCmdProcessCommandsInfoNVX = False
type FieldIsArray "indirectCommandsTokenCount" VkCmdProcessCommandsInfoNVX Source # 
type FieldIsArray "indirectCommandsTokenCount" VkCmdProcessCommandsInfoNVX = False
type FieldIsArray "maxSequencesCount" VkCmdProcessCommandsInfoNVX Source # 
type FieldIsArray "objectTable" VkCmdProcessCommandsInfoNVX Source # 
type FieldIsArray "pIndirectCommandsTokens" VkCmdProcessCommandsInfoNVX Source # 
type FieldIsArray "pIndirectCommandsTokens" VkCmdProcessCommandsInfoNVX = False
type FieldIsArray "pNext" VkCmdProcessCommandsInfoNVX Source # 
type FieldIsArray "sType" VkCmdProcessCommandsInfoNVX Source # 
type FieldIsArray "sequencesCountBuffer" VkCmdProcessCommandsInfoNVX Source # 
type FieldIsArray "sequencesCountBuffer" VkCmdProcessCommandsInfoNVX = False
type FieldIsArray "sequencesCountOffset" VkCmdProcessCommandsInfoNVX Source # 
type FieldIsArray "sequencesCountOffset" VkCmdProcessCommandsInfoNVX = False
type FieldIsArray "sequencesIndexBuffer" VkCmdProcessCommandsInfoNVX Source # 
type FieldIsArray "sequencesIndexBuffer" VkCmdProcessCommandsInfoNVX = False
type FieldIsArray "sequencesIndexOffset" VkCmdProcessCommandsInfoNVX Source # 
type FieldIsArray "sequencesIndexOffset" VkCmdProcessCommandsInfoNVX = False
type FieldIsArray "targetCommandBuffer" VkCmdProcessCommandsInfoNVX Source # 
type FieldIsArray "targetCommandBuffer" VkCmdProcessCommandsInfoNVX = False

data VkCmdReserveSpaceForCommandsInfoNVX Source #

typedef struct VkCmdReserveSpaceForCommandsInfoNVX {
    VkStructureType sType;
    const void*                      pNext;
    VkObjectTableNVX                                         objectTable;
    VkIndirectCommandsLayoutNVX                              indirectCommandsLayout;
    uint32_t                                                 maxSequencesCount;
} VkCmdReserveSpaceForCommandsInfoNVX;

VkCmdReserveSpaceForCommandsInfoNVX registry at www.khronos.org

Instances

Eq VkCmdReserveSpaceForCommandsInfoNVX Source # 
Ord VkCmdReserveSpaceForCommandsInfoNVX Source # 
Show VkCmdReserveSpaceForCommandsInfoNVX Source # 
Storable VkCmdReserveSpaceForCommandsInfoNVX Source # 
VulkanMarshalPrim VkCmdReserveSpaceForCommandsInfoNVX Source # 
VulkanMarshal VkCmdReserveSpaceForCommandsInfoNVX Source # 
CanWriteField "indirectCommandsLayout" VkCmdReserveSpaceForCommandsInfoNVX Source # 
CanWriteField "maxSequencesCount" VkCmdReserveSpaceForCommandsInfoNVX Source # 
CanWriteField "objectTable" VkCmdReserveSpaceForCommandsInfoNVX Source # 
CanWriteField "pNext" VkCmdReserveSpaceForCommandsInfoNVX Source # 
CanWriteField "sType" VkCmdReserveSpaceForCommandsInfoNVX Source # 
CanReadField "indirectCommandsLayout" VkCmdReserveSpaceForCommandsInfoNVX Source # 
CanReadField "maxSequencesCount" VkCmdReserveSpaceForCommandsInfoNVX Source # 
CanReadField "objectTable" VkCmdReserveSpaceForCommandsInfoNVX Source # 
CanReadField "pNext" VkCmdReserveSpaceForCommandsInfoNVX Source # 
CanReadField "sType" VkCmdReserveSpaceForCommandsInfoNVX Source # 
HasField "indirectCommandsLayout" VkCmdReserveSpaceForCommandsInfoNVX Source # 

Associated Types

type FieldType ("indirectCommandsLayout" :: Symbol) VkCmdReserveSpaceForCommandsInfoNVX :: Type Source #

type FieldOptional ("indirectCommandsLayout" :: Symbol) VkCmdReserveSpaceForCommandsInfoNVX :: Bool Source #

type FieldOffset ("indirectCommandsLayout" :: Symbol) VkCmdReserveSpaceForCommandsInfoNVX :: Nat Source #

type FieldIsArray ("indirectCommandsLayout" :: Symbol) VkCmdReserveSpaceForCommandsInfoNVX :: Bool Source #

HasField "maxSequencesCount" VkCmdReserveSpaceForCommandsInfoNVX Source # 
HasField "objectTable" VkCmdReserveSpaceForCommandsInfoNVX Source # 
HasField "pNext" VkCmdReserveSpaceForCommandsInfoNVX Source # 
HasField "sType" VkCmdReserveSpaceForCommandsInfoNVX Source # 
type StructFields VkCmdReserveSpaceForCommandsInfoNVX Source # 
type StructFields VkCmdReserveSpaceForCommandsInfoNVX = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "objectTable" ((:) Symbol "indirectCommandsLayout" ((:) Symbol "maxSequencesCount" ([] Symbol)))))
type CUnionType VkCmdReserveSpaceForCommandsInfoNVX Source # 
type ReturnedOnly VkCmdReserveSpaceForCommandsInfoNVX Source # 
type StructExtends VkCmdReserveSpaceForCommandsInfoNVX Source # 
type FieldType "indirectCommandsLayout" VkCmdReserveSpaceForCommandsInfoNVX Source # 
type FieldType "maxSequencesCount" VkCmdReserveSpaceForCommandsInfoNVX Source # 
type FieldType "objectTable" VkCmdReserveSpaceForCommandsInfoNVX Source # 
type FieldType "pNext" VkCmdReserveSpaceForCommandsInfoNVX Source # 
type FieldType "sType" VkCmdReserveSpaceForCommandsInfoNVX Source # 
type FieldOptional "indirectCommandsLayout" VkCmdReserveSpaceForCommandsInfoNVX Source # 
type FieldOptional "maxSequencesCount" VkCmdReserveSpaceForCommandsInfoNVX Source # 
type FieldOptional "objectTable" VkCmdReserveSpaceForCommandsInfoNVX Source # 
type FieldOptional "pNext" VkCmdReserveSpaceForCommandsInfoNVX Source # 
type FieldOptional "sType" VkCmdReserveSpaceForCommandsInfoNVX Source # 
type FieldOffset "indirectCommandsLayout" VkCmdReserveSpaceForCommandsInfoNVX Source # 
type FieldOffset "indirectCommandsLayout" VkCmdReserveSpaceForCommandsInfoNVX = 24
type FieldOffset "maxSequencesCount" VkCmdReserveSpaceForCommandsInfoNVX Source # 
type FieldOffset "maxSequencesCount" VkCmdReserveSpaceForCommandsInfoNVX = 32
type FieldOffset "objectTable" VkCmdReserveSpaceForCommandsInfoNVX Source # 
type FieldOffset "pNext" VkCmdReserveSpaceForCommandsInfoNVX Source # 
type FieldOffset "sType" VkCmdReserveSpaceForCommandsInfoNVX Source # 
type FieldIsArray "indirectCommandsLayout" VkCmdReserveSpaceForCommandsInfoNVX Source # 
type FieldIsArray "maxSequencesCount" VkCmdReserveSpaceForCommandsInfoNVX Source # 
type FieldIsArray "objectTable" VkCmdReserveSpaceForCommandsInfoNVX Source # 
type FieldIsArray "pNext" VkCmdReserveSpaceForCommandsInfoNVX Source # 
type FieldIsArray "sType" VkCmdReserveSpaceForCommandsInfoNVX Source # 

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 VkIndexType Source #

Constructors

VkIndexType Int32 

Instances

Bounded VkIndexType Source # 
Enum VkIndexType Source # 
Eq VkIndexType Source # 
Data VkIndexType Source # 

Methods

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

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

toConstr :: VkIndexType -> Constr #

dataTypeOf :: VkIndexType -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkIndexType Source # 
Ord VkIndexType Source # 
Read VkIndexType Source # 
Show VkIndexType Source # 
Generic VkIndexType Source # 

Associated Types

type Rep VkIndexType :: * -> * #

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

data VkIndirectCommandsLayoutCreateInfoNVX Source #

typedef struct VkIndirectCommandsLayoutCreateInfoNVX {
    VkStructureType sType;
    const void*                      pNext;
    VkPipelineBindPoint                      pipelineBindPoint;
    VkIndirectCommandsLayoutUsageFlagsNVX    flags;
    uint32_t                                 tokenCount;
    const VkIndirectCommandsLayoutTokenNVX*  pTokens;
} VkIndirectCommandsLayoutCreateInfoNVX;

VkIndirectCommandsLayoutCreateInfoNVX registry at www.khronos.org

Instances

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

data VkIndirectCommandsLayoutTokenNVX Source #

typedef struct VkIndirectCommandsLayoutTokenNVX {
    VkIndirectCommandsTokenTypeNVX      tokenType;
    uint32_t                         bindingUnit;
    uint32_t                         dynamicCount;
    uint32_t                         divisor;
} VkIndirectCommandsLayoutTokenNVX;

VkIndirectCommandsLayoutTokenNVX registry at www.khronos.org

Instances

Eq VkIndirectCommandsLayoutTokenNVX Source # 
Ord VkIndirectCommandsLayoutTokenNVX Source # 
Show VkIndirectCommandsLayoutTokenNVX Source # 
Storable VkIndirectCommandsLayoutTokenNVX Source # 
VulkanMarshalPrim VkIndirectCommandsLayoutTokenNVX Source # 
VulkanMarshal VkIndirectCommandsLayoutTokenNVX Source # 
CanWriteField "bindingUnit" VkIndirectCommandsLayoutTokenNVX Source # 
CanWriteField "divisor" VkIndirectCommandsLayoutTokenNVX Source # 
CanWriteField "dynamicCount" VkIndirectCommandsLayoutTokenNVX Source # 
CanWriteField "tokenType" VkIndirectCommandsLayoutTokenNVX Source # 
CanReadField "bindingUnit" VkIndirectCommandsLayoutTokenNVX Source # 
CanReadField "divisor" VkIndirectCommandsLayoutTokenNVX Source # 
CanReadField "dynamicCount" VkIndirectCommandsLayoutTokenNVX Source # 
CanReadField "tokenType" VkIndirectCommandsLayoutTokenNVX Source # 
HasField "bindingUnit" VkIndirectCommandsLayoutTokenNVX Source # 
HasField "divisor" VkIndirectCommandsLayoutTokenNVX Source # 
HasField "dynamicCount" VkIndirectCommandsLayoutTokenNVX Source # 
HasField "tokenType" VkIndirectCommandsLayoutTokenNVX Source # 
type StructFields VkIndirectCommandsLayoutTokenNVX Source # 
type StructFields VkIndirectCommandsLayoutTokenNVX = (:) Symbol "tokenType" ((:) Symbol "bindingUnit" ((:) Symbol "dynamicCount" ((:) Symbol "divisor" ([] Symbol))))
type CUnionType VkIndirectCommandsLayoutTokenNVX Source # 
type ReturnedOnly VkIndirectCommandsLayoutTokenNVX Source # 
type StructExtends VkIndirectCommandsLayoutTokenNVX Source # 
type FieldType "bindingUnit" VkIndirectCommandsLayoutTokenNVX Source # 
type FieldType "divisor" VkIndirectCommandsLayoutTokenNVX Source # 
type FieldType "dynamicCount" VkIndirectCommandsLayoutTokenNVX Source # 
type FieldType "tokenType" VkIndirectCommandsLayoutTokenNVX Source # 
type FieldOptional "bindingUnit" VkIndirectCommandsLayoutTokenNVX Source # 
type FieldOptional "divisor" VkIndirectCommandsLayoutTokenNVX Source # 
type FieldOptional "dynamicCount" VkIndirectCommandsLayoutTokenNVX Source # 
type FieldOptional "tokenType" VkIndirectCommandsLayoutTokenNVX Source # 
type FieldOffset "bindingUnit" VkIndirectCommandsLayoutTokenNVX Source # 
type FieldOffset "divisor" VkIndirectCommandsLayoutTokenNVX Source # 
type FieldOffset "dynamicCount" VkIndirectCommandsLayoutTokenNVX Source # 
type FieldOffset "tokenType" VkIndirectCommandsLayoutTokenNVX Source # 
type FieldIsArray "bindingUnit" VkIndirectCommandsLayoutTokenNVX Source # 
type FieldIsArray "divisor" VkIndirectCommandsLayoutTokenNVX Source # 
type FieldIsArray "dynamicCount" VkIndirectCommandsLayoutTokenNVX Source # 
type FieldIsArray "tokenType" VkIndirectCommandsLayoutTokenNVX Source # 

data VkIndirectCommandsTokenNVX Source #

typedef struct VkIndirectCommandsTokenNVX {
    VkIndirectCommandsTokenTypeNVX      tokenType;
    VkBuffer                         buffer;
    VkDeviceSize                     offset;
} VkIndirectCommandsTokenNVX;

VkIndirectCommandsTokenNVX registry at www.khronos.org

Instances

Eq VkIndirectCommandsTokenNVX Source # 
Ord VkIndirectCommandsTokenNVX Source # 
Show VkIndirectCommandsTokenNVX Source # 
Storable VkIndirectCommandsTokenNVX Source # 
VulkanMarshalPrim VkIndirectCommandsTokenNVX Source # 
VulkanMarshal VkIndirectCommandsTokenNVX Source # 
CanWriteField "buffer" VkIndirectCommandsTokenNVX Source # 
CanWriteField "offset" VkIndirectCommandsTokenNVX Source # 
CanWriteField "tokenType" VkIndirectCommandsTokenNVX Source # 
CanReadField "buffer" VkIndirectCommandsTokenNVX Source # 
CanReadField "offset" VkIndirectCommandsTokenNVX Source # 
CanReadField "tokenType" VkIndirectCommandsTokenNVX Source # 
HasField "buffer" VkIndirectCommandsTokenNVX Source # 
HasField "offset" VkIndirectCommandsTokenNVX Source # 
HasField "tokenType" VkIndirectCommandsTokenNVX Source # 
type StructFields VkIndirectCommandsTokenNVX Source # 
type StructFields VkIndirectCommandsTokenNVX = (:) Symbol "tokenType" ((:) Symbol "buffer" ((:) Symbol "offset" ([] Symbol)))
type CUnionType VkIndirectCommandsTokenNVX Source # 
type ReturnedOnly VkIndirectCommandsTokenNVX Source # 
type StructExtends VkIndirectCommandsTokenNVX Source # 
type FieldType "buffer" VkIndirectCommandsTokenNVX Source # 
type FieldType "offset" VkIndirectCommandsTokenNVX Source # 
type FieldType "tokenType" VkIndirectCommandsTokenNVX Source # 
type FieldOptional "buffer" VkIndirectCommandsTokenNVX Source # 
type FieldOptional "offset" VkIndirectCommandsTokenNVX Source # 
type FieldOptional "tokenType" VkIndirectCommandsTokenNVX Source # 
type FieldOffset "buffer" VkIndirectCommandsTokenNVX Source # 
type FieldOffset "offset" VkIndirectCommandsTokenNVX Source # 
type FieldOffset "tokenType" VkIndirectCommandsTokenNVX Source # 
type FieldIsArray "buffer" VkIndirectCommandsTokenNVX Source # 
type FieldIsArray "offset" VkIndirectCommandsTokenNVX Source # 
type FieldIsArray "tokenType" VkIndirectCommandsTokenNVX Source # 

newtype VkIndirectCommandsLayoutUsageBitmaskNVX a Source #

Instances

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

Methods

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

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

toConstr :: VkIndirectCommandsLayoutUsageBitmaskNVX a -> Constr #

dataTypeOf :: VkIndirectCommandsLayoutUsageBitmaskNVX a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

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

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

xor :: VkIndirectCommandsLayoutUsageBitmaskNVX FlagMask -> VkIndirectCommandsLayoutUsageBitmaskNVX FlagMask -> VkIndirectCommandsLayoutUsageBitmaskNVX FlagMask #

complement :: VkIndirectCommandsLayoutUsageBitmaskNVX FlagMask -> VkIndirectCommandsLayoutUsageBitmaskNVX FlagMask #

shift :: VkIndirectCommandsLayoutUsageBitmaskNVX FlagMask -> Int -> VkIndirectCommandsLayoutUsageBitmaskNVX FlagMask #

rotate :: VkIndirectCommandsLayoutUsageBitmaskNVX FlagMask -> Int -> VkIndirectCommandsLayoutUsageBitmaskNVX FlagMask #

zeroBits :: VkIndirectCommandsLayoutUsageBitmaskNVX FlagMask #

bit :: Int -> VkIndirectCommandsLayoutUsageBitmaskNVX FlagMask #

setBit :: VkIndirectCommandsLayoutUsageBitmaskNVX FlagMask -> Int -> VkIndirectCommandsLayoutUsageBitmaskNVX FlagMask #

clearBit :: VkIndirectCommandsLayoutUsageBitmaskNVX FlagMask -> Int -> VkIndirectCommandsLayoutUsageBitmaskNVX FlagMask #

complementBit :: VkIndirectCommandsLayoutUsageBitmaskNVX FlagMask -> Int -> VkIndirectCommandsLayoutUsageBitmaskNVX FlagMask #

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

bitSizeMaybe :: VkIndirectCommandsLayoutUsageBitmaskNVX FlagMask -> Maybe Int #

bitSize :: VkIndirectCommandsLayoutUsageBitmaskNVX FlagMask -> Int #

isSigned :: VkIndirectCommandsLayoutUsageBitmaskNVX FlagMask -> Bool #

shiftL :: VkIndirectCommandsLayoutUsageBitmaskNVX FlagMask -> Int -> VkIndirectCommandsLayoutUsageBitmaskNVX FlagMask #

unsafeShiftL :: VkIndirectCommandsLayoutUsageBitmaskNVX FlagMask -> Int -> VkIndirectCommandsLayoutUsageBitmaskNVX FlagMask #

shiftR :: VkIndirectCommandsLayoutUsageBitmaskNVX FlagMask -> Int -> VkIndirectCommandsLayoutUsageBitmaskNVX FlagMask #

unsafeShiftR :: VkIndirectCommandsLayoutUsageBitmaskNVX FlagMask -> Int -> VkIndirectCommandsLayoutUsageBitmaskNVX FlagMask #

rotateL :: VkIndirectCommandsLayoutUsageBitmaskNVX FlagMask -> Int -> VkIndirectCommandsLayoutUsageBitmaskNVX FlagMask #

rotateR :: VkIndirectCommandsLayoutUsageBitmaskNVX FlagMask -> Int -> VkIndirectCommandsLayoutUsageBitmaskNVX FlagMask #

popCount :: VkIndirectCommandsLayoutUsageBitmaskNVX FlagMask -> Int #

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

newtype VkIndirectCommandsTokenTypeNVX Source #

Instances

Bounded VkIndirectCommandsTokenTypeNVX Source # 
Enum VkIndirectCommandsTokenTypeNVX Source # 
Eq VkIndirectCommandsTokenTypeNVX Source # 
Data VkIndirectCommandsTokenTypeNVX Source # 

Methods

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

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

toConstr :: VkIndirectCommandsTokenTypeNVX -> Constr #

dataTypeOf :: VkIndirectCommandsTokenTypeNVX -> DataType #

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

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

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

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

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

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

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

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

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

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

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

newtype VkObjectEntryTypeNVX Source #

Instances

Bounded VkObjectEntryTypeNVX Source # 
Enum VkObjectEntryTypeNVX Source # 
Eq VkObjectEntryTypeNVX Source # 
Data VkObjectEntryTypeNVX Source # 

Methods

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

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

toConstr :: VkObjectEntryTypeNVX -> Constr #

dataTypeOf :: VkObjectEntryTypeNVX -> DataType #

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

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

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

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

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

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

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

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

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

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

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

newtype VkObjectEntryUsageBitmaskNVX a Source #

Instances

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

Methods

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

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

toConstr :: VkObjectEntryUsageBitmaskNVX a -> Constr #

dataTypeOf :: VkObjectEntryUsageBitmaskNVX a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

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

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

xor :: VkObjectEntryUsageBitmaskNVX FlagMask -> VkObjectEntryUsageBitmaskNVX FlagMask -> VkObjectEntryUsageBitmaskNVX FlagMask #

complement :: VkObjectEntryUsageBitmaskNVX FlagMask -> VkObjectEntryUsageBitmaskNVX FlagMask #

shift :: VkObjectEntryUsageBitmaskNVX FlagMask -> Int -> VkObjectEntryUsageBitmaskNVX FlagMask #

rotate :: VkObjectEntryUsageBitmaskNVX FlagMask -> Int -> VkObjectEntryUsageBitmaskNVX FlagMask #

zeroBits :: VkObjectEntryUsageBitmaskNVX FlagMask #

bit :: Int -> VkObjectEntryUsageBitmaskNVX FlagMask #

setBit :: VkObjectEntryUsageBitmaskNVX FlagMask -> Int -> VkObjectEntryUsageBitmaskNVX FlagMask #

clearBit :: VkObjectEntryUsageBitmaskNVX FlagMask -> Int -> VkObjectEntryUsageBitmaskNVX FlagMask #

complementBit :: VkObjectEntryUsageBitmaskNVX FlagMask -> Int -> VkObjectEntryUsageBitmaskNVX FlagMask #

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

bitSizeMaybe :: VkObjectEntryUsageBitmaskNVX FlagMask -> Maybe Int #

bitSize :: VkObjectEntryUsageBitmaskNVX FlagMask -> Int #

isSigned :: VkObjectEntryUsageBitmaskNVX FlagMask -> Bool #

shiftL :: VkObjectEntryUsageBitmaskNVX FlagMask -> Int -> VkObjectEntryUsageBitmaskNVX FlagMask #

unsafeShiftL :: VkObjectEntryUsageBitmaskNVX FlagMask -> Int -> VkObjectEntryUsageBitmaskNVX FlagMask #

shiftR :: VkObjectEntryUsageBitmaskNVX FlagMask -> Int -> VkObjectEntryUsageBitmaskNVX FlagMask #

unsafeShiftR :: VkObjectEntryUsageBitmaskNVX FlagMask -> Int -> VkObjectEntryUsageBitmaskNVX FlagMask #

rotateL :: VkObjectEntryUsageBitmaskNVX FlagMask -> Int -> VkObjectEntryUsageBitmaskNVX FlagMask #

rotateR :: VkObjectEntryUsageBitmaskNVX FlagMask -> Int -> VkObjectEntryUsageBitmaskNVX FlagMask #

popCount :: VkObjectEntryUsageBitmaskNVX FlagMask -> Int #

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

newtype VkObjectType Source #

Enums to track objects of various types

type = enum

VkObjectType registry at www.khronos.org

Constructors

VkObjectType Int32 

Instances

Bounded VkObjectType Source # 
Enum VkObjectType Source # 
Eq VkObjectType Source # 
Data VkObjectType Source # 

Methods

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

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

toConstr :: VkObjectType -> Constr #

dataTypeOf :: VkObjectType -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkObjectType Source # 
Ord VkObjectType Source # 
Read VkObjectType Source # 
Show VkObjectType Source # 
Generic VkObjectType Source # 

Associated Types

type Rep VkObjectType :: * -> * #

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

data VkObjectTableCreateInfoNVX Source #

typedef struct VkObjectTableCreateInfoNVX {
    VkStructureType sType;
    const void*                      pNext;
    uint32_t                                          objectCount;
    const VkObjectEntryTypeNVX*       pObjectEntryTypes;
    const uint32_t*                   pObjectEntryCounts;
    const VkObjectEntryUsageFlagsNVX* pObjectEntryUsageFlags;
    uint32_t maxUniformBuffersPerDescriptor;
    uint32_t maxStorageBuffersPerDescriptor;
    uint32_t maxStorageImagesPerDescriptor;
    uint32_t maxSampledImagesPerDescriptor;
    uint32_t maxPipelineLayouts;
} VkObjectTableCreateInfoNVX;

VkObjectTableCreateInfoNVX registry at www.khronos.org

Instances

Eq VkObjectTableCreateInfoNVX Source # 
Ord VkObjectTableCreateInfoNVX Source # 
Show VkObjectTableCreateInfoNVX Source # 
Storable VkObjectTableCreateInfoNVX Source # 
VulkanMarshalPrim VkObjectTableCreateInfoNVX Source # 
VulkanMarshal VkObjectTableCreateInfoNVX Source # 
CanWriteField "maxPipelineLayouts" VkObjectTableCreateInfoNVX Source # 
CanWriteField "maxSampledImagesPerDescriptor" VkObjectTableCreateInfoNVX Source # 

Methods

writeField :: Ptr VkObjectTableCreateInfoNVX -> FieldType "maxSampledImagesPerDescriptor" VkObjectTableCreateInfoNVX -> IO () Source #

CanWriteField "maxStorageBuffersPerDescriptor" VkObjectTableCreateInfoNVX Source # 

Methods

writeField :: Ptr VkObjectTableCreateInfoNVX -> FieldType "maxStorageBuffersPerDescriptor" VkObjectTableCreateInfoNVX -> IO () Source #

CanWriteField "maxStorageImagesPerDescriptor" VkObjectTableCreateInfoNVX Source # 

Methods

writeField :: Ptr VkObjectTableCreateInfoNVX -> FieldType "maxStorageImagesPerDescriptor" VkObjectTableCreateInfoNVX -> IO () Source #

CanWriteField "maxUniformBuffersPerDescriptor" VkObjectTableCreateInfoNVX Source # 

Methods

writeField :: Ptr VkObjectTableCreateInfoNVX -> FieldType "maxUniformBuffersPerDescriptor" VkObjectTableCreateInfoNVX -> IO () Source #

CanWriteField "objectCount" VkObjectTableCreateInfoNVX Source # 
CanWriteField "pNext" VkObjectTableCreateInfoNVX Source # 
CanWriteField "pObjectEntryCounts" VkObjectTableCreateInfoNVX Source # 
CanWriteField "pObjectEntryTypes" VkObjectTableCreateInfoNVX Source # 
CanWriteField "pObjectEntryUsageFlags" VkObjectTableCreateInfoNVX Source # 
CanWriteField "sType" VkObjectTableCreateInfoNVX Source # 
CanReadField "maxPipelineLayouts" VkObjectTableCreateInfoNVX Source # 
CanReadField "maxSampledImagesPerDescriptor" VkObjectTableCreateInfoNVX Source # 
CanReadField "maxStorageBuffersPerDescriptor" VkObjectTableCreateInfoNVX Source # 
CanReadField "maxStorageImagesPerDescriptor" VkObjectTableCreateInfoNVX Source # 
CanReadField "maxUniformBuffersPerDescriptor" VkObjectTableCreateInfoNVX Source # 
CanReadField "objectCount" VkObjectTableCreateInfoNVX Source # 
CanReadField "pNext" VkObjectTableCreateInfoNVX Source # 
CanReadField "pObjectEntryCounts" VkObjectTableCreateInfoNVX Source # 
CanReadField "pObjectEntryTypes" VkObjectTableCreateInfoNVX Source # 
CanReadField "pObjectEntryUsageFlags" VkObjectTableCreateInfoNVX Source # 
CanReadField "sType" VkObjectTableCreateInfoNVX Source # 
HasField "maxPipelineLayouts" VkObjectTableCreateInfoNVX Source # 

Associated Types

type FieldType ("maxPipelineLayouts" :: Symbol) VkObjectTableCreateInfoNVX :: Type Source #

type FieldOptional ("maxPipelineLayouts" :: Symbol) VkObjectTableCreateInfoNVX :: Bool Source #

type FieldOffset ("maxPipelineLayouts" :: Symbol) VkObjectTableCreateInfoNVX :: Nat Source #

type FieldIsArray ("maxPipelineLayouts" :: Symbol) VkObjectTableCreateInfoNVX :: Bool Source #

HasField "maxSampledImagesPerDescriptor" VkObjectTableCreateInfoNVX Source # 

Associated Types

type FieldType ("maxSampledImagesPerDescriptor" :: Symbol) VkObjectTableCreateInfoNVX :: Type Source #

type FieldOptional ("maxSampledImagesPerDescriptor" :: Symbol) VkObjectTableCreateInfoNVX :: Bool Source #

type FieldOffset ("maxSampledImagesPerDescriptor" :: Symbol) VkObjectTableCreateInfoNVX :: Nat Source #

type FieldIsArray ("maxSampledImagesPerDescriptor" :: Symbol) VkObjectTableCreateInfoNVX :: Bool Source #

HasField "maxStorageBuffersPerDescriptor" VkObjectTableCreateInfoNVX Source # 

Associated Types

type FieldType ("maxStorageBuffersPerDescriptor" :: Symbol) VkObjectTableCreateInfoNVX :: Type Source #

type FieldOptional ("maxStorageBuffersPerDescriptor" :: Symbol) VkObjectTableCreateInfoNVX :: Bool Source #

type FieldOffset ("maxStorageBuffersPerDescriptor" :: Symbol) VkObjectTableCreateInfoNVX :: Nat Source #

type FieldIsArray ("maxStorageBuffersPerDescriptor" :: Symbol) VkObjectTableCreateInfoNVX :: Bool Source #

HasField "maxStorageImagesPerDescriptor" VkObjectTableCreateInfoNVX Source # 

Associated Types

type FieldType ("maxStorageImagesPerDescriptor" :: Symbol) VkObjectTableCreateInfoNVX :: Type Source #

type FieldOptional ("maxStorageImagesPerDescriptor" :: Symbol) VkObjectTableCreateInfoNVX :: Bool Source #

type FieldOffset ("maxStorageImagesPerDescriptor" :: Symbol) VkObjectTableCreateInfoNVX :: Nat Source #

type FieldIsArray ("maxStorageImagesPerDescriptor" :: Symbol) VkObjectTableCreateInfoNVX :: Bool Source #

HasField "maxUniformBuffersPerDescriptor" VkObjectTableCreateInfoNVX Source # 

Associated Types

type FieldType ("maxUniformBuffersPerDescriptor" :: Symbol) VkObjectTableCreateInfoNVX :: Type Source #

type FieldOptional ("maxUniformBuffersPerDescriptor" :: Symbol) VkObjectTableCreateInfoNVX :: Bool Source #

type FieldOffset ("maxUniformBuffersPerDescriptor" :: Symbol) VkObjectTableCreateInfoNVX :: Nat Source #

type FieldIsArray ("maxUniformBuffersPerDescriptor" :: Symbol) VkObjectTableCreateInfoNVX :: Bool Source #

HasField "objectCount" VkObjectTableCreateInfoNVX Source # 
HasField "pNext" VkObjectTableCreateInfoNVX Source # 
HasField "pObjectEntryCounts" VkObjectTableCreateInfoNVX Source # 

Associated Types

type FieldType ("pObjectEntryCounts" :: Symbol) VkObjectTableCreateInfoNVX :: Type Source #

type FieldOptional ("pObjectEntryCounts" :: Symbol) VkObjectTableCreateInfoNVX :: Bool Source #

type FieldOffset ("pObjectEntryCounts" :: Symbol) VkObjectTableCreateInfoNVX :: Nat Source #

type FieldIsArray ("pObjectEntryCounts" :: Symbol) VkObjectTableCreateInfoNVX :: Bool Source #

HasField "pObjectEntryTypes" VkObjectTableCreateInfoNVX Source # 

Associated Types

type FieldType ("pObjectEntryTypes" :: Symbol) VkObjectTableCreateInfoNVX :: Type Source #

type FieldOptional ("pObjectEntryTypes" :: Symbol) VkObjectTableCreateInfoNVX :: Bool Source #

type FieldOffset ("pObjectEntryTypes" :: Symbol) VkObjectTableCreateInfoNVX :: Nat Source #

type FieldIsArray ("pObjectEntryTypes" :: Symbol) VkObjectTableCreateInfoNVX :: Bool Source #

HasField "pObjectEntryUsageFlags" VkObjectTableCreateInfoNVX Source # 

Associated Types

type FieldType ("pObjectEntryUsageFlags" :: Symbol) VkObjectTableCreateInfoNVX :: Type Source #

type FieldOptional ("pObjectEntryUsageFlags" :: Symbol) VkObjectTableCreateInfoNVX :: Bool Source #

type FieldOffset ("pObjectEntryUsageFlags" :: Symbol) VkObjectTableCreateInfoNVX :: Nat Source #

type FieldIsArray ("pObjectEntryUsageFlags" :: Symbol) VkObjectTableCreateInfoNVX :: Bool Source #

HasField "sType" VkObjectTableCreateInfoNVX Source # 
type StructFields VkObjectTableCreateInfoNVX Source # 
type StructFields VkObjectTableCreateInfoNVX = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "objectCount" ((:) Symbol "pObjectEntryTypes" ((:) Symbol "pObjectEntryCounts" ((:) Symbol "pObjectEntryUsageFlags" ((:) Symbol "maxUniformBuffersPerDescriptor" ((:) Symbol "maxStorageBuffersPerDescriptor" ((:) Symbol "maxStorageImagesPerDescriptor" ((:) Symbol "maxSampledImagesPerDescriptor" ((:) Symbol "maxPipelineLayouts" ([] Symbol)))))))))))
type CUnionType VkObjectTableCreateInfoNVX Source # 
type ReturnedOnly VkObjectTableCreateInfoNVX Source # 
type StructExtends VkObjectTableCreateInfoNVX Source # 
type FieldType "maxPipelineLayouts" VkObjectTableCreateInfoNVX Source # 
type FieldType "maxPipelineLayouts" VkObjectTableCreateInfoNVX = Word32
type FieldType "maxSampledImagesPerDescriptor" VkObjectTableCreateInfoNVX Source # 
type FieldType "maxSampledImagesPerDescriptor" VkObjectTableCreateInfoNVX = Word32
type FieldType "maxStorageBuffersPerDescriptor" VkObjectTableCreateInfoNVX Source # 
type FieldType "maxStorageBuffersPerDescriptor" VkObjectTableCreateInfoNVX = Word32
type FieldType "maxStorageImagesPerDescriptor" VkObjectTableCreateInfoNVX Source # 
type FieldType "maxStorageImagesPerDescriptor" VkObjectTableCreateInfoNVX = Word32
type FieldType "maxUniformBuffersPerDescriptor" VkObjectTableCreateInfoNVX Source # 
type FieldType "maxUniformBuffersPerDescriptor" VkObjectTableCreateInfoNVX = Word32
type FieldType "objectCount" VkObjectTableCreateInfoNVX Source # 
type FieldType "pNext" VkObjectTableCreateInfoNVX Source # 
type FieldType "pObjectEntryCounts" VkObjectTableCreateInfoNVX Source # 
type FieldType "pObjectEntryCounts" VkObjectTableCreateInfoNVX = Ptr Word32
type FieldType "pObjectEntryTypes" VkObjectTableCreateInfoNVX Source # 
type FieldType "pObjectEntryUsageFlags" VkObjectTableCreateInfoNVX Source # 
type FieldType "sType" VkObjectTableCreateInfoNVX Source # 
type FieldOptional "maxPipelineLayouts" VkObjectTableCreateInfoNVX Source # 
type FieldOptional "maxPipelineLayouts" VkObjectTableCreateInfoNVX = False
type FieldOptional "maxSampledImagesPerDescriptor" VkObjectTableCreateInfoNVX Source # 
type FieldOptional "maxSampledImagesPerDescriptor" VkObjectTableCreateInfoNVX = False
type FieldOptional "maxStorageBuffersPerDescriptor" VkObjectTableCreateInfoNVX Source # 
type FieldOptional "maxStorageBuffersPerDescriptor" VkObjectTableCreateInfoNVX = False
type FieldOptional "maxStorageImagesPerDescriptor" VkObjectTableCreateInfoNVX Source # 
type FieldOptional "maxStorageImagesPerDescriptor" VkObjectTableCreateInfoNVX = False
type FieldOptional "maxUniformBuffersPerDescriptor" VkObjectTableCreateInfoNVX Source # 
type FieldOptional "maxUniformBuffersPerDescriptor" VkObjectTableCreateInfoNVX = False
type FieldOptional "objectCount" VkObjectTableCreateInfoNVX Source # 
type FieldOptional "pNext" VkObjectTableCreateInfoNVX Source # 
type FieldOptional "pObjectEntryCounts" VkObjectTableCreateInfoNVX Source # 
type FieldOptional "pObjectEntryCounts" VkObjectTableCreateInfoNVX = False
type FieldOptional "pObjectEntryTypes" VkObjectTableCreateInfoNVX Source # 
type FieldOptional "pObjectEntryUsageFlags" VkObjectTableCreateInfoNVX Source # 
type FieldOptional "pObjectEntryUsageFlags" VkObjectTableCreateInfoNVX = False
type FieldOptional "sType" VkObjectTableCreateInfoNVX Source # 
type FieldOffset "maxPipelineLayouts" VkObjectTableCreateInfoNVX Source # 
type FieldOffset "maxPipelineLayouts" VkObjectTableCreateInfoNVX = 64
type FieldOffset "maxSampledImagesPerDescriptor" VkObjectTableCreateInfoNVX Source # 
type FieldOffset "maxSampledImagesPerDescriptor" VkObjectTableCreateInfoNVX = 60
type FieldOffset "maxStorageBuffersPerDescriptor" VkObjectTableCreateInfoNVX Source # 
type FieldOffset "maxStorageBuffersPerDescriptor" VkObjectTableCreateInfoNVX = 52
type FieldOffset "maxStorageImagesPerDescriptor" VkObjectTableCreateInfoNVX Source # 
type FieldOffset "maxStorageImagesPerDescriptor" VkObjectTableCreateInfoNVX = 56
type FieldOffset "maxUniformBuffersPerDescriptor" VkObjectTableCreateInfoNVX Source # 
type FieldOffset "maxUniformBuffersPerDescriptor" VkObjectTableCreateInfoNVX = 48
type FieldOffset "objectCount" VkObjectTableCreateInfoNVX Source # 
type FieldOffset "objectCount" VkObjectTableCreateInfoNVX = 16
type FieldOffset "pNext" VkObjectTableCreateInfoNVX Source # 
type FieldOffset "pObjectEntryCounts" VkObjectTableCreateInfoNVX Source # 
type FieldOffset "pObjectEntryCounts" VkObjectTableCreateInfoNVX = 32
type FieldOffset "pObjectEntryTypes" VkObjectTableCreateInfoNVX Source # 
type FieldOffset "pObjectEntryTypes" VkObjectTableCreateInfoNVX = 24
type FieldOffset "pObjectEntryUsageFlags" VkObjectTableCreateInfoNVX Source # 
type FieldOffset "pObjectEntryUsageFlags" VkObjectTableCreateInfoNVX = 40
type FieldOffset "sType" VkObjectTableCreateInfoNVX Source # 
type FieldIsArray "maxPipelineLayouts" VkObjectTableCreateInfoNVX Source # 
type FieldIsArray "maxPipelineLayouts" VkObjectTableCreateInfoNVX = False
type FieldIsArray "maxSampledImagesPerDescriptor" VkObjectTableCreateInfoNVX Source # 
type FieldIsArray "maxSampledImagesPerDescriptor" VkObjectTableCreateInfoNVX = False
type FieldIsArray "maxStorageBuffersPerDescriptor" VkObjectTableCreateInfoNVX Source # 
type FieldIsArray "maxStorageBuffersPerDescriptor" VkObjectTableCreateInfoNVX = False
type FieldIsArray "maxStorageImagesPerDescriptor" VkObjectTableCreateInfoNVX Source # 
type FieldIsArray "maxStorageImagesPerDescriptor" VkObjectTableCreateInfoNVX = False
type FieldIsArray "maxUniformBuffersPerDescriptor" VkObjectTableCreateInfoNVX Source # 
type FieldIsArray "maxUniformBuffersPerDescriptor" VkObjectTableCreateInfoNVX = False
type FieldIsArray "objectCount" VkObjectTableCreateInfoNVX Source # 
type FieldIsArray "pNext" VkObjectTableCreateInfoNVX Source # 
type FieldIsArray "pObjectEntryCounts" VkObjectTableCreateInfoNVX Source # 
type FieldIsArray "pObjectEntryCounts" VkObjectTableCreateInfoNVX = False
type FieldIsArray "pObjectEntryTypes" VkObjectTableCreateInfoNVX Source # 
type FieldIsArray "pObjectEntryTypes" VkObjectTableCreateInfoNVX = False
type FieldIsArray "pObjectEntryUsageFlags" VkObjectTableCreateInfoNVX Source # 
type FieldIsArray "pObjectEntryUsageFlags" VkObjectTableCreateInfoNVX = False
type FieldIsArray "sType" VkObjectTableCreateInfoNVX Source # 

data VkObjectTableDescriptorSetEntryNVX Source #

typedef struct VkObjectTableDescriptorSetEntryNVX {
    VkObjectEntryTypeNVX         type;
    VkObjectEntryUsageFlagsNVX   flags;
    VkPipelineLayout             pipelineLayout;
    VkDescriptorSet              descriptorSet;
} VkObjectTableDescriptorSetEntryNVX;

VkObjectTableDescriptorSetEntryNVX registry at www.khronos.org

Instances

Eq VkObjectTableDescriptorSetEntryNVX Source # 
Ord VkObjectTableDescriptorSetEntryNVX Source # 
Show VkObjectTableDescriptorSetEntryNVX Source # 
Storable VkObjectTableDescriptorSetEntryNVX Source # 
VulkanMarshalPrim VkObjectTableDescriptorSetEntryNVX Source # 
VulkanMarshal VkObjectTableDescriptorSetEntryNVX Source # 
CanWriteField "descriptorSet" VkObjectTableDescriptorSetEntryNVX Source # 
CanWriteField "flags" VkObjectTableDescriptorSetEntryNVX Source # 
CanWriteField "pipelineLayout" VkObjectTableDescriptorSetEntryNVX Source # 
CanWriteField "type" VkObjectTableDescriptorSetEntryNVX Source # 
CanReadField "descriptorSet" VkObjectTableDescriptorSetEntryNVX Source # 
CanReadField "flags" VkObjectTableDescriptorSetEntryNVX Source # 
CanReadField "pipelineLayout" VkObjectTableDescriptorSetEntryNVX Source # 
CanReadField "type" VkObjectTableDescriptorSetEntryNVX Source # 
HasField "descriptorSet" VkObjectTableDescriptorSetEntryNVX Source # 
HasField "flags" VkObjectTableDescriptorSetEntryNVX Source # 
HasField "pipelineLayout" VkObjectTableDescriptorSetEntryNVX Source # 
HasField "type" VkObjectTableDescriptorSetEntryNVX Source # 
type StructFields VkObjectTableDescriptorSetEntryNVX Source # 
type StructFields VkObjectTableDescriptorSetEntryNVX = (:) Symbol "type" ((:) Symbol "flags" ((:) Symbol "pipelineLayout" ((:) Symbol "descriptorSet" ([] Symbol))))
type CUnionType VkObjectTableDescriptorSetEntryNVX Source # 
type ReturnedOnly VkObjectTableDescriptorSetEntryNVX Source # 
type StructExtends VkObjectTableDescriptorSetEntryNVX Source # 
type FieldType "descriptorSet" VkObjectTableDescriptorSetEntryNVX Source # 
type FieldType "flags" VkObjectTableDescriptorSetEntryNVX Source # 
type FieldType "pipelineLayout" VkObjectTableDescriptorSetEntryNVX Source # 
type FieldType "type" VkObjectTableDescriptorSetEntryNVX Source # 
type FieldOptional "descriptorSet" VkObjectTableDescriptorSetEntryNVX Source # 
type FieldOptional "flags" VkObjectTableDescriptorSetEntryNVX Source # 
type FieldOptional "pipelineLayout" VkObjectTableDescriptorSetEntryNVX Source # 
type FieldOptional "type" VkObjectTableDescriptorSetEntryNVX Source # 
type FieldOffset "descriptorSet" VkObjectTableDescriptorSetEntryNVX Source # 
type FieldOffset "flags" VkObjectTableDescriptorSetEntryNVX Source # 
type FieldOffset "pipelineLayout" VkObjectTableDescriptorSetEntryNVX Source # 
type FieldOffset "type" VkObjectTableDescriptorSetEntryNVX Source # 
type FieldIsArray "descriptorSet" VkObjectTableDescriptorSetEntryNVX Source # 
type FieldIsArray "flags" VkObjectTableDescriptorSetEntryNVX Source # 
type FieldIsArray "pipelineLayout" VkObjectTableDescriptorSetEntryNVX Source # 
type FieldIsArray "type" VkObjectTableDescriptorSetEntryNVX Source # 

data VkObjectTableEntryNVX Source #

typedef struct VkObjectTableEntryNVX {
    VkObjectEntryTypeNVX         type;
    VkObjectEntryUsageFlagsNVX   flags;
} VkObjectTableEntryNVX;

VkObjectTableEntryNVX registry at www.khronos.org

Instances

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

data VkObjectTableIndexBufferEntryNVX Source #

typedef struct VkObjectTableIndexBufferEntryNVX {
    VkObjectEntryTypeNVX         type;
    VkObjectEntryUsageFlagsNVX   flags;
    VkBuffer                     buffer;
    VkIndexType                  indexType;
} VkObjectTableIndexBufferEntryNVX;

VkObjectTableIndexBufferEntryNVX registry at www.khronos.org

Instances

Eq VkObjectTableIndexBufferEntryNVX Source # 
Ord VkObjectTableIndexBufferEntryNVX Source # 
Show VkObjectTableIndexBufferEntryNVX Source # 
Storable VkObjectTableIndexBufferEntryNVX Source # 
VulkanMarshalPrim VkObjectTableIndexBufferEntryNVX Source # 
VulkanMarshal VkObjectTableIndexBufferEntryNVX Source # 
CanWriteField "buffer" VkObjectTableIndexBufferEntryNVX Source # 
CanWriteField "flags" VkObjectTableIndexBufferEntryNVX Source # 
CanWriteField "indexType" VkObjectTableIndexBufferEntryNVX Source # 
CanWriteField "type" VkObjectTableIndexBufferEntryNVX Source # 
CanReadField "buffer" VkObjectTableIndexBufferEntryNVX Source # 
CanReadField "flags" VkObjectTableIndexBufferEntryNVX Source # 
CanReadField "indexType" VkObjectTableIndexBufferEntryNVX Source # 
CanReadField "type" VkObjectTableIndexBufferEntryNVX Source # 
HasField "buffer" VkObjectTableIndexBufferEntryNVX Source # 
HasField "flags" VkObjectTableIndexBufferEntryNVX Source # 
HasField "indexType" VkObjectTableIndexBufferEntryNVX Source # 
HasField "type" VkObjectTableIndexBufferEntryNVX Source # 
type StructFields VkObjectTableIndexBufferEntryNVX Source # 
type StructFields VkObjectTableIndexBufferEntryNVX = (:) Symbol "type" ((:) Symbol "flags" ((:) Symbol "buffer" ((:) Symbol "indexType" ([] Symbol))))
type CUnionType VkObjectTableIndexBufferEntryNVX Source # 
type ReturnedOnly VkObjectTableIndexBufferEntryNVX Source # 
type StructExtends VkObjectTableIndexBufferEntryNVX Source # 
type FieldType "buffer" VkObjectTableIndexBufferEntryNVX Source # 
type FieldType "flags" VkObjectTableIndexBufferEntryNVX Source # 
type FieldType "indexType" VkObjectTableIndexBufferEntryNVX Source # 
type FieldType "type" VkObjectTableIndexBufferEntryNVX Source # 
type FieldOptional "buffer" VkObjectTableIndexBufferEntryNVX Source # 
type FieldOptional "flags" VkObjectTableIndexBufferEntryNVX Source # 
type FieldOptional "indexType" VkObjectTableIndexBufferEntryNVX Source # 
type FieldOptional "type" VkObjectTableIndexBufferEntryNVX Source # 
type FieldOffset "buffer" VkObjectTableIndexBufferEntryNVX Source # 
type FieldOffset "flags" VkObjectTableIndexBufferEntryNVX Source # 
type FieldOffset "indexType" VkObjectTableIndexBufferEntryNVX Source # 
type FieldOffset "type" VkObjectTableIndexBufferEntryNVX Source # 
type FieldIsArray "buffer" VkObjectTableIndexBufferEntryNVX Source # 
type FieldIsArray "flags" VkObjectTableIndexBufferEntryNVX Source # 
type FieldIsArray "indexType" VkObjectTableIndexBufferEntryNVX Source # 
type FieldIsArray "type" VkObjectTableIndexBufferEntryNVX Source # 

data VkObjectTablePipelineEntryNVX Source #

typedef struct VkObjectTablePipelineEntryNVX {
    VkObjectEntryTypeNVX         type;
    VkObjectEntryUsageFlagsNVX   flags;
    VkPipeline                   pipeline;
} VkObjectTablePipelineEntryNVX;

VkObjectTablePipelineEntryNVX registry at www.khronos.org

Instances

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

data VkObjectTablePushConstantEntryNVX Source #

typedef struct VkObjectTablePushConstantEntryNVX {
    VkObjectEntryTypeNVX         type;
    VkObjectEntryUsageFlagsNVX   flags;
    VkPipelineLayout             pipelineLayout;
    VkShaderStageFlags           stageFlags;
} VkObjectTablePushConstantEntryNVX;

VkObjectTablePushConstantEntryNVX registry at www.khronos.org

Instances

Eq VkObjectTablePushConstantEntryNVX Source # 
Ord VkObjectTablePushConstantEntryNVX Source # 
Show VkObjectTablePushConstantEntryNVX Source # 
Storable VkObjectTablePushConstantEntryNVX Source # 
VulkanMarshalPrim VkObjectTablePushConstantEntryNVX Source # 
VulkanMarshal VkObjectTablePushConstantEntryNVX Source # 
CanWriteField "flags" VkObjectTablePushConstantEntryNVX Source # 
CanWriteField "pipelineLayout" VkObjectTablePushConstantEntryNVX Source # 
CanWriteField "stageFlags" VkObjectTablePushConstantEntryNVX Source # 
CanWriteField "type" VkObjectTablePushConstantEntryNVX Source # 
CanReadField "flags" VkObjectTablePushConstantEntryNVX Source # 
CanReadField "pipelineLayout" VkObjectTablePushConstantEntryNVX Source # 
CanReadField "stageFlags" VkObjectTablePushConstantEntryNVX Source # 
CanReadField "type" VkObjectTablePushConstantEntryNVX Source # 
HasField "flags" VkObjectTablePushConstantEntryNVX Source # 
HasField "pipelineLayout" VkObjectTablePushConstantEntryNVX Source # 
HasField "stageFlags" VkObjectTablePushConstantEntryNVX Source # 
HasField "type" VkObjectTablePushConstantEntryNVX Source # 
type StructFields VkObjectTablePushConstantEntryNVX Source # 
type StructFields VkObjectTablePushConstantEntryNVX = (:) Symbol "type" ((:) Symbol "flags" ((:) Symbol "pipelineLayout" ((:) Symbol "stageFlags" ([] Symbol))))
type CUnionType VkObjectTablePushConstantEntryNVX Source # 
type ReturnedOnly VkObjectTablePushConstantEntryNVX Source # 
type StructExtends VkObjectTablePushConstantEntryNVX Source # 
type FieldType "flags" VkObjectTablePushConstantEntryNVX Source # 
type FieldType "pipelineLayout" VkObjectTablePushConstantEntryNVX Source # 
type FieldType "stageFlags" VkObjectTablePushConstantEntryNVX Source # 
type FieldType "type" VkObjectTablePushConstantEntryNVX Source # 
type FieldOptional "flags" VkObjectTablePushConstantEntryNVX Source # 
type FieldOptional "pipelineLayout" VkObjectTablePushConstantEntryNVX Source # 
type FieldOptional "stageFlags" VkObjectTablePushConstantEntryNVX Source # 
type FieldOptional "type" VkObjectTablePushConstantEntryNVX Source # 
type FieldOffset "flags" VkObjectTablePushConstantEntryNVX Source # 
type FieldOffset "pipelineLayout" VkObjectTablePushConstantEntryNVX Source # 
type FieldOffset "stageFlags" VkObjectTablePushConstantEntryNVX Source # 
type FieldOffset "type" VkObjectTablePushConstantEntryNVX Source # 
type FieldIsArray "flags" VkObjectTablePushConstantEntryNVX Source # 
type FieldIsArray "pipelineLayout" VkObjectTablePushConstantEntryNVX Source # 
type FieldIsArray "stageFlags" VkObjectTablePushConstantEntryNVX Source # 
type FieldIsArray "type" VkObjectTablePushConstantEntryNVX Source # 

data VkObjectTableVertexBufferEntryNVX Source #

typedef struct VkObjectTableVertexBufferEntryNVX {
    VkObjectEntryTypeNVX         type;
    VkObjectEntryUsageFlagsNVX   flags;
    VkBuffer                     buffer;
} VkObjectTableVertexBufferEntryNVX;

VkObjectTableVertexBufferEntryNVX registry at www.khronos.org

Instances

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

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 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

type VkCmdProcessCommandsNVX = "vkCmdProcessCommandsNVX" Source #

type HS_vkCmdProcessCommandsNVX Source #

Arguments

 = VkCommandBuffer

commandBuffer

-> Ptr VkCmdProcessCommandsInfoNVX

pProcessCommandsInfo

-> IO () 

Queues: graphics, compute.

Renderpass: inside

void vkCmdProcessCommandsNVX
    ( VkCommandBuffer commandBuffer
    , const VkCmdProcessCommandsInfoNVX* pProcessCommandsInfo
    )

vkCmdProcessCommandsNVX registry at www.khronos.org

type VkCmdReserveSpaceForCommandsNVX = "vkCmdReserveSpaceForCommandsNVX" Source #

type HS_vkCmdReserveSpaceForCommandsNVX Source #

Arguments

 = VkCommandBuffer

commandBuffer

-> Ptr VkCmdReserveSpaceForCommandsInfoNVX

pReserveSpaceInfo

-> IO () 

Queues: graphics, compute.

Renderpass: inside

void vkCmdReserveSpaceForCommandsNVX
    ( VkCommandBuffer commandBuffer
    , const VkCmdReserveSpaceForCommandsInfoNVX* pReserveSpaceInfo
    )

vkCmdReserveSpaceForCommandsNVX registry at www.khronos.org

type VkCreateIndirectCommandsLayoutNVX = "vkCreateIndirectCommandsLayoutNVX" Source #

type HS_vkCreateIndirectCommandsLayoutNVX Source #

Arguments

 = VkDevice

device

-> Ptr VkIndirectCommandsLayoutCreateInfoNVX

pCreateInfo

-> Ptr VkAllocationCallbacks

pAllocator

-> Ptr VkIndirectCommandsLayoutNVX

pIndirectCommandsLayout

-> IO VkResult 

Success codes: VK_SUCCESS.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY.

VkResult vkCreateIndirectCommandsLayoutNVX
    ( VkDevice device
    , const VkIndirectCommandsLayoutCreateInfoNVX* pCreateInfo
    , const VkAllocationCallbacks* pAllocator
    , VkIndirectCommandsLayoutNVX* pIndirectCommandsLayout
    )

vkCreateIndirectCommandsLayoutNVX registry at www.khronos.org

type VkDestroyIndirectCommandsLayoutNVX = "vkDestroyIndirectCommandsLayoutNVX" Source #

type HS_vkDestroyIndirectCommandsLayoutNVX Source #

Arguments

 = VkDevice

device

-> VkIndirectCommandsLayoutNVX

indirectCommandsLayout

-> Ptr VkAllocationCallbacks

pAllocator

-> IO () 
void vkDestroyIndirectCommandsLayoutNVX
    ( VkDevice device
    , VkIndirectCommandsLayoutNVX indirectCommandsLayout
    , const VkAllocationCallbacks* pAllocator
    )

vkDestroyIndirectCommandsLayoutNVX registry at www.khronos.org

type VkCreateObjectTableNVX = "vkCreateObjectTableNVX" Source #

type HS_vkCreateObjectTableNVX Source #

Arguments

 = VkDevice

device

-> Ptr VkObjectTableCreateInfoNVX

pCreateInfo

-> Ptr VkAllocationCallbacks

pAllocator

-> Ptr VkObjectTableNVX

pObjectTable

-> IO VkResult 

Success codes: VK_SUCCESS.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY.

VkResult vkCreateObjectTableNVX
    ( VkDevice device
    , const VkObjectTableCreateInfoNVX* pCreateInfo
    , const VkAllocationCallbacks* pAllocator
    , VkObjectTableNVX* pObjectTable
    )

vkCreateObjectTableNVX registry at www.khronos.org

type VkDestroyObjectTableNVX = "vkDestroyObjectTableNVX" Source #

type HS_vkDestroyObjectTableNVX Source #

Arguments

 = VkDevice

device

-> VkObjectTableNVX

objectTable

-> Ptr VkAllocationCallbacks

pAllocator

-> IO () 
void vkDestroyObjectTableNVX
    ( VkDevice device
    , VkObjectTableNVX objectTable
    , const VkAllocationCallbacks* pAllocator
    )

vkDestroyObjectTableNVX registry at www.khronos.org

type VkRegisterObjectsNVX = "vkRegisterObjectsNVX" Source #

type HS_vkRegisterObjectsNVX Source #

Arguments

 = VkDevice

device

-> VkObjectTableNVX

objectTable

-> Word32

objectCount

-> Ptr (Ptr VkObjectTableEntryNVX)

ppObjectTableEntries

-> Ptr Word32

pObjectIndices

-> IO VkResult 

Success codes: VK_SUCCESS.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY.

VkResult vkRegisterObjectsNVX
    ( VkDevice device
    , VkObjectTableNVX objectTable
    , uint32_t objectCount
    , const VkObjectTableEntryNVX* const*    ppObjectTableEntries
    , const uint32_t* pObjectIndices
    )

vkRegisterObjectsNVX registry at www.khronos.org

type VkUnregisterObjectsNVX = "vkUnregisterObjectsNVX" Source #

type HS_vkUnregisterObjectsNVX Source #

Arguments

 = VkDevice

device

-> VkObjectTableNVX

objectTable

-> Word32

objectCount

-> Ptr VkObjectEntryTypeNVX

pObjectEntryTypes

-> Ptr Word32

pObjectIndices

-> IO VkResult 

Success codes: VK_SUCCESS.

Error codes: VK_ERROR_OUT_OF_HOST_MEMORY, VK_ERROR_OUT_OF_DEVICE_MEMORY.

VkResult vkUnregisterObjectsNVX
    ( VkDevice device
    , VkObjectTableNVX objectTable
    , uint32_t objectCount
    , const VkObjectEntryTypeNVX* pObjectEntryTypes
    , const uint32_t* pObjectIndices
    )

vkUnregisterObjectsNVX registry at www.khronos.org

type VkGetPhysicalDeviceGeneratedCommandsPropertiesNVX = "vkGetPhysicalDeviceGeneratedCommandsPropertiesNVX" Source #

type HS_vkGetPhysicalDeviceGeneratedCommandsPropertiesNVX Source #

void vkGetPhysicalDeviceGeneratedCommandsPropertiesNVX
    ( VkPhysicalDevice physicalDevice
    , VkDeviceGeneratedCommandsFeaturesNVX* pFeatures
    , VkDeviceGeneratedCommandsLimitsNVX* pLimits
    )

vkGetPhysicalDeviceGeneratedCommandsPropertiesNVX registry at www.khronos.org

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 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

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 VkBuffer_T Source #

Opaque data type referenced by VkBuffer

data VkBufferView_T Source #

Opaque data type referenced by VkBufferView

data VkCommandBuffer_T Source #

Opaque data type referenced by VkCommandBuffer

data VkCommandPool_T Source #

Opaque data type referenced by VkCommandPool

data VkDebugReportCallbackEXT_T Source #

Opaque data type referenced by VkDebugReportCallbackEXT

data VkDebugUtilsMessengerEXT_T Source #

Opaque data type referenced by VkDebugUtilsMessengerEXT

data VkDescriptorPool_T Source #

Opaque data type referenced by VkDescriptorPool

data VkDescriptorSet_T Source #

Opaque data type referenced by VkDescriptorSet

data VkDescriptorSetLayout_T Source #

Opaque data type referenced by VkDescriptorSetLayout

data VkDescriptorUpdateTemplate_T Source #

Opaque data type referenced by VkDescriptorUpdateTemplate

data VkDescriptorUpdateTemplateKHR_T Source #

Opaque data type referenced by VkDescriptorUpdateTemplateKHR

data VkDevice_T Source #

Opaque data type referenced by VkDevice

data VkDeviceMemory_T Source #

Opaque data type referenced by VkDeviceMemory

data VkDisplayKHR_T Source #

Opaque data type referenced by VkDisplayKHR

data VkDisplayModeKHR_T Source #

Opaque data type referenced by VkDisplayModeKHR

data VkEvent_T Source #

Opaque data type referenced by VkEvent

data VkFence_T Source #

Opaque data type referenced by VkFence

data VkFramebuffer_T Source #

Opaque data type referenced by VkFramebuffer

data VkImage_T Source #

Opaque data type referenced by VkImage

data VkImageView_T Source #

Opaque data type referenced by VkImageView

data VkIndirectCommandsLayoutNVX_T Source #

Opaque data type referenced by VkIndirectCommandsLayoutNVX

data VkInstance_T Source #

Opaque data type referenced by VkInstance

data VkObjectTableNVX_T Source #

Opaque data type referenced by VkObjectTableNVX

data VkPhysicalDevice_T Source #

Opaque data type referenced by VkPhysicalDevice

data VkPipeline_T Source #

Opaque data type referenced by VkPipeline

data VkPipelineCache_T Source #

Opaque data type referenced by VkPipelineCache

data VkPipelineLayout_T Source #

Opaque data type referenced by VkPipelineLayout

data VkQueryPool_T Source #

Opaque data type referenced by VkQueryPool

data VkQueue_T Source #

Opaque data type referenced by VkQueue

data VkRenderPass_T Source #

Opaque data type referenced by VkRenderPass

data VkSampler_T Source #

Opaque data type referenced by VkSampler

data VkSamplerYcbcrConversion_T Source #

Opaque data type referenced by VkSamplerYcbcrConversion

data VkSamplerYcbcrConversionKHR_T Source #

Opaque data type referenced by VkSamplerYcbcrConversionKHR

data VkSemaphore_T Source #

Opaque data type referenced by VkSemaphore

data VkShaderModule_T Source #

Opaque data type referenced by VkShaderModule

data VkSurfaceKHR_T Source #

Opaque data type referenced by VkSurfaceKHR

data VkSwapchainKHR_T Source #

Opaque data type referenced by VkSwapchainKHR

data VkValidationCacheEXT_T Source #

Opaque data type referenced by VkValidationCacheEXT

data VkAllocationCallbacks Source #

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

VkAllocationCallbacks registry at www.khronos.org

Instances

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

Methods

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

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

Associated Types

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

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

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

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

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

Associated Types

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

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

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

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

HasField "pfnInternalFree" VkAllocationCallbacks Source # 

Associated Types

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

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

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

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

HasField "pfnReallocation" VkAllocationCallbacks Source # 

Associated Types

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

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

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

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

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

type VK_NVX_DEVICE_GENERATED_COMMANDS_EXTENSION_NAME = "VK_NVX_device_generated_commands" Source #

Orphan instances

VulkanProc "vkCmdProcessCommandsNVX" Source # 

Associated Types

type VkProcType ("vkCmdProcessCommandsNVX" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkCmdProcessCommandsNVX") -> VkProcType "vkCmdProcessCommandsNVX" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkCmdProcessCommandsNVX") -> VkProcType "vkCmdProcessCommandsNVX" Source #

VulkanProc "vkCmdReserveSpaceForCommandsNVX" Source # 

Associated Types

type VkProcType ("vkCmdReserveSpaceForCommandsNVX" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkCmdReserveSpaceForCommandsNVX") -> VkProcType "vkCmdReserveSpaceForCommandsNVX" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkCmdReserveSpaceForCommandsNVX") -> VkProcType "vkCmdReserveSpaceForCommandsNVX" Source #

VulkanProc "vkCreateIndirectCommandsLayoutNVX" Source # 

Associated Types

type VkProcType ("vkCreateIndirectCommandsLayoutNVX" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkCreateIndirectCommandsLayoutNVX") -> VkProcType "vkCreateIndirectCommandsLayoutNVX" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkCreateIndirectCommandsLayoutNVX") -> VkProcType "vkCreateIndirectCommandsLayoutNVX" Source #

VulkanProc "vkCreateObjectTableNVX" Source # 

Associated Types

type VkProcType ("vkCreateObjectTableNVX" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkCreateObjectTableNVX") -> VkProcType "vkCreateObjectTableNVX" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkCreateObjectTableNVX") -> VkProcType "vkCreateObjectTableNVX" Source #

VulkanProc "vkDestroyIndirectCommandsLayoutNVX" Source # 

Associated Types

type VkProcType ("vkDestroyIndirectCommandsLayoutNVX" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkDestroyIndirectCommandsLayoutNVX") -> VkProcType "vkDestroyIndirectCommandsLayoutNVX" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkDestroyIndirectCommandsLayoutNVX") -> VkProcType "vkDestroyIndirectCommandsLayoutNVX" Source #

VulkanProc "vkDestroyObjectTableNVX" Source # 

Associated Types

type VkProcType ("vkDestroyObjectTableNVX" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkDestroyObjectTableNVX") -> VkProcType "vkDestroyObjectTableNVX" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkDestroyObjectTableNVX") -> VkProcType "vkDestroyObjectTableNVX" Source #

VulkanProc "vkGetPhysicalDeviceGeneratedCommandsPropertiesNVX" Source # 

Associated Types

type VkProcType ("vkGetPhysicalDeviceGeneratedCommandsPropertiesNVX" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkGetPhysicalDeviceGeneratedCommandsPropertiesNVX") -> VkProcType "vkGetPhysicalDeviceGeneratedCommandsPropertiesNVX" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkGetPhysicalDeviceGeneratedCommandsPropertiesNVX") -> VkProcType "vkGetPhysicalDeviceGeneratedCommandsPropertiesNVX" Source #

VulkanProc "vkRegisterObjectsNVX" Source # 

Associated Types

type VkProcType ("vkRegisterObjectsNVX" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkRegisterObjectsNVX") -> VkProcType "vkRegisterObjectsNVX" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkRegisterObjectsNVX") -> VkProcType "vkRegisterObjectsNVX" Source #

VulkanProc "vkUnregisterObjectsNVX" Source # 

Associated Types

type VkProcType ("vkUnregisterObjectsNVX" :: Symbol) :: * Source #

Methods

vkProcSymbol :: CString Source #

unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkUnregisterObjectsNVX") -> VkProcType "vkUnregisterObjectsNVX" Source #

unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkUnregisterObjectsNVX") -> VkProcType "vkUnregisterObjectsNVX" Source #