{-# LINE 1 "src/Gpu/Vulkan/Pipeline/ColorBlendState/Middle/Internal.hsc" #-} {-# LANGUAGE ImportQualifiedPost #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE BlockArguments #-} {-# LANGUAGE MonoLocalBinds #-} {-# LANGUAGE FlexibleContexts, UndecidableInstances #-} {-# LANGUAGE PatternSynonyms, ViewPatterns #-} {-# LANGUAGE StandaloneDeriving, GeneralizedNewtypeDeriving #-} {-# OPTIONS_GHC -Wall -fno-warn-tabs #-} module Gpu.Vulkan.Pipeline.ColorBlendState.Middle.Internal ( CreateInfo(..), CreateFlags, createInfoToCore ) where import Foreign.Ptr import Foreign.Marshal.Array import Foreign.Storable import Foreign.Storable.PeekPoke import Foreign.C.Enum import Control.Arrow import Data.TypeLevel.Maybe qualified as TMaybe import Data.Bits import Data.Word import Data.Color import Gpu.Vulkan.Enum import Gpu.Vulkan.Base.Middle.Internal import qualified Gpu.Vulkan.Pipeline.ColorBlendAttachment.Middle.Internal as ColorBlendAttachment import qualified Gpu.Vulkan.Pipeline.ColorBlendState.Core as C enum "CreateFlags" ''Word32 {-# LINE 35 "src/Gpu/Vulkan/Pipeline/ColorBlendState/Middle/Internal.hsc" #-} [''Show, ''Storable, ''Eq, ''Bits] [("CreateFlagsZero", 0)] data CreateInfo mn = CreateInfo { forall (mn :: Maybe (*)). CreateInfo mn -> M mn createInfoNext :: TMaybe.M mn, forall (mn :: Maybe (*)). CreateInfo mn -> CreateFlags createInfoFlags :: CreateFlags, forall (mn :: Maybe (*)). CreateInfo mn -> Bool createInfoLogicOpEnable :: Bool, forall (mn :: Maybe (*)). CreateInfo mn -> LogicOp createInfoLogicOp :: LogicOp, forall (mn :: Maybe (*)). CreateInfo mn -> [State] createInfoAttachments :: [ColorBlendAttachment.State], forall (mn :: Maybe (*)). CreateInfo mn -> Rgba Float createInfoBlendConstants :: Rgba Float } deriving instance Show (TMaybe.M mn) => Show (CreateInfo mn) createInfoToCore :: WithPoked (TMaybe.M mn) => CreateInfo mn -> (Ptr C.CreateInfo -> IO a) -> IO () createInfoToCore :: forall (mn :: Maybe (*)) a. WithPoked (M mn) => CreateInfo mn -> (Ptr CreateInfo -> IO a) -> IO () createInfoToCore CreateInfo { createInfoNext :: forall (mn :: Maybe (*)). CreateInfo mn -> M mn createInfoNext = M mn mnxt, createInfoFlags :: forall (mn :: Maybe (*)). CreateInfo mn -> CreateFlags createInfoFlags = CreateFlags Word32 flgs, createInfoLogicOpEnable :: forall (mn :: Maybe (*)). CreateInfo mn -> Bool createInfoLogicOpEnable = Bool -> Word32 boolToBool32 -> Word32 loe, createInfoLogicOp :: forall (mn :: Maybe (*)). CreateInfo mn -> LogicOp createInfoLogicOp = LogicOp Word32 lo, createInfoAttachments :: forall (mn :: Maybe (*)). CreateInfo mn -> [State] createInfoAttachments = [State] -> Int forall a. [a] -> Int forall (t :: * -> *) a. Foldable t => t a -> Int length ([State] -> Int) -> ([State] -> [State]) -> [State] -> (Int, [State]) forall b c c'. (b -> c) -> (b -> c') -> b -> (c, c') forall (a :: * -> * -> *) b c c'. Arrow a => a b c -> a b c' -> a b (c, c') &&& (State -> State ColorBlendAttachment.stateToCore (State -> State) -> [State] -> [State] forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$>) -> (Int ac, [State] as), createInfoBlendConstants :: forall (mn :: Maybe (*)). CreateInfo mn -> Rgba Float createInfoBlendConstants = RgbaDouble Float r Float g Float b Float a } Ptr CreateInfo -> IO a f = M mn -> (forall s. PtrS s (M mn) -> IO ()) -> IO () forall a b. WithPoked a => a -> (forall s. PtrS s a -> IO b) -> IO b forall b. M mn -> (forall s. PtrS s (M mn) -> IO b) -> IO b withPoked' M mn mnxt \PtrS s (M mn) pnxt -> PtrS s (M mn) -> (Ptr (M mn) -> IO a) -> IO () forall s a b. PtrS s a -> (Ptr a -> IO b) -> IO () withPtrS PtrS s (M mn) pnxt \(Ptr (M mn) -> Ptr () forall a b. Ptr a -> Ptr b castPtr -> Ptr () pnxt') -> Int -> (Ptr State -> IO a) -> IO a forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b allocaArray Int ac \Ptr State pas -> Ptr State -> [State] -> IO () forall a. Storable a => Ptr a -> [a] -> IO () pokeArray Ptr State pas [State] as IO () -> IO a -> IO a forall a b. IO a -> IO b -> IO b forall (m :: * -> *) a b. Monad m => m a -> m b -> m b >> let ci :: CreateInfo ci = C.CreateInfo { createInfoSType :: () C.createInfoSType = (), createInfoPNext :: Ptr () C.createInfoPNext = Ptr () pnxt', createInfoFlags :: Word32 C.createInfoFlags = Word32 flgs, createInfoLogicOpEnable :: Word32 C.createInfoLogicOpEnable = Word32 loe, createInfoLogicOp :: Word32 C.createInfoLogicOp = Word32 lo, createInfoAttachmentCount :: Word32 C.createInfoAttachmentCount = Int -> Word32 forall a b. (Integral a, Num b) => a -> b fromIntegral Int ac, createInfoPAttachments :: Ptr State C.createInfoPAttachments = Ptr State pas, createInfoBlendConstants :: ListFloat C.createInfoBlendConstants = [Float r, Float g, Float b, Float a] } in CreateInfo -> (Ptr CreateInfo -> IO a) -> IO a forall a b. Pokable a => a -> (Ptr a -> IO b) -> IO b withPoked CreateInfo ci Ptr CreateInfo -> IO a f