gpu-vulkan-0.1.0.153: Vulkan library
Safe HaskellNone
LanguageHaskell2010

Gpu.Vulkan.Memory

Synopsis

ALLOCATE AND BIND

allocateBind :: forall (mn :: Maybe Type) (ibargs :: [(Type, ImageBufferArg)]) (mac :: Maybe (Type, Type)) sd a. (WithPoked (M mn), Bindable ibargs, ToMiddle mac) => D sd -> PL (U2 ImageBuffer) ibargs -> AllocateInfo mn -> M (U2 A) mac -> (forall s. PL (U2 (ImageBufferBinded s)) ibargs -> M s ibargs -> IO a) -> IO a Source #

unsafeReallocateBind :: forall (mn :: Maybe Type) (ibargs :: [(Type, ImageBufferArg)]) (mac :: Maybe (Type, Type)) sd sm. (WithPoked (M mn), Rebindable ibargs, ToMiddle mac) => D sd -> PL (U2 (ImageBufferBinded sm)) ibargs -> AllocateInfo mn -> M (U2 A) mac -> M sm ibargs -> IO () Source #

unsafeReallocateBind' :: forall (mn :: Maybe Type) (ibargs :: [(Type, ImageBufferArg)]) (mac :: Maybe (Type, Type)) sd sm a. (WithPoked (M mn), Rebindable ibargs, ToMiddle mac) => D sd -> PL (U2 (ImageBufferBinded sm)) ibargs -> AllocateInfo mn -> M (U2 A) mac -> M sm ibargs -> IO a -> IO () Source #

Destruction Group

data Group sd (ma :: Maybe (Type, Type)) s k (ibargs :: [(Type, ImageBufferArg)]) Source #

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

allocateBind' :: forall k (mn :: Maybe Type) (ibargs :: [(Type, ImageBufferArg)]) (ma :: Maybe (Type, Type)) sd sm. (Ord k, WithPoked (M mn), Bindable ibargs, ToMiddle ma) => Group sd ma sm k ibargs -> k -> PL (U2 ImageBuffer) ibargs -> AllocateInfo mn -> IO (Either String (PL (U2 (ImageBufferBinded sm)) ibargs, M sm ibargs)) Source #

unsafeFree :: forall k (ma :: Maybe (Type, Type)) sd smng (ibargs :: [(Type, ImageBufferArg)]). (Ord k, ToMiddle ma) => Group sd ma smng k ibargs -> k -> IO (Either String ()) Source #

lookup :: forall k sd (ma :: Maybe (Type, Type)) sm (ibargs :: [(Type, ImageBufferArg)]) s. Ord k => Group sd ma sm k ibargs -> k -> IO (Maybe (M s ibargs)) Source #

MEMORY

data M s (ibargs :: [(Type, ImageBufferArg)]) Source #

getBinded :: forall s (ibargs :: [(Type, ImageBufferArg)]). M s ibargs -> IO (PL (U2 (ImageBufferBinded s)) ibargs) Source #

data ImageBuffer s (ibarg :: ImageBufferArg) where Source #

Constructors

Image :: forall s (nm :: Symbol) (fmt :: Format). I s nm fmt -> ImageBuffer s ('ImageArg nm fmt) 
Buffer :: forall s (nm :: Symbol) (objs :: [O]). B s nm objs -> ImageBuffer s ('BufferArg nm objs) 
Raw :: forall s. Size -> Size -> ImageBuffer s 'RawArg 

Instances

Instances details
Show (PL Length objs) => Show (ImageBuffer sib ('BufferArg nm objs)) Source # 
Instance details

Defined in Gpu.Vulkan.Memory.ImageBuffer

Methods

showsPrec :: Int -> ImageBuffer sib ('BufferArg nm objs) -> ShowS #

show :: ImageBuffer sib ('BufferArg nm objs) -> String #

showList :: [ImageBuffer sib ('BufferArg nm objs)] -> ShowS #

data ImageBufferBinded sm sib (ibarg :: ImageBufferArg) where Source #

Constructors

ImageBinded :: forall sm sib (nm :: Symbol) (fmt :: Format). Binded sm sib nm fmt -> ImageBufferBinded sm sib ('ImageArg nm fmt) 
BufferBinded :: forall sm sib (nm :: Symbol) (objs :: [O]). Binded sm sib nm objs -> ImageBufferBinded sm sib ('BufferArg nm objs) 
RawBinded :: forall sm sib. Size -> Size -> ImageBufferBinded sm sib 'RawArg 

Instances

Instances details
Show (PL Length objs) => Show (ImageBufferBinded sm sib ('BufferArg nm objs)) Source # 
Instance details

Defined in Gpu.Vulkan.Memory.ImageBuffer

Methods

showsPrec :: Int -> ImageBufferBinded sm sib ('BufferArg nm objs) -> ShowS #

show :: ImageBufferBinded sm sib ('BufferArg nm objs) -> String #

showList :: [ImageBufferBinded sm sib ('BufferArg nm objs)] -> ShowS #

data ImageBufferArg Source #

Instances

Instances details
(OffsetRange obj objs i, LengthOf obj objs) => OffsetSize nm obj ('(sib, 'BufferArg nm objs) ': ibargs) i Source # 
Instance details

Defined in Gpu.Vulkan.Memory.OffsetSize

Methods

offsetSize' :: D sd -> PL (U2 ImageBuffer) ('(sib, 'BufferArg nm objs) ': ibargs) -> Size -> IO (Size, Size)

OffsetSize nm obj ibargs i => OffsetSize nm obj ('(sib, ib) ': ibargs) i Source # 
Instance details

Defined in Gpu.Vulkan.Memory.OffsetSize

Methods

offsetSize' :: D sd -> PL (U2 ImageBuffer) ('(sib, ib) ': ibargs) -> Size -> IO (Size, Size)

BindSparseInfosToMiddle ('[] :: [(Maybe Type, [Type], [(Type, Symbol, [O], [(Type, [(Type, ImageBufferArg)], Nat)])], [(Type, Symbol, Format, [(Type, [(Type, ImageBufferArg)], Nat)])], [(Type, Symbol, Format, [(Type, [(Type, ImageBufferArg)], Nat)])], [Type])]) Source # 
Instance details

Defined in Gpu.Vulkan.Queue

Methods

bindSparseInfosToMiddle :: D sd -> PL (U6 BindSparseInfo) ('[] :: [(Maybe Type, [Type], [(Type, Symbol, [O], [(Type, [(Type, ImageBufferArg)], Nat)])], [(Type, Symbol, Format, [(Type, [(Type, ImageBufferArg)], Nat)])], [(Type, Symbol, Format, [(Type, [(Type, ImageBufferArg)], Nat)])], [Type])]) -> IO (PL BindSparseInfo (M0_6 ('[] :: [(Maybe Type, [Type], [(Type, Symbol, [O], [(Type, [(Type, ImageBufferArg)], Nat)])], [(Type, Symbol, Format, [(Type, [(Type, ImageBufferArg)], Nat)])], [(Type, Symbol, Format, [(Type, [(Type, ImageBufferArg)], Nat)])], [Type])])))

(MemoryBindInfosToMiddle bbs, OpaqueMemoryBindInfosToMiddle iobs, MemoryBindInfosToMiddle ibs, BindSparseInfosToMiddle bsias) => BindSparseInfosToMiddle ('(mn, swss, bbs, iobs, ibs, ssss) ': bsias) Source # 
Instance details

Defined in Gpu.Vulkan.Queue

Methods

bindSparseInfosToMiddle :: D sd -> PL (U6 BindSparseInfo) ('(mn, swss, bbs, iobs, ibs, ssss) ': bsias) -> IO (PL BindSparseInfo (M0_6 ('(mn, swss, bbs, iobs, ibs, ssss) ': bsias)))

ALLOCATE INFO

data AllocateInfo (mn :: Maybe Type) Source #

Instances

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

Defined in Gpu.Vulkan.Memory

Eq (M mn) => Eq (AllocateInfo mn) Source # 
Instance details

Defined in Gpu.Vulkan.Memory

Methods

(==) :: AllocateInfo mn -> AllocateInfo mn -> Bool #

(/=) :: AllocateInfo mn -> AllocateInfo mn -> Bool #

data MType #

Instances

Instances details
Show MType 
Instance details

Defined in Gpu.Vulkan.Memory.Middle.Internal

Methods

showsPrec :: Int -> MType -> ShowS #

show :: MType -> String #

showList :: [MType] -> ShowS #

data TypeIndex #

Instances

Instances details
Enum TypeIndex 
Instance details

Defined in Gpu.Vulkan.Memory.Middle.Internal

Num TypeIndex 
Instance details

Defined in Gpu.Vulkan.Memory.Middle.Internal

Integral TypeIndex 
Instance details

Defined in Gpu.Vulkan.Memory.Middle.Internal

Real TypeIndex 
Instance details

Defined in Gpu.Vulkan.Memory.Middle.Internal

Show TypeIndex 
Instance details

Defined in Gpu.Vulkan.Memory.Middle.Internal

Eq TypeIndex 
Instance details

Defined in Gpu.Vulkan.Memory.Middle.Internal

Ord TypeIndex 
Instance details

Defined in Gpu.Vulkan.Memory.Middle.Internal

data Heap #

Constructors

Heap 

Instances

Instances details
Show Heap 
Instance details

Defined in Gpu.Vulkan.Memory.Middle.Internal

Methods

showsPrec :: Int -> Heap -> ShowS #

show :: Heap -> String #

showList :: [Heap] -> ShowS #

BINDABLE AND REBINDABLE

class (BindAll ibargs ibargs, Alignments ibargs) => Bindable (ibargs :: [(Type, ImageBufferArg)]) Source #

Instances

Instances details
(BindAll ibargs ibargs, Alignments ibargs) => Bindable ibargs Source # 
Instance details

Defined in Gpu.Vulkan.Memory.Bind

class (RebindAll ibargs ibargs, Alignments ibargs) => Rebindable (ibargs :: [(Type, ImageBufferArg)]) Source #

Instances

Instances details
(RebindAll ibargs ibargs, Alignments ibargs) => Rebindable ibargs Source # 
Instance details

Defined in Gpu.Vulkan.Memory.Bind

GET REQUREMENTS

getRequirementsList :: forall sd (ibargs :: [(Type, ImageBufferArg)]). D sd -> PL (U2 ImageBuffer) ibargs -> IO [Either AlgnSize Requirements] Source #

READ AND WRITE

read :: forall (nm :: Symbol) (obj :: O) (i :: Nat) v sd sm (ibargs :: [(Type, ImageBufferArg)]). (Store v obj, OffsetSize nm obj ibargs i) => D sd -> M sm ibargs -> MapFlags -> IO v Source #

write :: forall (nm :: Symbol) (obj :: O) (i :: Nat) sd sm (ibargs :: [(Type, ImageBufferArg)]) v. (Store v obj, OffsetSize nm obj ibargs i) => D sd -> M sm ibargs -> MapFlags -> v -> IO () Source #

class ObjectLength nm obj ibargs => OffsetSize (nm :: Symbol) (obj :: O) (ibargs :: [(Type, ImageBufferArg)]) (i :: Nat) Source #

Minimal complete definition

offsetSize'

Instances

Instances details
(OffsetRange obj objs i, LengthOf obj objs) => OffsetSize nm obj ('(sib, 'BufferArg nm objs) ': ibargs) i Source # 
Instance details

Defined in Gpu.Vulkan.Memory.OffsetSize

Methods

offsetSize' :: D sd -> PL (U2 ImageBuffer) ('(sib, 'BufferArg nm objs) ': ibargs) -> Size -> IO (Size, Size)

OffsetSize nm obj ibargs i => OffsetSize nm obj ('(sib, ib) ': ibargs) i Source # 
Instance details

Defined in Gpu.Vulkan.Memory.OffsetSize

Methods

offsetSize' :: D sd -> PL (U2 ImageBuffer) ('(sib, ib) ': ibargs) -> Size -> IO (Size, Size)

data MapFlags #

Instances

Instances details
Storable MapFlags 
Instance details

Defined in Gpu.Vulkan.Memory.Middle.Internal

Bits MapFlags 
Instance details

Defined in Gpu.Vulkan.Memory.Middle.Internal

Show MapFlags 
Instance details

Defined in Gpu.Vulkan.Memory.Middle.Internal

Default MapFlags 
Instance details

Defined in Gpu.Vulkan.Memory.Middle.Internal

Methods

def :: MapFlags #

Eq MapFlags 
Instance details

Defined in Gpu.Vulkan.Memory.Middle.Internal

BARRIER

data Barrier (mn :: Maybe Type) #

Instances

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

Defined in Gpu.Vulkan.Memory.Middle.Internal

Methods

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

show :: Barrier mn -> String #

showList :: [Barrier mn] -> ShowS #

OTHERS

newtype RawOffset (n :: Nat) Source #

Constructors

RawOffset Size 

Instances

Instances details
Num (RawOffset n) Source # 
Instance details

Defined in Gpu.Vulkan.Memory.ImageBuffer

Show (RawOffset n) Source # 
Instance details

Defined in Gpu.Vulkan.Memory.ImageBuffer

ENUM

newtype PropertyFlagBits #

Constructors

PropertyFlagBits Word32 

Instances

Instances details
Storable PropertyFlagBits 
Instance details

Defined in Gpu.Vulkan.Memory.Enum

Bits PropertyFlagBits 
Instance details

Defined in Gpu.Vulkan.Memory.Enum

FiniteBits PropertyFlagBits 
Instance details

Defined in Gpu.Vulkan.Memory.Enum

Show PropertyFlagBits 
Instance details

Defined in Gpu.Vulkan.Memory.Enum

Eq PropertyFlagBits 
Instance details

Defined in Gpu.Vulkan.Memory.Enum

newtype HeapFlagBits #

Constructors

HeapFlagBits Word32 

Instances

Instances details
Storable HeapFlagBits 
Instance details

Defined in Gpu.Vulkan.Memory.Enum

Bits HeapFlagBits 
Instance details

Defined in Gpu.Vulkan.Memory.Enum

FiniteBits HeapFlagBits 
Instance details

Defined in Gpu.Vulkan.Memory.Enum

Show HeapFlagBits 
Instance details

Defined in Gpu.Vulkan.Memory.Enum

Eq HeapFlagBits 
Instance details

Defined in Gpu.Vulkan.Memory.Enum