| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Capnp
Description
Synopsis
- data LimitT m a
- class Monad m => MonadLimit m where
- runLimitT :: MonadThrow m => WordCount -> LimitT m a -> m (a, WordCount)
- evalLimitT :: MonadThrow m => WordCount -> LimitT m a -> m a
- execLimitT :: MonadThrow m => WordCount -> LimitT m a -> m WordCount
- defaultLimit :: WordCount
- newtype Client a = Client Client
- newtype Pipeline a = Pipeline Pipeline
- hPutMsg :: Handle -> Message 'Const -> IO ()
- putMsg :: Message 'Const -> IO ()
- hGetMsg :: Handle -> WordCount -> IO (Message 'Const)
- getMsg :: WordCount -> IO (Message 'Const)
- structPtrs :: Parsed AnyStruct -> Vector (Maybe (Parsed AnyPointer))
- structData :: Parsed AnyStruct -> Vector Word64
- ListStruct :: ParsedList (Parsed AnyStruct) %1 -> Parsed AnyList
- List64 :: ParsedList Word64 %1 -> Parsed AnyList
- List32 :: ParsedList Word32 %1 -> Parsed AnyList
- List16 :: ParsedList Word16 %1 -> Parsed AnyList
- List8 :: ParsedList Word8 %1 -> Parsed AnyList
- List1 :: ParsedList Bool %1 -> Parsed AnyList
- List0 :: ParsedList () %1 -> Parsed AnyList
- PtrStruct :: Parsed AnyStruct %1 -> Parsed AnyPointer
- PtrList :: Parsed AnyList %1 -> Parsed AnyPointer
- PtrCap :: Client %1 -> Parsed AnyPointer
- Struct :: Vector Word64 %1 -> Vector (Maybe (Parsed AnyPointer)) %1 -> Parsed AnyStruct
- ListPtr :: ParsedList (Maybe (Parsed AnyPointer)) %1 -> Parsed AnyList
- class (Parse a ap, Allocate (List a)) => EstimateListAlloc a ap where- estimateListAlloc :: Vector ap -> AllocHint (List a)
 
- class (IsCap p, IsCap c) => Super p c
- type MarshalElement a ap = (Parse a ap, EstimateListAlloc a ap, Element (ReprFor a), ListItem (ElemRepr (ListReprFor (ReprFor a))), HasMessage (ListOf (ElemRepr (ListReprFor (ReprFor a)))), MarshalElementByRepr (ListReprFor (ReprFor a)), MarshalElementReprConstraints (ListReprFor (ReprFor a)) a ap)
- class (IsStruct a, Allocate a, HasTypeId a, AllocHint a ~ ()) => TypedStruct a where
- class HasTypeId a where
- class Parse t p => Marshal t p where- marshalInto :: RWCtx m s => Raw t ('Mut s) -> p -> m ()
 
- class AllocateList a where- type ListAllocHint a
- newList :: RWCtx m s => ListAllocHint a -> Message ('Mut s) -> m (Raw (List a) ('Mut s))
 
- class Allocate a where
- class (Parse t p, Allocate t) => EstimateAlloc t p where- estimateAlloc :: p -> AllocHint t
 
- class Parse t p | t -> p, p -> t where
- newFromRepr :: forall a r m s. (Allocate r, 'Ptr ('Just r) ~ ReprFor a, RWCtx m s) => AllocHint r -> Message ('Mut s) -> m (Raw a ('Mut s))
- newTypedStruct :: forall a m s. (TypedStruct a, RWCtx m s) => Message ('Mut s) -> m (Raw a ('Mut s))
- newTypedStructList :: forall a m s. (TypedStruct a, RWCtx m s) => Int -> Message ('Mut s) -> m (Raw (List a) ('Mut s))
- structSizes :: forall a. TypedStruct a => (Word16, Word16)
- newRoot :: forall a m s. (RWCtx m s, IsStruct a, Allocate a) => AllocHint a -> Message ('Mut s) -> m (Raw a ('Mut s))
- setRoot :: (RWCtx m s, IsStruct a) => Raw a ('Mut s) -> m ()
- class IsWord a where
- msgToBuilder :: Message 'Const -> Builder
- msgToLBS :: Message 'Const -> ByteString
- msgToBS :: Message 'Const -> ByteString
- bsToMsg :: MonadThrow m => ByteString -> m (Message 'Const)
- lbsToMsg :: MonadThrow m => ByteString -> m (Message 'Const)
- msgToRaw :: forall a m mut. (ReadCtx m mut, IsStruct a) => Message mut -> m (Raw a mut)
- msgToParsed :: forall a m pa. (ReadCtx m 'Const, IsStruct a, Parse a pa) => Message 'Const -> m pa
- bsToRaw :: forall a m. (ReadCtx m 'Const, IsStruct a) => ByteString -> m (Raw a 'Const)
- bsToParsed :: forall a pa m. (ReadCtx m 'Const, IsStruct a, Parse a pa) => ByteString -> m pa
- lbsToRaw :: forall a m. (ReadCtx m 'Const, IsStruct a) => ByteString -> m (Raw a 'Const)
- lbsToParsed :: forall a pa m. (ReadCtx m 'Const, IsStruct a, Parse a pa) => ByteString -> m pa
- parsedToRaw :: forall a m pa s. (RWCtx m s, IsStruct a, Parse a pa) => pa -> m (Raw a ('Mut s))
- parsedToMsg :: forall a m pa s. (RWCtx m s, IsStruct a, Parse a pa) => pa -> m (Message ('Mut s))
- parsedToBuilder :: forall a m pa s. (RWCtx m s, IsStruct a, Parse a pa) => pa -> m Builder
- parsedToLBS :: forall a m pa s. (RWCtx m s, IsStruct a, Parse a pa) => pa -> m ByteString
- parsedToBS :: forall a m pa s. (RWCtx m s, IsStruct a, Parse a pa) => pa -> m ByteString
- sGetMsg :: Socket -> WordCount -> IO (Message 'Const)
- sPutMsg :: Socket -> Message 'Const -> IO ()
- hGetParsed :: forall a pa. (IsStruct a, Parse a pa) => Handle -> WordCount -> IO pa
- sGetParsed :: forall a pa. (IsStruct a, Parse a pa) => Socket -> WordCount -> IO pa
- getParsed :: (IsStruct a, Parse a pa) => WordCount -> IO pa
- hPutParsed :: (IsStruct a, Parse a pa) => Handle -> pa -> IO ()
- putParsed :: (IsStruct a, Parse a pa) => pa -> IO ()
- sPutParsed :: (IsStruct a, Parse a pa) => Socket -> pa -> IO ()
- hGetRaw :: IsStruct a => Handle -> WordCount -> IO (Raw a 'Const)
- getRaw :: IsStruct a => WordCount -> IO (Raw a 'Const)
- sGetRaw :: IsStruct a => Socket -> WordCount -> IO (Raw a 'Const)
- type ParsedList a = Vector a
- data Capability
- data AnyStruct
- data AnyList
- data AnyPointer
- data Data
- data Text
- textBuffer :: MonadThrow m => Raw Text mut -> m (Raw Data mut)
- textBytes :: ReadCtx m 'Const => Raw Text 'Const -> m ByteString
- type TypeParam a = (IsPtr a, Parse a (Parsed a))
- readField :: forall k a b mut m. (IsStruct a, ReadCtx m mut) => Field k a b -> Raw a mut -> m (Raw b mut)
- hasField :: (ReadCtx m mut, IsStruct a, IsPtr b) => Field 'Slot a b -> Raw a mut -> m Bool
- getField :: (IsStruct a, ReprFor b ~ 'Data sz, Parse b bp) => Field 'Slot a b -> Raw a 'Const -> bp
- setField :: forall a b m s. (IsStruct a, RWCtx m s) => Field 'Slot a b -> Raw b ('Mut s) -> Raw a ('Mut s) -> m ()
- newField :: forall a b m s. (IsStruct a, Allocate b, RWCtx m s) => Field 'Slot a b -> AllocHint b -> Raw a ('Mut s) -> m (Raw b ('Mut s))
- encodeField :: forall a b m s bp. (IsStruct a, Parse b bp, RWCtx m s) => Field 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
- parseField :: (IsStruct a, Parse b bp, ReadCtx m 'Const) => Field k a b -> Raw a 'Const -> m bp
- setVariant :: forall a b m s. (HasUnion a, RWCtx m s) => Variant 'Slot a b -> Raw a ('Mut s) -> Raw b ('Mut s) -> m ()
- encodeVariant :: forall a b m s bp. (HasUnion a, Parse b bp, RWCtx m s) => Variant 'Slot a b -> bp -> Raw a ('Mut s) -> m ()
- initVariant :: forall a b m s. (HasUnion a, RWCtx m s) => Variant 'Group a b -> Raw a ('Mut s) -> m (Raw b ('Mut s))
- structUnion :: HasUnion a => Raw a mut -> Raw (Which a) mut
- unionStruct :: HasUnion a => Raw (Which a) mut -> Raw a mut
- structWhich :: forall a mut m. (ReadCtx m mut, HasUnion a) => Raw a mut -> m (RawWhich a mut)
- unionWhich :: forall a mut m. (ReadCtx m mut, HasUnion a) => Raw (Which a) mut -> m (RawWhich a mut)
- class AsClient f where
- class (IsCap c, IsStruct p, IsStruct r) => HasMethod (name :: Symbol) c p r | name c -> p r where- methodByLabel :: Method c p r
 
- data Method c p r = Method {- interfaceId :: !Word64
- methodId :: !Word16
 
- upcast :: (AsClient f, Coercible (f p) (f c), Super p c) => f c -> f p
- callB :: (AsClient f, IsCap c, IsStruct p, MonadIO m) => Method c p r -> (forall s. PureBuilder s (Raw p ('Mut s))) -> f c -> m (Pipeline r)
- callR :: (AsClient f, IsCap c, IsStruct p, MonadIO m) => Method c p r -> Raw p 'Const -> f c -> m (Pipeline r)
- callP :: forall c p r f m pp. (AsClient f, IsCap c, IsStruct p, Parse p pp, MonadIO m) => Method c p r -> pp -> f c -> m (Pipeline r)
- pipe :: (IsStruct a, ReprFor b ~ 'Ptr pr) => Field k a b -> Pipeline a -> Pipeline b
- pipelineClient :: (IsCap a, MonadSTM m) => Pipeline a -> m (Client a)
- waitPipeline :: forall a m pr. ('Ptr pr ~ ReprFor a, IsPtrRepr pr, MonadSTM m) => Pipeline a -> m (Raw a 'Const)
- type Parsed a = ParsedByRepr (ReprFor a) a
- newtype Raw (a :: Type) (mut :: Mutability) = Raw {}
- data List a
- index :: forall a m mut. (ReadCtx m mut, HasMessage (ListOf (ElemRepr (ListReprFor (ReprFor a)))), ListElem a) => Int -> Raw (List a) mut -> m (Raw a mut)
- setIndex :: forall a m s. (RWCtx m s, ListItem (ElemRepr (ListReprFor (ReprFor a))), Element (ReprFor a)) => Raw a ('Mut s) -> Int -> Raw (List a) ('Mut s) -> m ()
- length :: ListElem a => Raw (List a) mut -> Int
- data Field (k :: FieldKind) a b
- data FieldKind
- class IsStruct a => HasField (name :: Symbol) k a b | a name -> k b where- fieldByLabel :: Field k a b
 
- class IsStruct a => HasUnion a where- data Which a
- data RawWhich a (mut :: Mutability)
- unionField :: Field 'Slot a Word16
- internalWhich :: ReadCtx m mut => Word16 -> Raw a mut -> m (RawWhich a mut)
 
- class HasUnion a => HasVariant (name :: Symbol) k a b | a name -> k b where- variantByLabel :: Variant k a b
 
- data family Message (mut :: Mutability)
- data family Segment (mut :: Mutability)
- data Mutability
- class Monad m => MonadReadMessage mut m where- numSegs :: Message mut -> m Int
- numWords :: Segment mut -> m WordCount
- numCaps :: Message mut -> m Int
- getSegment :: Message mut -> Int -> m (Segment mut)
- internalGetCap :: Message mut -> Int -> m Client
- slice :: WordCount -> WordCount -> Segment mut -> m (Segment mut)
- read :: Segment mut -> WordCount -> m Word64
 
- newMessage :: WriteCtx m s => Maybe WordCount -> m (Message ('Mut s))
- fromByteString :: ByteString -> Segment 'Const
- toByteString :: Segment 'Const -> ByteString
- data PureBuilder s a
- createPure :: (MonadThrow m, MaybeMutable f) => WordCount -> (forall s. PureBuilder s (f ('Mut s))) -> m (f 'Const)
- canonicalize :: RWCtx m s => Struct 'Const -> m (Message ('Mut s), Segment ('Mut s))
- type MethodHandler p r = Raw p 'Const -> Fulfiller (Raw r 'Const) -> IO ()
- class SomeServer a where
- class (IsCap i, HasTypeId i) => Export i where- type Server i :: Type -> Constraint
 
- export :: forall i s m. (MonadSTM m, Export i, Server i s, SomeServer s) => Supervisor -> s -> m (Client i)
- handleParsed :: (Parse p pp, IsStruct p, Parse r pr, IsStruct r) => (pp -> IO pr) -> MethodHandler p r
- handleRaw :: (IsStruct p, IsStruct r) => (Raw p 'Const -> IO (Raw r 'Const)) -> MethodHandler p r
- methodUnimplemented :: MethodHandler p r
- type IsStruct a = ReprFor a ~ 'Ptr ('Just 'Struct)
- type IsCap a = ReprFor a ~ 'Ptr ('Just 'Cap)
- type IsPtr a = (ReprFor a ~ 'Ptr (PtrReprFor (ReprFor a)), Untyped (ReprFor a) ~ UntypedPtr (PtrReprFor (ReprFor a)), IsPtrRepr (PtrReprFor (ReprFor a)))
- def :: Default a => a
Documentation
Monad transformer implementing MonadLimit. The underlying monad
 must implement MonadThrow. invoice calls throwM TraversalLimitError
Instances
| MonadTrans LimitT Source # | |
| Defined in Capnp.TraversalLimit | |
| MonadState s m => MonadState s (LimitT m) Source # | |
| MonadFail m => MonadFail (LimitT m) Source # | |
| Defined in Capnp.TraversalLimit | |
| MonadIO m => MonadIO (LimitT m) Source # | |
| Defined in Capnp.TraversalLimit | |
| Monad m => Applicative (LimitT m) Source # | |
| Functor m => Functor (LimitT m) Source # | |
| Monad m => Monad (LimitT m) Source # | |
| MonadThrow m => MonadLimit (LimitT m) Source # | |
| MonadCatch m => MonadCatch (LimitT m) Source # | |
| MonadThrow m => MonadThrow (LimitT m) Source # | |
| Defined in Capnp.TraversalLimit | |
| (PrimMonad m, s ~ PrimState m) => PrimMonad (LimitT m) Source # | |
| type PrimState (LimitT m) Source # | |
| Defined in Capnp.TraversalLimit | |
class Monad m => MonadLimit m where Source #
mtl-style type class to track the traversal limit. This is used by other parts of the library which actually do the reading.
Methods
invoice :: WordCount -> m () Source #
invoice nn from the traversal limit, signaling
 an error if the limit is exhausted.
Instances
| MonadThrow m => MonadLimit (LimitT m) Source # | |
| MonadLimit (PureBuilder s) Source # | |
| Defined in Internal.BuildPure Methods invoice :: WordCount -> PureBuilder s () Source # | |
| MonadLimit m => MonadLimit (ReaderT r m) Source # | |
| MonadLimit m => MonadLimit (StateT s m) Source # | |
| MonadLimit m => MonadLimit (StateT s m) Source # | |
| (Monoid w, MonadLimit m) => MonadLimit (WriterT w m) Source # | |
| (Monoid w, MonadLimit m) => MonadLimit (RWST r w s m) Source # | |
runLimitT :: MonadThrow m => WordCount -> LimitT m a -> m (a, WordCount) Source #
Run a LimitT, returning the value from the computation and the remaining
 traversal limit.
evalLimitT :: MonadThrow m => WordCount -> LimitT m a -> m a Source #
Run a LimitT, returning the value from the computation.
execLimitT :: MonadThrow m => WordCount -> LimitT m a -> m WordCount Source #
Run a LimitT, returning the remaining traversal limit.
defaultLimit :: WordCount Source #
A sensible default traversal limit. Currently 64 MiB.
Instances
| AsClient Client Source # | |
| Show (Client a) Source # | |
| ReprFor a ~ 'Ptr ('Just 'Cap) => IsClient (Client a) Source # | |
| Eq (Client a) Source # | |
| (TypeParam sturdyRef, TypeParam owner) => Parse (Persistent sturdyRef owner) (Client (Persistent sturdyRef owner)) Source # | |
| Defined in Capnp.Gen.Capnp.Persistent | |
| (TypeParam internalRef, TypeParam externalRef, TypeParam internalOwner, TypeParam externalOwner) => Parse (RealmGateway internalRef externalRef internalOwner externalOwner) (Client (RealmGateway internalRef externalRef internalOwner externalOwner)) Source # | |
| Defined in Capnp.Gen.Capnp.Persistent Methods parse :: ReadCtx m 'Const => Raw (RealmGateway internalRef externalRef internalOwner externalOwner) 'Const -> m (Client (RealmGateway internalRef externalRef internalOwner externalOwner)) Source # encode :: RWCtx m s => Message ('Mut s) -> Client (RealmGateway internalRef externalRef internalOwner externalOwner) -> m (Raw (RealmGateway internalRef externalRef internalOwner externalOwner) ('Mut s)) Source # | |
A Pipeline a
hGetMsg :: Handle -> WordCount -> IO (Message 'Const) Source #
hGetMsg handle limithandle that is at most
 limit 64-bit words in length.
structPtrs :: Parsed AnyStruct -> Vector (Maybe (Parsed AnyPointer)) Source #
ListStruct :: ParsedList (Parsed AnyStruct) %1 -> Parsed AnyList Source #
ListPtr :: ParsedList (Maybe (Parsed AnyPointer)) %1 -> Parsed AnyList Source #
class (Parse a ap, Allocate (List a)) => EstimateListAlloc a ap where Source #
Minimal complete definition
Nothing
Instances
class (IsCap p, IsCap c) => Super p c Source #
An instance Super p cc extends
 the interface p.
type MarshalElement a ap = (Parse a ap, EstimateListAlloc a ap, Element (ReprFor a), ListItem (ElemRepr (ListReprFor (ReprFor a))), HasMessage (ListOf (ElemRepr (ListReprFor (ReprFor a)))), MarshalElementByRepr (ListReprFor (ReprFor a)), MarshalElementReprConstraints (ListReprFor (ReprFor a)) a ap) Source #
Type alias capturing the constraints on a type needed by
 marshalElement
class (IsStruct a, Allocate a, HasTypeId a, AllocHint a ~ ()) => TypedStruct a where Source #
Operations on typed structs.
Instances
class HasTypeId a where Source #
Types which have a numeric type-id defined in a capnp schema.
Methods
The node id for this type. You will generally want to use the
 TypeApplications extension to specify the type.
Instances
class Parse t p => Marshal t p where Source #
An instance of marshal allows a parsed value to be inserted into pre-allocated space in a message.
Methods
marshalInto :: RWCtx m s => Raw t ('Mut s) -> p -> m () Source #
Marshal a value into the pre-allocated object inside the message.
Note that caller must arrange for the object to be of the correct size. This is is not necessarily guaranteed; for example, list types must coordinate the length of the list.
Instances
class AllocateList a where Source #
Like Allocate, but for allocating *lists* of a.
Minimal complete definition
Nothing
Methods
newList :: RWCtx m s => ListAllocHint a -> Message ('Mut s) -> m (Raw (List a) ('Mut s)) Source #
Instances
class Allocate a where Source #
Types which may be allocated directly inside a message.
Minimal complete definition
Nothing
Associated Types
Extra information needed to allocate a value of this type, e.g. the length for a list. May be () if no extra info is needed.
Methods
new :: RWCtx m s => AllocHint a -> Message ('Mut s) -> m (Raw a ('Mut s)) Source #
new hint msga inside msg.
Instances
class (Parse t p, Allocate t) => EstimateAlloc t p where Source #
Types where the necessary allocation is inferrable from the parsed form.
...this is most types.
Minimal complete definition
Nothing
Methods
estimateAlloc :: p -> AllocHint t Source #
Determine the appropriate hint needed to allocate space for the serialied form of the value.
default estimateAlloc :: AllocHint t ~ () => p -> AllocHint t Source #
Instances
class Parse t p | t -> p, p -> t where Source #
Capnp types that can be parsed into a more "natural" Haskell form.
- tis the capnproto type.
- pis the type of the parsed value.
Minimal complete definition
Methods
parse :: ReadCtx m 'Const => Raw t 'Const -> m p Source #
Parse a value from a constant message
encode :: RWCtx m s => Message ('Mut s) -> p -> m (Raw t ('Mut s)) Source #
Encode a value into Raw form, using the message as storage.
Instances
newFromRepr :: forall a r m s. (Allocate r, 'Ptr ('Just r) ~ ReprFor a, RWCtx m s) => AllocHint r -> Message ('Mut s) -> m (Raw a ('Mut s)) Source #
newTypedStruct :: forall a m s. (TypedStruct a, RWCtx m s) => Message ('Mut s) -> m (Raw a ('Mut s)) Source #
newTypedStructList :: forall a m s. (TypedStruct a, RWCtx m s) => Int -> Message ('Mut s) -> m (Raw (List a) ('Mut s)) Source #
Like newTypedStruct, but for lists.
structSizes :: forall a. TypedStruct a => (Word16, Word16) Source #
Get the maximum word and pointer counts needed for a struct type's fields.
newRoot :: forall a m s. (RWCtx m s, IsStruct a, Allocate a) => AllocHint a -> Message ('Mut s) -> m (Raw a ('Mut s)) Source #
Like new, but also sets the value as the root of the message.
setRoot :: (RWCtx m s, IsStruct a) => Raw a ('Mut s) -> m () Source #
Sets the struct to be the root of its containing message.
Types that can be converted to and from a 64-bit word.
Anything that goes in the data section of a struct will have an instance of this.
Methods
fromWord :: Word64 -> a Source #
Convert from a 64-bit words Truncates the word if the type has less than 64 bits.
toWord :: a -> Word64 Source #
Convert to a 64-bit word.
Instances
| IsWord Int16 Source # | |
| IsWord Int32 Source # | |
| IsWord Int64 Source # | |
| IsWord Int8 Source # | |
| IsWord Word16 Source # | |
| IsWord Word32 Source # | |
| IsWord Word64 Source # | |
| IsWord Word8 Source # | |
| IsWord Word1 Source # | |
| IsWord Exception'Type Source # | |
| Defined in Capnp.Gen.Capnp.Rpc | |
| IsWord Side Source # | |
| IsWord ElementSize Source # | |
| Defined in Capnp.Gen.Capnp.Schema | |
| IsWord Bool Source # | |
| IsWord Double Source # | |
| IsWord Float Source # | |
msgToLBS :: Message 'Const -> ByteString Source #
Convert an immutable message to a lazy ByteString.
 To convert a mutable message, freeze it first.
msgToBS :: Message 'Const -> ByteString Source #
Convert an immutable message to a strict ByteString.
 To convert a mutable message, freeze it first.
bsToMsg :: MonadThrow m => ByteString -> m (Message 'Const) Source #
Convert a strict ByteString to a message.
lbsToMsg :: MonadThrow m => ByteString -> m (Message 'Const) Source #
Convert a lazy ByteString to a message.
msgToRaw :: forall a m mut. (ReadCtx m mut, IsStruct a) => Message mut -> m (Raw a mut) Source #
Get the root pointer of a message, wrapped as a Raw.
msgToParsed :: forall a m pa. (ReadCtx m 'Const, IsStruct a, Parse a pa) => Message 'Const -> m pa Source #
Get the root pointer of a message, as a parsed ADT.
bsToRaw :: forall a m. (ReadCtx m 'Const, IsStruct a) => ByteString -> m (Raw a 'Const) Source #
Like msgToRaw, but takes a (strict) bytestring.
bsToParsed :: forall a pa m. (ReadCtx m 'Const, IsStruct a, Parse a pa) => ByteString -> m pa Source #
Like msgToParsed, but takes a (strict) bytestring.
lbsToRaw :: forall a m. (ReadCtx m 'Const, IsStruct a) => ByteString -> m (Raw a 'Const) Source #
Like msgToRaw, but takes a (lazy) bytestring.
lbsToParsed :: forall a pa m. (ReadCtx m 'Const, IsStruct a, Parse a pa) => ByteString -> m pa Source #
Like msgToParsed, but takes a (lazzy) bytestring.
parsedToRaw :: forall a m pa s. (RWCtx m s, IsStruct a, Parse a pa) => pa -> m (Raw a ('Mut s)) Source #
Serialize the parsed form of a struct into its Raw form, and make it the root
 of its message.
parsedToMsg :: forall a m pa s. (RWCtx m s, IsStruct a, Parse a pa) => pa -> m (Message ('Mut s)) Source #
Serialize the parsed form of a struct into a message with that value as its root, returning the message.
parsedToBuilder :: forall a m pa s. (RWCtx m s, IsStruct a, Parse a pa) => pa -> m Builder Source #
Serialize the parsed form of a struct and return it as a Builder
parsedToLBS :: forall a m pa s. (RWCtx m s, IsStruct a, Parse a pa) => pa -> m ByteString Source #
Serialize the parsed form of a struct and return it as a lazy ByteString
parsedToBS :: forall a m pa s. (RWCtx m s, IsStruct a, Parse a pa) => pa -> m ByteString Source #
Serialize the parsed form of a struct and return it as a strict ByteString
sGetMsg :: Socket -> WordCount -> IO (Message 'Const) Source #
Like hGetMsg, except that it takes a socket instead of a Handle.
hGetParsed :: forall a pa. (IsStruct a, Parse a pa) => Handle -> WordCount -> IO pa Source #
Read a struct from the handle in its parsed form, using the supplied read limit.
sGetParsed :: forall a pa. (IsStruct a, Parse a pa) => Socket -> WordCount -> IO pa Source #
Read a struct from the socket in its parsed form, using the supplied read limit.
getParsed :: (IsStruct a, Parse a pa) => WordCount -> IO pa Source #
Read a struct from stdin in its parsed form, using the supplied read limit.
hPutParsed :: (IsStruct a, Parse a pa) => Handle -> pa -> IO () Source #
Write the parsed form of a struct to the handle
putParsed :: (IsStruct a, Parse a pa) => pa -> IO () Source #
Write the parsed form of a struct to stdout
sPutParsed :: (IsStruct a, Parse a pa) => Socket -> pa -> IO () Source #
Write the parsed form of a struct to the socket.
hGetRaw :: IsStruct a => Handle -> WordCount -> IO (Raw a 'Const) Source #
Read a struct from the handle using the supplied read limit, and return its root pointer.
getRaw :: IsStruct a => WordCount -> IO (Raw a 'Const) Source #
Read a struct from stdin using the supplied read limit, and return its root pointer.
sGetRaw :: IsStruct a => Socket -> WordCount -> IO (Raw a 'Const) Source #
Read a struct from the socket using the supplied read limit, and return its root pointer.
type ParsedList a = Vector a Source #
data Capability Source #
A Cap'n Proto capability with unknown interfaces.
Instances
| Parse Capability Client Source # | |
| type ReprFor Capability Source # | |
| Defined in Capnp.Basics | |
A Cap'n Proto struct of unknown type.
Instances
A Cap'n Proto List with unknown element type.
Instances
data AnyPointer Source #
A Cap'n Proto AnyPointer, i.e. an arbitrary pointer with unknown schema.
Instances
The Cap'n Proto Data type.
Instances
| Allocate Data Source # | |
| AllocateList Data Source # | |
| EstimateAlloc Data ByteString Source # | |
| Defined in Capnp.Basics Methods estimateAlloc :: ByteString -> AllocHint Data Source # | |
| EstimateListAlloc Data ByteString Source # | |
| Defined in Capnp.Basics Methods estimateListAlloc :: Vector ByteString -> AllocHint (List Data) Source # | |
| Marshal Data ByteString Source # | |
| Defined in Capnp.Basics Methods marshalInto :: RWCtx m s => Raw Data ('Mut s) -> ByteString -> m () Source # | |
| Parse Data ByteString Source # | |
| HasVariant "data_" 'Slot Value Data Source # | |
| Defined in Capnp.Gen.Capnp.Schema | |
| type AllocHint Data Source # | |
| Defined in Capnp.Basics | |
| type ListAllocHint Data Source # | |
| Defined in Capnp.Basics | |
| type ReprFor Data Source # | |
The Cap'n Proto Text type.
Instances
textBuffer :: MonadThrow m => Raw Text mut -> m (Raw Data mut) Source #
Return the underlying buffer containing the text. This does not include the null terminator.
textBytes :: ReadCtx m 'Const => Raw Text 'Const -> m ByteString Source #
Convert a Text to a ByteString, comprising the raw bytes of the text
 (not counting the NUL terminator).
type TypeParam a = (IsPtr a, Parse a (Parsed a)) Source #
Constraints needed for a to be a capnproto type parameter.
readField :: forall k a b mut m. (IsStruct a, ReadCtx m mut) => Field k a b -> Raw a mut -> m (Raw b mut) Source #
Read the value of a field of a struct.
hasField :: (ReadCtx m mut, IsStruct a, IsPtr b) => Field 'Slot a b -> Raw a mut -> m Bool Source #
Return whether the specified field is present. Only applicable for pointer fields.
getField :: (IsStruct a, ReprFor b ~ 'Data sz, Parse b bp) => Field 'Slot a b -> Raw a 'Const -> bp Source #
Like readField, but:
- Doesn't need the monadic context; can be used in pure code.
- Only works for immutable values.
- Only works for fields in the struct's data section.
setField :: forall a b m s. (IsStruct a, RWCtx m s) => Field 'Slot a b -> Raw b ('Mut s) -> Raw a ('Mut s) -> m () Source #
Set a struct field to a value. Not usable for group fields.
newField :: forall a b m s. (IsStruct a, Allocate b, RWCtx m s) => Field 'Slot a b -> AllocHint b -> Raw a ('Mut s) -> m (Raw b ('Mut s)) Source #
Allocate space for the value of a field, and return it.
encodeField :: forall a b m s bp. (IsStruct a, Parse b bp, RWCtx m s) => Field 'Slot a b -> bp -> Raw a ('Mut s) -> m () Source #
Marshal a parsed value into a struct's field.
parseField :: (IsStruct a, Parse b bp, ReadCtx m 'Const) => Field k a b -> Raw a 'Const -> m bp Source #
parse a struct's field and return its parsed form.
setVariant :: forall a b m s. (HasUnion a, RWCtx m s) => Variant 'Slot a b -> Raw a ('Mut s) -> Raw b ('Mut s) -> m () Source #
Set the struct's anonymous union to the given variant, with the
 supplied value as its argument. Not applicable for variants whose
 argument is a group; use initVariant instead.
encodeVariant :: forall a b m s bp. (HasUnion a, Parse b bp, RWCtx m s) => Variant 'Slot a b -> bp -> Raw a ('Mut s) -> 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 a ('Mut s) -> m (Raw b ('Mut s)) 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.
structUnion :: HasUnion a => Raw a mut -> Raw (Which a) mut Source #
Get the anonymous union for a struct.
unionStruct :: HasUnion a => Raw (Which a) mut -> Raw a mut Source #
Get the struct enclosing an anonymous union.
structWhich :: forall a mut m. (ReadCtx m mut, HasUnion a) => Raw a mut -> m (RawWhich a mut) Source #
Get a non-opaque view on the struct's anonymous union, which can be used to pattern match on.
unionWhich :: forall a mut m. (ReadCtx m mut, HasUnion a) => Raw (Which a) mut -> m (RawWhich a mut) Source #
Get a non-opaque view on the anonymous union, which can be used to pattern match on.
class (IsCap c, IsStruct p, IsStruct r) => HasMethod (name :: Symbol) c p r | name c -> p r where Source #
An instance HasMethod name c p rc has a method named name with parameter type p and
 return type r. The generated code includes instances of this
 for each method in the schema.
Methods
methodByLabel :: Method c p r Source #
Instances
| (TypeParam sturdyRef, TypeParam owner) => HasMethod "save" (Persistent sturdyRef owner) (Persistent'SaveParams sturdyRef owner) (Persistent'SaveResults sturdyRef owner) Source # | |
| Defined in Capnp.Gen.Capnp.Persistent Methods methodByLabel :: Method (Persistent sturdyRef owner) (Persistent'SaveParams sturdyRef owner) (Persistent'SaveResults sturdyRef owner) Source # | |
| (TypeParam internalRef, TypeParam externalRef, TypeParam internalOwner, TypeParam externalOwner) => HasMethod "export" (RealmGateway internalRef externalRef internalOwner externalOwner) (RealmGateway'export'params internalRef externalRef internalOwner externalOwner) (Persistent'SaveResults externalRef externalOwner) Source # | |
| Defined in Capnp.Gen.Capnp.Persistent Methods methodByLabel :: Method (RealmGateway internalRef externalRef internalOwner externalOwner) (RealmGateway'export'params internalRef externalRef internalOwner externalOwner) (Persistent'SaveResults externalRef externalOwner) Source # | |
| (TypeParam internalRef, TypeParam externalRef, TypeParam internalOwner, TypeParam externalOwner) => HasMethod "import_" (RealmGateway internalRef externalRef internalOwner externalOwner) (RealmGateway'import'params internalRef externalRef internalOwner externalOwner) (Persistent'SaveResults internalRef internalOwner) Source # | |
| Defined in Capnp.Gen.Capnp.Persistent Methods methodByLabel :: Method (RealmGateway internalRef externalRef internalOwner externalOwner) (RealmGateway'import'params internalRef externalRef internalOwner externalOwner) (Persistent'SaveResults internalRef internalOwner) Source # | |
Represents a method on the interface type c with parameter
 type p and return type r.
Constructors
| Method | |
| Fields 
 | |
upcast :: (AsClient f, Coercible (f p) (f c), Super p c) => f c -> f p Source #
Upcast is a (safe) cast from an interface to one of its superclasses.
callB :: (AsClient f, IsCap c, IsStruct p, MonadIO m) => Method c p r -> (forall s. PureBuilder s (Raw p ('Mut s))) -> f c -> m (Pipeline r) Source #
Call a method. Use the provided PureBuilder to construct the parameters.
callR :: (AsClient f, IsCap c, IsStruct p, MonadIO m) => Method c p r -> Raw p 'Const -> f c -> m (Pipeline r) Source #
Call a method, supplying the parameters as a Raw struct.
callP :: forall c p r f m pp. (AsClient f, IsCap c, IsStruct p, Parse p pp, MonadIO m) => Method c p r -> pp -> f c -> m (Pipeline r) Source #
Call a method, supplying the parmaeters in parsed form.
pipe :: (IsStruct a, ReprFor b ~ 'Ptr pr) => Field k a b -> Pipeline a -> Pipeline b Source #
Project a pipeline to a struct onto one of its pointer fields.
waitPipeline :: forall a m pr. ('Ptr pr ~ ReprFor a, IsPtrRepr pr, MonadSTM m) => Pipeline a -> m (Raw a 'Const) Source #
Wait for the result of a pipeline, and return its value.
type Parsed a = ParsedByRepr (ReprFor a) a Source #
Parsed aa. For struct types this is equivalent to Parsed aParsed DataByteString.
Working with raw values
newtype Raw (a :: Type) (mut :: Mutability) Source #
A Raw mut aa embedded in a capnproto message with mutability
 mut.
Instances
Working with raw lists
A phantom type denoting capnproto lists of type a.
Instances
index :: forall a m mut. (ReadCtx m mut, HasMessage (ListOf (ElemRepr (ListReprFor (ReprFor a)))), ListElem a) => Int -> Raw (List a) mut -> m (Raw a mut) Source #
index i listith element of the list.
setIndex :: forall a m s. (RWCtx m s, ListItem (ElemRepr (ListReprFor (ReprFor a))), Element (ReprFor a)) => Raw a ('Mut s) -> Int -> Raw (List a) ('Mut s) -> m () Source #
setIndex value i listith element of list to value.
Working with fields
data Field (k :: FieldKind) a b Source #
Field k a bb within
 an a, where a must be a struct type.
What sort of field is this? This corresponds to the slot/group variants
 in the Field type in schema.capnp. Mostly used at the type level with
 the DataKinds extension.
(Note that this has nothing to do with kinds in the usual type system sense of the word).
class IsStruct a => HasField (name :: Symbol) k a b | a name -> k b where Source #
An instance HasField name k a ba
 has a field named name with type b (with k being the FieldKind for
 the field). The generated code includes instances of this for each field
 in the schema.
Methods
fieldByLabel :: Field k a b Source #
Instances
class IsStruct a => HasUnion a where Source #
An instance of HasUnion indicates that the given type is a capnproto struct
 (or group) with an anonymous union.
Associated Types
Which is the abstract capnproto type of the union itself. Like
 generated struct types (in this case a), this is typically
 uninhabitied, and used to define instances and/or act as a phantom type.
data RawWhich a (mut :: Mutability) Source #
Concrete view into a union embedded in a message. This will be a sum
 type with other Raw values as arguments.
Methods
unionField :: Field 'Slot a Word16 Source #
unionField is a field holding the union's tag.
internalWhich :: ReadCtx m mut => Word16 -> Raw a mut -> m (RawWhich a mut) Source #
Helper used in generated code to extract a RawWhich from its
 surrounding struct.
Instances
class HasUnion a => HasVariant (name :: Symbol) k a b | a name -> k b where Source #
An instance 'HasVariant name k a b indicates that the struct type a
 has an anonymous union with a variant named name, whose argument is of type
 b.
Methods
variantByLabel :: Variant k a b Source #
Instances
Working with messages
data family Message (mut :: Mutability) Source #
A Cap'n Proto message, parametrized over its mutability.
Instances
| MaybeMutable Message Source # | |
| Defined in Capnp.Message Methods thaw :: (PrimMonad m, PrimState m ~ s) => Message 'Const -> m (Message ('Mut s)) Source # freeze :: (PrimMonad m, PrimState m ~ s) => Message ('Mut s) -> m (Message 'Const) Source # unsafeThaw :: (PrimMonad m, PrimState m ~ s) => Message 'Const -> m (Message ('Mut s)) Source # unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Message ('Mut s) -> m (Message 'Const) Source # | |
| Eq (Message 'Const) Source # | |
| Eq (Message ('Mut s)) Source # | |
| newtype Message 'Const Source # | |
| Defined in Capnp.Message | |
| newtype Message ('Mut s) Source # | |
| Defined in Capnp.Message | |
data family Segment (mut :: Mutability) Source #
A segment in a Cap'n Proto message.
Instances
| MaybeMutable Segment Source # | |
| Defined in Capnp.Message Methods thaw :: (PrimMonad m, PrimState m ~ s) => Segment 'Const -> m (Segment ('Mut s)) Source # freeze :: (PrimMonad m, PrimState m ~ s) => Segment ('Mut s) -> m (Segment 'Const) Source # unsafeThaw :: (PrimMonad m, PrimState m ~ s) => Segment 'Const -> m (Segment ('Mut s)) Source # unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Segment ('Mut s) -> m (Segment 'Const) Source # | |
| Eq (Segment 'Const) Source # | |
| Eq (Segment ('Mut s)) Source # | |
| newtype Segment 'Const Source # | |
| Defined in Capnp.Message | |
| newtype Segment ('Mut s) Source # | |
| Defined in Capnp.Message | |
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 Mut ss.
class Monad m => MonadReadMessage mut m where Source #
A Message is a (possibly read-only) capnproto message. It is
 parameterized over a monad in which operations are performed.
Methods
numSegs :: Message mut -> m Int Source #
numSegs gets the number of segments in a message.
numWords :: Segment mut -> m WordCount Source #
numWords gets the number of words in a segment.
numCaps :: Message mut -> m Int Source #
numCaps gets the number of capabilities in a message's capability
 table.
getSegment :: Message mut -> Int -> m (Segment mut) Source #
getSegment message indexindex
 in message.
internalGetCap :: Message mut -> Int -> m Client Source #
internalGetCap cap index
slice :: WordCount -> WordCount -> Segment mut -> m (Segment mut) Source #
slice start length segmentstart, of length length.
Instances
| Monad m => MonadReadMessage 'Const m Source # | |
| Defined in Capnp.Message Methods numSegs :: Message 'Const -> m Int Source # numWords :: Segment 'Const -> m WordCount Source # numCaps :: Message 'Const -> m Int Source # getSegment :: Message 'Const -> Int -> m (Segment 'Const) Source # internalGetCap :: Message 'Const -> Int -> m Client Source # slice :: WordCount -> WordCount -> Segment 'Const -> m (Segment 'Const) Source # | |
| (PrimMonad m, s ~ PrimState m) => MonadReadMessage ('Mut s) m Source # | |
| Defined in Capnp.Message Methods numSegs :: Message ('Mut s) -> m Int Source # numWords :: Segment ('Mut s) -> m WordCount Source # numCaps :: Message ('Mut s) -> m Int Source # getSegment :: Message ('Mut s) -> Int -> m (Segment ('Mut s)) Source # internalGetCap :: Message ('Mut s) -> Int -> m Client Source # slice :: WordCount -> WordCount -> Segment ('Mut s) -> m (Segment ('Mut s)) Source # | |
newMessage :: WriteCtx m s => Maybe WordCount -> m (Message ('Mut s)) Source #
newMessage sizeHintsizeHint. If sizeHint is Nothing, defaults to a sensible
 value.
fromByteString :: ByteString -> Segment 'Const Source #
Convert a ByteString to a segment. O(1)
toByteString :: Segment 'Const -> ByteString Source #
Convert a segment to a byte string. O(1)
Building messages in pure code
data PureBuilder s a Source #
PureBuilder is a monad transformer stack with the instnaces needed
 manipulate mutable messages. PureBuilder s aLimitT (CatchT (ST s)) a
Instances
createPure :: (MonadThrow m, MaybeMutable f) => WordCount -> (forall s. PureBuilder s (f ('Mut s))) -> m (f 'Const) Source #
createPure limit mm, then freezes it without copying. If m calls throwM then
 createPure rethrows the exception in the specified monad.
Canonicalizing messages
canonicalize :: RWCtx m s => Struct 'Const -> m (Message ('Mut s), Segment ('Mut s)) Source #
Return a canonicalized message with a copy of the given struct as its root. returns a (message, segment) pair, where the segment is the first and only segment of the returned message.
In addition to the usual reasons for failure when reading a message (traversal limit, malformed messages), this can fail if the message does not fit in a single segment, as the canonical form requires single-segment messages.
Implementing RPC servers
type MethodHandler p r = Raw p 'Const -> Fulfiller (Raw r 'Const) -> IO () Source #
Type alias for a handler for a particular rpc method.
class SomeServer a where Source #
Base class for things that can act as capnproto servers.
Minimal complete definition
Nothing
Methods
shutdown :: a -> IO () Source #
Called when the last live reference to a server is dropped.
unwrap :: Typeable b => a -> Maybe b Source #
Try to extract a value of a given type. The default implementation
 always fails (returns Nothing). If an instance chooses to implement
 this, it will be possible to use "reflection" on clients that point
 at local servers to dynamically unwrap the server value. A typical
 implementation will just call Typeable's cast method, but this
 needn't be the case -- a server may wish to allow local peers to
 unwrap some value that is not exactly the data the server has access
 to.
class (IsCap i, HasTypeId i) => Export i Source #
Generated interface types have instances of Export, which allows a server
 for that interface to be exported as a Client.
Minimal complete definition
Associated Types
type Server i :: Type -> Constraint Source #
The constraint needed for a server to implement an interface;
 if Server i ss is a server for interface i.
 The code generator generates a type class for each interface, and
 this will aways be an alias for that type class.
Instances
| (TypeParam sturdyRef, TypeParam owner) => Export (Persistent sturdyRef owner) Source # | |
| Defined in Capnp.Gen.Capnp.Persistent Associated Types type Server (Persistent sturdyRef owner) :: Type -> Constraint Source # Methods methodHandlerTree :: Server (Persistent sturdyRef owner) s => Proxy (Persistent sturdyRef owner) -> s -> MethodHandlerTree Source # | |
| (TypeParam internalRef, TypeParam externalRef, TypeParam internalOwner, TypeParam externalOwner) => Export (RealmGateway internalRef externalRef internalOwner externalOwner) Source # | |
| Defined in Capnp.Gen.Capnp.Persistent Associated Types type Server (RealmGateway internalRef externalRef internalOwner externalOwner) :: Type -> Constraint Source # Methods methodHandlerTree :: Server (RealmGateway internalRef externalRef internalOwner externalOwner) s => Proxy (RealmGateway internalRef externalRef internalOwner externalOwner) -> s -> MethodHandlerTree Source # | |
export :: forall i s m. (MonadSTM m, Export i, Server i s, SomeServer s) => Supervisor -> s -> m (Client i) Source #
Export the server as a client for interface i. Spawns a server thread
 with its lifetime bound to the supervisor.
handleParsed :: (Parse p pp, IsStruct p, Parse r pr, IsStruct r) => (pp -> IO pr) -> MethodHandler p r Source #
Handle a method, working with the parsed form of parameters and results.
handleRaw :: (IsStruct p, IsStruct r) => (Raw p 'Const -> IO (Raw r 'Const)) -> MethodHandler p r Source #
Handle a method, working with the raw (unparsed) form of parameters and results.
methodUnimplemented :: MethodHandler p r Source #
MethodHandler that always throws unimplemented.
Shorthands for types
type IsPtr a = (ReprFor a ~ 'Ptr (PtrReprFor (ReprFor a)), Untyped (ReprFor a) ~ UntypedPtr (PtrReprFor (ReprFor a)), IsPtrRepr (PtrReprFor (ReprFor a))) Source #
Constraint that a is a pointer type.