{-# LINE 1 "src/Gpu/Vulkan/Pipeline/ViewportState/Middle/Internal.hsc" #-} {-# LANGUAGE ImportQualifiedPost #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE BlockArguments #-} {-# LANGUAGE MonoLocalBinds #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE FlexibleContexts, FlexibleInstances, UndecidableInstances #-} {-# LANGUAGE PatternSynonyms, ViewPatterns #-} {-# LANGUAGE StandaloneDeriving, GeneralizedNewtypeDeriving #-} {-# OPTIONS_GHC -Wall -fno-warn-tabs #-} module Gpu.Vulkan.Pipeline.ViewportState.Middle.Internal 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.Default import Data.Bits import Data.Word import Gpu.Vulkan.Core import qualified Gpu.Vulkan.Pipeline.ViewportState.Core as C enum "CreateFlags" ''Word32 {-# LINE 31 "src/Gpu/Vulkan/Pipeline/ViewportState/Middle/Internal.hsc" #-} [''Show, ''Eq, ''Storable, ''Bits] [] 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 -> [Viewport] createInfoViewports :: [Viewport], forall (mn :: Maybe (*)). CreateInfo mn -> [Rect2d] createInfoScissors :: [Rect2d] } deriving instance Show (TMaybe.M mn) => Show (CreateInfo mn) instance Default (CreateInfo 'Nothing) where def :: CreateInfo 'Nothing def = CreateInfo { createInfoNext :: M 'Nothing createInfoNext = M 'Nothing TMaybe.N, createInfoFlags :: CreateFlags createInfoFlags = CreateFlags forall a. Bits a => a zeroBits, createInfoViewports :: [Viewport] createInfoViewports = [], createInfoScissors :: [Rect2d] createInfoScissors = [] } 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, createInfoViewports :: forall (mn :: Maybe (*)). CreateInfo mn -> [Viewport] createInfoViewports = ([Viewport] -> Int forall a. [a] -> Int forall (t :: * -> *) a. Foldable t => t a -> Int length ([Viewport] -> Int) -> ([Viewport] -> [Viewport]) -> [Viewport] -> (Int, [Viewport]) 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') &&& [Viewport] -> [Viewport] forall a. a -> a id) -> (Int vpc, [Viewport] vps), createInfoScissors :: forall (mn :: Maybe (*)). CreateInfo mn -> [Rect2d] createInfoScissors = ([Rect2d] -> Int forall a. [a] -> Int forall (t :: * -> *) a. Foldable t => t a -> Int length ([Rect2d] -> Int) -> ([Rect2d] -> [Rect2d]) -> [Rect2d] -> (Int, [Rect2d]) 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') &&& [Rect2d] -> [Rect2d] forall a. a -> a id) -> (Int scc, [Rect2d] scs) } 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 Viewport -> IO a) -> IO a forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b allocaArray Int vpc \Ptr Viewport pvps -> Ptr Viewport -> [Viewport] -> IO () forall a. Storable a => Ptr a -> [a] -> IO () pokeArray Ptr Viewport pvps [Viewport] vps 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 >> Int -> (Ptr Rect2d -> IO a) -> IO a forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b allocaArray Int scc \Ptr Rect2d pscs -> Ptr Rect2d -> [Rect2d] -> IO () forall a. Storable a => Ptr a -> [a] -> IO () pokeArray Ptr Rect2d pscs [Rect2d] scs 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, createInfoViewportCount :: Word32 C.createInfoViewportCount = Int -> Word32 forall a b. (Integral a, Num b) => a -> b fromIntegral Int vpc, createInfoPViewports :: Ptr Viewport C.createInfoPViewports = Ptr Viewport pvps, createInfoScissorCount :: Word32 C.createInfoScissorCount = Int -> Word32 forall a b. (Integral a, Num b) => a -> b fromIntegral Int scc, createInfoPScissors :: Ptr Rect2d C.createInfoPScissors = Ptr Rect2d pscs } 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