Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- 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
- 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 ()
- 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 ()
- data I (nm :: Symbol) (fmt :: Format) si
- data CreateInfo (n :: Maybe Type) sm si (nm :: Symbol) (ifmt :: Format) (ivfmt :: Format) = CreateInfo {
- createInfoNext :: M n
- createInfoFlags :: CreateFlags
- createInfoImage :: Binded sm si nm ifmt
- createInfoViewType :: Type
- createInfoComponents :: Mapping
- createInfoSubresourceRange :: SubresourceRange
- 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
- 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))
- 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 ())
- 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))
- data Group sd (ma :: Maybe (Type, Type)) s k (nm :: Symbol) (ivfmt :: Format)
- newtype Type = Type Word32
- newtype CreateFlagBits = CreateFlagBits Word32
- pattern CreateFlagBitsMaxEnum :: CreateFlagBits
- pattern CreateDescriptorBufferCaptureReplayBitExt :: CreateFlagBits
- pattern CreateFlagsZero :: CreateFlagBits
- unCreateFlagBits :: CreateFlagBits -> Word32
- type CreateFlags = CreateFlagBits
- pattern TypeMaxEnum :: Type
- unType :: Type -> Word32
- pattern Type3d :: Type
- pattern Type2d :: Type
- pattern Type1d :: Type
- pattern CreateFragmentDensityMapDeferredBitExt :: CreateFlagBits
- pattern CreateFragmentDensityMapDynamicBitExt :: CreateFlagBits
- pattern TypeCubeArray :: Type
- pattern Type2dArray :: Type
- pattern Type1dArray :: Type
- pattern TypeCube :: Type
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 CreateInfo (n :: Maybe Type) sm si (nm :: Symbol) (ifmt :: Format) (ivfmt :: Format) Source #
CreateInfo | |
|
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 #
ENUM
newtype CreateFlagBits #
Instances
pattern CreateFlagBitsMaxEnum :: CreateFlagBits #
pattern CreateFlagsZero :: CreateFlagBits #
type CreateFlags = CreateFlagBits #
pattern TypeMaxEnum :: Type #
pattern CreateFragmentDensityMapDynamicBitExt :: CreateFlagBits #
pattern TypeCubeArray :: Type #
pattern Type2dArray :: Type #
pattern Type1dArray :: Type #