gpu-vulkan-0.1.0.157: Vulkan library
Safe HaskellNone
LanguageHaskell2010

Gpu.Vulkan.Image

Synopsis

CREATE

create :: forall (mn :: Maybe Type) (fmt :: Format) (mac :: Maybe (Type, Type)) sd (nm :: Symbol) a. (WithPoked (M mn), FormatToValue fmt, ToMiddle mac) => D sd -> CreateInfo mn fmt -> M (U2 A) mac -> (forall s. I s nm fmt -> IO a) -> IO a Source #

unsafeRecreate :: forall (mn :: Maybe Type) (mac :: Maybe (Type, Type)) (fmt :: Format) sd sm si (nm :: Symbol). (WithPoked (M mn), ToMiddle mac, FormatToValue fmt) => D sd -> CreateInfo mn fmt -> M (U2 A) mac -> Binded sm si nm fmt -> IO () Source #

unsafeRecreate' :: forall (mn :: Maybe Type) (mac :: Maybe (Type, Type)) (fmt :: Format) sd sm si (nm :: Symbol) a. (WithPoked (M mn), ToMiddle mac, FormatToValue fmt) => D sd -> CreateInfo mn fmt -> M (U2 A) mac -> Binded sm si nm fmt -> IO a -> IO () Source #

data I s (nm :: Symbol) (fmt :: Format) Source #

data Binded sm si (nm :: Symbol) (fmt :: Format) Source #

Manage Multiple Image

data Group sd (ma :: Maybe (Type, Type)) s k2 (nm :: k) (fmt :: k1) Source #

group :: forall {k1} {k2} (mac :: Maybe (Type, Type)) sd k3 (nm :: k1) (fmt :: k2) a. ToMiddle mac => D sd -> M (U2 A) mac -> (forall s. Group sd mac s k3 nm fmt -> IO a) -> IO a Source #

create' :: forall k (mn :: Maybe Type) (fmt :: Format) (mac :: Maybe (Type, Type)) sd sm (nm :: Symbol). (Ord k, WithPoked (M mn), FormatToValue fmt, ToMiddle mac) => Group sd mac sm k nm fmt -> k -> CreateInfo mn fmt -> IO (Either String (I sm nm fmt)) Source #

unsafeDestroy :: forall {k1} {k2} k3 (mac :: Maybe (Type, Type)) sd sm (nm :: k1) (fmt :: k2). (Ord k3, ToMiddle mac) => Group sd mac sm k3 nm fmt -> k3 -> IO (Either String ()) Source #

lookup :: forall k sd (ma :: Maybe (Type, Type)) smng (nm :: Symbol) (fmt :: Format). Ord k => Group sd ma smng k nm fmt -> k -> IO (Maybe (I smng nm fmt)) Source #

GET MEMORY REQUIREMENTS

getMemoryRequirements :: forall sd si (nm :: Symbol) (fmt :: Format). D sd -> I si nm fmt -> IO Requirements Source #

getMemoryRequirementsBinded :: forall sd sm si (nm :: Symbol) (fmt :: Format). D sd -> Binded sm si nm fmt -> IO Requirements Source #

MEMORY BARRIER

class MemoryBarrierListToMiddle (mbargs :: [(Maybe Type, Type, Type, Symbol, Format)]) Source #

Minimal complete definition

memoryBarrierListToMiddle

Instances

Instances details
MemoryBarrierListToMiddle ('[] :: [(Maybe Type, Type, Type, Symbol, Format)]) Source # 
Instance details

Defined in Gpu.Vulkan.Image.Internal

MemoryBarrierListToMiddle mbargs => MemoryBarrierListToMiddle ('(mn, si, sm, nm, fmt) ': mbargs) Source # 
Instance details

Defined in Gpu.Vulkan.Image.Internal

Methods

memoryBarrierListToMiddle :: PL (U5 MemoryBarrier) ('(mn, si, sm, nm, fmt) ': mbargs) -> PL MemoryBarrier (M0_5 ('(mn, si, sm, nm, fmt) ': mbargs)) Source #

BLIT

OTHERS

unsafeToBinded :: forall si (nm :: Symbol) (fmt :: Format) sm (hm :: Symbol). I si nm fmt -> Binded sm si hm fmt Source #

ENUM

newtype Type #

Constructors

Type Word32 

Instances

Instances details
Storable Type 
Instance details

Defined in Gpu.Vulkan.Image.Enum

Methods

sizeOf :: Type -> Int #

alignment :: Type -> Int #

peekElemOff :: Ptr Type -> Int -> IO Type #

pokeElemOff :: Ptr Type -> Int -> Type -> IO () #

peekByteOff :: Ptr b -> Int -> IO Type #

pokeByteOff :: Ptr b -> Int -> Type -> IO () #

peek :: Ptr Type -> IO Type #

poke :: Ptr Type -> Type -> IO () #

Show Type 
Instance details

Defined in Gpu.Vulkan.Image.Enum

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

Eq Type 
Instance details

Defined in Gpu.Vulkan.Image.Enum

Methods

(==) :: Type -> Type -> Bool #

(/=) :: Type -> Type -> Bool #

newtype CreateFlagBits #

Constructors

CreateFlagBits Word32 

Instances

Instances details
Bits CreateFlagBits 
Instance details

Defined in Gpu.Vulkan.Image.Enum

Storable CreateFlagBits 
Instance details

Defined in Gpu.Vulkan.Image.Enum

Show CreateFlagBits 
Instance details

Defined in Gpu.Vulkan.Image.Enum

Eq CreateFlagBits 
Instance details

Defined in Gpu.Vulkan.Image.Enum

newtype UsageFlagBits #

Constructors

UsageFlagBits Word32 

Instances

Instances details
Bits UsageFlagBits 
Instance details

Defined in Gpu.Vulkan.Image.Enum

Storable UsageFlagBits 
Instance details

Defined in Gpu.Vulkan.Image.Enum

Show UsageFlagBits 
Instance details

Defined in Gpu.Vulkan.Image.Enum

Eq UsageFlagBits 
Instance details

Defined in Gpu.Vulkan.Image.Enum

pattern TypeMaxEnum :: Type #

newtype AspectFlagBits #

Constructors

AspectFlagBits Word32 

Instances

Instances details
Bits AspectFlagBits 
Instance details

Defined in Gpu.Vulkan.Image.Enum

Storable AspectFlagBits 
Instance details

Defined in Gpu.Vulkan.Image.Enum

Show AspectFlagBits 
Instance details

Defined in Gpu.Vulkan.Image.Enum

Eq AspectFlagBits 
Instance details

Defined in Gpu.Vulkan.Image.Enum

newtype Layout #

Constructors

Layout Word32 

Instances

Instances details
Storable Layout 
Instance details

Defined in Gpu.Vulkan.Image.Enum

Show Layout 
Instance details

Defined in Gpu.Vulkan.Image.Enum

Eq Layout 
Instance details

Defined in Gpu.Vulkan.Image.Enum

Methods

(==) :: Layout -> Layout -> Bool #

(/=) :: Layout -> Layout -> Bool #

pattern Type3d :: Type #

pattern Type2d :: Type #

pattern Type1d :: Type #

newtype Tiling #

Constructors

Tiling Word32 

Instances

Instances details
Storable Tiling 
Instance details

Defined in Gpu.Vulkan.Image.Enum

Show Tiling 
Instance details

Defined in Gpu.Vulkan.Image.Enum

Eq Tiling 
Instance details

Defined in Gpu.Vulkan.Image.Enum

Methods

(==) :: Tiling -> Tiling -> Bool #

(/=) :: Tiling -> Tiling -> Bool #

pattern TilingLinear :: Tiling #