gpu-vulkan-0.1.0.166: Vulkan library
Safe HaskellNone
LanguageHaskell2010

Gpu.Vulkan.ImageView

Synopsis

CREATE

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

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

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

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

Instances

Instances details
Show (I nm fmt si) Source # 
Instance details

Defined in Gpu.Vulkan.ImageView.Type

Methods

showsPrec :: Int -> I nm fmt si -> ShowS #

show :: I nm fmt si -> String #

showList :: [I nm fmt si] -> ShowS #

Manage Multiple Image View

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

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

unsafeDestroy :: forall k (ma :: Maybe (Type, Type)) sd sm (nm :: Symbol) (ivfmt :: Format). (Ord k, ToMiddle ma) => Group sd ma sm k nm ivfmt -> k -> IO (Either String ()) Source #

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

data Group sd (ma :: Maybe (Type, Type)) s k (nm :: Symbol) (ivfmt :: Format) Source #

ENUM

newtype Type #

Constructors

Type Word32 

Instances

Instances details
Storable Type 
Instance details

Defined in Gpu.Vulkan.ImageView.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.ImageView.Enum

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

Eq Type 
Instance details

Defined in Gpu.Vulkan.ImageView.Enum

Methods

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

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

newtype CreateFlagBits #

Constructors

CreateFlagBits Word32 

Instances

Instances details
Bits CreateFlagBits 
Instance details

Defined in Gpu.Vulkan.ImageView.Enum

Storable CreateFlagBits 
Instance details

Defined in Gpu.Vulkan.ImageView.Enum

Show CreateFlagBits 
Instance details

Defined in Gpu.Vulkan.ImageView.Enum

Eq CreateFlagBits 
Instance details

Defined in Gpu.Vulkan.ImageView.Enum

pattern TypeMaxEnum :: Type #

pattern Type3d :: Type #

pattern Type2d :: Type #

pattern Type1d :: Type #

pattern TypeCubeArray :: Type #

pattern Type2dArray :: Type #

pattern Type1dArray :: Type #

pattern TypeCube :: Type #