{-# LINE 1 "lib/Data/SpirV/Reflect/FFI/Internal.chs" #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE Strict #-}
module Data.SpirV.Reflect.FFI.Internal where
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.Ptr as C2HSImp
import qualified Foreign.Storable as C2HSImp
import Data.Coerce (Coercible, coerce)
import Data.Ord (comparing)
import Data.SpirV.Enum qualified as SpirV
import Data.SpirV.Enum.StorageClass qualified as StorageClass
import Data.Text (Text)
import Data.Text qualified as Text
import Data.Vector (Vector)
import Data.Vector qualified as Vector
import Data.Vector.Algorithms.Heap qualified as Heap
import Data.Word (Word32)
import Foreign.C.String (CString)
import Foreign.C.Types (CULong)
import Foreign.Marshal.Utils (maybePeek)
import Foreign.Ptr (Ptr, castPtr, plusPtr, nullPtr)
import Foreign.Storable (peek)
import GHC.Ptr qualified as GHC
import Data.SpirV.Reflect.BlockVariable (BlockVariable)
import Data.SpirV.Reflect.BlockVariable qualified as BlockVariable
import Data.SpirV.Reflect.DescriptorBinding (DescriptorBinding)
import Data.SpirV.Reflect.DescriptorBinding qualified as DescriptorBinding
import Data.SpirV.Reflect.DescriptorSet (DescriptorSet)
import Data.SpirV.Reflect.DescriptorSet qualified as DescriptorSet
import Data.SpirV.Reflect.Enums qualified as Reflect
import Data.SpirV.Reflect.InterfaceVariable (InterfaceVariable)
import Data.SpirV.Reflect.InterfaceVariable qualified as InterfaceVariable
import Data.SpirV.Reflect.Module (Module)
import Data.SpirV.Reflect.Module qualified as Module
import Data.SpirV.Reflect.Traits qualified as Traits
import Data.SpirV.Reflect.TypeDescription (TypeDescription)
import Data.SpirV.Reflect.TypeDescription qualified as TypeDescription
import Data.SpirV.Reflect.SpecializationConstant (SpecializationConstant)
import Data.SpirV.Reflect.SpecializationConstant qualified as SpecializationConstant
type ShaderModulePtr = C2HSImp.Ptr (())
{-# LINE 46 "lib/Data/SpirV/Reflect/FFI/Internal.chs" #-}
data Result = SpvReflectResultSuccess
| SpvReflectResultNotReady
| SpvReflectResultErrorParseFailed
| SpvReflectResultErrorAllocFailed
| SpvReflectResultErrorRangeExceeded
| SpvReflectResultErrorNullPointer
| SpvReflectResultErrorInternalError
| SpvReflectResultErrorCountMismatch
| SpvReflectResultErrorElementNotFound
| SpvReflectResultErrorSpirvInvalidCodeSize
| SpvReflectResultErrorSpirvInvalidMagicNumber
| SpvReflectResultErrorSpirvUnexpectedEof
| SpvReflectResultErrorSpirvInvalidIdReference
| SpvReflectResultErrorSpirvSetNumberOverflow
| SpvReflectResultErrorSpirvInvalidStorageClass
| SpvReflectResultErrorSpirvRecursion
| SpvReflectResultErrorSpirvInvalidInstruction
| SpvReflectResultErrorSpirvUnexpectedBlockData
| SpvReflectResultErrorSpirvInvalidBlockMemberReference
| SpvReflectResultErrorSpirvInvalidEntryPoint
| SpvReflectResultErrorSpirvInvalidExecutionMode
| SpvReflectResultErrorSpirvMaxRecursiveExceeded
deriving (Enum,Eq,Ord,Show)
{-# LINE 52 "lib/Data/SpirV/Reflect/FFI/Internal.chs" #-}
createShaderModule :: (CULong) -> (Ptr ()) -> (ShaderModulePtr) -> IO ((Result))
createShaderModule a1 a2 a3 =
let {a1' = id a1} in
let {a2' = id a2} in
let {a3' = id a3} in
createShaderModule'_ a1' a2' a3' >>= \res ->
let {res' = (toEnum . fromIntegral) res} in
return (res')
{-# LINE 60 "lib/Data/SpirV/Reflect/FFI/Internal.chs" #-}
data ModuleFlags = SpvReflectModuleFlagNone
| SpvReflectModuleFlagNoCopy
deriving (Eq,Ord,Show)
instance Enum ModuleFlags where
succ SpvReflectModuleFlagNone = SpvReflectModuleFlagNoCopy
succ SpvReflectModuleFlagNoCopy = error "ModuleFlags.succ: SpvReflectModuleFlagNoCopy has no successor"
pred SpvReflectModuleFlagNoCopy = SpvReflectModuleFlagNone
pred SpvReflectModuleFlagNone = error "ModuleFlags.pred: SpvReflectModuleFlagNone has no predecessor"
enumFromTo from to = go from
where
end = fromEnum to
go v = case compare (fromEnum v) end of
LT -> v : go (succ v)
EQ -> [v]
GT -> []
enumFrom from = enumFromTo from SpvReflectModuleFlagNoCopy
fromEnum :: ModuleFlags -> Int
fromEnum ModuleFlags
SpvReflectModuleFlagNone = Int
0
fromEnum ModuleFlags
SpvReflectModuleFlagNoCopy = Int
1
toEnum :: Int -> ModuleFlags
toEnum Int
0 = ModuleFlags
SpvReflectModuleFlagNone
toEnum Int
1 = ModuleFlags
SpvReflectModuleFlagNoCopy
toEnum Int
unmatched = String -> ModuleFlags
forall a. HasCallStack => String -> a
error (String
"ModuleFlags.toEnum: Cannot match " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
unmatched)
{-# LINE 66 "lib/Data/SpirV/Reflect/FFI/Internal.chs" #-}
createShaderModule2 :: (ModuleFlags) -> (CULong) -> (Ptr ()) -> (ShaderModulePtr) -> IO ((Result))
createShaderModule2 a1 a2 a3 a4 =
let {a1' = (fromIntegral . fromEnum) a1} in
let {a2' = id a2} in
let {a3' = id a3} in
let {a4' = id a4} in
createShaderModule2'_ a1' a2' a3' a4' >>= \res ->
let {res' = (toEnum . fromIntegral) res} in
return (res')
{-# LINE 75 "lib/Data/SpirV/Reflect/FFI/Internal.chs" #-}
destroyShaderModule :: (ShaderModulePtr) -> IO ()
destroyShaderModule a1 =
let {a1' = id a1} in
destroyShaderModule'_ a1' >>
return ()
{-# LINE 81 "lib/Data/SpirV/Reflect/FFI/Internal.chs" #-}
shaderModuleSize :: Int
shaderModuleSize = 1216
{-# LINE 88 "lib/Data/SpirV/Reflect/FFI/Internal.chs" #-}
inflateModule :: ShaderModulePtr -> IO Module
inflateModule :: TypeDescriptionPtr -> IO Module
inflateModule TypeDescriptionPtr
smp = do
let sm :: Ptr b
sm = TypeDescriptionPtr -> Ptr b
forall a b. Ptr a -> Ptr b
castPtr TypeDescriptionPtr
smp
Generator
generator <- IO CInt -> IO Generator
forall a b. (Integral a, Enum b) => IO a -> IO b
inflateEnum (IO CInt -> IO Generator) -> IO CInt -> IO Generator
forall a b. (a -> b) -> a -> b
$
(\Ptr Any
ptr -> do {Ptr Any -> Int -> IO CInt
forall b. Ptr b -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr Any
ptr Int
0 :: IO C2HSImp.CInt}) Ptr Any
forall {b}. Ptr b
sm
Text
entry_point_name <- IO (Ptr CChar) -> IO Text
inflateText (IO (Ptr CChar) -> IO Text) -> IO (Ptr CChar) -> IO Text
forall a b. (a -> b) -> a -> b
$
(\Ptr Any
ptr -> do {Ptr Any -> Int -> IO (Ptr CChar)
forall b. Ptr b -> Int -> IO (Ptr CChar)
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr Any
ptr Int
8 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) Ptr Any
forall {b}. Ptr b
sm
Int
entry_point_id <- IO CUInt -> IO Int
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CUInt -> IO Int) -> IO CUInt -> IO Int
forall a b. (a -> b) -> a -> b
$
(\Ptr Any
ptr -> do {Ptr Any -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr Any
ptr Int
16 :: IO C2HSImp.CUInt}) Ptr Any
forall {b}. Ptr b
sm
Int
source_language <- IO CInt -> IO Int
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CInt -> IO Int) -> IO CInt -> IO Int
forall a b. (a -> b) -> a -> b
$
(\Ptr Any
ptr -> do {Ptr Any -> Int -> IO CInt
forall b. Ptr b -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr Any
ptr Int
32 :: IO C2HSImp.CInt}) Ptr Any
forall {b}. Ptr b
sm
Int
source_language_version <- IO CUInt -> IO Int
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CUInt -> IO Int) -> IO CUInt -> IO Int
forall a b. (a -> b) -> a -> b
$
(\Ptr Any
ptr -> do {Ptr Any -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr Any
ptr Int
36 :: IO C2HSImp.CUInt}) Ptr Any
forall {b}. Ptr b
sm
Int
spirv_execution_model <- IO CInt -> IO Int
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CInt -> IO Int) -> IO CInt -> IO Int
forall a b. (a -> b) -> a -> b
$
(\Ptr Any
ptr -> do {Ptr Any -> Int -> IO CInt
forall b. Ptr b -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr Any
ptr Int
72 :: IO C2HSImp.CInt}) Ptr Any
forall {b}. Ptr b
sm
Int
shader_stage <- IO CInt -> IO Int
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CInt -> IO Int) -> IO CInt -> IO Int
forall a b. (a -> b) -> a -> b
$
(\Ptr Any
ptr -> do {Ptr Any -> Int -> IO CInt
forall b. Ptr b -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr Any
ptr Int
76 :: IO C2HSImp.CInt}) Ptr Any
forall {b}. Ptr b
sm
Vector DescriptorBinding
descriptor_bindings <-
IO CUInt
-> IO TypeDescriptionPtr
-> Int
-> (TypeDescriptionPtr -> IO DescriptorBinding)
-> IO (Vector DescriptorBinding)
forall i p a.
Integral i =>
IO i -> IO (Ptr p) -> Int -> (Ptr p -> IO a) -> IO (Vector a)
inflateVector
((\Ptr Any
ptr -> do {Ptr Any -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr Any
ptr Int
80 :: IO C2HSImp.CUInt}) Ptr Any
forall {b}. Ptr b
sm)
((\Ptr Any
ptr -> do {Ptr Any -> Int -> IO TypeDescriptionPtr
forall b. Ptr b -> Int -> IO TypeDescriptionPtr
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr Any
ptr Int
88 :: IO (C2HSImp.Ptr ())}) Ptr Any
forall {b}. Ptr b
sm)
Int
616
{-# LINE 124 "lib/Data/SpirV/Reflect/FFI/Internal.chs" #-}
inflateDescriptorBinding
Vector DescriptorSet
descriptor_sets <-
IO CUInt
-> IO TypeDescriptionPtr
-> Int
-> (TypeDescriptionPtr -> IO DescriptorSet)
-> IO (Vector DescriptorSet)
forall i p a.
Integral i =>
IO i -> IO (Ptr p) -> Int -> (Ptr p -> IO a) -> IO (Vector a)
inflateVector
((\Ptr Any
ptr -> do {Ptr Any -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr Any
ptr Int
96 :: IO C2HSImp.CUInt}) Ptr Any
forall {b}. Ptr b
sm)
((\Ptr Any
ptr -> do {TypeDescriptionPtr -> IO TypeDescriptionPtr
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (TypeDescriptionPtr -> IO TypeDescriptionPtr)
-> TypeDescriptionPtr -> IO TypeDescriptionPtr
forall a b. (a -> b) -> a -> b
$ Ptr Any
ptr Ptr Any -> Int -> TypeDescriptionPtr
forall a b. Ptr a -> Int -> Ptr b
`C2HSImp.plusPtr` Int
104 :: IO (C2HSImp.Ptr ())}) Ptr Any
forall {b}. Ptr b
sm)
Int
16
{-# LINE 131 "lib/Data/SpirV/Reflect/FFI/Internal.chs" #-}
inflateDescriptorSet
Vector InterfaceVariable
interface_variables <-
IO CUInt
-> IO TypeDescriptionPtr
-> Int
-> (TypeDescriptionPtr -> IO InterfaceVariable)
-> IO (Vector InterfaceVariable)
forall i p a.
Integral i =>
IO i -> IO (Ptr p) -> Int -> (Ptr p -> IO a) -> IO (Vector a)
inflateVector
((\Ptr Any
ptr -> do {Ptr Any -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr Any
ptr Int
1160 :: IO C2HSImp.CUInt}) Ptr Any
forall {b}. Ptr b
sm)
((\Ptr Any
ptr -> do {Ptr Any -> Int -> IO TypeDescriptionPtr
forall b. Ptr b -> Int -> IO TypeDescriptionPtr
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr Any
ptr Int
1168 :: IO (C2HSImp.Ptr ())}) Ptr Any
forall {b}. Ptr b
sm)
Int
376
{-# LINE 138 "lib/Data/SpirV/Reflect/FFI/Internal.chs" #-}
inflateInterfaceVariable
let
ivLocation :: InterfaceVariable -> Word32
ivLocation InterfaceVariable.InterfaceVariable{Word32
location :: Word32
$sel:location:InterfaceVariable :: InterfaceVariable -> Word32
location} =
Word32
location
pickIvs :: (InterfaceVariable -> Bool) -> Vector InterfaceVariable
pickIvs InterfaceVariable -> Bool
query =
(forall s. MVector s InterfaceVariable -> ST s ())
-> Vector InterfaceVariable -> Vector InterfaceVariable
forall a.
(forall s. MVector s a -> ST s ()) -> Vector a -> Vector a
Vector.modify (Comparison InterfaceVariable
-> MVector (PrimState (ST s)) InterfaceVariable -> ST s ()
forall (m :: * -> *) (v :: * -> * -> *) e.
(PrimMonad m, MVector v e) =>
Comparison e -> v (PrimState m) e -> m ()
Heap.sortBy (Comparison InterfaceVariable
-> MVector (PrimState (ST s)) InterfaceVariable -> ST s ())
-> Comparison InterfaceVariable
-> MVector (PrimState (ST s)) InterfaceVariable
-> ST s ()
forall a b. (a -> b) -> a -> b
$ (InterfaceVariable -> Word32) -> Comparison InterfaceVariable
forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing InterfaceVariable -> Word32
ivLocation) (Vector InterfaceVariable -> Vector InterfaceVariable)
-> Vector InterfaceVariable -> Vector InterfaceVariable
forall a b. (a -> b) -> a -> b
$ (InterfaceVariable -> Bool)
-> Vector InterfaceVariable -> Vector InterfaceVariable
forall a. (a -> Bool) -> Vector a -> Vector a
Vector.filter InterfaceVariable -> Bool
query Vector InterfaceVariable
interface_variables
input_variables :: Vector InterfaceVariable
input_variables =
(InterfaceVariable -> Bool) -> Vector InterfaceVariable
pickIvs ((InterfaceVariable -> Bool) -> Vector InterfaceVariable)
-> (InterfaceVariable -> Bool) -> Vector InterfaceVariable
forall a b. (a -> b) -> a -> b
$
(StorageClass -> StorageClass -> Bool
forall a. Eq a => a -> a -> Bool
== StorageClass
StorageClass.Input) (StorageClass -> Bool)
-> (InterfaceVariable -> StorageClass) -> InterfaceVariable -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InterfaceVariable -> StorageClass
InterfaceVariable.storage_class
output_variables :: Vector InterfaceVariable
output_variables =
(InterfaceVariable -> Bool) -> Vector InterfaceVariable
pickIvs ((InterfaceVariable -> Bool) -> Vector InterfaceVariable)
-> (InterfaceVariable -> Bool) -> Vector InterfaceVariable
forall a b. (a -> b) -> a -> b
$
(StorageClass -> StorageClass -> Bool
forall a. Eq a => a -> a -> Bool
== StorageClass
StorageClass.Output) (StorageClass -> Bool)
-> (InterfaceVariable -> StorageClass) -> InterfaceVariable -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InterfaceVariable -> StorageClass
InterfaceVariable.storage_class
Vector BlockVariable
push_constants <-
IO CUInt
-> IO TypeDescriptionPtr
-> Int
-> (TypeDescriptionPtr -> IO BlockVariable)
-> IO (Vector BlockVariable)
forall i p a.
Integral i =>
IO i -> IO (Ptr p) -> Int -> (Ptr p -> IO a) -> IO (Vector a)
inflateVector
((\Ptr Any
ptr -> do {Ptr Any -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr Any
ptr Int
1176 :: IO C2HSImp.CUInt}) Ptr Any
forall {b}. Ptr b
sm)
((\Ptr Any
ptr -> do {Ptr Any -> Int -> IO TypeDescriptionPtr
forall b. Ptr b -> Int -> IO TypeDescriptionPtr
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr Any
ptr Int
1184 :: IO (C2HSImp.Ptr ())}) Ptr Any
forall {b}. Ptr b
sm)
Int
360
{-# LINE 160 "lib/Data/SpirV/Reflect/FFI/Internal.chs" #-}
inflateBlockVariable
Vector SpecializationConstant
spec_constants <-
IO CUInt
-> IO TypeDescriptionPtr
-> Int
-> (TypeDescriptionPtr -> IO SpecializationConstant)
-> IO (Vector SpecializationConstant)
forall i p a.
Integral i =>
IO i -> IO (Ptr p) -> Int -> (Ptr p -> IO a) -> IO (Vector a)
inflateVector
((\Ptr Any
ptr -> do {Ptr Any -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr Any
ptr Int
1192 :: IO C2HSImp.CUInt}) Ptr Any
forall {b}. Ptr b
sm)
((\Ptr Any
ptr -> do {Ptr Any -> Int -> IO TypeDescriptionPtr
forall b. Ptr b -> Int -> IO TypeDescriptionPtr
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr Any
ptr Int
1200 :: IO (C2HSImp.Ptr ())}) Ptr Any
forall {b}. Ptr b
sm)
Int
16
{-# LINE 167 "lib/Data/SpirV/Reflect/FFI/Internal.chs" #-}
inflateSpecConstant
pure Module.Module{Int
Generator
Text
Vector SpecializationConstant
Vector InterfaceVariable
Vector BlockVariable
Vector DescriptorBinding
Vector DescriptorSet
generator :: Generator
entry_point_name :: Text
entry_point_id :: Int
source_language :: Int
source_language_version :: Int
spirv_execution_model :: Int
shader_stage :: Int
descriptor_bindings :: Vector DescriptorBinding
descriptor_sets :: Vector DescriptorSet
input_variables :: Vector InterfaceVariable
output_variables :: Vector InterfaceVariable
push_constants :: Vector BlockVariable
spec_constants :: Vector SpecializationConstant
$sel:generator:Module :: Generator
$sel:entry_point_name:Module :: Text
$sel:entry_point_id:Module :: Int
$sel:source_language:Module :: Int
$sel:source_language_version:Module :: Int
$sel:spirv_execution_model:Module :: Int
$sel:shader_stage:Module :: Int
$sel:descriptor_bindings:Module :: Vector DescriptorBinding
$sel:descriptor_sets:Module :: Vector DescriptorSet
$sel:input_variables:Module :: Vector InterfaceVariable
$sel:output_variables:Module :: Vector InterfaceVariable
$sel:push_constants:Module :: Vector BlockVariable
$sel:spec_constants:Module :: Vector SpecializationConstant
..}
type DescriptorBindingPtr = C2HSImp.Ptr (())
{-# LINE 172 "lib/Data/SpirV/Reflect/FFI/Internal.chs" #-}
inflateDescriptorBinding :: DescriptorBindingPtr -> IO DescriptorBinding
inflateDescriptorBinding :: TypeDescriptionPtr -> IO DescriptorBinding
inflateDescriptorBinding TypeDescriptionPtr
db = do
Maybe Word32
spirv_id <- (Word32 -> Maybe Word32) -> IO Word32 -> IO (Maybe Word32)
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Word32 -> Maybe Word32
forall a. a -> Maybe a
just (IO Word32 -> IO (Maybe Word32))
-> (IO CUInt -> IO Word32) -> IO CUInt -> IO (Maybe Word32)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO CUInt -> IO Word32
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CUInt -> IO (Maybe Word32)) -> IO CUInt -> IO (Maybe Word32)
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
0 :: IO C2HSImp.CUInt}) TypeDescriptionPtr
db
Text
name <- IO (Ptr CChar) -> IO Text
inflateText (IO (Ptr CChar) -> IO Text) -> IO (Ptr CChar) -> IO Text
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO (Ptr CChar)
forall b. Ptr b -> Int -> IO (Ptr CChar)
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
8 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) TypeDescriptionPtr
db
Word32
binding <- IO CUInt -> IO Word32
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CUInt -> IO Word32) -> IO CUInt -> IO Word32
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
16 :: IO C2HSImp.CUInt}) TypeDescriptionPtr
db
Word32
input_attachment_index <- IO CUInt -> IO Word32
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CUInt -> IO Word32) -> IO CUInt -> IO Word32
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
20 :: IO C2HSImp.CUInt}) TypeDescriptionPtr
db
Word32
set <- IO CUInt -> IO Word32
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CUInt -> IO Word32) -> IO CUInt -> IO Word32
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
24 :: IO C2HSImp.CUInt}) TypeDescriptionPtr
db
DescriptorType
descriptor_type <- IO CInt -> IO DescriptorType
forall a b. (Integral a, Enum b) => IO a -> IO b
inflateEnum (IO CInt -> IO DescriptorType) -> IO CInt -> IO DescriptorType
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO CInt
forall b. Ptr b -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
28 :: IO C2HSImp.CInt}) TypeDescriptionPtr
db
ResourceFlags
resource_type <- IO CInt -> IO ResourceFlags
forall a b. (Integral a, Coercible Word32 b) => IO a -> IO b
inflateFlags32 (IO CInt -> IO ResourceFlags) -> IO CInt -> IO ResourceFlags
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO CInt
forall b. Ptr b -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
32 :: IO C2HSImp.CInt}) TypeDescriptionPtr
db
Image
image <-
TypeDescriptionPtr -> Int -> IO Image
forall struct. Ptr struct -> Int -> IO Image
inflateImageTraits
TypeDescriptionPtr
db
(Int
36)
{-# LINE 200 "lib/Data/SpirV/Reflect/FFI/Internal.chs" #-}
Maybe BlockVariable
block <-
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO TypeDescriptionPtr
forall b. Ptr b -> Int -> IO TypeDescriptionPtr
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
64 :: IO (C2HSImp.Ptr ())}) TypeDescriptionPtr
db IO TypeDescriptionPtr
-> (TypeDescriptionPtr -> IO (Maybe BlockVariable))
-> IO (Maybe BlockVariable)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
(TypeDescriptionPtr -> IO BlockVariable)
-> TypeDescriptionPtr -> IO (Maybe BlockVariable)
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek TypeDescriptionPtr -> IO BlockVariable
inflateBlockVariable
Array
array <-
TypeDescriptionPtr -> Int -> IO Array
forall struct. Ptr struct -> Int -> IO Array
inflateArrayTraits
TypeDescriptionPtr
db
(Int
424)
{-# LINE 209 "lib/Data/SpirV/Reflect/FFI/Internal.chs" #-}
Maybe Word32
count <- (Word32 -> Maybe Word32) -> IO Word32 -> IO (Maybe Word32)
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Word32 -> Maybe Word32
forall a. a -> Maybe a
just (IO Word32 -> IO (Maybe Word32))
-> (IO CUInt -> IO Word32) -> IO CUInt -> IO (Maybe Word32)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO CUInt -> IO Word32
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CUInt -> IO (Maybe Word32)) -> IO CUInt -> IO (Maybe Word32)
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
556 :: IO C2HSImp.CUInt}) TypeDescriptionPtr
db
Word32
accessed <- IO CUInt -> IO Word32
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CUInt -> IO Word32) -> IO CUInt -> IO Word32
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
560 :: IO C2HSImp.CUInt}) TypeDescriptionPtr
db
Word32
uav_counter_id <- IO CUInt -> IO Word32
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CUInt -> IO Word32) -> IO CUInt -> IO Word32
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
564 :: IO C2HSImp.CUInt}) TypeDescriptionPtr
db
Maybe DescriptorBinding
uav_counter_binding <-
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO TypeDescriptionPtr
forall b. Ptr b -> Int -> IO TypeDescriptionPtr
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
568 :: IO (DescriptorBindingPtr)}) TypeDescriptionPtr
db IO TypeDescriptionPtr
-> (TypeDescriptionPtr -> IO (Maybe DescriptorBinding))
-> IO (Maybe DescriptorBinding)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
(TypeDescriptionPtr -> IO DescriptorBinding)
-> TypeDescriptionPtr -> IO (Maybe DescriptorBinding)
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek TypeDescriptionPtr -> IO DescriptorBinding
inflateDescriptorBinding
Maybe TypeDescription
type_description <-
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO TypeDescriptionPtr
forall b. Ptr b -> Int -> IO TypeDescriptionPtr
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
592 :: IO (C2HSImp.Ptr ())}) TypeDescriptionPtr
db IO TypeDescriptionPtr
-> (TypeDescriptionPtr -> IO (Maybe TypeDescription))
-> IO (Maybe TypeDescription)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
(TypeDescriptionPtr -> IO TypeDescription)
-> TypeDescriptionPtr -> IO (Maybe TypeDescription)
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek TypeDescriptionPtr -> IO TypeDescription
inflateTypeDescription
let word_offset :: WordOffset
word_offset = DescriptorBinding.WordOffset{Word32
binding :: Word32
set :: Word32
$sel:binding:WordOffset :: Word32
$sel:set:WordOffset :: Word32
..}
DecorationFlagBits
decoration_flags <- IO CUInt -> IO DecorationFlagBits
forall a b. (Integral a, Coercible Word32 b) => IO a -> IO b
inflateFlags32 (IO CUInt -> IO DecorationFlagBits)
-> IO CUInt -> IO DecorationFlagBits
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
608 :: IO C2HSImp.CUInt}) TypeDescriptionPtr
db
Vector Word32
byte_address_buffer_offsets <-
IO CUInt
-> IO (Ptr CUInt)
-> Int
-> (Ptr CUInt -> IO Word32)
-> IO (Vector Word32)
forall i p a.
Integral i =>
IO i -> IO (Ptr p) -> Int -> (Ptr p -> IO a) -> IO (Vector a)
inflateVector
((\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
576 :: IO C2HSImp.CUInt}) TypeDescriptionPtr
db)
((\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO (Ptr CUInt)
forall b. Ptr b -> Int -> IO (Ptr CUInt)
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
584 :: IO (C2HSImp.Ptr C2HSImp.CUInt)}) TypeDescriptionPtr
db)
Int
4
{-# LINE 237 "lib/Data/SpirV/Reflect/FFI/Internal.chs" #-}
(fmap fromIntegral . peek)
Maybe UserType
user_type <- UserType
-> (IO CInt -> IO UserType) -> IO CInt -> IO (Maybe UserType)
forall b a. Eq b => b -> (IO a -> IO b) -> IO a -> IO (Maybe b)
inflateMaybe (Int -> UserType
Reflect.UserType Int
0) IO CInt -> IO UserType
forall a b. (Integral a, Enum b) => IO a -> IO b
inflateEnum (IO CInt -> IO (Maybe UserType)) -> IO CInt -> IO (Maybe UserType)
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO CInt
forall b. Ptr b -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
612 :: IO C2HSImp.CInt}) TypeDescriptionPtr
db
pure DescriptorBinding.DescriptorBinding{Maybe Word32
Maybe UserType
Maybe TypeDescription
Maybe BlockVariable
Maybe DescriptorBinding
Word32
DecorationFlagBits
DescriptorType
ResourceFlags
Image
Array
WordOffset
Text
Vector Word32
spirv_id :: Maybe Word32
name :: Text
binding :: Word32
input_attachment_index :: Word32
set :: Word32
descriptor_type :: DescriptorType
resource_type :: ResourceFlags
image :: Image
block :: Maybe BlockVariable
array :: Array
count :: Maybe Word32
accessed :: Word32
uav_counter_id :: Word32
uav_counter_binding :: Maybe DescriptorBinding
type_description :: Maybe TypeDescription
word_offset :: WordOffset
decoration_flags :: DecorationFlagBits
byte_address_buffer_offsets :: Vector Word32
user_type :: Maybe UserType
$sel:spirv_id:DescriptorBinding :: Maybe Word32
$sel:name:DescriptorBinding :: Text
$sel:binding:DescriptorBinding :: Word32
$sel:input_attachment_index:DescriptorBinding :: Word32
$sel:set:DescriptorBinding :: Word32
$sel:descriptor_type:DescriptorBinding :: DescriptorType
$sel:resource_type:DescriptorBinding :: ResourceFlags
$sel:image:DescriptorBinding :: Image
$sel:block:DescriptorBinding :: Maybe BlockVariable
$sel:array:DescriptorBinding :: Array
$sel:count:DescriptorBinding :: Maybe Word32
$sel:accessed:DescriptorBinding :: Word32
$sel:uav_counter_id:DescriptorBinding :: Word32
$sel:uav_counter_binding:DescriptorBinding :: Maybe DescriptorBinding
$sel:byte_address_buffer_offsets:DescriptorBinding :: Vector Word32
$sel:type_description:DescriptorBinding :: Maybe TypeDescription
$sel:word_offset:DescriptorBinding :: WordOffset
$sel:decoration_flags:DescriptorBinding :: DecorationFlagBits
$sel:user_type:DescriptorBinding :: Maybe UserType
..}
inflateSpecConstant :: Ptr () -> IO SpecializationConstant
inflateSpecConstant :: TypeDescriptionPtr -> IO SpecializationConstant
inflateSpecConstant TypeDescriptionPtr
sc = do
Maybe Word32
spirv_id <- (Word32 -> Maybe Word32) -> IO Word32 -> IO (Maybe Word32)
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Word32 -> Maybe Word32
forall a. a -> Maybe a
just (IO Word32 -> IO (Maybe Word32))
-> (IO CUInt -> IO Word32) -> IO CUInt -> IO (Maybe Word32)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO CUInt -> IO Word32
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CUInt -> IO (Maybe Word32)) -> IO CUInt -> IO (Maybe Word32)
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
0 :: IO C2HSImp.CUInt}) TypeDescriptionPtr
sc
Word32
constant_id <- IO CUInt -> IO Word32
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CUInt -> IO Word32) -> IO CUInt -> IO Word32
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
4 :: IO C2HSImp.CUInt}) TypeDescriptionPtr
sc
Maybe Text
name <- Text
-> (IO (Ptr CChar) -> IO Text) -> IO (Ptr CChar) -> IO (Maybe Text)
forall b a. Eq b => b -> (IO a -> IO b) -> IO a -> IO (Maybe b)
inflateMaybe Text
"" IO (Ptr CChar) -> IO Text
inflateText (IO (Ptr CChar) -> IO (Maybe Text))
-> IO (Ptr CChar) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO (Ptr CChar)
forall b. Ptr b -> Int -> IO (Ptr CChar)
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
8 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) TypeDescriptionPtr
sc
pure SpecializationConstant.SpecializationConstant {Maybe Word32
Maybe Text
Word32
spirv_id :: Maybe Word32
constant_id :: Word32
name :: Maybe Text
$sel:spirv_id:SpecializationConstant :: Maybe Word32
$sel:constant_id:SpecializationConstant :: Word32
$sel:name:SpecializationConstant :: Maybe Text
..}
type BlockVariablePtr = C2HSImp.Ptr (())
{-# LINE 258 "lib/Data/SpirV/Reflect/FFI/Internal.chs" #-}
inflateBlockVariable :: BlockVariablePtr -> IO BlockVariable
inflateBlockVariable :: TypeDescriptionPtr -> IO BlockVariable
inflateBlockVariable TypeDescriptionPtr
bv = do
Maybe Word32
spirv_id <- (Word32 -> Maybe Word32) -> IO Word32 -> IO (Maybe Word32)
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Word32 -> Maybe Word32
forall a. a -> Maybe a
just (IO Word32 -> IO (Maybe Word32))
-> (IO CUInt -> IO Word32) -> IO CUInt -> IO (Maybe Word32)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO CUInt -> IO Word32
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CUInt -> IO (Maybe Word32)) -> IO CUInt -> IO (Maybe Word32)
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
0 :: IO C2HSImp.CUInt}) TypeDescriptionPtr
bv
Maybe Text
name <- Text
-> (IO (Ptr CChar) -> IO Text) -> IO (Ptr CChar) -> IO (Maybe Text)
forall b a. Eq b => b -> (IO a -> IO b) -> IO a -> IO (Maybe b)
inflateMaybe Text
"" IO (Ptr CChar) -> IO Text
inflateText (IO (Ptr CChar) -> IO (Maybe Text))
-> IO (Ptr CChar) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO (Ptr CChar)
forall b. Ptr b -> Int -> IO (Ptr CChar)
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
8 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) TypeDescriptionPtr
bv
Word32
offset <- IO CUInt -> IO Word32
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CUInt -> IO Word32) -> IO CUInt -> IO Word32
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
16 :: IO C2HSImp.CUInt}) TypeDescriptionPtr
bv
Word32
absolute_offset <- IO CUInt -> IO Word32
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CUInt -> IO Word32) -> IO CUInt -> IO Word32
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
20 :: IO C2HSImp.CUInt}) TypeDescriptionPtr
bv
Word32
size <- IO CUInt -> IO Word32
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CUInt -> IO Word32) -> IO CUInt -> IO Word32
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
24 :: IO C2HSImp.CUInt}) TypeDescriptionPtr
bv
Word32
padded_size <- IO CUInt -> IO Word32
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CUInt -> IO Word32) -> IO CUInt -> IO Word32
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
28 :: IO C2HSImp.CUInt}) TypeDescriptionPtr
bv
DecorationFlagBits
decorations <- IO CUInt -> IO DecorationFlagBits
forall a b. (Integral a, Coercible Word32 b) => IO a -> IO b
inflateFlags32 (IO CUInt -> IO DecorationFlagBits)
-> IO CUInt -> IO DecorationFlagBits
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
32 :: IO C2HSImp.CUInt}) TypeDescriptionPtr
bv
Numeric
numeric <-
TypeDescriptionPtr -> Int -> IO Numeric
forall struct. Ptr struct -> Int -> IO Numeric
inflateNumericTraits
TypeDescriptionPtr
bv
(Int
36)
{-# LINE 286 "lib/Data/SpirV/Reflect/FFI/Internal.chs" #-}
Array
array <-
TypeDescriptionPtr -> Int -> IO Array
forall struct. Ptr struct -> Int -> IO Array
inflateArrayTraits
TypeDescriptionPtr
bv
(Int
60)
{-# LINE 291 "lib/Data/SpirV/Reflect/FFI/Internal.chs" #-}
Vector BlockVariable
members <-
IO CUInt
-> IO TypeDescriptionPtr
-> Int
-> (TypeDescriptionPtr -> IO BlockVariable)
-> IO (Vector BlockVariable)
forall i p a.
Integral i =>
IO i -> IO (Ptr p) -> Int -> (Ptr p -> IO a) -> IO (Vector a)
inflateVector
((\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
328 :: IO C2HSImp.CUInt}) TypeDescriptionPtr
bv)
((\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO TypeDescriptionPtr
forall b. Ptr b -> Int -> IO TypeDescriptionPtr
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
336 :: IO (BlockVariablePtr)}) TypeDescriptionPtr
bv)
Int
360
{-# LINE 297 "lib/Data/SpirV/Reflect/FFI/Internal.chs" #-}
inflateBlockVariable
Maybe TypeDescription
type_description <-
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO TypeDescriptionPtr
forall b. Ptr b -> Int -> IO TypeDescriptionPtr
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
344 :: IO (C2HSImp.Ptr ())}) TypeDescriptionPtr
bv IO TypeDescriptionPtr
-> (TypeDescriptionPtr -> IO (Maybe TypeDescription))
-> IO (Maybe TypeDescription)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
(TypeDescriptionPtr -> IO TypeDescription)
-> TypeDescriptionPtr -> IO (Maybe TypeDescription)
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek TypeDescriptionPtr -> IO TypeDescription
inflateTypeDescription
Maybe WordOffset
word_offset <-
(Word32 -> Maybe WordOffset) -> IO Word32 -> IO (Maybe WordOffset)
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (WordOffset -> Maybe WordOffset
forall a. a -> Maybe a
Just (WordOffset -> Maybe WordOffset)
-> (Word32 -> WordOffset) -> Word32 -> Maybe WordOffset
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32 -> WordOffset
BlockVariable.WordOffset) (IO Word32 -> IO (Maybe WordOffset))
-> (IO CUInt -> IO Word32) -> IO CUInt -> IO (Maybe WordOffset)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO CUInt -> IO Word32
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CUInt -> IO (Maybe WordOffset))
-> IO CUInt -> IO (Maybe WordOffset)
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
352 :: IO C2HSImp.CUInt}) TypeDescriptionPtr
bv
pure BlockVariable.BlockVariable{Maybe Word32
Maybe TypeDescription
Maybe WordOffset
Maybe Text
Word32
DecorationFlagBits
Array
Numeric
Vector BlockVariable
spirv_id :: Maybe Word32
name :: Maybe Text
offset :: Word32
absolute_offset :: Word32
size :: Word32
padded_size :: Word32
decorations :: DecorationFlagBits
numeric :: Numeric
array :: Array
members :: Vector BlockVariable
type_description :: Maybe TypeDescription
word_offset :: Maybe WordOffset
$sel:spirv_id:BlockVariable :: Maybe Word32
$sel:name:BlockVariable :: Maybe Text
$sel:offset:BlockVariable :: Word32
$sel:absolute_offset:BlockVariable :: Word32
$sel:size:BlockVariable :: Word32
$sel:padded_size:BlockVariable :: Word32
$sel:decorations:BlockVariable :: DecorationFlagBits
$sel:numeric:BlockVariable :: Numeric
$sel:array:BlockVariable :: Array
$sel:members:BlockVariable :: Vector BlockVariable
$sel:type_description:BlockVariable :: Maybe TypeDescription
$sel:word_offset:BlockVariable :: Maybe WordOffset
..}
type TypeDescriptionPtr = C2HSImp.Ptr (())
{-# LINE 310 "lib/Data/SpirV/Reflect/FFI/Internal.chs" #-}
inflateTypeDescription :: TypeDescriptionPtr -> IO TypeDescription
inflateTypeDescription :: TypeDescriptionPtr -> IO TypeDescription
inflateTypeDescription TypeDescriptionPtr
td = do
Maybe Word32
id_ <- (Word32 -> Maybe Word32) -> IO Word32 -> IO (Maybe Word32)
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Word32 -> Maybe Word32
forall a. a -> Maybe a
just (IO Word32 -> IO (Maybe Word32))
-> (IO CUInt -> IO Word32) -> IO CUInt -> IO (Maybe Word32)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO CUInt -> IO Word32
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CUInt -> IO (Maybe Word32)) -> IO CUInt -> IO (Maybe Word32)
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
0 :: IO C2HSImp.CUInt}) TypeDescriptionPtr
td
Maybe Op
op <- (Int32 -> Maybe Op) -> IO Int32 -> IO (Maybe Op)
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Op -> Maybe Op
forall a. a -> Maybe a
just (Op -> Maybe Op) -> (Int32 -> Op) -> Int32 -> Maybe Op
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int32 -> Op
SpirV.Op) (IO Int32 -> IO (Maybe Op))
-> (IO CInt -> IO Int32) -> IO CInt -> IO (Maybe Op)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO CInt -> IO Int32
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CInt -> IO (Maybe Op)) -> IO CInt -> IO (Maybe Op)
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO CInt
forall b. Ptr b -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
4 :: IO C2HSImp.CInt}) TypeDescriptionPtr
td
Maybe Text
type_name <- Text
-> (IO (Ptr CChar) -> IO Text) -> IO (Ptr CChar) -> IO (Maybe Text)
forall b a. Eq b => b -> (IO a -> IO b) -> IO a -> IO (Maybe b)
inflateMaybe Text
"" IO (Ptr CChar) -> IO Text
inflateText (IO (Ptr CChar) -> IO (Maybe Text))
-> IO (Ptr CChar) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO (Ptr CChar)
forall b. Ptr b -> Int -> IO (Ptr CChar)
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
8 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) TypeDescriptionPtr
td
Maybe Text
struct_member_name <- Text
-> (IO (Ptr CChar) -> IO Text) -> IO (Ptr CChar) -> IO (Maybe Text)
forall b a. Eq b => b -> (IO a -> IO b) -> IO a -> IO (Maybe b)
inflateMaybe Text
"" IO (Ptr CChar) -> IO Text
inflateText (IO (Ptr CChar) -> IO (Maybe Text))
-> IO (Ptr CChar) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO (Ptr CChar)
forall b. Ptr b -> Int -> IO (Ptr CChar)
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
16 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) TypeDescriptionPtr
td
StorageClass
storage_class <- (Int32 -> StorageClass) -> IO Int32 -> IO StorageClass
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Int32 -> StorageClass
SpirV.StorageClass (IO Int32 -> IO StorageClass)
-> (IO CInt -> IO Int32) -> IO CInt -> IO StorageClass
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO CInt -> IO Int32
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CInt -> IO StorageClass) -> IO CInt -> IO StorageClass
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO CInt
forall b. Ptr b -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
24 :: IO C2HSImp.CInt}) TypeDescriptionPtr
td
TypeFlagBits
type_flags <- IO CUInt -> IO TypeFlagBits
forall a b. (Integral a, Coercible Word32 b) => IO a -> IO b
inflateFlags32 (IO CUInt -> IO TypeFlagBits) -> IO CUInt -> IO TypeFlagBits
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
28 :: IO C2HSImp.CUInt}) TypeDescriptionPtr
td
Numeric
numeric <-
TypeDescriptionPtr -> Int -> IO Numeric
forall struct. Ptr struct -> Int -> IO Numeric
inflateNumericTraits
TypeDescriptionPtr
td
(Int
36)
{-# LINE 335 "lib/Data/SpirV/Reflect/FFI/Internal.chs" #-}
Image
image <-
TypeDescriptionPtr -> Int -> IO Image
forall struct. Ptr struct -> Int -> IO Image
inflateImageTraits
TypeDescriptionPtr
td
(Int
60)
{-# LINE 340 "lib/Data/SpirV/Reflect/FFI/Internal.chs" #-}
Array
array <-
TypeDescriptionPtr -> Int -> IO Array
forall struct. Ptr struct -> Int -> IO Array
inflateArrayTraits
TypeDescriptionPtr
td
(Int
84)
{-# LINE 345 "lib/Data/SpirV/Reflect/FFI/Internal.chs" #-}
let
traits' :: Maybe Traits
traits' = Traits -> Maybe Traits
forall a. a -> Maybe a
Just TypeDescription.Traits{Image
Array
Numeric
numeric :: Numeric
image :: Image
array :: Array
$sel:numeric:Traits :: Numeric
$sel:image:Traits :: Image
$sel:array:Traits :: Array
..}
traits :: Maybe Traits
traits = if Maybe Traits
traits' Maybe Traits -> Maybe Traits -> Bool
forall a. Eq a => a -> a -> Bool
== Traits -> Maybe Traits
forall a. a -> Maybe a
Just Traits
TypeDescription.emptyTraits then Maybe Traits
forall a. Maybe a
Nothing else Maybe Traits
traits'
Maybe TypeDescription
struct_type_description <-
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO TypeDescriptionPtr
forall b. Ptr b -> Int -> IO TypeDescriptionPtr
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
352 :: IO (TypeDescriptionPtr)}) TypeDescriptionPtr
td IO TypeDescriptionPtr
-> (TypeDescriptionPtr -> IO (Maybe TypeDescription))
-> IO (Maybe TypeDescription)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
(TypeDescriptionPtr -> IO TypeDescription)
-> TypeDescriptionPtr -> IO (Maybe TypeDescription)
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek TypeDescriptionPtr -> IO TypeDescription
inflateTypeDescription
Maybe Word32
copied <-
(Word32 -> Maybe Word32) -> IO Word32 -> IO (Maybe Word32)
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Word32
n -> if Word32
n Word32 -> Word32 -> Bool
forall a. Ord a => a -> a -> Bool
> Word32
0 then Word32 -> Maybe Word32
forall a. a -> Maybe a
Just Word32
n else Maybe Word32
forall a. Maybe a
Nothing) (IO Word32 -> IO (Maybe Word32))
-> (IO CUInt -> IO Word32) -> IO CUInt -> IO (Maybe Word32)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO CUInt -> IO Word32
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CUInt -> IO (Maybe Word32)) -> IO CUInt -> IO (Maybe Word32)
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
360 :: IO C2HSImp.CUInt}) TypeDescriptionPtr
td
Vector TypeDescription
members <-
IO CUInt
-> IO TypeDescriptionPtr
-> Int
-> (TypeDescriptionPtr -> IO TypeDescription)
-> IO (Vector TypeDescription)
forall i p a.
Integral i =>
IO i -> IO (Ptr p) -> Int -> (Ptr p -> IO a) -> IO (Vector a)
inflateVector
((\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
364 :: IO C2HSImp.CUInt}) TypeDescriptionPtr
td)
((\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO TypeDescriptionPtr
forall b. Ptr b -> Int -> IO TypeDescriptionPtr
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
368 :: IO (TypeDescriptionPtr)}) TypeDescriptionPtr
td)
Int
376
{-# LINE 365 "lib/Data/SpirV/Reflect/FFI/Internal.chs" #-}
inflateTypeDescription
pure TypeDescription.TypeDescription{$sel:id:TypeDescription :: Maybe Word32
id=Maybe Word32
id_, Maybe Word32
Maybe Op
Maybe Traits
Maybe TypeDescription
Maybe Text
StorageClass
TypeFlagBits
Vector TypeDescription
op :: Maybe Op
type_name :: Maybe Text
struct_member_name :: Maybe Text
storage_class :: StorageClass
type_flags :: TypeFlagBits
traits :: Maybe Traits
struct_type_description :: Maybe TypeDescription
copied :: Maybe Word32
members :: Vector TypeDescription
$sel:op:TypeDescription :: Maybe Op
$sel:type_name:TypeDescription :: Maybe Text
$sel:struct_member_name:TypeDescription :: Maybe Text
$sel:storage_class:TypeDescription :: StorageClass
$sel:type_flags:TypeDescription :: TypeFlagBits
$sel:traits:TypeDescription :: Maybe Traits
$sel:struct_type_description:TypeDescription :: Maybe TypeDescription
$sel:copied:TypeDescription :: Maybe Word32
$sel:members:TypeDescription :: Vector TypeDescription
..}
type DescriptorSetPtr = C2HSImp.Ptr (())
{-# LINE 370 "lib/Data/SpirV/Reflect/FFI/Internal.chs" #-}
inflateDescriptorSet :: DescriptorSetPtr -> IO DescriptorSet
inflateDescriptorSet :: TypeDescriptionPtr -> IO DescriptorSet
inflateDescriptorSet TypeDescriptionPtr
ds = do
Word32
set <- IO CUInt -> IO Word32
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CUInt -> IO Word32) -> IO CUInt -> IO Word32
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
0 :: IO C2HSImp.CUInt}) TypeDescriptionPtr
ds
Ptr TypeDescriptionPtr
bindingsPtr <- (\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO (Ptr TypeDescriptionPtr)
forall b. Ptr b -> Int -> IO (Ptr TypeDescriptionPtr)
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
8 :: IO (C2HSImp.Ptr (DescriptorBindingPtr))}) TypeDescriptionPtr
ds
Vector DescriptorBinding
bindings <-
IO CUInt
-> IO TypeDescriptionPtr
-> Int
-> (TypeDescriptionPtr -> IO DescriptorBinding)
-> IO (Vector DescriptorBinding)
forall i p a.
Integral i =>
IO i -> IO (Ptr p) -> Int -> (Ptr p -> IO a) -> IO (Vector a)
inflateVector
((\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
4 :: IO C2HSImp.CUInt}) TypeDescriptionPtr
ds)
(Ptr TypeDescriptionPtr -> IO TypeDescriptionPtr
forall a. Storable a => Ptr a -> IO a
peek Ptr TypeDescriptionPtr
bindingsPtr)
Int
616
{-# LINE 382 "lib/Data/SpirV/Reflect/FFI/Internal.chs" #-}
inflateDescriptorBinding
pure DescriptorSet.DescriptorSet{Word32
Vector DescriptorBinding
set :: Word32
bindings :: Vector DescriptorBinding
$sel:set:DescriptorSet :: Word32
$sel:bindings:DescriptorSet :: Vector DescriptorBinding
..}
type InterfaceVariablePtr = C2HSImp.Ptr (())
{-# LINE 387 "lib/Data/SpirV/Reflect/FFI/Internal.chs" #-}
inflateInterfaceVariable :: InterfaceVariablePtr -> IO InterfaceVariable
inflateInterfaceVariable :: TypeDescriptionPtr -> IO InterfaceVariable
inflateInterfaceVariable TypeDescriptionPtr
iv = do
Maybe Word32
spirv_id <- (Word32 -> Maybe Word32) -> IO Word32 -> IO (Maybe Word32)
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Word32 -> Maybe Word32
forall a. a -> Maybe a
just (IO Word32 -> IO (Maybe Word32))
-> (IO CUInt -> IO Word32) -> IO CUInt -> IO (Maybe Word32)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO CUInt -> IO Word32
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CUInt -> IO (Maybe Word32)) -> IO CUInt -> IO (Maybe Word32)
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
0 :: IO C2HSImp.CUInt}) TypeDescriptionPtr
iv
Maybe Text
name <- Text
-> (IO (Ptr CChar) -> IO Text) -> IO (Ptr CChar) -> IO (Maybe Text)
forall b a. Eq b => b -> (IO a -> IO b) -> IO a -> IO (Maybe b)
inflateMaybe Text
"" IO (Ptr CChar) -> IO Text
inflateText (IO (Ptr CChar) -> IO (Maybe Text))
-> IO (Ptr CChar) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO (Ptr CChar)
forall b. Ptr b -> Int -> IO (Ptr CChar)
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
8 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) TypeDescriptionPtr
iv
Word32
location <- IO CUInt -> IO Word32
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CUInt -> IO Word32) -> IO CUInt -> IO Word32
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
16 :: IO C2HSImp.CUInt}) TypeDescriptionPtr
iv
Maybe Word32
component <- Word32 -> (IO CUInt -> IO Word32) -> IO CUInt -> IO (Maybe Word32)
forall b a. Eq b => b -> (IO a -> IO b) -> IO a -> IO (Maybe b)
inflateMaybe Word32
4294967295 IO CUInt -> IO Word32
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CUInt -> IO (Maybe Word32)) -> IO CUInt -> IO (Maybe Word32)
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
20 :: IO C2HSImp.CUInt}) TypeDescriptionPtr
iv
StorageClass
storage_class <- (Int32 -> StorageClass) -> IO Int32 -> IO StorageClass
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Int32 -> StorageClass
SpirV.StorageClass (IO Int32 -> IO StorageClass)
-> (IO CInt -> IO Int32) -> IO CInt -> IO StorageClass
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO CInt -> IO Int32
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CInt -> IO StorageClass) -> IO CInt -> IO StorageClass
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO CInt
forall b. Ptr b -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
24 :: IO C2HSImp.CInt}) TypeDescriptionPtr
iv
Maybe Text
semantic <- Text
-> (IO (Ptr CChar) -> IO Text) -> IO (Ptr CChar) -> IO (Maybe Text)
forall b a. Eq b => b -> (IO a -> IO b) -> IO a -> IO (Maybe b)
inflateMaybe Text
"" IO (Ptr CChar) -> IO Text
inflateText (IO (Ptr CChar) -> IO (Maybe Text))
-> IO (Ptr CChar) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO (Ptr CChar)
forall b. Ptr b -> Int -> IO (Ptr CChar)
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
32 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) TypeDescriptionPtr
iv
DecorationFlagBits
decoration_flags <- IO CUInt -> IO DecorationFlagBits
forall a b. (Integral a, Coercible Word32 b) => IO a -> IO b
inflateFlags32 (IO CUInt -> IO DecorationFlagBits)
-> IO CUInt -> IO DecorationFlagBits
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
40 :: IO C2HSImp.CUInt}) TypeDescriptionPtr
iv
Maybe BuiltIn
built_in <- BuiltIn -> (IO CInt -> IO BuiltIn) -> IO CInt -> IO (Maybe BuiltIn)
forall b a. Eq b => b -> (IO a -> IO b) -> IO a -> IO (Maybe b)
inflateMaybe (Int32 -> BuiltIn
SpirV.BuiltIn Int32
forall a. Bounded a => a
maxBound) ((Int32 -> BuiltIn) -> IO Int32 -> IO BuiltIn
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Int32 -> BuiltIn
SpirV.BuiltIn (IO Int32 -> IO BuiltIn)
-> (IO CInt -> IO Int32) -> IO CInt -> IO BuiltIn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO CInt -> IO Int32
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral) (IO CInt -> IO (Maybe BuiltIn)) -> IO CInt -> IO (Maybe BuiltIn)
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO CInt
forall b. Ptr b -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
44 :: IO C2HSImp.CInt}) TypeDescriptionPtr
iv
Numeric
numeric <-
TypeDescriptionPtr -> Int -> IO Numeric
forall struct. Ptr struct -> Int -> IO Numeric
inflateNumericTraits
TypeDescriptionPtr
iv
(Int
48)
{-# LINE 418 "lib/Data/SpirV/Reflect/FFI/Internal.chs" #-}
Array
array <-
TypeDescriptionPtr -> Int -> IO Array
forall struct. Ptr struct -> Int -> IO Array
inflateArrayTraits
TypeDescriptionPtr
iv
(Int
72)
{-# LINE 423 "lib/Data/SpirV/Reflect/FFI/Internal.chs" #-}
Vector InterfaceVariable
members <-
IO CUInt
-> IO TypeDescriptionPtr
-> Int
-> (TypeDescriptionPtr -> IO InterfaceVariable)
-> IO (Vector InterfaceVariable)
forall i p a.
Integral i =>
IO i -> IO (Ptr p) -> Int -> (Ptr p -> IO a) -> IO (Vector a)
inflateVector
((\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
336 :: IO C2HSImp.CUInt}) TypeDescriptionPtr
iv)
((\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO TypeDescriptionPtr
forall b. Ptr b -> Int -> IO TypeDescriptionPtr
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
344 :: IO (InterfaceVariablePtr)}) TypeDescriptionPtr
iv)
Int
376
{-# LINE 429 "lib/Data/SpirV/Reflect/FFI/Internal.chs" #-}
inflateInterfaceVariable
Format
format <- IO CInt -> IO Format
forall a b. (Integral a, Enum b) => IO a -> IO b
inflateEnum (IO CInt -> IO Format) -> IO CInt -> IO Format
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO CInt
forall b. Ptr b -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
352 :: IO C2HSImp.CInt}) TypeDescriptionPtr
iv
Maybe TypeDescription
type_description <-
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO TypeDescriptionPtr
forall b. Ptr b -> Int -> IO TypeDescriptionPtr
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
360 :: IO (TypeDescriptionPtr)}) TypeDescriptionPtr
iv IO TypeDescriptionPtr
-> (TypeDescriptionPtr -> IO (Maybe TypeDescription))
-> IO (Maybe TypeDescription)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
(TypeDescriptionPtr -> IO TypeDescription)
-> TypeDescriptionPtr -> IO (Maybe TypeDescription)
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek TypeDescriptionPtr -> IO TypeDescription
inflateTypeDescription
Word32
wo_location <- IO CUInt -> IO Word32
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CUInt -> IO Word32) -> IO CUInt -> IO Word32
forall a b. (a -> b) -> a -> b
$
(\TypeDescriptionPtr
ptr -> do {TypeDescriptionPtr -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff TypeDescriptionPtr
ptr Int
368 :: IO C2HSImp.CUInt}) TypeDescriptionPtr
iv
let word_offset :: WordOffset
word_offset = InterfaceVariable.WordOffset{$sel:location:WordOffset :: Word32
location=Word32
wo_location}
pure InterfaceVariable.InterfaceVariable{Maybe Word32
Maybe BuiltIn
Maybe TypeDescription
Maybe Text
Word32
StorageClass
DecorationFlagBits
Format
Array
Numeric
WordOffset
Vector InterfaceVariable
$sel:location:InterfaceVariable :: Word32
$sel:storage_class:InterfaceVariable :: StorageClass
spirv_id :: Maybe Word32
name :: Maybe Text
location :: Word32
component :: Maybe Word32
storage_class :: StorageClass
semantic :: Maybe Text
decoration_flags :: DecorationFlagBits
built_in :: Maybe BuiltIn
numeric :: Numeric
array :: Array
members :: Vector InterfaceVariable
format :: Format
type_description :: Maybe TypeDescription
word_offset :: WordOffset
$sel:spirv_id:InterfaceVariable :: Maybe Word32
$sel:name:InterfaceVariable :: Maybe Text
$sel:component:InterfaceVariable :: Maybe Word32
$sel:semantic:InterfaceVariable :: Maybe Text
$sel:decoration_flags:InterfaceVariable :: DecorationFlagBits
$sel:built_in:InterfaceVariable :: Maybe BuiltIn
$sel:numeric:InterfaceVariable :: Numeric
$sel:array:InterfaceVariable :: Array
$sel:members:InterfaceVariable :: Vector InterfaceVariable
$sel:format:InterfaceVariable :: Format
$sel:type_description:InterfaceVariable :: Maybe TypeDescription
$sel:word_offset:InterfaceVariable :: WordOffset
..}
type ImageTraitsPtr = C2HSImp.Ptr (())
{-# LINE 447 "lib/Data/SpirV/Reflect/FFI/Internal.chs" #-}
inflateImageTraits :: Ptr struct -> Int -> IO Traits.Image
inflateImageTraits :: forall struct. Ptr struct -> Int -> IO Image
inflateImageTraits Ptr struct
src Int
offset = do
let it :: Ptr b
it = Ptr struct -> Ptr Any
forall a b. Ptr a -> Ptr b
castPtr Ptr struct
src Ptr Any -> Int -> Ptr b
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
offset
Dim
dim <- (Int32 -> Dim) -> IO Int32 -> IO Dim
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Int32 -> Dim
SpirV.Dim (IO Int32 -> IO Dim) -> (IO CInt -> IO Int32) -> IO CInt -> IO Dim
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO CInt -> IO Int32
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CInt -> IO Dim) -> IO CInt -> IO Dim
forall a b. (a -> b) -> a -> b
$
(\Ptr Any
ptr -> do {Ptr Any -> Int -> IO CInt
forall b. Ptr b -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr Any
ptr Int
0 :: IO C2HSImp.CInt}) Ptr Any
forall {b}. Ptr b
it
Word32
depth <- IO CUInt -> IO Word32
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CUInt -> IO Word32) -> IO CUInt -> IO Word32
forall a b. (a -> b) -> a -> b
$
(\Ptr Any
ptr -> do {Ptr Any -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr Any
ptr Int
4 :: IO C2HSImp.CUInt}) Ptr Any
forall {b}. Ptr b
it
Word32
arrayed <- IO CUInt -> IO Word32
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CUInt -> IO Word32) -> IO CUInt -> IO Word32
forall a b. (a -> b) -> a -> b
$
(\Ptr Any
ptr -> do {Ptr Any -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr Any
ptr Int
8 :: IO C2HSImp.CUInt}) Ptr Any
forall {b}. Ptr b
it
Word32
ms <- IO CUInt -> IO Word32
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CUInt -> IO Word32) -> IO CUInt -> IO Word32
forall a b. (a -> b) -> a -> b
$
(\Ptr Any
ptr -> do {Ptr Any -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr Any
ptr Int
12 :: IO C2HSImp.CUInt}) Ptr Any
forall {b}. Ptr b
it
Word32
sampled <- IO CUInt -> IO Word32
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CUInt -> IO Word32) -> IO CUInt -> IO Word32
forall a b. (a -> b) -> a -> b
$
(\Ptr Any
ptr -> do {Ptr Any -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr Any
ptr Int
16 :: IO C2HSImp.CUInt}) Ptr Any
forall {b}. Ptr b
it
ImageFormat
image_format <- (Int32 -> ImageFormat) -> IO Int32 -> IO ImageFormat
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Int32 -> ImageFormat
SpirV.ImageFormat (IO Int32 -> IO ImageFormat)
-> (IO CInt -> IO Int32) -> IO CInt -> IO ImageFormat
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO CInt -> IO Int32
forall a b. (Integral a, Enum b) => IO a -> IO b
inflateEnum (IO CInt -> IO ImageFormat) -> IO CInt -> IO ImageFormat
forall a b. (a -> b) -> a -> b
$
(\Ptr Any
ptr -> do {Ptr Any -> Int -> IO CInt
forall b. Ptr b -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr Any
ptr Int
20 :: IO C2HSImp.CInt}) Ptr Any
forall {b}. Ptr b
it
pure Traits.Image{Word32
Dim
ImageFormat
dim :: Dim
depth :: Word32
arrayed :: Word32
ms :: Word32
sampled :: Word32
image_format :: ImageFormat
$sel:dim:Image :: Dim
$sel:depth:Image :: Word32
$sel:arrayed:Image :: Word32
$sel:ms:Image :: Word32
$sel:sampled:Image :: Word32
$sel:image_format:Image :: ImageFormat
..}
type NumericTraitsPtr = C2HSImp.Ptr (())
{-# LINE 473 "lib/Data/SpirV/Reflect/FFI/Internal.chs" #-}
inflateNumericTraits :: Ptr struct -> Int -> IO Traits.Numeric
inflateNumericTraits :: forall struct. Ptr struct -> Int -> IO Numeric
inflateNumericTraits Ptr struct
src Int
offset = do
let nt :: Ptr b
nt = Ptr struct -> Ptr Any
forall a b. Ptr a -> Ptr b
castPtr Ptr struct
src Ptr Any -> Int -> Ptr b
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
offset
Word32
width <- IO CUInt -> IO Word32
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CUInt -> IO Word32) -> IO CUInt -> IO Word32
forall a b. (a -> b) -> a -> b
$
(\Ptr Any
ptr -> do {Ptr Any -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr Any
ptr Int
0 :: IO C2HSImp.CUInt}) Ptr Any
forall {b}. Ptr b
nt
CUInt
signedness <- IO CUInt -> IO CUInt
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CUInt -> IO CUInt) -> IO CUInt -> IO CUInt
forall a b. (a -> b) -> a -> b
$
(\Ptr Any
ptr -> do {Ptr Any -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr Any
ptr Int
4 :: IO C2HSImp.CUInt}) Ptr Any
forall {b}. Ptr b
nt
let signed :: Bool
signed = CUInt
signedness CUInt -> CUInt -> Bool
forall a. Eq a => a -> a -> Bool
/= (CUInt
0 :: C2HSImp.CUInt)
let scalar :: Scalar
scalar = Traits.Scalar{Bool
Word32
width :: Word32
signed :: Bool
$sel:width:Scalar :: Word32
$sel:signed:Scalar :: Bool
..}
Word32
component_count <- IO CUInt -> IO Word32
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CUInt -> IO Word32) -> IO CUInt -> IO Word32
forall a b. (a -> b) -> a -> b
$
(\Ptr Any
ptr -> do {Ptr Any -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr Any
ptr Int
8 :: IO C2HSImp.CUInt}) Ptr Any
forall {b}. Ptr b
nt
let vector :: Vector
vector = Traits.Vector{Word32
component_count :: Word32
$sel:component_count:Vector :: Word32
..}
Word32
column_count <- IO CUInt -> IO Word32
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CUInt -> IO Word32) -> IO CUInt -> IO Word32
forall a b. (a -> b) -> a -> b
$
(\Ptr Any
ptr -> do {Ptr Any -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr Any
ptr Int
12 :: IO C2HSImp.CUInt}) Ptr Any
forall {b}. Ptr b
nt
Word32
row_count <- IO CUInt -> IO Word32
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CUInt -> IO Word32) -> IO CUInt -> IO Word32
forall a b. (a -> b) -> a -> b
$
(\Ptr Any
ptr -> do {Ptr Any -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr Any
ptr Int
16 :: IO C2HSImp.CUInt}) Ptr Any
forall {b}. Ptr b
nt
Word32
stride <- IO CUInt -> IO Word32
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CUInt -> IO Word32) -> IO CUInt -> IO Word32
forall a b. (a -> b) -> a -> b
$
(\Ptr Any
ptr -> do {Ptr Any -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr Any
ptr Int
20 :: IO C2HSImp.CUInt}) Ptr Any
forall {b}. Ptr b
nt
let matrix :: Matrix
matrix = Traits.Matrix{Word32
column_count :: Word32
row_count :: Word32
stride :: Word32
$sel:column_count:Matrix :: Word32
$sel:row_count:Matrix :: Word32
$sel:stride:Matrix :: Word32
..}
pure Traits.Numeric{Matrix
Vector
Scalar
scalar :: Scalar
vector :: Vector
matrix :: Matrix
$sel:scalar:Numeric :: Scalar
$sel:vector:Numeric :: Vector
$sel:matrix:Numeric :: Matrix
..}
type ArrayTraitsPtr = C2HSImp.Ptr (())
{-# LINE 500 "lib/Data/SpirV/Reflect/FFI/Internal.chs" #-}
inflateArrayTraits :: Ptr struct -> Int -> IO Traits.Array
inflateArrayTraits :: forall struct. Ptr struct -> Int -> IO Array
inflateArrayTraits Ptr struct
src Int
offset = do
let at :: Ptr b
at = Ptr struct -> Ptr Any
forall a b. Ptr a -> Ptr b
castPtr Ptr struct
src Ptr Any -> Int -> Ptr b
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
offset
Word32
dims_count <- IO CUInt -> IO Word32
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CUInt -> IO Word32) -> IO CUInt -> IO Word32
forall a b. (a -> b) -> a -> b
$
(\Ptr Any
ptr -> do {Ptr Any -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr Any
ptr Int
0 :: IO C2HSImp.CUInt}) Ptr Any
forall {b}. Ptr b
at
Vector Word32
dims <- (Vector Word32 -> Vector Word32)
-> IO (Vector Word32) -> IO (Vector Word32)
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Vector Word32 -> Vector Word32
forall (v :: * -> *) a (w :: * -> *).
(Vector v a, Vector w a) =>
v a -> w a
Vector.convert (IO (Vector Word32) -> IO (Vector Word32))
-> IO (Vector Word32) -> IO (Vector Word32)
forall a b. (a -> b) -> a -> b
$ IO CUInt
-> IO (Ptr CUInt)
-> Int
-> (Ptr CUInt -> IO Word32)
-> IO (Vector Word32)
forall i p a.
Integral i =>
IO i -> IO (Ptr p) -> Int -> (Ptr p -> IO a) -> IO (Vector a)
inflateVector
((\Ptr Any
ptr -> do {Ptr Any -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr Any
ptr Int
0 :: IO C2HSImp.CUInt}) Ptr Any
forall {b}. Ptr b
at)
((\Ptr Any
ptr -> do {Ptr CUInt -> IO (Ptr CUInt)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr CUInt -> IO (Ptr CUInt)) -> Ptr CUInt -> IO (Ptr CUInt)
forall a b. (a -> b) -> a -> b
$ Ptr Any
ptr Ptr Any -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`C2HSImp.plusPtr` Int
4 :: IO (C2HSImp.Ptr C2HSImp.CUInt)}) Ptr Any
forall {b}. Ptr b
at)
Int
4
{-# LINE 512 "lib/Data/SpirV/Reflect/FFI/Internal.chs" #-}
(fmap fromIntegral . peek)
Maybe Word32
stride <- Word32 -> (IO CUInt -> IO Word32) -> IO CUInt -> IO (Maybe Word32)
forall b a. Eq b => b -> (IO a -> IO b) -> IO a -> IO (Maybe b)
inflateMaybe Word32
0 IO CUInt -> IO Word32
forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral (IO CUInt -> IO (Maybe Word32)) -> IO CUInt -> IO (Maybe Word32)
forall a b. (a -> b) -> a -> b
$
(\Ptr Any
ptr -> do {Ptr Any -> Int -> IO CUInt
forall b. Ptr b -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr Any
ptr Int
260 :: IO C2HSImp.CUInt}) Ptr Any
forall {b}. Ptr b
at
pure Traits.Array{Maybe Word32
Word32
Vector Word32
dims_count :: Word32
dims :: Vector Word32
stride :: Maybe Word32
$sel:dims_count:Array :: Word32
$sel:dims:Array :: Vector Word32
$sel:stride:Array :: Maybe Word32
..}
inflateVector :: Integral i => IO i -> IO (Ptr p) -> Int -> (Ptr p -> IO a) -> IO (Vector a)
inflateVector :: forall i p a.
Integral i =>
IO i -> IO (Ptr p) -> Int -> (Ptr p -> IO a) -> IO (Vector a)
inflateVector IO i
getCount IO (Ptr p)
getItems Int
itemSize Ptr p -> IO a
inflate = do
i
count <- IO i
getCount
Ptr p
itemsPtr <- IO (Ptr p)
getItems
Int -> (Int -> IO a) -> IO (Vector a)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
Vector.generateM (i -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral i
count) \Int
pos -> do
a
x <- Ptr p -> IO a
inflate (Ptr p -> IO a) -> Ptr p -> IO a
forall a b. (a -> b) -> a -> b
$ Ptr p
itemsPtr Ptr p -> Int -> Ptr p
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
itemSize Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
pos)
a -> IO a
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a -> IO a) -> a -> IO a
forall a b. (a -> b) -> a -> b
$! a
x
inflateIntegral :: (Integral a, Num b) => IO a -> IO b
inflateIntegral :: forall a b. (Integral a, Num b) => IO a -> IO b
inflateIntegral IO a
getIntegral =
IO a
getIntegral IO a -> (a -> IO b) -> IO b
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \a
i ->
b -> IO b
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (b -> IO b) -> b -> IO b
forall a b. (a -> b) -> a -> b
$! a -> b
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
i
inflateEnum :: (Integral a, Enum b) => IO a -> IO b
inflateEnum :: forall a b. (Integral a, Enum b) => IO a -> IO b
inflateEnum IO a
getEnum =
IO a
getEnum IO a -> (a -> IO b) -> IO b
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \a
i ->
b -> IO b
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (b -> IO b) -> b -> IO b
forall a b. (a -> b) -> a -> b
$! Int -> b
forall a. Enum a => Int -> a
toEnum (a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
i)
inflateFlags32 :: forall a b . (Integral a, Coercible Word32 b) => IO a -> IO b
inflateFlags32 :: forall a b. (Integral a, Coercible Word32 b) => IO a -> IO b
inflateFlags32 IO a
gitBits =
IO a
gitBits IO a -> (a -> IO b) -> IO b
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \a
i ->
b -> IO b
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (b -> IO b) -> b -> IO b
forall a b. (a -> b) -> a -> b
$! forall a b. Coercible a b => a -> b
forall a b. Coercible a b => a -> b
coerce @Word32 @b (a -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
i)
inflateText :: IO CString -> IO Text
inflateText :: IO (Ptr CChar) -> IO Text
inflateText IO (Ptr CChar)
getPtr =
IO (Ptr CChar)
getPtr IO (Ptr CChar) -> (Ptr CChar -> IO Text) -> IO Text
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Ptr CChar
ptr ->
if Ptr CChar
forall {b}. Ptr b
nullPtr Ptr CChar -> Ptr CChar -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr CChar
ptr then
Text -> IO Text
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
forall a. Monoid a => a
mempty
else
case Ptr CChar
ptr of
GHC.Ptr Addr#
addr ->
Text -> IO Text
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> IO Text) -> Text -> IO Text
forall a b. (a -> b) -> a -> b
$! Addr# -> Text
Text.unpackCString# Addr#
addr
inflateMaybe :: Eq b => b -> (IO a -> IO b) -> IO a -> IO (Maybe b)
inflateMaybe :: forall b a. Eq b => b -> (IO a -> IO b) -> IO a -> IO (Maybe b)
inflateMaybe b
nothingBurger IO a -> IO b
inflate = (b -> Maybe b) -> IO b -> IO (Maybe b)
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\b
x -> if b
x b -> b -> Bool
forall a. Eq a => a -> a -> Bool
== b
nothingBurger then Maybe b
forall a. Maybe a
Nothing else b -> Maybe b
forall a. a -> Maybe a
Just b
x) (IO b -> IO (Maybe b)) -> (IO a -> IO b) -> IO a -> IO (Maybe b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO a -> IO b
inflate
just :: a -> Maybe a
just :: forall a. a -> Maybe a
just a
x = a
x a -> Maybe a -> Maybe a
forall a b. a -> b -> b
`seq` a -> Maybe a
forall a. a -> Maybe a
Just a
x
foreign import ccall unsafe "Data/SpirV/Reflect/FFI/Internal.chs.h spvReflectCreateShaderModule"
createShaderModule'_ :: (C2HSImp.CULong -> ((C2HSImp.Ptr ()) -> ((ShaderModulePtr) -> (IO C2HSImp.CInt))))
foreign import ccall unsafe "Data/SpirV/Reflect/FFI/Internal.chs.h spvReflectCreateShaderModule2"
createShaderModule2'_ :: (C2HSImp.CUInt -> (C2HSImp.CULong -> ((C2HSImp.Ptr ()) -> ((ShaderModulePtr) -> (IO C2HSImp.CInt)))))
foreign import ccall unsafe "Data/SpirV/Reflect/FFI/Internal.chs.h spvReflectDestroyShaderModule"
destroyShaderModule'_ :: ((ShaderModulePtr) -> (IO ()))