{-# language CPP #-}
-- | = Name
--
-- VK_EXT_pci_bus_info - device extension
--
-- == VK_EXT_pci_bus_info
--
-- [__Name String__]
--     @VK_EXT_pci_bus_info@
--
-- [__Extension Type__]
--     Device extension
--
-- [__Registered Extension Number__]
--     213
--
-- [__Revision__]
--     2
--
-- [__Extension and Version Dependencies__]
--
--     -   Requires Vulkan 1.0
--
--     -   Requires @VK_KHR_get_physical_device_properties2@
--
-- [__Contact__]
--
--     -   Matthaeus G. Chajdas
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_EXT_pci_bus_info] @anteru%0A<<Here describe the issue or question you have about the VK_EXT_pci_bus_info extension>> >
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2018-12-10
--
-- [__IP Status__]
--     No known IP claims.
--
-- [__Contributors__]
--
--     -   Matthaeus G. Chajdas, AMD
--
--     -   Daniel Rakos, AMD
--
-- == Description
--
-- This extension adds a new query to obtain PCI bus information about a
-- physical device.
--
-- Not all physical devices have PCI bus information, either due to the
-- device not being connected to the system through a PCI interface or due
-- to platform specific restrictions and policies. Thus this extension is
-- only expected to be supported by physical devices which can provide the
-- information.
--
-- As a consequence, applications should always check for the presence of
-- the extension string for each individual physical device for which they
-- intend to issue the new query for and should not have any assumptions
-- about the availability of the extension on any given platform.
--
-- == New Structures
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceProperties2':
--
--     -   'PhysicalDevicePCIBusInfoPropertiesEXT'
--
-- == New Enum Constants
--
-- -   'EXT_PCI_BUS_INFO_EXTENSION_NAME'
--
-- -   'EXT_PCI_BUS_INFO_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_PCI_BUS_INFO_PROPERTIES_EXT'
--
-- == Version History
--
-- -   Revision 2, 2018-12-10 (Daniel Rakos)
--
--     -   Changed all members of the new structure to have the uint32_t
--         type
--
-- -   Revision 1, 2018-10-11 (Daniel Rakos)
--
--     -   Initial revision
--
-- == See Also
--
-- 'PhysicalDevicePCIBusInfoPropertiesEXT'
--
-- == Document Notes
--
-- For more information, see the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_pci_bus_info Vulkan Specification>
--
-- This page is a generated document. Fixes and changes should be made to
-- the generator scripts, not directly.
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 (allocaBytes)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
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.Core10.Enums.StructureType (StructureType)
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
--
-- = Description
--
-- If the 'PhysicalDevicePCIBusInfoPropertiesEXT' structure is included in
-- the @pNext@ chain of the
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceProperties2'
-- structure passed to
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceProperties2',
-- it is filled in with each corresponding implementation-dependent
-- property.
--
-- These are properties of the PCI bus information of a physical device.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_pci_bus_info VK_EXT_pci_bus_info>,
-- '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 PhysicalDevicePCIBusInfoPropertiesEXT
x Ptr PhysicalDevicePCIBusInfoPropertiesEXT -> IO b
f = Int -> (Ptr PhysicalDevicePCIBusInfoPropertiesEXT -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 ((Ptr PhysicalDevicePCIBusInfoPropertiesEXT -> IO b) -> IO b)
-> (Ptr PhysicalDevicePCIBusInfoPropertiesEXT -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \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 Ptr PhysicalDevicePCIBusInfoPropertiesEXT
p PhysicalDevicePCIBusInfoPropertiesEXT{Word32
pciFunction :: Word32
pciDevice :: Word32
pciBus :: Word32
pciDomain :: Word32
$sel:pciFunction:PhysicalDevicePCIBusInfoPropertiesEXT :: PhysicalDevicePCIBusInfoPropertiesEXT -> Word32
$sel:pciDevice:PhysicalDevicePCIBusInfoPropertiesEXT :: PhysicalDevicePCIBusInfoPropertiesEXT -> Word32
$sel:pciBus:PhysicalDevicePCIBusInfoPropertiesEXT :: PhysicalDevicePCIBusInfoPropertiesEXT -> Word32
$sel:pciDomain:PhysicalDevicePCIBusInfoPropertiesEXT :: PhysicalDevicePCIBusInfoPropertiesEXT -> Word32
..} 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` Int
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` Int
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` Int
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` Int
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` Int
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` Int
28 :: Ptr Word32)) (Word32
pciFunction)
    IO b
f
  cStructSize :: Int
cStructSize = Int
32
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: Ptr PhysicalDevicePCIBusInfoPropertiesEXT -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDevicePCIBusInfoPropertiesEXT
p 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` Int
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` Int
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` Int
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` Int
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` Int
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` Int
28 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct PhysicalDevicePCIBusInfoPropertiesEXT where
  peekCStruct :: Ptr PhysicalDevicePCIBusInfoPropertiesEXT
-> IO PhysicalDevicePCIBusInfoPropertiesEXT
peekCStruct 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` Int
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` Int
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` Int
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` Int
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
_ = Int
32
  alignment :: PhysicalDevicePCIBusInfoPropertiesEXT -> Int
alignment ~PhysicalDevicePCIBusInfoPropertiesEXT
_ = Int
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 PhysicalDevicePCIBusInfoPropertiesEXT
ptr 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"