{-# LINE 1 "src/Gpu/Vulkan/Pipeline/InputAssemblyState/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.InputAssemblyState.Middle.Internal ( CreateInfo(..), CreateFlags, createInfoToCore ) where import Foreign.Ptr import Foreign.Storable import Foreign.Storable.PeekPoke import Foreign.C.Enum import Data.TypeLevel.Maybe qualified as TMaybe import Data.Bits import Data.Word import Gpu.Vulkan.Base.Middle.Internal import Gpu.Vulkan.Enum import qualified Gpu.Vulkan.Pipeline.InputAssemblyState.Core as C enum "CreateFlags" ''Word32 {-# LINE 30 "src/Gpu/Vulkan/Pipeline/InputAssemblyState/Middle/Internal.hsc" #-} [''Show, ''Eq, ''Storable, ''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 -> PrimitiveTopology createInfoTopology :: PrimitiveTopology, forall (mn :: Maybe (*)). CreateInfo mn -> Bool createInfoPrimitiveRestartEnable :: Bool } 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, createInfoTopology :: forall (mn :: Maybe (*)). CreateInfo mn -> PrimitiveTopology createInfoTopology = PrimitiveTopology Word32 tplg, createInfoPrimitiveRestartEnable :: forall (mn :: Maybe (*)). CreateInfo mn -> Bool createInfoPrimitiveRestartEnable = Bool pre } 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') -> let ci :: CreateInfo ci = C.CreateInfo { createInfoSType :: () C.createInfoSType = (), createInfoPNext :: Ptr () C.createInfoPNext = Ptr () pnxt', createInfoFlags :: Word32 C.createInfoFlags = Word32 flgs, createInfoTopology :: Word32 C.createInfoTopology = Word32 tplg, createInfoPrimitiveRestartEnable :: Word32 C.createInfoPrimitiveRestartEnable = Bool -> Word32 boolToBool32 Bool pre } 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