Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- allocate :: forall (mn :: Maybe Type) (ma :: Maybe Type). WithPoked (M mn) => D -> AllocateInfo mn -> M A ma -> IO M
- reallocate :: forall (mn :: Maybe Type) (ma :: Maybe Type). WithPoked (M mn) => D -> AllocateInfo mn -> M A ma -> M -> IO ()
- reallocate' :: forall (mn :: Maybe Type) (ma :: Maybe Type) a. WithPoked (M mn) => D -> AllocateInfo mn -> M A ma -> M -> IO a -> IO ()
- free :: forall (mf :: Maybe Type). D -> M -> M A mf -> IO ()
- data M
- data AllocateInfo (mn :: Maybe Type) = AllocateInfo {}
- data Group s k
- group :: forall (mf :: Maybe Type) k a. D -> M A mf -> (forall s. Group s k -> IO a) -> IO a
- 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)
- free' :: forall k smng (mc :: Maybe Type). Ord k => D -> Group smng k -> k -> M A mc -> IO (Either String ())
- lookup :: Ord k => Group sm k -> k -> IO (Maybe M)
- map :: D -> M -> Size -> Size -> MapFlags -> IO (Ptr a)
- unmap :: D -> M -> IO ()
- newtype MapFlags = MapFlags Word32
- data Requirements = Requirements {}
- data Barrier (mn :: Maybe Type) = Barrier {}
- data MType = MType {}
- data TypeBits
- data TypeIndex
- elemTypeIndex :: TypeIndex -> TypeBits -> Bool
- data Heap = Heap {}
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 #
data AllocateInfo (mn :: Maybe Type) Source #
Instances
Show (M mn) => Show (AllocateInfo mn) Source # | |
Defined in Gpu.Vulkan.Memory.Middle.Internal showsPrec :: Int -> AllocateInfo mn -> ShowS # show :: AllocateInfo mn -> String # showList :: [AllocateInfo mn] -> ShowS # |
Destruction Group
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 #
MAP AND UNMNAP
Instances
Storable MapFlags Source # | |
Defined in Gpu.Vulkan.Memory.Middle.Internal | |
Bits MapFlags Source # | |
Defined in Gpu.Vulkan.Memory.Middle.Internal (.&.) :: MapFlags -> MapFlags -> MapFlags # (.|.) :: MapFlags -> MapFlags -> MapFlags # xor :: MapFlags -> MapFlags -> MapFlags # complement :: MapFlags -> MapFlags # shift :: MapFlags -> Int -> MapFlags # rotate :: MapFlags -> Int -> MapFlags # setBit :: MapFlags -> Int -> MapFlags # clearBit :: MapFlags -> Int -> MapFlags # complementBit :: MapFlags -> Int -> MapFlags # testBit :: MapFlags -> Int -> Bool # bitSizeMaybe :: MapFlags -> Maybe Int # isSigned :: MapFlags -> Bool # shiftL :: MapFlags -> Int -> MapFlags # unsafeShiftL :: MapFlags -> Int -> MapFlags # shiftR :: MapFlags -> Int -> MapFlags # unsafeShiftR :: MapFlags -> Int -> MapFlags # rotateL :: MapFlags -> Int -> MapFlags # | |
Show MapFlags Source # | |
Default MapFlags Source # | |
Defined in Gpu.Vulkan.Memory.Middle.Internal | |
Eq MapFlags Source # | |
REQUIREMENTS AND BARRIER
data Requirements Source #
Instances
Show Requirements Source # | |
Defined in Gpu.Vulkan.Memory.Middle.Internal showsPrec :: Int -> Requirements -> ShowS # show :: Requirements -> String # showList :: [Requirements] -> ShowS # |
MEMORY TYPE
Instances
Bits TypeBits Source # | |
Defined in Gpu.Vulkan.Memory.Middle.Internal (.&.) :: TypeBits -> TypeBits -> TypeBits # (.|.) :: TypeBits -> TypeBits -> TypeBits # xor :: TypeBits -> TypeBits -> TypeBits # complement :: TypeBits -> TypeBits # shift :: TypeBits -> Int -> TypeBits # rotate :: TypeBits -> Int -> TypeBits # setBit :: TypeBits -> Int -> TypeBits # clearBit :: TypeBits -> Int -> TypeBits # complementBit :: TypeBits -> Int -> TypeBits # testBit :: TypeBits -> Int -> Bool # bitSizeMaybe :: TypeBits -> Maybe Int # isSigned :: TypeBits -> Bool # shiftL :: TypeBits -> Int -> TypeBits # unsafeShiftL :: TypeBits -> Int -> TypeBits # shiftR :: TypeBits -> Int -> TypeBits # unsafeShiftR :: TypeBits -> Int -> TypeBits # rotateL :: TypeBits -> Int -> TypeBits # | |
FiniteBits TypeBits Source # | |
Defined in Gpu.Vulkan.Memory.Middle.Internal finiteBitSize :: TypeBits -> Int # countLeadingZeros :: TypeBits -> Int # countTrailingZeros :: TypeBits -> Int # | |
Show TypeBits Source # | |
Eq TypeBits Source # | |
Instances
Enum TypeIndex Source # | |
Defined in Gpu.Vulkan.Memory.Middle.Internal succ :: TypeIndex -> TypeIndex # pred :: TypeIndex -> TypeIndex # fromEnum :: TypeIndex -> Int # enumFrom :: TypeIndex -> [TypeIndex] # enumFromThen :: TypeIndex -> TypeIndex -> [TypeIndex] # enumFromTo :: TypeIndex -> TypeIndex -> [TypeIndex] # enumFromThenTo :: TypeIndex -> TypeIndex -> TypeIndex -> [TypeIndex] # | |
Num TypeIndex Source # | |
Defined in Gpu.Vulkan.Memory.Middle.Internal | |
Integral TypeIndex Source # | |
Defined in Gpu.Vulkan.Memory.Middle.Internal | |
Real TypeIndex Source # | |
Defined in Gpu.Vulkan.Memory.Middle.Internal toRational :: TypeIndex -> Rational # | |
Show TypeIndex Source # | |
Eq TypeIndex Source # | |
Ord TypeIndex Source # | |
Defined in Gpu.Vulkan.Memory.Middle.Internal |