{-# language CPP #-}
module Vulkan.Extensions.VK_EXT_pci_bus_info  ( PhysicalDevicePCIBusInfoPropertiesEXT(..)
                                              , EXT_PCI_BUS_INFO_SPEC_VERSION
                                              , pattern EXT_PCI_BUS_INFO_SPEC_VERSION
                                              , EXT_PCI_BUS_INFO_EXTENSION_NAME
                                              , pattern EXT_PCI_BUS_INFO_EXTENSION_NAME
                                              ) where

import Foreign.Marshal.Alloc (allocaBytesAligned)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Data.String (IsString)
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 Foreign.Ptr (Ptr)
import Data.Word (Word32)
import Data.Kind (Type)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
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_PCI_BUS_INFO_PROPERTIES_EXT))
-- | VkPhysicalDevicePCIBusInfoPropertiesEXT - Structure containing PCI bus
-- information of a physical device
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDevicePCIBusInfoPropertiesEXT = PhysicalDevicePCIBusInfoPropertiesEXT
  { -- | @pciDomain@ is the PCI bus domain.
    PhysicalDevicePCIBusInfoPropertiesEXT -> Word32
pciDomain :: Word32
  , -- | @pciBus@ is the PCI bus identifier.
    PhysicalDevicePCIBusInfoPropertiesEXT -> Word32
pciBus :: Word32
  , -- | @pciDevice@ is the PCI device identifier.
    PhysicalDevicePCIBusInfoPropertiesEXT -> Word32
pciDevice :: Word32
  , -- | @pciFunction@ is the PCI device function identifier.
    PhysicalDevicePCIBusInfoPropertiesEXT -> Word32
pciFunction :: Word32
  }
  deriving (Typeable, PhysicalDevicePCIBusInfoPropertiesEXT
-> PhysicalDevicePCIBusInfoPropertiesEXT -> Bool
(PhysicalDevicePCIBusInfoPropertiesEXT
 -> PhysicalDevicePCIBusInfoPropertiesEXT -> Bool)
-> (PhysicalDevicePCIBusInfoPropertiesEXT
    -> PhysicalDevicePCIBusInfoPropertiesEXT -> Bool)
-> Eq PhysicalDevicePCIBusInfoPropertiesEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDevicePCIBusInfoPropertiesEXT
-> PhysicalDevicePCIBusInfoPropertiesEXT -> Bool
$c/= :: PhysicalDevicePCIBusInfoPropertiesEXT
-> PhysicalDevicePCIBusInfoPropertiesEXT -> Bool
== :: PhysicalDevicePCIBusInfoPropertiesEXT
-> PhysicalDevicePCIBusInfoPropertiesEXT -> Bool
$c== :: PhysicalDevicePCIBusInfoPropertiesEXT
-> PhysicalDevicePCIBusInfoPropertiesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDevicePCIBusInfoPropertiesEXT)
#endif
deriving instance Show PhysicalDevicePCIBusInfoPropertiesEXT

instance ToCStruct PhysicalDevicePCIBusInfoPropertiesEXT where
  withCStruct :: PhysicalDevicePCIBusInfoPropertiesEXT
-> (Ptr PhysicalDevicePCIBusInfoPropertiesEXT -> IO b) -> IO b
withCStruct x :: PhysicalDevicePCIBusInfoPropertiesEXT
x f :: Ptr PhysicalDevicePCIBusInfoPropertiesEXT -> IO b
f = Int
-> Int
-> (Ptr PhysicalDevicePCIBusInfoPropertiesEXT -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((Ptr PhysicalDevicePCIBusInfoPropertiesEXT -> IO b) -> IO b)
-> (Ptr PhysicalDevicePCIBusInfoPropertiesEXT -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PhysicalDevicePCIBusInfoPropertiesEXT
p -> Ptr PhysicalDevicePCIBusInfoPropertiesEXT
-> PhysicalDevicePCIBusInfoPropertiesEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDevicePCIBusInfoPropertiesEXT
p PhysicalDevicePCIBusInfoPropertiesEXT
x (Ptr PhysicalDevicePCIBusInfoPropertiesEXT -> IO b
f Ptr PhysicalDevicePCIBusInfoPropertiesEXT
p)
  pokeCStruct :: Ptr PhysicalDevicePCIBusInfoPropertiesEXT
-> PhysicalDevicePCIBusInfoPropertiesEXT -> IO b -> IO b
pokeCStruct p :: Ptr PhysicalDevicePCIBusInfoPropertiesEXT
p PhysicalDevicePCIBusInfoPropertiesEXT{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePCIBusInfoPropertiesEXT
p Ptr PhysicalDevicePCIBusInfoPropertiesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_PCI_BUS_INFO_PROPERTIES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePCIBusInfoPropertiesEXT
p Ptr PhysicalDevicePCIBusInfoPropertiesEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePCIBusInfoPropertiesEXT
p Ptr PhysicalDevicePCIBusInfoPropertiesEXT -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) (Word32
pciDomain)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePCIBusInfoPropertiesEXT
p Ptr PhysicalDevicePCIBusInfoPropertiesEXT -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) (Word32
pciBus)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePCIBusInfoPropertiesEXT
p Ptr PhysicalDevicePCIBusInfoPropertiesEXT -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32)) (Word32
pciDevice)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePCIBusInfoPropertiesEXT
p Ptr PhysicalDevicePCIBusInfoPropertiesEXT -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Word32)) (Word32
pciFunction)
    IO b
f
  cStructSize :: Int
cStructSize = 32
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PhysicalDevicePCIBusInfoPropertiesEXT -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDevicePCIBusInfoPropertiesEXT
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePCIBusInfoPropertiesEXT
p Ptr PhysicalDevicePCIBusInfoPropertiesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_PCI_BUS_INFO_PROPERTIES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePCIBusInfoPropertiesEXT
p Ptr PhysicalDevicePCIBusInfoPropertiesEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePCIBusInfoPropertiesEXT
p Ptr PhysicalDevicePCIBusInfoPropertiesEXT -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePCIBusInfoPropertiesEXT
p Ptr PhysicalDevicePCIBusInfoPropertiesEXT -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePCIBusInfoPropertiesEXT
p Ptr PhysicalDevicePCIBusInfoPropertiesEXT -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePCIBusInfoPropertiesEXT
p Ptr PhysicalDevicePCIBusInfoPropertiesEXT -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct PhysicalDevicePCIBusInfoPropertiesEXT where
  peekCStruct :: Ptr PhysicalDevicePCIBusInfoPropertiesEXT
-> IO PhysicalDevicePCIBusInfoPropertiesEXT
peekCStruct p :: Ptr PhysicalDevicePCIBusInfoPropertiesEXT
p = do
    Word32
pciDomain <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDevicePCIBusInfoPropertiesEXT
p Ptr PhysicalDevicePCIBusInfoPropertiesEXT -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32))
    Word32
pciBus <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDevicePCIBusInfoPropertiesEXT
p Ptr PhysicalDevicePCIBusInfoPropertiesEXT -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32))
    Word32
pciDevice <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDevicePCIBusInfoPropertiesEXT
p Ptr PhysicalDevicePCIBusInfoPropertiesEXT -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32))
    Word32
pciFunction <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDevicePCIBusInfoPropertiesEXT
p Ptr PhysicalDevicePCIBusInfoPropertiesEXT -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Word32))
    PhysicalDevicePCIBusInfoPropertiesEXT
-> IO PhysicalDevicePCIBusInfoPropertiesEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDevicePCIBusInfoPropertiesEXT
 -> IO PhysicalDevicePCIBusInfoPropertiesEXT)
-> PhysicalDevicePCIBusInfoPropertiesEXT
-> IO PhysicalDevicePCIBusInfoPropertiesEXT
forall a b. (a -> b) -> a -> b
$ Word32
-> Word32
-> Word32
-> Word32
-> PhysicalDevicePCIBusInfoPropertiesEXT
PhysicalDevicePCIBusInfoPropertiesEXT
             Word32
pciDomain Word32
pciBus Word32
pciDevice Word32
pciFunction

instance Storable PhysicalDevicePCIBusInfoPropertiesEXT where
  sizeOf :: PhysicalDevicePCIBusInfoPropertiesEXT -> Int
sizeOf ~PhysicalDevicePCIBusInfoPropertiesEXT
_ = 32
  alignment :: PhysicalDevicePCIBusInfoPropertiesEXT -> Int
alignment ~PhysicalDevicePCIBusInfoPropertiesEXT
_ = 8
  peek :: Ptr PhysicalDevicePCIBusInfoPropertiesEXT
-> IO PhysicalDevicePCIBusInfoPropertiesEXT
peek = Ptr PhysicalDevicePCIBusInfoPropertiesEXT
-> IO PhysicalDevicePCIBusInfoPropertiesEXT
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr PhysicalDevicePCIBusInfoPropertiesEXT
-> PhysicalDevicePCIBusInfoPropertiesEXT -> IO ()
poke ptr :: Ptr PhysicalDevicePCIBusInfoPropertiesEXT
ptr poked :: PhysicalDevicePCIBusInfoPropertiesEXT
poked = Ptr PhysicalDevicePCIBusInfoPropertiesEXT
-> PhysicalDevicePCIBusInfoPropertiesEXT -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDevicePCIBusInfoPropertiesEXT
ptr PhysicalDevicePCIBusInfoPropertiesEXT
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero PhysicalDevicePCIBusInfoPropertiesEXT where
  zero :: PhysicalDevicePCIBusInfoPropertiesEXT
zero = Word32
-> Word32
-> Word32
-> Word32
-> PhysicalDevicePCIBusInfoPropertiesEXT
PhysicalDevicePCIBusInfoPropertiesEXT
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero


type EXT_PCI_BUS_INFO_SPEC_VERSION = 2

-- No documentation found for TopLevel "VK_EXT_PCI_BUS_INFO_SPEC_VERSION"
pattern EXT_PCI_BUS_INFO_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_PCI_BUS_INFO_SPEC_VERSION :: a
$mEXT_PCI_BUS_INFO_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
EXT_PCI_BUS_INFO_SPEC_VERSION = 2


type EXT_PCI_BUS_INFO_EXTENSION_NAME = "VK_EXT_pci_bus_info"

-- No documentation found for TopLevel "VK_EXT_PCI_BUS_INFO_EXTENSION_NAME"
pattern EXT_PCI_BUS_INFO_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_PCI_BUS_INFO_EXTENSION_NAME :: a
$mEXT_PCI_BUS_INFO_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
EXT_PCI_BUS_INFO_EXTENSION_NAME = "VK_EXT_pci_bus_info"