| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Capnp.GenHelpers.New
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 mut a -> m (Raw mut b)
 - 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 ('Mut s) a)
 - parseField :: (IsStruct a, Parse b bp, ReadCtx m 'Const) => Field k a b -> Raw 'Const a -> m bp
 - encodeField :: forall a b m s bp. (IsStruct a, Parse b bp, RWCtx m s) => Field 'Slot a b -> bp -> Raw ('Mut s) a -> m ()
 - encodeVariant :: forall a b m s bp. (HasUnion a, Parse b bp, RWCtx m s) => Variant 'Slot a b -> bp -> Raw ('Mut s) a -> m ()
 - initVariant :: forall a b m s. (HasUnion a, RWCtx m s) => Variant 'Group a b -> Raw ('Mut s) a -> m (Raw ('Mut s) b)
 - unionWhich :: forall a mut m. (ReadCtx m mut, HasUnion a) => Raw mut (Which a) -> m (RawWhich mut a)
 - readField :: forall k a b mut m. (IsStruct a, ReadCtx m mut) => Field k a b -> Raw mut a -> m (Raw mut b)
 - structUnion :: HasUnion a => Raw mut a -> Raw mut (Which a)
 - unionStruct :: HasUnion a => Raw mut (Which a) -> Raw mut a
 - parseEnum :: (ReprFor a ~ 'Data 'Sz16, Enum a, Applicative m) => Raw 'Const a -> m a
 - encodeEnum :: forall a m s. (ReprFor a ~ 'Data 'Sz16, Enum a, RWCtx m s) => Message ('Mut s) -> a -> m (Raw ('Mut s) a)
 - parseCap :: (IsCap a, ReadCtx m 'Const) => Raw 'Const a -> m (Client a)
 - encodeCap :: (IsCap a, RWCtx m s) => Message ('Mut s) -> Client a -> m (Raw ('Mut s) a)
 - getPtrConst :: FromPtr 'Const a => ByteString -> a
 - module Capnp.Fields
 - module Capnp.Repr.Methods
 - module Capnp.New.Rpc.Server
 - buildCallHandler :: [(Word64, [UntypedMethodHandler])] -> CallHandler
 - 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 mut a -> m (Raw mut b) 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 ('Mut s) a) Source #
parseField :: (IsStruct a, Parse b bp, ReadCtx m 'Const) => Field k a b -> Raw 'Const a -> m bp Source #
parse a struct's field and return its parsed form.
encodeField :: forall a b m s bp. (IsStruct a, Parse b bp, RWCtx m s) => Field 'Slot a b -> bp -> Raw ('Mut s) a -> m () Source #
Marshal a parsed value into a struct's field.
encodeVariant :: forall a b m s bp. (HasUnion a, Parse b bp, RWCtx m s) => Variant 'Slot a b -> bp -> Raw ('Mut s) a -> m () Source #
Set the struct's anonymous union to the given variant, marshalling
 the supplied value into the message to be its argument. Not applicable
 for variants whose argument is a group; use initVariant instead.
initVariant :: forall a b m s. (HasUnion a, RWCtx m s) => Variant 'Group a b -> Raw ('Mut s) a -> m (Raw ('Mut s) b) Source #
Set the struct's anonymous union to the given variant, returning
 the variant's argument, which must be a group (for non-group fields,
 use setVariant or encodeVariant.
unionWhich :: forall a mut m. (ReadCtx m mut, HasUnion a) => Raw mut (Which a) -> m (RawWhich mut a) Source #
Get a non-opaque view on the anonymous union, which can be used to pattern match on.
readField :: forall k a b mut m. (IsStruct a, ReadCtx m mut) => Field k a b -> Raw mut a -> m (Raw mut b) Source #
Read the value of a field of a struct.
structUnion :: HasUnion a => Raw mut a -> Raw mut (Which a) Source #
Get the anonymous union for a struct.
unionStruct :: HasUnion a => Raw mut (Which a) -> Raw mut a Source #
Get the struct enclosing an anonymous union.
encodeEnum :: forall a m s. (ReprFor a ~ 'Data 'Sz16, Enum a, RWCtx m s) => Message ('Mut s) -> a -> m (Raw ('Mut s) a) Source #
getPtrConst :: FromPtr 'Const a => ByteString -> a 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.
module Capnp.Fields
module Capnp.Repr.Methods
module Capnp.New.Rpc.Server
buildCallHandler :: [(Word64, [UntypedMethodHandler])] -> CallHandler Source #
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 EitherProxy
>>>Proxy :: Proxy FunctorProxy
>>>Proxy :: Proxy complicatedStructureProxy
Constructors
| Proxy | 
Instances
| Generic1 (Proxy :: k -> Type) | Since: base-4.6.0.0  | 
| Monad (Proxy :: Type -> Type) | Since: base-4.7.0.0  | 
| Functor (Proxy :: Type -> Type) | Since: base-4.7.0.0  | 
| Applicative (Proxy :: Type -> Type) | Since: base-4.7.0.0  | 
| Foldable (Proxy :: Type -> Type) | Since: base-4.7.0.0  | 
Defined in Data.Foldable Methods 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 #  | |
| Traversable (Proxy :: Type -> Type) | Since: base-4.7.0.0  | 
| 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 -> Type) | Since: base-4.9.0.0  | 
| Alternative (Proxy :: Type -> Type) | Since: base-4.9.0.0  | 
| MonadPlus (Proxy :: Type -> Type) | Since: base-4.9.0.0  | 
| Hashable1 (Proxy :: Type -> Type) | |
Defined in Data.Hashable.Class  | |
| Bounded (Proxy t) | Since: base-4.7.0.0  | 
| Enum (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  | 
| Read (Proxy t) | Since: base-4.7.0.0  | 
| Show (Proxy s) | Since: base-4.7.0.0  | 
| Ix (Proxy s) | Since: base-4.7.0.0  | 
Defined in Data.Proxy  | |
| Generic (Proxy t) | Since: base-4.6.0.0  | 
| Semigroup (Proxy s) | Since: base-4.9.0.0  | 
| Monoid (Proxy s) | Since: base-4.7.0.0  | 
| Hashable (Proxy a) | |
Defined in Data.Hashable.Class  | |
| type Rep1 (Proxy :: k -> Type) | |
| type Rep (Proxy t) | |