gpu-vulkan-0.1.0.139: Vulkan library
Safe HaskellNone
LanguageHaskell2010

Gpu.Vulkan.QueryPool

Synopsis

CREATE

create :: forall (mn :: Maybe Type) (tp :: Bool -> Type) (mac :: Maybe (Type, Type)) sd a. (WithPoked (M mn), QueryType tp, ToMiddle mac) => D sd -> CreateInfo mn tp -> M (U2 A) mac -> (forall s. Q s tp -> IO a) -> IO a Source #

data Q sq (tp :: Bool -> Type) Source #

Instances

Instances details
Show (Q sq tp) Source # 
Instance details

Defined in Gpu.Vulkan.QueryPool.Type

Methods

showsPrec :: Int -> Q sq tp -> ShowS #

show :: Q sq tp -> String #

showList :: [Q sq tp] -> ShowS #

data CreateInfo (mn :: Maybe Type) (tp :: Bool -> Type) Source #

Instances

Instances details
Show (M mn) => Show (CreateInfo mn tp) Source # 
Instance details

Defined in Gpu.Vulkan.QueryPool

Methods

showsPrec :: Int -> CreateInfo mn tp -> ShowS #

show :: CreateInfo mn tp -> String #

showList :: [CreateInfo mn tp] -> ShowS #

GET RESULTS

getResults :: forall sd sq (av :: Bool) tp (w64 :: Bool). (QueryType tp, Storable (W32W64 w64), W32W64Tools w64, AvailabilityTools av (W32W64 w64)) => P -> D sd -> Q sq tp -> First -> Count -> ResultFlags -> IO [Availability av (tp w64)] Source #

class QueryType (qt :: Bool -> Type) Source #

Minimal complete definition

queryType, fromWord, getQueryArg

Instances

Instances details
QueryType PipelineStatistics Source # 
Instance details

Defined in Gpu.Vulkan.QueryPool

Methods

queryType :: Type

fromWord :: forall (w64 :: Bool). QueryArg PipelineStatistics -> W32W64 w64 -> PipelineStatistics w64

getQueryArg :: P -> IO (QueryArg PipelineStatistics)

QueryType Timestamp Source # 
Instance details

Defined in Gpu.Vulkan.QueryPool

Methods

queryType :: Type

fromWord :: forall (w64 :: Bool). QueryArg Timestamp -> W32W64 w64 -> Timestamp w64

getQueryArg :: P -> IO (QueryArg Timestamp)

data PipelineStatistics (w64 :: Bool) where Source #

Instances

Instances details
QueryType PipelineStatistics Source # 
Instance details

Defined in Gpu.Vulkan.QueryPool

Methods

queryType :: Type

fromWord :: forall (w64 :: Bool). QueryArg PipelineStatistics -> W32W64 w64 -> PipelineStatistics w64

getQueryArg :: P -> IO (QueryArg PipelineStatistics)

Show (PipelineStatistics w64) Source # 
Instance details

Defined in Gpu.Vulkan.QueryPool

data Timestamp (w64 :: Bool) where Source #

Constructors

Timestamp32 

Fields

Timestamp64 

Fields

Instances

Instances details
QueryType Timestamp Source # 
Instance details

Defined in Gpu.Vulkan.QueryPool

Methods

queryType :: Type

fromWord :: forall (w64 :: Bool). QueryArg Timestamp -> W32W64 w64 -> Timestamp w64

getQueryArg :: P -> IO (QueryArg Timestamp)

Show (Timestamp w64) Source # 
Instance details

Defined in Gpu.Vulkan.QueryPool

Methods

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

show :: Timestamp w64 -> String #

showList :: [Timestamp w64] -> ShowS #

data Availability (av :: Bool) a where #

Constructors

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

Instances

Instances details
Functor (Availability av) 
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) 
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 #