{-# language CPP #-}
module Vulkan.Extensions.VK_EXT_depth_bias_control ( cmdSetDepthBias2EXT
, DepthBiasInfoEXT(..)
, DepthBiasRepresentationInfoEXT(..)
, PhysicalDeviceDepthBiasControlFeaturesEXT(..)
, DepthBiasRepresentationEXT( DEPTH_BIAS_REPRESENTATION_LEAST_REPRESENTABLE_VALUE_FORMAT_EXT
, DEPTH_BIAS_REPRESENTATION_LEAST_REPRESENTABLE_VALUE_FORCE_UNORM_EXT
, DEPTH_BIAS_REPRESENTATION_FLOAT_EXT
, ..
)
, EXT_DEPTH_BIAS_CONTROL_SPEC_VERSION
, pattern EXT_DEPTH_BIAS_CONTROL_SPEC_VERSION
, EXT_DEPTH_BIAS_CONTROL_EXTENSION_NAME
, pattern EXT_DEPTH_BIAS_CONTROL_EXTENSION_NAME
) where
import Vulkan.Internal.Utils (enumReadPrec)
import Vulkan.Internal.Utils (enumShowsPrec)
import Vulkan.Internal.Utils (traceAroundEvent)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Data.Typeable (eqT)
import Foreign.Marshal.Alloc (allocaBytes)
import GHC.IO (throwIO)
import GHC.Ptr (castPtr)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import GHC.Show (showsPrec)
import Data.Coerce (coerce)
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.Type.Equality ((:~:)(Refl))
import Data.Typeable (Typeable)
import Foreign.C.Types (CFloat)
import Foreign.C.Types (CFloat(..))
import Foreign.C.Types (CFloat(CFloat))
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 Data.Int (Int32)
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import GHC.Read (Read(readPrec))
import GHC.Show (Show(showsPrec))
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.CStruct.Extends (forgetExtensions)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.CStruct.Extends (Chain)
import Vulkan.Core10.Handles (CommandBuffer)
import Vulkan.Core10.Handles (CommandBuffer(..))
import Vulkan.Core10.Handles (CommandBuffer(CommandBuffer))
import Vulkan.Core10.Handles (CommandBuffer_T)
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetDepthBias2EXT))
import Vulkan.CStruct.Extends (Extends)
import Vulkan.CStruct.Extends (Extendss)
import Vulkan.CStruct.Extends (Extensible(..))
import Vulkan.CStruct.Extends (PeekChain)
import Vulkan.CStruct.Extends (PeekChain(..))
import Vulkan.CStruct.Extends (PokeChain)
import Vulkan.CStruct.Extends (PokeChain(..))
import Vulkan.CStruct.Extends (SomeStruct)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DEPTH_BIAS_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DEPTH_BIAS_REPRESENTATION_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_DEPTH_BIAS_CONTROL_FEATURES_EXT))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkCmdSetDepthBias2EXT
:: FunPtr (Ptr CommandBuffer_T -> Ptr (SomeStruct DepthBiasInfoEXT) -> IO ()) -> Ptr CommandBuffer_T -> Ptr (SomeStruct DepthBiasInfoEXT) -> IO ()
cmdSetDepthBias2EXT :: forall a io
. (Extendss DepthBiasInfoEXT a, PokeChain a, MonadIO io)
=>
CommandBuffer
->
(DepthBiasInfoEXT a)
-> io ()
cmdSetDepthBias2EXT :: forall (a :: [*]) (io :: * -> *).
(Extendss DepthBiasInfoEXT a, PokeChain a, MonadIO io) =>
CommandBuffer -> DepthBiasInfoEXT a -> io ()
cmdSetDepthBias2EXT CommandBuffer
commandBuffer DepthBiasInfoEXT a
depthBiasInfo = 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 vkCmdSetDepthBias2EXTPtr :: FunPtr
(Ptr CommandBuffer_T
-> ("pDepthBiasInfo" ::: Ptr (SomeStruct DepthBiasInfoEXT))
-> IO ())
vkCmdSetDepthBias2EXTPtr = DeviceCmds
-> FunPtr
(Ptr CommandBuffer_T
-> ("pDepthBiasInfo" ::: Ptr (SomeStruct DepthBiasInfoEXT))
-> IO ())
pVkCmdSetDepthBias2EXT (case CommandBuffer
commandBuffer of CommandBuffer{DeviceCmds
$sel:deviceCmds:CommandBuffer :: CommandBuffer -> 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 CommandBuffer_T
-> ("pDepthBiasInfo" ::: Ptr (SomeStruct DepthBiasInfoEXT))
-> IO ())
vkCmdSetDepthBias2EXTPtr 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 vkCmdSetDepthBias2EXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkCmdSetDepthBias2EXT' :: Ptr CommandBuffer_T
-> ("pDepthBiasInfo" ::: Ptr (SomeStruct DepthBiasInfoEXT))
-> IO ()
vkCmdSetDepthBias2EXT' = FunPtr
(Ptr CommandBuffer_T
-> ("pDepthBiasInfo" ::: Ptr (SomeStruct DepthBiasInfoEXT))
-> IO ())
-> Ptr CommandBuffer_T
-> ("pDepthBiasInfo" ::: Ptr (SomeStruct DepthBiasInfoEXT))
-> IO ()
mkVkCmdSetDepthBias2EXT FunPtr
(Ptr CommandBuffer_T
-> ("pDepthBiasInfo" ::: Ptr (SomeStruct DepthBiasInfoEXT))
-> IO ())
vkCmdSetDepthBias2EXTPtr
Ptr (DepthBiasInfoEXT a)
pDepthBiasInfo <- 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 (DepthBiasInfoEXT a
depthBiasInfo)
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
"vkCmdSetDepthBias2EXT" (Ptr CommandBuffer_T
-> ("pDepthBiasInfo" ::: Ptr (SomeStruct DepthBiasInfoEXT))
-> IO ()
vkCmdSetDepthBias2EXT'
(CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
(forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions Ptr (DepthBiasInfoEXT a)
pDepthBiasInfo))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ()
data DepthBiasInfoEXT (es :: [Type]) = DepthBiasInfoEXT
{
forall (es :: [*]). DepthBiasInfoEXT es -> Chain es
next :: Chain es
,
forall (es :: [*]). DepthBiasInfoEXT es -> Float
depthBiasConstantFactor :: Float
,
forall (es :: [*]). DepthBiasInfoEXT es -> Float
depthBiasClamp :: Float
,
forall (es :: [*]). DepthBiasInfoEXT es -> Float
depthBiasSlopeFactor :: Float
}
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DepthBiasInfoEXT (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (DepthBiasInfoEXT es)
instance Extensible DepthBiasInfoEXT where
extensibleTypeName :: String
extensibleTypeName = String
"DepthBiasInfoEXT"
setNext :: forall (ds :: [*]) (es :: [*]).
DepthBiasInfoEXT ds -> Chain es -> DepthBiasInfoEXT es
setNext DepthBiasInfoEXT{Float
Chain ds
depthBiasSlopeFactor :: Float
depthBiasClamp :: Float
depthBiasConstantFactor :: Float
next :: Chain ds
$sel:depthBiasSlopeFactor:DepthBiasInfoEXT :: forall (es :: [*]). DepthBiasInfoEXT es -> Float
$sel:depthBiasClamp:DepthBiasInfoEXT :: forall (es :: [*]). DepthBiasInfoEXT es -> Float
$sel:depthBiasConstantFactor:DepthBiasInfoEXT :: forall (es :: [*]). DepthBiasInfoEXT es -> Float
$sel:next:DepthBiasInfoEXT :: forall (es :: [*]). DepthBiasInfoEXT es -> Chain es
..} Chain es
next' = DepthBiasInfoEXT{$sel:next:DepthBiasInfoEXT :: Chain es
next = Chain es
next', Float
depthBiasSlopeFactor :: Float
depthBiasClamp :: Float
depthBiasConstantFactor :: Float
$sel:depthBiasSlopeFactor:DepthBiasInfoEXT :: Float
$sel:depthBiasClamp:DepthBiasInfoEXT :: Float
$sel:depthBiasConstantFactor:DepthBiasInfoEXT :: Float
..}
getNext :: forall (es :: [*]). DepthBiasInfoEXT es -> Chain es
getNext DepthBiasInfoEXT{Float
Chain es
depthBiasSlopeFactor :: Float
depthBiasClamp :: Float
depthBiasConstantFactor :: Float
next :: Chain es
$sel:depthBiasSlopeFactor:DepthBiasInfoEXT :: forall (es :: [*]). DepthBiasInfoEXT es -> Float
$sel:depthBiasClamp:DepthBiasInfoEXT :: forall (es :: [*]). DepthBiasInfoEXT es -> Float
$sel:depthBiasConstantFactor:DepthBiasInfoEXT :: forall (es :: [*]). DepthBiasInfoEXT es -> Float
$sel:next:DepthBiasInfoEXT :: forall (es :: [*]). DepthBiasInfoEXT es -> Chain es
..} = Chain es
next
extends :: forall e b proxy. Typeable e => proxy e -> (Extends DepthBiasInfoEXT e => b) -> Maybe b
extends :: forall e b (proxy :: * -> *).
Typeable e =>
proxy e -> (Extends DepthBiasInfoEXT e => b) -> Maybe b
extends proxy e
_ Extends DepthBiasInfoEXT e => b
f
| Just e :~: DepthBiasRepresentationInfoEXT
Refl <- forall {k} (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @DepthBiasRepresentationInfoEXT = forall a. a -> Maybe a
Just Extends DepthBiasInfoEXT e => b
f
| Bool
otherwise = forall a. Maybe a
Nothing
instance ( Extendss DepthBiasInfoEXT es
, PokeChain es ) => ToCStruct (DepthBiasInfoEXT es) where
withCStruct :: forall b.
DepthBiasInfoEXT es -> (Ptr (DepthBiasInfoEXT es) -> IO b) -> IO b
withCStruct DepthBiasInfoEXT es
x Ptr (DepthBiasInfoEXT 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 (DepthBiasInfoEXT es)
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (DepthBiasInfoEXT es)
p DepthBiasInfoEXT es
x (Ptr (DepthBiasInfoEXT es) -> IO b
f Ptr (DepthBiasInfoEXT es)
p)
pokeCStruct :: forall b.
Ptr (DepthBiasInfoEXT es) -> DepthBiasInfoEXT es -> IO b -> IO b
pokeCStruct Ptr (DepthBiasInfoEXT es)
p DepthBiasInfoEXT{Float
Chain es
depthBiasSlopeFactor :: Float
depthBiasClamp :: Float
depthBiasConstantFactor :: Float
next :: Chain es
$sel:depthBiasSlopeFactor:DepthBiasInfoEXT :: forall (es :: [*]). DepthBiasInfoEXT es -> Float
$sel:depthBiasClamp:DepthBiasInfoEXT :: forall (es :: [*]). DepthBiasInfoEXT es -> Float
$sel:depthBiasConstantFactor:DepthBiasInfoEXT :: forall (es :: [*]). DepthBiasInfoEXT es -> Float
$sel:next:DepthBiasInfoEXT :: forall (es :: [*]). DepthBiasInfoEXT 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 (DepthBiasInfoEXT es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEPTH_BIAS_INFO_EXT)
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 (DepthBiasInfoEXT 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 (DepthBiasInfoEXT es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
depthBiasConstantFactor))
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 (DepthBiasInfoEXT es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
depthBiasClamp))
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 (DepthBiasInfoEXT es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
depthBiasSlopeFactor))
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 (DepthBiasInfoEXT es) -> IO b -> IO b
pokeZeroCStruct Ptr (DepthBiasInfoEXT 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 (DepthBiasInfoEXT es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEPTH_BIAS_INFO_EXT)
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 (DepthBiasInfoEXT 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 (DepthBiasInfoEXT es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr CFloat)) (Float -> CFloat
CFloat (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 (DepthBiasInfoEXT es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr CFloat)) (Float -> CFloat
CFloat (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 (DepthBiasInfoEXT es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr CFloat)) (Float -> CFloat
CFloat (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 DepthBiasInfoEXT es
, PeekChain es ) => FromCStruct (DepthBiasInfoEXT es) where
peekCStruct :: Ptr (DepthBiasInfoEXT es) -> IO (DepthBiasInfoEXT es)
peekCStruct Ptr (DepthBiasInfoEXT es)
p = do
Ptr ()
pNext <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (DepthBiasInfoEXT 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)
CFloat
depthBiasConstantFactor <- forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr (DepthBiasInfoEXT es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr CFloat))
CFloat
depthBiasClamp <- forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr (DepthBiasInfoEXT es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr CFloat))
CFloat
depthBiasSlopeFactor <- forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr (DepthBiasInfoEXT es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr CFloat))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (es :: [*]).
Chain es -> Float -> Float -> Float -> DepthBiasInfoEXT es
DepthBiasInfoEXT
Chain es
next
(coerce :: forall a b. Coercible a b => a -> b
coerce @CFloat @Float CFloat
depthBiasConstantFactor)
(coerce :: forall a b. Coercible a b => a -> b
coerce @CFloat @Float CFloat
depthBiasClamp)
(coerce :: forall a b. Coercible a b => a -> b
coerce @CFloat @Float CFloat
depthBiasSlopeFactor)
instance es ~ '[] => Zero (DepthBiasInfoEXT es) where
zero :: DepthBiasInfoEXT es
zero = forall (es :: [*]).
Chain es -> Float -> Float -> Float -> DepthBiasInfoEXT es
DepthBiasInfoEXT
()
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data DepthBiasRepresentationInfoEXT = DepthBiasRepresentationInfoEXT
{
DepthBiasRepresentationInfoEXT -> DepthBiasRepresentationEXT
depthBiasRepresentation :: DepthBiasRepresentationEXT
,
DepthBiasRepresentationInfoEXT -> Bool
depthBiasExact :: Bool
}
deriving (Typeable, DepthBiasRepresentationInfoEXT
-> DepthBiasRepresentationInfoEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DepthBiasRepresentationInfoEXT
-> DepthBiasRepresentationInfoEXT -> Bool
$c/= :: DepthBiasRepresentationInfoEXT
-> DepthBiasRepresentationInfoEXT -> Bool
== :: DepthBiasRepresentationInfoEXT
-> DepthBiasRepresentationInfoEXT -> Bool
$c== :: DepthBiasRepresentationInfoEXT
-> DepthBiasRepresentationInfoEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DepthBiasRepresentationInfoEXT)
#endif
deriving instance Show DepthBiasRepresentationInfoEXT
instance ToCStruct DepthBiasRepresentationInfoEXT where
withCStruct :: forall b.
DepthBiasRepresentationInfoEXT
-> (Ptr DepthBiasRepresentationInfoEXT -> IO b) -> IO b
withCStruct DepthBiasRepresentationInfoEXT
x Ptr DepthBiasRepresentationInfoEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr DepthBiasRepresentationInfoEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DepthBiasRepresentationInfoEXT
p DepthBiasRepresentationInfoEXT
x (Ptr DepthBiasRepresentationInfoEXT -> IO b
f Ptr DepthBiasRepresentationInfoEXT
p)
pokeCStruct :: forall b.
Ptr DepthBiasRepresentationInfoEXT
-> DepthBiasRepresentationInfoEXT -> IO b -> IO b
pokeCStruct Ptr DepthBiasRepresentationInfoEXT
p DepthBiasRepresentationInfoEXT{Bool
DepthBiasRepresentationEXT
depthBiasExact :: Bool
depthBiasRepresentation :: DepthBiasRepresentationEXT
$sel:depthBiasExact:DepthBiasRepresentationInfoEXT :: DepthBiasRepresentationInfoEXT -> Bool
$sel:depthBiasRepresentation:DepthBiasRepresentationInfoEXT :: DepthBiasRepresentationInfoEXT -> DepthBiasRepresentationEXT
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DepthBiasRepresentationInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEPTH_BIAS_REPRESENTATION_INFO_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DepthBiasRepresentationInfoEXT
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 DepthBiasRepresentationInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DepthBiasRepresentationEXT)) (DepthBiasRepresentationEXT
depthBiasRepresentation)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DepthBiasRepresentationInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
depthBiasExact))
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr DepthBiasRepresentationInfoEXT -> IO b -> IO b
pokeZeroCStruct Ptr DepthBiasRepresentationInfoEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DepthBiasRepresentationInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEPTH_BIAS_REPRESENTATION_INFO_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DepthBiasRepresentationInfoEXT
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 DepthBiasRepresentationInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DepthBiasRepresentationEXT)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DepthBiasRepresentationInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
IO b
f
instance FromCStruct DepthBiasRepresentationInfoEXT where
peekCStruct :: Ptr DepthBiasRepresentationInfoEXT
-> IO DepthBiasRepresentationInfoEXT
peekCStruct Ptr DepthBiasRepresentationInfoEXT
p = do
DepthBiasRepresentationEXT
depthBiasRepresentation <- forall a. Storable a => Ptr a -> IO a
peek @DepthBiasRepresentationEXT ((Ptr DepthBiasRepresentationInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DepthBiasRepresentationEXT))
Bool32
depthBiasExact <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr DepthBiasRepresentationInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ DepthBiasRepresentationEXT
-> Bool -> DepthBiasRepresentationInfoEXT
DepthBiasRepresentationInfoEXT
DepthBiasRepresentationEXT
depthBiasRepresentation (Bool32 -> Bool
bool32ToBool Bool32
depthBiasExact)
instance Storable DepthBiasRepresentationInfoEXT where
sizeOf :: DepthBiasRepresentationInfoEXT -> Int
sizeOf ~DepthBiasRepresentationInfoEXT
_ = Int
24
alignment :: DepthBiasRepresentationInfoEXT -> Int
alignment ~DepthBiasRepresentationInfoEXT
_ = Int
8
peek :: Ptr DepthBiasRepresentationInfoEXT
-> IO DepthBiasRepresentationInfoEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr DepthBiasRepresentationInfoEXT
-> DepthBiasRepresentationInfoEXT -> IO ()
poke Ptr DepthBiasRepresentationInfoEXT
ptr DepthBiasRepresentationInfoEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DepthBiasRepresentationInfoEXT
ptr DepthBiasRepresentationInfoEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero DepthBiasRepresentationInfoEXT where
zero :: DepthBiasRepresentationInfoEXT
zero = DepthBiasRepresentationEXT
-> Bool -> DepthBiasRepresentationInfoEXT
DepthBiasRepresentationInfoEXT
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data PhysicalDeviceDepthBiasControlFeaturesEXT = PhysicalDeviceDepthBiasControlFeaturesEXT
{
PhysicalDeviceDepthBiasControlFeaturesEXT -> Bool
depthBiasControl :: Bool
,
PhysicalDeviceDepthBiasControlFeaturesEXT -> Bool
leastRepresentableValueForceUnormRepresentation :: Bool
,
PhysicalDeviceDepthBiasControlFeaturesEXT -> Bool
floatRepresentation :: Bool
,
PhysicalDeviceDepthBiasControlFeaturesEXT -> Bool
depthBiasExact :: Bool
}
deriving (Typeable, PhysicalDeviceDepthBiasControlFeaturesEXT
-> PhysicalDeviceDepthBiasControlFeaturesEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceDepthBiasControlFeaturesEXT
-> PhysicalDeviceDepthBiasControlFeaturesEXT -> Bool
$c/= :: PhysicalDeviceDepthBiasControlFeaturesEXT
-> PhysicalDeviceDepthBiasControlFeaturesEXT -> Bool
== :: PhysicalDeviceDepthBiasControlFeaturesEXT
-> PhysicalDeviceDepthBiasControlFeaturesEXT -> Bool
$c== :: PhysicalDeviceDepthBiasControlFeaturesEXT
-> PhysicalDeviceDepthBiasControlFeaturesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceDepthBiasControlFeaturesEXT)
#endif
deriving instance Show PhysicalDeviceDepthBiasControlFeaturesEXT
instance ToCStruct PhysicalDeviceDepthBiasControlFeaturesEXT where
withCStruct :: forall b.
PhysicalDeviceDepthBiasControlFeaturesEXT
-> (Ptr PhysicalDeviceDepthBiasControlFeaturesEXT -> IO b) -> IO b
withCStruct PhysicalDeviceDepthBiasControlFeaturesEXT
x Ptr PhysicalDeviceDepthBiasControlFeaturesEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceDepthBiasControlFeaturesEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDepthBiasControlFeaturesEXT
p PhysicalDeviceDepthBiasControlFeaturesEXT
x (Ptr PhysicalDeviceDepthBiasControlFeaturesEXT -> IO b
f Ptr PhysicalDeviceDepthBiasControlFeaturesEXT
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceDepthBiasControlFeaturesEXT
-> PhysicalDeviceDepthBiasControlFeaturesEXT -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDepthBiasControlFeaturesEXT
p PhysicalDeviceDepthBiasControlFeaturesEXT{Bool
depthBiasExact :: Bool
floatRepresentation :: Bool
leastRepresentableValueForceUnormRepresentation :: Bool
depthBiasControl :: Bool
$sel:depthBiasExact:PhysicalDeviceDepthBiasControlFeaturesEXT :: PhysicalDeviceDepthBiasControlFeaturesEXT -> Bool
$sel:floatRepresentation:PhysicalDeviceDepthBiasControlFeaturesEXT :: PhysicalDeviceDepthBiasControlFeaturesEXT -> Bool
$sel:leastRepresentableValueForceUnormRepresentation:PhysicalDeviceDepthBiasControlFeaturesEXT :: PhysicalDeviceDepthBiasControlFeaturesEXT -> Bool
$sel:depthBiasControl:PhysicalDeviceDepthBiasControlFeaturesEXT :: PhysicalDeviceDepthBiasControlFeaturesEXT -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDepthBiasControlFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_DEPTH_BIAS_CONTROL_FEATURES_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDepthBiasControlFeaturesEXT
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 PhysicalDeviceDepthBiasControlFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
depthBiasControl))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDepthBiasControlFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
leastRepresentableValueForceUnormRepresentation))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDepthBiasControlFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
floatRepresentation))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDepthBiasControlFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
depthBiasExact))
IO b
f
cStructSize :: Int
cStructSize = Int
32
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceDepthBiasControlFeaturesEXT -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceDepthBiasControlFeaturesEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDepthBiasControlFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_DEPTH_BIAS_CONTROL_FEATURES_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDepthBiasControlFeaturesEXT
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 PhysicalDeviceDepthBiasControlFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDepthBiasControlFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDepthBiasControlFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDepthBiasControlFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
IO b
f
instance FromCStruct PhysicalDeviceDepthBiasControlFeaturesEXT where
peekCStruct :: Ptr PhysicalDeviceDepthBiasControlFeaturesEXT
-> IO PhysicalDeviceDepthBiasControlFeaturesEXT
peekCStruct Ptr PhysicalDeviceDepthBiasControlFeaturesEXT
p = do
Bool32
depthBiasControl <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDepthBiasControlFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
Bool32
leastRepresentableValueForceUnormRepresentation <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDepthBiasControlFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32))
Bool32
floatRepresentation <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDepthBiasControlFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32))
Bool32
depthBiasExact <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDepthBiasControlFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Bool32))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Bool
-> Bool
-> Bool
-> Bool
-> PhysicalDeviceDepthBiasControlFeaturesEXT
PhysicalDeviceDepthBiasControlFeaturesEXT
(Bool32 -> Bool
bool32ToBool Bool32
depthBiasControl)
(Bool32 -> Bool
bool32ToBool Bool32
leastRepresentableValueForceUnormRepresentation)
(Bool32 -> Bool
bool32ToBool Bool32
floatRepresentation)
(Bool32 -> Bool
bool32ToBool Bool32
depthBiasExact)
instance Storable PhysicalDeviceDepthBiasControlFeaturesEXT where
sizeOf :: PhysicalDeviceDepthBiasControlFeaturesEXT -> Int
sizeOf ~PhysicalDeviceDepthBiasControlFeaturesEXT
_ = Int
32
alignment :: PhysicalDeviceDepthBiasControlFeaturesEXT -> Int
alignment ~PhysicalDeviceDepthBiasControlFeaturesEXT
_ = Int
8
peek :: Ptr PhysicalDeviceDepthBiasControlFeaturesEXT
-> IO PhysicalDeviceDepthBiasControlFeaturesEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceDepthBiasControlFeaturesEXT
-> PhysicalDeviceDepthBiasControlFeaturesEXT -> IO ()
poke Ptr PhysicalDeviceDepthBiasControlFeaturesEXT
ptr PhysicalDeviceDepthBiasControlFeaturesEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDepthBiasControlFeaturesEXT
ptr PhysicalDeviceDepthBiasControlFeaturesEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceDepthBiasControlFeaturesEXT where
zero :: PhysicalDeviceDepthBiasControlFeaturesEXT
zero = Bool
-> Bool
-> Bool
-> Bool
-> PhysicalDeviceDepthBiasControlFeaturesEXT
PhysicalDeviceDepthBiasControlFeaturesEXT
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
newtype DepthBiasRepresentationEXT = DepthBiasRepresentationEXT Int32
deriving newtype (DepthBiasRepresentationEXT -> DepthBiasRepresentationEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DepthBiasRepresentationEXT -> DepthBiasRepresentationEXT -> Bool
$c/= :: DepthBiasRepresentationEXT -> DepthBiasRepresentationEXT -> Bool
== :: DepthBiasRepresentationEXT -> DepthBiasRepresentationEXT -> Bool
$c== :: DepthBiasRepresentationEXT -> DepthBiasRepresentationEXT -> Bool
Eq, Eq DepthBiasRepresentationEXT
DepthBiasRepresentationEXT -> DepthBiasRepresentationEXT -> Bool
DepthBiasRepresentationEXT
-> DepthBiasRepresentationEXT -> Ordering
DepthBiasRepresentationEXT
-> DepthBiasRepresentationEXT -> DepthBiasRepresentationEXT
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 :: DepthBiasRepresentationEXT
-> DepthBiasRepresentationEXT -> DepthBiasRepresentationEXT
$cmin :: DepthBiasRepresentationEXT
-> DepthBiasRepresentationEXT -> DepthBiasRepresentationEXT
max :: DepthBiasRepresentationEXT
-> DepthBiasRepresentationEXT -> DepthBiasRepresentationEXT
$cmax :: DepthBiasRepresentationEXT
-> DepthBiasRepresentationEXT -> DepthBiasRepresentationEXT
>= :: DepthBiasRepresentationEXT -> DepthBiasRepresentationEXT -> Bool
$c>= :: DepthBiasRepresentationEXT -> DepthBiasRepresentationEXT -> Bool
> :: DepthBiasRepresentationEXT -> DepthBiasRepresentationEXT -> Bool
$c> :: DepthBiasRepresentationEXT -> DepthBiasRepresentationEXT -> Bool
<= :: DepthBiasRepresentationEXT -> DepthBiasRepresentationEXT -> Bool
$c<= :: DepthBiasRepresentationEXT -> DepthBiasRepresentationEXT -> Bool
< :: DepthBiasRepresentationEXT -> DepthBiasRepresentationEXT -> Bool
$c< :: DepthBiasRepresentationEXT -> DepthBiasRepresentationEXT -> Bool
compare :: DepthBiasRepresentationEXT
-> DepthBiasRepresentationEXT -> Ordering
$ccompare :: DepthBiasRepresentationEXT
-> DepthBiasRepresentationEXT -> Ordering
Ord, Ptr DepthBiasRepresentationEXT -> IO DepthBiasRepresentationEXT
Ptr DepthBiasRepresentationEXT
-> Int -> IO DepthBiasRepresentationEXT
Ptr DepthBiasRepresentationEXT
-> Int -> DepthBiasRepresentationEXT -> IO ()
Ptr DepthBiasRepresentationEXT
-> DepthBiasRepresentationEXT -> IO ()
DepthBiasRepresentationEXT -> Int
forall b. Ptr b -> Int -> IO DepthBiasRepresentationEXT
forall b. Ptr b -> Int -> DepthBiasRepresentationEXT -> 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 DepthBiasRepresentationEXT
-> DepthBiasRepresentationEXT -> IO ()
$cpoke :: Ptr DepthBiasRepresentationEXT
-> DepthBiasRepresentationEXT -> IO ()
peek :: Ptr DepthBiasRepresentationEXT -> IO DepthBiasRepresentationEXT
$cpeek :: Ptr DepthBiasRepresentationEXT -> IO DepthBiasRepresentationEXT
pokeByteOff :: forall b. Ptr b -> Int -> DepthBiasRepresentationEXT -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> DepthBiasRepresentationEXT -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO DepthBiasRepresentationEXT
$cpeekByteOff :: forall b. Ptr b -> Int -> IO DepthBiasRepresentationEXT
pokeElemOff :: Ptr DepthBiasRepresentationEXT
-> Int -> DepthBiasRepresentationEXT -> IO ()
$cpokeElemOff :: Ptr DepthBiasRepresentationEXT
-> Int -> DepthBiasRepresentationEXT -> IO ()
peekElemOff :: Ptr DepthBiasRepresentationEXT
-> Int -> IO DepthBiasRepresentationEXT
$cpeekElemOff :: Ptr DepthBiasRepresentationEXT
-> Int -> IO DepthBiasRepresentationEXT
alignment :: DepthBiasRepresentationEXT -> Int
$calignment :: DepthBiasRepresentationEXT -> Int
sizeOf :: DepthBiasRepresentationEXT -> Int
$csizeOf :: DepthBiasRepresentationEXT -> Int
Storable, DepthBiasRepresentationEXT
forall a. a -> Zero a
zero :: DepthBiasRepresentationEXT
$czero :: DepthBiasRepresentationEXT
Zero)
pattern $bDEPTH_BIAS_REPRESENTATION_LEAST_REPRESENTABLE_VALUE_FORMAT_EXT :: DepthBiasRepresentationEXT
$mDEPTH_BIAS_REPRESENTATION_LEAST_REPRESENTABLE_VALUE_FORMAT_EXT :: forall {r}.
DepthBiasRepresentationEXT -> ((# #) -> r) -> ((# #) -> r) -> r
DEPTH_BIAS_REPRESENTATION_LEAST_REPRESENTABLE_VALUE_FORMAT_EXT = DepthBiasRepresentationEXT 0
pattern $bDEPTH_BIAS_REPRESENTATION_LEAST_REPRESENTABLE_VALUE_FORCE_UNORM_EXT :: DepthBiasRepresentationEXT
$mDEPTH_BIAS_REPRESENTATION_LEAST_REPRESENTABLE_VALUE_FORCE_UNORM_EXT :: forall {r}.
DepthBiasRepresentationEXT -> ((# #) -> r) -> ((# #) -> r) -> r
DEPTH_BIAS_REPRESENTATION_LEAST_REPRESENTABLE_VALUE_FORCE_UNORM_EXT = DepthBiasRepresentationEXT 1
pattern $bDEPTH_BIAS_REPRESENTATION_FLOAT_EXT :: DepthBiasRepresentationEXT
$mDEPTH_BIAS_REPRESENTATION_FLOAT_EXT :: forall {r}.
DepthBiasRepresentationEXT -> ((# #) -> r) -> ((# #) -> r) -> r
DEPTH_BIAS_REPRESENTATION_FLOAT_EXT = DepthBiasRepresentationEXT 2
{-# COMPLETE
DEPTH_BIAS_REPRESENTATION_LEAST_REPRESENTABLE_VALUE_FORMAT_EXT
, DEPTH_BIAS_REPRESENTATION_LEAST_REPRESENTABLE_VALUE_FORCE_UNORM_EXT
, DEPTH_BIAS_REPRESENTATION_FLOAT_EXT ::
DepthBiasRepresentationEXT
#-}
conNameDepthBiasRepresentationEXT :: String
conNameDepthBiasRepresentationEXT :: String
conNameDepthBiasRepresentationEXT = String
"DepthBiasRepresentationEXT"
enumPrefixDepthBiasRepresentationEXT :: String
enumPrefixDepthBiasRepresentationEXT :: String
enumPrefixDepthBiasRepresentationEXT = String
"DEPTH_BIAS_REPRESENTATION_"
showTableDepthBiasRepresentationEXT :: [(DepthBiasRepresentationEXT, String)]
showTableDepthBiasRepresentationEXT :: [(DepthBiasRepresentationEXT, String)]
showTableDepthBiasRepresentationEXT =
[
( DepthBiasRepresentationEXT
DEPTH_BIAS_REPRESENTATION_LEAST_REPRESENTABLE_VALUE_FORMAT_EXT
, String
"LEAST_REPRESENTABLE_VALUE_FORMAT_EXT"
)
,
( DepthBiasRepresentationEXT
DEPTH_BIAS_REPRESENTATION_LEAST_REPRESENTABLE_VALUE_FORCE_UNORM_EXT
, String
"LEAST_REPRESENTABLE_VALUE_FORCE_UNORM_EXT"
)
,
( DepthBiasRepresentationEXT
DEPTH_BIAS_REPRESENTATION_FLOAT_EXT
, String
"FLOAT_EXT"
)
]
instance Show DepthBiasRepresentationEXT where
showsPrec :: Int -> DepthBiasRepresentationEXT -> ShowS
showsPrec =
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
String
enumPrefixDepthBiasRepresentationEXT
[(DepthBiasRepresentationEXT, String)]
showTableDepthBiasRepresentationEXT
String
conNameDepthBiasRepresentationEXT
(\(DepthBiasRepresentationEXT Int32
x) -> Int32
x)
(forall a. Show a => Int -> a -> ShowS
showsPrec Int
11)
instance Read DepthBiasRepresentationEXT where
readPrec :: ReadPrec DepthBiasRepresentationEXT
readPrec =
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
String
enumPrefixDepthBiasRepresentationEXT
[(DepthBiasRepresentationEXT, String)]
showTableDepthBiasRepresentationEXT
String
conNameDepthBiasRepresentationEXT
Int32 -> DepthBiasRepresentationEXT
DepthBiasRepresentationEXT
type EXT_DEPTH_BIAS_CONTROL_SPEC_VERSION = 1
pattern EXT_DEPTH_BIAS_CONTROL_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_DEPTH_BIAS_CONTROL_SPEC_VERSION :: forall a. Integral a => a
$mEXT_DEPTH_BIAS_CONTROL_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_DEPTH_BIAS_CONTROL_SPEC_VERSION = 1
type EXT_DEPTH_BIAS_CONTROL_EXTENSION_NAME = "VK_EXT_depth_bias_control"
pattern EXT_DEPTH_BIAS_CONTROL_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_DEPTH_BIAS_CONTROL_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mEXT_DEPTH_BIAS_CONTROL_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_DEPTH_BIAS_CONTROL_EXTENSION_NAME = "VK_EXT_depth_bias_control"