Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- create :: forall (mn :: Maybe Type) (qcis :: [Maybe Type]) (mac :: Maybe (Type, Type)) a. (WithPoked (M mn), ToListWithCM' WithPoked M qcis, ToMiddle mac) => P -> CreateInfo mn qcis -> M (U2 A) mac -> (forall s. D s -> IO a) -> IO a
- newtype D s = D D
- data CreateInfo (mn :: Maybe Type) (qcis :: [Maybe Type]) = CreateInfo {}
- type CreateFlags = CreateFlagBits
- data QueueCreateInfo (mn :: Maybe Type) = QueueCreateInfo {}
- group :: forall (ma :: Maybe (Type, Type)) k a. ToMiddle ma => M (U2 A) ma -> (forall sd. Group ma sd k -> IO a) -> IO a
- data Group (ma :: Maybe (Type, Type)) sd k
- create' :: forall k (mn :: Maybe Type) (qcis :: [Maybe Type]) (ma :: Maybe (Type, Type)) sd. (Ord k, WithPoked (M mn), ToListWithCM' WithPoked M qcis, ToMiddle ma) => P -> Group ma sd k -> k -> CreateInfo mn qcis -> IO (Either String (D sd))
- unsafeDestroy :: forall k (ma :: Maybe (Type, Type)) sd. (Ord k, ToMiddle ma) => Group ma sd k -> k -> IO (Either String ())
- lookup :: forall k (ma :: Maybe (Type, Type)) sd. Ord k => Group ma sd k -> k -> IO (Maybe (D sd))
- getQueue :: D sd -> Index -> Index -> IO Q
- waitIdle :: D s -> IO ()
- data Size
CREATE
create :: forall (mn :: Maybe Type) (qcis :: [Maybe Type]) (mac :: Maybe (Type, Type)) a. (WithPoked (M mn), ToListWithCM' WithPoked M qcis, ToMiddle mac) => P -> CreateInfo mn qcis -> M (U2 A) mac -> (forall s. D s -> IO a) -> IO a Source #
data CreateInfo (mn :: Maybe Type) (qcis :: [Maybe Type]) Source #
Instances
(Show (M mn), Show (PL QueueCreateInfo qcis)) => Show (CreateInfo mn qcis) Source # | |
Defined in Gpu.Vulkan.Device.Internal showsPrec :: Int -> CreateInfo mn qcis -> ShowS # show :: CreateInfo mn qcis -> String # showList :: [CreateInfo mn qcis] -> ShowS # |
type CreateFlags = CreateFlagBits #
data QueueCreateInfo (mn :: Maybe Type) #
Instances
Show (M mn) => Show (QueueCreateInfo mn) | |
Defined in Gpu.Vulkan.Device.Middle.Internal showsPrec :: Int -> QueueCreateInfo mn -> ShowS # show :: QueueCreateInfo mn -> String # showList :: [QueueCreateInfo mn] -> ShowS # |
Group
group :: forall (ma :: Maybe (Type, Type)) k a. ToMiddle ma => M (U2 A) ma -> (forall sd. Group ma sd k -> IO a) -> IO a Source #
create' :: forall k (mn :: Maybe Type) (qcis :: [Maybe Type]) (ma :: Maybe (Type, Type)) sd. (Ord k, WithPoked (M mn), ToListWithCM' WithPoked M qcis, ToMiddle ma) => P -> Group ma sd k -> k -> CreateInfo mn qcis -> IO (Either String (D sd)) Source #
unsafeDestroy :: forall k (ma :: Maybe (Type, Type)) sd. (Ord k, ToMiddle ma) => Group ma sd k -> k -> IO (Either String ()) Source #
lookup :: forall k (ma :: Maybe (Type, Type)) sd. Ord k => Group ma sd k -> k -> IO (Maybe (D sd)) Source #