gpu-vulkan-middle-0.1.0.63: Medium wrapper for Vulkan API
Safe HaskellNone
LanguageHaskell2010

Gpu.Vulkan.QueryPool.Middle

Synopsis

CREATE AND DESTROY

create :: forall (mn :: Maybe Type) (mc :: Maybe Type). WithPoked (M mn) => D -> CreateInfo mn -> M A mc -> IO Q Source #

destroy :: forall (md :: Maybe Type). D -> Q -> M A md -> IO () Source #

data Q Source #

Instances

Instances details
Show Q Source # 
Instance details

Defined in Gpu.Vulkan.QueryPool.Middle.Internal

Methods

showsPrec :: Int -> Q -> ShowS #

show :: Q -> String #

showList :: [Q] -> ShowS #

type CreateFlags = CreateFlagBits Source #

GET RESULTS

getResults :: forall (av :: Bool) (w64 :: Bool). (Storable (W32W64 w64), W32W64Tools w64, AvailabilityTools av (W32W64 w64)) => D -> Q -> Word32 -> Word32 -> ResultFlags -> IO [Availability av (W32W64 w64)] Source #

class W32W64Tools (w64 :: Bool) Source #

Minimal complete definition

bytesOf, result64Bit

Instances

Instances details
W32W64Tools 'False Source # 
Instance details

Defined in Gpu.Vulkan.QueryPool.Middle.Internal

W32W64Tools 'True Source # 
Instance details

Defined in Gpu.Vulkan.QueryPool.Middle.Internal

data W32W64 (w64 :: Bool) where Source #

Constructors

W32 :: Word32 -> W32W64 'False 
W64 :: Word64 -> W32W64 'True 

Instances

Instances details
Storable (W32W64 'False) Source # 
Instance details

Defined in Gpu.Vulkan.QueryPool.Middle.Internal

Storable (W32W64 'True) Source # 
Instance details

Defined in Gpu.Vulkan.QueryPool.Middle.Internal

Methods

sizeOf :: W32W64 'True -> Int #

alignment :: W32W64 'True -> Int #

peekElemOff :: Ptr (W32W64 'True) -> Int -> IO (W32W64 'True) #

pokeElemOff :: Ptr (W32W64 'True) -> Int -> W32W64 'True -> IO () #

peekByteOff :: Ptr b -> Int -> IO (W32W64 'True) #

pokeByteOff :: Ptr b -> Int -> W32W64 'True -> IO () #

peek :: Ptr (W32W64 'True) -> IO (W32W64 'True) #

poke :: Ptr (W32W64 'True) -> W32W64 'True -> IO () #

Num (W32W64 'False) Source # 
Instance details

Defined in Gpu.Vulkan.QueryPool.Middle.Internal

Num (W32W64 'True) Source # 
Instance details

Defined in Gpu.Vulkan.QueryPool.Middle.Internal

Show (W32W64 w64) Source # 
Instance details

Defined in Gpu.Vulkan.QueryPool.Middle.Internal

Methods

showsPrec :: Int -> W32W64 w64 -> ShowS #

show :: W32W64 w64 -> String #

showList :: [W32W64 w64] -> ShowS #

Eq (W32W64 w64) Source # 
Instance details

Defined in Gpu.Vulkan.QueryPool.Middle.Internal

Methods

(==) :: W32W64 w64 -> W32W64 w64 -> Bool #

(/=) :: W32W64 w64 -> W32W64 w64 -> Bool #

class AvailabilityTools (av :: Bool) a Source #

Minimal complete definition

numOfWords, resultWithAvailBit, mkAvailability

data Availability (av :: Bool) a where Source #

Constructors

NonAvailability :: forall a. a -> Availability 'False a 
Availability :: forall a. Maybe a -> Availability 'True a 

Instances

Instances details
Functor (Availability av) Source # 
Instance details

Defined in Gpu.Vulkan.QueryPool.Middle.Internal

Methods

fmap :: (a -> b) -> Availability av a -> Availability av b #

(<$) :: a -> Availability av b -> Availability av a #

Show a => Show (Availability av a) Source # 
Instance details

Defined in Gpu.Vulkan.QueryPool.Middle.Internal

Methods

showsPrec :: Int -> Availability av a -> ShowS #

show :: Availability av a -> String #

showList :: [Availability av a] -> ShowS #