{-# LINE 1 "src/Gpu/Vulkan/Pipeline/ColorBlendAttachment/Core.hsc" #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE PatternSynonyms, ViewPatterns #-}
{-# OPTIONS_GHC -Wall -fno-warn-tabs #-}
module Gpu.Vulkan.Pipeline.ColorBlendAttachment.Core (
State, PtrState, pattern State,
stateBlendEnable,
stateSrcColorBlendFactor, stateDstColorBlendFactor, stateColorBlendOp,
stateSrcAlphaBlendFactor, stateDstAlphaBlendFactor, stateAlphaBlendOp,
stateColorWriteMask
) where
import Foreign.Ptr
import Foreign.Storable
import Foreign.C.Struct
import Data.Word
struct "State" (32)
{-# LINE 26 "src/Gpu/Vulkan/Pipeline/ColorBlendAttachment/Core.hsc" #-}
4 [
{-# LINE 27 "src/Gpu/Vulkan/Pipeline/ColorBlendAttachment/Core.hsc" #-}
("blendEnable", ''Word32,
{-# LINE 28 "src/Gpu/Vulkan/Pipeline/ColorBlendAttachment/Core.hsc" #-}
[| (\hsc_ptr -> peekByteOff hsc_ptr 0) |],
{-# LINE 29 "src/Gpu/Vulkan/Pipeline/ColorBlendAttachment/Core.hsc" #-}
[| (\hsc_ptr -> pokeByteOff hsc_ptr 0) |]),
{-# LINE 30 "src/Gpu/Vulkan/Pipeline/ColorBlendAttachment/Core.hsc" #-}
("srcColorBlendFactor", ''Word32,
{-# LINE 31 "src/Gpu/Vulkan/Pipeline/ColorBlendAttachment/Core.hsc" #-}
[| (\hsc_ptr -> peekByteOff hsc_ptr 4) |],
{-# LINE 33 "src/Gpu/Vulkan/Pipeline/ColorBlendAttachment/Core.hsc" #-}
[| (\hsc_ptr -> pokeByteOff hsc_ptr 4) |]),
{-# LINE 35 "src/Gpu/Vulkan/Pipeline/ColorBlendAttachment/Core.hsc" #-}
("dstColorBlendFactor", ''Word32,
{-# LINE 36 "src/Gpu/Vulkan/Pipeline/ColorBlendAttachment/Core.hsc" #-}
[| (\hsc_ptr -> peekByteOff hsc_ptr 8) |],
{-# LINE 38 "src/Gpu/Vulkan/Pipeline/ColorBlendAttachment/Core.hsc" #-}
[| (\hsc_ptr -> pokeByteOff hsc_ptr 8) |]),
{-# LINE 40 "src/Gpu/Vulkan/Pipeline/ColorBlendAttachment/Core.hsc" #-}
("colorBlendOp", ''Word32,
{-# LINE 41 "src/Gpu/Vulkan/Pipeline/ColorBlendAttachment/Core.hsc" #-}
[| (\hsc_ptr -> peekByteOff hsc_ptr 12) |],
{-# LINE 42 "src/Gpu/Vulkan/Pipeline/ColorBlendAttachment/Core.hsc" #-}
[| (\hsc_ptr -> pokeByteOff hsc_ptr 12) |]),
{-# LINE 44 "src/Gpu/Vulkan/Pipeline/ColorBlendAttachment/Core.hsc" #-}
("srcAlphaBlendFactor", ''Word32,
{-# LINE 45 "src/Gpu/Vulkan/Pipeline/ColorBlendAttachment/Core.hsc" #-}
[| (\hsc_ptr -> peekByteOff hsc_ptr 16) |],
{-# LINE 47 "src/Gpu/Vulkan/Pipeline/ColorBlendAttachment/Core.hsc" #-}
[| (\hsc_ptr -> pokeByteOff hsc_ptr 16) |]),
{-# LINE 49 "src/Gpu/Vulkan/Pipeline/ColorBlendAttachment/Core.hsc" #-}
("dstAlphaBlendFactor", ''Word32,
{-# LINE 50 "src/Gpu/Vulkan/Pipeline/ColorBlendAttachment/Core.hsc" #-}
[| (\hsc_ptr -> peekByteOff hsc_ptr 20) |],
{-# LINE 52 "src/Gpu/Vulkan/Pipeline/ColorBlendAttachment/Core.hsc" #-}
[| (\hsc_ptr -> pokeByteOff hsc_ptr 20) |]),
{-# LINE 54 "src/Gpu/Vulkan/Pipeline/ColorBlendAttachment/Core.hsc" #-}
("alphaBlendOp", ''Word32,
{-# LINE 55 "src/Gpu/Vulkan/Pipeline/ColorBlendAttachment/Core.hsc" #-}
[| (\hsc_ptr -> peekByteOff hsc_ptr 24) |],
{-# LINE 56 "src/Gpu/Vulkan/Pipeline/ColorBlendAttachment/Core.hsc" #-}
[| (\hsc_ptr -> pokeByteOff hsc_ptr 24) |]),
{-# LINE 58 "src/Gpu/Vulkan/Pipeline/ColorBlendAttachment/Core.hsc" #-}
("colorWriteMask", ''Word32,
{-# LINE 59 "src/Gpu/Vulkan/Pipeline/ColorBlendAttachment/Core.hsc" #-}
[| (\hsc_ptr -> peekByteOff hsc_ptr 28) |],
{-# LINE 61 "src/Gpu/Vulkan/Pipeline/ColorBlendAttachment/Core.hsc" #-}
[| (\hsc_ptr -> pokeByteOff hsc_ptr 28) |]) ]
{-# LINE 63 "src/Gpu/Vulkan/Pipeline/ColorBlendAttachment/Core.hsc" #-}
[''Show, ''Storable]
type PtrState = Ptr State