Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data BaseOutStructure = BaseOutStructure {}
- data BaseInStructure = BaseInStructure {}
- type family Extends (a :: [Type] -> Type) (b :: Type) :: Constraint where ...
- class PeekChain es where
- class PokeChain es where
- type family Chain (xs :: [a]) = (r :: a) | r -> xs where ...
- type family Extendss (p :: [Type] -> Type) (xs :: [Type]) :: Constraint where ...
- data SomeStruct (a :: [Type] -> Type) where
- SomeStruct :: forall a es. (Extendss a es, PokeChain es, Show (Chain es)) => a es -> SomeStruct a
- extendSomeStruct :: (Extensible a, Extends a e, ToCStruct e, Show e) => e -> SomeStruct a -> SomeStruct a
- withSomeStruct :: forall a b. SomeStruct a -> (forall es. (Extendss a es, PokeChain es, Show (Chain es)) => a es -> b) -> b
- withSomeCStruct :: forall a b. (forall es. (Extendss a es, PokeChain es) => ToCStruct (a es)) => SomeStruct a -> (forall es. (Extendss a es, PokeChain es) => Ptr (a es) -> IO b) -> IO b
- peekSomeCStruct :: forall a. (Extensible a, forall es. (Extendss a es, PeekChain es) => FromCStruct (a es)) => Ptr (SomeStruct a) -> IO (SomeStruct a)
- pokeSomeCStruct :: (forall es. (Extendss a es, PokeChain es) => ToCStruct (a es)) => Ptr (SomeStruct a) -> SomeStruct a -> IO b -> IO b
- forgetExtensions :: Ptr (a es) -> Ptr (SomeStruct a)
- class Extensible (a :: [Type] -> Type) where
- pattern (::&) :: Extensible a => a es' -> Chain es -> a es
- pattern (:&) :: e -> Chain es -> Chain (e ': es)
Documentation
data BaseOutStructure Source #
VkBaseOutStructure - Base structure for a read-only pointer chain
Description
BaseOutStructure
can be used to facilitate iterating through a
structure pointer chain that returns data back to the application.
See Also
VK_VERSION_1_0,
BaseOutStructure
, StructureType
,
getPipelinePropertiesEXT
BaseOutStructure | |
|
Instances
data BaseInStructure Source #
VkBaseInStructure - Base structure for a read-only pointer chain
Description
BaseInStructure
can be used to facilitate iterating through a
read-only structure pointer chain.
See Also
BaseInStructure | |
|
Instances
type family Extends (a :: [Type] -> Type) (b :: Type) :: Constraint where ... Source #
data SomeStruct (a :: [Type] -> Type) where Source #
SomeStruct :: forall a es. (Extendss a es, PokeChain es, Show (Chain es)) => a es -> SomeStruct a |
Instances
(forall (es :: [TYPE LiftedRep]). Show (Chain es) => Show (a es)) => Show (SomeStruct a) Source # | |
Defined in Vulkan.CStruct.Extends showsPrec :: Int -> SomeStruct a -> ShowS # show :: SomeStruct a -> String # showList :: [SomeStruct a] -> ShowS # | |
Zero (a ('[] :: [Type])) => Zero (SomeStruct a) Source # | The constraint is so on this instance to encourage type inference |
Defined in Vulkan.CStruct.Extends zero :: SomeStruct a Source # |
extendSomeStruct :: (Extensible a, Extends a e, ToCStruct e, Show e) => e -> SomeStruct a -> SomeStruct a Source #
Add an extension to the beginning of the struct chain
This can be used to optionally extend structs based on some condition (for example, an extension or layer being available)
withSomeStruct :: forall a b. SomeStruct a -> (forall es. (Extendss a es, PokeChain es, Show (Chain es)) => a es -> b) -> b Source #
Consume a SomeStruct
value
withSomeCStruct :: forall a b. (forall es. (Extendss a es, PokeChain es) => ToCStruct (a es)) => SomeStruct a -> (forall es. (Extendss a es, PokeChain es) => Ptr (a es) -> IO b) -> IO b Source #
Write the C representation of some extended a
and use the pointer,
the pointer must not be returned from the continuation.
peekSomeCStruct :: forall a. (Extensible a, forall es. (Extendss a es, PeekChain es) => FromCStruct (a es)) => Ptr (SomeStruct a) -> IO (SomeStruct a) Source #
Given a pointer to a struct with an unknown chain, peek the struct and its chain.
:: (forall es. (Extendss a es, PokeChain es) => ToCStruct (a es)) | |
=> Ptr (SomeStruct a) | Pointer to some memory at least the size of the head of the struct chain. |
-> SomeStruct a | The struct to poke |
-> IO b | Computation to run while the poked tail is valid |
-> IO b |
Given some memory for the head of the chain, allocate and poke the tail and run an action.
forgetExtensions :: Ptr (a es) -> Ptr (SomeStruct a) Source #
Forget which extensions a pointed-to struct has by casting the pointer
class Extensible (a :: [Type] -> Type) where Source #
extensibleTypeName :: String Source #
For error reporting an invalid extension
getNext :: a es -> Chain es Source #
setNext :: a ds -> Chain es -> a es Source #
extends :: forall e b proxy. Typeable e => proxy e -> (Extends a e => b) -> Maybe b Source #
Instances
pattern (::&) :: Extensible a => a es' -> Chain es -> a es infix 6 Source #
A pattern synonym to separate the head of a struct chain from the
tail, use in conjunction with :&
to extract several members.
Head{..} ::& () <- returningNoTail a b c -- Equivalent to Head{..} <- returningNoTail @'[] a b c
Head{..} ::& Foo{..} :& Bar{..} :& () <- returningWithTail a b c
myFun (Head{..} :&& Foo{..} :& ())