{-# language CPP #-}
module Vulkan.Core12.Promoted_From_VK_KHR_driver_properties  ( ConformanceVersion(..)
                                                             , PhysicalDeviceDriverProperties(..)
                                                             , StructureType(..)
                                                             , DriverId(..)
                                                             , MAX_DRIVER_NAME_SIZE
                                                             , pattern MAX_DRIVER_NAME_SIZE
                                                             , MAX_DRIVER_INFO_SIZE
                                                             , pattern MAX_DRIVER_INFO_SIZE
                                                             ) where
import Vulkan.CStruct.Utils (FixedArray)
import Foreign.Marshal.Alloc (allocaBytesAligned)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Data.ByteString (packCString)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Data.Typeable (Typeable)
import Foreign.C.Types (CChar)
import Foreign.Storable (Storable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import qualified Foreign.Storable (Storable(..))
import GHC.Generics (Generic)
import Foreign.Ptr (Ptr)
import Data.Word (Word8)
import Data.ByteString (ByteString)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Vulkan.CStruct.Utils (lowerArrayPtr)
import Vulkan.CStruct.Utils (pokeFixedLengthNullTerminatedByteString)
import Vulkan.Core12.Enums.DriverId (DriverId)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.APIConstants (MAX_DRIVER_INFO_SIZE)
import Vulkan.Core10.APIConstants (MAX_DRIVER_NAME_SIZE)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_DRIVER_PROPERTIES))
import Vulkan.Core12.Enums.DriverId (DriverId(..))
import Vulkan.Core10.APIConstants (MAX_DRIVER_INFO_SIZE)
import Vulkan.Core10.APIConstants (MAX_DRIVER_NAME_SIZE)
import Vulkan.Core10.Enums.StructureType (StructureType(..))
import Vulkan.Core10.APIConstants (pattern MAX_DRIVER_INFO_SIZE)
import Vulkan.Core10.APIConstants (pattern MAX_DRIVER_NAME_SIZE)
data ConformanceVersion = ConformanceVersion
  { 
    ConformanceVersion -> Word8
major :: Word8
  , 
    ConformanceVersion -> Word8
minor :: Word8
  , 
    ConformanceVersion -> Word8
subminor :: Word8
  , 
    ConformanceVersion -> Word8
patch :: Word8
  }
  deriving (Typeable, ConformanceVersion -> ConformanceVersion -> Bool
(ConformanceVersion -> ConformanceVersion -> Bool)
-> (ConformanceVersion -> ConformanceVersion -> Bool)
-> Eq ConformanceVersion
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConformanceVersion -> ConformanceVersion -> Bool
$c/= :: ConformanceVersion -> ConformanceVersion -> Bool
== :: ConformanceVersion -> ConformanceVersion -> Bool
$c== :: ConformanceVersion -> ConformanceVersion -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ConformanceVersion)
#endif
deriving instance Show ConformanceVersion
instance ToCStruct ConformanceVersion where
  withCStruct :: ConformanceVersion -> (Ptr ConformanceVersion -> IO b) -> IO b
withCStruct x :: ConformanceVersion
x f :: Ptr ConformanceVersion -> IO b
f = Int -> Int -> (Ptr ConformanceVersion -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 4 1 ((Ptr ConformanceVersion -> IO b) -> IO b)
-> (Ptr ConformanceVersion -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr ConformanceVersion
p -> Ptr ConformanceVersion -> ConformanceVersion -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ConformanceVersion
p ConformanceVersion
x (Ptr ConformanceVersion -> IO b
f Ptr ConformanceVersion
p)
  pokeCStruct :: Ptr ConformanceVersion -> ConformanceVersion -> IO b -> IO b
pokeCStruct p :: Ptr ConformanceVersion
p ConformanceVersion{..} f :: IO b
f = do
    Ptr Word8 -> Word8 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ConformanceVersion
p Ptr ConformanceVersion -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word8)) (Word8
major)
    Ptr Word8 -> Word8 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ConformanceVersion
p Ptr ConformanceVersion -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 1 :: Ptr Word8)) (Word8
minor)
    Ptr Word8 -> Word8 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ConformanceVersion
p Ptr ConformanceVersion -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 2 :: Ptr Word8)) (Word8
subminor)
    Ptr Word8 -> Word8 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ConformanceVersion
p Ptr ConformanceVersion -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 3 :: Ptr Word8)) (Word8
patch)
    IO b
f
  cStructSize :: Int
cStructSize = 4
  cStructAlignment :: Int
cStructAlignment = 1
  pokeZeroCStruct :: Ptr ConformanceVersion -> IO b -> IO b
pokeZeroCStruct p :: Ptr ConformanceVersion
p f :: IO b
f = do
    Ptr Word8 -> Word8 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ConformanceVersion
p Ptr ConformanceVersion -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word8)) (Word8
forall a. Zero a => a
zero)
    Ptr Word8 -> Word8 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ConformanceVersion
p Ptr ConformanceVersion -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 1 :: Ptr Word8)) (Word8
forall a. Zero a => a
zero)
    Ptr Word8 -> Word8 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ConformanceVersion
p Ptr ConformanceVersion -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 2 :: Ptr Word8)) (Word8
forall a. Zero a => a
zero)
    Ptr Word8 -> Word8 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ConformanceVersion
p Ptr ConformanceVersion -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 3 :: Ptr Word8)) (Word8
forall a. Zero a => a
zero)
    IO b
f
instance FromCStruct ConformanceVersion where
  peekCStruct :: Ptr ConformanceVersion -> IO ConformanceVersion
peekCStruct p :: Ptr ConformanceVersion
p = do
    Word8
major <- Ptr Word8 -> IO Word8
forall a. Storable a => Ptr a -> IO a
peek @Word8 ((Ptr ConformanceVersion
p Ptr ConformanceVersion -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word8))
    Word8
minor <- Ptr Word8 -> IO Word8
forall a. Storable a => Ptr a -> IO a
peek @Word8 ((Ptr ConformanceVersion
p Ptr ConformanceVersion -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 1 :: Ptr Word8))
    Word8
subminor <- Ptr Word8 -> IO Word8
forall a. Storable a => Ptr a -> IO a
peek @Word8 ((Ptr ConformanceVersion
p Ptr ConformanceVersion -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 2 :: Ptr Word8))
    Word8
patch <- Ptr Word8 -> IO Word8
forall a. Storable a => Ptr a -> IO a
peek @Word8 ((Ptr ConformanceVersion
p Ptr ConformanceVersion -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 3 :: Ptr Word8))
    ConformanceVersion -> IO ConformanceVersion
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ConformanceVersion -> IO ConformanceVersion)
-> ConformanceVersion -> IO ConformanceVersion
forall a b. (a -> b) -> a -> b
$ Word8 -> Word8 -> Word8 -> Word8 -> ConformanceVersion
ConformanceVersion
             Word8
major Word8
minor Word8
subminor Word8
patch
instance Storable ConformanceVersion where
  sizeOf :: ConformanceVersion -> Int
sizeOf ~ConformanceVersion
_ = 4
  alignment :: ConformanceVersion -> Int
alignment ~ConformanceVersion
_ = 1
  peek :: Ptr ConformanceVersion -> IO ConformanceVersion
peek = Ptr ConformanceVersion -> IO ConformanceVersion
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr ConformanceVersion -> ConformanceVersion -> IO ()
poke ptr :: Ptr ConformanceVersion
ptr poked :: ConformanceVersion
poked = Ptr ConformanceVersion -> ConformanceVersion -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ConformanceVersion
ptr ConformanceVersion
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero ConformanceVersion where
  zero :: ConformanceVersion
zero = Word8 -> Word8 -> Word8 -> Word8 -> ConformanceVersion
ConformanceVersion
           Word8
forall a. Zero a => a
zero
           Word8
forall a. Zero a => a
zero
           Word8
forall a. Zero a => a
zero
           Word8
forall a. Zero a => a
zero
data PhysicalDeviceDriverProperties = PhysicalDeviceDriverProperties
  { 
    PhysicalDeviceDriverProperties -> DriverId
driverID :: DriverId
  , 
    
    
    PhysicalDeviceDriverProperties -> ByteString
driverName :: ByteString
  , 
    
    
    
    PhysicalDeviceDriverProperties -> ByteString
driverInfo :: ByteString
  , 
    
    PhysicalDeviceDriverProperties -> ConformanceVersion
conformanceVersion :: ConformanceVersion
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceDriverProperties)
#endif
deriving instance Show PhysicalDeviceDriverProperties
instance ToCStruct PhysicalDeviceDriverProperties where
  withCStruct :: PhysicalDeviceDriverProperties
-> (Ptr PhysicalDeviceDriverProperties -> IO b) -> IO b
withCStruct x :: PhysicalDeviceDriverProperties
x f :: Ptr PhysicalDeviceDriverProperties -> IO b
f = Int -> Int -> (Ptr PhysicalDeviceDriverProperties -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 536 8 ((Ptr PhysicalDeviceDriverProperties -> IO b) -> IO b)
-> (Ptr PhysicalDeviceDriverProperties -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PhysicalDeviceDriverProperties
p -> Ptr PhysicalDeviceDriverProperties
-> PhysicalDeviceDriverProperties -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDriverProperties
p PhysicalDeviceDriverProperties
x (Ptr PhysicalDeviceDriverProperties -> IO b
f Ptr PhysicalDeviceDriverProperties
p)
  pokeCStruct :: Ptr PhysicalDeviceDriverProperties
-> PhysicalDeviceDriverProperties -> IO b -> IO b
pokeCStruct p :: Ptr PhysicalDeviceDriverProperties
p PhysicalDeviceDriverProperties{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDriverProperties
p Ptr PhysicalDeviceDriverProperties -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_DRIVER_PROPERTIES)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDriverProperties
p Ptr PhysicalDeviceDriverProperties -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DriverId -> DriverId -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDriverProperties
p Ptr PhysicalDeviceDriverProperties -> Int -> Ptr DriverId
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DriverId)) (DriverId
driverID)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (FixedArray MAX_DRIVER_NAME_SIZE CChar) -> ByteString -> IO ()
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n CChar) -> ByteString -> IO ()
pokeFixedLengthNullTerminatedByteString ((Ptr PhysicalDeviceDriverProperties
p Ptr PhysicalDeviceDriverProperties
-> Int -> Ptr (FixedArray MAX_DRIVER_NAME_SIZE CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr (FixedArray MAX_DRIVER_NAME_SIZE CChar))) (ByteString
driverName)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (FixedArray MAX_DRIVER_NAME_SIZE CChar) -> ByteString -> IO ()
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n CChar) -> ByteString -> IO ()
pokeFixedLengthNullTerminatedByteString ((Ptr PhysicalDeviceDriverProperties
p Ptr PhysicalDeviceDriverProperties
-> Int -> Ptr (FixedArray MAX_DRIVER_NAME_SIZE CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 276 :: Ptr (FixedArray MAX_DRIVER_INFO_SIZE CChar))) (ByteString
driverInfo)
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ConformanceVersion -> ConformanceVersion -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr PhysicalDeviceDriverProperties
p Ptr PhysicalDeviceDriverProperties -> Int -> Ptr ConformanceVersion
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 532 :: Ptr ConformanceVersion)) (ConformanceVersion
conformanceVersion) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = 536
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PhysicalDeviceDriverProperties -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDeviceDriverProperties
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDriverProperties
p Ptr PhysicalDeviceDriverProperties -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_DRIVER_PROPERTIES)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDriverProperties
p Ptr PhysicalDeviceDriverProperties -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DriverId -> DriverId -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDriverProperties
p Ptr PhysicalDeviceDriverProperties -> Int -> Ptr DriverId
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DriverId)) (DriverId
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (FixedArray MAX_DRIVER_NAME_SIZE CChar) -> ByteString -> IO ()
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n CChar) -> ByteString -> IO ()
pokeFixedLengthNullTerminatedByteString ((Ptr PhysicalDeviceDriverProperties
p Ptr PhysicalDeviceDriverProperties
-> Int -> Ptr (FixedArray MAX_DRIVER_NAME_SIZE CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr (FixedArray MAX_DRIVER_NAME_SIZE CChar))) (ByteString
forall a. Monoid a => a
mempty)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (FixedArray MAX_DRIVER_NAME_SIZE CChar) -> ByteString -> IO ()
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n CChar) -> ByteString -> IO ()
pokeFixedLengthNullTerminatedByteString ((Ptr PhysicalDeviceDriverProperties
p Ptr PhysicalDeviceDriverProperties
-> Int -> Ptr (FixedArray MAX_DRIVER_NAME_SIZE CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 276 :: Ptr (FixedArray MAX_DRIVER_INFO_SIZE CChar))) (ByteString
forall a. Monoid a => a
mempty)
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ConformanceVersion -> ConformanceVersion -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr PhysicalDeviceDriverProperties
p Ptr PhysicalDeviceDriverProperties -> Int -> Ptr ConformanceVersion
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 532 :: Ptr ConformanceVersion)) (ConformanceVersion
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
instance FromCStruct PhysicalDeviceDriverProperties where
  peekCStruct :: Ptr PhysicalDeviceDriverProperties
-> IO PhysicalDeviceDriverProperties
peekCStruct p :: Ptr PhysicalDeviceDriverProperties
p = do
    DriverId
driverID <- Ptr DriverId -> IO DriverId
forall a. Storable a => Ptr a -> IO a
peek @DriverId ((Ptr PhysicalDeviceDriverProperties
p Ptr PhysicalDeviceDriverProperties -> Int -> Ptr DriverId
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DriverId))
    ByteString
driverName <- CString -> IO ByteString
packCString (Ptr (FixedArray MAX_DRIVER_NAME_SIZE CChar) -> CString
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr ((Ptr PhysicalDeviceDriverProperties
p Ptr PhysicalDeviceDriverProperties
-> Int -> Ptr (FixedArray MAX_DRIVER_NAME_SIZE CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr (FixedArray MAX_DRIVER_NAME_SIZE CChar))))
    ByteString
driverInfo <- CString -> IO ByteString
packCString (Ptr (FixedArray MAX_DRIVER_NAME_SIZE CChar) -> CString
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr ((Ptr PhysicalDeviceDriverProperties
p Ptr PhysicalDeviceDriverProperties
-> Int -> Ptr (FixedArray MAX_DRIVER_NAME_SIZE CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 276 :: Ptr (FixedArray MAX_DRIVER_INFO_SIZE CChar))))
    ConformanceVersion
conformanceVersion <- Ptr ConformanceVersion -> IO ConformanceVersion
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @ConformanceVersion ((Ptr PhysicalDeviceDriverProperties
p Ptr PhysicalDeviceDriverProperties -> Int -> Ptr ConformanceVersion
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 532 :: Ptr ConformanceVersion))
    PhysicalDeviceDriverProperties -> IO PhysicalDeviceDriverProperties
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceDriverProperties
 -> IO PhysicalDeviceDriverProperties)
-> PhysicalDeviceDriverProperties
-> IO PhysicalDeviceDriverProperties
forall a b. (a -> b) -> a -> b
$ DriverId
-> ByteString
-> ByteString
-> ConformanceVersion
-> PhysicalDeviceDriverProperties
PhysicalDeviceDriverProperties
             DriverId
driverID ByteString
driverName ByteString
driverInfo ConformanceVersion
conformanceVersion
instance Zero PhysicalDeviceDriverProperties where
  zero :: PhysicalDeviceDriverProperties
zero = DriverId
-> ByteString
-> ByteString
-> ConformanceVersion
-> PhysicalDeviceDriverProperties
PhysicalDeviceDriverProperties
           DriverId
forall a. Zero a => a
zero
           ByteString
forall a. Monoid a => a
mempty
           ByteString
forall a. Monoid a => a
mempty
           ConformanceVersion
forall a. Zero a => a
zero