Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- 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
- data Q sq (tp :: Bool -> Type)
- data CreateInfo (mn :: Maybe Type) (tp :: Bool -> Type) = CreateInfo {}
- 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)]
- class QueryType (qt :: Bool -> Type)
- data PipelineStatistics (w64 :: Bool) where
- data Timestamp (w64 :: Bool) where
- Timestamp32 :: {..} -> Timestamp 'False
- Timestamp64 :: {..} -> Timestamp 'True
- data Availability (av :: Bool) a where
- NonAvailability :: forall a. a -> Availability 'False a
- Availability :: forall a. Maybe a -> Availability 'True a
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 CreateInfo (mn :: Maybe Type) (tp :: Bool -> Type) Source #
Instances
Show (M mn) => Show (CreateInfo mn tp) Source # | |
Defined in Gpu.Vulkan.QueryPool 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 #
queryType, fromWord, getQueryArg
Instances
QueryType PipelineStatistics Source # | |
Defined in Gpu.Vulkan.QueryPool fromWord :: forall (w64 :: Bool). QueryArg PipelineStatistics -> W32W64 w64 -> PipelineStatistics w64 getQueryArg :: P -> IO (QueryArg PipelineStatistics) | |
QueryType Timestamp Source # | |
data PipelineStatistics (w64 :: Bool) where Source #
PipelineStatistics32 :: Word32 -> PipelineStatistics 'False | |
PipelineStatistics64 :: Word64 -> PipelineStatistics 'True |
Instances
QueryType PipelineStatistics Source # | |
Defined in Gpu.Vulkan.QueryPool fromWord :: forall (w64 :: Bool). QueryArg PipelineStatistics -> W32W64 w64 -> PipelineStatistics w64 getQueryArg :: P -> IO (QueryArg PipelineStatistics) | |
Show (PipelineStatistics w64) Source # | |
Defined in Gpu.Vulkan.QueryPool showsPrec :: Int -> PipelineStatistics w64 -> ShowS # show :: PipelineStatistics w64 -> String # showList :: [PipelineStatistics w64] -> ShowS # |
data Timestamp (w64 :: Bool) where Source #
Timestamp32 | |
| |
Timestamp64 | |
|
data Availability (av :: Bool) a where #
NonAvailability :: forall a. a -> Availability 'False a | |
Availability :: forall a. Maybe a -> Availability 'True a |
Instances
Functor (Availability av) | |
Defined in Gpu.Vulkan.QueryPool.Middle.Internal fmap :: (a -> b) -> Availability av a -> Availability av b # (<$) :: a -> Availability av b -> Availability av a # | |
Show a => Show (Availability av a) | |
Defined in Gpu.Vulkan.QueryPool.Middle.Internal showsPrec :: Int -> Availability av a -> ShowS # show :: Availability av a -> String # showList :: [Availability av a] -> ShowS # |