gpu-vulkan-0.1.0.161: Vulkan library
Safe HaskellNone
LanguageHaskell2010

Gpu.Vulkan.PhysicalDevice

Synopsis

ENUMERATE

enumerate :: I s -> IO [P] Source #

data P #

Instances

Instances details
Show P 
Instance details

Defined in Gpu.Vulkan.PhysicalDevice.Middle.Internal

Methods

showsPrec :: Int -> P -> ShowS #

show :: P -> String #

showList :: [P] -> ShowS #

PHYSICAL DEVICE PROPERTIES AND FEATURES

Get Properties 2

getFeatures2 :: forall (mn :: Maybe Type). ReadChain mn => P -> IO (Features2 mn) #

data Features2 (mn :: Maybe Type) #

Constructors

Features2 

Instances

Instances details
Show (M mn) => Show (Features2 mn) 
Instance details

Defined in Gpu.Vulkan.PhysicalDevice.Middle.Internal

Methods

showsPrec :: Int -> Features2 mn -> ShowS #

show :: Features2 mn -> String #

showList :: [Features2 mn] -> ShowS #

WithPoked (M mn) => WithPoked (Features2 mn) 
Instance details

Defined in Gpu.Vulkan.PhysicalDevice.Middle.Internal

Methods

withPoked' :: Features2 mn -> (forall s. PtrS s (Features2 mn) -> IO b) -> IO b #

OTHER PROPERTIES

newtype ExtensionName Source #

Constructors

ExtensionName 

Instances

Instances details
Show ExtensionName Source # 
Instance details

Defined in Gpu.Vulkan.PhysicalDevice

Eq ExtensionName Source # 
Instance details

Defined in Gpu.Vulkan.PhysicalDevice

OTHER FEATURES

EXTENSIONS

ENUM AND STRUCT

newtype Type #

Constructors

Type Word32 

Instances

Instances details
Storable Type 
Instance details

Defined in Gpu.Vulkan.PhysicalDevice.Enum

Methods

sizeOf :: Type -> Int #

alignment :: Type -> Int #

peekElemOff :: Ptr Type -> Int -> IO Type #

pokeElemOff :: Ptr Type -> Int -> Type -> IO () #

peekByteOff :: Ptr b -> Int -> IO Type #

pokeByteOff :: Ptr b -> Int -> Type -> IO () #

peek :: Ptr Type -> IO Type #

poke :: Ptr Type -> Type -> IO () #

Show Type 
Instance details

Defined in Gpu.Vulkan.PhysicalDevice.Enum

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

Eq Type 
Instance details

Defined in Gpu.Vulkan.PhysicalDevice.Enum

Methods

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

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

pattern TypeMaxEnum :: Type #

pattern TypeCpu :: Type #

pattern TypeVirtualGpu :: Type #

pattern TypeOther :: Type #

data Limits #

Constructors

Limits 

Fields

Instances

Instances details
Show Limits 
Instance details

Defined in Gpu.Vulkan.PhysicalDevice.Struct

data Features #

Constructors

Features 

Fields

Instances

Instances details
Default Features 
Instance details

Defined in Gpu.Vulkan.PhysicalDevice.Struct

Methods

def :: Features #

Show Features 
Instance details

Defined in Gpu.Vulkan.PhysicalDevice.Struct

data Vulkan12Features (mn :: Maybe Type) #

Constructors

Vulkan12Features 

Fields

Instances

Instances details
Nextable Vulkan12Features 
Instance details

Defined in Gpu.Vulkan.PhysicalDevice.Struct

Methods

nextableSize :: Int #

nextableType :: StructureType #

nextPtr :: Ptr () -> IO (Ptr ()) #

createNextable :: forall (mn' :: Maybe Type). Ptr () -> M mn' -> IO (Vulkan12Features mn') #

Show (M mn) => Show (Vulkan12Features mn) 
Instance details

Defined in Gpu.Vulkan.PhysicalDevice.Struct

WithPoked (M mn) => WithPoked (Vulkan12Features mn) 
Instance details

Defined in Gpu.Vulkan.PhysicalDevice.Struct

Methods

withPoked' :: Vulkan12Features mn -> (forall s. PtrS s (Vulkan12Features mn) -> IO b) -> IO b #

data Vulkan12FeaturesNoNext #

Constructors

Vulkan12FeaturesNoNext 

Fields

vulkan12FeaturesZero :: forall (mn :: Maybe Type). M mn -> Vulkan12Features mn #

data Vulkan13Features (mn :: Maybe Type) #

Instances

Instances details
Nextable Vulkan13Features 
Instance details

Defined in Gpu.Vulkan.PhysicalDevice.Struct

Methods

nextableSize :: Int #

nextableType :: StructureType #

nextPtr :: Ptr () -> IO (Ptr ()) #

createNextable :: forall (mn' :: Maybe Type). Ptr () -> M mn' -> IO (Vulkan13Features mn') #

Show (M mn) => Show (Vulkan13Features mn) 
Instance details

Defined in Gpu.Vulkan.PhysicalDevice.Struct

WithPoked (M mn) => WithPoked (Vulkan13Features mn) 
Instance details

Defined in Gpu.Vulkan.PhysicalDevice.Struct

Methods

withPoked' :: Vulkan13Features mn -> (forall s. PtrS s (Vulkan13Features mn) -> IO b) -> IO b #

data Vulkan13FeaturesNoNext #

vulkan13FeaturesZero :: forall (mn :: Maybe Type). M mn -> Vulkan13Features mn #

data DescriptorIndexingFeatures (mn :: Maybe Type) #

Constructors

DescriptorIndexingFeatures 

Fields

data DescriptorIndexingFeaturesNoNext #

Constructors

DescriptorIndexingFeaturesNoNext 

Fields