gpu-vulkan-0.1.0.142: Vulkan library
Safe HaskellNone
LanguageHaskell2010

Gpu.Vulkan.Semaphore

Contents

Synopsis

CREATE

create :: forall (mn :: Maybe Type) (mac :: Maybe (Type, Type)) sd a. (WithPoked (M mn), ToMiddle mac) => D sd -> CreateInfo mn -> M (U2 A) mac -> (forall ss. S ss -> IO a) -> IO a Source #

data S s Source #

Instances

Instances details
Show (S s) Source # 
Instance details

Defined in Gpu.Vulkan.Semaphore.Type

Methods

showsPrec :: Int -> S s -> ShowS #

show :: S s -> String #

showList :: [S s] -> ShowS #

data CreateInfo (mn :: Maybe Type) #

Constructors

CreateInfo 

Instances

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

Defined in Gpu.Vulkan.Semaphore.Middle.Internal

Methods

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

show :: CreateInfo mn -> String #

showList :: [CreateInfo mn] -> ShowS #

Default (CreateInfo ('Nothing :: Maybe Type)) 
Instance details

Defined in Gpu.Vulkan.Semaphore.Middle.Internal

Methods

def :: CreateInfo ('Nothing :: Maybe Type) #

Group

group :: forall (ma :: Maybe (Type, Type)) sd k a. ToMiddle ma => D sd -> M (U2 A) ma -> (forall ss. Group sd ma ss k -> IO a) -> IO a Source #

data Group sd (ma :: Maybe (Type, Type)) ss k Source #

create' :: forall k (mn :: Maybe Type) (ma :: Maybe (Type, Type)) sd ss. (Ord k, WithPoked (M mn), ToMiddle ma) => Group sd ma ss k -> k -> CreateInfo mn -> IO (Either String (S ss)) Source #

unsafeDestroy :: forall k (ma :: Maybe (Type, Type)) sd ss. (Ord k, ToMiddle ma) => Group sd ma ss k -> k -> IO (Either String ()) Source #

lookup :: forall k sd (ma :: Maybe (Type, Type)) ss. Ord k => Group sd ma ss k -> k -> IO (Maybe (S ss)) Source #