| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Graphics.Vulkan.CStruct.Extends
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
 
- withSomeCStruct :: forall a b. (forall 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. 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- extensibleType :: StructureType
- getNext :: a es -> Chain es
- setNext :: a ds -> Chain es -> a es
- extends :: forall e b proxy. Typeable e => proxy e -> (Extends a e => b) -> Maybe b
 
- 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
Constructors
| BaseOutStructure | |
| Fields 
 | |
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
Constructors
| BaseInStructure | |
| Fields 
 | |
Instances
type family Extends (a :: [Type] -> Type) (b :: Type) :: Constraint where ... Source #
Equations
data SomeStruct (a :: [Type] -> Type) where Source #
Constructors
| SomeStruct :: forall a es. (Extendss a es, PokeChain es, Show (Chain es)) => a es -> SomeStruct a | 
Instances
| (forall (es :: [Type]). Show (Chain es) => Show (a es)) => Show (SomeStruct a) Source # | |
| Defined in Graphics.Vulkan.CStruct.Extends Methods showsPrec :: Int -> SomeStruct a -> ShowS # show :: SomeStruct a -> String # showList :: [SomeStruct a] -> ShowS # | |
| Zero (a ([] :: [Type])) => Zero (SomeStruct a) Source # | |
| Defined in Graphics.Vulkan.CStruct.Extends Methods zero :: SomeStruct a Source # | |
withSomeCStruct :: forall a b. (forall es. PokeChain es => ToCStruct (a es)) => SomeStruct a -> (forall es. (Extendss a es, PokeChain es) => Ptr (a es) -> IO b) -> IO b Source #
peekSomeCStruct :: forall a. (Extensible a, forall es. (Extendss a es, PeekChain es) => FromCStruct (a es)) => Ptr (SomeStruct a) -> IO (SomeStruct a) Source #
pokeSomeCStruct :: (forall es. PokeChain es => ToCStruct (a es)) => Ptr (SomeStruct a) -> SomeStruct a -> IO b -> IO b Source #
forgetExtensions :: Ptr (a es) -> Ptr (SomeStruct a) Source #
class Extensible (a :: [Type] -> Type) where Source #
Methods
extensibleType :: StructureType Source #
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 infixr 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{..} :& ())