{-# LINE 1 "src/Gpu/Vulkan/Pipeline/DynamicState/Middle/Internal.hsc" #-} {-# LANGUAGE ImportQualifiedPost #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE BlockArguments #-} {-# LANGUAGE MonoLocalBinds #-} {-# LANGUAGE FlexibleContexts, UndecidableInstances #-} {-# LANGUAGE PatternSynonyms, ViewPatterns #-} {-# LANGUAGE StandaloneDeriving #-} {-# OPTIONS_GHC -Wall -fno-warn-tabs #-} module Gpu.Vulkan.Pipeline.DynamicState.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.Word import Gpu.Vulkan.Enum import qualified Gpu.Vulkan.Pipeline.DynamicState.Core as C enum "CreateFlags" ''Word32 {-# LINE 30 "src/Gpu/Vulkan/Pipeline/DynamicState/Middle/Internal.hsc" #-} [''Show, ''Storable] [("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 -> [DynamicState] createInfoDynamicStates :: [DynamicState] } 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, createInfoDynamicStates :: forall (mn :: Maybe (*)). CreateInfo mn -> [DynamicState] createInfoDynamicStates = ( [DynamicState] -> Int forall a. [a] -> Int forall (t :: * -> *) a. Foldable t => t a -> Int length ([DynamicState] -> Int) -> ([DynamicState] -> [Word32]) -> [DynamicState] -> (Int, [Word32]) 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') &&& ((\(DynamicState Word32 ds) -> Word32 ds) (DynamicState -> Word32) -> [DynamicState] -> [Word32] forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$>) ) -> (Int dsc, [Word32] dss) } 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 Word32 -> IO a) -> IO a forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b allocaArray Int dsc \Ptr Word32 pdss -> Ptr Word32 -> [Word32] -> IO () forall a. Storable a => Ptr a -> [a] -> IO () pokeArray Ptr Word32 pdss [Word32] dss 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, createInfoDynamicStateCount :: Word32 C.createInfoDynamicStateCount = Int -> Word32 forall a b. (Integral a, Num b) => a -> b fromIntegral Int dsc, createInfoPDynamicStates :: Ptr Word32 C.createInfoPDynamicStates = Ptr Word32 pdss } 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