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

Gpu.Vulkan.Memory.Middle

Synopsis

ALLOCATE AND FREE

allocate :: forall (mn :: Maybe Type) (ma :: Maybe Type). WithPoked (M mn) => D -> AllocateInfo mn -> M A ma -> IO M Source #

reallocate :: forall (mn :: Maybe Type) (ma :: Maybe Type). WithPoked (M mn) => D -> AllocateInfo mn -> M A ma -> M -> IO () Source #

reallocate' :: forall (mn :: Maybe Type) (ma :: Maybe Type) a. WithPoked (M mn) => D -> AllocateInfo mn -> M A ma -> M -> IO a -> IO () Source #

free :: forall (mf :: Maybe Type). D -> M -> M A mf -> IO () Source #

data M Source #

data AllocateInfo (mn :: Maybe Type) Source #

Instances

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

Defined in Gpu.Vulkan.Memory.Middle.Internal

Destruction Group

data Group s k Source #

group :: forall (mf :: Maybe Type) k a. D -> M A mf -> (forall s. Group s k -> IO a) -> IO a Source #

allocate' :: forall k (mn :: Maybe Type) sm (ma :: Maybe Type). (Ord k, WithPoked (M mn)) => D -> Group sm k -> k -> AllocateInfo mn -> M A ma -> IO (Either String M) Source #

free' :: forall k smng (mc :: Maybe Type). Ord k => D -> Group smng k -> k -> M A mc -> IO (Either String ()) Source #

lookup :: Ord k => Group sm k -> k -> IO (Maybe M) Source #

MAP AND UNMNAP

map :: D -> M -> Size -> Size -> MapFlags -> IO (Ptr a) Source #

unmap :: D -> M -> IO () Source #

newtype MapFlags Source #

Constructors

MapFlags Word32 

Instances

Instances details
Storable MapFlags Source # 
Instance details

Defined in Gpu.Vulkan.Memory.Middle.Internal

Bits MapFlags Source # 
Instance details

Defined in Gpu.Vulkan.Memory.Middle.Internal

Show MapFlags Source # 
Instance details

Defined in Gpu.Vulkan.Memory.Middle.Internal

Default MapFlags Source # 
Instance details

Defined in Gpu.Vulkan.Memory.Middle.Internal

Methods

def :: MapFlags #

Eq MapFlags Source # 
Instance details

Defined in Gpu.Vulkan.Memory.Middle.Internal

REQUIREMENTS AND BARRIER

data Barrier (mn :: Maybe Type) Source #

Instances

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

Defined in Gpu.Vulkan.Memory.Middle.Internal

Methods

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

show :: Barrier mn -> String #

showList :: [Barrier mn] -> ShowS #

MEMORY TYPE

data MType Source #

Instances

Instances details
Show MType Source # 
Instance details

Defined in Gpu.Vulkan.Memory.Middle.Internal

Methods

showsPrec :: Int -> MType -> ShowS #

show :: MType -> String #

showList :: [MType] -> ShowS #

data TypeBits Source #

Instances

Instances details
Bits TypeBits Source # 
Instance details

Defined in Gpu.Vulkan.Memory.Middle.Internal

FiniteBits TypeBits Source # 
Instance details

Defined in Gpu.Vulkan.Memory.Middle.Internal

Show TypeBits Source # 
Instance details

Defined in Gpu.Vulkan.Memory.Middle.Internal

Eq TypeBits Source # 
Instance details

Defined in Gpu.Vulkan.Memory.Middle.Internal

data TypeIndex Source #

Instances

Instances details
Enum TypeIndex Source # 
Instance details

Defined in Gpu.Vulkan.Memory.Middle.Internal

Num TypeIndex Source # 
Instance details

Defined in Gpu.Vulkan.Memory.Middle.Internal

Integral TypeIndex Source # 
Instance details

Defined in Gpu.Vulkan.Memory.Middle.Internal

Real TypeIndex Source # 
Instance details

Defined in Gpu.Vulkan.Memory.Middle.Internal

Show TypeIndex Source # 
Instance details

Defined in Gpu.Vulkan.Memory.Middle.Internal

Eq TypeIndex Source # 
Instance details

Defined in Gpu.Vulkan.Memory.Middle.Internal

Ord TypeIndex Source # 
Instance details

Defined in Gpu.Vulkan.Memory.Middle.Internal

data Heap Source #

Constructors

Heap 

Instances

Instances details
Show Heap Source # 
Instance details

Defined in Gpu.Vulkan.Memory.Middle.Internal

Methods

showsPrec :: Int -> Heap -> ShowS #

show :: Heap -> String #

showList :: [Heap] -> ShowS #