{-# language CPP #-}
module Vulkan.Core10.Enums.BlendOp  (BlendOp( BLEND_OP_ADD
                                            , BLEND_OP_SUBTRACT
                                            , BLEND_OP_REVERSE_SUBTRACT
                                            , BLEND_OP_MIN
                                            , BLEND_OP_MAX
                                            , BLEND_OP_BLUE_EXT
                                            , BLEND_OP_GREEN_EXT
                                            , BLEND_OP_RED_EXT
                                            , BLEND_OP_INVERT_OVG_EXT
                                            , BLEND_OP_CONTRAST_EXT
                                            , BLEND_OP_MINUS_CLAMPED_EXT
                                            , BLEND_OP_MINUS_EXT
                                            , BLEND_OP_PLUS_DARKER_EXT
                                            , BLEND_OP_PLUS_CLAMPED_ALPHA_EXT
                                            , BLEND_OP_PLUS_CLAMPED_EXT
                                            , BLEND_OP_PLUS_EXT
                                            , BLEND_OP_HSL_LUMINOSITY_EXT
                                            , BLEND_OP_HSL_COLOR_EXT
                                            , BLEND_OP_HSL_SATURATION_EXT
                                            , BLEND_OP_HSL_HUE_EXT
                                            , BLEND_OP_HARDMIX_EXT
                                            , BLEND_OP_PINLIGHT_EXT
                                            , BLEND_OP_LINEARLIGHT_EXT
                                            , BLEND_OP_VIVIDLIGHT_EXT
                                            , BLEND_OP_LINEARBURN_EXT
                                            , BLEND_OP_LINEARDODGE_EXT
                                            , BLEND_OP_INVERT_RGB_EXT
                                            , BLEND_OP_INVERT_EXT
                                            , BLEND_OP_EXCLUSION_EXT
                                            , BLEND_OP_DIFFERENCE_EXT
                                            , BLEND_OP_SOFTLIGHT_EXT
                                            , BLEND_OP_HARDLIGHT_EXT
                                            , BLEND_OP_COLORBURN_EXT
                                            , BLEND_OP_COLORDODGE_EXT
                                            , BLEND_OP_LIGHTEN_EXT
                                            , BLEND_OP_DARKEN_EXT
                                            , BLEND_OP_OVERLAY_EXT
                                            , BLEND_OP_SCREEN_EXT
                                            , BLEND_OP_MULTIPLY_EXT
                                            , BLEND_OP_XOR_EXT
                                            , BLEND_OP_DST_ATOP_EXT
                                            , BLEND_OP_SRC_ATOP_EXT
                                            , BLEND_OP_DST_OUT_EXT
                                            , BLEND_OP_SRC_OUT_EXT
                                            , BLEND_OP_DST_IN_EXT
                                            , BLEND_OP_SRC_IN_EXT
                                            , BLEND_OP_DST_OVER_EXT
                                            , BLEND_OP_SRC_OVER_EXT
                                            , BLEND_OP_DST_EXT
                                            , BLEND_OP_SRC_EXT
                                            , BLEND_OP_ZERO_EXT
                                            , ..
                                            )) where

import GHC.Read (choose)
import GHC.Read (expectP)
import GHC.Read (parens)
import GHC.Show (showParen)
import GHC.Show (showString)
import GHC.Show (showsPrec)
import Text.ParserCombinators.ReadPrec ((+++))
import Text.ParserCombinators.ReadPrec (prec)
import Text.ParserCombinators.ReadPrec (step)
import Foreign.Storable (Storable)
import Data.Int (Int32)
import GHC.Read (Read(readPrec))
import Text.Read.Lex (Lexeme(Ident))
import Vulkan.Zero (Zero)
-- | VkBlendOp - Framebuffer blending operations
--
-- = Description
--
-- The semantics of each basic blend operations is described in the table
-- below:
--
-- +-------------------------------+--------------------+-----------------+
-- | 'BlendOp'                     | RGB Components     | Alpha Component |
-- +===============================+====================+=================+
-- | 'BLEND_OP_ADD'                | R = Rs0 × Sr + Rd  | A = As0 × Sa +  |
-- |                               | × Dr               | Ad × Da         |
-- |                               | G = Gs0 × Sg + Gd  |                 |
-- |                               | × Dg               |                 |
-- |                               | B = Bs0 × Sb + Bd  |                 |
-- |                               | × Db               |                 |
-- +-------------------------------+--------------------+-----------------+
-- | 'BLEND_OP_SUBTRACT'           | R = Rs0 × Sr - Rd  | A = As0 × Sa -  |
-- |                               | × Dr               | Ad × Da         |
-- |                               | G = Gs0 × Sg - Gd  |                 |
-- |                               | × Dg               |                 |
-- |                               | B = Bs0 × Sb - Bd  |                 |
-- |                               | × Db               |                 |
-- +-------------------------------+--------------------+-----------------+
-- | 'BLEND_OP_REVERSE_SUBTRACT'   | R = Rd × Dr - Rs0  | A = Ad × Da -   |
-- |                               | × Sr               | As0 × Sa        |
-- |                               | G = Gd × Dg - Gs0  |                 |
-- |                               | × Sg               |                 |
-- |                               | B = Bd × Db - Bs0  |                 |
-- |                               | × Sb               |                 |
-- +-------------------------------+--------------------+-----------------+
-- | 'BLEND_OP_MIN'                | R = min(Rs0,Rd)    | A = min(As0,Ad) |
-- |                               | G = min(Gs0,Gd)    |                 |
-- |                               | B = min(Bs0,Bd)    |                 |
-- +-------------------------------+--------------------+-----------------+
-- | 'BLEND_OP_MAX'                | R = max(Rs0,Rd)    | A = max(As0,Ad) |
-- |                               | G = max(Gs0,Gd)    |                 |
-- |                               | B = max(Bs0,Bd)    |                 |
-- +-------------------------------+--------------------+-----------------+
--
-- Basic Blend Operations
--
-- In this table, the following conventions are used:
--
-- -   Rs0, Gs0, Bs0 and As0 represent the first source color R, G, B, and
--     A components, respectively.
--
-- -   Rd, Gd, Bd and Ad represent the R, G, B, and A components of the
--     destination color. That is, the color currently in the corresponding
--     color attachment for this fragment\/sample.
--
-- -   Sr, Sg, Sb and Sa represent the source blend factor R, G, B, and A
--     components, respectively.
--
-- -   Dr, Dg, Db and Da represent the destination blend factor R, G, B,
--     and A components, respectively.
--
-- The blending operation produces a new set of values R, G, B and A, which
-- are written to the framebuffer attachment. If blending is not enabled
-- for this attachment, then R, G, B and A are assigned Rs0, Gs0, Bs0 and
-- As0, respectively.
--
-- If the color attachment is fixed-point, the components of the source and
-- destination values and blend factors are each clamped to [0,1] or [-1,1]
-- respectively for an unsigned normalized or signed normalized color
-- attachment prior to evaluating the blend operations. If the color
-- attachment is floating-point, no clamping occurs.
--
-- = See Also
--
-- 'Vulkan.Core10.Pipeline.PipelineColorBlendAttachmentState'
newtype BlendOp = BlendOp Int32
  deriving newtype (BlendOp -> BlendOp -> Bool
(BlendOp -> BlendOp -> Bool)
-> (BlendOp -> BlendOp -> Bool) -> Eq BlendOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BlendOp -> BlendOp -> Bool
$c/= :: BlendOp -> BlendOp -> Bool
== :: BlendOp -> BlendOp -> Bool
$c== :: BlendOp -> BlendOp -> Bool
Eq, Eq BlendOp
Eq BlendOp =>
(BlendOp -> BlendOp -> Ordering)
-> (BlendOp -> BlendOp -> Bool)
-> (BlendOp -> BlendOp -> Bool)
-> (BlendOp -> BlendOp -> Bool)
-> (BlendOp -> BlendOp -> Bool)
-> (BlendOp -> BlendOp -> BlendOp)
-> (BlendOp -> BlendOp -> BlendOp)
-> Ord BlendOp
BlendOp -> BlendOp -> Bool
BlendOp -> BlendOp -> Ordering
BlendOp -> BlendOp -> BlendOp
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 :: BlendOp -> BlendOp -> BlendOp
$cmin :: BlendOp -> BlendOp -> BlendOp
max :: BlendOp -> BlendOp -> BlendOp
$cmax :: BlendOp -> BlendOp -> BlendOp
>= :: BlendOp -> BlendOp -> Bool
$c>= :: BlendOp -> BlendOp -> Bool
> :: BlendOp -> BlendOp -> Bool
$c> :: BlendOp -> BlendOp -> Bool
<= :: BlendOp -> BlendOp -> Bool
$c<= :: BlendOp -> BlendOp -> Bool
< :: BlendOp -> BlendOp -> Bool
$c< :: BlendOp -> BlendOp -> Bool
compare :: BlendOp -> BlendOp -> Ordering
$ccompare :: BlendOp -> BlendOp -> Ordering
$cp1Ord :: Eq BlendOp
Ord, Ptr b -> Int -> IO BlendOp
Ptr b -> Int -> BlendOp -> IO ()
Ptr BlendOp -> IO BlendOp
Ptr BlendOp -> Int -> IO BlendOp
Ptr BlendOp -> Int -> BlendOp -> IO ()
Ptr BlendOp -> BlendOp -> IO ()
BlendOp -> Int
(BlendOp -> Int)
-> (BlendOp -> Int)
-> (Ptr BlendOp -> Int -> IO BlendOp)
-> (Ptr BlendOp -> Int -> BlendOp -> IO ())
-> (forall b. Ptr b -> Int -> IO BlendOp)
-> (forall b. Ptr b -> Int -> BlendOp -> IO ())
-> (Ptr BlendOp -> IO BlendOp)
-> (Ptr BlendOp -> BlendOp -> IO ())
-> Storable BlendOp
forall b. Ptr b -> Int -> IO BlendOp
forall b. Ptr b -> Int -> BlendOp -> 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 BlendOp -> BlendOp -> IO ()
$cpoke :: Ptr BlendOp -> BlendOp -> IO ()
peek :: Ptr BlendOp -> IO BlendOp
$cpeek :: Ptr BlendOp -> IO BlendOp
pokeByteOff :: Ptr b -> Int -> BlendOp -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> BlendOp -> IO ()
peekByteOff :: Ptr b -> Int -> IO BlendOp
$cpeekByteOff :: forall b. Ptr b -> Int -> IO BlendOp
pokeElemOff :: Ptr BlendOp -> Int -> BlendOp -> IO ()
$cpokeElemOff :: Ptr BlendOp -> Int -> BlendOp -> IO ()
peekElemOff :: Ptr BlendOp -> Int -> IO BlendOp
$cpeekElemOff :: Ptr BlendOp -> Int -> IO BlendOp
alignment :: BlendOp -> Int
$calignment :: BlendOp -> Int
sizeOf :: BlendOp -> Int
$csizeOf :: BlendOp -> Int
Storable, BlendOp
BlendOp -> Zero BlendOp
forall a. a -> Zero a
zero :: BlendOp
$czero :: BlendOp
Zero)

-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_ADD"
pattern $bBLEND_OP_ADD :: BlendOp
$mBLEND_OP_ADD :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_ADD = BlendOp 0
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_SUBTRACT"
pattern $bBLEND_OP_SUBTRACT :: BlendOp
$mBLEND_OP_SUBTRACT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_SUBTRACT = BlendOp 1
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_REVERSE_SUBTRACT"
pattern $bBLEND_OP_REVERSE_SUBTRACT :: BlendOp
$mBLEND_OP_REVERSE_SUBTRACT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_REVERSE_SUBTRACT = BlendOp 2
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_MIN"
pattern $bBLEND_OP_MIN :: BlendOp
$mBLEND_OP_MIN :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_MIN = BlendOp 3
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_MAX"
pattern $bBLEND_OP_MAX :: BlendOp
$mBLEND_OP_MAX :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_MAX = BlendOp 4
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_BLUE_EXT"
pattern $bBLEND_OP_BLUE_EXT :: BlendOp
$mBLEND_OP_BLUE_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_BLUE_EXT = BlendOp 1000148045
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_GREEN_EXT"
pattern $bBLEND_OP_GREEN_EXT :: BlendOp
$mBLEND_OP_GREEN_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_GREEN_EXT = BlendOp 1000148044
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_RED_EXT"
pattern $bBLEND_OP_RED_EXT :: BlendOp
$mBLEND_OP_RED_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_RED_EXT = BlendOp 1000148043
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_INVERT_OVG_EXT"
pattern $bBLEND_OP_INVERT_OVG_EXT :: BlendOp
$mBLEND_OP_INVERT_OVG_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_INVERT_OVG_EXT = BlendOp 1000148042
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_CONTRAST_EXT"
pattern $bBLEND_OP_CONTRAST_EXT :: BlendOp
$mBLEND_OP_CONTRAST_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_CONTRAST_EXT = BlendOp 1000148041
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_MINUS_CLAMPED_EXT"
pattern $bBLEND_OP_MINUS_CLAMPED_EXT :: BlendOp
$mBLEND_OP_MINUS_CLAMPED_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_MINUS_CLAMPED_EXT = BlendOp 1000148040
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_MINUS_EXT"
pattern $bBLEND_OP_MINUS_EXT :: BlendOp
$mBLEND_OP_MINUS_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_MINUS_EXT = BlendOp 1000148039
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_PLUS_DARKER_EXT"
pattern $bBLEND_OP_PLUS_DARKER_EXT :: BlendOp
$mBLEND_OP_PLUS_DARKER_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_PLUS_DARKER_EXT = BlendOp 1000148038
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_PLUS_CLAMPED_ALPHA_EXT"
pattern $bBLEND_OP_PLUS_CLAMPED_ALPHA_EXT :: BlendOp
$mBLEND_OP_PLUS_CLAMPED_ALPHA_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_PLUS_CLAMPED_ALPHA_EXT = BlendOp 1000148037
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_PLUS_CLAMPED_EXT"
pattern $bBLEND_OP_PLUS_CLAMPED_EXT :: BlendOp
$mBLEND_OP_PLUS_CLAMPED_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_PLUS_CLAMPED_EXT = BlendOp 1000148036
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_PLUS_EXT"
pattern $bBLEND_OP_PLUS_EXT :: BlendOp
$mBLEND_OP_PLUS_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_PLUS_EXT = BlendOp 1000148035
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_HSL_LUMINOSITY_EXT"
pattern $bBLEND_OP_HSL_LUMINOSITY_EXT :: BlendOp
$mBLEND_OP_HSL_LUMINOSITY_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_HSL_LUMINOSITY_EXT = BlendOp 1000148034
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_HSL_COLOR_EXT"
pattern $bBLEND_OP_HSL_COLOR_EXT :: BlendOp
$mBLEND_OP_HSL_COLOR_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_HSL_COLOR_EXT = BlendOp 1000148033
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_HSL_SATURATION_EXT"
pattern $bBLEND_OP_HSL_SATURATION_EXT :: BlendOp
$mBLEND_OP_HSL_SATURATION_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_HSL_SATURATION_EXT = BlendOp 1000148032
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_HSL_HUE_EXT"
pattern $bBLEND_OP_HSL_HUE_EXT :: BlendOp
$mBLEND_OP_HSL_HUE_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_HSL_HUE_EXT = BlendOp 1000148031
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_HARDMIX_EXT"
pattern $bBLEND_OP_HARDMIX_EXT :: BlendOp
$mBLEND_OP_HARDMIX_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_HARDMIX_EXT = BlendOp 1000148030
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_PINLIGHT_EXT"
pattern $bBLEND_OP_PINLIGHT_EXT :: BlendOp
$mBLEND_OP_PINLIGHT_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_PINLIGHT_EXT = BlendOp 1000148029
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_LINEARLIGHT_EXT"
pattern $bBLEND_OP_LINEARLIGHT_EXT :: BlendOp
$mBLEND_OP_LINEARLIGHT_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_LINEARLIGHT_EXT = BlendOp 1000148028
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_VIVIDLIGHT_EXT"
pattern $bBLEND_OP_VIVIDLIGHT_EXT :: BlendOp
$mBLEND_OP_VIVIDLIGHT_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_VIVIDLIGHT_EXT = BlendOp 1000148027
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_LINEARBURN_EXT"
pattern $bBLEND_OP_LINEARBURN_EXT :: BlendOp
$mBLEND_OP_LINEARBURN_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_LINEARBURN_EXT = BlendOp 1000148026
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_LINEARDODGE_EXT"
pattern $bBLEND_OP_LINEARDODGE_EXT :: BlendOp
$mBLEND_OP_LINEARDODGE_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_LINEARDODGE_EXT = BlendOp 1000148025
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_INVERT_RGB_EXT"
pattern $bBLEND_OP_INVERT_RGB_EXT :: BlendOp
$mBLEND_OP_INVERT_RGB_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_INVERT_RGB_EXT = BlendOp 1000148024
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_INVERT_EXT"
pattern $bBLEND_OP_INVERT_EXT :: BlendOp
$mBLEND_OP_INVERT_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_INVERT_EXT = BlendOp 1000148023
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_EXCLUSION_EXT"
pattern $bBLEND_OP_EXCLUSION_EXT :: BlendOp
$mBLEND_OP_EXCLUSION_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_EXCLUSION_EXT = BlendOp 1000148022
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_DIFFERENCE_EXT"
pattern $bBLEND_OP_DIFFERENCE_EXT :: BlendOp
$mBLEND_OP_DIFFERENCE_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_DIFFERENCE_EXT = BlendOp 1000148021
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_SOFTLIGHT_EXT"
pattern $bBLEND_OP_SOFTLIGHT_EXT :: BlendOp
$mBLEND_OP_SOFTLIGHT_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_SOFTLIGHT_EXT = BlendOp 1000148020
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_HARDLIGHT_EXT"
pattern $bBLEND_OP_HARDLIGHT_EXT :: BlendOp
$mBLEND_OP_HARDLIGHT_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_HARDLIGHT_EXT = BlendOp 1000148019
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_COLORBURN_EXT"
pattern $bBLEND_OP_COLORBURN_EXT :: BlendOp
$mBLEND_OP_COLORBURN_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_COLORBURN_EXT = BlendOp 1000148018
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_COLORDODGE_EXT"
pattern $bBLEND_OP_COLORDODGE_EXT :: BlendOp
$mBLEND_OP_COLORDODGE_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_COLORDODGE_EXT = BlendOp 1000148017
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_LIGHTEN_EXT"
pattern $bBLEND_OP_LIGHTEN_EXT :: BlendOp
$mBLEND_OP_LIGHTEN_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_LIGHTEN_EXT = BlendOp 1000148016
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_DARKEN_EXT"
pattern $bBLEND_OP_DARKEN_EXT :: BlendOp
$mBLEND_OP_DARKEN_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_DARKEN_EXT = BlendOp 1000148015
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_OVERLAY_EXT"
pattern $bBLEND_OP_OVERLAY_EXT :: BlendOp
$mBLEND_OP_OVERLAY_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_OVERLAY_EXT = BlendOp 1000148014
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_SCREEN_EXT"
pattern $bBLEND_OP_SCREEN_EXT :: BlendOp
$mBLEND_OP_SCREEN_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_SCREEN_EXT = BlendOp 1000148013
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_MULTIPLY_EXT"
pattern $bBLEND_OP_MULTIPLY_EXT :: BlendOp
$mBLEND_OP_MULTIPLY_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_MULTIPLY_EXT = BlendOp 1000148012
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_XOR_EXT"
pattern $bBLEND_OP_XOR_EXT :: BlendOp
$mBLEND_OP_XOR_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_XOR_EXT = BlendOp 1000148011
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_DST_ATOP_EXT"
pattern $bBLEND_OP_DST_ATOP_EXT :: BlendOp
$mBLEND_OP_DST_ATOP_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_DST_ATOP_EXT = BlendOp 1000148010
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_SRC_ATOP_EXT"
pattern $bBLEND_OP_SRC_ATOP_EXT :: BlendOp
$mBLEND_OP_SRC_ATOP_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_SRC_ATOP_EXT = BlendOp 1000148009
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_DST_OUT_EXT"
pattern $bBLEND_OP_DST_OUT_EXT :: BlendOp
$mBLEND_OP_DST_OUT_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_DST_OUT_EXT = BlendOp 1000148008
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_SRC_OUT_EXT"
pattern $bBLEND_OP_SRC_OUT_EXT :: BlendOp
$mBLEND_OP_SRC_OUT_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_SRC_OUT_EXT = BlendOp 1000148007
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_DST_IN_EXT"
pattern $bBLEND_OP_DST_IN_EXT :: BlendOp
$mBLEND_OP_DST_IN_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_DST_IN_EXT = BlendOp 1000148006
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_SRC_IN_EXT"
pattern $bBLEND_OP_SRC_IN_EXT :: BlendOp
$mBLEND_OP_SRC_IN_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_SRC_IN_EXT = BlendOp 1000148005
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_DST_OVER_EXT"
pattern $bBLEND_OP_DST_OVER_EXT :: BlendOp
$mBLEND_OP_DST_OVER_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_DST_OVER_EXT = BlendOp 1000148004
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_SRC_OVER_EXT"
pattern $bBLEND_OP_SRC_OVER_EXT :: BlendOp
$mBLEND_OP_SRC_OVER_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_SRC_OVER_EXT = BlendOp 1000148003
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_DST_EXT"
pattern $bBLEND_OP_DST_EXT :: BlendOp
$mBLEND_OP_DST_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_DST_EXT = BlendOp 1000148002
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_SRC_EXT"
pattern $bBLEND_OP_SRC_EXT :: BlendOp
$mBLEND_OP_SRC_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_SRC_EXT = BlendOp 1000148001
-- No documentation found for Nested "VkBlendOp" "VK_BLEND_OP_ZERO_EXT"
pattern $bBLEND_OP_ZERO_EXT :: BlendOp
$mBLEND_OP_ZERO_EXT :: forall r. BlendOp -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OP_ZERO_EXT = BlendOp 1000148000
{-# complete BLEND_OP_ADD,
             BLEND_OP_SUBTRACT,
             BLEND_OP_REVERSE_SUBTRACT,
             BLEND_OP_MIN,
             BLEND_OP_MAX,
             BLEND_OP_BLUE_EXT,
             BLEND_OP_GREEN_EXT,
             BLEND_OP_RED_EXT,
             BLEND_OP_INVERT_OVG_EXT,
             BLEND_OP_CONTRAST_EXT,
             BLEND_OP_MINUS_CLAMPED_EXT,
             BLEND_OP_MINUS_EXT,
             BLEND_OP_PLUS_DARKER_EXT,
             BLEND_OP_PLUS_CLAMPED_ALPHA_EXT,
             BLEND_OP_PLUS_CLAMPED_EXT,
             BLEND_OP_PLUS_EXT,
             BLEND_OP_HSL_LUMINOSITY_EXT,
             BLEND_OP_HSL_COLOR_EXT,
             BLEND_OP_HSL_SATURATION_EXT,
             BLEND_OP_HSL_HUE_EXT,
             BLEND_OP_HARDMIX_EXT,
             BLEND_OP_PINLIGHT_EXT,
             BLEND_OP_LINEARLIGHT_EXT,
             BLEND_OP_VIVIDLIGHT_EXT,
             BLEND_OP_LINEARBURN_EXT,
             BLEND_OP_LINEARDODGE_EXT,
             BLEND_OP_INVERT_RGB_EXT,
             BLEND_OP_INVERT_EXT,
             BLEND_OP_EXCLUSION_EXT,
             BLEND_OP_DIFFERENCE_EXT,
             BLEND_OP_SOFTLIGHT_EXT,
             BLEND_OP_HARDLIGHT_EXT,
             BLEND_OP_COLORBURN_EXT,
             BLEND_OP_COLORDODGE_EXT,
             BLEND_OP_LIGHTEN_EXT,
             BLEND_OP_DARKEN_EXT,
             BLEND_OP_OVERLAY_EXT,
             BLEND_OP_SCREEN_EXT,
             BLEND_OP_MULTIPLY_EXT,
             BLEND_OP_XOR_EXT,
             BLEND_OP_DST_ATOP_EXT,
             BLEND_OP_SRC_ATOP_EXT,
             BLEND_OP_DST_OUT_EXT,
             BLEND_OP_SRC_OUT_EXT,
             BLEND_OP_DST_IN_EXT,
             BLEND_OP_SRC_IN_EXT,
             BLEND_OP_DST_OVER_EXT,
             BLEND_OP_SRC_OVER_EXT,
             BLEND_OP_DST_EXT,
             BLEND_OP_SRC_EXT,
             BLEND_OP_ZERO_EXT :: BlendOp #-}

instance Show BlendOp where
  showsPrec :: Int -> BlendOp -> ShowS
showsPrec p :: Int
p = \case
    BLEND_OP_ADD -> String -> ShowS
showString "BLEND_OP_ADD"
    BLEND_OP_SUBTRACT -> String -> ShowS
showString "BLEND_OP_SUBTRACT"
    BLEND_OP_REVERSE_SUBTRACT -> String -> ShowS
showString "BLEND_OP_REVERSE_SUBTRACT"
    BLEND_OP_MIN -> String -> ShowS
showString "BLEND_OP_MIN"
    BLEND_OP_MAX -> String -> ShowS
showString "BLEND_OP_MAX"
    BLEND_OP_BLUE_EXT -> String -> ShowS
showString "BLEND_OP_BLUE_EXT"
    BLEND_OP_GREEN_EXT -> String -> ShowS
showString "BLEND_OP_GREEN_EXT"
    BLEND_OP_RED_EXT -> String -> ShowS
showString "BLEND_OP_RED_EXT"
    BLEND_OP_INVERT_OVG_EXT -> String -> ShowS
showString "BLEND_OP_INVERT_OVG_EXT"
    BLEND_OP_CONTRAST_EXT -> String -> ShowS
showString "BLEND_OP_CONTRAST_EXT"
    BLEND_OP_MINUS_CLAMPED_EXT -> String -> ShowS
showString "BLEND_OP_MINUS_CLAMPED_EXT"
    BLEND_OP_MINUS_EXT -> String -> ShowS
showString "BLEND_OP_MINUS_EXT"
    BLEND_OP_PLUS_DARKER_EXT -> String -> ShowS
showString "BLEND_OP_PLUS_DARKER_EXT"
    BLEND_OP_PLUS_CLAMPED_ALPHA_EXT -> String -> ShowS
showString "BLEND_OP_PLUS_CLAMPED_ALPHA_EXT"
    BLEND_OP_PLUS_CLAMPED_EXT -> String -> ShowS
showString "BLEND_OP_PLUS_CLAMPED_EXT"
    BLEND_OP_PLUS_EXT -> String -> ShowS
showString "BLEND_OP_PLUS_EXT"
    BLEND_OP_HSL_LUMINOSITY_EXT -> String -> ShowS
showString "BLEND_OP_HSL_LUMINOSITY_EXT"
    BLEND_OP_HSL_COLOR_EXT -> String -> ShowS
showString "BLEND_OP_HSL_COLOR_EXT"
    BLEND_OP_HSL_SATURATION_EXT -> String -> ShowS
showString "BLEND_OP_HSL_SATURATION_EXT"
    BLEND_OP_HSL_HUE_EXT -> String -> ShowS
showString "BLEND_OP_HSL_HUE_EXT"
    BLEND_OP_HARDMIX_EXT -> String -> ShowS
showString "BLEND_OP_HARDMIX_EXT"
    BLEND_OP_PINLIGHT_EXT -> String -> ShowS
showString "BLEND_OP_PINLIGHT_EXT"
    BLEND_OP_LINEARLIGHT_EXT -> String -> ShowS
showString "BLEND_OP_LINEARLIGHT_EXT"
    BLEND_OP_VIVIDLIGHT_EXT -> String -> ShowS
showString "BLEND_OP_VIVIDLIGHT_EXT"
    BLEND_OP_LINEARBURN_EXT -> String -> ShowS
showString "BLEND_OP_LINEARBURN_EXT"
    BLEND_OP_LINEARDODGE_EXT -> String -> ShowS
showString "BLEND_OP_LINEARDODGE_EXT"
    BLEND_OP_INVERT_RGB_EXT -> String -> ShowS
showString "BLEND_OP_INVERT_RGB_EXT"
    BLEND_OP_INVERT_EXT -> String -> ShowS
showString "BLEND_OP_INVERT_EXT"
    BLEND_OP_EXCLUSION_EXT -> String -> ShowS
showString "BLEND_OP_EXCLUSION_EXT"
    BLEND_OP_DIFFERENCE_EXT -> String -> ShowS
showString "BLEND_OP_DIFFERENCE_EXT"
    BLEND_OP_SOFTLIGHT_EXT -> String -> ShowS
showString "BLEND_OP_SOFTLIGHT_EXT"
    BLEND_OP_HARDLIGHT_EXT -> String -> ShowS
showString "BLEND_OP_HARDLIGHT_EXT"
    BLEND_OP_COLORBURN_EXT -> String -> ShowS
showString "BLEND_OP_COLORBURN_EXT"
    BLEND_OP_COLORDODGE_EXT -> String -> ShowS
showString "BLEND_OP_COLORDODGE_EXT"
    BLEND_OP_LIGHTEN_EXT -> String -> ShowS
showString "BLEND_OP_LIGHTEN_EXT"
    BLEND_OP_DARKEN_EXT -> String -> ShowS
showString "BLEND_OP_DARKEN_EXT"
    BLEND_OP_OVERLAY_EXT -> String -> ShowS
showString "BLEND_OP_OVERLAY_EXT"
    BLEND_OP_SCREEN_EXT -> String -> ShowS
showString "BLEND_OP_SCREEN_EXT"
    BLEND_OP_MULTIPLY_EXT -> String -> ShowS
showString "BLEND_OP_MULTIPLY_EXT"
    BLEND_OP_XOR_EXT -> String -> ShowS
showString "BLEND_OP_XOR_EXT"
    BLEND_OP_DST_ATOP_EXT -> String -> ShowS
showString "BLEND_OP_DST_ATOP_EXT"
    BLEND_OP_SRC_ATOP_EXT -> String -> ShowS
showString "BLEND_OP_SRC_ATOP_EXT"
    BLEND_OP_DST_OUT_EXT -> String -> ShowS
showString "BLEND_OP_DST_OUT_EXT"
    BLEND_OP_SRC_OUT_EXT -> String -> ShowS
showString "BLEND_OP_SRC_OUT_EXT"
    BLEND_OP_DST_IN_EXT -> String -> ShowS
showString "BLEND_OP_DST_IN_EXT"
    BLEND_OP_SRC_IN_EXT -> String -> ShowS
showString "BLEND_OP_SRC_IN_EXT"
    BLEND_OP_DST_OVER_EXT -> String -> ShowS
showString "BLEND_OP_DST_OVER_EXT"
    BLEND_OP_SRC_OVER_EXT -> String -> ShowS
showString "BLEND_OP_SRC_OVER_EXT"
    BLEND_OP_DST_EXT -> String -> ShowS
showString "BLEND_OP_DST_EXT"
    BLEND_OP_SRC_EXT -> String -> ShowS
showString "BLEND_OP_SRC_EXT"
    BLEND_OP_ZERO_EXT -> String -> ShowS
showString "BLEND_OP_ZERO_EXT"
    BlendOp x :: Int32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "BlendOp " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec 11 Int32
x)

instance Read BlendOp where
  readPrec :: ReadPrec BlendOp
readPrec = ReadPrec BlendOp -> ReadPrec BlendOp
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec BlendOp)] -> ReadPrec BlendOp
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("BLEND_OP_ADD", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_ADD)
                            , ("BLEND_OP_SUBTRACT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_SUBTRACT)
                            , ("BLEND_OP_REVERSE_SUBTRACT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_REVERSE_SUBTRACT)
                            , ("BLEND_OP_MIN", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_MIN)
                            , ("BLEND_OP_MAX", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_MAX)
                            , ("BLEND_OP_BLUE_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_BLUE_EXT)
                            , ("BLEND_OP_GREEN_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_GREEN_EXT)
                            , ("BLEND_OP_RED_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_RED_EXT)
                            , ("BLEND_OP_INVERT_OVG_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_INVERT_OVG_EXT)
                            , ("BLEND_OP_CONTRAST_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_CONTRAST_EXT)
                            , ("BLEND_OP_MINUS_CLAMPED_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_MINUS_CLAMPED_EXT)
                            , ("BLEND_OP_MINUS_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_MINUS_EXT)
                            , ("BLEND_OP_PLUS_DARKER_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_PLUS_DARKER_EXT)
                            , ("BLEND_OP_PLUS_CLAMPED_ALPHA_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_PLUS_CLAMPED_ALPHA_EXT)
                            , ("BLEND_OP_PLUS_CLAMPED_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_PLUS_CLAMPED_EXT)
                            , ("BLEND_OP_PLUS_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_PLUS_EXT)
                            , ("BLEND_OP_HSL_LUMINOSITY_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_HSL_LUMINOSITY_EXT)
                            , ("BLEND_OP_HSL_COLOR_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_HSL_COLOR_EXT)
                            , ("BLEND_OP_HSL_SATURATION_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_HSL_SATURATION_EXT)
                            , ("BLEND_OP_HSL_HUE_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_HSL_HUE_EXT)
                            , ("BLEND_OP_HARDMIX_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_HARDMIX_EXT)
                            , ("BLEND_OP_PINLIGHT_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_PINLIGHT_EXT)
                            , ("BLEND_OP_LINEARLIGHT_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_LINEARLIGHT_EXT)
                            , ("BLEND_OP_VIVIDLIGHT_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_VIVIDLIGHT_EXT)
                            , ("BLEND_OP_LINEARBURN_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_LINEARBURN_EXT)
                            , ("BLEND_OP_LINEARDODGE_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_LINEARDODGE_EXT)
                            , ("BLEND_OP_INVERT_RGB_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_INVERT_RGB_EXT)
                            , ("BLEND_OP_INVERT_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_INVERT_EXT)
                            , ("BLEND_OP_EXCLUSION_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_EXCLUSION_EXT)
                            , ("BLEND_OP_DIFFERENCE_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_DIFFERENCE_EXT)
                            , ("BLEND_OP_SOFTLIGHT_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_SOFTLIGHT_EXT)
                            , ("BLEND_OP_HARDLIGHT_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_HARDLIGHT_EXT)
                            , ("BLEND_OP_COLORBURN_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_COLORBURN_EXT)
                            , ("BLEND_OP_COLORDODGE_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_COLORDODGE_EXT)
                            , ("BLEND_OP_LIGHTEN_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_LIGHTEN_EXT)
                            , ("BLEND_OP_DARKEN_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_DARKEN_EXT)
                            , ("BLEND_OP_OVERLAY_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_OVERLAY_EXT)
                            , ("BLEND_OP_SCREEN_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_SCREEN_EXT)
                            , ("BLEND_OP_MULTIPLY_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_MULTIPLY_EXT)
                            , ("BLEND_OP_XOR_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_XOR_EXT)
                            , ("BLEND_OP_DST_ATOP_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_DST_ATOP_EXT)
                            , ("BLEND_OP_SRC_ATOP_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_SRC_ATOP_EXT)
                            , ("BLEND_OP_DST_OUT_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_DST_OUT_EXT)
                            , ("BLEND_OP_SRC_OUT_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_SRC_OUT_EXT)
                            , ("BLEND_OP_DST_IN_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_DST_IN_EXT)
                            , ("BLEND_OP_SRC_IN_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_SRC_IN_EXT)
                            , ("BLEND_OP_DST_OVER_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_DST_OVER_EXT)
                            , ("BLEND_OP_SRC_OVER_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_SRC_OVER_EXT)
                            , ("BLEND_OP_DST_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_DST_EXT)
                            , ("BLEND_OP_SRC_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_SRC_EXT)
                            , ("BLEND_OP_ZERO_EXT", BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlendOp
BLEND_OP_ZERO_EXT)]
                     ReadPrec BlendOp -> ReadPrec BlendOp -> ReadPrec BlendOp
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                     Int -> ReadPrec BlendOp -> ReadPrec BlendOp
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
                       Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "BlendOp")
                       Int32
v <- ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec
                       BlendOp -> ReadPrec BlendOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int32 -> BlendOp
BlendOp Int32
v)))