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

Safe HaskellNone
LanguageHaskell2010

Graphics.Vulkan.Ext.VK_NV_dedicated_allocation

Contents

Synopsis

Vulkan extension: VK_NV_dedicated_allocation

supported: vulkan

contact: Jeff Bolz jeffbolznv@

author: NV

type: device

Extension number: 27

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

newtype VkBufferCreateBitmask a Source #

Instances

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

Methods

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

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

toConstr :: VkBufferCreateBitmask a -> Constr #

dataTypeOf :: VkBufferCreateBitmask a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

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

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

xor :: VkBufferCreateBitmask FlagMask -> VkBufferCreateBitmask FlagMask -> VkBufferCreateBitmask FlagMask #

complement :: VkBufferCreateBitmask FlagMask -> VkBufferCreateBitmask FlagMask #

shift :: VkBufferCreateBitmask FlagMask -> Int -> VkBufferCreateBitmask FlagMask #

rotate :: VkBufferCreateBitmask FlagMask -> Int -> VkBufferCreateBitmask FlagMask #

zeroBits :: VkBufferCreateBitmask FlagMask #

bit :: Int -> VkBufferCreateBitmask FlagMask #

setBit :: VkBufferCreateBitmask FlagMask -> Int -> VkBufferCreateBitmask FlagMask #

clearBit :: VkBufferCreateBitmask FlagMask -> Int -> VkBufferCreateBitmask FlagMask #

complementBit :: VkBufferCreateBitmask FlagMask -> Int -> VkBufferCreateBitmask FlagMask #

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

bitSizeMaybe :: VkBufferCreateBitmask FlagMask -> Maybe Int #

bitSize :: VkBufferCreateBitmask FlagMask -> Int #

isSigned :: VkBufferCreateBitmask FlagMask -> Bool #

shiftL :: VkBufferCreateBitmask FlagMask -> Int -> VkBufferCreateBitmask FlagMask #

unsafeShiftL :: VkBufferCreateBitmask FlagMask -> Int -> VkBufferCreateBitmask FlagMask #

shiftR :: VkBufferCreateBitmask FlagMask -> Int -> VkBufferCreateBitmask FlagMask #

unsafeShiftR :: VkBufferCreateBitmask FlagMask -> Int -> VkBufferCreateBitmask FlagMask #

rotateL :: VkBufferCreateBitmask FlagMask -> Int -> VkBufferCreateBitmask FlagMask #

rotateR :: VkBufferCreateBitmask FlagMask -> Int -> VkBufferCreateBitmask FlagMask #

popCount :: VkBufferCreateBitmask FlagMask -> Int #

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

pattern VK_BUFFER_CREATE_SPARSE_BINDING_BIT :: forall a. VkBufferCreateBitmask a Source #

Buffer should support sparse backing

bitpos = 0

pattern VK_BUFFER_CREATE_SPARSE_RESIDENCY_BIT :: forall a. VkBufferCreateBitmask a Source #

Buffer should support sparse backing with partial residency

bitpos = 1

pattern VK_BUFFER_CREATE_SPARSE_ALIASED_BIT :: forall a. VkBufferCreateBitmask a Source #

Buffer should support constent data access to physical memory ranges mapped into multiple locations of sparse buffers

bitpos = 2

newtype VkBufferUsageBitmask a Source #

Instances

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

Methods

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

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

toConstr :: VkBufferUsageBitmask a -> Constr #

dataTypeOf :: VkBufferUsageBitmask a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

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

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

xor :: VkBufferUsageBitmask FlagMask -> VkBufferUsageBitmask FlagMask -> VkBufferUsageBitmask FlagMask #

complement :: VkBufferUsageBitmask FlagMask -> VkBufferUsageBitmask FlagMask #

shift :: VkBufferUsageBitmask FlagMask -> Int -> VkBufferUsageBitmask FlagMask #

rotate :: VkBufferUsageBitmask FlagMask -> Int -> VkBufferUsageBitmask FlagMask #

zeroBits :: VkBufferUsageBitmask FlagMask #

bit :: Int -> VkBufferUsageBitmask FlagMask #

setBit :: VkBufferUsageBitmask FlagMask -> Int -> VkBufferUsageBitmask FlagMask #

clearBit :: VkBufferUsageBitmask FlagMask -> Int -> VkBufferUsageBitmask FlagMask #

complementBit :: VkBufferUsageBitmask FlagMask -> Int -> VkBufferUsageBitmask FlagMask #

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

bitSizeMaybe :: VkBufferUsageBitmask FlagMask -> Maybe Int #

bitSize :: VkBufferUsageBitmask FlagMask -> Int #

isSigned :: VkBufferUsageBitmask FlagMask -> Bool #

shiftL :: VkBufferUsageBitmask FlagMask -> Int -> VkBufferUsageBitmask FlagMask #

unsafeShiftL :: VkBufferUsageBitmask FlagMask -> Int -> VkBufferUsageBitmask FlagMask #

shiftR :: VkBufferUsageBitmask FlagMask -> Int -> VkBufferUsageBitmask FlagMask #

unsafeShiftR :: VkBufferUsageBitmask FlagMask -> Int -> VkBufferUsageBitmask FlagMask #

rotateL :: VkBufferUsageBitmask FlagMask -> Int -> VkBufferUsageBitmask FlagMask #

rotateR :: VkBufferUsageBitmask FlagMask -> Int -> VkBufferUsageBitmask FlagMask #

popCount :: VkBufferUsageBitmask FlagMask -> Int #

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

pattern VK_BUFFER_USAGE_TRANSFER_SRC_BIT :: forall a. VkBufferUsageBitmask a Source #

Can be used as a source of transfer operations

bitpos = 0

pattern VK_BUFFER_USAGE_TRANSFER_DST_BIT :: forall a. VkBufferUsageBitmask a Source #

Can be used as a destination of transfer operations

bitpos = 1

pattern VK_BUFFER_USAGE_UNIFORM_TEXEL_BUFFER_BIT :: forall a. VkBufferUsageBitmask a Source #

Can be used as TBO

bitpos = 2

pattern VK_BUFFER_USAGE_STORAGE_TEXEL_BUFFER_BIT :: forall a. VkBufferUsageBitmask a Source #

Can be used as IBO

bitpos = 3

pattern VK_BUFFER_USAGE_UNIFORM_BUFFER_BIT :: forall a. VkBufferUsageBitmask a Source #

Can be used as UBO

bitpos = 4

pattern VK_BUFFER_USAGE_STORAGE_BUFFER_BIT :: forall a. VkBufferUsageBitmask a Source #

Can be used as SSBO

bitpos = 5

pattern VK_BUFFER_USAGE_INDEX_BUFFER_BIT :: forall a. VkBufferUsageBitmask a Source #

Can be used as source of fixed-function index fetch (index buffer)

bitpos = 6

pattern VK_BUFFER_USAGE_VERTEX_BUFFER_BIT :: forall a. VkBufferUsageBitmask a Source #

Can be used as source of fixed-function vertex fetch (VBO)

bitpos = 7

pattern VK_BUFFER_USAGE_INDIRECT_BUFFER_BIT :: forall a. VkBufferUsageBitmask a Source #

Can be the source of indirect parameters (e.g. indirect buffer, parameter buffer)

bitpos = 8

newtype VkBufferViewCreateFlagBits Source #

Instances

Bounded VkBufferViewCreateFlagBits Source # 
Enum VkBufferViewCreateFlagBits Source # 
Eq VkBufferViewCreateFlagBits Source # 
Integral VkBufferViewCreateFlagBits Source # 
Data VkBufferViewCreateFlagBits Source # 

Methods

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

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

toConstr :: VkBufferViewCreateFlagBits -> Constr #

dataTypeOf :: VkBufferViewCreateFlagBits -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VkBufferViewCreateFlagBits Source # 
Ord VkBufferViewCreateFlagBits Source # 
Read VkBufferViewCreateFlagBits Source # 
Real VkBufferViewCreateFlagBits Source # 
Show VkBufferViewCreateFlagBits Source # 
Generic VkBufferViewCreateFlagBits Source # 
Storable VkBufferViewCreateFlagBits Source # 
Bits VkBufferViewCreateFlagBits Source # 

Methods

(.&.) :: VkBufferViewCreateFlagBits -> VkBufferViewCreateFlagBits -> VkBufferViewCreateFlagBits #

(.|.) :: VkBufferViewCreateFlagBits -> VkBufferViewCreateFlagBits -> VkBufferViewCreateFlagBits #

xor :: VkBufferViewCreateFlagBits -> VkBufferViewCreateFlagBits -> VkBufferViewCreateFlagBits #

complement :: VkBufferViewCreateFlagBits -> VkBufferViewCreateFlagBits #

shift :: VkBufferViewCreateFlagBits -> Int -> VkBufferViewCreateFlagBits #

rotate :: VkBufferViewCreateFlagBits -> Int -> VkBufferViewCreateFlagBits #

zeroBits :: VkBufferViewCreateFlagBits #

bit :: Int -> VkBufferViewCreateFlagBits #

setBit :: VkBufferViewCreateFlagBits -> Int -> VkBufferViewCreateFlagBits #

clearBit :: VkBufferViewCreateFlagBits -> Int -> VkBufferViewCreateFlagBits #

complementBit :: VkBufferViewCreateFlagBits -> Int -> VkBufferViewCreateFlagBits #

testBit :: VkBufferViewCreateFlagBits -> Int -> Bool #

bitSizeMaybe :: VkBufferViewCreateFlagBits -> Maybe Int #

bitSize :: VkBufferViewCreateFlagBits -> Int #

isSigned :: VkBufferViewCreateFlagBits -> Bool #

shiftL :: VkBufferViewCreateFlagBits -> Int -> VkBufferViewCreateFlagBits #

unsafeShiftL :: VkBufferViewCreateFlagBits -> Int -> VkBufferViewCreateFlagBits #

shiftR :: VkBufferViewCreateFlagBits -> Int -> VkBufferViewCreateFlagBits #

unsafeShiftR :: VkBufferViewCreateFlagBits -> Int -> VkBufferViewCreateFlagBits #

rotateL :: VkBufferViewCreateFlagBits -> Int -> VkBufferViewCreateFlagBits #

rotateR :: VkBufferViewCreateFlagBits -> Int -> VkBufferViewCreateFlagBits #

popCount :: VkBufferViewCreateFlagBits -> Int #

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

data VkBufferCopy Source #

typedef struct VkBufferCopy {
    VkDeviceSize           srcOffset;
    VkDeviceSize           dstOffset;
    VkDeviceSize           size;
} VkBufferCopy;

VkBufferCopy registry at www.khronos.org

Instances

Eq VkBufferCopy Source # 
Ord VkBufferCopy Source # 
Show VkBufferCopy Source # 
Storable VkBufferCopy Source # 
VulkanMarshalPrim VkBufferCopy Source # 
VulkanMarshal VkBufferCopy Source # 
CanWriteField "dstOffset" VkBufferCopy Source # 

Methods

writeField :: Ptr VkBufferCopy -> FieldType "dstOffset" VkBufferCopy -> IO () Source #

CanWriteField "size" VkBufferCopy Source # 
CanWriteField "srcOffset" VkBufferCopy Source # 

Methods

writeField :: Ptr VkBufferCopy -> FieldType "srcOffset" VkBufferCopy -> IO () Source #

CanReadField "dstOffset" VkBufferCopy Source # 
CanReadField "size" VkBufferCopy Source # 
CanReadField "srcOffset" VkBufferCopy Source # 
HasField "dstOffset" VkBufferCopy Source # 

Associated Types

type FieldType ("dstOffset" :: Symbol) VkBufferCopy :: Type Source #

type FieldOptional ("dstOffset" :: Symbol) VkBufferCopy :: Bool Source #

type FieldOffset ("dstOffset" :: Symbol) VkBufferCopy :: Nat Source #

type FieldIsArray ("dstOffset" :: Symbol) VkBufferCopy :: Bool Source #

HasField "size" VkBufferCopy Source # 
HasField "srcOffset" VkBufferCopy Source # 

Associated Types

type FieldType ("srcOffset" :: Symbol) VkBufferCopy :: Type Source #

type FieldOptional ("srcOffset" :: Symbol) VkBufferCopy :: Bool Source #

type FieldOffset ("srcOffset" :: Symbol) VkBufferCopy :: Nat Source #

type FieldIsArray ("srcOffset" :: Symbol) VkBufferCopy :: Bool Source #

type StructFields VkBufferCopy Source # 
type StructFields VkBufferCopy = (:) Symbol "srcOffset" ((:) Symbol "dstOffset" ((:) Symbol "size" ([] Symbol)))
type CUnionType VkBufferCopy Source # 
type ReturnedOnly VkBufferCopy Source # 
type StructExtends VkBufferCopy Source # 
type FieldType "dstOffset" VkBufferCopy Source # 
type FieldType "size" VkBufferCopy Source # 
type FieldType "srcOffset" VkBufferCopy Source # 
type FieldOptional "dstOffset" VkBufferCopy Source # 
type FieldOptional "dstOffset" VkBufferCopy = False
type FieldOptional "size" VkBufferCopy Source # 
type FieldOptional "srcOffset" VkBufferCopy Source # 
type FieldOptional "srcOffset" VkBufferCopy = False
type FieldOffset "dstOffset" VkBufferCopy Source # 
type FieldOffset "dstOffset" VkBufferCopy = 8
type FieldOffset "size" VkBufferCopy Source # 
type FieldOffset "size" VkBufferCopy = 16
type FieldOffset "srcOffset" VkBufferCopy Source # 
type FieldOffset "srcOffset" VkBufferCopy = 0
type FieldIsArray "dstOffset" VkBufferCopy Source # 
type FieldIsArray "dstOffset" VkBufferCopy = False
type FieldIsArray "size" VkBufferCopy Source # 
type FieldIsArray "srcOffset" VkBufferCopy Source # 
type FieldIsArray "srcOffset" VkBufferCopy = False

data VkBufferCreateInfo Source #

typedef struct VkBufferCreateInfo {
    VkStructureType sType;
    const void*            pNext;
    VkBufferCreateFlags    flags;
    VkDeviceSize           size;
    VkBufferUsageFlags     usage;
    VkSharingMode          sharingMode;
    uint32_t               queueFamilyIndexCount;
    const uint32_t*        pQueueFamilyIndices;
} VkBufferCreateInfo;

VkBufferCreateInfo registry at www.khronos.org

Instances

Eq VkBufferCreateInfo Source # 
Ord VkBufferCreateInfo Source # 
Show VkBufferCreateInfo Source # 
Storable VkBufferCreateInfo Source # 
VulkanMarshalPrim VkBufferCreateInfo Source # 
VulkanMarshal VkBufferCreateInfo Source # 
CanWriteField "flags" VkBufferCreateInfo Source # 
CanWriteField "pNext" VkBufferCreateInfo Source # 
CanWriteField "pQueueFamilyIndices" VkBufferCreateInfo Source # 

Methods

writeField :: Ptr VkBufferCreateInfo -> FieldType "pQueueFamilyIndices" VkBufferCreateInfo -> IO () Source #

CanWriteField "queueFamilyIndexCount" VkBufferCreateInfo Source # 

Methods

writeField :: Ptr VkBufferCreateInfo -> FieldType "queueFamilyIndexCount" VkBufferCreateInfo -> IO () Source #

CanWriteField "sType" VkBufferCreateInfo Source # 
CanWriteField "sharingMode" VkBufferCreateInfo Source # 
CanWriteField "size" VkBufferCreateInfo Source # 
CanWriteField "usage" VkBufferCreateInfo Source # 
CanReadField "flags" VkBufferCreateInfo Source # 
CanReadField "pNext" VkBufferCreateInfo Source # 
CanReadField "pQueueFamilyIndices" VkBufferCreateInfo Source # 
CanReadField "queueFamilyIndexCount" VkBufferCreateInfo Source # 
CanReadField "sType" VkBufferCreateInfo Source # 
CanReadField "sharingMode" VkBufferCreateInfo Source # 
CanReadField "size" VkBufferCreateInfo Source # 
CanReadField "usage" VkBufferCreateInfo Source # 
HasField "flags" VkBufferCreateInfo Source # 
HasField "pNext" VkBufferCreateInfo Source # 
HasField "pQueueFamilyIndices" VkBufferCreateInfo Source # 

Associated Types

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

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

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

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

HasField "queueFamilyIndexCount" VkBufferCreateInfo Source # 

Associated Types

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

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

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

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

HasField "sType" VkBufferCreateInfo Source # 
HasField "sharingMode" VkBufferCreateInfo Source # 

Associated Types

type FieldType ("sharingMode" :: Symbol) VkBufferCreateInfo :: Type Source #

type FieldOptional ("sharingMode" :: Symbol) VkBufferCreateInfo :: Bool Source #

type FieldOffset ("sharingMode" :: Symbol) VkBufferCreateInfo :: Nat Source #

type FieldIsArray ("sharingMode" :: Symbol) VkBufferCreateInfo :: Bool Source #

HasField "size" VkBufferCreateInfo Source # 
HasField "usage" VkBufferCreateInfo Source # 
type StructFields VkBufferCreateInfo Source # 
type StructFields VkBufferCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "size" ((:) Symbol "usage" ((:) Symbol "sharingMode" ((:) Symbol "queueFamilyIndexCount" ((:) Symbol "pQueueFamilyIndices" ([] Symbol))))))))
type CUnionType VkBufferCreateInfo Source # 
type ReturnedOnly VkBufferCreateInfo Source # 
type StructExtends VkBufferCreateInfo Source # 
type FieldType "flags" VkBufferCreateInfo Source # 
type FieldType "pNext" VkBufferCreateInfo Source # 
type FieldType "pQueueFamilyIndices" VkBufferCreateInfo Source # 
type FieldType "pQueueFamilyIndices" VkBufferCreateInfo = Ptr Word32
type FieldType "queueFamilyIndexCount" VkBufferCreateInfo Source # 
type FieldType "queueFamilyIndexCount" VkBufferCreateInfo = Word32
type FieldType "sType" VkBufferCreateInfo Source # 
type FieldType "sharingMode" VkBufferCreateInfo Source # 
type FieldType "size" VkBufferCreateInfo Source # 
type FieldType "usage" VkBufferCreateInfo Source # 
type FieldOptional "flags" VkBufferCreateInfo Source # 
type FieldOptional "pNext" VkBufferCreateInfo Source # 
type FieldOptional "pQueueFamilyIndices" VkBufferCreateInfo Source # 
type FieldOptional "pQueueFamilyIndices" VkBufferCreateInfo = False
type FieldOptional "queueFamilyIndexCount" VkBufferCreateInfo Source # 
type FieldOptional "queueFamilyIndexCount" VkBufferCreateInfo = True
type FieldOptional "sType" VkBufferCreateInfo Source # 
type FieldOptional "sharingMode" VkBufferCreateInfo Source # 
type FieldOptional "size" VkBufferCreateInfo Source # 
type FieldOptional "usage" VkBufferCreateInfo Source # 
type FieldOffset "flags" VkBufferCreateInfo Source # 
type FieldOffset "pNext" VkBufferCreateInfo Source # 
type FieldOffset "pQueueFamilyIndices" VkBufferCreateInfo Source # 
type FieldOffset "pQueueFamilyIndices" VkBufferCreateInfo = 48
type FieldOffset "queueFamilyIndexCount" VkBufferCreateInfo Source # 
type FieldOffset "queueFamilyIndexCount" VkBufferCreateInfo = 40
type FieldOffset "sType" VkBufferCreateInfo Source # 
type FieldOffset "sharingMode" VkBufferCreateInfo Source # 
type FieldOffset "sharingMode" VkBufferCreateInfo = 36
type FieldOffset "size" VkBufferCreateInfo Source # 
type FieldOffset "usage" VkBufferCreateInfo Source # 
type FieldIsArray "flags" VkBufferCreateInfo Source # 
type FieldIsArray "pNext" VkBufferCreateInfo Source # 
type FieldIsArray "pQueueFamilyIndices" VkBufferCreateInfo Source # 
type FieldIsArray "pQueueFamilyIndices" VkBufferCreateInfo = False
type FieldIsArray "queueFamilyIndexCount" VkBufferCreateInfo Source # 
type FieldIsArray "queueFamilyIndexCount" VkBufferCreateInfo = False
type FieldIsArray "sType" VkBufferCreateInfo Source # 
type FieldIsArray "sharingMode" VkBufferCreateInfo Source # 
type FieldIsArray "size" VkBufferCreateInfo Source # 
type FieldIsArray "usage" VkBufferCreateInfo Source # 

data VkBufferImageCopy Source #

typedef struct VkBufferImageCopy {
    VkDeviceSize           bufferOffset;
    uint32_t               bufferRowLength;
    uint32_t               bufferImageHeight;
    VkImageSubresourceLayers imageSubresource;
    VkOffset3D             imageOffset;
    VkExtent3D             imageExtent;
} VkBufferImageCopy;

VkBufferImageCopy registry at www.khronos.org

Instances

Eq VkBufferImageCopy Source # 
Ord VkBufferImageCopy Source # 
Show VkBufferImageCopy Source # 
Storable VkBufferImageCopy Source # 
VulkanMarshalPrim VkBufferImageCopy Source # 
VulkanMarshal VkBufferImageCopy Source # 
CanWriteField "bufferImageHeight" VkBufferImageCopy Source # 

Methods

writeField :: Ptr VkBufferImageCopy -> FieldType "bufferImageHeight" VkBufferImageCopy -> IO () Source #

CanWriteField "bufferOffset" VkBufferImageCopy Source # 
CanWriteField "bufferRowLength" VkBufferImageCopy Source # 

Methods

writeField :: Ptr VkBufferImageCopy -> FieldType "bufferRowLength" VkBufferImageCopy -> IO () Source #

CanWriteField "imageExtent" VkBufferImageCopy Source # 
CanWriteField "imageOffset" VkBufferImageCopy Source # 
CanWriteField "imageSubresource" VkBufferImageCopy Source # 

Methods

writeField :: Ptr VkBufferImageCopy -> FieldType "imageSubresource" VkBufferImageCopy -> IO () Source #

CanReadField "bufferImageHeight" VkBufferImageCopy Source # 
CanReadField "bufferOffset" VkBufferImageCopy Source # 
CanReadField "bufferRowLength" VkBufferImageCopy Source # 
CanReadField "imageExtent" VkBufferImageCopy Source # 
CanReadField "imageOffset" VkBufferImageCopy Source # 
CanReadField "imageSubresource" VkBufferImageCopy Source # 
HasField "bufferImageHeight" VkBufferImageCopy Source # 

Associated Types

type FieldType ("bufferImageHeight" :: Symbol) VkBufferImageCopy :: Type Source #

type FieldOptional ("bufferImageHeight" :: Symbol) VkBufferImageCopy :: Bool Source #

type FieldOffset ("bufferImageHeight" :: Symbol) VkBufferImageCopy :: Nat Source #

type FieldIsArray ("bufferImageHeight" :: Symbol) VkBufferImageCopy :: Bool Source #

HasField "bufferOffset" VkBufferImageCopy Source # 

Associated Types

type FieldType ("bufferOffset" :: Symbol) VkBufferImageCopy :: Type Source #

type FieldOptional ("bufferOffset" :: Symbol) VkBufferImageCopy :: Bool Source #

type FieldOffset ("bufferOffset" :: Symbol) VkBufferImageCopy :: Nat Source #

type FieldIsArray ("bufferOffset" :: Symbol) VkBufferImageCopy :: Bool Source #

HasField "bufferRowLength" VkBufferImageCopy Source # 

Associated Types

type FieldType ("bufferRowLength" :: Symbol) VkBufferImageCopy :: Type Source #

type FieldOptional ("bufferRowLength" :: Symbol) VkBufferImageCopy :: Bool Source #

type FieldOffset ("bufferRowLength" :: Symbol) VkBufferImageCopy :: Nat Source #

type FieldIsArray ("bufferRowLength" :: Symbol) VkBufferImageCopy :: Bool Source #

HasField "imageExtent" VkBufferImageCopy Source # 

Associated Types

type FieldType ("imageExtent" :: Symbol) VkBufferImageCopy :: Type Source #

type FieldOptional ("imageExtent" :: Symbol) VkBufferImageCopy :: Bool Source #

type FieldOffset ("imageExtent" :: Symbol) VkBufferImageCopy :: Nat Source #

type FieldIsArray ("imageExtent" :: Symbol) VkBufferImageCopy :: Bool Source #

HasField "imageOffset" VkBufferImageCopy Source # 

Associated Types

type FieldType ("imageOffset" :: Symbol) VkBufferImageCopy :: Type Source #

type FieldOptional ("imageOffset" :: Symbol) VkBufferImageCopy :: Bool Source #

type FieldOffset ("imageOffset" :: Symbol) VkBufferImageCopy :: Nat Source #

type FieldIsArray ("imageOffset" :: Symbol) VkBufferImageCopy :: Bool Source #

HasField "imageSubresource" VkBufferImageCopy Source # 

Associated Types

type FieldType ("imageSubresource" :: Symbol) VkBufferImageCopy :: Type Source #

type FieldOptional ("imageSubresource" :: Symbol) VkBufferImageCopy :: Bool Source #

type FieldOffset ("imageSubresource" :: Symbol) VkBufferImageCopy :: Nat Source #

type FieldIsArray ("imageSubresource" :: Symbol) VkBufferImageCopy :: Bool Source #

type StructFields VkBufferImageCopy Source # 
type StructFields VkBufferImageCopy = (:) Symbol "bufferOffset" ((:) Symbol "bufferRowLength" ((:) Symbol "bufferImageHeight" ((:) Symbol "imageSubresource" ((:) Symbol "imageOffset" ((:) Symbol "imageExtent" ([] Symbol))))))
type CUnionType VkBufferImageCopy Source # 
type ReturnedOnly VkBufferImageCopy Source # 
type StructExtends VkBufferImageCopy Source # 
type FieldType "bufferImageHeight" VkBufferImageCopy Source # 
type FieldType "bufferImageHeight" VkBufferImageCopy = Word32
type FieldType "bufferOffset" VkBufferImageCopy Source # 
type FieldType "bufferRowLength" VkBufferImageCopy Source # 
type FieldType "bufferRowLength" VkBufferImageCopy = Word32
type FieldType "imageExtent" VkBufferImageCopy Source # 
type FieldType "imageOffset" VkBufferImageCopy Source # 
type FieldType "imageSubresource" VkBufferImageCopy Source # 
type FieldOptional "bufferImageHeight" VkBufferImageCopy Source # 
type FieldOptional "bufferImageHeight" VkBufferImageCopy = False
type FieldOptional "bufferOffset" VkBufferImageCopy Source # 
type FieldOptional "bufferOffset" VkBufferImageCopy = False
type FieldOptional "bufferRowLength" VkBufferImageCopy Source # 
type FieldOptional "bufferRowLength" VkBufferImageCopy = False
type FieldOptional "imageExtent" VkBufferImageCopy Source # 
type FieldOptional "imageOffset" VkBufferImageCopy Source # 
type FieldOptional "imageSubresource" VkBufferImageCopy Source # 
type FieldOptional "imageSubresource" VkBufferImageCopy = False
type FieldOffset "bufferImageHeight" VkBufferImageCopy Source # 
type FieldOffset "bufferImageHeight" VkBufferImageCopy = 12
type FieldOffset "bufferOffset" VkBufferImageCopy Source # 
type FieldOffset "bufferOffset" VkBufferImageCopy = 0
type FieldOffset "bufferRowLength" VkBufferImageCopy Source # 
type FieldOffset "bufferRowLength" VkBufferImageCopy = 8
type FieldOffset "imageExtent" VkBufferImageCopy Source # 
type FieldOffset "imageExtent" VkBufferImageCopy = 44
type FieldOffset "imageOffset" VkBufferImageCopy Source # 
type FieldOffset "imageOffset" VkBufferImageCopy = 32
type FieldOffset "imageSubresource" VkBufferImageCopy Source # 
type FieldOffset "imageSubresource" VkBufferImageCopy = 16
type FieldIsArray "bufferImageHeight" VkBufferImageCopy Source # 
type FieldIsArray "bufferImageHeight" VkBufferImageCopy = False
type FieldIsArray "bufferOffset" VkBufferImageCopy Source # 
type FieldIsArray "bufferOffset" VkBufferImageCopy = False
type FieldIsArray "bufferRowLength" VkBufferImageCopy Source # 
type FieldIsArray "bufferRowLength" VkBufferImageCopy = False
type FieldIsArray "imageExtent" VkBufferImageCopy Source # 
type FieldIsArray "imageExtent" VkBufferImageCopy = False
type FieldIsArray "imageOffset" VkBufferImageCopy Source # 
type FieldIsArray "imageOffset" VkBufferImageCopy = False
type FieldIsArray "imageSubresource" VkBufferImageCopy Source # 
type FieldIsArray "imageSubresource" VkBufferImageCopy = False

data VkBufferMemoryBarrier Source #

typedef struct VkBufferMemoryBarrier {
    VkStructureType sType;
    const void*            pNext;
    VkAccessFlags          srcAccessMask;
    VkAccessFlags          dstAccessMask;
    uint32_t               srcQueueFamilyIndex;
    uint32_t               dstQueueFamilyIndex;
    VkBuffer               buffer;
    VkDeviceSize           offset;
    VkDeviceSize           size;
} VkBufferMemoryBarrier;

VkBufferMemoryBarrier registry at www.khronos.org

Instances

Eq VkBufferMemoryBarrier Source # 
Ord VkBufferMemoryBarrier Source # 
Show VkBufferMemoryBarrier Source # 
Storable VkBufferMemoryBarrier Source # 
VulkanMarshalPrim VkBufferMemoryBarrier Source # 
VulkanMarshal VkBufferMemoryBarrier Source # 
CanWriteField "buffer" VkBufferMemoryBarrier Source # 
CanWriteField "dstAccessMask" VkBufferMemoryBarrier Source # 
CanWriteField "dstQueueFamilyIndex" VkBufferMemoryBarrier Source # 
CanWriteField "offset" VkBufferMemoryBarrier Source # 
CanWriteField "pNext" VkBufferMemoryBarrier Source # 
CanWriteField "sType" VkBufferMemoryBarrier Source # 
CanWriteField "size" VkBufferMemoryBarrier Source # 
CanWriteField "srcAccessMask" VkBufferMemoryBarrier Source # 
CanWriteField "srcQueueFamilyIndex" VkBufferMemoryBarrier Source # 
CanReadField "buffer" VkBufferMemoryBarrier Source # 
CanReadField "dstAccessMask" VkBufferMemoryBarrier Source # 
CanReadField "dstQueueFamilyIndex" VkBufferMemoryBarrier Source # 
CanReadField "offset" VkBufferMemoryBarrier Source # 
CanReadField "pNext" VkBufferMemoryBarrier Source # 
CanReadField "sType" VkBufferMemoryBarrier Source # 
CanReadField "size" VkBufferMemoryBarrier Source # 
CanReadField "srcAccessMask" VkBufferMemoryBarrier Source # 
CanReadField "srcQueueFamilyIndex" VkBufferMemoryBarrier Source # 
HasField "buffer" VkBufferMemoryBarrier Source # 
HasField "dstAccessMask" VkBufferMemoryBarrier Source # 

Associated Types

type FieldType ("dstAccessMask" :: Symbol) VkBufferMemoryBarrier :: Type Source #

type FieldOptional ("dstAccessMask" :: Symbol) VkBufferMemoryBarrier :: Bool Source #

type FieldOffset ("dstAccessMask" :: Symbol) VkBufferMemoryBarrier :: Nat Source #

type FieldIsArray ("dstAccessMask" :: Symbol) VkBufferMemoryBarrier :: Bool Source #

HasField "dstQueueFamilyIndex" VkBufferMemoryBarrier Source # 

Associated Types

type FieldType ("dstQueueFamilyIndex" :: Symbol) VkBufferMemoryBarrier :: Type Source #

type FieldOptional ("dstQueueFamilyIndex" :: Symbol) VkBufferMemoryBarrier :: Bool Source #

type FieldOffset ("dstQueueFamilyIndex" :: Symbol) VkBufferMemoryBarrier :: Nat Source #

type FieldIsArray ("dstQueueFamilyIndex" :: Symbol) VkBufferMemoryBarrier :: Bool Source #

HasField "offset" VkBufferMemoryBarrier Source # 
HasField "pNext" VkBufferMemoryBarrier Source # 
HasField "sType" VkBufferMemoryBarrier Source # 
HasField "size" VkBufferMemoryBarrier Source # 
HasField "srcAccessMask" VkBufferMemoryBarrier Source # 

Associated Types

type FieldType ("srcAccessMask" :: Symbol) VkBufferMemoryBarrier :: Type Source #

type FieldOptional ("srcAccessMask" :: Symbol) VkBufferMemoryBarrier :: Bool Source #

type FieldOffset ("srcAccessMask" :: Symbol) VkBufferMemoryBarrier :: Nat Source #

type FieldIsArray ("srcAccessMask" :: Symbol) VkBufferMemoryBarrier :: Bool Source #

HasField "srcQueueFamilyIndex" VkBufferMemoryBarrier Source # 

Associated Types

type FieldType ("srcQueueFamilyIndex" :: Symbol) VkBufferMemoryBarrier :: Type Source #

type FieldOptional ("srcQueueFamilyIndex" :: Symbol) VkBufferMemoryBarrier :: Bool Source #

type FieldOffset ("srcQueueFamilyIndex" :: Symbol) VkBufferMemoryBarrier :: Nat Source #

type FieldIsArray ("srcQueueFamilyIndex" :: Symbol) VkBufferMemoryBarrier :: Bool Source #

type StructFields VkBufferMemoryBarrier Source # 
type StructFields VkBufferMemoryBarrier = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "srcAccessMask" ((:) Symbol "dstAccessMask" ((:) Symbol "srcQueueFamilyIndex" ((:) Symbol "dstQueueFamilyIndex" ((:) Symbol "buffer" ((:) Symbol "offset" ((:) Symbol "size" ([] Symbol)))))))))
type CUnionType VkBufferMemoryBarrier Source # 
type ReturnedOnly VkBufferMemoryBarrier Source # 
type StructExtends VkBufferMemoryBarrier Source # 
type FieldType "buffer" VkBufferMemoryBarrier Source # 
type FieldType "dstAccessMask" VkBufferMemoryBarrier Source # 
type FieldType "dstQueueFamilyIndex" VkBufferMemoryBarrier Source # 
type FieldType "dstQueueFamilyIndex" VkBufferMemoryBarrier = Word32
type FieldType "offset" VkBufferMemoryBarrier Source # 
type FieldType "pNext" VkBufferMemoryBarrier Source # 
type FieldType "sType" VkBufferMemoryBarrier Source # 
type FieldType "size" VkBufferMemoryBarrier Source # 
type FieldType "srcAccessMask" VkBufferMemoryBarrier Source # 
type FieldType "srcQueueFamilyIndex" VkBufferMemoryBarrier Source # 
type FieldType "srcQueueFamilyIndex" VkBufferMemoryBarrier = Word32
type FieldOptional "buffer" VkBufferMemoryBarrier Source # 
type FieldOptional "dstAccessMask" VkBufferMemoryBarrier Source # 
type FieldOptional "dstQueueFamilyIndex" VkBufferMemoryBarrier Source # 
type FieldOptional "dstQueueFamilyIndex" VkBufferMemoryBarrier = False
type FieldOptional "offset" VkBufferMemoryBarrier Source # 
type FieldOptional "pNext" VkBufferMemoryBarrier Source # 
type FieldOptional "sType" VkBufferMemoryBarrier Source # 
type FieldOptional "size" VkBufferMemoryBarrier Source # 
type FieldOptional "srcAccessMask" VkBufferMemoryBarrier Source # 
type FieldOptional "srcQueueFamilyIndex" VkBufferMemoryBarrier Source # 
type FieldOptional "srcQueueFamilyIndex" VkBufferMemoryBarrier = False
type FieldOffset "buffer" VkBufferMemoryBarrier Source # 
type FieldOffset "dstAccessMask" VkBufferMemoryBarrier Source # 
type FieldOffset "dstAccessMask" VkBufferMemoryBarrier = 20
type FieldOffset "dstQueueFamilyIndex" VkBufferMemoryBarrier Source # 
type FieldOffset "dstQueueFamilyIndex" VkBufferMemoryBarrier = 28
type FieldOffset "offset" VkBufferMemoryBarrier Source # 
type FieldOffset "pNext" VkBufferMemoryBarrier Source # 
type FieldOffset "sType" VkBufferMemoryBarrier Source # 
type FieldOffset "size" VkBufferMemoryBarrier Source # 
type FieldOffset "srcAccessMask" VkBufferMemoryBarrier Source # 
type FieldOffset "srcAccessMask" VkBufferMemoryBarrier = 16
type FieldOffset "srcQueueFamilyIndex" VkBufferMemoryBarrier Source # 
type FieldOffset "srcQueueFamilyIndex" VkBufferMemoryBarrier = 24
type FieldIsArray "buffer" VkBufferMemoryBarrier Source # 
type FieldIsArray "dstAccessMask" VkBufferMemoryBarrier Source # 
type FieldIsArray "dstQueueFamilyIndex" VkBufferMemoryBarrier Source # 
type FieldIsArray "dstQueueFamilyIndex" VkBufferMemoryBarrier = False
type FieldIsArray "offset" VkBufferMemoryBarrier Source # 
type FieldIsArray "pNext" VkBufferMemoryBarrier Source # 
type FieldIsArray "sType" VkBufferMemoryBarrier Source # 
type FieldIsArray "size" VkBufferMemoryBarrier Source # 
type FieldIsArray "srcAccessMask" VkBufferMemoryBarrier Source # 
type FieldIsArray "srcQueueFamilyIndex" VkBufferMemoryBarrier Source # 
type FieldIsArray "srcQueueFamilyIndex" VkBufferMemoryBarrier = False

data VkBufferMemoryRequirementsInfo2 Source #

typedef struct VkBufferMemoryRequirementsInfo2 {
    VkStructureType sType;
    const void*                                                          pNext;
    VkBuffer                                                             buffer;
} VkBufferMemoryRequirementsInfo2;

VkBufferMemoryRequirementsInfo2 registry at www.khronos.org

Instances

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

data VkBufferViewCreateInfo Source #

typedef struct VkBufferViewCreateInfo {
    VkStructureType sType;
    const void*            pNext;
    VkBufferViewCreateFlagsflags;
    VkBuffer               buffer;
    VkFormat               format;
    VkDeviceSize           offset;
    VkDeviceSize           range;
} VkBufferViewCreateInfo;

VkBufferViewCreateInfo registry at www.khronos.org

Instances

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

data VkDedicatedAllocationBufferCreateInfoNV Source #

typedef struct VkDedicatedAllocationBufferCreateInfoNV {
    VkStructureType sType;
    const void*                      pNext;
    VkBool32                         dedicatedAllocation;
} VkDedicatedAllocationBufferCreateInfoNV;

VkDedicatedAllocationBufferCreateInfoNV registry at www.khronos.org

Instances

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

data VkDedicatedAllocationImageCreateInfoNV Source #

typedef struct VkDedicatedAllocationImageCreateInfoNV {
    VkStructureType sType;
    const void*                      pNext;
    VkBool32                         dedicatedAllocation;
} VkDedicatedAllocationImageCreateInfoNV;

VkDedicatedAllocationImageCreateInfoNV registry at www.khronos.org

Instances

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

data VkDedicatedAllocationMemoryAllocateInfoNV Source #

typedef struct VkDedicatedAllocationMemoryAllocateInfoNV {
    VkStructureType sType;
    const void*                      pNext;
    VkImage          image;
    VkBuffer         buffer;
} VkDedicatedAllocationMemoryAllocateInfoNV;

VkDedicatedAllocationMemoryAllocateInfoNV registry at www.khronos.org

Instances

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

data VkExtent2D Source #

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

VkExtent2D registry at www.khronos.org

Instances

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

Methods

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

CanWriteField "width" VkExtent2D Source # 

Methods

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

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

Associated Types

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

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

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

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

HasField "width" VkExtent2D Source # 

Associated Types

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

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

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

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

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

data VkExtent3D Source #

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

VkExtent3D registry at www.khronos.org

Instances

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

Methods

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

CanWriteField "height" VkExtent3D Source # 

Methods

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

CanWriteField "width" VkExtent3D Source # 

Methods

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

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

Associated Types

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

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

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

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

HasField "height" VkExtent3D Source # 

Associated Types

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

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

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

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

HasField "width" VkExtent3D Source # 

Associated Types

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

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

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

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

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

newtype VkFormat Source #

Vulkan format definitions

type = enum

VkFormat registry at www.khronos.org

Constructors

VkFormat Int32 

Instances

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

Methods

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

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

toConstr :: VkFormat -> Constr #

dataTypeOf :: VkFormat -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Associated Types

type Rep VkFormat :: * -> * #

Methods

from :: VkFormat -> Rep VkFormat x #

to :: Rep VkFormat x -> VkFormat #

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

newtype VkFormatFeatureBitmask a Source #

Instances

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

Methods

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

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

toConstr :: VkFormatFeatureBitmask a -> Constr #

dataTypeOf :: VkFormatFeatureBitmask a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

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

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

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

complement :: VkFormatFeatureBitmask FlagMask -> VkFormatFeatureBitmask FlagMask #

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

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

zeroBits :: VkFormatFeatureBitmask FlagMask #

bit :: Int -> VkFormatFeatureBitmask FlagMask #

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

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

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

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

bitSizeMaybe :: VkFormatFeatureBitmask FlagMask -> Maybe Int #

bitSize :: VkFormatFeatureBitmask FlagMask -> Int #

isSigned :: VkFormatFeatureBitmask FlagMask -> Bool #

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

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

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

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

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

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

popCount :: VkFormatFeatureBitmask FlagMask -> Int #

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

pattern VK_FORMAT_FEATURE_SAMPLED_IMAGE_BIT :: forall a. VkFormatFeatureBitmask a Source #

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

bitpos = 0

pattern VK_FORMAT_FEATURE_STORAGE_IMAGE_BIT :: forall a. VkFormatFeatureBitmask a Source #

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

bitpos = 1

pattern VK_FORMAT_FEATURE_STORAGE_IMAGE_ATOMIC_BIT :: forall a. VkFormatFeatureBitmask a Source #

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

bitpos = 2

pattern VK_FORMAT_FEATURE_UNIFORM_TEXEL_BUFFER_BIT :: forall a. VkFormatFeatureBitmask a Source #

Format can be used for uniform texel buffers (TBOs)

bitpos = 3

pattern VK_FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_BIT :: forall a. VkFormatFeatureBitmask a Source #

Format can be used for storage texel buffers (IBOs)

bitpos = 4

pattern VK_FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_ATOMIC_BIT :: forall a. VkFormatFeatureBitmask a Source #

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

bitpos = 5

pattern VK_FORMAT_FEATURE_VERTEX_BUFFER_BIT :: forall a. VkFormatFeatureBitmask a Source #

Format can be used for vertex buffers (VBOs)

bitpos = 6

pattern VK_FORMAT_FEATURE_COLOR_ATTACHMENT_BIT :: forall a. VkFormatFeatureBitmask a Source #

Format can be used for color attachment images

bitpos = 7

pattern VK_FORMAT_FEATURE_COLOR_ATTACHMENT_BLEND_BIT :: forall a. VkFormatFeatureBitmask a Source #

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

bitpos = 8

pattern VK_FORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT :: forall a. VkFormatFeatureBitmask a Source #

Format can be used for depth/stencil attachment images

bitpos = 9

pattern VK_FORMAT_FEATURE_BLIT_SRC_BIT :: forall a. VkFormatFeatureBitmask a Source #

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

bitpos = 10

pattern VK_FORMAT_FEATURE_BLIT_DST_BIT :: forall a. VkFormatFeatureBitmask a Source #

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

bitpos = 11

pattern VK_FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT :: forall a. VkFormatFeatureBitmask a Source #

Format can be filtered with VK_FILTER_LINEAR when being sampled

bitpos = 12

newtype VkImageAspectBitmask a Source #

Instances

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

Methods

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

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

toConstr :: VkImageAspectBitmask a -> Constr #

dataTypeOf :: VkImageAspectBitmask a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

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

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

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

complement :: VkImageAspectBitmask FlagMask -> VkImageAspectBitmask FlagMask #

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

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

zeroBits :: VkImageAspectBitmask FlagMask #

bit :: Int -> VkImageAspectBitmask FlagMask #

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

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

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

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

bitSizeMaybe :: VkImageAspectBitmask FlagMask -> Maybe Int #

bitSize :: VkImageAspectBitmask FlagMask -> Int #

isSigned :: VkImageAspectBitmask FlagMask -> Bool #

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

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

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

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

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

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

popCount :: VkImageAspectBitmask FlagMask -> Int #

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

pattern VK_IMAGE_ASPECT_COLOR_BIT :: forall a. VkImageAspectBitmask a Source #

bitpos = 0

pattern VK_IMAGE_ASPECT_DEPTH_BIT :: forall a. VkImageAspectBitmask a Source #

bitpos = 1

pattern VK_IMAGE_ASPECT_STENCIL_BIT :: forall a. VkImageAspectBitmask a Source #

bitpos = 2

newtype VkImageCreateBitmask a Source #

Instances

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

Methods

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

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

toConstr :: VkImageCreateBitmask a -> Constr #

dataTypeOf :: VkImageCreateBitmask a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

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

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

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

complement :: VkImageCreateBitmask FlagMask -> VkImageCreateBitmask FlagMask #

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

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

zeroBits :: VkImageCreateBitmask FlagMask #

bit :: Int -> VkImageCreateBitmask FlagMask #

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

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

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

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

bitSizeMaybe :: VkImageCreateBitmask FlagMask -> Maybe Int #

bitSize :: VkImageCreateBitmask FlagMask -> Int #

isSigned :: VkImageCreateBitmask FlagMask -> Bool #

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

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

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

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

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

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

popCount :: VkImageCreateBitmask FlagMask -> Int #

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

pattern VK_IMAGE_CREATE_SPARSE_BINDING_BIT :: forall a. VkImageCreateBitmask a Source #

Image should support sparse backing

bitpos = 0

pattern VK_IMAGE_CREATE_SPARSE_RESIDENCY_BIT :: forall a. VkImageCreateBitmask a Source #

Image should support sparse backing with partial residency

bitpos = 1

pattern VK_IMAGE_CREATE_SPARSE_ALIASED_BIT :: forall a. VkImageCreateBitmask a Source #

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

bitpos = 2

pattern VK_IMAGE_CREATE_MUTABLE_FORMAT_BIT :: forall a. VkImageCreateBitmask a Source #

Allows image views to have different format than the base image

bitpos = 3

pattern VK_IMAGE_CREATE_CUBE_COMPATIBLE_BIT :: forall a. VkImageCreateBitmask a Source #

Allows creating image views with cube type from the created image

bitpos = 4

newtype VkImageLayout Source #

Constructors

VkImageLayout Int32 

Instances

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

Methods

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

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

toConstr :: VkImageLayout -> Constr #

dataTypeOf :: VkImageLayout -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Associated Types

type Rep VkImageLayout :: * -> * #

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

pattern VK_IMAGE_LAYOUT_UNDEFINED :: VkImageLayout Source #

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

pattern VK_IMAGE_LAYOUT_GENERAL :: VkImageLayout Source #

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

pattern VK_IMAGE_LAYOUT_COLOR_ATTACHMENT_OPTIMAL :: VkImageLayout Source #

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

pattern VK_IMAGE_LAYOUT_DEPTH_STENCIL_ATTACHMENT_OPTIMAL :: VkImageLayout Source #

Optimal layout when image is only used for depthstencil attachment readwrite

pattern VK_IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL :: VkImageLayout Source #

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

pattern VK_IMAGE_LAYOUT_SHADER_READ_ONLY_OPTIMAL :: VkImageLayout Source #

Optimal layout when image is used for read only shader access

pattern VK_IMAGE_LAYOUT_TRANSFER_SRC_OPTIMAL :: VkImageLayout Source #

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

pattern VK_IMAGE_LAYOUT_TRANSFER_DST_OPTIMAL :: VkImageLayout Source #

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

pattern VK_IMAGE_LAYOUT_PREINITIALIZED :: VkImageLayout Source #

Initial layout used when the data is populated by the CPU

newtype VkImageTiling Source #

Constructors

VkImageTiling Int32 

Instances

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

Methods

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

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

toConstr :: VkImageTiling -> Constr #

dataTypeOf :: VkImageTiling -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Associated Types

type Rep VkImageTiling :: * -> * #

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

newtype VkImageType Source #

Constructors

VkImageType Int32 

Instances

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

Methods

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

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

toConstr :: VkImageType -> Constr #

dataTypeOf :: VkImageType -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Associated Types

type Rep VkImageType :: * -> * #

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

newtype VkImageUsageBitmask a Source #

Instances

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

Methods

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

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

toConstr :: VkImageUsageBitmask a -> Constr #

dataTypeOf :: VkImageUsageBitmask a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Associated Types

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

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

Methods

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

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

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

complement :: VkImageUsageBitmask FlagMask -> VkImageUsageBitmask FlagMask #

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

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

zeroBits :: VkImageUsageBitmask FlagMask #

bit :: Int -> VkImageUsageBitmask FlagMask #

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

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

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

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

bitSizeMaybe :: VkImageUsageBitmask FlagMask -> Maybe Int #

bitSize :: VkImageUsageBitmask FlagMask -> Int #

isSigned :: VkImageUsageBitmask FlagMask -> Bool #

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

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

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

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

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

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

popCount :: VkImageUsageBitmask FlagMask -> Int #

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

pattern VK_IMAGE_USAGE_TRANSFER_SRC_BIT :: forall a. VkImageUsageBitmask a Source #

Can be used as a source of transfer operations

bitpos = 0

pattern VK_IMAGE_USAGE_TRANSFER_DST_BIT :: forall a. VkImageUsageBitmask a Source #

Can be used as a destination of transfer operations

bitpos = 1

pattern VK_IMAGE_USAGE_SAMPLED_BIT :: forall a. VkImageUsageBitmask a Source #

Can be sampled from (SAMPLED_IMAGE and COMBINED_IMAGE_SAMPLER descriptor types)

bitpos = 2

pattern VK_IMAGE_USAGE_STORAGE_BIT :: forall a. VkImageUsageBitmask a Source #

Can be used as storage image (STORAGE_IMAGE descriptor type)

bitpos = 3

pattern VK_IMAGE_USAGE_COLOR_ATTACHMENT_BIT :: forall a. VkImageUsageBitmask a Source #

Can be used as framebuffer color attachment

bitpos = 4

pattern VK_IMAGE_USAGE_DEPTH_STENCIL_ATTACHMENT_BIT :: forall a. VkImageUsageBitmask a Source #

Can be used as framebuffer depth/stencil attachment

bitpos = 5

pattern VK_IMAGE_USAGE_TRANSIENT_ATTACHMENT_BIT :: forall a. VkImageUsageBitmask a Source #

Image data not needed outside of rendering

bitpos = 6

pattern VK_IMAGE_USAGE_INPUT_ATTACHMENT_BIT :: forall a. VkImageUsageBitmask a Source #

Can be used as framebuffer input attachment

bitpos = 7

newtype VkImageViewType Source #

Constructors

VkImageViewType Int32 

Instances

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

Methods

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

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

toConstr :: VkImageViewType -> Constr #

dataTypeOf :: VkImageViewType -> DataType #

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

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

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

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

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

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

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

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

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

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

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

data VkImageBlit Source #

typedef struct VkImageBlit {
    VkImageSubresourceLayers srcSubresource;
    VkOffset3D             srcOffsets[2];
    VkImageSubresourceLayers dstSubresource;
    VkOffset3D             dstOffsets[2];
} VkImageBlit;

VkImageBlit registry at www.khronos.org

Instances

Eq VkImageBlit Source # 
Ord VkImageBlit Source # 
Show VkImageBlit Source # 
Storable VkImageBlit Source # 
VulkanMarshalPrim VkImageBlit Source # 
VulkanMarshal VkImageBlit Source # 
CanWriteField "dstSubresource" VkImageBlit Source # 

Methods

writeField :: Ptr VkImageBlit -> FieldType "dstSubresource" VkImageBlit -> IO () Source #

CanWriteField "srcSubresource" VkImageBlit Source # 

Methods

writeField :: Ptr VkImageBlit -> FieldType "srcSubresource" VkImageBlit -> IO () Source #

CanReadField "dstSubresource" VkImageBlit Source # 

Methods

getField :: VkImageBlit -> FieldType "dstSubresource" VkImageBlit Source #

readField :: Ptr VkImageBlit -> IO (FieldType "dstSubresource" VkImageBlit) Source #

CanReadField "srcSubresource" VkImageBlit Source # 

Methods

getField :: VkImageBlit -> FieldType "srcSubresource" VkImageBlit Source #

readField :: Ptr VkImageBlit -> IO (FieldType "srcSubresource" VkImageBlit) Source #

HasField "dstOffsets" VkImageBlit Source # 

Associated Types

type FieldType ("dstOffsets" :: Symbol) VkImageBlit :: Type Source #

type FieldOptional ("dstOffsets" :: Symbol) VkImageBlit :: Bool Source #

type FieldOffset ("dstOffsets" :: Symbol) VkImageBlit :: Nat Source #

type FieldIsArray ("dstOffsets" :: Symbol) VkImageBlit :: Bool Source #

HasField "dstSubresource" VkImageBlit Source # 

Associated Types

type FieldType ("dstSubresource" :: Symbol) VkImageBlit :: Type Source #

type FieldOptional ("dstSubresource" :: Symbol) VkImageBlit :: Bool Source #

type FieldOffset ("dstSubresource" :: Symbol) VkImageBlit :: Nat Source #

type FieldIsArray ("dstSubresource" :: Symbol) VkImageBlit :: Bool Source #

HasField "srcOffsets" VkImageBlit Source # 

Associated Types

type FieldType ("srcOffsets" :: Symbol) VkImageBlit :: Type Source #

type FieldOptional ("srcOffsets" :: Symbol) VkImageBlit :: Bool Source #

type FieldOffset ("srcOffsets" :: Symbol) VkImageBlit :: Nat Source #

type FieldIsArray ("srcOffsets" :: Symbol) VkImageBlit :: Bool Source #

HasField "srcSubresource" VkImageBlit Source # 

Associated Types

type FieldType ("srcSubresource" :: Symbol) VkImageBlit :: Type Source #

type FieldOptional ("srcSubresource" :: Symbol) VkImageBlit :: Bool Source #

type FieldOffset ("srcSubresource" :: Symbol) VkImageBlit :: Nat Source #

type FieldIsArray ("srcSubresource" :: Symbol) VkImageBlit :: Bool Source #

(KnownNat idx, IndexInBounds "dstOffsets" idx VkImageBlit) => CanWriteFieldArray "dstOffsets" idx VkImageBlit Source # 

Methods

writeFieldArray :: Ptr VkImageBlit -> FieldType "dstOffsets" VkImageBlit -> IO () Source #

(KnownNat idx, IndexInBounds "srcOffsets" idx VkImageBlit) => CanWriteFieldArray "srcOffsets" idx VkImageBlit Source # 

Methods

writeFieldArray :: Ptr VkImageBlit -> FieldType "srcOffsets" VkImageBlit -> IO () Source #

(KnownNat idx, IndexInBounds "dstOffsets" idx VkImageBlit) => CanReadFieldArray "dstOffsets" idx VkImageBlit Source # 
(KnownNat idx, IndexInBounds "srcOffsets" idx VkImageBlit) => CanReadFieldArray "srcOffsets" idx VkImageBlit Source # 
type StructFields VkImageBlit Source # 
type StructFields VkImageBlit = (:) Symbol "srcSubresource" ((:) Symbol "srcOffsets" ((:) Symbol "dstSubresource" ((:) Symbol "dstOffsets" ([] Symbol))))
type CUnionType VkImageBlit Source # 
type ReturnedOnly VkImageBlit Source # 
type StructExtends VkImageBlit Source # 
type FieldArrayLength "dstOffsets" VkImageBlit Source # 
type FieldArrayLength "dstOffsets" VkImageBlit = 2
type FieldArrayLength "srcOffsets" VkImageBlit Source # 
type FieldArrayLength "srcOffsets" VkImageBlit = 2
type FieldType "dstOffsets" VkImageBlit Source # 
type FieldType "dstOffsets" VkImageBlit = VkOffset3D
type FieldType "dstSubresource" VkImageBlit Source # 
type FieldType "srcOffsets" VkImageBlit Source # 
type FieldType "srcOffsets" VkImageBlit = VkOffset3D
type FieldType "srcSubresource" VkImageBlit Source # 
type FieldOptional "dstOffsets" VkImageBlit Source # 
type FieldOptional "dstOffsets" VkImageBlit = False
type FieldOptional "dstSubresource" VkImageBlit Source # 
type FieldOptional "dstSubresource" VkImageBlit = False
type FieldOptional "srcOffsets" VkImageBlit Source # 
type FieldOptional "srcOffsets" VkImageBlit = False
type FieldOptional "srcSubresource" VkImageBlit Source # 
type FieldOptional "srcSubresource" VkImageBlit = False
type FieldOffset "dstOffsets" VkImageBlit Source # 
type FieldOffset "dstOffsets" VkImageBlit = 56
type FieldOffset "dstSubresource" VkImageBlit Source # 
type FieldOffset "dstSubresource" VkImageBlit = 40
type FieldOffset "srcOffsets" VkImageBlit Source # 
type FieldOffset "srcOffsets" VkImageBlit = 16
type FieldOffset "srcSubresource" VkImageBlit Source # 
type FieldOffset "srcSubresource" VkImageBlit = 0
type FieldIsArray "dstOffsets" VkImageBlit Source # 
type FieldIsArray "dstOffsets" VkImageBlit = True
type FieldIsArray "dstSubresource" VkImageBlit Source # 
type FieldIsArray "dstSubresource" VkImageBlit = False
type FieldIsArray "srcOffsets" VkImageBlit Source # 
type FieldIsArray "srcOffsets" VkImageBlit = True
type FieldIsArray "srcSubresource" VkImageBlit Source # 
type FieldIsArray "srcSubresource" VkImageBlit = False

data VkImageCopy Source #

typedef struct VkImageCopy {
    VkImageSubresourceLayers srcSubresource;
    VkOffset3D             srcOffset;
    VkImageSubresourceLayers dstSubresource;
    VkOffset3D             dstOffset;
    VkExtent3D             extent;
} VkImageCopy;

VkImageCopy registry at www.khronos.org

Instances

Eq VkImageCopy Source # 
Ord VkImageCopy Source # 
Show VkImageCopy Source # 
Storable VkImageCopy Source # 
VulkanMarshalPrim VkImageCopy Source # 
VulkanMarshal VkImageCopy Source # 
CanWriteField "dstOffset" VkImageCopy Source # 

Methods

writeField :: Ptr VkImageCopy -> FieldType "dstOffset" VkImageCopy -> IO () Source #

CanWriteField "dstSubresource" VkImageCopy Source # 

Methods

writeField :: Ptr VkImageCopy -> FieldType "dstSubresource" VkImageCopy -> IO () Source #

CanWriteField "extent" VkImageCopy Source # 
CanWriteField "srcOffset" VkImageCopy Source # 

Methods

writeField :: Ptr VkImageCopy -> FieldType "srcOffset" VkImageCopy -> IO () Source #

CanWriteField "srcSubresource" VkImageCopy Source # 

Methods

writeField :: Ptr VkImageCopy -> FieldType "srcSubresource" VkImageCopy -> IO () Source #

CanReadField "dstOffset" VkImageCopy Source # 
CanReadField "dstSubresource" VkImageCopy Source # 

Methods

getField :: VkImageCopy -> FieldType "dstSubresource" VkImageCopy Source #

readField :: Ptr VkImageCopy -> IO (FieldType "dstSubresource" VkImageCopy) Source #

CanReadField "extent" VkImageCopy Source # 
CanReadField "srcOffset" VkImageCopy Source # 
CanReadField "srcSubresource" VkImageCopy Source # 

Methods

getField :: VkImageCopy -> FieldType "srcSubresource" VkImageCopy Source #

readField :: Ptr VkImageCopy -> IO (FieldType "srcSubresource" VkImageCopy) Source #

HasField "dstOffset" VkImageCopy Source # 

Associated Types

type FieldType ("dstOffset" :: Symbol) VkImageCopy :: Type Source #

type FieldOptional ("dstOffset" :: Symbol) VkImageCopy :: Bool Source #

type FieldOffset ("dstOffset" :: Symbol) VkImageCopy :: Nat Source #

type FieldIsArray ("dstOffset" :: Symbol) VkImageCopy :: Bool Source #

HasField "dstSubresource" VkImageCopy Source # 

Associated Types

type FieldType ("dstSubresource" :: Symbol) VkImageCopy :: Type Source #

type FieldOptional ("dstSubresource" :: Symbol) VkImageCopy :: Bool Source #

type FieldOffset ("dstSubresource" :: Symbol) VkImageCopy :: Nat Source #

type FieldIsArray ("dstSubresource" :: Symbol) VkImageCopy :: Bool Source #

HasField "extent" VkImageCopy Source # 

Associated Types

type FieldType ("extent" :: Symbol) VkImageCopy :: Type Source #

type FieldOptional ("extent" :: Symbol) VkImageCopy :: Bool Source #

type FieldOffset ("extent" :: Symbol) VkImageCopy :: Nat Source #

type FieldIsArray ("extent" :: Symbol) VkImageCopy :: Bool Source #

HasField "srcOffset" VkImageCopy Source # 

Associated Types

type FieldType ("srcOffset" :: Symbol) VkImageCopy :: Type Source #

type FieldOptional ("srcOffset" :: Symbol) VkImageCopy :: Bool Source #

type FieldOffset ("srcOffset" :: Symbol) VkImageCopy :: Nat Source #

type FieldIsArray ("srcOffset" :: Symbol) VkImageCopy :: Bool Source #

HasField "srcSubresource" VkImageCopy Source # 

Associated Types

type FieldType ("srcSubresource" :: Symbol) VkImageCopy :: Type Source #

type FieldOptional ("srcSubresource" :: Symbol) VkImageCopy :: Bool Source #

type FieldOffset ("srcSubresource" :: Symbol) VkImageCopy :: Nat Source #

type FieldIsArray ("srcSubresource" :: Symbol) VkImageCopy :: Bool Source #

type StructFields VkImageCopy Source # 
type StructFields VkImageCopy = (:) Symbol "srcSubresource" ((:) Symbol "srcOffset" ((:) Symbol "dstSubresource" ((:) Symbol "dstOffset" ((:) Symbol "extent" ([] Symbol)))))
type CUnionType VkImageCopy Source # 
type ReturnedOnly VkImageCopy Source # 
type StructExtends VkImageCopy Source # 
type FieldType "dstOffset" VkImageCopy Source # 
type FieldType "dstOffset" VkImageCopy = VkOffset3D
type FieldType "dstSubresource" VkImageCopy Source # 
type FieldType "extent" VkImageCopy Source # 
type FieldType "srcOffset" VkImageCopy Source # 
type FieldType "srcOffset" VkImageCopy = VkOffset3D
type FieldType "srcSubresource" VkImageCopy Source # 
type FieldOptional "dstOffset" VkImageCopy Source # 
type FieldOptional "dstOffset" VkImageCopy = False
type FieldOptional "dstSubresource" VkImageCopy Source # 
type FieldOptional "dstSubresource" VkImageCopy = False
type FieldOptional "extent" VkImageCopy Source # 
type FieldOptional "srcOffset" VkImageCopy Source # 
type FieldOptional "srcOffset" VkImageCopy = False
type FieldOptional "srcSubresource" VkImageCopy Source # 
type FieldOptional "srcSubresource" VkImageCopy = False
type FieldOffset "dstOffset" VkImageCopy Source # 
type FieldOffset "dstOffset" VkImageCopy = 44
type FieldOffset "dstSubresource" VkImageCopy Source # 
type FieldOffset "dstSubresource" VkImageCopy = 28
type FieldOffset "extent" VkImageCopy Source # 
type FieldOffset "extent" VkImageCopy = 56
type FieldOffset "srcOffset" VkImageCopy Source # 
type FieldOffset "srcOffset" VkImageCopy = 16
type FieldOffset "srcSubresource" VkImageCopy Source # 
type FieldOffset "srcSubresource" VkImageCopy = 0
type FieldIsArray "dstOffset" VkImageCopy Source # 
type FieldIsArray "dstOffset" VkImageCopy = False
type FieldIsArray "dstSubresource" VkImageCopy Source # 
type FieldIsArray "dstSubresource" VkImageCopy = False
type FieldIsArray "extent" VkImageCopy Source # 
type FieldIsArray "srcOffset" VkImageCopy Source # 
type FieldIsArray "srcOffset" VkImageCopy = False
type FieldIsArray "srcSubresource" VkImageCopy Source # 
type FieldIsArray "srcSubresource" VkImageCopy = False

data VkImageCreateInfo Source #

typedef struct VkImageCreateInfo {
    VkStructureType sType;
    const void*            pNext;
    VkImageCreateFlags     flags;
    VkImageType            imageType;
    VkFormat               format;
    VkExtent3D             extent;
    uint32_t               mipLevels;
    uint32_t               arrayLayers;
    VkSampleCountFlagBits  samples;
    VkImageTiling          tiling;
    VkImageUsageFlags      usage;
    VkSharingMode          sharingMode;
    uint32_t               queueFamilyIndexCount;
    const uint32_t*        pQueueFamilyIndices;
    VkImageLayout          initialLayout;
} VkImageCreateInfo;

VkImageCreateInfo registry at www.khronos.org

Instances

Eq VkImageCreateInfo Source # 
Ord VkImageCreateInfo Source # 
Show VkImageCreateInfo Source # 
Storable VkImageCreateInfo Source # 
VulkanMarshalPrim VkImageCreateInfo Source # 
VulkanMarshal VkImageCreateInfo Source # 
CanWriteField "arrayLayers" VkImageCreateInfo Source # 
CanWriteField "extent" VkImageCreateInfo Source # 
CanWriteField "flags" VkImageCreateInfo Source # 
CanWriteField "format" VkImageCreateInfo Source # 
CanWriteField "imageType" VkImageCreateInfo Source # 
CanWriteField "initialLayout" VkImageCreateInfo Source # 
CanWriteField "mipLevels" VkImageCreateInfo Source # 
CanWriteField "pNext" VkImageCreateInfo Source # 
CanWriteField "pQueueFamilyIndices" VkImageCreateInfo Source # 

Methods

writeField :: Ptr VkImageCreateInfo -> FieldType "pQueueFamilyIndices" VkImageCreateInfo -> IO () Source #

CanWriteField "queueFamilyIndexCount" VkImageCreateInfo Source # 

Methods

writeField :: Ptr VkImageCreateInfo -> FieldType "queueFamilyIndexCount" VkImageCreateInfo -> IO () Source #

CanWriteField "sType" VkImageCreateInfo Source # 
CanWriteField "samples" VkImageCreateInfo Source # 
CanWriteField "sharingMode" VkImageCreateInfo Source # 
CanWriteField "tiling" VkImageCreateInfo Source # 
CanWriteField "usage" VkImageCreateInfo Source # 
CanReadField "arrayLayers" VkImageCreateInfo Source # 
CanReadField "extent" VkImageCreateInfo Source # 
CanReadField "flags" VkImageCreateInfo Source # 
CanReadField "format" VkImageCreateInfo Source # 
CanReadField "imageType" VkImageCreateInfo Source # 
CanReadField "initialLayout" VkImageCreateInfo Source # 
CanReadField "mipLevels" VkImageCreateInfo Source # 
CanReadField "pNext" VkImageCreateInfo Source # 
CanReadField "pQueueFamilyIndices" VkImageCreateInfo Source # 
CanReadField "queueFamilyIndexCount" VkImageCreateInfo Source # 
CanReadField "sType" VkImageCreateInfo Source # 
CanReadField "samples" VkImageCreateInfo Source # 
CanReadField "sharingMode" VkImageCreateInfo Source # 
CanReadField "tiling" VkImageCreateInfo Source # 
CanReadField "usage" VkImageCreateInfo Source # 
HasField "arrayLayers" VkImageCreateInfo Source # 

Associated Types

type FieldType ("arrayLayers" :: Symbol) VkImageCreateInfo :: Type Source #

type FieldOptional ("arrayLayers" :: Symbol) VkImageCreateInfo :: Bool Source #

type FieldOffset ("arrayLayers" :: Symbol) VkImageCreateInfo :: Nat Source #

type FieldIsArray ("arrayLayers" :: Symbol) VkImageCreateInfo :: Bool Source #

HasField "extent" VkImageCreateInfo Source # 
HasField "flags" VkImageCreateInfo Source # 
HasField "format" VkImageCreateInfo Source # 
HasField "imageType" VkImageCreateInfo Source # 

Associated Types

type FieldType ("imageType" :: Symbol) VkImageCreateInfo :: Type Source #

type FieldOptional ("imageType" :: Symbol) VkImageCreateInfo :: Bool Source #

type FieldOffset ("imageType" :: Symbol) VkImageCreateInfo :: Nat Source #

type FieldIsArray ("imageType" :: Symbol) VkImageCreateInfo :: Bool Source #

HasField "initialLayout" VkImageCreateInfo Source # 

Associated Types

type FieldType ("initialLayout" :: Symbol) VkImageCreateInfo :: Type Source #

type FieldOptional ("initialLayout" :: Symbol) VkImageCreateInfo :: Bool Source #

type FieldOffset ("initialLayout" :: Symbol) VkImageCreateInfo :: Nat Source #

type FieldIsArray ("initialLayout" :: Symbol) VkImageCreateInfo :: Bool Source #

HasField "mipLevels" VkImageCreateInfo Source # 

Associated Types

type FieldType ("mipLevels" :: Symbol) VkImageCreateInfo :: Type Source #

type FieldOptional ("mipLevels" :: Symbol) VkImageCreateInfo :: Bool Source #

type FieldOffset ("mipLevels" :: Symbol) VkImageCreateInfo :: Nat Source #

type FieldIsArray ("mipLevels" :: Symbol) VkImageCreateInfo :: Bool Source #

HasField "pNext" VkImageCreateInfo Source # 
HasField "pQueueFamilyIndices" VkImageCreateInfo Source # 

Associated Types

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

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

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

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

HasField "queueFamilyIndexCount" VkImageCreateInfo Source # 

Associated Types

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

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

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

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

HasField "sType" VkImageCreateInfo Source # 
HasField "samples" VkImageCreateInfo Source # 
HasField "sharingMode" VkImageCreateInfo Source # 

Associated Types

type FieldType ("sharingMode" :: Symbol) VkImageCreateInfo :: Type Source #

type FieldOptional ("sharingMode" :: Symbol) VkImageCreateInfo :: Bool Source #

type FieldOffset ("sharingMode" :: Symbol) VkImageCreateInfo :: Nat Source #

type FieldIsArray ("sharingMode" :: Symbol) VkImageCreateInfo :: Bool Source #

HasField "tiling" VkImageCreateInfo Source # 
HasField "usage" VkImageCreateInfo Source # 
type StructFields VkImageCreateInfo Source # 
type StructFields VkImageCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "imageType" ((:) Symbol "format" ((:) Symbol "extent" ((:) Symbol "mipLevels" ((:) Symbol "arrayLayers" ((:) Symbol "samples" ((:) Symbol "tiling" ((:) Symbol "usage" ((:) Symbol "sharingMode" ((:) Symbol "queueFamilyIndexCount" ((:) Symbol "pQueueFamilyIndices" ((:) Symbol "initialLayout" ([] Symbol)))))))))))))))
type CUnionType VkImageCreateInfo Source # 
type ReturnedOnly VkImageCreateInfo Source # 
type StructExtends VkImageCreateInfo Source # 
type FieldType "arrayLayers" VkImageCreateInfo Source # 
type FieldType "arrayLayers" VkImageCreateInfo = Word32
type FieldType "extent" VkImageCreateInfo Source # 
type FieldType "flags" VkImageCreateInfo Source # 
type FieldType "format" VkImageCreateInfo Source # 
type FieldType "imageType" VkImageCreateInfo Source # 
type FieldType "initialLayout" VkImageCreateInfo Source # 
type FieldType "mipLevels" VkImageCreateInfo Source # 
type FieldType "pNext" VkImageCreateInfo Source # 
type FieldType "pQueueFamilyIndices" VkImageCreateInfo Source # 
type FieldType "pQueueFamilyIndices" VkImageCreateInfo = Ptr Word32
type FieldType "queueFamilyIndexCount" VkImageCreateInfo Source # 
type FieldType "queueFamilyIndexCount" VkImageCreateInfo = Word32
type FieldType "sType" VkImageCreateInfo Source # 
type FieldType "samples" VkImageCreateInfo Source # 
type FieldType "sharingMode" VkImageCreateInfo Source # 
type FieldType "tiling" VkImageCreateInfo Source # 
type FieldType "usage" VkImageCreateInfo Source # 
type FieldOptional "arrayLayers" VkImageCreateInfo Source # 
type FieldOptional "extent" VkImageCreateInfo Source # 
type FieldOptional "flags" VkImageCreateInfo Source # 
type FieldOptional "format" VkImageCreateInfo Source # 
type FieldOptional "imageType" VkImageCreateInfo Source # 
type FieldOptional "initialLayout" VkImageCreateInfo Source # 
type FieldOptional "initialLayout" VkImageCreateInfo = False
type FieldOptional "mipLevels" VkImageCreateInfo Source # 
type FieldOptional "pNext" VkImageCreateInfo Source # 
type FieldOptional "pQueueFamilyIndices" VkImageCreateInfo Source # 
type FieldOptional "pQueueFamilyIndices" VkImageCreateInfo = False
type FieldOptional "queueFamilyIndexCount" VkImageCreateInfo Source # 
type FieldOptional "queueFamilyIndexCount" VkImageCreateInfo = True
type FieldOptional "sType" VkImageCreateInfo Source # 
type FieldOptional "samples" VkImageCreateInfo Source # 
type FieldOptional "sharingMode" VkImageCreateInfo Source # 
type FieldOptional "tiling" VkImageCreateInfo Source # 
type FieldOptional "usage" VkImageCreateInfo Source # 
type FieldOffset "arrayLayers" VkImageCreateInfo Source # 
type FieldOffset "arrayLayers" VkImageCreateInfo = 44
type FieldOffset "extent" VkImageCreateInfo Source # 
type FieldOffset "extent" VkImageCreateInfo = 28
type FieldOffset "flags" VkImageCreateInfo Source # 
type FieldOffset "flags" VkImageCreateInfo = 16
type FieldOffset "format" VkImageCreateInfo Source # 
type FieldOffset "format" VkImageCreateInfo = 24
type FieldOffset "imageType" VkImageCreateInfo Source # 
type FieldOffset "imageType" VkImageCreateInfo = 20
type FieldOffset "initialLayout" VkImageCreateInfo Source # 
type FieldOffset "initialLayout" VkImageCreateInfo = 80
type FieldOffset "mipLevels" VkImageCreateInfo Source # 
type FieldOffset "mipLevels" VkImageCreateInfo = 40
type FieldOffset "pNext" VkImageCreateInfo Source # 
type FieldOffset "pQueueFamilyIndices" VkImageCreateInfo Source # 
type FieldOffset "pQueueFamilyIndices" VkImageCreateInfo = 72
type FieldOffset "queueFamilyIndexCount" VkImageCreateInfo Source # 
type FieldOffset "queueFamilyIndexCount" VkImageCreateInfo = 64
type FieldOffset "sType" VkImageCreateInfo Source # 
type FieldOffset "samples" VkImageCreateInfo Source # 
type FieldOffset "samples" VkImageCreateInfo = 48
type FieldOffset "sharingMode" VkImageCreateInfo Source # 
type FieldOffset "sharingMode" VkImageCreateInfo = 60
type FieldOffset "tiling" VkImageCreateInfo Source # 
type FieldOffset "tiling" VkImageCreateInfo = 52
type FieldOffset "usage" VkImageCreateInfo Source # 
type FieldOffset "usage" VkImageCreateInfo = 56
type FieldIsArray "arrayLayers" VkImageCreateInfo Source # 
type FieldIsArray "arrayLayers" VkImageCreateInfo = False
type FieldIsArray "extent" VkImageCreateInfo Source # 
type FieldIsArray "flags" VkImageCreateInfo Source # 
type FieldIsArray "format" VkImageCreateInfo Source # 
type FieldIsArray "imageType" VkImageCreateInfo Source # 
type FieldIsArray "initialLayout" VkImageCreateInfo Source # 
type FieldIsArray "initialLayout" VkImageCreateInfo = False
type FieldIsArray "mipLevels" VkImageCreateInfo Source # 
type FieldIsArray "pNext" VkImageCreateInfo Source # 
type FieldIsArray "pQueueFamilyIndices" VkImageCreateInfo Source # 
type FieldIsArray "pQueueFamilyIndices" VkImageCreateInfo = False
type FieldIsArray "queueFamilyIndexCount" VkImageCreateInfo Source # 
type FieldIsArray "queueFamilyIndexCount" VkImageCreateInfo = False
type FieldIsArray "sType" VkImageCreateInfo Source # 
type FieldIsArray "samples" VkImageCreateInfo Source # 
type FieldIsArray "sharingMode" VkImageCreateInfo Source # 
type FieldIsArray "sharingMode" VkImageCreateInfo = False
type FieldIsArray "tiling" VkImageCreateInfo Source # 
type FieldIsArray "usage" VkImageCreateInfo Source # 

data VkImageFormatListCreateInfoKHR Source #

typedef struct VkImageFormatListCreateInfoKHR {
    VkStructureType sType;
    const void*            pNext;
    uint32_t               viewFormatCount;
    const VkFormat*      pViewFormats;
} VkImageFormatListCreateInfoKHR;

VkImageFormatListCreateInfoKHR registry at www.khronos.org

Instances

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

data VkImageFormatProperties Source #

typedef struct VkImageFormatProperties {
    VkExtent3D             maxExtent;
    uint32_t               maxMipLevels;
    uint32_t               maxArrayLayers;
    VkSampleCountFlags     sampleCounts;
    VkDeviceSize           maxResourceSize;
} VkImageFormatProperties;

VkImageFormatProperties registry at www.khronos.org

Instances

Eq VkImageFormatProperties Source # 
Ord VkImageFormatProperties Source # 
Show VkImageFormatProperties Source # 
Storable VkImageFormatProperties Source # 
VulkanMarshalPrim VkImageFormatProperties Source # 
VulkanMarshal VkImageFormatProperties Source # 
CanWriteField "maxArrayLayers" VkImageFormatProperties Source # 
CanWriteField "maxExtent" VkImageFormatProperties Source # 
CanWriteField "maxMipLevels" VkImageFormatProperties Source # 
CanWriteField "maxResourceSize" VkImageFormatProperties Source # 
CanWriteField "sampleCounts" VkImageFormatProperties Source # 
CanReadField "maxArrayLayers" VkImageFormatProperties Source # 
CanReadField "maxExtent" VkImageFormatProperties Source # 
CanReadField "maxMipLevels" VkImageFormatProperties Source # 
CanReadField "maxResourceSize" VkImageFormatProperties Source # 
CanReadField "sampleCounts" VkImageFormatProperties Source # 
HasField "maxArrayLayers" VkImageFormatProperties Source # 

Associated Types

type FieldType ("maxArrayLayers" :: Symbol) VkImageFormatProperties :: Type Source #

type FieldOptional ("maxArrayLayers" :: Symbol) VkImageFormatProperties :: Bool Source #

type FieldOffset ("maxArrayLayers" :: Symbol) VkImageFormatProperties :: Nat Source #

type FieldIsArray ("maxArrayLayers" :: Symbol) VkImageFormatProperties :: Bool Source #

HasField "maxExtent" VkImageFormatProperties Source # 
HasField "maxMipLevels" VkImageFormatProperties Source # 

Associated Types

type FieldType ("maxMipLevels" :: Symbol) VkImageFormatProperties :: Type Source #

type FieldOptional ("maxMipLevels" :: Symbol) VkImageFormatProperties :: Bool Source #

type FieldOffset ("maxMipLevels" :: Symbol) VkImageFormatProperties :: Nat Source #

type FieldIsArray ("maxMipLevels" :: Symbol) VkImageFormatProperties :: Bool Source #

HasField "maxResourceSize" VkImageFormatProperties Source # 

Associated Types

type FieldType ("maxResourceSize" :: Symbol) VkImageFormatProperties :: Type Source #

type FieldOptional ("maxResourceSize" :: Symbol) VkImageFormatProperties :: Bool Source #

type FieldOffset ("maxResourceSize" :: Symbol) VkImageFormatProperties :: Nat Source #

type FieldIsArray ("maxResourceSize" :: Symbol) VkImageFormatProperties :: Bool Source #

HasField "sampleCounts" VkImageFormatProperties Source # 

Associated Types

type FieldType ("sampleCounts" :: Symbol) VkImageFormatProperties :: Type Source #

type FieldOptional ("sampleCounts" :: Symbol) VkImageFormatProperties :: Bool Source #

type FieldOffset ("sampleCounts" :: Symbol) VkImageFormatProperties :: Nat Source #

type FieldIsArray ("sampleCounts" :: Symbol) VkImageFormatProperties :: Bool Source #

type StructFields VkImageFormatProperties Source # 
type StructFields VkImageFormatProperties = (:) Symbol "maxExtent" ((:) Symbol "maxMipLevels" ((:) Symbol "maxArrayLayers" ((:) Symbol "sampleCounts" ((:) Symbol "maxResourceSize" ([] Symbol)))))
type CUnionType VkImageFormatProperties Source # 
type ReturnedOnly VkImageFormatProperties Source # 
type StructExtends VkImageFormatProperties Source # 
type FieldType "maxArrayLayers" VkImageFormatProperties Source # 
type FieldType "maxArrayLayers" VkImageFormatProperties = Word32
type FieldType "maxExtent" VkImageFormatProperties Source # 
type FieldType "maxMipLevels" VkImageFormatProperties Source # 
type FieldType "maxResourceSize" VkImageFormatProperties Source # 
type FieldType "sampleCounts" VkImageFormatProperties Source # 
type FieldOptional "maxArrayLayers" VkImageFormatProperties Source # 
type FieldOptional "maxExtent" VkImageFormatProperties Source # 
type FieldOptional "maxMipLevels" VkImageFormatProperties Source # 
type FieldOptional "maxResourceSize" VkImageFormatProperties Source # 
type FieldOptional "sampleCounts" VkImageFormatProperties Source # 
type FieldOffset "maxArrayLayers" VkImageFormatProperties Source # 
type FieldOffset "maxArrayLayers" VkImageFormatProperties = 16
type FieldOffset "maxExtent" VkImageFormatProperties Source # 
type FieldOffset "maxMipLevels" VkImageFormatProperties Source # 
type FieldOffset "maxMipLevels" VkImageFormatProperties = 12
type FieldOffset "maxResourceSize" VkImageFormatProperties Source # 
type FieldOffset "maxResourceSize" VkImageFormatProperties = 24
type FieldOffset "sampleCounts" VkImageFormatProperties Source # 
type FieldOffset "sampleCounts" VkImageFormatProperties = 20
type FieldIsArray "maxArrayLayers" VkImageFormatProperties Source # 
type FieldIsArray "maxExtent" VkImageFormatProperties Source # 
type FieldIsArray "maxMipLevels" VkImageFormatProperties Source # 
type FieldIsArray "maxResourceSize" VkImageFormatProperties Source # 
type FieldIsArray "maxResourceSize" VkImageFormatProperties = False
type FieldIsArray "sampleCounts" VkImageFormatProperties Source # 

data VkImageFormatProperties2 Source #

typedef struct VkImageFormatProperties2 {
    VkStructureType sType;
    void* pNext;
    VkImageFormatProperties          imageFormatProperties;
} VkImageFormatProperties2;

VkImageFormatProperties2 registry at www.khronos.org

Instances

Eq VkImageFormatProperties2 Source # 
Ord VkImageFormatProperties2 Source # 
Show VkImageFormatProperties2 Source # 
Storable VkImageFormatProperties2 Source # 
VulkanMarshalPrim VkImageFormatProperties2 Source # 
VulkanMarshal VkImageFormatProperties2 Source # 
CanWriteField "imageFormatProperties" VkImageFormatProperties2 Source # 
CanWriteField "pNext" VkImageFormatProperties2 Source # 
CanWriteField "sType" VkImageFormatProperties2 Source # 
CanReadField "imageFormatProperties" VkImageFormatProperties2 Source # 
CanReadField "pNext" VkImageFormatProperties2 Source # 
CanReadField "sType" VkImageFormatProperties2 Source # 
HasField "imageFormatProperties" VkImageFormatProperties2 Source # 

Associated Types

type FieldType ("imageFormatProperties" :: Symbol) VkImageFormatProperties2 :: Type Source #

type FieldOptional ("imageFormatProperties" :: Symbol) VkImageFormatProperties2 :: Bool Source #

type FieldOffset ("imageFormatProperties" :: Symbol) VkImageFormatProperties2 :: Nat Source #

type FieldIsArray ("imageFormatProperties" :: Symbol) VkImageFormatProperties2 :: Bool Source #

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

data VkImageMemoryBarrier Source #

typedef struct VkImageMemoryBarrier {
    VkStructureType sType;
    const void*            pNext;
    VkAccessFlags          srcAccessMask;
    VkAccessFlags          dstAccessMask;
    VkImageLayout          oldLayout;
    VkImageLayout          newLayout;
    uint32_t               srcQueueFamilyIndex;
    uint32_t               dstQueueFamilyIndex;
    VkImage                image;
    VkImageSubresourceRange subresourceRange;
} VkImageMemoryBarrier;

VkImageMemoryBarrier registry at www.khronos.org

Instances

Eq VkImageMemoryBarrier Source # 
Ord VkImageMemoryBarrier Source # 
Show VkImageMemoryBarrier Source # 
Storable VkImageMemoryBarrier Source # 
VulkanMarshalPrim VkImageMemoryBarrier Source # 
VulkanMarshal VkImageMemoryBarrier Source # 
CanWriteField "dstAccessMask" VkImageMemoryBarrier Source # 
CanWriteField "dstQueueFamilyIndex" VkImageMemoryBarrier Source # 

Methods

writeField :: Ptr VkImageMemoryBarrier -> FieldType "dstQueueFamilyIndex" VkImageMemoryBarrier -> IO () Source #

CanWriteField "image" VkImageMemoryBarrier Source # 
CanWriteField "newLayout" VkImageMemoryBarrier Source # 
CanWriteField "oldLayout" VkImageMemoryBarrier Source # 
CanWriteField "pNext" VkImageMemoryBarrier Source # 
CanWriteField "sType" VkImageMemoryBarrier Source # 
CanWriteField "srcAccessMask" VkImageMemoryBarrier Source # 
CanWriteField "srcQueueFamilyIndex" VkImageMemoryBarrier Source # 

Methods

writeField :: Ptr VkImageMemoryBarrier -> FieldType "srcQueueFamilyIndex" VkImageMemoryBarrier -> IO () Source #

CanWriteField "subresourceRange" VkImageMemoryBarrier Source # 
CanReadField "dstAccessMask" VkImageMemoryBarrier Source # 
CanReadField "dstQueueFamilyIndex" VkImageMemoryBarrier Source # 
CanReadField "image" VkImageMemoryBarrier Source # 
CanReadField "newLayout" VkImageMemoryBarrier Source # 
CanReadField "oldLayout" VkImageMemoryBarrier Source # 
CanReadField "pNext" VkImageMemoryBarrier Source # 
CanReadField "sType" VkImageMemoryBarrier Source # 
CanReadField "srcAccessMask" VkImageMemoryBarrier Source # 
CanReadField "srcQueueFamilyIndex" VkImageMemoryBarrier Source # 
CanReadField "subresourceRange" VkImageMemoryBarrier Source # 
HasField "dstAccessMask" VkImageMemoryBarrier Source # 

Associated Types

type FieldType ("dstAccessMask" :: Symbol) VkImageMemoryBarrier :: Type Source #

type FieldOptional ("dstAccessMask" :: Symbol) VkImageMemoryBarrier :: Bool Source #

type FieldOffset ("dstAccessMask" :: Symbol) VkImageMemoryBarrier :: Nat Source #

type FieldIsArray ("dstAccessMask" :: Symbol) VkImageMemoryBarrier :: Bool Source #

HasField "dstQueueFamilyIndex" VkImageMemoryBarrier Source # 

Associated Types

type FieldType ("dstQueueFamilyIndex" :: Symbol) VkImageMemoryBarrier :: Type Source #

type FieldOptional ("dstQueueFamilyIndex" :: Symbol) VkImageMemoryBarrier :: Bool Source #

type FieldOffset ("dstQueueFamilyIndex" :: Symbol) VkImageMemoryBarrier :: Nat Source #

type FieldIsArray ("dstQueueFamilyIndex" :: Symbol) VkImageMemoryBarrier :: Bool Source #

HasField "image" VkImageMemoryBarrier Source # 
HasField "newLayout" VkImageMemoryBarrier Source # 
HasField "oldLayout" VkImageMemoryBarrier Source # 
HasField "pNext" VkImageMemoryBarrier Source # 
HasField "sType" VkImageMemoryBarrier Source # 
HasField "srcAccessMask" VkImageMemoryBarrier Source # 

Associated Types

type FieldType ("srcAccessMask" :: Symbol) VkImageMemoryBarrier :: Type Source #

type FieldOptional ("srcAccessMask" :: Symbol) VkImageMemoryBarrier :: Bool Source #

type FieldOffset ("srcAccessMask" :: Symbol) VkImageMemoryBarrier :: Nat Source #

type FieldIsArray ("srcAccessMask" :: Symbol) VkImageMemoryBarrier :: Bool Source #

HasField "srcQueueFamilyIndex" VkImageMemoryBarrier Source # 

Associated Types

type FieldType ("srcQueueFamilyIndex" :: Symbol) VkImageMemoryBarrier :: Type Source #

type FieldOptional ("srcQueueFamilyIndex" :: Symbol) VkImageMemoryBarrier :: Bool Source #

type FieldOffset ("srcQueueFamilyIndex" :: Symbol) VkImageMemoryBarrier :: Nat Source #

type FieldIsArray ("srcQueueFamilyIndex" :: Symbol) VkImageMemoryBarrier :: Bool Source #

HasField "subresourceRange" VkImageMemoryBarrier Source # 

Associated Types

type FieldType ("subresourceRange" :: Symbol) VkImageMemoryBarrier :: Type Source #

type FieldOptional ("subresourceRange" :: Symbol) VkImageMemoryBarrier :: Bool Source #

type FieldOffset ("subresourceRange" :: Symbol) VkImageMemoryBarrier :: Nat Source #

type FieldIsArray ("subresourceRange" :: Symbol) VkImageMemoryBarrier :: Bool Source #

type StructFields VkImageMemoryBarrier Source # 
type StructFields VkImageMemoryBarrier = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "srcAccessMask" ((:) Symbol "dstAccessMask" ((:) Symbol "oldLayout" ((:) Symbol "newLayout" ((:) Symbol "srcQueueFamilyIndex" ((:) Symbol "dstQueueFamilyIndex" ((:) Symbol "image" ((:) Symbol "subresourceRange" ([] Symbol))))))))))
type CUnionType VkImageMemoryBarrier Source # 
type ReturnedOnly VkImageMemoryBarrier Source # 
type StructExtends VkImageMemoryBarrier Source # 
type FieldType "dstAccessMask" VkImageMemoryBarrier Source # 
type FieldType "dstQueueFamilyIndex" VkImageMemoryBarrier Source # 
type FieldType "dstQueueFamilyIndex" VkImageMemoryBarrier = Word32
type FieldType "image" VkImageMemoryBarrier Source # 
type FieldType "newLayout" VkImageMemoryBarrier Source # 
type FieldType "oldLayout" VkImageMemoryBarrier Source # 
type FieldType "pNext" VkImageMemoryBarrier Source # 
type FieldType "sType" VkImageMemoryBarrier Source # 
type FieldType "srcAccessMask" VkImageMemoryBarrier Source # 
type FieldType "srcQueueFamilyIndex" VkImageMemoryBarrier Source # 
type FieldType "srcQueueFamilyIndex" VkImageMemoryBarrier = Word32
type FieldType "subresourceRange" VkImageMemoryBarrier Source # 
type FieldOptional "dstAccessMask" VkImageMemoryBarrier Source # 
type FieldOptional "dstAccessMask" VkImageMemoryBarrier = True
type FieldOptional "dstQueueFamilyIndex" VkImageMemoryBarrier Source # 
type FieldOptional "dstQueueFamilyIndex" VkImageMemoryBarrier = False
type FieldOptional "image" VkImageMemoryBarrier Source # 
type FieldOptional "newLayout" VkImageMemoryBarrier Source # 
type FieldOptional "oldLayout" VkImageMemoryBarrier Source # 
type FieldOptional "pNext" VkImageMemoryBarrier Source # 
type FieldOptional "sType" VkImageMemoryBarrier Source # 
type FieldOptional "srcAccessMask" VkImageMemoryBarrier Source # 
type FieldOptional "srcAccessMask" VkImageMemoryBarrier = True
type FieldOptional "srcQueueFamilyIndex" VkImageMemoryBarrier Source # 
type FieldOptional "srcQueueFamilyIndex" VkImageMemoryBarrier = False
type FieldOptional "subresourceRange" VkImageMemoryBarrier Source # 
type FieldOptional "subresourceRange" VkImageMemoryBarrier = False
type FieldOffset "dstAccessMask" VkImageMemoryBarrier Source # 
type FieldOffset "dstAccessMask" VkImageMemoryBarrier = 20
type FieldOffset "dstQueueFamilyIndex" VkImageMemoryBarrier Source # 
type FieldOffset "dstQueueFamilyIndex" VkImageMemoryBarrier = 36
type FieldOffset "image" VkImageMemoryBarrier Source # 
type FieldOffset "newLayout" VkImageMemoryBarrier Source # 
type FieldOffset "newLayout" VkImageMemoryBarrier = 28
type FieldOffset "oldLayout" VkImageMemoryBarrier Source # 
type FieldOffset "oldLayout" VkImageMemoryBarrier = 24
type FieldOffset "pNext" VkImageMemoryBarrier Source # 
type FieldOffset "sType" VkImageMemoryBarrier Source # 
type FieldOffset "srcAccessMask" VkImageMemoryBarrier Source # 
type FieldOffset "srcAccessMask" VkImageMemoryBarrier = 16
type FieldOffset "srcQueueFamilyIndex" VkImageMemoryBarrier Source # 
type FieldOffset "srcQueueFamilyIndex" VkImageMemoryBarrier = 32
type FieldOffset "subresourceRange" VkImageMemoryBarrier Source # 
type FieldOffset "subresourceRange" VkImageMemoryBarrier = 48
type FieldIsArray "dstAccessMask" VkImageMemoryBarrier Source # 
type FieldIsArray "dstAccessMask" VkImageMemoryBarrier = False
type FieldIsArray "dstQueueFamilyIndex" VkImageMemoryBarrier Source # 
type FieldIsArray "dstQueueFamilyIndex" VkImageMemoryBarrier = False
type FieldIsArray "image" VkImageMemoryBarrier Source # 
type FieldIsArray "newLayout" VkImageMemoryBarrier Source # 
type FieldIsArray "oldLayout" VkImageMemoryBarrier Source # 
type FieldIsArray "pNext" VkImageMemoryBarrier Source # 
type FieldIsArray "sType" VkImageMemoryBarrier Source # 
type FieldIsArray "srcAccessMask" VkImageMemoryBarrier Source # 
type FieldIsArray "srcAccessMask" VkImageMemoryBarrier = False
type FieldIsArray "srcQueueFamilyIndex" VkImageMemoryBarrier Source # 
type FieldIsArray "srcQueueFamilyIndex" VkImageMemoryBarrier = False
type FieldIsArray "subresourceRange" VkImageMemoryBarrier Source # 
type FieldIsArray "subresourceRange" VkImageMemoryBarrier = False

data VkImageMemoryRequirementsInfo2 Source #

typedef struct VkImageMemoryRequirementsInfo2 {
    VkStructureType sType;
    const void*                                                          pNext;
    VkImage                                                              image;
} VkImageMemoryRequirementsInfo2;

VkImageMemoryRequirementsInfo2 registry at www.khronos.org

Instances

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

data VkImagePlaneMemoryRequirementsInfo Source #

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

VkImagePlaneMemoryRequirementsInfo registry at www.khronos.org

Instances

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

data VkImageResolve Source #

typedef struct VkImageResolve {
    VkImageSubresourceLayers srcSubresource;
    VkOffset3D             srcOffset;
    VkImageSubresourceLayers dstSubresource;
    VkOffset3D             dstOffset;
    VkExtent3D             extent;
} VkImageResolve;

VkImageResolve registry at www.khronos.org

Instances

Eq VkImageResolve Source # 
Ord VkImageResolve Source # 
Show VkImageResolve Source # 
Storable VkImageResolve Source # 
VulkanMarshalPrim VkImageResolve Source # 
VulkanMarshal VkImageResolve Source # 
CanWriteField "dstOffset" VkImageResolve Source # 
CanWriteField "dstSubresource" VkImageResolve Source # 

Methods

writeField :: Ptr VkImageResolve -> FieldType "dstSubresource" VkImageResolve -> IO () Source #

CanWriteField "extent" VkImageResolve Source # 
CanWriteField "srcOffset" VkImageResolve Source # 
CanWriteField "srcSubresource" VkImageResolve Source # 

Methods

writeField :: Ptr VkImageResolve -> FieldType "srcSubresource" VkImageResolve -> IO () Source #

CanReadField "dstOffset" VkImageResolve Source # 
CanReadField "dstSubresource" VkImageResolve Source # 
CanReadField "extent" VkImageResolve Source # 
CanReadField "srcOffset" VkImageResolve Source # 
CanReadField "srcSubresource" VkImageResolve Source # 
HasField "dstOffset" VkImageResolve Source # 

Associated Types

type FieldType ("dstOffset" :: Symbol) VkImageResolve :: Type Source #

type FieldOptional ("dstOffset" :: Symbol) VkImageResolve :: Bool Source #

type FieldOffset ("dstOffset" :: Symbol) VkImageResolve :: Nat Source #

type FieldIsArray ("dstOffset" :: Symbol) VkImageResolve :: Bool Source #

HasField "dstSubresource" VkImageResolve Source # 

Associated Types

type FieldType ("dstSubresource" :: Symbol) VkImageResolve :: Type Source #

type FieldOptional ("dstSubresource" :: Symbol) VkImageResolve :: Bool Source #

type FieldOffset ("dstSubresource" :: Symbol) VkImageResolve :: Nat Source #

type FieldIsArray ("dstSubresource" :: Symbol) VkImageResolve :: Bool Source #

HasField "extent" VkImageResolve Source # 

Associated Types

type FieldType ("extent" :: Symbol) VkImageResolve :: Type Source #

type FieldOptional ("extent" :: Symbol) VkImageResolve :: Bool Source #

type FieldOffset ("extent" :: Symbol) VkImageResolve :: Nat Source #

type FieldIsArray ("extent" :: Symbol) VkImageResolve :: Bool Source #

HasField "srcOffset" VkImageResolve Source # 

Associated Types

type FieldType ("srcOffset" :: Symbol) VkImageResolve :: Type Source #

type FieldOptional ("srcOffset" :: Symbol) VkImageResolve :: Bool Source #

type FieldOffset ("srcOffset" :: Symbol) VkImageResolve :: Nat Source #

type FieldIsArray ("srcOffset" :: Symbol) VkImageResolve :: Bool Source #

HasField "srcSubresource" VkImageResolve Source # 

Associated Types

type FieldType ("srcSubresource" :: Symbol) VkImageResolve :: Type Source #

type FieldOptional ("srcSubresource" :: Symbol) VkImageResolve :: Bool Source #

type FieldOffset ("srcSubresource" :: Symbol) VkImageResolve :: Nat Source #

type FieldIsArray ("srcSubresource" :: Symbol) VkImageResolve :: Bool Source #

type StructFields VkImageResolve Source # 
type StructFields VkImageResolve = (:) Symbol "srcSubresource" ((:) Symbol "srcOffset" ((:) Symbol "dstSubresource" ((:) Symbol "dstOffset" ((:) Symbol "extent" ([] Symbol)))))
type CUnionType VkImageResolve Source # 
type ReturnedOnly VkImageResolve Source # 
type StructExtends VkImageResolve Source # 
type FieldType "dstOffset" VkImageResolve Source # 
type FieldType "dstSubresource" VkImageResolve Source # 
type FieldType "extent" VkImageResolve Source # 
type FieldType "srcOffset" VkImageResolve Source # 
type FieldType "srcSubresource" VkImageResolve Source # 
type FieldOptional "dstOffset" VkImageResolve Source # 
type FieldOptional "dstSubresource" VkImageResolve Source # 
type FieldOptional "dstSubresource" VkImageResolve = False
type FieldOptional "extent" VkImageResolve Source # 
type FieldOptional "srcOffset" VkImageResolve Source # 
type FieldOptional "srcSubresource" VkImageResolve Source # 
type FieldOptional "srcSubresource" VkImageResolve = False
type FieldOffset "dstOffset" VkImageResolve Source # 
type FieldOffset "dstOffset" VkImageResolve = 44
type FieldOffset "dstSubresource" VkImageResolve Source # 
type FieldOffset "dstSubresource" VkImageResolve = 28
type FieldOffset "extent" VkImageResolve Source # 
type FieldOffset "extent" VkImageResolve = 56
type FieldOffset "srcOffset" VkImageResolve Source # 
type FieldOffset "srcOffset" VkImageResolve = 16
type FieldOffset "srcSubresource" VkImageResolve Source # 
type FieldOffset "srcSubresource" VkImageResolve = 0
type FieldIsArray "dstOffset" VkImageResolve Source # 
type FieldIsArray "dstOffset" VkImageResolve = False
type FieldIsArray "dstSubresource" VkImageResolve Source # 
type FieldIsArray "dstSubresource" VkImageResolve = False
type FieldIsArray "extent" VkImageResolve Source # 
type FieldIsArray "srcOffset" VkImageResolve Source # 
type FieldIsArray "srcOffset" VkImageResolve = False
type FieldIsArray "srcSubresource" VkImageResolve Source # 
type FieldIsArray "srcSubresource" VkImageResolve = False

data VkImageSparseMemoryRequirementsInfo2 Source #

typedef struct VkImageSparseMemoryRequirementsInfo2 {
    VkStructureType sType;
    const void*                                                          pNext;
    VkImage                                                              image;
} VkImageSparseMemoryRequirementsInfo2;

VkImageSparseMemoryRequirementsInfo2 registry at www.khronos.org

Instances

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

data VkImageSubresource Source #

typedef struct VkImageSubresource {
    VkImageAspectFlags     aspectMask;
    uint32_t               mipLevel;
    uint32_t               arrayLayer;
} VkImageSubresource;

VkImageSubresource registry at www.khronos.org

Instances

Eq VkImageSubresource Source # 
Ord VkImageSubresource Source # 
Show VkImageSubresource Source # 
Storable VkImageSubresource Source # 
VulkanMarshalPrim VkImageSubresource Source # 
VulkanMarshal VkImageSubresource Source # 
CanWriteField "arrayLayer" VkImageSubresource Source # 
CanWriteField "aspectMask" VkImageSubresource Source # 
CanWriteField "mipLevel" VkImageSubresource Source # 
CanReadField "arrayLayer" VkImageSubresource Source # 
CanReadField "aspectMask" VkImageSubresource Source # 
CanReadField "mipLevel" VkImageSubresource Source # 
HasField "arrayLayer" VkImageSubresource Source # 

Associated Types

type FieldType ("arrayLayer" :: Symbol) VkImageSubresource :: Type Source #

type FieldOptional ("arrayLayer" :: Symbol) VkImageSubresource :: Bool Source #

type FieldOffset ("arrayLayer" :: Symbol) VkImageSubresource :: Nat Source #

type FieldIsArray ("arrayLayer" :: Symbol) VkImageSubresource :: Bool Source #

HasField "aspectMask" VkImageSubresource Source # 

Associated Types

type FieldType ("aspectMask" :: Symbol) VkImageSubresource :: Type Source #

type FieldOptional ("aspectMask" :: Symbol) VkImageSubresource :: Bool Source #

type FieldOffset ("aspectMask" :: Symbol) VkImageSubresource :: Nat Source #

type FieldIsArray ("aspectMask" :: Symbol) VkImageSubresource :: Bool Source #

HasField "mipLevel" VkImageSubresource Source # 
type StructFields VkImageSubresource Source # 
type StructFields VkImageSubresource = (:) Symbol "aspectMask" ((:) Symbol "mipLevel" ((:) Symbol "arrayLayer" ([] Symbol)))
type CUnionType VkImageSubresource Source # 
type ReturnedOnly VkImageSubresource Source # 
type StructExtends VkImageSubresource Source # 
type FieldType "arrayLayer" VkImageSubresource Source # 
type FieldType "arrayLayer" VkImageSubresource = Word32
type FieldType "aspectMask" VkImageSubresource Source # 
type FieldType "mipLevel" VkImageSubresource Source # 
type FieldOptional "arrayLayer" VkImageSubresource Source # 
type FieldOptional "aspectMask" VkImageSubresource Source # 
type FieldOptional "mipLevel" VkImageSubresource Source # 
type FieldOffset "arrayLayer" VkImageSubresource Source # 
type FieldOffset "arrayLayer" VkImageSubresource = 8
type FieldOffset "aspectMask" VkImageSubresource Source # 
type FieldOffset "aspectMask" VkImageSubresource = 0
type FieldOffset "mipLevel" VkImageSubresource Source # 
type FieldOffset "mipLevel" VkImageSubresource = 4
type FieldIsArray "arrayLayer" VkImageSubresource Source # 
type FieldIsArray "aspectMask" VkImageSubresource Source # 
type FieldIsArray "mipLevel" VkImageSubresource Source # 

data VkImageSubresourceLayers Source #

typedef struct VkImageSubresourceLayers {
    VkImageAspectFlags     aspectMask;
    uint32_t               mipLevel;
    uint32_t               baseArrayLayer;
    uint32_t               layerCount;
} VkImageSubresourceLayers;

VkImageSubresourceLayers registry at www.khronos.org

Instances

Eq VkImageSubresourceLayers Source # 
Ord VkImageSubresourceLayers Source # 
Show VkImageSubresourceLayers Source # 
Storable VkImageSubresourceLayers Source # 
VulkanMarshalPrim VkImageSubresourceLayers Source # 
VulkanMarshal VkImageSubresourceLayers Source # 
CanWriteField "aspectMask" VkImageSubresourceLayers Source # 
CanWriteField "baseArrayLayer" VkImageSubresourceLayers Source # 
CanWriteField "layerCount" VkImageSubresourceLayers Source # 
CanWriteField "mipLevel" VkImageSubresourceLayers Source # 
CanReadField "aspectMask" VkImageSubresourceLayers Source # 
CanReadField "baseArrayLayer" VkImageSubresourceLayers Source # 
CanReadField "layerCount" VkImageSubresourceLayers Source # 
CanReadField "mipLevel" VkImageSubresourceLayers Source # 
HasField "aspectMask" VkImageSubresourceLayers Source # 
HasField "baseArrayLayer" VkImageSubresourceLayers Source # 

Associated Types

type FieldType ("baseArrayLayer" :: Symbol) VkImageSubresourceLayers :: Type Source #

type FieldOptional ("baseArrayLayer" :: Symbol) VkImageSubresourceLayers :: Bool Source #

type FieldOffset ("baseArrayLayer" :: Symbol) VkImageSubresourceLayers :: Nat Source #

type FieldIsArray ("baseArrayLayer" :: Symbol) VkImageSubresourceLayers :: Bool Source #

HasField "layerCount" VkImageSubresourceLayers Source # 
HasField "mipLevel" VkImageSubresourceLayers Source # 
type StructFields VkImageSubresourceLayers Source # 
type StructFields VkImageSubresourceLayers = (:) Symbol "aspectMask" ((:) Symbol "mipLevel" ((:) Symbol "baseArrayLayer" ((:) Symbol "layerCount" ([] Symbol))))
type CUnionType VkImageSubresourceLayers Source # 
type ReturnedOnly VkImageSubresourceLayers Source # 
type StructExtends VkImageSubresourceLayers Source # 
type FieldType "aspectMask" VkImageSubresourceLayers Source # 
type FieldType "baseArrayLayer" VkImageSubresourceLayers Source # 
type FieldType "baseArrayLayer" VkImageSubresourceLayers = Word32
type FieldType "layerCount" VkImageSubresourceLayers Source # 
type FieldType "mipLevel" VkImageSubresourceLayers Source # 
type FieldOptional "aspectMask" VkImageSubresourceLayers Source # 
type FieldOptional "baseArrayLayer" VkImageSubresourceLayers Source # 
type FieldOptional "layerCount" VkImageSubresourceLayers Source # 
type FieldOptional "mipLevel" VkImageSubresourceLayers Source # 
type FieldOffset "aspectMask" VkImageSubresourceLayers Source # 
type FieldOffset "baseArrayLayer" VkImageSubresourceLayers Source # 
type FieldOffset "baseArrayLayer" VkImageSubresourceLayers = 8
type FieldOffset "layerCount" VkImageSubresourceLayers Source # 
type FieldOffset "layerCount" VkImageSubresourceLayers = 12
type FieldOffset "mipLevel" VkImageSubresourceLayers Source # 
type FieldIsArray "aspectMask" VkImageSubresourceLayers Source # 
type FieldIsArray "baseArrayLayer" VkImageSubresourceLayers Source # 
type FieldIsArray "layerCount" VkImageSubresourceLayers Source # 
type FieldIsArray "mipLevel" VkImageSubresourceLayers Source # 

data VkImageSubresourceRange Source #

typedef struct VkImageSubresourceRange {
    VkImageAspectFlags     aspectMask;
    uint32_t               baseMipLevel;
    uint32_t               levelCount;
    uint32_t               baseArrayLayer;
    uint32_t               layerCount;
} VkImageSubresourceRange;

VkImageSubresourceRange registry at www.khronos.org

Instances

Eq VkImageSubresourceRange Source # 
Ord VkImageSubresourceRange Source # 
Show VkImageSubresourceRange Source # 
Storable VkImageSubresourceRange Source # 
VulkanMarshalPrim VkImageSubresourceRange Source # 
VulkanMarshal VkImageSubresourceRange Source # 
CanWriteField "aspectMask" VkImageSubresourceRange Source # 
CanWriteField "baseArrayLayer" VkImageSubresourceRange Source # 
CanWriteField "baseMipLevel" VkImageSubresourceRange Source # 
CanWriteField "layerCount" VkImageSubresourceRange Source # 
CanWriteField "levelCount" VkImageSubresourceRange Source # 
CanReadField "aspectMask" VkImageSubresourceRange Source # 
CanReadField "baseArrayLayer" VkImageSubresourceRange Source # 
CanReadField "baseMipLevel" VkImageSubresourceRange Source # 
CanReadField "layerCount" VkImageSubresourceRange Source # 
CanReadField "levelCount" VkImageSubresourceRange Source # 
HasField "aspectMask" VkImageSubresourceRange Source # 
HasField "baseArrayLayer" VkImageSubresourceRange Source # 

Associated Types

type FieldType ("baseArrayLayer" :: Symbol) VkImageSubresourceRange :: Type Source #

type FieldOptional ("baseArrayLayer" :: Symbol) VkImageSubresourceRange :: Bool Source #

type FieldOffset ("baseArrayLayer" :: Symbol) VkImageSubresourceRange :: Nat Source #

type FieldIsArray ("baseArrayLayer" :: Symbol) VkImageSubresourceRange :: Bool Source #

HasField "baseMipLevel" VkImageSubresourceRange Source # 

Associated Types

type FieldType ("baseMipLevel" :: Symbol) VkImageSubresourceRange :: Type Source #

type FieldOptional ("baseMipLevel" :: Symbol) VkImageSubresourceRange :: Bool Source #

type FieldOffset ("baseMipLevel" :: Symbol) VkImageSubresourceRange :: Nat Source #

type FieldIsArray ("baseMipLevel" :: Symbol) VkImageSubresourceRange :: Bool Source #

HasField "layerCount" VkImageSubresourceRange Source # 
HasField "levelCount" VkImageSubresourceRange Source # 
type StructFields VkImageSubresourceRange Source # 
type StructFields VkImageSubresourceRange = (:) Symbol "aspectMask" ((:) Symbol "baseMipLevel" ((:) Symbol "levelCount" ((:) Symbol "baseArrayLayer" ((:) Symbol "layerCount" ([] Symbol)))))
type CUnionType VkImageSubresourceRange Source # 
type ReturnedOnly VkImageSubresourceRange Source # 
type StructExtends VkImageSubresourceRange Source # 
type FieldType "aspectMask" VkImageSubresourceRange Source # 
type FieldType "baseArrayLayer" VkImageSubresourceRange Source # 
type FieldType "baseArrayLayer" VkImageSubresourceRange = Word32
type FieldType "baseMipLevel" VkImageSubresourceRange Source # 
type FieldType "layerCount" VkImageSubresourceRange Source # 
type FieldType "levelCount" VkImageSubresourceRange Source # 
type FieldOptional "aspectMask" VkImageSubresourceRange Source # 
type FieldOptional "baseArrayLayer" VkImageSubresourceRange Source # 
type FieldOptional "baseMipLevel" VkImageSubresourceRange Source # 
type FieldOptional "layerCount" VkImageSubresourceRange Source # 
type FieldOptional "levelCount" VkImageSubresourceRange Source # 
type FieldOffset "aspectMask" VkImageSubresourceRange Source # 
type FieldOffset "aspectMask" VkImageSubresourceRange = 0
type FieldOffset "baseArrayLayer" VkImageSubresourceRange Source # 
type FieldOffset "baseArrayLayer" VkImageSubresourceRange = 12
type FieldOffset "baseMipLevel" VkImageSubresourceRange Source # 
type FieldOffset "baseMipLevel" VkImageSubresourceRange = 4
type FieldOffset "layerCount" VkImageSubresourceRange Source # 
type FieldOffset "layerCount" VkImageSubresourceRange = 16
type FieldOffset "levelCount" VkImageSubresourceRange Source # 
type FieldOffset "levelCount" VkImageSubresourceRange = 8
type FieldIsArray "aspectMask" VkImageSubresourceRange Source # 
type FieldIsArray "baseArrayLayer" VkImageSubresourceRange Source # 
type FieldIsArray "baseMipLevel" VkImageSubresourceRange Source # 
type FieldIsArray "layerCount" VkImageSubresourceRange Source # 
type FieldIsArray "levelCount" VkImageSubresourceRange Source # 

data VkImageSwapchainCreateInfoKHR Source #

typedef struct VkImageSwapchainCreateInfoKHR {
    VkStructureType sType;
    const void*                      pNext;
    VkSwapchainKHR   swapchain;
} VkImageSwapchainCreateInfoKHR;

VkImageSwapchainCreateInfoKHR registry at www.khronos.org

Instances

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

data VkImageViewCreateInfo Source #

typedef struct VkImageViewCreateInfo {
    VkStructureType sType;
    const void*            pNext;
    VkImageViewCreateFlags flags;
    VkImage                image;
    VkImageViewType        viewType;
    VkFormat               format;
    VkComponentMapping     components;
    VkImageSubresourceRange subresourceRange;
} VkImageViewCreateInfo;

VkImageViewCreateInfo registry at www.khronos.org

Instances

Eq VkImageViewCreateInfo Source # 
Ord VkImageViewCreateInfo Source # 
Show VkImageViewCreateInfo Source # 
Storable VkImageViewCreateInfo Source # 
VulkanMarshalPrim VkImageViewCreateInfo Source # 
VulkanMarshal VkImageViewCreateInfo Source # 
CanWriteField "components" VkImageViewCreateInfo Source # 
CanWriteField "flags" VkImageViewCreateInfo Source # 
CanWriteField "format" VkImageViewCreateInfo Source # 
CanWriteField "image" VkImageViewCreateInfo Source # 
CanWriteField "pNext" VkImageViewCreateInfo Source # 
CanWriteField "sType" VkImageViewCreateInfo Source # 
CanWriteField "subresourceRange" VkImageViewCreateInfo Source # 
CanWriteField "viewType" VkImageViewCreateInfo Source # 
CanReadField "components" VkImageViewCreateInfo Source # 
CanReadField "flags" VkImageViewCreateInfo Source # 
CanReadField "format" VkImageViewCreateInfo Source # 
CanReadField "image" VkImageViewCreateInfo Source # 
CanReadField "pNext" VkImageViewCreateInfo Source # 
CanReadField "sType" VkImageViewCreateInfo Source # 
CanReadField "subresourceRange" VkImageViewCreateInfo Source # 
CanReadField "viewType" VkImageViewCreateInfo Source # 
HasField "components" VkImageViewCreateInfo Source # 
HasField "flags" VkImageViewCreateInfo Source # 
HasField "format" VkImageViewCreateInfo Source # 
HasField "image" VkImageViewCreateInfo Source # 
HasField "pNext" VkImageViewCreateInfo Source # 
HasField "sType" VkImageViewCreateInfo Source # 
HasField "subresourceRange" VkImageViewCreateInfo Source # 

Associated Types

type FieldType ("subresourceRange" :: Symbol) VkImageViewCreateInfo :: Type Source #

type FieldOptional ("subresourceRange" :: Symbol) VkImageViewCreateInfo :: Bool Source #

type FieldOffset ("subresourceRange" :: Symbol) VkImageViewCreateInfo :: Nat Source #

type FieldIsArray ("subresourceRange" :: Symbol) VkImageViewCreateInfo :: Bool Source #

HasField "viewType" VkImageViewCreateInfo Source # 
type StructFields VkImageViewCreateInfo Source # 
type StructFields VkImageViewCreateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "flags" ((:) Symbol "image" ((:) Symbol "viewType" ((:) Symbol "format" ((:) Symbol "components" ((:) Symbol "subresourceRange" ([] Symbol))))))))
type CUnionType VkImageViewCreateInfo Source # 
type ReturnedOnly VkImageViewCreateInfo Source # 
type StructExtends VkImageViewCreateInfo Source # 
type FieldType "components" VkImageViewCreateInfo Source # 
type FieldType "flags" VkImageViewCreateInfo Source # 
type FieldType "format" VkImageViewCreateInfo Source # 
type FieldType "image" VkImageViewCreateInfo Source # 
type FieldType "pNext" VkImageViewCreateInfo Source # 
type FieldType "sType" VkImageViewCreateInfo Source # 
type FieldType "subresourceRange" VkImageViewCreateInfo Source # 
type FieldType "viewType" VkImageViewCreateInfo Source # 
type FieldOptional "components" VkImageViewCreateInfo Source # 
type FieldOptional "flags" VkImageViewCreateInfo Source # 
type FieldOptional "format" VkImageViewCreateInfo Source # 
type FieldOptional "image" VkImageViewCreateInfo Source # 
type FieldOptional "pNext" VkImageViewCreateInfo Source # 
type FieldOptional "sType" VkImageViewCreateInfo Source # 
type FieldOptional "subresourceRange" VkImageViewCreateInfo Source # 
type FieldOptional "subresourceRange" VkImageViewCreateInfo = False
type FieldOptional "viewType" VkImageViewCreateInfo Source # 
type FieldOffset "components" VkImageViewCreateInfo Source # 
type FieldOffset "components" VkImageViewCreateInfo = 40
type FieldOffset "flags" VkImageViewCreateInfo Source # 
type FieldOffset "format" VkImageViewCreateInfo Source # 
type FieldOffset "image" VkImageViewCreateInfo Source # 
type FieldOffset "pNext" VkImageViewCreateInfo Source # 
type FieldOffset "sType" VkImageViewCreateInfo Source # 
type FieldOffset "subresourceRange" VkImageViewCreateInfo Source # 
type FieldOffset "subresourceRange" VkImageViewCreateInfo = 56
type FieldOffset "viewType" VkImageViewCreateInfo Source # 
type FieldOffset "viewType" VkImageViewCreateInfo = 32
type FieldIsArray "components" VkImageViewCreateInfo Source # 
type FieldIsArray "flags" VkImageViewCreateInfo Source # 
type FieldIsArray "format" VkImageViewCreateInfo Source # 
type FieldIsArray "image" VkImageViewCreateInfo Source # 
type FieldIsArray "pNext" VkImageViewCreateInfo Source # 
type FieldIsArray "sType" VkImageViewCreateInfo Source # 
type FieldIsArray "subresourceRange" VkImageViewCreateInfo Source # 
type FieldIsArray "subresourceRange" VkImageViewCreateInfo = False
type FieldIsArray "viewType" VkImageViewCreateInfo Source # 

data VkImageViewUsageCreateInfo Source #

typedef struct VkImageViewUsageCreateInfo {
    VkStructureType sType;
    const void* pNext;
    VkImageUsageFlags usage;
} VkImageViewUsageCreateInfo;

VkImageViewUsageCreateInfo registry at www.khronos.org

Instances

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

data VkMemoryAllocateFlagsInfo Source #

typedef struct VkMemoryAllocateFlagsInfo {
    VkStructureType sType;
    const void*                      pNext;
    VkMemoryAllocateFlags flags;
    uint32_t                         deviceMask;
} VkMemoryAllocateFlagsInfo;

VkMemoryAllocateFlagsInfo registry at www.khronos.org

Instances

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

data VkMemoryAllocateInfo Source #

typedef struct VkMemoryAllocateInfo {
    VkStructureType sType;
    const void*            pNext;
    VkDeviceSize           allocationSize;
    uint32_t               memoryTypeIndex;
} VkMemoryAllocateInfo;

VkMemoryAllocateInfo registry at www.khronos.org

Instances

Eq VkMemoryAllocateInfo Source # 
Ord VkMemoryAllocateInfo Source # 
Show VkMemoryAllocateInfo Source # 
Storable VkMemoryAllocateInfo Source # 
VulkanMarshalPrim VkMemoryAllocateInfo Source # 
VulkanMarshal VkMemoryAllocateInfo Source # 
CanWriteField "allocationSize" VkMemoryAllocateInfo Source # 
CanWriteField "memoryTypeIndex" VkMemoryAllocateInfo Source # 
CanWriteField "pNext" VkMemoryAllocateInfo Source # 
CanWriteField "sType" VkMemoryAllocateInfo Source # 
CanReadField "allocationSize" VkMemoryAllocateInfo Source # 
CanReadField "memoryTypeIndex" VkMemoryAllocateInfo Source # 
CanReadField "pNext" VkMemoryAllocateInfo Source # 
CanReadField "sType" VkMemoryAllocateInfo Source # 
HasField "allocationSize" VkMemoryAllocateInfo Source # 

Associated Types

type FieldType ("allocationSize" :: Symbol) VkMemoryAllocateInfo :: Type Source #

type FieldOptional ("allocationSize" :: Symbol) VkMemoryAllocateInfo :: Bool Source #

type FieldOffset ("allocationSize" :: Symbol) VkMemoryAllocateInfo :: Nat Source #

type FieldIsArray ("allocationSize" :: Symbol) VkMemoryAllocateInfo :: Bool Source #

HasField "memoryTypeIndex" VkMemoryAllocateInfo Source # 

Associated Types

type FieldType ("memoryTypeIndex" :: Symbol) VkMemoryAllocateInfo :: Type Source #

type FieldOptional ("memoryTypeIndex" :: Symbol) VkMemoryAllocateInfo :: Bool Source #

type FieldOffset ("memoryTypeIndex" :: Symbol) VkMemoryAllocateInfo :: Nat Source #

type FieldIsArray ("memoryTypeIndex" :: Symbol) VkMemoryAllocateInfo :: Bool Source #

HasField "pNext" VkMemoryAllocateInfo Source # 
HasField "sType" VkMemoryAllocateInfo Source # 
type StructFields VkMemoryAllocateInfo Source # 
type StructFields VkMemoryAllocateInfo = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "allocationSize" ((:) Symbol "memoryTypeIndex" ([] Symbol))))
type CUnionType VkMemoryAllocateInfo Source # 
type ReturnedOnly VkMemoryAllocateInfo Source # 
type StructExtends VkMemoryAllocateInfo Source # 
type FieldType "allocationSize" VkMemoryAllocateInfo Source # 
type FieldType "memoryTypeIndex" VkMemoryAllocateInfo Source # 
type FieldType "memoryTypeIndex" VkMemoryAllocateInfo = Word32
type FieldType "pNext" VkMemoryAllocateInfo Source # 
type FieldType "sType" VkMemoryAllocateInfo Source # 
type FieldOptional "allocationSize" VkMemoryAllocateInfo Source # 
type FieldOptional "allocationSize" VkMemoryAllocateInfo = False
type FieldOptional "memoryTypeIndex" VkMemoryAllocateInfo Source # 
type FieldOptional "memoryTypeIndex" VkMemoryAllocateInfo = False
type FieldOptional "pNext" VkMemoryAllocateInfo Source # 
type FieldOptional "sType" VkMemoryAllocateInfo Source # 
type FieldOffset "allocationSize" VkMemoryAllocateInfo Source # 
type FieldOffset "allocationSize" VkMemoryAllocateInfo = 16
type FieldOffset "memoryTypeIndex" VkMemoryAllocateInfo Source # 
type FieldOffset "memoryTypeIndex" VkMemoryAllocateInfo = 24
type FieldOffset "pNext" VkMemoryAllocateInfo Source # 
type FieldOffset "sType" VkMemoryAllocateInfo Source # 
type FieldIsArray "allocationSize" VkMemoryAllocateInfo Source # 
type FieldIsArray "allocationSize" VkMemoryAllocateInfo = False
type FieldIsArray "memoryTypeIndex" VkMemoryAllocateInfo Source # 
type FieldIsArray "memoryTypeIndex" VkMemoryAllocateInfo = False
type FieldIsArray "pNext" VkMemoryAllocateInfo Source # 
type FieldIsArray "sType" VkMemoryAllocateInfo Source # 

data VkMemoryBarrier Source #

typedef struct VkMemoryBarrier {
    VkStructureType sType;
    const void*            pNext;
    VkAccessFlags          srcAccessMask;
    VkAccessFlags          dstAccessMask;
} VkMemoryBarrier;

VkMemoryBarrier registry at www.khronos.org

Instances

Eq VkMemoryBarrier Source # 
Ord VkMemoryBarrier Source # 
Show VkMemoryBarrier Source # 
Storable VkMemoryBarrier Source # 
VulkanMarshalPrim VkMemoryBarrier Source # 
VulkanMarshal VkMemoryBarrier Source # 
CanWriteField "dstAccessMask" VkMemoryBarrier Source # 

Methods

writeField :: Ptr VkMemoryBarrier -> FieldType "dstAccessMask" VkMemoryBarrier -> IO () Source #

CanWriteField "pNext" VkMemoryBarrier Source # 
CanWriteField "sType" VkMemoryBarrier Source # 
CanWriteField "srcAccessMask" VkMemoryBarrier Source # 

Methods

writeField :: Ptr VkMemoryBarrier -> FieldType "srcAccessMask" VkMemoryBarrier -> IO () Source #

CanReadField "dstAccessMask" VkMemoryBarrier Source # 
CanReadField "pNext" VkMemoryBarrier Source # 
CanReadField "sType" VkMemoryBarrier Source # 
CanReadField "srcAccessMask" VkMemoryBarrier Source # 
HasField "dstAccessMask" VkMemoryBarrier Source # 

Associated Types

type FieldType ("dstAccessMask" :: Symbol) VkMemoryBarrier :: Type Source #

type FieldOptional ("dstAccessMask" :: Symbol) VkMemoryBarrier :: Bool Source #

type FieldOffset ("dstAccessMask" :: Symbol) VkMemoryBarrier :: Nat Source #

type FieldIsArray ("dstAccessMask" :: Symbol) VkMemoryBarrier :: Bool Source #

HasField "pNext" VkMemoryBarrier Source # 
HasField "sType" VkMemoryBarrier Source # 
HasField "srcAccessMask" VkMemoryBarrier Source # 

Associated Types

type FieldType ("srcAccessMask" :: Symbol) VkMemoryBarrier :: Type Source #

type FieldOptional ("srcAccessMask" :: Symbol) VkMemoryBarrier :: Bool Source #

type FieldOffset ("srcAccessMask" :: Symbol) VkMemoryBarrier :: Nat Source #

type FieldIsArray ("srcAccessMask" :: Symbol) VkMemoryBarrier :: Bool Source #

type StructFields VkMemoryBarrier Source # 
type StructFields VkMemoryBarrier = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "srcAccessMask" ((:) Symbol "dstAccessMask" ([] Symbol))))
type CUnionType VkMemoryBarrier Source # 
type ReturnedOnly VkMemoryBarrier Source # 
type StructExtends VkMemoryBarrier Source # 
type FieldType "dstAccessMask" VkMemoryBarrier Source # 
type FieldType "dstAccessMask" VkMemoryBarrier = VkAccessFlags
type FieldType "pNext" VkMemoryBarrier Source # 
type FieldType "sType" VkMemoryBarrier Source # 
type FieldType "srcAccessMask" VkMemoryBarrier Source # 
type FieldType "srcAccessMask" VkMemoryBarrier = VkAccessFlags
type FieldOptional "dstAccessMask" VkMemoryBarrier Source # 
type FieldOptional "dstAccessMask" VkMemoryBarrier = True
type FieldOptional "pNext" VkMemoryBarrier Source # 
type FieldOptional "sType" VkMemoryBarrier Source # 
type FieldOptional "srcAccessMask" VkMemoryBarrier Source # 
type FieldOptional "srcAccessMask" VkMemoryBarrier = True
type FieldOffset "dstAccessMask" VkMemoryBarrier Source # 
type FieldOffset "dstAccessMask" VkMemoryBarrier = 20
type FieldOffset "pNext" VkMemoryBarrier Source # 
type FieldOffset "pNext" VkMemoryBarrier = 8
type FieldOffset "sType" VkMemoryBarrier Source # 
type FieldOffset "sType" VkMemoryBarrier = 0
type FieldOffset "srcAccessMask" VkMemoryBarrier Source # 
type FieldOffset "srcAccessMask" VkMemoryBarrier = 16
type FieldIsArray "dstAccessMask" VkMemoryBarrier Source # 
type FieldIsArray "dstAccessMask" VkMemoryBarrier = False
type FieldIsArray "pNext" VkMemoryBarrier Source # 
type FieldIsArray "sType" VkMemoryBarrier Source # 
type FieldIsArray "srcAccessMask" VkMemoryBarrier Source # 
type FieldIsArray "srcAccessMask" VkMemoryBarrier = False

data VkMemoryDedicatedAllocateInfo Source #

typedef struct VkMemoryDedicatedAllocateInfo {
    VkStructureType sType;
    const void*                      pNext;
    VkImage          image;
    VkBuffer         buffer;
} VkMemoryDedicatedAllocateInfo;

VkMemoryDedicatedAllocateInfo registry at www.khronos.org

Instances

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

data VkMemoryDedicatedRequirements Source #

typedef struct VkMemoryDedicatedRequirements {
    VkStructureType sType;
    void*                            pNext;
    VkBool32                         prefersDedicatedAllocation;
    VkBool32                         requiresDedicatedAllocation;
} VkMemoryDedicatedRequirements;

VkMemoryDedicatedRequirements registry at www.khronos.org

Instances

Eq VkMemoryDedicatedRequirements Source # 
Ord VkMemoryDedicatedRequirements Source # 
Show VkMemoryDedicatedRequirements Source # 
Storable VkMemoryDedicatedRequirements Source # 
VulkanMarshalPrim VkMemoryDedicatedRequirements Source # 
VulkanMarshal VkMemoryDedicatedRequirements Source # 
CanWriteField "pNext" VkMemoryDedicatedRequirements Source # 
CanWriteField "prefersDedicatedAllocation" VkMemoryDedicatedRequirements Source # 
CanWriteField "requiresDedicatedAllocation" VkMemoryDedicatedRequirements Source # 
CanWriteField "sType" VkMemoryDedicatedRequirements Source # 
CanReadField "pNext" VkMemoryDedicatedRequirements Source # 
CanReadField "prefersDedicatedAllocation" VkMemoryDedicatedRequirements Source # 
CanReadField "requiresDedicatedAllocation" VkMemoryDedicatedRequirements Source # 
CanReadField "sType" VkMemoryDedicatedRequirements Source # 
HasField "pNext" VkMemoryDedicatedRequirements Source # 
HasField "prefersDedicatedAllocation" VkMemoryDedicatedRequirements Source # 

Associated Types

type FieldType ("prefersDedicatedAllocation" :: Symbol) VkMemoryDedicatedRequirements :: Type Source #

type FieldOptional ("prefersDedicatedAllocation" :: Symbol) VkMemoryDedicatedRequirements :: Bool Source #

type FieldOffset ("prefersDedicatedAllocation" :: Symbol) VkMemoryDedicatedRequirements :: Nat Source #

type FieldIsArray ("prefersDedicatedAllocation" :: Symbol) VkMemoryDedicatedRequirements :: Bool Source #

HasField "requiresDedicatedAllocation" VkMemoryDedicatedRequirements Source # 

Associated Types

type FieldType ("requiresDedicatedAllocation" :: Symbol) VkMemoryDedicatedRequirements :: Type Source #

type FieldOptional ("requiresDedicatedAllocation" :: Symbol) VkMemoryDedicatedRequirements :: Bool Source #

type FieldOffset ("requiresDedicatedAllocation" :: Symbol) VkMemoryDedicatedRequirements :: Nat Source #

type FieldIsArray ("requiresDedicatedAllocation" :: Symbol) VkMemoryDedicatedRequirements :: Bool Source #

HasField "sType" VkMemoryDedicatedRequirements Source # 
type StructFields VkMemoryDedicatedRequirements Source # 
type StructFields VkMemoryDedicatedRequirements = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "prefersDedicatedAllocation" ((:) Symbol "requiresDedicatedAllocation" ([] Symbol))))
type CUnionType VkMemoryDedicatedRequirements Source # 
type ReturnedOnly VkMemoryDedicatedRequirements Source # 
type StructExtends VkMemoryDedicatedRequirements Source # 
type FieldType "pNext" VkMemoryDedicatedRequirements Source # 
type FieldType "prefersDedicatedAllocation" VkMemoryDedicatedRequirements Source # 
type FieldType "prefersDedicatedAllocation" VkMemoryDedicatedRequirements = VkBool32
type FieldType "requiresDedicatedAllocation" VkMemoryDedicatedRequirements Source # 
type FieldType "requiresDedicatedAllocation" VkMemoryDedicatedRequirements = VkBool32
type FieldType "sType" VkMemoryDedicatedRequirements Source # 
type FieldOptional "pNext" VkMemoryDedicatedRequirements Source # 
type FieldOptional "prefersDedicatedAllocation" VkMemoryDedicatedRequirements Source # 
type FieldOptional "prefersDedicatedAllocation" VkMemoryDedicatedRequirements = False
type FieldOptional "requiresDedicatedAllocation" VkMemoryDedicatedRequirements Source # 
type FieldOptional "requiresDedicatedAllocation" VkMemoryDedicatedRequirements = False
type FieldOptional "sType" VkMemoryDedicatedRequirements Source # 
type FieldOffset "pNext" VkMemoryDedicatedRequirements Source # 
type FieldOffset "prefersDedicatedAllocation" VkMemoryDedicatedRequirements Source # 
type FieldOffset "prefersDedicatedAllocation" VkMemoryDedicatedRequirements = 16
type FieldOffset "requiresDedicatedAllocation" VkMemoryDedicatedRequirements Source # 
type FieldOffset "requiresDedicatedAllocation" VkMemoryDedicatedRequirements = 20
type FieldOffset "sType" VkMemoryDedicatedRequirements Source # 
type FieldIsArray "pNext" VkMemoryDedicatedRequirements Source # 
type FieldIsArray "prefersDedicatedAllocation" VkMemoryDedicatedRequirements Source # 
type FieldIsArray "prefersDedicatedAllocation" VkMemoryDedicatedRequirements = False
type FieldIsArray "requiresDedicatedAllocation" VkMemoryDedicatedRequirements Source # 
type FieldIsArray "requiresDedicatedAllocation" VkMemoryDedicatedRequirements = False
type FieldIsArray "sType" VkMemoryDedicatedRequirements Source # 

data VkMemoryFdPropertiesKHR Source #

typedef struct VkMemoryFdPropertiesKHR {
    VkStructureType sType;
    void*                            pNext;
    uint32_t                         memoryTypeBits;
} VkMemoryFdPropertiesKHR;

VkMemoryFdPropertiesKHR registry at www.khronos.org

Instances

Eq VkMemoryFdPropertiesKHR Source # 
Ord VkMemoryFdPropertiesKHR Source # 
Show VkMemoryFdPropertiesKHR Source # 
Storable VkMemoryFdPropertiesKHR Source # 
VulkanMarshalPrim VkMemoryFdPropertiesKHR Source # 
VulkanMarshal VkMemoryFdPropertiesKHR Source # 
CanWriteField "memoryTypeBits" VkMemoryFdPropertiesKHR Source # 
CanWriteField "pNext" VkMemoryFdPropertiesKHR Source # 
CanWriteField "sType" VkMemoryFdPropertiesKHR Source # 
CanReadField "memoryTypeBits" VkMemoryFdPropertiesKHR Source # 
CanReadField "pNext" VkMemoryFdPropertiesKHR Source # 
CanReadField "sType" VkMemoryFdPropertiesKHR Source # 
HasField "memoryTypeBits" VkMemoryFdPropertiesKHR Source # 

Associated Types

type FieldType ("memoryTypeBits" :: Symbol) VkMemoryFdPropertiesKHR :: Type Source #

type FieldOptional ("memoryTypeBits" :: Symbol) VkMemoryFdPropertiesKHR :: Bool Source #

type FieldOffset ("memoryTypeBits" :: Symbol) VkMemoryFdPropertiesKHR :: Nat Source #

type FieldIsArray ("memoryTypeBits" :: Symbol) VkMemoryFdPropertiesKHR :: Bool Source #

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

data VkMemoryGetFdInfoKHR Source #

typedef struct VkMemoryGetFdInfoKHR {
    VkStructureType sType;
    const void*                      pNext;
    VkDeviceMemory                   memory;
    VkExternalMemoryHandleTypeFlagBits handleType;
} VkMemoryGetFdInfoKHR;

VkMemoryGetFdInfoKHR registry at www.khronos.org

Instances

Eq VkMemoryGetFdInfoKHR Source # 
Ord VkMemoryGetFdInfoKHR Source # 
Show VkMemoryGetFdInfoKHR Source # 
Storable VkMemoryGetFdInfoKHR Source # 
VulkanMarshalPrim VkMemoryGetFdInfoKHR Source # 
VulkanMarshal VkMemoryGetFdInfoKHR Source # 
CanWriteField "handleType" VkMemoryGetFdInfoKHR Source # 
CanWriteField "memory" VkMemoryGetFdInfoKHR Source # 
CanWriteField "pNext" VkMemoryGetFdInfoKHR Source # 
CanWriteField "sType" VkMemoryGetFdInfoKHR Source # 
CanReadField "handleType" VkMemoryGetFdInfoKHR Source # 
CanReadField "memory" VkMemoryGetFdInfoKHR Source # 
CanReadField "pNext" VkMemoryGetFdInfoKHR Source # 
CanReadField "sType" VkMemoryGetFdInfoKHR Source # 
HasField "handleType" VkMemoryGetFdInfoKHR Source # 

Associated Types

type FieldType ("handleType" :: Symbol) VkMemoryGetFdInfoKHR :: Type Source #

type FieldOptional ("handleType" :: Symbol) VkMemoryGetFdInfoKHR :: Bool Source #

type FieldOffset ("handleType" :: Symbol) VkMemoryGetFdInfoKHR :: Nat Source #

type FieldIsArray ("handleType" :: Symbol) VkMemoryGetFdInfoKHR :: Bool Source #

HasField "memory" VkMemoryGetFdInfoKHR Source # 
HasField "pNext" VkMemoryGetFdInfoKHR Source # 
HasField "sType" VkMemoryGetFdInfoKHR Source # 
type StructFields VkMemoryGetFdInfoKHR Source # 
type StructFields VkMemoryGetFdInfoKHR = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "memory" ((:) Symbol "handleType" ([] Symbol))))
type CUnionType VkMemoryGetFdInfoKHR Source # 
type ReturnedOnly VkMemoryGetFdInfoKHR Source # 
type StructExtends VkMemoryGetFdInfoKHR Source # 
type FieldType "handleType" VkMemoryGetFdInfoKHR Source # 
type FieldType "memory" VkMemoryGetFdInfoKHR Source # 
type FieldType "pNext" VkMemoryGetFdInfoKHR Source # 
type FieldType "sType" VkMemoryGetFdInfoKHR Source # 
type FieldOptional "handleType" VkMemoryGetFdInfoKHR Source # 
type FieldOptional "memory" VkMemoryGetFdInfoKHR Source # 
type FieldOptional "pNext" VkMemoryGetFdInfoKHR Source # 
type FieldOptional "sType" VkMemoryGetFdInfoKHR Source # 
type FieldOffset "handleType" VkMemoryGetFdInfoKHR Source # 
type FieldOffset "handleType" VkMemoryGetFdInfoKHR = 24
type FieldOffset "memory" VkMemoryGetFdInfoKHR Source # 
type FieldOffset "pNext" VkMemoryGetFdInfoKHR Source # 
type FieldOffset "sType" VkMemoryGetFdInfoKHR Source # 
type FieldIsArray "handleType" VkMemoryGetFdInfoKHR Source # 
type FieldIsArray "memory" VkMemoryGetFdInfoKHR Source # 
type FieldIsArray "pNext" VkMemoryGetFdInfoKHR Source # 
type FieldIsArray "sType" VkMemoryGetFdInfoKHR Source # 

data VkMemoryHeap Source #

typedef struct VkMemoryHeap {
    VkDeviceSize           size;
    VkMemoryHeapFlags      flags;
} VkMemoryHeap;

VkMemoryHeap registry at www.khronos.org

Instances

Eq VkMemoryHeap Source # 
Ord VkMemoryHeap Source # 
Show VkMemoryHeap Source # 
Storable VkMemoryHeap Source # 
VulkanMarshalPrim VkMemoryHeap Source # 
VulkanMarshal VkMemoryHeap Source # 
CanWriteField "flags" VkMemoryHeap Source # 
CanWriteField "size" VkMemoryHeap Source # 
CanReadField "flags" VkMemoryHeap Source # 
CanReadField "size" VkMemoryHeap Source # 
HasField "flags" VkMemoryHeap Source # 

Associated Types

type FieldType ("flags" :: Symbol) VkMemoryHeap :: Type Source #

type FieldOptional ("flags" :: Symbol) VkMemoryHeap :: Bool Source #

type FieldOffset ("flags" :: Symbol) VkMemoryHeap :: Nat Source #

type FieldIsArray ("flags" :: Symbol) VkMemoryHeap :: Bool Source #

HasField "size" VkMemoryHeap Source # 
type StructFields VkMemoryHeap Source # 
type StructFields VkMemoryHeap = (:) Symbol "size" ((:) Symbol "flags" ([] Symbol))
type CUnionType VkMemoryHeap Source # 
type ReturnedOnly VkMemoryHeap Source # 
type StructExtends VkMemoryHeap Source # 
type FieldType "flags" VkMemoryHeap Source # 
type FieldType "size" VkMemoryHeap Source # 
type FieldOptional "flags" VkMemoryHeap Source # 
type FieldOptional "size" VkMemoryHeap Source # 
type FieldOffset "flags" VkMemoryHeap Source # 
type FieldOffset "flags" VkMemoryHeap = 8
type FieldOffset "size" VkMemoryHeap Source # 
type FieldOffset "size" VkMemoryHeap = 0
type FieldIsArray "flags" VkMemoryHeap Source # 
type FieldIsArray "size" VkMemoryHeap Source # 

data VkMemoryHostPointerPropertiesEXT Source #

typedef struct VkMemoryHostPointerPropertiesEXT {
    VkStructureType sType;
    void* pNext;
    uint32_t memoryTypeBits;
} VkMemoryHostPointerPropertiesEXT;

VkMemoryHostPointerPropertiesEXT registry at www.khronos.org

Instances

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

data VkMemoryRequirements Source #

typedef struct VkMemoryRequirements {
    VkDeviceSize           size;
    VkDeviceSize           alignment;
    uint32_t               memoryTypeBits;
} VkMemoryRequirements;

VkMemoryRequirements registry at www.khronos.org

Instances

Eq VkMemoryRequirements Source # 
Ord VkMemoryRequirements Source # 
Show VkMemoryRequirements Source # 
Storable VkMemoryRequirements Source # 
VulkanMarshalPrim VkMemoryRequirements Source # 
VulkanMarshal VkMemoryRequirements Source # 
CanWriteField "alignment" VkMemoryRequirements Source # 
CanWriteField "memoryTypeBits" VkMemoryRequirements Source # 
CanWriteField "size" VkMemoryRequirements Source # 
CanReadField "alignment" VkMemoryRequirements Source # 
CanReadField "memoryTypeBits" VkMemoryRequirements Source # 
CanReadField "size" VkMemoryRequirements Source # 
HasField "alignment" VkMemoryRequirements Source # 
HasField "memoryTypeBits" VkMemoryRequirements Source # 

Associated Types

type FieldType ("memoryTypeBits" :: Symbol) VkMemoryRequirements :: Type Source #

type FieldOptional ("memoryTypeBits" :: Symbol) VkMemoryRequirements :: Bool Source #

type FieldOffset ("memoryTypeBits" :: Symbol) VkMemoryRequirements :: Nat Source #

type FieldIsArray ("memoryTypeBits" :: Symbol) VkMemoryRequirements :: Bool Source #

HasField "size" VkMemoryRequirements Source # 
type StructFields VkMemoryRequirements Source # 
type StructFields VkMemoryRequirements = (:) Symbol "size" ((:) Symbol "alignment" ((:) Symbol "memoryTypeBits" ([] Symbol)))
type CUnionType VkMemoryRequirements Source # 
type ReturnedOnly VkMemoryRequirements Source # 
type StructExtends VkMemoryRequirements Source # 
type FieldType "alignment" VkMemoryRequirements Source # 
type FieldType "memoryTypeBits" VkMemoryRequirements Source # 
type FieldType "memoryTypeBits" VkMemoryRequirements = Word32
type FieldType "size" VkMemoryRequirements Source # 
type FieldOptional "alignment" VkMemoryRequirements Source # 
type FieldOptional "memoryTypeBits" VkMemoryRequirements Source # 
type FieldOptional "memoryTypeBits" VkMemoryRequirements = False
type FieldOptional "size" VkMemoryRequirements Source # 
type FieldOffset "alignment" VkMemoryRequirements Source # 
type FieldOffset "alignment" VkMemoryRequirements = 8
type FieldOffset "memoryTypeBits" VkMemoryRequirements Source # 
type FieldOffset "memoryTypeBits" VkMemoryRequirements = 16
type FieldOffset "size" VkMemoryRequirements Source # 
type FieldIsArray "alignment" VkMemoryRequirements Source # 
type FieldIsArray "memoryTypeBits" VkMemoryRequirements Source # 
type FieldIsArray "memoryTypeBits" VkMemoryRequirements = False
type FieldIsArray "size" VkMemoryRequirements Source # 

data VkMemoryRequirements2 Source #

typedef struct VkMemoryRequirements2 {
    VkStructureType sType;
    void* pNext;
    VkMemoryRequirements                                                 memoryRequirements;
} VkMemoryRequirements2;

VkMemoryRequirements2 registry at www.khronos.org

Instances

Eq VkMemoryRequirements2 Source # 
Ord VkMemoryRequirements2 Source # 
Show VkMemoryRequirements2 Source # 
Storable VkMemoryRequirements2 Source # 
VulkanMarshalPrim VkMemoryRequirements2 Source # 
VulkanMarshal VkMemoryRequirements2 Source # 
CanWriteField "memoryRequirements" VkMemoryRequirements2 Source # 
CanWriteField "pNext" VkMemoryRequirements2 Source # 
CanWriteField "sType" VkMemoryRequirements2 Source # 
CanReadField "memoryRequirements" VkMemoryRequirements2 Source # 
CanReadField "pNext" VkMemoryRequirements2 Source # 
CanReadField "sType" VkMemoryRequirements2 Source # 
HasField "memoryRequirements" VkMemoryRequirements2 Source # 

Associated Types

type FieldType ("memoryRequirements" :: Symbol) VkMemoryRequirements2 :: Type Source #

type FieldOptional ("memoryRequirements" :: Symbol) VkMemoryRequirements2 :: Bool Source #

type FieldOffset ("memoryRequirements" :: Symbol) VkMemoryRequirements2 :: Nat Source #

type FieldIsArray ("memoryRequirements" :: Symbol) VkMemoryRequirements2 :: Bool Source #

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

data VkMemoryType Source #

typedef struct VkMemoryType {
    VkMemoryPropertyFlags  propertyFlags;
    uint32_t               heapIndex;
} VkMemoryType;

VkMemoryType registry at www.khronos.org

Instances

Eq VkMemoryType Source # 
Ord VkMemoryType Source # 
Show VkMemoryType Source # 
Storable VkMemoryType Source # 
VulkanMarshalPrim VkMemoryType Source # 
VulkanMarshal VkMemoryType Source # 
CanWriteField "heapIndex" VkMemoryType Source # 

Methods

writeField :: Ptr VkMemoryType -> FieldType "heapIndex" VkMemoryType -> IO () Source #

CanWriteField "propertyFlags" VkMemoryType Source # 

Methods

writeField :: Ptr VkMemoryType -> FieldType "propertyFlags" VkMemoryType -> IO () Source #

CanReadField "heapIndex" VkMemoryType Source # 
CanReadField "propertyFlags" VkMemoryType Source # 
HasField "heapIndex" VkMemoryType Source # 

Associated Types

type FieldType ("heapIndex" :: Symbol) VkMemoryType :: Type Source #

type FieldOptional ("heapIndex" :: Symbol) VkMemoryType :: Bool Source #

type FieldOffset ("heapIndex" :: Symbol) VkMemoryType :: Nat Source #

type FieldIsArray ("heapIndex" :: Symbol) VkMemoryType :: Bool Source #

HasField "propertyFlags" VkMemoryType Source # 

Associated Types

type FieldType ("propertyFlags" :: Symbol) VkMemoryType :: Type Source #

type FieldOptional ("propertyFlags" :: Symbol) VkMemoryType :: Bool Source #

type FieldOffset ("propertyFlags" :: Symbol) VkMemoryType :: Nat Source #

type FieldIsArray ("propertyFlags" :: Symbol) VkMemoryType :: Bool Source #

type StructFields VkMemoryType Source # 
type StructFields VkMemoryType = (:) Symbol "propertyFlags" ((:) Symbol "heapIndex" ([] Symbol))
type CUnionType VkMemoryType Source # 
type ReturnedOnly VkMemoryType Source # 
type StructExtends VkMemoryType Source # 
type FieldType "heapIndex" VkMemoryType Source # 
type FieldType "heapIndex" VkMemoryType = Word32
type FieldType "propertyFlags" VkMemoryType Source # 
type FieldOptional "heapIndex" VkMemoryType Source # 
type FieldOptional "heapIndex" VkMemoryType = False
type FieldOptional "propertyFlags" VkMemoryType Source # 
type FieldOptional "propertyFlags" VkMemoryType = True
type FieldOffset "heapIndex" VkMemoryType Source # 
type FieldOffset "heapIndex" VkMemoryType = 4
type FieldOffset "propertyFlags" VkMemoryType Source # 
type FieldOffset "propertyFlags" VkMemoryType = 0
type FieldIsArray "heapIndex" VkMemoryType Source # 
type FieldIsArray "heapIndex" VkMemoryType = False
type FieldIsArray "propertyFlags" VkMemoryType Source # 
type FieldIsArray "propertyFlags" VkMemoryType = False

newtype VkSampleCountBitmask a Source #

Instances

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

Methods

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

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

toConstr :: VkSampleCountBitmask a -> Constr #

dataTypeOf :: VkSampleCountBitmask a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

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

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

xor :: VkSampleCountBitmask FlagMask -> VkSampleCountBitmask FlagMask -> VkSampleCountBitmask FlagMask #

complement :: VkSampleCountBitmask FlagMask -> VkSampleCountBitmask FlagMask #

shift :: VkSampleCountBitmask FlagMask -> Int -> VkSampleCountBitmask FlagMask #

rotate :: VkSampleCountBitmask FlagMask -> Int -> VkSampleCountBitmask FlagMask #

zeroBits :: VkSampleCountBitmask FlagMask #

bit :: Int -> VkSampleCountBitmask FlagMask #

setBit :: VkSampleCountBitmask FlagMask -> Int -> VkSampleCountBitmask FlagMask #

clearBit :: VkSampleCountBitmask FlagMask -> Int -> VkSampleCountBitmask FlagMask #

complementBit :: VkSampleCountBitmask FlagMask -> Int -> VkSampleCountBitmask FlagMask #

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

bitSizeMaybe :: VkSampleCountBitmask FlagMask -> Maybe Int #

bitSize :: VkSampleCountBitmask FlagMask -> Int #

isSigned :: VkSampleCountBitmask FlagMask -> Bool #

shiftL :: VkSampleCountBitmask FlagMask -> Int -> VkSampleCountBitmask FlagMask #

unsafeShiftL :: VkSampleCountBitmask FlagMask -> Int -> VkSampleCountBitmask FlagMask #

shiftR :: VkSampleCountBitmask FlagMask -> Int -> VkSampleCountBitmask FlagMask #

unsafeShiftR :: VkSampleCountBitmask FlagMask -> Int -> VkSampleCountBitmask FlagMask #

rotateL :: VkSampleCountBitmask FlagMask -> Int -> VkSampleCountBitmask FlagMask #

rotateR :: VkSampleCountBitmask FlagMask -> Int -> VkSampleCountBitmask FlagMask #

popCount :: VkSampleCountBitmask FlagMask -> Int #

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

pattern VK_SAMPLE_COUNT_1_BIT :: forall a. VkSampleCountBitmask a Source #

Sample count 1 supported

bitpos = 0

pattern VK_SAMPLE_COUNT_2_BIT :: forall a. VkSampleCountBitmask a Source #

Sample count 2 supported

bitpos = 1

pattern VK_SAMPLE_COUNT_4_BIT :: forall a. VkSampleCountBitmask a Source #

Sample count 4 supported

bitpos = 2

pattern VK_SAMPLE_COUNT_8_BIT :: forall a. VkSampleCountBitmask a Source #

Sample count 8 supported

bitpos = 3

pattern VK_SAMPLE_COUNT_16_BIT :: forall a. VkSampleCountBitmask a Source #

Sample count 16 supported

bitpos = 4

pattern VK_SAMPLE_COUNT_32_BIT :: forall a. VkSampleCountBitmask a Source #

Sample count 32 supported

bitpos = 5

pattern VK_SAMPLE_COUNT_64_BIT :: forall a. VkSampleCountBitmask a Source #

Sample count 64 supported

bitpos = 6

newtype VkSharingMode Source #

Constructors

VkSharingMode Int32 

Instances

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

Methods

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

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

toConstr :: VkSharingMode -> Constr #

dataTypeOf :: VkSharingMode -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Associated Types

type Rep VkSharingMode :: * -> * #

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

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

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

type VK_NV_DEDICATED_ALLOCATION_EXTENSION_NAME = "VK_NV_dedicated_allocation" Source #