Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- dataField :: forall b a sz. (ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) => BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b
- ptrField :: forall a b. IsPtr b => Word16 -> Field 'Slot a b
- groupField :: ReprFor b ~ 'Ptr ('Just 'Struct) => Field 'Group a b
- voidField :: ReprFor b ~ 'Data 'Sz0 => Field 'Slot a b
- readVariant :: forall k a b mut m. (IsStruct a, ReadCtx m mut) => Variant k a b -> Raw a mut -> m (Raw b mut)
- data Mutability
- type TypeParam a = (IsPtr a, Parse a (Parsed a))
- newStruct :: forall a m s. (RWCtx m s, TypedStruct a) => () -> Message ('Mut s) -> m (Raw a ('Mut s))
- parseEnum :: (ReprFor a ~ 'Data 'Sz16, Enum a, Applicative m) => Raw a 'Const -> m a
- encodeEnum :: forall a m s. (ReprFor a ~ 'Data 'Sz16, Enum a, RWCtx m s) => Message ('Mut s) -> a -> m (Raw a ('Mut s))
- getPtrConst :: forall a. IsPtr a => ByteString -> Raw a 'Const
- data ByteString
- module Capnp.Fields
- module Capnp.Accessors
- data Proxy (t :: k) = Proxy
Documentation
dataField :: forall b a sz. (ReprFor b ~ 'Data sz, IsWord (UntypedData sz)) => BitCount -> Word16 -> BitCount -> Word64 -> Field 'Slot a b Source #
readVariant :: forall k a b mut m. (IsStruct a, ReadCtx m mut) => Variant k a b -> Raw a mut -> m (Raw b mut) Source #
Like readField
, but accepts a variant. Warning: *DOES NOT CHECK* that the
variant is the one that is set. This should only be used by generated code.
data Mutability Source #
Mutability
is used as a type parameter (with the DataKinds extension)
to indicate the mutability of some values in this library; Const
denotes
an immutable value, while
denotes a value that can be mutated
in the scope of the state token Mut
ss
.
type TypeParam a = (IsPtr a, Parse a (Parsed a)) Source #
Constraints needed for a
to be a capnproto type parameter.
newStruct :: forall a m s. (RWCtx m s, TypedStruct a) => () -> Message ('Mut s) -> m (Raw a ('Mut s)) Source #
encodeEnum :: forall a m s. (ReprFor a ~ 'Data 'Sz16, Enum a, RWCtx m s) => Message ('Mut s) -> a -> m (Raw a ('Mut s)) Source #
getPtrConst :: forall a. IsPtr a => ByteString -> Raw a 'Const Source #
Get a pointer from a ByteString, where the root object is a struct with
one pointer, which is the pointer we will retrieve. This is only safe for
trusted inputs; it reads the message with a traversal limit of maxBound
(and so is suseptable to denial of service attacks), and it calls error
if decoding is not successful.
The purpose of this is for defining constants of pointer type from a schema.
data ByteString #
A space-efficient representation of a Word8
vector, supporting many
efficient operations.
A ByteString
contains 8-bit bytes, or by using the operations from
Data.ByteString.Char8 it can be interpreted as containing 8-bit
characters.
Instances
module Capnp.Fields
module Capnp.Accessors
Re-exports from the standard library.
Proxy
is a type that holds no data, but has a phantom parameter of
arbitrary type (or even kind). Its use is to provide type information, even
though there is no value available of that type (or it may be too costly to
create one).
Historically,
is a safer alternative to the
Proxy
:: Proxy
a
idiom.undefined
:: a
>>>
Proxy :: Proxy (Void, Int -> Int)
Proxy
Proxy can even hold types of higher kinds,
>>>
Proxy :: Proxy Either
Proxy
>>>
Proxy :: Proxy Functor
Proxy
>>>
Proxy :: Proxy complicatedStructure
Proxy
Instances
Generic1 (Proxy :: k -> Type) | |
Foldable (Proxy :: TYPE LiftedRep -> Type) | Since: base-4.7.0.0 |
Defined in Data.Foldable fold :: Monoid m => Proxy m -> m # foldMap :: Monoid m => (a -> m) -> Proxy a -> m # foldMap' :: Monoid m => (a -> m) -> Proxy a -> m # foldr :: (a -> b -> b) -> b -> Proxy a -> b # foldr' :: (a -> b -> b) -> b -> Proxy a -> b # foldl :: (b -> a -> b) -> b -> Proxy a -> b # foldl' :: (b -> a -> b) -> b -> Proxy a -> b # foldr1 :: (a -> a -> a) -> Proxy a -> a # foldl1 :: (a -> a -> a) -> Proxy a -> a # elem :: Eq a => a -> Proxy a -> Bool # maximum :: Ord a => Proxy a -> a # minimum :: Ord a => Proxy a -> a # | |
Eq1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Ord1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Show1 (Proxy :: TYPE LiftedRep -> Type) | Since: base-4.9.0.0 |
Traversable (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Alternative (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Applicative (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Functor (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Monad (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
MonadPlus (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Hashable1 (Proxy :: Type -> Type) | |
Defined in Data.Hashable.Class | |
Monoid (Proxy s) | Since: base-4.7.0.0 |
Semigroup (Proxy s) | Since: base-4.9.0.0 |
Bounded (Proxy t) | Since: base-4.7.0.0 |
Enum (Proxy s) | Since: base-4.7.0.0 |
Generic (Proxy t) | |
Ix (Proxy s) | Since: base-4.7.0.0 |
Defined in Data.Proxy | |
Read (Proxy t) | Since: base-4.7.0.0 |
Show (Proxy s) | Since: base-4.7.0.0 |
Eq (Proxy s) | Since: base-4.7.0.0 |
Ord (Proxy s) | Since: base-4.7.0.0 |
Hashable (Proxy a) | |
Defined in Data.Hashable.Class | |
type Rep1 (Proxy :: k -> Type) | Since: base-4.6.0.0 |
type Rep (Proxy t) | Since: base-4.6.0.0 |