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

Safe HaskellNone
LanguageHaskell2010

Graphics.Vulkan.Ext.VK_AMD_texture_gather_bias_lod

Contents

Synopsis

Vulkan extension: VK_AMD_texture_gather_bias_lod

supported: vulkan

contact: Rex Xu amdrexu@

author: AMD

type: device

Extension number: 42

Required extensions: VK_KHR_get_physical_device_properties2.

Required extensions: VK_KHR_get_physical_device_properties2.

newtype VkBool32 Source #

Constructors

VkBool32 Word32 

Instances

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

Methods

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

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

toConstr :: VkBool32 -> Constr #

dataTypeOf :: VkBool32 -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Associated Types

type Rep VkBool32 :: * -> * #

Methods

from :: VkBool32 -> Rep VkBool32 x #

to :: Rep VkBool32 x -> VkBool32 #

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

newtype VkDeviceSize Source #

Constructors

VkDeviceSize Word64 

Instances

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

Methods

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

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

toConstr :: VkDeviceSize -> Constr #

dataTypeOf :: VkDeviceSize -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Associated Types

type Rep VkDeviceSize :: * -> * #

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

newtype VkFlags Source #

Constructors

VkFlags Word32 

Instances

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

Methods

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

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

Integral VkFlags Source # 
Data VkFlags Source # 

Methods

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

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

toConstr :: VkFlags -> Constr #

dataTypeOf :: VkFlags -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Associated Types

type Rep VkFlags :: * -> * #

Methods

from :: VkFlags -> Rep VkFlags x #

to :: Rep VkFlags x -> VkFlags #

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

newtype VkSampleMask Source #

Constructors

VkSampleMask Word32 

Instances

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

Methods

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

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

toConstr :: VkSampleMask -> Constr #

dataTypeOf :: VkSampleMask -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Associated Types

type Rep VkSampleMask :: * -> * #

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

data VkExtent2D Source #

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

VkExtent2D registry at www.khronos.org

Instances

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

Methods

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

CanWriteField "width" VkExtent2D Source # 

Methods

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

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

Associated Types

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

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

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

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

HasField "width" VkExtent2D Source # 

Associated Types

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

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

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

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

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

data VkExtent3D Source #

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

VkExtent3D registry at www.khronos.org

Instances

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

Methods

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

CanWriteField "height" VkExtent3D Source # 

Methods

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

CanWriteField "width" VkExtent3D Source # 

Methods

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

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

Associated Types

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

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

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

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

HasField "height" VkExtent3D Source # 

Associated Types

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

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

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

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

HasField "width" VkExtent3D Source # 

Associated Types

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

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

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

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

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

data VkImageBlit Source #

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

VkImageBlit registry at www.khronos.org

Instances

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

Methods

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

CanWriteField "srcSubresource" VkImageBlit Source # 

Methods

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

CanReadField "dstSubresource" VkImageBlit Source # 

Methods

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

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

CanReadField "srcSubresource" VkImageBlit Source # 

Methods

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

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

HasField "dstOffsets" VkImageBlit Source # 

Associated Types

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

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

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

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

HasField "dstSubresource" VkImageBlit Source # 

Associated Types

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

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

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

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

HasField "srcOffsets" VkImageBlit Source # 

Associated Types

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

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

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

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

HasField "srcSubresource" VkImageBlit Source # 

Associated Types

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

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

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

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

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

Methods

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

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

Methods

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

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

data VkImageCopy Source #

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

VkImageCopy registry at www.khronos.org

Instances

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

Methods

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

CanWriteField "dstSubresource" VkImageCopy Source # 

Methods

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

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

Methods

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

CanWriteField "srcSubresource" VkImageCopy Source # 

Methods

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

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

Methods

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

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

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

Methods

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

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

HasField "dstOffset" VkImageCopy Source # 

Associated Types

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

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

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

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

HasField "dstSubresource" VkImageCopy Source # 

Associated Types

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

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

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

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

HasField "extent" VkImageCopy Source # 

Associated Types

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

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

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

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

HasField "srcOffset" VkImageCopy Source # 

Associated Types

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

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

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

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

HasField "srcSubresource" VkImageCopy Source # 

Associated Types

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

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

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

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

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

data VkImageCreateInfo Source #

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

VkImageCreateInfo registry at www.khronos.org

Instances

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

Methods

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

CanWriteField "queueFamilyIndexCount" VkImageCreateInfo Source # 

Methods

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

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

Associated Types

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

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

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

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

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

Associated Types

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

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

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

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

HasField "initialLayout" VkImageCreateInfo Source # 

Associated Types

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

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

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

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

HasField "mipLevels" VkImageCreateInfo Source # 

Associated Types

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

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

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

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

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

Associated Types

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

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

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

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

HasField "queueFamilyIndexCount" VkImageCreateInfo Source # 

Associated Types

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

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

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

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

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

Associated Types

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

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

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

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

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

data VkImageFormatListCreateInfoKHR Source #

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

VkImageFormatListCreateInfoKHR registry at www.khronos.org

Instances

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

data VkImageFormatProperties Source #

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

VkImageFormatProperties registry at www.khronos.org

Instances

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

Associated Types

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

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

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

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

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

Associated Types

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

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

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

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

HasField "maxResourceSize" VkImageFormatProperties Source # 

Associated Types

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

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

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

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

HasField "sampleCounts" VkImageFormatProperties Source # 

Associated Types

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

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

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

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

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

data VkImageFormatProperties2 Source #

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

VkImageFormatProperties2 registry at www.khronos.org

Instances

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

Associated Types

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

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

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

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

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

data VkImageMemoryBarrier Source #

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

VkImageMemoryBarrier registry at www.khronos.org

Instances

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

Methods

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

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

Methods

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

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

Associated Types

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

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

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

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

HasField "dstQueueFamilyIndex" VkImageMemoryBarrier Source # 

Associated Types

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

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

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

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

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

Associated Types

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

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

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

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

HasField "srcQueueFamilyIndex" VkImageMemoryBarrier Source # 

Associated Types

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

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

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

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

HasField "subresourceRange" VkImageMemoryBarrier Source # 

Associated Types

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

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

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

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

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

data VkImageMemoryRequirementsInfo2 Source #

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

VkImageMemoryRequirementsInfo2 registry at www.khronos.org

Instances

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

data VkImagePlaneMemoryRequirementsInfo Source #

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

VkImagePlaneMemoryRequirementsInfo registry at www.khronos.org

Instances

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

data VkImageResolve Source #

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

VkImageResolve registry at www.khronos.org

Instances

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

Methods

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

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

Methods

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

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

Associated Types

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

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

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

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

HasField "dstSubresource" VkImageResolve Source # 

Associated Types

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

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

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

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

HasField "extent" VkImageResolve Source # 

Associated Types

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

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

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

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

HasField "srcOffset" VkImageResolve Source # 

Associated Types

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

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

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

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

HasField "srcSubresource" VkImageResolve Source # 

Associated Types

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

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

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

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

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

data VkImageSparseMemoryRequirementsInfo2 Source #

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

VkImageSparseMemoryRequirementsInfo2 registry at www.khronos.org

Instances

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

data VkImageSubresource Source #

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

VkImageSubresource registry at www.khronos.org

Instances

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

Associated Types

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

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

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

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

HasField "aspectMask" VkImageSubresource Source # 

Associated Types

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

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

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

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

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

data VkImageSubresourceLayers Source #

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

VkImageSubresourceLayers registry at www.khronos.org

Instances

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

Associated Types

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

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

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

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

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

data VkImageSubresourceRange Source #

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

VkImageSubresourceRange registry at www.khronos.org

Instances

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

Associated Types

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

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

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

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

HasField "baseMipLevel" VkImageSubresourceRange Source # 

Associated Types

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

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

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

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

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

data VkImageSwapchainCreateInfoKHR Source #

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

VkImageSwapchainCreateInfoKHR registry at www.khronos.org

Instances

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

data VkImageViewCreateInfo Source #

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

VkImageViewCreateInfo registry at www.khronos.org

Instances

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

Associated Types

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

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

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

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

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

data VkImageViewUsageCreateInfo Source #

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

VkImageViewUsageCreateInfo registry at www.khronos.org

Instances

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

newtype VkSampleCountBitmask a Source #

Instances

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

Methods

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

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

toConstr :: VkSampleCountBitmask a -> Constr #

dataTypeOf :: VkSampleCountBitmask a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

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

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

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

complement :: VkSampleCountBitmask FlagMask -> VkSampleCountBitmask FlagMask #

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

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

zeroBits :: VkSampleCountBitmask FlagMask #

bit :: Int -> VkSampleCountBitmask FlagMask #

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

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

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

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

bitSizeMaybe :: VkSampleCountBitmask FlagMask -> Maybe Int #

bitSize :: VkSampleCountBitmask FlagMask -> Int #

isSigned :: VkSampleCountBitmask FlagMask -> Bool #

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

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

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

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

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

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

popCount :: VkSampleCountBitmask FlagMask -> Int #

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

pattern VK_SAMPLE_COUNT_1_BIT :: forall a. VkSampleCountBitmask a Source #

Sample count 1 supported

bitpos = 0

pattern VK_SAMPLE_COUNT_2_BIT :: forall a. VkSampleCountBitmask a Source #

Sample count 2 supported

bitpos = 1

pattern VK_SAMPLE_COUNT_4_BIT :: forall a. VkSampleCountBitmask a Source #

Sample count 4 supported

bitpos = 2

pattern VK_SAMPLE_COUNT_8_BIT :: forall a. VkSampleCountBitmask a Source #

Sample count 8 supported

bitpos = 3

pattern VK_SAMPLE_COUNT_16_BIT :: forall a. VkSampleCountBitmask a Source #

Sample count 16 supported

bitpos = 4

pattern VK_SAMPLE_COUNT_32_BIT :: forall a. VkSampleCountBitmask a Source #

Sample count 32 supported

bitpos = 5

pattern VK_SAMPLE_COUNT_64_BIT :: forall a. VkSampleCountBitmask a Source #

Sample count 64 supported

bitpos = 6

newtype VkStructureType Source #

Structure type enumerant

type = enum

VkStructureType registry at www.khronos.org

Constructors

VkStructureType Int32 

Instances

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

Methods

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

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

toConstr :: VkStructureType -> Constr #

dataTypeOf :: VkStructureType -> DataType #

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

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

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

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

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

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

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

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

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

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

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

pattern VK_STRUCTURE_TYPE_LOADER_INSTANCE_CREATE_INFO :: VkStructureType Source #

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

pattern VK_STRUCTURE_TYPE_LOADER_DEVICE_CREATE_INFO :: VkStructureType Source #

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

data VkTextureLODGatherFormatPropertiesAMD Source #

typedef struct VkTextureLODGatherFormatPropertiesAMD {
    VkStructureType sType;
    void*                            pNext;
    VkBool32                         supportsTextureGatherLODBiasAMD;
} VkTextureLODGatherFormatPropertiesAMD;

VkTextureLODGatherFormatPropertiesAMD registry at www.khronos.org

Instances

Eq VkTextureLODGatherFormatPropertiesAMD Source # 
Ord VkTextureLODGatherFormatPropertiesAMD Source # 
Show VkTextureLODGatherFormatPropertiesAMD Source # 
Storable VkTextureLODGatherFormatPropertiesAMD Source # 
VulkanMarshalPrim VkTextureLODGatherFormatPropertiesAMD Source # 
VulkanMarshal VkTextureLODGatherFormatPropertiesAMD Source # 
CanWriteField "pNext" VkTextureLODGatherFormatPropertiesAMD Source # 
CanWriteField "sType" VkTextureLODGatherFormatPropertiesAMD Source # 
CanWriteField "supportsTextureGatherLODBiasAMD" VkTextureLODGatherFormatPropertiesAMD Source # 
CanReadField "pNext" VkTextureLODGatherFormatPropertiesAMD Source # 
CanReadField "sType" VkTextureLODGatherFormatPropertiesAMD Source # 
CanReadField "supportsTextureGatherLODBiasAMD" VkTextureLODGatherFormatPropertiesAMD Source # 
HasField "pNext" VkTextureLODGatherFormatPropertiesAMD Source # 
HasField "sType" VkTextureLODGatherFormatPropertiesAMD Source # 
HasField "supportsTextureGatherLODBiasAMD" VkTextureLODGatherFormatPropertiesAMD Source # 

Associated Types

type FieldType ("supportsTextureGatherLODBiasAMD" :: Symbol) VkTextureLODGatherFormatPropertiesAMD :: Type Source #

type FieldOptional ("supportsTextureGatherLODBiasAMD" :: Symbol) VkTextureLODGatherFormatPropertiesAMD :: Bool Source #

type FieldOffset ("supportsTextureGatherLODBiasAMD" :: Symbol) VkTextureLODGatherFormatPropertiesAMD :: Nat Source #

type FieldIsArray ("supportsTextureGatherLODBiasAMD" :: Symbol) VkTextureLODGatherFormatPropertiesAMD :: Bool Source #

type StructFields VkTextureLODGatherFormatPropertiesAMD Source # 
type StructFields VkTextureLODGatherFormatPropertiesAMD = (:) Symbol "sType" ((:) Symbol "pNext" ((:) Symbol "supportsTextureGatherLODBiasAMD" ([] Symbol)))
type CUnionType VkTextureLODGatherFormatPropertiesAMD Source # 
type ReturnedOnly VkTextureLODGatherFormatPropertiesAMD Source # 
type StructExtends VkTextureLODGatherFormatPropertiesAMD Source # 
type FieldType "pNext" VkTextureLODGatherFormatPropertiesAMD Source # 
type FieldType "sType" VkTextureLODGatherFormatPropertiesAMD Source # 
type FieldType "supportsTextureGatherLODBiasAMD" VkTextureLODGatherFormatPropertiesAMD Source # 
type FieldType "supportsTextureGatherLODBiasAMD" VkTextureLODGatherFormatPropertiesAMD = VkBool32
type FieldOptional "pNext" VkTextureLODGatherFormatPropertiesAMD Source # 
type FieldOptional "sType" VkTextureLODGatherFormatPropertiesAMD Source # 
type FieldOptional "supportsTextureGatherLODBiasAMD" VkTextureLODGatherFormatPropertiesAMD Source # 
type FieldOptional "supportsTextureGatherLODBiasAMD" VkTextureLODGatherFormatPropertiesAMD = False
type FieldOffset "pNext" VkTextureLODGatherFormatPropertiesAMD Source # 
type FieldOffset "sType" VkTextureLODGatherFormatPropertiesAMD Source # 
type FieldOffset "supportsTextureGatherLODBiasAMD" VkTextureLODGatherFormatPropertiesAMD Source # 
type FieldOffset "supportsTextureGatherLODBiasAMD" VkTextureLODGatherFormatPropertiesAMD = 16
type FieldIsArray "pNext" VkTextureLODGatherFormatPropertiesAMD Source # 
type FieldIsArray "sType" VkTextureLODGatherFormatPropertiesAMD Source # 
type FieldIsArray "supportsTextureGatherLODBiasAMD" VkTextureLODGatherFormatPropertiesAMD Source # 
type FieldIsArray "supportsTextureGatherLODBiasAMD" VkTextureLODGatherFormatPropertiesAMD = False

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

type VK_AMD_TEXTURE_GATHER_BIAS_LOD_EXTENSION_NAME = "VK_AMD_texture_gather_bias_lod" Source #