{-# language CPP #-}
module Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer ( getAndroidHardwareBufferPropertiesANDROID
, getMemoryAndroidHardwareBufferANDROID
, ImportAndroidHardwareBufferInfoANDROID(..)
, AndroidHardwareBufferUsageANDROID(..)
, AndroidHardwareBufferPropertiesANDROID(..)
, MemoryGetAndroidHardwareBufferInfoANDROID(..)
, AndroidHardwareBufferFormatPropertiesANDROID(..)
, ExternalFormatANDROID(..)
, AndroidHardwareBufferFormatProperties2ANDROID(..)
, ANDROID_EXTERNAL_MEMORY_ANDROID_HARDWARE_BUFFER_SPEC_VERSION
, pattern ANDROID_EXTERNAL_MEMORY_ANDROID_HARDWARE_BUFFER_SPEC_VERSION
, ANDROID_EXTERNAL_MEMORY_ANDROID_HARDWARE_BUFFER_EXTENSION_NAME
, pattern ANDROID_EXTERNAL_MEMORY_ANDROID_HARDWARE_BUFFER_EXTENSION_NAME
, AHardwareBuffer
) where
import Vulkan.Internal.Utils (traceAroundEvent)
import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Data.Typeable (eqT)
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Marshal.Alloc (callocBytes)
import Foreign.Marshal.Alloc (free)
import GHC.Base (when)
import GHC.IO (throwIO)
import GHC.Ptr (castPtr)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Control.Monad.IO.Class (MonadIO)
import Data.String (IsString)
import Data.Type.Equality ((:~:)(Refl))
import Data.Typeable (Typeable)
import Foreign.Storable (Storable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import qualified Foreign.Storable (Storable(..))
import GHC.Generics (Generic)
import GHC.IO.Exception (IOErrorType(..))
import GHC.IO.Exception (IOException(..))
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import Data.Word (Word32)
import Data.Word (Word64)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Vulkan.CStruct.Extends (forgetExtensions)
import {-# SOURCE #-} Vulkan.Extensions.VK_ANDROID_external_format_resolve (AndroidHardwareBufferFormatResolvePropertiesANDROID)
import Vulkan.CStruct.Extends (Chain)
import Vulkan.Core11.Enums.ChromaLocation (ChromaLocation)
import Vulkan.Core10.ImageView (ComponentMapping)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Core10.Handles (Device(Device))
import Vulkan.Dynamic (DeviceCmds(pVkGetAndroidHardwareBufferPropertiesANDROID))
import Vulkan.Dynamic (DeviceCmds(pVkGetMemoryAndroidHardwareBufferANDROID))
import Vulkan.Core10.Handles (DeviceMemory)
import Vulkan.Core10.FundamentalTypes (DeviceSize)
import Vulkan.Core10.Handles (Device_T)
import Vulkan.CStruct.Extends (Extends)
import Vulkan.CStruct.Extends (Extendss)
import Vulkan.CStruct.Extends (Extensible(..))
import Vulkan.Core10.Enums.Format (Format)
import Vulkan.Core10.Enums.FormatFeatureFlagBits (FormatFeatureFlags)
import Vulkan.Core13.Enums.FormatFeatureFlags2 (FormatFeatureFlags2)
import Vulkan.CStruct.Extends (PeekChain)
import Vulkan.CStruct.Extends (PeekChain(..))
import Vulkan.CStruct.Extends (PokeChain)
import Vulkan.CStruct.Extends (PokeChain(..))
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Core11.Enums.SamplerYcbcrModelConversion (SamplerYcbcrModelConversion)
import Vulkan.Core11.Enums.SamplerYcbcrRange (SamplerYcbcrRange)
import Vulkan.CStruct.Extends (SomeStruct)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Exception (VulkanException(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_ANDROID_HARDWARE_BUFFER_FORMAT_PROPERTIES_2_ANDROID))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_ANDROID_HARDWARE_BUFFER_FORMAT_PROPERTIES_ANDROID))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_ANDROID_HARDWARE_BUFFER_PROPERTIES_ANDROID))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_ANDROID_HARDWARE_BUFFER_USAGE_ANDROID))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_EXTERNAL_FORMAT_ANDROID))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_IMPORT_ANDROID_HARDWARE_BUFFER_INFO_ANDROID))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_MEMORY_GET_ANDROID_HARDWARE_BUFFER_INFO_ANDROID))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkGetAndroidHardwareBufferPropertiesANDROID
:: FunPtr (Ptr Device_T -> Ptr AHardwareBuffer -> Ptr (SomeStruct AndroidHardwareBufferPropertiesANDROID) -> IO Result) -> Ptr Device_T -> Ptr AHardwareBuffer -> Ptr (SomeStruct AndroidHardwareBufferPropertiesANDROID) -> IO Result
getAndroidHardwareBufferPropertiesANDROID :: forall a io
. ( Extendss AndroidHardwareBufferPropertiesANDROID a
, PokeChain a
, PeekChain a
, MonadIO io )
=>
Device
->
(Ptr AHardwareBuffer)
-> io (AndroidHardwareBufferPropertiesANDROID a)
getAndroidHardwareBufferPropertiesANDROID :: forall (a :: [*]) (io :: * -> *).
(Extendss AndroidHardwareBufferPropertiesANDROID a, PokeChain a,
PeekChain a, MonadIO io) =>
Device
-> Ptr AHardwareBuffer
-> io (AndroidHardwareBufferPropertiesANDROID a)
getAndroidHardwareBufferPropertiesANDROID Device
device
Ptr AHardwareBuffer
buffer = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
let vkGetAndroidHardwareBufferPropertiesANDROIDPtr :: FunPtr
(Ptr Device_T
-> Ptr AHardwareBuffer
-> ("pProperties"
::: Ptr (SomeStruct AndroidHardwareBufferPropertiesANDROID))
-> IO Result)
vkGetAndroidHardwareBufferPropertiesANDROIDPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> Ptr AHardwareBuffer
-> ("pProperties"
::: Ptr (SomeStruct AndroidHardwareBufferPropertiesANDROID))
-> IO Result)
pVkGetAndroidHardwareBufferPropertiesANDROID (case Device
device of Device{DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds :: DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr Device_T
-> Ptr AHardwareBuffer
-> ("pProperties"
::: Ptr (SomeStruct AndroidHardwareBufferPropertiesANDROID))
-> IO Result)
vkGetAndroidHardwareBufferPropertiesANDROIDPtr forall a. Eq a => a -> a -> Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkGetAndroidHardwareBufferPropertiesANDROID is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkGetAndroidHardwareBufferPropertiesANDROID' :: Ptr Device_T
-> Ptr AHardwareBuffer
-> ("pProperties"
::: Ptr (SomeStruct AndroidHardwareBufferPropertiesANDROID))
-> IO Result
vkGetAndroidHardwareBufferPropertiesANDROID' = FunPtr
(Ptr Device_T
-> Ptr AHardwareBuffer
-> ("pProperties"
::: Ptr (SomeStruct AndroidHardwareBufferPropertiesANDROID))
-> IO Result)
-> Ptr Device_T
-> Ptr AHardwareBuffer
-> ("pProperties"
::: Ptr (SomeStruct AndroidHardwareBufferPropertiesANDROID))
-> IO Result
mkVkGetAndroidHardwareBufferPropertiesANDROID FunPtr
(Ptr Device_T
-> Ptr AHardwareBuffer
-> ("pProperties"
::: Ptr (SomeStruct AndroidHardwareBufferPropertiesANDROID))
-> IO Result)
vkGetAndroidHardwareBufferPropertiesANDROIDPtr
Ptr (AndroidHardwareBufferPropertiesANDROID a)
pPProperties <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @(AndroidHardwareBufferPropertiesANDROID _))
Result
r <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetAndroidHardwareBufferPropertiesANDROID" (Ptr Device_T
-> Ptr AHardwareBuffer
-> ("pProperties"
::: Ptr (SomeStruct AndroidHardwareBufferPropertiesANDROID))
-> IO Result
vkGetAndroidHardwareBufferPropertiesANDROID'
(Device -> Ptr Device_T
deviceHandle (Device
device))
(Ptr AHardwareBuffer
buffer)
(forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (AndroidHardwareBufferPropertiesANDROID a)
pPProperties)))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
AndroidHardwareBufferPropertiesANDROID a
pProperties <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @(AndroidHardwareBufferPropertiesANDROID _) Ptr (AndroidHardwareBufferPropertiesANDROID a)
pPProperties
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ (AndroidHardwareBufferPropertiesANDROID a
pProperties)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkGetMemoryAndroidHardwareBufferANDROID
:: FunPtr (Ptr Device_T -> Ptr MemoryGetAndroidHardwareBufferInfoANDROID -> Ptr (Ptr AHardwareBuffer) -> IO Result) -> Ptr Device_T -> Ptr MemoryGetAndroidHardwareBufferInfoANDROID -> Ptr (Ptr AHardwareBuffer) -> IO Result
getMemoryAndroidHardwareBufferANDROID :: forall io
. (MonadIO io)
=>
Device
->
MemoryGetAndroidHardwareBufferInfoANDROID
-> io (Ptr AHardwareBuffer)
getMemoryAndroidHardwareBufferANDROID :: forall (io :: * -> *).
MonadIO io =>
Device
-> MemoryGetAndroidHardwareBufferInfoANDROID
-> io (Ptr AHardwareBuffer)
getMemoryAndroidHardwareBufferANDROID Device
device MemoryGetAndroidHardwareBufferInfoANDROID
info = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
let vkGetMemoryAndroidHardwareBufferANDROIDPtr :: FunPtr
(Ptr Device_T
-> ("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID)
-> ("pBuffer" ::: Ptr (Ptr AHardwareBuffer))
-> IO Result)
vkGetMemoryAndroidHardwareBufferANDROIDPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> ("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID)
-> ("pBuffer" ::: Ptr (Ptr AHardwareBuffer))
-> IO Result)
pVkGetMemoryAndroidHardwareBufferANDROID (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr Device_T
-> ("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID)
-> ("pBuffer" ::: Ptr (Ptr AHardwareBuffer))
-> IO Result)
vkGetMemoryAndroidHardwareBufferANDROIDPtr forall a. Eq a => a -> a -> Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkGetMemoryAndroidHardwareBufferANDROID is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkGetMemoryAndroidHardwareBufferANDROID' :: Ptr Device_T
-> ("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID)
-> ("pBuffer" ::: Ptr (Ptr AHardwareBuffer))
-> IO Result
vkGetMemoryAndroidHardwareBufferANDROID' = FunPtr
(Ptr Device_T
-> ("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID)
-> ("pBuffer" ::: Ptr (Ptr AHardwareBuffer))
-> IO Result)
-> Ptr Device_T
-> ("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID)
-> ("pBuffer" ::: Ptr (Ptr AHardwareBuffer))
-> IO Result
mkVkGetMemoryAndroidHardwareBufferANDROID FunPtr
(Ptr Device_T
-> ("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID)
-> ("pBuffer" ::: Ptr (Ptr AHardwareBuffer))
-> IO Result)
vkGetMemoryAndroidHardwareBufferANDROIDPtr
"pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID
pInfo <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (MemoryGetAndroidHardwareBufferInfoANDROID
info)
"pBuffer" ::: Ptr (Ptr AHardwareBuffer)
pPBuffer <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (forall a. Int -> IO (Ptr a)
callocBytes @(Ptr AHardwareBuffer) Int
8) forall a. Ptr a -> IO ()
free
Result
r <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetMemoryAndroidHardwareBufferANDROID" (Ptr Device_T
-> ("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID)
-> ("pBuffer" ::: Ptr (Ptr AHardwareBuffer))
-> IO Result
vkGetMemoryAndroidHardwareBufferANDROID'
(Device -> Ptr Device_T
deviceHandle (Device
device))
"pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID
pInfo
("pBuffer" ::: Ptr (Ptr AHardwareBuffer)
pPBuffer))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
Ptr AHardwareBuffer
pBuffer <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> IO a
peek @(Ptr AHardwareBuffer) "pBuffer" ::: Ptr (Ptr AHardwareBuffer)
pPBuffer
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ (Ptr AHardwareBuffer
pBuffer)
data ImportAndroidHardwareBufferInfoANDROID = ImportAndroidHardwareBufferInfoANDROID
{
ImportAndroidHardwareBufferInfoANDROID -> Ptr AHardwareBuffer
buffer :: Ptr AHardwareBuffer }
deriving (Typeable, ImportAndroidHardwareBufferInfoANDROID
-> ImportAndroidHardwareBufferInfoANDROID -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImportAndroidHardwareBufferInfoANDROID
-> ImportAndroidHardwareBufferInfoANDROID -> Bool
$c/= :: ImportAndroidHardwareBufferInfoANDROID
-> ImportAndroidHardwareBufferInfoANDROID -> Bool
== :: ImportAndroidHardwareBufferInfoANDROID
-> ImportAndroidHardwareBufferInfoANDROID -> Bool
$c== :: ImportAndroidHardwareBufferInfoANDROID
-> ImportAndroidHardwareBufferInfoANDROID -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ImportAndroidHardwareBufferInfoANDROID)
#endif
deriving instance Show ImportAndroidHardwareBufferInfoANDROID
instance ToCStruct ImportAndroidHardwareBufferInfoANDROID where
withCStruct :: forall b.
ImportAndroidHardwareBufferInfoANDROID
-> (Ptr ImportAndroidHardwareBufferInfoANDROID -> IO b) -> IO b
withCStruct ImportAndroidHardwareBufferInfoANDROID
x Ptr ImportAndroidHardwareBufferInfoANDROID -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr ImportAndroidHardwareBufferInfoANDROID
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ImportAndroidHardwareBufferInfoANDROID
p ImportAndroidHardwareBufferInfoANDROID
x (Ptr ImportAndroidHardwareBufferInfoANDROID -> IO b
f Ptr ImportAndroidHardwareBufferInfoANDROID
p)
pokeCStruct :: forall b.
Ptr ImportAndroidHardwareBufferInfoANDROID
-> ImportAndroidHardwareBufferInfoANDROID -> IO b -> IO b
pokeCStruct Ptr ImportAndroidHardwareBufferInfoANDROID
p ImportAndroidHardwareBufferInfoANDROID{Ptr AHardwareBuffer
buffer :: Ptr AHardwareBuffer
$sel:buffer:ImportAndroidHardwareBufferInfoANDROID :: ImportAndroidHardwareBufferInfoANDROID -> Ptr AHardwareBuffer
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImportAndroidHardwareBufferInfoANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMPORT_ANDROID_HARDWARE_BUFFER_INFO_ANDROID)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImportAndroidHardwareBufferInfoANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImportAndroidHardwareBufferInfoANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr (Ptr AHardwareBuffer))) (Ptr AHardwareBuffer
buffer)
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr ImportAndroidHardwareBufferInfoANDROID -> IO b -> IO b
pokeZeroCStruct Ptr ImportAndroidHardwareBufferInfoANDROID
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImportAndroidHardwareBufferInfoANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMPORT_ANDROID_HARDWARE_BUFFER_INFO_ANDROID)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImportAndroidHardwareBufferInfoANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImportAndroidHardwareBufferInfoANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr (Ptr AHardwareBuffer))) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct ImportAndroidHardwareBufferInfoANDROID where
peekCStruct :: Ptr ImportAndroidHardwareBufferInfoANDROID
-> IO ImportAndroidHardwareBufferInfoANDROID
peekCStruct Ptr ImportAndroidHardwareBufferInfoANDROID
p = do
Ptr AHardwareBuffer
buffer <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr AHardwareBuffer) ((Ptr ImportAndroidHardwareBufferInfoANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr (Ptr AHardwareBuffer)))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Ptr AHardwareBuffer -> ImportAndroidHardwareBufferInfoANDROID
ImportAndroidHardwareBufferInfoANDROID
Ptr AHardwareBuffer
buffer
instance Storable ImportAndroidHardwareBufferInfoANDROID where
sizeOf :: ImportAndroidHardwareBufferInfoANDROID -> Int
sizeOf ~ImportAndroidHardwareBufferInfoANDROID
_ = Int
24
alignment :: ImportAndroidHardwareBufferInfoANDROID -> Int
alignment ~ImportAndroidHardwareBufferInfoANDROID
_ = Int
8
peek :: Ptr ImportAndroidHardwareBufferInfoANDROID
-> IO ImportAndroidHardwareBufferInfoANDROID
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr ImportAndroidHardwareBufferInfoANDROID
-> ImportAndroidHardwareBufferInfoANDROID -> IO ()
poke Ptr ImportAndroidHardwareBufferInfoANDROID
ptr ImportAndroidHardwareBufferInfoANDROID
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ImportAndroidHardwareBufferInfoANDROID
ptr ImportAndroidHardwareBufferInfoANDROID
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero ImportAndroidHardwareBufferInfoANDROID where
zero :: ImportAndroidHardwareBufferInfoANDROID
zero = Ptr AHardwareBuffer -> ImportAndroidHardwareBufferInfoANDROID
ImportAndroidHardwareBufferInfoANDROID
forall a. Zero a => a
zero
data AndroidHardwareBufferUsageANDROID = AndroidHardwareBufferUsageANDROID
{
AndroidHardwareBufferUsageANDROID -> Word64
androidHardwareBufferUsage :: Word64 }
deriving (Typeable, AndroidHardwareBufferUsageANDROID
-> AndroidHardwareBufferUsageANDROID -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AndroidHardwareBufferUsageANDROID
-> AndroidHardwareBufferUsageANDROID -> Bool
$c/= :: AndroidHardwareBufferUsageANDROID
-> AndroidHardwareBufferUsageANDROID -> Bool
== :: AndroidHardwareBufferUsageANDROID
-> AndroidHardwareBufferUsageANDROID -> Bool
$c== :: AndroidHardwareBufferUsageANDROID
-> AndroidHardwareBufferUsageANDROID -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (AndroidHardwareBufferUsageANDROID)
#endif
deriving instance Show AndroidHardwareBufferUsageANDROID
instance ToCStruct AndroidHardwareBufferUsageANDROID where
withCStruct :: forall b.
AndroidHardwareBufferUsageANDROID
-> (Ptr AndroidHardwareBufferUsageANDROID -> IO b) -> IO b
withCStruct AndroidHardwareBufferUsageANDROID
x Ptr AndroidHardwareBufferUsageANDROID -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr AndroidHardwareBufferUsageANDROID
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr AndroidHardwareBufferUsageANDROID
p AndroidHardwareBufferUsageANDROID
x (Ptr AndroidHardwareBufferUsageANDROID -> IO b
f Ptr AndroidHardwareBufferUsageANDROID
p)
pokeCStruct :: forall b.
Ptr AndroidHardwareBufferUsageANDROID
-> AndroidHardwareBufferUsageANDROID -> IO b -> IO b
pokeCStruct Ptr AndroidHardwareBufferUsageANDROID
p AndroidHardwareBufferUsageANDROID{Word64
androidHardwareBufferUsage :: Word64
$sel:androidHardwareBufferUsage:AndroidHardwareBufferUsageANDROID :: AndroidHardwareBufferUsageANDROID -> Word64
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferUsageANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ANDROID_HARDWARE_BUFFER_USAGE_ANDROID)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferUsageANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferUsageANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word64)) (Word64
androidHardwareBufferUsage)
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr AndroidHardwareBufferUsageANDROID -> IO b -> IO b
pokeZeroCStruct Ptr AndroidHardwareBufferUsageANDROID
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferUsageANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ANDROID_HARDWARE_BUFFER_USAGE_ANDROID)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferUsageANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferUsageANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word64)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct AndroidHardwareBufferUsageANDROID where
peekCStruct :: Ptr AndroidHardwareBufferUsageANDROID
-> IO AndroidHardwareBufferUsageANDROID
peekCStruct Ptr AndroidHardwareBufferUsageANDROID
p = do
Word64
androidHardwareBufferUsage <- forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr AndroidHardwareBufferUsageANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word64))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Word64 -> AndroidHardwareBufferUsageANDROID
AndroidHardwareBufferUsageANDROID
Word64
androidHardwareBufferUsage
instance Storable AndroidHardwareBufferUsageANDROID where
sizeOf :: AndroidHardwareBufferUsageANDROID -> Int
sizeOf ~AndroidHardwareBufferUsageANDROID
_ = Int
24
alignment :: AndroidHardwareBufferUsageANDROID -> Int
alignment ~AndroidHardwareBufferUsageANDROID
_ = Int
8
peek :: Ptr AndroidHardwareBufferUsageANDROID
-> IO AndroidHardwareBufferUsageANDROID
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr AndroidHardwareBufferUsageANDROID
-> AndroidHardwareBufferUsageANDROID -> IO ()
poke Ptr AndroidHardwareBufferUsageANDROID
ptr AndroidHardwareBufferUsageANDROID
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr AndroidHardwareBufferUsageANDROID
ptr AndroidHardwareBufferUsageANDROID
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero AndroidHardwareBufferUsageANDROID where
zero :: AndroidHardwareBufferUsageANDROID
zero = Word64 -> AndroidHardwareBufferUsageANDROID
AndroidHardwareBufferUsageANDROID
forall a. Zero a => a
zero
data AndroidHardwareBufferPropertiesANDROID (es :: [Type]) = AndroidHardwareBufferPropertiesANDROID
{
forall (es :: [*]).
AndroidHardwareBufferPropertiesANDROID es -> Chain es
next :: Chain es
,
forall (es :: [*]).
AndroidHardwareBufferPropertiesANDROID es -> Word64
allocationSize :: DeviceSize
,
forall (es :: [*]).
AndroidHardwareBufferPropertiesANDROID es -> Word32
memoryTypeBits :: Word32
}
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (AndroidHardwareBufferPropertiesANDROID (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (AndroidHardwareBufferPropertiesANDROID es)
instance Extensible AndroidHardwareBufferPropertiesANDROID where
extensibleTypeName :: String
extensibleTypeName = String
"AndroidHardwareBufferPropertiesANDROID"
setNext :: forall (ds :: [*]) (es :: [*]).
AndroidHardwareBufferPropertiesANDROID ds
-> Chain es -> AndroidHardwareBufferPropertiesANDROID es
setNext AndroidHardwareBufferPropertiesANDROID{Word32
Word64
Chain ds
memoryTypeBits :: Word32
allocationSize :: Word64
next :: Chain ds
$sel:memoryTypeBits:AndroidHardwareBufferPropertiesANDROID :: forall (es :: [*]).
AndroidHardwareBufferPropertiesANDROID es -> Word32
$sel:allocationSize:AndroidHardwareBufferPropertiesANDROID :: forall (es :: [*]).
AndroidHardwareBufferPropertiesANDROID es -> Word64
$sel:next:AndroidHardwareBufferPropertiesANDROID :: forall (es :: [*]).
AndroidHardwareBufferPropertiesANDROID es -> Chain es
..} Chain es
next' = AndroidHardwareBufferPropertiesANDROID{$sel:next:AndroidHardwareBufferPropertiesANDROID :: Chain es
next = Chain es
next', Word32
Word64
memoryTypeBits :: Word32
allocationSize :: Word64
$sel:memoryTypeBits:AndroidHardwareBufferPropertiesANDROID :: Word32
$sel:allocationSize:AndroidHardwareBufferPropertiesANDROID :: Word64
..}
getNext :: forall (es :: [*]).
AndroidHardwareBufferPropertiesANDROID es -> Chain es
getNext AndroidHardwareBufferPropertiesANDROID{Word32
Word64
Chain es
memoryTypeBits :: Word32
allocationSize :: Word64
next :: Chain es
$sel:memoryTypeBits:AndroidHardwareBufferPropertiesANDROID :: forall (es :: [*]).
AndroidHardwareBufferPropertiesANDROID es -> Word32
$sel:allocationSize:AndroidHardwareBufferPropertiesANDROID :: forall (es :: [*]).
AndroidHardwareBufferPropertiesANDROID es -> Word64
$sel:next:AndroidHardwareBufferPropertiesANDROID :: forall (es :: [*]).
AndroidHardwareBufferPropertiesANDROID es -> Chain es
..} = Chain es
next
extends :: forall e b proxy. Typeable e => proxy e -> (Extends AndroidHardwareBufferPropertiesANDROID e => b) -> Maybe b
extends :: forall e b (proxy :: * -> *).
Typeable e =>
proxy e
-> (Extends AndroidHardwareBufferPropertiesANDROID e => b)
-> Maybe b
extends proxy e
_ Extends AndroidHardwareBufferPropertiesANDROID e => b
f
| Just e :~: AndroidHardwareBufferFormatResolvePropertiesANDROID
Refl <- forall {k} (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @AndroidHardwareBufferFormatResolvePropertiesANDROID = forall a. a -> Maybe a
Just Extends AndroidHardwareBufferPropertiesANDROID e => b
f
| Just e :~: AndroidHardwareBufferFormatProperties2ANDROID
Refl <- forall {k} (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @AndroidHardwareBufferFormatProperties2ANDROID = forall a. a -> Maybe a
Just Extends AndroidHardwareBufferPropertiesANDROID e => b
f
| Just e :~: AndroidHardwareBufferFormatPropertiesANDROID
Refl <- forall {k} (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @AndroidHardwareBufferFormatPropertiesANDROID = forall a. a -> Maybe a
Just Extends AndroidHardwareBufferPropertiesANDROID e => b
f
| Bool
otherwise = forall a. Maybe a
Nothing
instance ( Extendss AndroidHardwareBufferPropertiesANDROID es
, PokeChain es ) => ToCStruct (AndroidHardwareBufferPropertiesANDROID es) where
withCStruct :: forall b.
AndroidHardwareBufferPropertiesANDROID es
-> (Ptr (AndroidHardwareBufferPropertiesANDROID es) -> IO b)
-> IO b
withCStruct AndroidHardwareBufferPropertiesANDROID es
x Ptr (AndroidHardwareBufferPropertiesANDROID es) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \Ptr (AndroidHardwareBufferPropertiesANDROID es)
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (AndroidHardwareBufferPropertiesANDROID es)
p AndroidHardwareBufferPropertiesANDROID es
x (Ptr (AndroidHardwareBufferPropertiesANDROID es) -> IO b
f Ptr (AndroidHardwareBufferPropertiesANDROID es)
p)
pokeCStruct :: forall b.
Ptr (AndroidHardwareBufferPropertiesANDROID es)
-> AndroidHardwareBufferPropertiesANDROID es -> IO b -> IO b
pokeCStruct Ptr (AndroidHardwareBufferPropertiesANDROID es)
p AndroidHardwareBufferPropertiesANDROID{Word32
Word64
Chain es
memoryTypeBits :: Word32
allocationSize :: Word64
next :: Chain es
$sel:memoryTypeBits:AndroidHardwareBufferPropertiesANDROID :: forall (es :: [*]).
AndroidHardwareBufferPropertiesANDROID es -> Word32
$sel:allocationSize:AndroidHardwareBufferPropertiesANDROID :: forall (es :: [*]).
AndroidHardwareBufferPropertiesANDROID es -> Word64
$sel:next:AndroidHardwareBufferPropertiesANDROID :: forall (es :: [*]).
AndroidHardwareBufferPropertiesANDROID es -> Chain es
..} IO b
f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AndroidHardwareBufferPropertiesANDROID es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ANDROID_HARDWARE_BUFFER_PROPERTIES_ANDROID)
Ptr ()
pNext'' <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. Ptr a -> Ptr b
castPtr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AndroidHardwareBufferPropertiesANDROID es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) Ptr ()
pNext''
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AndroidHardwareBufferPropertiesANDROID es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceSize)) (Word64
allocationSize)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AndroidHardwareBufferPropertiesANDROID es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word32)) (Word32
memoryTypeBits)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ IO b
f
cStructSize :: Int
cStructSize = Int
32
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr (AndroidHardwareBufferPropertiesANDROID es) -> IO b -> IO b
pokeZeroCStruct Ptr (AndroidHardwareBufferPropertiesANDROID es)
p IO b
f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AndroidHardwareBufferPropertiesANDROID es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ANDROID_HARDWARE_BUFFER_PROPERTIES_ANDROID)
Ptr ()
pNext' <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. Ptr a -> Ptr b
castPtr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AndroidHardwareBufferPropertiesANDROID es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) Ptr ()
pNext'
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AndroidHardwareBufferPropertiesANDROID es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceSize)) (forall a. Zero a => a
zero)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AndroidHardwareBufferPropertiesANDROID es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ IO b
f
instance ( Extendss AndroidHardwareBufferPropertiesANDROID es
, PeekChain es ) => FromCStruct (AndroidHardwareBufferPropertiesANDROID es) where
peekCStruct :: Ptr (AndroidHardwareBufferPropertiesANDROID es)
-> IO (AndroidHardwareBufferPropertiesANDROID es)
peekCStruct Ptr (AndroidHardwareBufferPropertiesANDROID es)
p = do
Ptr ()
pNext <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (AndroidHardwareBufferPropertiesANDROID es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ())))
Chain es
next <- forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es)
peekChain (forall a b. Ptr a -> Ptr b
castPtr Ptr ()
pNext)
Word64
allocationSize <- forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr (AndroidHardwareBufferPropertiesANDROID es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceSize))
Word32
memoryTypeBits <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (AndroidHardwareBufferPropertiesANDROID es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word32))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (es :: [*]).
Chain es
-> Word64 -> Word32 -> AndroidHardwareBufferPropertiesANDROID es
AndroidHardwareBufferPropertiesANDROID
Chain es
next Word64
allocationSize Word32
memoryTypeBits
instance es ~ '[] => Zero (AndroidHardwareBufferPropertiesANDROID es) where
zero :: AndroidHardwareBufferPropertiesANDROID es
zero = forall (es :: [*]).
Chain es
-> Word64 -> Word32 -> AndroidHardwareBufferPropertiesANDROID es
AndroidHardwareBufferPropertiesANDROID
()
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data MemoryGetAndroidHardwareBufferInfoANDROID = MemoryGetAndroidHardwareBufferInfoANDROID
{
MemoryGetAndroidHardwareBufferInfoANDROID -> DeviceMemory
memory :: DeviceMemory }
deriving (Typeable, MemoryGetAndroidHardwareBufferInfoANDROID
-> MemoryGetAndroidHardwareBufferInfoANDROID -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MemoryGetAndroidHardwareBufferInfoANDROID
-> MemoryGetAndroidHardwareBufferInfoANDROID -> Bool
$c/= :: MemoryGetAndroidHardwareBufferInfoANDROID
-> MemoryGetAndroidHardwareBufferInfoANDROID -> Bool
== :: MemoryGetAndroidHardwareBufferInfoANDROID
-> MemoryGetAndroidHardwareBufferInfoANDROID -> Bool
$c== :: MemoryGetAndroidHardwareBufferInfoANDROID
-> MemoryGetAndroidHardwareBufferInfoANDROID -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (MemoryGetAndroidHardwareBufferInfoANDROID)
#endif
deriving instance Show MemoryGetAndroidHardwareBufferInfoANDROID
instance ToCStruct MemoryGetAndroidHardwareBufferInfoANDROID where
withCStruct :: forall b.
MemoryGetAndroidHardwareBufferInfoANDROID
-> (("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID)
-> IO b)
-> IO b
withCStruct MemoryGetAndroidHardwareBufferInfoANDROID
x ("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \"pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID
p MemoryGetAndroidHardwareBufferInfoANDROID
x (("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID) -> IO b
f "pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID
p)
pokeCStruct :: forall b.
("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID)
-> MemoryGetAndroidHardwareBufferInfoANDROID -> IO b -> IO b
pokeCStruct "pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID
p MemoryGetAndroidHardwareBufferInfoANDROID{DeviceMemory
memory :: DeviceMemory
$sel:memory:MemoryGetAndroidHardwareBufferInfoANDROID :: MemoryGetAndroidHardwareBufferInfoANDROID -> DeviceMemory
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MEMORY_GET_ANDROID_HARDWARE_BUFFER_INFO_ANDROID)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceMemory)) (DeviceMemory
memory)
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID)
-> IO b -> IO b
pokeZeroCStruct "pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MEMORY_GET_ANDROID_HARDWARE_BUFFER_INFO_ANDROID)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceMemory)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct MemoryGetAndroidHardwareBufferInfoANDROID where
peekCStruct :: ("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID)
-> IO MemoryGetAndroidHardwareBufferInfoANDROID
peekCStruct "pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID
p = do
DeviceMemory
memory <- forall a. Storable a => Ptr a -> IO a
peek @DeviceMemory (("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceMemory))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ DeviceMemory -> MemoryGetAndroidHardwareBufferInfoANDROID
MemoryGetAndroidHardwareBufferInfoANDROID
DeviceMemory
memory
instance Storable MemoryGetAndroidHardwareBufferInfoANDROID where
sizeOf :: MemoryGetAndroidHardwareBufferInfoANDROID -> Int
sizeOf ~MemoryGetAndroidHardwareBufferInfoANDROID
_ = Int
24
alignment :: MemoryGetAndroidHardwareBufferInfoANDROID -> Int
alignment ~MemoryGetAndroidHardwareBufferInfoANDROID
_ = Int
8
peek :: ("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID)
-> IO MemoryGetAndroidHardwareBufferInfoANDROID
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID)
-> MemoryGetAndroidHardwareBufferInfoANDROID -> IO ()
poke "pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID
ptr MemoryGetAndroidHardwareBufferInfoANDROID
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID
ptr MemoryGetAndroidHardwareBufferInfoANDROID
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero MemoryGetAndroidHardwareBufferInfoANDROID where
zero :: MemoryGetAndroidHardwareBufferInfoANDROID
zero = DeviceMemory -> MemoryGetAndroidHardwareBufferInfoANDROID
MemoryGetAndroidHardwareBufferInfoANDROID
forall a. Zero a => a
zero
data AndroidHardwareBufferFormatPropertiesANDROID = AndroidHardwareBufferFormatPropertiesANDROID
{
AndroidHardwareBufferFormatPropertiesANDROID -> Format
format :: Format
,
AndroidHardwareBufferFormatPropertiesANDROID -> Word64
externalFormat :: Word64
,
AndroidHardwareBufferFormatPropertiesANDROID -> FormatFeatureFlags
formatFeatures :: FormatFeatureFlags
,
AndroidHardwareBufferFormatPropertiesANDROID -> ComponentMapping
samplerYcbcrConversionComponents :: ComponentMapping
,
AndroidHardwareBufferFormatPropertiesANDROID
-> SamplerYcbcrModelConversion
suggestedYcbcrModel :: SamplerYcbcrModelConversion
,
AndroidHardwareBufferFormatPropertiesANDROID -> SamplerYcbcrRange
suggestedYcbcrRange :: SamplerYcbcrRange
,
AndroidHardwareBufferFormatPropertiesANDROID -> ChromaLocation
suggestedXChromaOffset :: ChromaLocation
,
AndroidHardwareBufferFormatPropertiesANDROID -> ChromaLocation
suggestedYChromaOffset :: ChromaLocation
}
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (AndroidHardwareBufferFormatPropertiesANDROID)
#endif
deriving instance Show AndroidHardwareBufferFormatPropertiesANDROID
instance ToCStruct AndroidHardwareBufferFormatPropertiesANDROID where
withCStruct :: forall b.
AndroidHardwareBufferFormatPropertiesANDROID
-> (Ptr AndroidHardwareBufferFormatPropertiesANDROID -> IO b)
-> IO b
withCStruct AndroidHardwareBufferFormatPropertiesANDROID
x Ptr AndroidHardwareBufferFormatPropertiesANDROID -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
72 forall a b. (a -> b) -> a -> b
$ \Ptr AndroidHardwareBufferFormatPropertiesANDROID
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr AndroidHardwareBufferFormatPropertiesANDROID
p AndroidHardwareBufferFormatPropertiesANDROID
x (Ptr AndroidHardwareBufferFormatPropertiesANDROID -> IO b
f Ptr AndroidHardwareBufferFormatPropertiesANDROID
p)
pokeCStruct :: forall b.
Ptr AndroidHardwareBufferFormatPropertiesANDROID
-> AndroidHardwareBufferFormatPropertiesANDROID -> IO b -> IO b
pokeCStruct Ptr AndroidHardwareBufferFormatPropertiesANDROID
p AndroidHardwareBufferFormatPropertiesANDROID{Word64
Format
ComponentMapping
SamplerYcbcrRange
SamplerYcbcrModelConversion
ChromaLocation
FormatFeatureFlags
suggestedYChromaOffset :: ChromaLocation
suggestedXChromaOffset :: ChromaLocation
suggestedYcbcrRange :: SamplerYcbcrRange
suggestedYcbcrModel :: SamplerYcbcrModelConversion
samplerYcbcrConversionComponents :: ComponentMapping
formatFeatures :: FormatFeatureFlags
externalFormat :: Word64
format :: Format
$sel:suggestedYChromaOffset:AndroidHardwareBufferFormatPropertiesANDROID :: AndroidHardwareBufferFormatPropertiesANDROID -> ChromaLocation
$sel:suggestedXChromaOffset:AndroidHardwareBufferFormatPropertiesANDROID :: AndroidHardwareBufferFormatPropertiesANDROID -> ChromaLocation
$sel:suggestedYcbcrRange:AndroidHardwareBufferFormatPropertiesANDROID :: AndroidHardwareBufferFormatPropertiesANDROID -> SamplerYcbcrRange
$sel:suggestedYcbcrModel:AndroidHardwareBufferFormatPropertiesANDROID :: AndroidHardwareBufferFormatPropertiesANDROID
-> SamplerYcbcrModelConversion
$sel:samplerYcbcrConversionComponents:AndroidHardwareBufferFormatPropertiesANDROID :: AndroidHardwareBufferFormatPropertiesANDROID -> ComponentMapping
$sel:formatFeatures:AndroidHardwareBufferFormatPropertiesANDROID :: AndroidHardwareBufferFormatPropertiesANDROID -> FormatFeatureFlags
$sel:externalFormat:AndroidHardwareBufferFormatPropertiesANDROID :: AndroidHardwareBufferFormatPropertiesANDROID -> Word64
$sel:format:AndroidHardwareBufferFormatPropertiesANDROID :: AndroidHardwareBufferFormatPropertiesANDROID -> Format
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ANDROID_HARDWARE_BUFFER_FORMAT_PROPERTIES_ANDROID)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Format)) (Format
format)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word64)) (Word64
externalFormat)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr FormatFeatureFlags)) (FormatFeatureFlags
formatFeatures)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr ComponentMapping)) (ComponentMapping
samplerYcbcrConversionComponents)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
52 :: Ptr SamplerYcbcrModelConversion)) (SamplerYcbcrModelConversion
suggestedYcbcrModel)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr SamplerYcbcrRange)) (SamplerYcbcrRange
suggestedYcbcrRange)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: Ptr ChromaLocation)) (ChromaLocation
suggestedXChromaOffset)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr ChromaLocation)) (ChromaLocation
suggestedYChromaOffset)
IO b
f
cStructSize :: Int
cStructSize = Int
72
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr AndroidHardwareBufferFormatPropertiesANDROID -> IO b -> IO b
pokeZeroCStruct Ptr AndroidHardwareBufferFormatPropertiesANDROID
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ANDROID_HARDWARE_BUFFER_FORMAT_PROPERTIES_ANDROID)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Format)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word64)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr FormatFeatureFlags)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr ComponentMapping)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
52 :: Ptr SamplerYcbcrModelConversion)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr SamplerYcbcrRange)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: Ptr ChromaLocation)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr ChromaLocation)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct AndroidHardwareBufferFormatPropertiesANDROID where
peekCStruct :: Ptr AndroidHardwareBufferFormatPropertiesANDROID
-> IO AndroidHardwareBufferFormatPropertiesANDROID
peekCStruct Ptr AndroidHardwareBufferFormatPropertiesANDROID
p = do
Format
format <- forall a. Storable a => Ptr a -> IO a
peek @Format ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Format))
Word64
externalFormat <- forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word64))
FormatFeatureFlags
formatFeatures <- forall a. Storable a => Ptr a -> IO a
peek @FormatFeatureFlags ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr FormatFeatureFlags))
ComponentMapping
samplerYcbcrConversionComponents <- forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @ComponentMapping ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr ComponentMapping))
SamplerYcbcrModelConversion
suggestedYcbcrModel <- forall a. Storable a => Ptr a -> IO a
peek @SamplerYcbcrModelConversion ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
52 :: Ptr SamplerYcbcrModelConversion))
SamplerYcbcrRange
suggestedYcbcrRange <- forall a. Storable a => Ptr a -> IO a
peek @SamplerYcbcrRange ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr SamplerYcbcrRange))
ChromaLocation
suggestedXChromaOffset <- forall a. Storable a => Ptr a -> IO a
peek @ChromaLocation ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: Ptr ChromaLocation))
ChromaLocation
suggestedYChromaOffset <- forall a. Storable a => Ptr a -> IO a
peek @ChromaLocation ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr ChromaLocation))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Format
-> Word64
-> FormatFeatureFlags
-> ComponentMapping
-> SamplerYcbcrModelConversion
-> SamplerYcbcrRange
-> ChromaLocation
-> ChromaLocation
-> AndroidHardwareBufferFormatPropertiesANDROID
AndroidHardwareBufferFormatPropertiesANDROID
Format
format
Word64
externalFormat
FormatFeatureFlags
formatFeatures
ComponentMapping
samplerYcbcrConversionComponents
SamplerYcbcrModelConversion
suggestedYcbcrModel
SamplerYcbcrRange
suggestedYcbcrRange
ChromaLocation
suggestedXChromaOffset
ChromaLocation
suggestedYChromaOffset
instance Storable AndroidHardwareBufferFormatPropertiesANDROID where
sizeOf :: AndroidHardwareBufferFormatPropertiesANDROID -> Int
sizeOf ~AndroidHardwareBufferFormatPropertiesANDROID
_ = Int
72
alignment :: AndroidHardwareBufferFormatPropertiesANDROID -> Int
alignment ~AndroidHardwareBufferFormatPropertiesANDROID
_ = Int
8
peek :: Ptr AndroidHardwareBufferFormatPropertiesANDROID
-> IO AndroidHardwareBufferFormatPropertiesANDROID
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr AndroidHardwareBufferFormatPropertiesANDROID
-> AndroidHardwareBufferFormatPropertiesANDROID -> IO ()
poke Ptr AndroidHardwareBufferFormatPropertiesANDROID
ptr AndroidHardwareBufferFormatPropertiesANDROID
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr AndroidHardwareBufferFormatPropertiesANDROID
ptr AndroidHardwareBufferFormatPropertiesANDROID
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero AndroidHardwareBufferFormatPropertiesANDROID where
zero :: AndroidHardwareBufferFormatPropertiesANDROID
zero = Format
-> Word64
-> FormatFeatureFlags
-> ComponentMapping
-> SamplerYcbcrModelConversion
-> SamplerYcbcrRange
-> ChromaLocation
-> ChromaLocation
-> AndroidHardwareBufferFormatPropertiesANDROID
AndroidHardwareBufferFormatPropertiesANDROID
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data ExternalFormatANDROID = ExternalFormatANDROID
{
ExternalFormatANDROID -> Word64
externalFormat :: Word64 }
deriving (Typeable, ExternalFormatANDROID -> ExternalFormatANDROID -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExternalFormatANDROID -> ExternalFormatANDROID -> Bool
$c/= :: ExternalFormatANDROID -> ExternalFormatANDROID -> Bool
== :: ExternalFormatANDROID -> ExternalFormatANDROID -> Bool
$c== :: ExternalFormatANDROID -> ExternalFormatANDROID -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ExternalFormatANDROID)
#endif
deriving instance Show ExternalFormatANDROID
instance ToCStruct ExternalFormatANDROID where
withCStruct :: forall b.
ExternalFormatANDROID
-> (Ptr ExternalFormatANDROID -> IO b) -> IO b
withCStruct ExternalFormatANDROID
x Ptr ExternalFormatANDROID -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr ExternalFormatANDROID
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ExternalFormatANDROID
p ExternalFormatANDROID
x (Ptr ExternalFormatANDROID -> IO b
f Ptr ExternalFormatANDROID
p)
pokeCStruct :: forall b.
Ptr ExternalFormatANDROID -> ExternalFormatANDROID -> IO b -> IO b
pokeCStruct Ptr ExternalFormatANDROID
p ExternalFormatANDROID{Word64
externalFormat :: Word64
$sel:externalFormat:ExternalFormatANDROID :: ExternalFormatANDROID -> Word64
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExternalFormatANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_EXTERNAL_FORMAT_ANDROID)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExternalFormatANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExternalFormatANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word64)) (Word64
externalFormat)
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr ExternalFormatANDROID -> IO b -> IO b
pokeZeroCStruct Ptr ExternalFormatANDROID
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExternalFormatANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_EXTERNAL_FORMAT_ANDROID)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExternalFormatANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExternalFormatANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word64)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct ExternalFormatANDROID where
peekCStruct :: Ptr ExternalFormatANDROID -> IO ExternalFormatANDROID
peekCStruct Ptr ExternalFormatANDROID
p = do
Word64
externalFormat <- forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr ExternalFormatANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word64))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Word64 -> ExternalFormatANDROID
ExternalFormatANDROID
Word64
externalFormat
instance Storable ExternalFormatANDROID where
sizeOf :: ExternalFormatANDROID -> Int
sizeOf ~ExternalFormatANDROID
_ = Int
24
alignment :: ExternalFormatANDROID -> Int
alignment ~ExternalFormatANDROID
_ = Int
8
peek :: Ptr ExternalFormatANDROID -> IO ExternalFormatANDROID
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr ExternalFormatANDROID -> ExternalFormatANDROID -> IO ()
poke Ptr ExternalFormatANDROID
ptr ExternalFormatANDROID
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ExternalFormatANDROID
ptr ExternalFormatANDROID
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero ExternalFormatANDROID where
zero :: ExternalFormatANDROID
zero = Word64 -> ExternalFormatANDROID
ExternalFormatANDROID
forall a. Zero a => a
zero
data AndroidHardwareBufferFormatProperties2ANDROID = AndroidHardwareBufferFormatProperties2ANDROID
{
AndroidHardwareBufferFormatProperties2ANDROID -> Format
format :: Format
,
AndroidHardwareBufferFormatProperties2ANDROID -> Word64
externalFormat :: Word64
,
AndroidHardwareBufferFormatProperties2ANDROID
-> FormatFeatureFlags2
formatFeatures :: FormatFeatureFlags2
,
AndroidHardwareBufferFormatProperties2ANDROID -> ComponentMapping
samplerYcbcrConversionComponents :: ComponentMapping
,
AndroidHardwareBufferFormatProperties2ANDROID
-> SamplerYcbcrModelConversion
suggestedYcbcrModel :: SamplerYcbcrModelConversion
,
AndroidHardwareBufferFormatProperties2ANDROID -> SamplerYcbcrRange
suggestedYcbcrRange :: SamplerYcbcrRange
,
AndroidHardwareBufferFormatProperties2ANDROID -> ChromaLocation
suggestedXChromaOffset :: ChromaLocation
,
AndroidHardwareBufferFormatProperties2ANDROID -> ChromaLocation
suggestedYChromaOffset :: ChromaLocation
}
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (AndroidHardwareBufferFormatProperties2ANDROID)
#endif
deriving instance Show AndroidHardwareBufferFormatProperties2ANDROID
instance ToCStruct AndroidHardwareBufferFormatProperties2ANDROID where
withCStruct :: forall b.
AndroidHardwareBufferFormatProperties2ANDROID
-> (Ptr AndroidHardwareBufferFormatProperties2ANDROID -> IO b)
-> IO b
withCStruct AndroidHardwareBufferFormatProperties2ANDROID
x Ptr AndroidHardwareBufferFormatProperties2ANDROID -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
72 forall a b. (a -> b) -> a -> b
$ \Ptr AndroidHardwareBufferFormatProperties2ANDROID
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr AndroidHardwareBufferFormatProperties2ANDROID
p AndroidHardwareBufferFormatProperties2ANDROID
x (Ptr AndroidHardwareBufferFormatProperties2ANDROID -> IO b
f Ptr AndroidHardwareBufferFormatProperties2ANDROID
p)
pokeCStruct :: forall b.
Ptr AndroidHardwareBufferFormatProperties2ANDROID
-> AndroidHardwareBufferFormatProperties2ANDROID -> IO b -> IO b
pokeCStruct Ptr AndroidHardwareBufferFormatProperties2ANDROID
p AndroidHardwareBufferFormatProperties2ANDROID{Word64
Format
ComponentMapping
SamplerYcbcrRange
SamplerYcbcrModelConversion
ChromaLocation
FormatFeatureFlags2
suggestedYChromaOffset :: ChromaLocation
suggestedXChromaOffset :: ChromaLocation
suggestedYcbcrRange :: SamplerYcbcrRange
suggestedYcbcrModel :: SamplerYcbcrModelConversion
samplerYcbcrConversionComponents :: ComponentMapping
formatFeatures :: FormatFeatureFlags2
externalFormat :: Word64
format :: Format
$sel:suggestedYChromaOffset:AndroidHardwareBufferFormatProperties2ANDROID :: AndroidHardwareBufferFormatProperties2ANDROID -> ChromaLocation
$sel:suggestedXChromaOffset:AndroidHardwareBufferFormatProperties2ANDROID :: AndroidHardwareBufferFormatProperties2ANDROID -> ChromaLocation
$sel:suggestedYcbcrRange:AndroidHardwareBufferFormatProperties2ANDROID :: AndroidHardwareBufferFormatProperties2ANDROID -> SamplerYcbcrRange
$sel:suggestedYcbcrModel:AndroidHardwareBufferFormatProperties2ANDROID :: AndroidHardwareBufferFormatProperties2ANDROID
-> SamplerYcbcrModelConversion
$sel:samplerYcbcrConversionComponents:AndroidHardwareBufferFormatProperties2ANDROID :: AndroidHardwareBufferFormatProperties2ANDROID -> ComponentMapping
$sel:formatFeatures:AndroidHardwareBufferFormatProperties2ANDROID :: AndroidHardwareBufferFormatProperties2ANDROID
-> FormatFeatureFlags2
$sel:externalFormat:AndroidHardwareBufferFormatProperties2ANDROID :: AndroidHardwareBufferFormatProperties2ANDROID -> Word64
$sel:format:AndroidHardwareBufferFormatProperties2ANDROID :: AndroidHardwareBufferFormatProperties2ANDROID -> Format
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ANDROID_HARDWARE_BUFFER_FORMAT_PROPERTIES_2_ANDROID)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Format)) (Format
format)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word64)) (Word64
externalFormat)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr FormatFeatureFlags2)) (FormatFeatureFlags2
formatFeatures)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr ComponentMapping)) (ComponentMapping
samplerYcbcrConversionComponents)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr SamplerYcbcrModelConversion)) (SamplerYcbcrModelConversion
suggestedYcbcrModel)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: Ptr SamplerYcbcrRange)) (SamplerYcbcrRange
suggestedYcbcrRange)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr ChromaLocation)) (ChromaLocation
suggestedXChromaOffset)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
68 :: Ptr ChromaLocation)) (ChromaLocation
suggestedYChromaOffset)
IO b
f
cStructSize :: Int
cStructSize = Int
72
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr AndroidHardwareBufferFormatProperties2ANDROID -> IO b -> IO b
pokeZeroCStruct Ptr AndroidHardwareBufferFormatProperties2ANDROID
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ANDROID_HARDWARE_BUFFER_FORMAT_PROPERTIES_2_ANDROID)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Format)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word64)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr FormatFeatureFlags2)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr ComponentMapping)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr SamplerYcbcrModelConversion)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: Ptr SamplerYcbcrRange)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr ChromaLocation)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
68 :: Ptr ChromaLocation)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct AndroidHardwareBufferFormatProperties2ANDROID where
peekCStruct :: Ptr AndroidHardwareBufferFormatProperties2ANDROID
-> IO AndroidHardwareBufferFormatProperties2ANDROID
peekCStruct Ptr AndroidHardwareBufferFormatProperties2ANDROID
p = do
Format
format <- forall a. Storable a => Ptr a -> IO a
peek @Format ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Format))
Word64
externalFormat <- forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word64))
FormatFeatureFlags2
formatFeatures <- forall a. Storable a => Ptr a -> IO a
peek @FormatFeatureFlags2 ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr FormatFeatureFlags2))
ComponentMapping
samplerYcbcrConversionComponents <- forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @ComponentMapping ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr ComponentMapping))
SamplerYcbcrModelConversion
suggestedYcbcrModel <- forall a. Storable a => Ptr a -> IO a
peek @SamplerYcbcrModelConversion ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr SamplerYcbcrModelConversion))
SamplerYcbcrRange
suggestedYcbcrRange <- forall a. Storable a => Ptr a -> IO a
peek @SamplerYcbcrRange ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: Ptr SamplerYcbcrRange))
ChromaLocation
suggestedXChromaOffset <- forall a. Storable a => Ptr a -> IO a
peek @ChromaLocation ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr ChromaLocation))
ChromaLocation
suggestedYChromaOffset <- forall a. Storable a => Ptr a -> IO a
peek @ChromaLocation ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
68 :: Ptr ChromaLocation))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Format
-> Word64
-> FormatFeatureFlags2
-> ComponentMapping
-> SamplerYcbcrModelConversion
-> SamplerYcbcrRange
-> ChromaLocation
-> ChromaLocation
-> AndroidHardwareBufferFormatProperties2ANDROID
AndroidHardwareBufferFormatProperties2ANDROID
Format
format
Word64
externalFormat
FormatFeatureFlags2
formatFeatures
ComponentMapping
samplerYcbcrConversionComponents
SamplerYcbcrModelConversion
suggestedYcbcrModel
SamplerYcbcrRange
suggestedYcbcrRange
ChromaLocation
suggestedXChromaOffset
ChromaLocation
suggestedYChromaOffset
instance Storable AndroidHardwareBufferFormatProperties2ANDROID where
sizeOf :: AndroidHardwareBufferFormatProperties2ANDROID -> Int
sizeOf ~AndroidHardwareBufferFormatProperties2ANDROID
_ = Int
72
alignment :: AndroidHardwareBufferFormatProperties2ANDROID -> Int
alignment ~AndroidHardwareBufferFormatProperties2ANDROID
_ = Int
8
peek :: Ptr AndroidHardwareBufferFormatProperties2ANDROID
-> IO AndroidHardwareBufferFormatProperties2ANDROID
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr AndroidHardwareBufferFormatProperties2ANDROID
-> AndroidHardwareBufferFormatProperties2ANDROID -> IO ()
poke Ptr AndroidHardwareBufferFormatProperties2ANDROID
ptr AndroidHardwareBufferFormatProperties2ANDROID
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr AndroidHardwareBufferFormatProperties2ANDROID
ptr AndroidHardwareBufferFormatProperties2ANDROID
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero AndroidHardwareBufferFormatProperties2ANDROID where
zero :: AndroidHardwareBufferFormatProperties2ANDROID
zero = Format
-> Word64
-> FormatFeatureFlags2
-> ComponentMapping
-> SamplerYcbcrModelConversion
-> SamplerYcbcrRange
-> ChromaLocation
-> ChromaLocation
-> AndroidHardwareBufferFormatProperties2ANDROID
AndroidHardwareBufferFormatProperties2ANDROID
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
type ANDROID_EXTERNAL_MEMORY_ANDROID_HARDWARE_BUFFER_SPEC_VERSION = 5
pattern ANDROID_EXTERNAL_MEMORY_ANDROID_HARDWARE_BUFFER_SPEC_VERSION :: forall a . Integral a => a
pattern $bANDROID_EXTERNAL_MEMORY_ANDROID_HARDWARE_BUFFER_SPEC_VERSION :: forall a. Integral a => a
$mANDROID_EXTERNAL_MEMORY_ANDROID_HARDWARE_BUFFER_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
ANDROID_EXTERNAL_MEMORY_ANDROID_HARDWARE_BUFFER_SPEC_VERSION = 5
type ANDROID_EXTERNAL_MEMORY_ANDROID_HARDWARE_BUFFER_EXTENSION_NAME = "VK_ANDROID_external_memory_android_hardware_buffer"
pattern ANDROID_EXTERNAL_MEMORY_ANDROID_HARDWARE_BUFFER_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bANDROID_EXTERNAL_MEMORY_ANDROID_HARDWARE_BUFFER_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mANDROID_EXTERNAL_MEMORY_ANDROID_HARDWARE_BUFFER_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
ANDROID_EXTERNAL_MEMORY_ANDROID_HARDWARE_BUFFER_EXTENSION_NAME = "VK_ANDROID_external_memory_android_hardware_buffer"
data AHardwareBuffer