{-# language CPP #-}
module Vulkan.Extensions.VK_GGP_stream_descriptor_surface ( createStreamDescriptorSurfaceGGP
, StreamDescriptorSurfaceCreateInfoGGP(..)
, StreamDescriptorSurfaceCreateFlagsGGP(..)
, GGP_STREAM_DESCRIPTOR_SURFACE_SPEC_VERSION
, pattern GGP_STREAM_DESCRIPTOR_SURFACE_SPEC_VERSION
, GGP_STREAM_DESCRIPTOR_SURFACE_EXTENSION_NAME
, pattern GGP_STREAM_DESCRIPTOR_SURFACE_EXTENSION_NAME
, GgpStreamDescriptor
, SurfaceKHR(..)
) where
import Data.Bits (Bits)
import Data.Bits (FiniteBits)
import Vulkan.Internal.Utils (enumReadPrec)
import Vulkan.Internal.Utils (enumShowsPrec)
import Vulkan.Internal.Utils (traceAroundEvent)
import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
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 (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import GHC.Show (showString)
import Numeric (showHex)
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 Vulkan.Zero (Zero(..))
import Control.Monad.IO.Class (MonadIO)
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 GHC.IO.Exception (IOErrorType(..))
import GHC.IO.Exception (IOException(..))
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import GHC.Read (Read(readPrec))
import GHC.Show (Show(showsPrec))
import Data.Word (Word32)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Vulkan.NamedType ((:::))
import Vulkan.Core10.AllocationCallbacks (AllocationCallbacks)
import Vulkan.Core10.FundamentalTypes (Flags)
import Vulkan.Core10.Handles (Instance)
import Vulkan.Core10.Handles (Instance(..))
import Vulkan.Core10.Handles (Instance(Instance))
import Vulkan.Dynamic (InstanceCmds(pVkCreateStreamDescriptorSurfaceGGP))
import Vulkan.Core10.Handles (Instance_T)
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Extensions.Handles (SurfaceKHR)
import Vulkan.Extensions.Handles (SurfaceKHR(..))
import Vulkan.Exception (VulkanException(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_STREAM_DESCRIPTOR_SURFACE_CREATE_INFO_GGP))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
import Vulkan.Extensions.Handles (SurfaceKHR(..))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkCreateStreamDescriptorSurfaceGGP
:: FunPtr (Ptr Instance_T -> Ptr StreamDescriptorSurfaceCreateInfoGGP -> Ptr AllocationCallbacks -> Ptr SurfaceKHR -> IO Result) -> Ptr Instance_T -> Ptr StreamDescriptorSurfaceCreateInfoGGP -> Ptr AllocationCallbacks -> Ptr SurfaceKHR -> IO Result
createStreamDescriptorSurfaceGGP :: forall io
. (MonadIO io)
=>
Instance
->
StreamDescriptorSurfaceCreateInfoGGP
->
("allocator" ::: Maybe AllocationCallbacks)
-> io (SurfaceKHR)
createStreamDescriptorSurfaceGGP :: forall (io :: * -> *).
MonadIO io =>
Instance
-> StreamDescriptorSurfaceCreateInfoGGP
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io SurfaceKHR
createStreamDescriptorSurfaceGGP Instance
instance'
StreamDescriptorSurfaceCreateInfoGGP
createInfo
"allocator" ::: Maybe AllocationCallbacks
allocator = 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 vkCreateStreamDescriptorSurfaceGGPPtr :: FunPtr
(Ptr Instance_T
-> ("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pSurface" ::: Ptr SurfaceKHR)
-> IO Result)
vkCreateStreamDescriptorSurfaceGGPPtr = InstanceCmds
-> FunPtr
(Ptr Instance_T
-> ("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pSurface" ::: Ptr SurfaceKHR)
-> IO Result)
pVkCreateStreamDescriptorSurfaceGGP (case Instance
instance' of Instance{InstanceCmds
$sel:instanceCmds:Instance :: Instance -> InstanceCmds
instanceCmds :: InstanceCmds
instanceCmds} -> InstanceCmds
instanceCmds)
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 Instance_T
-> ("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pSurface" ::: Ptr SurfaceKHR)
-> IO Result)
vkCreateStreamDescriptorSurfaceGGPPtr 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 vkCreateStreamDescriptorSurfaceGGP is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkCreateStreamDescriptorSurfaceGGP' :: Ptr Instance_T
-> ("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pSurface" ::: Ptr SurfaceKHR)
-> IO Result
vkCreateStreamDescriptorSurfaceGGP' = FunPtr
(Ptr Instance_T
-> ("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pSurface" ::: Ptr SurfaceKHR)
-> IO Result)
-> Ptr Instance_T
-> ("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pSurface" ::: Ptr SurfaceKHR)
-> IO Result
mkVkCreateStreamDescriptorSurfaceGGP FunPtr
(Ptr Instance_T
-> ("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pSurface" ::: Ptr SurfaceKHR)
-> IO Result)
vkCreateStreamDescriptorSurfaceGGPPtr
"pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP
pCreateInfo <- 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 (StreamDescriptorSurfaceCreateInfoGGP
createInfo)
"pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
"allocator" ::: Maybe AllocationCallbacks
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Ptr a
nullPtr
Just AllocationCallbacks
j -> 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 (AllocationCallbacks
j)
"pSurface" ::: Ptr SurfaceKHR
pPSurface <- 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 @SurfaceKHR 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
"vkCreateStreamDescriptorSurfaceGGP" (Ptr Instance_T
-> ("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pSurface" ::: Ptr SurfaceKHR)
-> IO Result
vkCreateStreamDescriptorSurfaceGGP'
(Instance -> Ptr Instance_T
instanceHandle (Instance
instance'))
"pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP
pCreateInfo
"pAllocator" ::: Ptr AllocationCallbacks
pAllocator
("pSurface" ::: Ptr SurfaceKHR
pPSurface))
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))
SurfaceKHR
pSurface <- 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 @SurfaceKHR "pSurface" ::: Ptr SurfaceKHR
pPSurface
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ (SurfaceKHR
pSurface)
data StreamDescriptorSurfaceCreateInfoGGP = StreamDescriptorSurfaceCreateInfoGGP
{
StreamDescriptorSurfaceCreateInfoGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
flags :: StreamDescriptorSurfaceCreateFlagsGGP
,
StreamDescriptorSurfaceCreateInfoGGP -> GgpStreamDescriptor
streamDescriptor :: GgpStreamDescriptor
}
deriving (Typeable, StreamDescriptorSurfaceCreateInfoGGP
-> StreamDescriptorSurfaceCreateInfoGGP -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StreamDescriptorSurfaceCreateInfoGGP
-> StreamDescriptorSurfaceCreateInfoGGP -> Bool
$c/= :: StreamDescriptorSurfaceCreateInfoGGP
-> StreamDescriptorSurfaceCreateInfoGGP -> Bool
== :: StreamDescriptorSurfaceCreateInfoGGP
-> StreamDescriptorSurfaceCreateInfoGGP -> Bool
$c== :: StreamDescriptorSurfaceCreateInfoGGP
-> StreamDescriptorSurfaceCreateInfoGGP -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (StreamDescriptorSurfaceCreateInfoGGP)
#endif
deriving instance Show StreamDescriptorSurfaceCreateInfoGGP
instance ToCStruct StreamDescriptorSurfaceCreateInfoGGP where
withCStruct :: forall b.
StreamDescriptorSurfaceCreateInfoGGP
-> (("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
-> IO b)
-> IO b
withCStruct StreamDescriptorSurfaceCreateInfoGGP
x ("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
-> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \"pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP
p StreamDescriptorSurfaceCreateInfoGGP
x (("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
-> IO b
f "pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP
p)
pokeCStruct :: forall b.
("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
-> StreamDescriptorSurfaceCreateInfoGGP -> IO b -> IO b
pokeCStruct "pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP
p StreamDescriptorSurfaceCreateInfoGGP{GgpStreamDescriptor
StreamDescriptorSurfaceCreateFlagsGGP
streamDescriptor :: GgpStreamDescriptor
flags :: StreamDescriptorSurfaceCreateFlagsGGP
$sel:streamDescriptor:StreamDescriptorSurfaceCreateInfoGGP :: StreamDescriptorSurfaceCreateInfoGGP -> GgpStreamDescriptor
$sel:flags:StreamDescriptorSurfaceCreateInfoGGP :: StreamDescriptorSurfaceCreateInfoGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_STREAM_DESCRIPTOR_SURFACE_CREATE_INFO_GGP)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP
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 (("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr StreamDescriptorSurfaceCreateFlagsGGP)) (StreamDescriptorSurfaceCreateFlagsGGP
flags)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr GgpStreamDescriptor)) (GgpStreamDescriptor
streamDescriptor)
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
-> IO b -> IO b
pokeZeroCStruct "pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_STREAM_DESCRIPTOR_SURFACE_CREATE_INFO_GGP)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP
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 (("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr GgpStreamDescriptor)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct StreamDescriptorSurfaceCreateInfoGGP where
peekCStruct :: ("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
-> IO StreamDescriptorSurfaceCreateInfoGGP
peekCStruct "pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP
p = do
StreamDescriptorSurfaceCreateFlagsGGP
flags <- forall a. Storable a => Ptr a -> IO a
peek @StreamDescriptorSurfaceCreateFlagsGGP (("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr StreamDescriptorSurfaceCreateFlagsGGP))
GgpStreamDescriptor
streamDescriptor <- forall a. Storable a => Ptr a -> IO a
peek @GgpStreamDescriptor (("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr GgpStreamDescriptor))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ StreamDescriptorSurfaceCreateFlagsGGP
-> GgpStreamDescriptor -> StreamDescriptorSurfaceCreateInfoGGP
StreamDescriptorSurfaceCreateInfoGGP
StreamDescriptorSurfaceCreateFlagsGGP
flags GgpStreamDescriptor
streamDescriptor
instance Storable StreamDescriptorSurfaceCreateInfoGGP where
sizeOf :: StreamDescriptorSurfaceCreateInfoGGP -> Int
sizeOf ~StreamDescriptorSurfaceCreateInfoGGP
_ = Int
24
alignment :: StreamDescriptorSurfaceCreateInfoGGP -> Int
alignment ~StreamDescriptorSurfaceCreateInfoGGP
_ = Int
8
peek :: ("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
-> IO StreamDescriptorSurfaceCreateInfoGGP
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
-> StreamDescriptorSurfaceCreateInfoGGP -> IO ()
poke "pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP
ptr StreamDescriptorSurfaceCreateInfoGGP
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP
ptr StreamDescriptorSurfaceCreateInfoGGP
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero StreamDescriptorSurfaceCreateInfoGGP where
zero :: StreamDescriptorSurfaceCreateInfoGGP
zero = StreamDescriptorSurfaceCreateFlagsGGP
-> GgpStreamDescriptor -> StreamDescriptorSurfaceCreateInfoGGP
StreamDescriptorSurfaceCreateInfoGGP
forall a. Zero a => a
zero
forall a. Zero a => a
zero
newtype StreamDescriptorSurfaceCreateFlagsGGP = StreamDescriptorSurfaceCreateFlagsGGP Flags
deriving newtype (StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> Bool
$c/= :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> Bool
== :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> Bool
$c== :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> Bool
Eq, Eq StreamDescriptorSurfaceCreateFlagsGGP
StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> Bool
StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> Ordering
StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
$cmin :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
max :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
$cmax :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
>= :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> Bool
$c>= :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> Bool
> :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> Bool
$c> :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> Bool
<= :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> Bool
$c<= :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> Bool
< :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> Bool
$c< :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> Bool
compare :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> Ordering
$ccompare :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> Ordering
Ord, Ptr StreamDescriptorSurfaceCreateFlagsGGP
-> IO StreamDescriptorSurfaceCreateFlagsGGP
Ptr StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> IO StreamDescriptorSurfaceCreateFlagsGGP
Ptr StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP -> IO ()
Ptr StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> IO ()
StreamDescriptorSurfaceCreateFlagsGGP -> Int
forall b. Ptr b -> Int -> IO StreamDescriptorSurfaceCreateFlagsGGP
forall b.
Ptr b -> Int -> StreamDescriptorSurfaceCreateFlagsGGP -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> IO ()
$cpoke :: Ptr StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> IO ()
peek :: Ptr StreamDescriptorSurfaceCreateFlagsGGP
-> IO StreamDescriptorSurfaceCreateFlagsGGP
$cpeek :: Ptr StreamDescriptorSurfaceCreateFlagsGGP
-> IO StreamDescriptorSurfaceCreateFlagsGGP
pokeByteOff :: forall b.
Ptr b -> Int -> StreamDescriptorSurfaceCreateFlagsGGP -> IO ()
$cpokeByteOff :: forall b.
Ptr b -> Int -> StreamDescriptorSurfaceCreateFlagsGGP -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO StreamDescriptorSurfaceCreateFlagsGGP
$cpeekByteOff :: forall b. Ptr b -> Int -> IO StreamDescriptorSurfaceCreateFlagsGGP
pokeElemOff :: Ptr StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP -> IO ()
$cpokeElemOff :: Ptr StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP -> IO ()
peekElemOff :: Ptr StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> IO StreamDescriptorSurfaceCreateFlagsGGP
$cpeekElemOff :: Ptr StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> IO StreamDescriptorSurfaceCreateFlagsGGP
alignment :: StreamDescriptorSurfaceCreateFlagsGGP -> Int
$calignment :: StreamDescriptorSurfaceCreateFlagsGGP -> Int
sizeOf :: StreamDescriptorSurfaceCreateFlagsGGP -> Int
$csizeOf :: StreamDescriptorSurfaceCreateFlagsGGP -> Int
Storable, StreamDescriptorSurfaceCreateFlagsGGP
forall a. a -> Zero a
zero :: StreamDescriptorSurfaceCreateFlagsGGP
$czero :: StreamDescriptorSurfaceCreateFlagsGGP
Zero, Eq StreamDescriptorSurfaceCreateFlagsGGP
StreamDescriptorSurfaceCreateFlagsGGP
Int -> StreamDescriptorSurfaceCreateFlagsGGP
StreamDescriptorSurfaceCreateFlagsGGP -> Bool
StreamDescriptorSurfaceCreateFlagsGGP -> Int
StreamDescriptorSurfaceCreateFlagsGGP -> Maybe Int
StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
StreamDescriptorSurfaceCreateFlagsGGP -> Int -> Bool
StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
forall a.
Eq a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
popCount :: StreamDescriptorSurfaceCreateFlagsGGP -> Int
$cpopCount :: StreamDescriptorSurfaceCreateFlagsGGP -> Int
rotateR :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
$crotateR :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
rotateL :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
$crotateL :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
unsafeShiftR :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
$cunsafeShiftR :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
shiftR :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
$cshiftR :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
unsafeShiftL :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
$cunsafeShiftL :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
shiftL :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
$cshiftL :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
isSigned :: StreamDescriptorSurfaceCreateFlagsGGP -> Bool
$cisSigned :: StreamDescriptorSurfaceCreateFlagsGGP -> Bool
bitSize :: StreamDescriptorSurfaceCreateFlagsGGP -> Int
$cbitSize :: StreamDescriptorSurfaceCreateFlagsGGP -> Int
bitSizeMaybe :: StreamDescriptorSurfaceCreateFlagsGGP -> Maybe Int
$cbitSizeMaybe :: StreamDescriptorSurfaceCreateFlagsGGP -> Maybe Int
testBit :: StreamDescriptorSurfaceCreateFlagsGGP -> Int -> Bool
$ctestBit :: StreamDescriptorSurfaceCreateFlagsGGP -> Int -> Bool
complementBit :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
$ccomplementBit :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
clearBit :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
$cclearBit :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
setBit :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
$csetBit :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
bit :: Int -> StreamDescriptorSurfaceCreateFlagsGGP
$cbit :: Int -> StreamDescriptorSurfaceCreateFlagsGGP
zeroBits :: StreamDescriptorSurfaceCreateFlagsGGP
$czeroBits :: StreamDescriptorSurfaceCreateFlagsGGP
rotate :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
$crotate :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
shift :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
$cshift :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
complement :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
$ccomplement :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
xor :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
$cxor :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
.|. :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
$c.|. :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
.&. :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
$c.&. :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
Bits, Bits StreamDescriptorSurfaceCreateFlagsGGP
StreamDescriptorSurfaceCreateFlagsGGP -> Int
forall b.
Bits b -> (b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
countTrailingZeros :: StreamDescriptorSurfaceCreateFlagsGGP -> Int
$ccountTrailingZeros :: StreamDescriptorSurfaceCreateFlagsGGP -> Int
countLeadingZeros :: StreamDescriptorSurfaceCreateFlagsGGP -> Int
$ccountLeadingZeros :: StreamDescriptorSurfaceCreateFlagsGGP -> Int
finiteBitSize :: StreamDescriptorSurfaceCreateFlagsGGP -> Int
$cfiniteBitSize :: StreamDescriptorSurfaceCreateFlagsGGP -> Int
FiniteBits)
conNameStreamDescriptorSurfaceCreateFlagsGGP :: String
conNameStreamDescriptorSurfaceCreateFlagsGGP :: String
conNameStreamDescriptorSurfaceCreateFlagsGGP = String
"StreamDescriptorSurfaceCreateFlagsGGP"
enumPrefixStreamDescriptorSurfaceCreateFlagsGGP :: String
enumPrefixStreamDescriptorSurfaceCreateFlagsGGP :: String
enumPrefixStreamDescriptorSurfaceCreateFlagsGGP = String
""
showTableStreamDescriptorSurfaceCreateFlagsGGP :: [(StreamDescriptorSurfaceCreateFlagsGGP, String)]
showTableStreamDescriptorSurfaceCreateFlagsGGP :: [(StreamDescriptorSurfaceCreateFlagsGGP, String)]
showTableStreamDescriptorSurfaceCreateFlagsGGP = []
instance Show StreamDescriptorSurfaceCreateFlagsGGP where
showsPrec :: Int -> StreamDescriptorSurfaceCreateFlagsGGP -> ShowS
showsPrec =
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
String
enumPrefixStreamDescriptorSurfaceCreateFlagsGGP
[(StreamDescriptorSurfaceCreateFlagsGGP, String)]
showTableStreamDescriptorSurfaceCreateFlagsGGP
String
conNameStreamDescriptorSurfaceCreateFlagsGGP
(\(StreamDescriptorSurfaceCreateFlagsGGP GgpStreamDescriptor
x) -> GgpStreamDescriptor
x)
(\GgpStreamDescriptor
x -> String -> ShowS
showString String
"0x" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (Integral a, Show a) => a -> ShowS
showHex GgpStreamDescriptor
x)
instance Read StreamDescriptorSurfaceCreateFlagsGGP where
readPrec :: ReadPrec StreamDescriptorSurfaceCreateFlagsGGP
readPrec =
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
String
enumPrefixStreamDescriptorSurfaceCreateFlagsGGP
[(StreamDescriptorSurfaceCreateFlagsGGP, String)]
showTableStreamDescriptorSurfaceCreateFlagsGGP
String
conNameStreamDescriptorSurfaceCreateFlagsGGP
GgpStreamDescriptor -> StreamDescriptorSurfaceCreateFlagsGGP
StreamDescriptorSurfaceCreateFlagsGGP
type GGP_STREAM_DESCRIPTOR_SURFACE_SPEC_VERSION = 1
pattern GGP_STREAM_DESCRIPTOR_SURFACE_SPEC_VERSION :: forall a . Integral a => a
pattern $bGGP_STREAM_DESCRIPTOR_SURFACE_SPEC_VERSION :: forall a. Integral a => a
$mGGP_STREAM_DESCRIPTOR_SURFACE_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
GGP_STREAM_DESCRIPTOR_SURFACE_SPEC_VERSION = 1
type GGP_STREAM_DESCRIPTOR_SURFACE_EXTENSION_NAME = "VK_GGP_stream_descriptor_surface"
pattern GGP_STREAM_DESCRIPTOR_SURFACE_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bGGP_STREAM_DESCRIPTOR_SURFACE_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mGGP_STREAM_DESCRIPTOR_SURFACE_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
GGP_STREAM_DESCRIPTOR_SURFACE_EXTENSION_NAME = "VK_GGP_stream_descriptor_surface"
type GgpStreamDescriptor = Word32