{-# LINE 1 "src/WGPU/Raw/Generated/Struct/WGPUComputePassDescriptor.hsc" #-}
{-# OPTIONS_GHC -Wno-unused-imports #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE NoImplicitPrelude #-}
module WGPU.Raw.Generated.Struct.WGPUComputePassDescriptor where
import Data.Word (Word16, Word32, Word64)
import Data.Int (Int32)
import Foreign
import Foreign.C.Types
import WGPU.Raw.Types
import Prelude (pure, ($!))
import WGPU.Raw.Generated.Struct.WGPUChainedStruct
data WGPUComputePassDescriptor = WGPUComputePassDescriptor {
  WGPUComputePassDescriptor -> Ptr WGPUChainedStruct
nextInChain :: Ptr (WGPUChainedStruct),
  WGPUComputePassDescriptor -> Ptr CChar
label :: Ptr (CChar)
}
instance Storable WGPUComputePassDescriptor where
  sizeOf :: WGPUComputePassDescriptor -> Int
sizeOf WGPUComputePassDescriptor
_ = ((Int
16))
{-# LINE 29 "src/WGPU/Raw/Generated/Struct/WGPUComputePassDescriptor.hsc" #-}
  alignment = sizeOf
  peek :: Ptr WGPUComputePassDescriptor -> IO WGPUComputePassDescriptor
peek Ptr WGPUComputePassDescriptor
ptr = do
    Ptr WGPUChainedStruct
nextInChain <- ((\Ptr WGPUComputePassDescriptor
hsc_ptr -> Ptr WGPUComputePassDescriptor -> Int -> IO (Ptr WGPUChainedStruct)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr WGPUComputePassDescriptor
hsc_ptr Int
0)) Ptr WGPUComputePassDescriptor
ptr
{-# LINE 32 "src/WGPU/Raw/Generated/Struct/WGPUComputePassDescriptor.hsc" #-}
    label <- ((\hsc_ptr -> peekByteOff hsc_ptr 8)) ptr
{-# LINE 33 "src/WGPU/Raw/Generated/Struct/WGPUComputePassDescriptor.hsc" #-}
    pure $! WGPUComputePassDescriptor{..}
  poke :: Ptr WGPUComputePassDescriptor -> WGPUComputePassDescriptor -> IO ()
poke Ptr WGPUComputePassDescriptor
ptr WGPUComputePassDescriptor{Ptr CChar
Ptr WGPUChainedStruct
label :: Ptr CChar
nextInChain :: Ptr WGPUChainedStruct
label :: WGPUComputePassDescriptor -> Ptr CChar
nextInChain :: WGPUComputePassDescriptor -> Ptr WGPUChainedStruct
..} = do
    ((\Ptr WGPUComputePassDescriptor
hsc_ptr -> Ptr WGPUComputePassDescriptor
-> Int -> Ptr WGPUChainedStruct -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr WGPUComputePassDescriptor
hsc_ptr Int
0)) Ptr WGPUComputePassDescriptor
ptr Ptr WGPUChainedStruct
nextInChain
{-# LINE 36 "src/WGPU/Raw/Generated/Struct/WGPUComputePassDescriptor.hsc" #-}
    ((\hsc_ptr -> pokeByteOff hsc_ptr 8)) ptr label