capnp-0.17.0.0: Cap'n Proto for Haskell
Safe HaskellSafe-Inferred
LanguageHaskell2010

Capnp.Untyped

Description

The types and functions in this module know about things like structs and lists, but are not schema aware.

Each of the data types exported by this module is parametrized over the mutability of the message it contains (see Capnp.Message).

Synopsis

Type-level descriptions of wire representations.

data Repr Source #

A Repr describes a wire representation for a value. This is mostly used at the type level (using DataKinds); types are parametrized over representations.

Constructors

Ptr (Maybe PtrRepr)

Pointer type. Nothing indicates an AnyPointer, Just describes a more specific pointer type.

Data DataSz

Non-pointer type.

Instances

Instances details
Show Repr Source # 
Instance details

Defined in Capnp.Untyped

Methods

showsPrec :: Int -> Repr -> ShowS #

show :: Repr -> String #

showList :: [Repr] -> ShowS #

data PtrRepr Source #

Information about the representation of a pointer type

Constructors

Cap

Capability pointer.

List (Maybe ListRepr)

List pointer. Nothing describes an AnyList, Just describes more specific list types.

Struct

A struct (or group).

Instances

Instances details
Show PtrRepr Source # 
Instance details

Defined in Capnp.Untyped

Element ('Ptr ('Just 'Cap)) Source # 
Instance details

Defined in Capnp.Untyped

Methods

fromElement :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Unwrapped (Untyped (ElemRepr (ListReprFor ('Ptr ('Just 'Cap)))) mut) -> m (Unwrapped (Untyped ('Ptr ('Just 'Cap)) mut)) Source #

toElement :: forall (mut :: Mutability). Unwrapped (Untyped ('Ptr ('Just 'Cap)) mut) -> Unwrapped (Untyped (ElemRepr (ListReprFor ('Ptr ('Just 'Cap)))) mut) Source #

IsPtrRepr ('Just ('List a)) => Element ('Ptr ('Just ('List a))) Source # 
Instance details

Defined in Capnp.Untyped

Methods

fromElement :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Unwrapped (Untyped (ElemRepr (ListReprFor ('Ptr ('Just ('List a))))) mut) -> m (Unwrapped (Untyped ('Ptr ('Just ('List a))) mut)) Source #

toElement :: forall (mut :: Mutability). Unwrapped (Untyped ('Ptr ('Just ('List a))) mut) -> Unwrapped (Untyped (ElemRepr (ListReprFor ('Ptr ('Just ('List a))))) mut) Source #

Element ('Ptr ('Just 'Struct)) Source # 
Instance details

Defined in Capnp.Untyped

Methods

fromElement :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Unwrapped (Untyped (ElemRepr (ListReprFor ('Ptr ('Just 'Struct)))) mut) -> m (Unwrapped (Untyped ('Ptr ('Just 'Struct)) mut)) Source #

toElement :: forall (mut :: Mutability). Unwrapped (Untyped ('Ptr ('Just 'Struct)) mut) -> Unwrapped (Untyped (ElemRepr (ListReprFor ('Ptr ('Just 'Struct)))) mut) Source #

Element ('Ptr ('Nothing :: Maybe PtrRepr)) Source # 
Instance details

Defined in Capnp.Untyped

Methods

fromElement :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Unwrapped (Untyped (ElemRepr (ListReprFor ('Ptr 'Nothing))) mut) -> m (Unwrapped (Untyped ('Ptr 'Nothing) mut)) Source #

toElement :: forall (mut :: Mutability). Unwrapped (Untyped ('Ptr 'Nothing) mut) -> Unwrapped (Untyped (ElemRepr (ListReprFor ('Ptr 'Nothing))) mut) Source #

HasMessage (ListOf ('Ptr ('Just 'Struct))) Source # 
Instance details

Defined in Capnp.Untyped

Methods

message :: forall (mut :: Mutability). Unwrapped (ListOf ('Ptr ('Just 'Struct)) mut) -> Message mut Source #

IsPtrRepr ('Nothing :: Maybe PtrRepr) Source # 
Instance details

Defined in Capnp.Untyped

Methods

toPtr :: forall (mut :: Mutability). Unwrapped (Untyped ('Ptr 'Nothing) mut) -> Maybe (Ptr mut) Source #

fromPtr :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (Unwrapped (Untyped ('Ptr 'Nothing) mut)) Source #

ListItem ('Ptr ('Just 'Struct)) Source # 
Instance details

Defined in Capnp.Untyped

Methods

length :: forall (mut :: Mutability). ListOf ('Ptr ('Just 'Struct)) mut -> Int Source #

unsafeIndex :: forall m (mut :: Mutability). ReadCtx m mut => Int -> ListOf ('Ptr ('Just 'Struct)) mut -> m (Unwrapped (Untyped ('Ptr ('Just 'Struct)) mut)) Source #

unsafeSetIndex :: (RWCtx m s, a ~ Unwrapped (Untyped ('Ptr ('Just 'Struct)) ('Mut s))) => a -> Int -> ListOf ('Ptr ('Just 'Struct)) ('Mut s) -> m () Source #

unsafeTake :: forall (mut :: Mutability). Int -> ListOf ('Ptr ('Just 'Struct)) mut -> ListOf ('Ptr ('Just 'Struct)) mut Source #

checkListOf :: forall m (mut :: Mutability). ReadCtx m mut => ListOf ('Ptr ('Just 'Struct)) mut -> m () Source #

copyListOf :: RWCtx m s => ListOf ('Ptr ('Just 'Struct)) ('Mut s) -> ListOf ('Ptr ('Just 'Struct)) ('Mut s) -> m () Source #

ListItem ('Ptr ('Nothing :: Maybe PtrRepr)) Source # 
Instance details

Defined in Capnp.Untyped

Methods

length :: forall (mut :: Mutability). ListOf ('Ptr 'Nothing) mut -> Int Source #

unsafeIndex :: forall m (mut :: Mutability). ReadCtx m mut => Int -> ListOf ('Ptr 'Nothing) mut -> m (Unwrapped (Untyped ('Ptr 'Nothing) mut)) Source #

unsafeSetIndex :: (RWCtx m s, a ~ Unwrapped (Untyped ('Ptr 'Nothing) ('Mut s))) => a -> Int -> ListOf ('Ptr 'Nothing) ('Mut s) -> m () Source #

unsafeTake :: forall (mut :: Mutability). Int -> ListOf ('Ptr 'Nothing) mut -> ListOf ('Ptr 'Nothing) mut Source #

checkListOf :: forall m (mut :: Mutability). ReadCtx m mut => ListOf ('Ptr 'Nothing) mut -> m () Source #

copyListOf :: RWCtx m s => ListOf ('Ptr 'Nothing) ('Mut s) -> ListOf ('Ptr 'Nothing) ('Mut s) -> m () Source #

MessageDefault (ListOf ('Ptr ('Just 'Struct))) Source # 
Instance details

Defined in Capnp.Untyped

Methods

messageDefault :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> m (Unwrapped (ListOf ('Ptr ('Just 'Struct)) mut)) Source #

IsPtrRepr ('Just 'Cap) Source # 
Instance details

Defined in Capnp.Untyped

Methods

toPtr :: forall (mut :: Mutability). Unwrapped (Untyped ('Ptr ('Just 'Cap)) mut) -> Maybe (Ptr mut) Source #

fromPtr :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (Unwrapped (Untyped ('Ptr ('Just 'Cap)) mut)) Source #

IsListPtrRepr r => IsPtrRepr ('Just ('List ('Just r))) Source # 
Instance details

Defined in Capnp.Untyped

Methods

toPtr :: forall (mut :: Mutability). Unwrapped (Untyped ('Ptr ('Just ('List ('Just r)))) mut) -> Maybe (Ptr mut) Source #

fromPtr :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (Unwrapped (Untyped ('Ptr ('Just ('List ('Just r)))) mut)) Source #

IsPtrRepr ('Just ('List ('Nothing :: Maybe ListRepr))) Source # 
Instance details

Defined in Capnp.Untyped

Methods

toPtr :: forall (mut :: Mutability). Unwrapped (Untyped ('Ptr ('Just ('List 'Nothing))) mut) -> Maybe (Ptr mut) Source #

fromPtr :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (Unwrapped (Untyped ('Ptr ('Just ('List 'Nothing))) mut)) Source #

IsPtrRepr ('Just 'Struct) Source # 
Instance details

Defined in Capnp.Untyped

Methods

toPtr :: forall (mut :: Mutability). Unwrapped (Untyped ('Ptr ('Just 'Struct)) mut) -> Maybe (Ptr mut) Source #

fromPtr :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (Unwrapped (Untyped ('Ptr ('Just 'Struct)) mut)) Source #

data ListRepr where Source #

Information about the representation of a list type.

Constructors

ListNormal :: NormalListRepr -> ListRepr

A "normal" list

ListComposite :: ListRepr

A composite (struct) list

Instances

Instances details
Show ListRepr Source # 
Instance details

Defined in Capnp.Untyped

Allocate ('List ('Just 'ListComposite)) Source # 
Instance details

Defined in Capnp.Untyped

Associated Types

type AllocHint ('List ('Just 'ListComposite)) Source #

AllocateNormalList r => Allocate ('List ('Just ('ListNormal r))) Source # 
Instance details

Defined in Capnp.Untyped

Associated Types

type AllocHint ('List ('Just ('ListNormal r))) Source #

Methods

alloc :: RWCtx m s => Message ('Mut s) -> AllocHint ('List ('Just ('ListNormal r))) -> m (Unwrapped (UntypedSomePtr ('List ('Just ('ListNormal r))) ('Mut s))) Source #

IsListPtrRepr r => IsPtrRepr ('Just ('List ('Just r))) Source # 
Instance details

Defined in Capnp.Untyped

Methods

toPtr :: forall (mut :: Mutability). Unwrapped (Untyped ('Ptr ('Just ('List ('Just r)))) mut) -> Maybe (Ptr mut) Source #

fromPtr :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (Unwrapped (Untyped ('Ptr ('Just ('List ('Just r)))) mut)) Source #

IsPtrRepr ('Just ('List ('Nothing :: Maybe ListRepr))) Source # 
Instance details

Defined in Capnp.Untyped

Methods

toPtr :: forall (mut :: Mutability). Unwrapped (Untyped ('Ptr ('Just ('List 'Nothing))) mut) -> Maybe (Ptr mut) Source #

fromPtr :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (Unwrapped (Untyped ('Ptr ('Just ('List 'Nothing))) mut)) Source #

type AllocHint ('List ('Just 'ListComposite)) Source # 
Instance details

Defined in Capnp.Untyped

type AllocHint ('List ('Just ('ListNormal r))) Source # 
Instance details

Defined in Capnp.Untyped

type AllocHint ('List ('Just ('ListNormal r))) = Int

data NormalListRepr where Source #

Information about the representation of a normal (non-composite) list.

Instances

Instances details
Show NormalListRepr Source # 
Instance details

Defined in Capnp.Untyped

data DataSz Source #

The size of a non-pointer type. SzN represents an N-bit value.

Constructors

Sz0 
Sz1 
Sz8 
Sz16 
Sz32 
Sz64 

Instances

Instances details
Show DataSz Source # 
Instance details

Defined in Capnp.Untyped

Mapping representations to value types.

type family Untyped (r :: Repr) :: Mutability -> Type where ... Source #

Untyped r mut is an untyped value with representation r stored in a message with mutability mut.

Note that the return type of this type family has kind Mutability -> Type. This is important, as it allows us to define instances on Untyped r, and use Untyped r in constraints.

This introduces some awkwardnesses though -- we really want this to be (Maybe (Ptr mut)) for 'Ptr 'Nothing, and Int typesBool() for 'Data sz. But we can't because these are the wrong kind.

So, we hack around this by introducing two newtypes, IgnoreMut and MaybePtr, and a type family Unwrapped, which lets us use Unwrapped (Untyped r mut) as the type we really want in some places, though we can't curry it then.

All this is super super awkward, but this is a low level mostly-internal API; most users will intract with this through the Raw type in Capnp.Repr, which hides all of this...

Equations

Untyped ('Data sz) = IgnoreMut (UntypedData sz) 
Untyped ('Ptr ptr) = UntypedPtr ptr 

type family UntypedData (sz :: DataSz) :: Type where ... Source #

UntypedData sz is an untyped value with size sz.

type family UntypedPtr (r :: Maybe PtrRepr) :: Mutability -> Type where ... Source #

Like Untyped, but for pointers only.

type family UntypedSomePtr (r :: PtrRepr) :: Mutability -> Type where ... Source #

Like UntypedPtr, but doesn't allow AnyPointers.

type family UntypedList (r :: Maybe ListRepr) :: Mutability -> Type where ... Source #

Like Untyped, but for lists only.

type family UntypedSomeList (r :: ListRepr) :: Mutability -> Type where ... Source #

Like UntypedList, but doesn't allow AnyLists.

Equations

UntypedSomeList r = ListOf (ElemRepr r) 

newtype IgnoreMut a (mut :: Mutability) Source #

Wrapper for use with Untyped; see docs for Untyped

Constructors

IgnoreMut a 

Instances

Instances details
MaybeMutable (IgnoreMut a) Source # 
Instance details

Defined in Capnp.Untyped

Methods

thaw :: (PrimMonad m, PrimState m ~ s) => IgnoreMut a 'Const -> m (IgnoreMut a ('Mut s)) Source #

freeze :: (PrimMonad m, PrimState m ~ s) => IgnoreMut a ('Mut s) -> m (IgnoreMut a 'Const) Source #

unsafeThaw :: (PrimMonad m, PrimState m ~ s) => IgnoreMut a 'Const -> m (IgnoreMut a ('Mut s)) Source #

unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => IgnoreMut a ('Mut s) -> m (IgnoreMut a 'Const) Source #

Bits a => Bits (IgnoreMut a mut) Source # 
Instance details

Defined in Capnp.Untyped

Methods

(.&.) :: IgnoreMut a mut -> IgnoreMut a mut -> IgnoreMut a mut #

(.|.) :: IgnoreMut a mut -> IgnoreMut a mut -> IgnoreMut a mut #

xor :: IgnoreMut a mut -> IgnoreMut a mut -> IgnoreMut a mut #

complement :: IgnoreMut a mut -> IgnoreMut a mut #

shift :: IgnoreMut a mut -> Int -> IgnoreMut a mut #

rotate :: IgnoreMut a mut -> Int -> IgnoreMut a mut #

zeroBits :: IgnoreMut a mut #

bit :: Int -> IgnoreMut a mut #

setBit :: IgnoreMut a mut -> Int -> IgnoreMut a mut #

clearBit :: IgnoreMut a mut -> Int -> IgnoreMut a mut #

complementBit :: IgnoreMut a mut -> Int -> IgnoreMut a mut #

testBit :: IgnoreMut a mut -> Int -> Bool #

bitSizeMaybe :: IgnoreMut a mut -> Maybe Int #

bitSize :: IgnoreMut a mut -> Int #

isSigned :: IgnoreMut a mut -> Bool #

shiftL :: IgnoreMut a mut -> Int -> IgnoreMut a mut #

unsafeShiftL :: IgnoreMut a mut -> Int -> IgnoreMut a mut #

shiftR :: IgnoreMut a mut -> Int -> IgnoreMut a mut #

unsafeShiftR :: IgnoreMut a mut -> Int -> IgnoreMut a mut #

rotateL :: IgnoreMut a mut -> Int -> IgnoreMut a mut #

rotateR :: IgnoreMut a mut -> Int -> IgnoreMut a mut #

popCount :: IgnoreMut a mut -> Int #

FiniteBits a => FiniteBits (IgnoreMut a mut) Source # 
Instance details

Defined in Capnp.Untyped

Bounded a => Bounded (IgnoreMut a mut) Source # 
Instance details

Defined in Capnp.Untyped

Methods

minBound :: IgnoreMut a mut #

maxBound :: IgnoreMut a mut #

Enum a => Enum (IgnoreMut a mut) Source # 
Instance details

Defined in Capnp.Untyped

Methods

succ :: IgnoreMut a mut -> IgnoreMut a mut #

pred :: IgnoreMut a mut -> IgnoreMut a mut #

toEnum :: Int -> IgnoreMut a mut #

fromEnum :: IgnoreMut a mut -> Int #

enumFrom :: IgnoreMut a mut -> [IgnoreMut a mut] #

enumFromThen :: IgnoreMut a mut -> IgnoreMut a mut -> [IgnoreMut a mut] #

enumFromTo :: IgnoreMut a mut -> IgnoreMut a mut -> [IgnoreMut a mut] #

enumFromThenTo :: IgnoreMut a mut -> IgnoreMut a mut -> IgnoreMut a mut -> [IgnoreMut a mut] #

Num a => Num (IgnoreMut a mut) Source # 
Instance details

Defined in Capnp.Untyped

Methods

(+) :: IgnoreMut a mut -> IgnoreMut a mut -> IgnoreMut a mut #

(-) :: IgnoreMut a mut -> IgnoreMut a mut -> IgnoreMut a mut #

(*) :: IgnoreMut a mut -> IgnoreMut a mut -> IgnoreMut a mut #

negate :: IgnoreMut a mut -> IgnoreMut a mut #

abs :: IgnoreMut a mut -> IgnoreMut a mut #

signum :: IgnoreMut a mut -> IgnoreMut a mut #

fromInteger :: Integer -> IgnoreMut a mut #

Read a => Read (IgnoreMut a mut) Source # 
Instance details

Defined in Capnp.Untyped

Integral a => Integral (IgnoreMut a mut) Source # 
Instance details

Defined in Capnp.Untyped

Methods

quot :: IgnoreMut a mut -> IgnoreMut a mut -> IgnoreMut a mut #

rem :: IgnoreMut a mut -> IgnoreMut a mut -> IgnoreMut a mut #

div :: IgnoreMut a mut -> IgnoreMut a mut -> IgnoreMut a mut #

mod :: IgnoreMut a mut -> IgnoreMut a mut -> IgnoreMut a mut #

quotRem :: IgnoreMut a mut -> IgnoreMut a mut -> (IgnoreMut a mut, IgnoreMut a mut) #

divMod :: IgnoreMut a mut -> IgnoreMut a mut -> (IgnoreMut a mut, IgnoreMut a mut) #

toInteger :: IgnoreMut a mut -> Integer #

Real a => Real (IgnoreMut a mut) Source # 
Instance details

Defined in Capnp.Untyped

Methods

toRational :: IgnoreMut a mut -> Rational #

Show a => Show (IgnoreMut a mut) Source # 
Instance details

Defined in Capnp.Untyped

Methods

showsPrec :: Int -> IgnoreMut a mut -> ShowS #

show :: IgnoreMut a mut -> String #

showList :: [IgnoreMut a mut] -> ShowS #

Eq a => Eq (IgnoreMut a mut) Source # 
Instance details

Defined in Capnp.Untyped

Methods

(==) :: IgnoreMut a mut -> IgnoreMut a mut -> Bool #

(/=) :: IgnoreMut a mut -> IgnoreMut a mut -> Bool #

Ord a => Ord (IgnoreMut a mut) Source # 
Instance details

Defined in Capnp.Untyped

Methods

compare :: IgnoreMut a mut -> IgnoreMut a mut -> Ordering #

(<) :: IgnoreMut a mut -> IgnoreMut a mut -> Bool #

(<=) :: IgnoreMut a mut -> IgnoreMut a mut -> Bool #

(>) :: IgnoreMut a mut -> IgnoreMut a mut -> Bool #

(>=) :: IgnoreMut a mut -> IgnoreMut a mut -> Bool #

max :: IgnoreMut a mut -> IgnoreMut a mut -> IgnoreMut a mut #

min :: IgnoreMut a mut -> IgnoreMut a mut -> IgnoreMut a mut #

newtype MaybePtr (mut :: Mutability) Source #

Wrapper for use with Untyped; see docs for Untyped.

Constructors

MaybePtr (Maybe (Ptr mut)) 

Instances

Instances details
MaybeMutable MaybePtr Source # 
Instance details

Defined in Capnp.Untyped

Methods

thaw :: (PrimMonad m, PrimState m ~ s) => MaybePtr 'Const -> m (MaybePtr ('Mut s)) Source #

freeze :: (PrimMonad m, PrimState m ~ s) => MaybePtr ('Mut s) -> m (MaybePtr 'Const) Source #

unsafeThaw :: (PrimMonad m, PrimState m ~ s) => MaybePtr 'Const -> m (MaybePtr ('Mut s)) Source #

unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => MaybePtr ('Mut s) -> m (MaybePtr 'Const) Source #

type family Unwrapped a where ... Source #

Normalizes types returned by Untyped; see docs for Untyped.

Equations

Unwrapped (IgnoreMut a mut) = a 
Unwrapped (MaybePtr mut) = Maybe (Ptr mut) 
Unwrapped a = a 

Relating the representations of lists & their elements.

class Element (r :: Repr) where Source #

Element supports converting between values of representation ElemRepr (ListReprFor r) and values of representation r.

At a glance, you might expect this to just be a no-op, but it is actually *not* always the case that ElemRepr (ListReprFor r) ~ r; in the case of pointer types, ListReprFor r can contain arbitrary pointers, so information is lost, and it is possible for the list to contain pointers of the incorrect type. In this case, fromElement will throw an error.

toElement is more trivial.

Methods

fromElement :: forall m mut. ReadCtx m mut => Message mut -> Unwrapped (Untyped (ElemRepr (ListReprFor r)) mut) -> m (Unwrapped (Untyped r mut)) Source #

toElement :: Unwrapped (Untyped r mut) -> Unwrapped (Untyped (ElemRepr (ListReprFor r)) mut) Source #

Instances

Instances details
Element ('Data sz) Source # 
Instance details

Defined in Capnp.Untyped

Methods

fromElement :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Unwrapped (Untyped (ElemRepr (ListReprFor ('Data sz))) mut) -> m (Unwrapped (Untyped ('Data sz) mut)) Source #

toElement :: forall (mut :: Mutability). Unwrapped (Untyped ('Data sz) mut) -> Unwrapped (Untyped (ElemRepr (ListReprFor ('Data sz))) mut) Source #

Element ('Ptr ('Just 'Cap)) Source # 
Instance details

Defined in Capnp.Untyped

Methods

fromElement :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Unwrapped (Untyped (ElemRepr (ListReprFor ('Ptr ('Just 'Cap)))) mut) -> m (Unwrapped (Untyped ('Ptr ('Just 'Cap)) mut)) Source #

toElement :: forall (mut :: Mutability). Unwrapped (Untyped ('Ptr ('Just 'Cap)) mut) -> Unwrapped (Untyped (ElemRepr (ListReprFor ('Ptr ('Just 'Cap)))) mut) Source #

IsPtrRepr ('Just ('List a)) => Element ('Ptr ('Just ('List a))) Source # 
Instance details

Defined in Capnp.Untyped

Methods

fromElement :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Unwrapped (Untyped (ElemRepr (ListReprFor ('Ptr ('Just ('List a))))) mut) -> m (Unwrapped (Untyped ('Ptr ('Just ('List a))) mut)) Source #

toElement :: forall (mut :: Mutability). Unwrapped (Untyped ('Ptr ('Just ('List a))) mut) -> Unwrapped (Untyped (ElemRepr (ListReprFor ('Ptr ('Just ('List a))))) mut) Source #

Element ('Ptr ('Just 'Struct)) Source # 
Instance details

Defined in Capnp.Untyped

Methods

fromElement :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Unwrapped (Untyped (ElemRepr (ListReprFor ('Ptr ('Just 'Struct)))) mut) -> m (Unwrapped (Untyped ('Ptr ('Just 'Struct)) mut)) Source #

toElement :: forall (mut :: Mutability). Unwrapped (Untyped ('Ptr ('Just 'Struct)) mut) -> Unwrapped (Untyped (ElemRepr (ListReprFor ('Ptr ('Just 'Struct)))) mut) Source #

Element ('Ptr ('Nothing :: Maybe PtrRepr)) Source # 
Instance details

Defined in Capnp.Untyped

Methods

fromElement :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Unwrapped (Untyped (ElemRepr (ListReprFor ('Ptr 'Nothing))) mut) -> m (Unwrapped (Untyped ('Ptr 'Nothing) mut)) Source #

toElement :: forall (mut :: Mutability). Unwrapped (Untyped ('Ptr 'Nothing) mut) -> Unwrapped (Untyped (ElemRepr (ListReprFor ('Ptr 'Nothing))) mut) Source #

class Element r => ListItem (r :: Repr) where Source #

ListItem r indicates that r is a representation for elements of some list type. Not every representation is covered; instances exist only for r where ElemRepr (ListReprFor r) ~ r.

Minimal complete definition

Nothing

Methods

length :: ListOf r mut -> Int Source #

Returns the length of a list

default length :: ListRepOf r ~ NormalList => ListOf r mut -> Int Source #

unsafeIndex :: ReadCtx m mut => Int -> ListOf r mut -> m (Unwrapped (Untyped r mut)) Source #

default unsafeIndex :: forall m mut. (ReadCtx m mut, Integral (Unwrapped (Untyped r mut)), ListRepOf r ~ NormalList, FiniteBits (Unwrapped (Untyped r mut))) => Int -> ListOf r mut -> m (Unwrapped (Untyped r mut)) Source #

unsafeSetIndex :: (RWCtx m s, a ~ Unwrapped (Untyped r ('Mut s))) => a -> Int -> ListOf r ('Mut s) -> m () Source #

default unsafeSetIndex :: forall m s a. (RWCtx m s, a ~ Unwrapped (Untyped r ('Mut s)), ListRepOf r ~ NormalList, Integral a, Bounded a, FiniteBits a) => a -> Int -> ListOf r ('Mut s) -> m () Source #

unsafeTake :: Int -> ListOf r mut -> ListOf r mut Source #

default unsafeTake :: ListRepOf r ~ NormalList => Int -> ListOf r mut -> ListOf r mut Source #

checkListOf :: ReadCtx m mut => ListOf r mut -> m () Source #

default checkListOf :: forall m mut. (ReadCtx m mut, ListRepOf r ~ NormalList, FiniteBits (Untyped r mut)) => ListOf r mut -> m () Source #

copyListOf :: RWCtx m s => ListOf r ('Mut s) -> ListOf r ('Mut s) -> m () Source #

Make a copy of the list, in the target message.

Instances

Instances details
ListItem ('Data 'Sz0) Source # 
Instance details

Defined in Capnp.Untyped

Methods

length :: forall (mut :: Mutability). ListOf ('Data 'Sz0) mut -> Int Source #

unsafeIndex :: forall m (mut :: Mutability). ReadCtx m mut => Int -> ListOf ('Data 'Sz0) mut -> m (Unwrapped (Untyped ('Data 'Sz0) mut)) Source #

unsafeSetIndex :: (RWCtx m s, a ~ Unwrapped (Untyped ('Data 'Sz0) ('Mut s))) => a -> Int -> ListOf ('Data 'Sz0) ('Mut s) -> m () Source #

unsafeTake :: forall (mut :: Mutability). Int -> ListOf ('Data 'Sz0) mut -> ListOf ('Data 'Sz0) mut Source #

checkListOf :: forall m (mut :: Mutability). ReadCtx m mut => ListOf ('Data 'Sz0) mut -> m () Source #

copyListOf :: RWCtx m s => ListOf ('Data 'Sz0) ('Mut s) -> ListOf ('Data 'Sz0) ('Mut s) -> m () Source #

ListItem ('Data 'Sz1) Source # 
Instance details

Defined in Capnp.Untyped

Methods

length :: forall (mut :: Mutability). ListOf ('Data 'Sz1) mut -> Int Source #

unsafeIndex :: forall m (mut :: Mutability). ReadCtx m mut => Int -> ListOf ('Data 'Sz1) mut -> m (Unwrapped (Untyped ('Data 'Sz1) mut)) Source #

unsafeSetIndex :: (RWCtx m s, a ~ Unwrapped (Untyped ('Data 'Sz1) ('Mut s))) => a -> Int -> ListOf ('Data 'Sz1) ('Mut s) -> m () Source #

unsafeTake :: forall (mut :: Mutability). Int -> ListOf ('Data 'Sz1) mut -> ListOf ('Data 'Sz1) mut Source #

checkListOf :: forall m (mut :: Mutability). ReadCtx m mut => ListOf ('Data 'Sz1) mut -> m () Source #

copyListOf :: RWCtx m s => ListOf ('Data 'Sz1) ('Mut s) -> ListOf ('Data 'Sz1) ('Mut s) -> m () Source #

ListItem ('Data 'Sz16) Source # 
Instance details

Defined in Capnp.Untyped

Methods

length :: forall (mut :: Mutability). ListOf ('Data 'Sz16) mut -> Int Source #

unsafeIndex :: forall m (mut :: Mutability). ReadCtx m mut => Int -> ListOf ('Data 'Sz16) mut -> m (Unwrapped (Untyped ('Data 'Sz16) mut)) Source #

unsafeSetIndex :: (RWCtx m s, a ~ Unwrapped (Untyped ('Data 'Sz16) ('Mut s))) => a -> Int -> ListOf ('Data 'Sz16) ('Mut s) -> m () Source #

unsafeTake :: forall (mut :: Mutability). Int -> ListOf ('Data 'Sz16) mut -> ListOf ('Data 'Sz16) mut Source #

checkListOf :: forall m (mut :: Mutability). ReadCtx m mut => ListOf ('Data 'Sz16) mut -> m () Source #

copyListOf :: RWCtx m s => ListOf ('Data 'Sz16) ('Mut s) -> ListOf ('Data 'Sz16) ('Mut s) -> m () Source #

ListItem ('Data 'Sz32) Source # 
Instance details

Defined in Capnp.Untyped

Methods

length :: forall (mut :: Mutability). ListOf ('Data 'Sz32) mut -> Int Source #

unsafeIndex :: forall m (mut :: Mutability). ReadCtx m mut => Int -> ListOf ('Data 'Sz32) mut -> m (Unwrapped (Untyped ('Data 'Sz32) mut)) Source #

unsafeSetIndex :: (RWCtx m s, a ~ Unwrapped (Untyped ('Data 'Sz32) ('Mut s))) => a -> Int -> ListOf ('Data 'Sz32) ('Mut s) -> m () Source #

unsafeTake :: forall (mut :: Mutability). Int -> ListOf ('Data 'Sz32) mut -> ListOf ('Data 'Sz32) mut Source #

checkListOf :: forall m (mut :: Mutability). ReadCtx m mut => ListOf ('Data 'Sz32) mut -> m () Source #

copyListOf :: RWCtx m s => ListOf ('Data 'Sz32) ('Mut s) -> ListOf ('Data 'Sz32) ('Mut s) -> m () Source #

ListItem ('Data 'Sz64) Source # 
Instance details

Defined in Capnp.Untyped

Methods

length :: forall (mut :: Mutability). ListOf ('Data 'Sz64) mut -> Int Source #

unsafeIndex :: forall m (mut :: Mutability). ReadCtx m mut => Int -> ListOf ('Data 'Sz64) mut -> m (Unwrapped (Untyped ('Data 'Sz64) mut)) Source #

unsafeSetIndex :: (RWCtx m s, a ~ Unwrapped (Untyped ('Data 'Sz64) ('Mut s))) => a -> Int -> ListOf ('Data 'Sz64) ('Mut s) -> m () Source #

unsafeTake :: forall (mut :: Mutability). Int -> ListOf ('Data 'Sz64) mut -> ListOf ('Data 'Sz64) mut Source #

checkListOf :: forall m (mut :: Mutability). ReadCtx m mut => ListOf ('Data 'Sz64) mut -> m () Source #

copyListOf :: RWCtx m s => ListOf ('Data 'Sz64) ('Mut s) -> ListOf ('Data 'Sz64) ('Mut s) -> m () Source #

ListItem ('Data 'Sz8) Source # 
Instance details

Defined in Capnp.Untyped

Methods

length :: forall (mut :: Mutability). ListOf ('Data 'Sz8) mut -> Int Source #

unsafeIndex :: forall m (mut :: Mutability). ReadCtx m mut => Int -> ListOf ('Data 'Sz8) mut -> m (Unwrapped (Untyped ('Data 'Sz8) mut)) Source #

unsafeSetIndex :: (RWCtx m s, a ~ Unwrapped (Untyped ('Data 'Sz8) ('Mut s))) => a -> Int -> ListOf ('Data 'Sz8) ('Mut s) -> m () Source #

unsafeTake :: forall (mut :: Mutability). Int -> ListOf ('Data 'Sz8) mut -> ListOf ('Data 'Sz8) mut Source #

checkListOf :: forall m (mut :: Mutability). ReadCtx m mut => ListOf ('Data 'Sz8) mut -> m () Source #

copyListOf :: RWCtx m s => ListOf ('Data 'Sz8) ('Mut s) -> ListOf ('Data 'Sz8) ('Mut s) -> m () Source #

ListItem ('Ptr ('Just 'Struct)) Source # 
Instance details

Defined in Capnp.Untyped

Methods

length :: forall (mut :: Mutability). ListOf ('Ptr ('Just 'Struct)) mut -> Int Source #

unsafeIndex :: forall m (mut :: Mutability). ReadCtx m mut => Int -> ListOf ('Ptr ('Just 'Struct)) mut -> m (Unwrapped (Untyped ('Ptr ('Just 'Struct)) mut)) Source #

unsafeSetIndex :: (RWCtx m s, a ~ Unwrapped (Untyped ('Ptr ('Just 'Struct)) ('Mut s))) => a -> Int -> ListOf ('Ptr ('Just 'Struct)) ('Mut s) -> m () Source #

unsafeTake :: forall (mut :: Mutability). Int -> ListOf ('Ptr ('Just 'Struct)) mut -> ListOf ('Ptr ('Just 'Struct)) mut Source #

checkListOf :: forall m (mut :: Mutability). ReadCtx m mut => ListOf ('Ptr ('Just 'Struct)) mut -> m () Source #

copyListOf :: RWCtx m s => ListOf ('Ptr ('Just 'Struct)) ('Mut s) -> ListOf ('Ptr ('Just 'Struct)) ('Mut s) -> m () Source #

ListItem ('Ptr ('Nothing :: Maybe PtrRepr)) Source # 
Instance details

Defined in Capnp.Untyped

Methods

length :: forall (mut :: Mutability). ListOf ('Ptr 'Nothing) mut -> Int Source #

unsafeIndex :: forall m (mut :: Mutability). ReadCtx m mut => Int -> ListOf ('Ptr 'Nothing) mut -> m (Unwrapped (Untyped ('Ptr 'Nothing) mut)) Source #

unsafeSetIndex :: (RWCtx m s, a ~ Unwrapped (Untyped ('Ptr 'Nothing) ('Mut s))) => a -> Int -> ListOf ('Ptr 'Nothing) ('Mut s) -> m () Source #

unsafeTake :: forall (mut :: Mutability). Int -> ListOf ('Ptr 'Nothing) mut -> ListOf ('Ptr 'Nothing) mut Source #

checkListOf :: forall m (mut :: Mutability). ReadCtx m mut => ListOf ('Ptr 'Nothing) mut -> m () Source #

copyListOf :: RWCtx m s => ListOf ('Ptr 'Nothing) ('Mut s) -> ListOf ('Ptr 'Nothing) ('Mut s) -> m () Source #

type family ElemRepr (rl :: ListRepr) :: Repr where ... Source #

ElemRepr r is the representation of elements of lists with representation r.

type family ListReprFor (e :: Repr) :: ListRepr where ... Source #

ListReprFor e is the representation of lists with elements whose representation is e.

Working with pointers

class IsPtrRepr (r :: Maybe PtrRepr) where Source #

Operations on types with pointer representations.

Methods

toPtr :: Unwrapped (Untyped ('Ptr r) mut) -> Maybe (Ptr mut) Source #

Convert an untyped value of this representation to an AnyPointer.

fromPtr :: ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (Unwrapped (Untyped ('Ptr r) mut)) Source #

Extract a value with this representation from an AnyPointer, failing if the pointer is the wrong type for this representation.

Instances

Instances details
IsPtrRepr ('Nothing :: Maybe PtrRepr) Source # 
Instance details

Defined in Capnp.Untyped

Methods

toPtr :: forall (mut :: Mutability). Unwrapped (Untyped ('Ptr 'Nothing) mut) -> Maybe (Ptr mut) Source #

fromPtr :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (Unwrapped (Untyped ('Ptr 'Nothing) mut)) Source #

IsPtrRepr ('Just 'Cap) Source # 
Instance details

Defined in Capnp.Untyped

Methods

toPtr :: forall (mut :: Mutability). Unwrapped (Untyped ('Ptr ('Just 'Cap)) mut) -> Maybe (Ptr mut) Source #

fromPtr :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (Unwrapped (Untyped ('Ptr ('Just 'Cap)) mut)) Source #

IsListPtrRepr r => IsPtrRepr ('Just ('List ('Just r))) Source # 
Instance details

Defined in Capnp.Untyped

Methods

toPtr :: forall (mut :: Mutability). Unwrapped (Untyped ('Ptr ('Just ('List ('Just r)))) mut) -> Maybe (Ptr mut) Source #

fromPtr :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (Unwrapped (Untyped ('Ptr ('Just ('List ('Just r)))) mut)) Source #

IsPtrRepr ('Just ('List ('Nothing :: Maybe ListRepr))) Source # 
Instance details

Defined in Capnp.Untyped

Methods

toPtr :: forall (mut :: Mutability). Unwrapped (Untyped ('Ptr ('Just ('List 'Nothing))) mut) -> Maybe (Ptr mut) Source #

fromPtr :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (Unwrapped (Untyped ('Ptr ('Just ('List 'Nothing))) mut)) Source #

IsPtrRepr ('Just 'Struct) Source # 
Instance details

Defined in Capnp.Untyped

Methods

toPtr :: forall (mut :: Mutability). Unwrapped (Untyped ('Ptr ('Just 'Struct)) mut) -> Maybe (Ptr mut) Source #

fromPtr :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (Unwrapped (Untyped ('Ptr ('Just 'Struct)) mut)) Source #

class IsListPtrRepr (r :: ListRepr) where Source #

Operations on types with list representations.

Methods

rToList :: UntypedSomeList r mut -> List mut Source #

Convert an untyped value of this representation to an AnyList.

rFromList :: ReadCtx m mut => List mut -> m (UntypedSomeList r mut) Source #

Extract a value with this representation from an AnyList, failing if the list is the wrong type for this representation.

rFromListMsg :: ReadCtx m mut => Message mut -> m (UntypedSomeList r mut) Source #

Create a zero-length value with this representation, living in the provided message.

Instances

Instances details
IsListPtrRepr 'ListComposite Source # 
Instance details

Defined in Capnp.Untyped

Methods

rToList :: forall (mut :: Mutability). UntypedSomeList 'ListComposite mut -> List mut Source #

rFromList :: forall m (mut :: Mutability). ReadCtx m mut => List mut -> m (UntypedSomeList 'ListComposite mut) Source #

rFromListMsg :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> m (UntypedSomeList 'ListComposite mut) Source #

IsListPtrRepr ('ListNormal ('NormalListData 'Sz0)) Source # 
Instance details

Defined in Capnp.Untyped

Methods

rToList :: forall (mut :: Mutability). UntypedSomeList ('ListNormal ('NormalListData 'Sz0)) mut -> List mut Source #

rFromList :: forall m (mut :: Mutability). ReadCtx m mut => List mut -> m (UntypedSomeList ('ListNormal ('NormalListData 'Sz0)) mut) Source #

rFromListMsg :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> m (UntypedSomeList ('ListNormal ('NormalListData 'Sz0)) mut) Source #

IsListPtrRepr ('ListNormal ('NormalListData 'Sz1)) Source # 
Instance details

Defined in Capnp.Untyped

Methods

rToList :: forall (mut :: Mutability). UntypedSomeList ('ListNormal ('NormalListData 'Sz1)) mut -> List mut Source #

rFromList :: forall m (mut :: Mutability). ReadCtx m mut => List mut -> m (UntypedSomeList ('ListNormal ('NormalListData 'Sz1)) mut) Source #

rFromListMsg :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> m (UntypedSomeList ('ListNormal ('NormalListData 'Sz1)) mut) Source #

IsListPtrRepr ('ListNormal ('NormalListData 'Sz16)) Source # 
Instance details

Defined in Capnp.Untyped

Methods

rToList :: forall (mut :: Mutability). UntypedSomeList ('ListNormal ('NormalListData 'Sz16)) mut -> List mut Source #

rFromList :: forall m (mut :: Mutability). ReadCtx m mut => List mut -> m (UntypedSomeList ('ListNormal ('NormalListData 'Sz16)) mut) Source #

rFromListMsg :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> m (UntypedSomeList ('ListNormal ('NormalListData 'Sz16)) mut) Source #

IsListPtrRepr ('ListNormal ('NormalListData 'Sz32)) Source # 
Instance details

Defined in Capnp.Untyped

Methods

rToList :: forall (mut :: Mutability). UntypedSomeList ('ListNormal ('NormalListData 'Sz32)) mut -> List mut Source #

rFromList :: forall m (mut :: Mutability). ReadCtx m mut => List mut -> m (UntypedSomeList ('ListNormal ('NormalListData 'Sz32)) mut) Source #

rFromListMsg :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> m (UntypedSomeList ('ListNormal ('NormalListData 'Sz32)) mut) Source #

IsListPtrRepr ('ListNormal ('NormalListData 'Sz64)) Source # 
Instance details

Defined in Capnp.Untyped

Methods

rToList :: forall (mut :: Mutability). UntypedSomeList ('ListNormal ('NormalListData 'Sz64)) mut -> List mut Source #

rFromList :: forall m (mut :: Mutability). ReadCtx m mut => List mut -> m (UntypedSomeList ('ListNormal ('NormalListData 'Sz64)) mut) Source #

rFromListMsg :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> m (UntypedSomeList ('ListNormal ('NormalListData 'Sz64)) mut) Source #

IsListPtrRepr ('ListNormal ('NormalListData 'Sz8)) Source # 
Instance details

Defined in Capnp.Untyped

Methods

rToList :: forall (mut :: Mutability). UntypedSomeList ('ListNormal ('NormalListData 'Sz8)) mut -> List mut Source #

rFromList :: forall m (mut :: Mutability). ReadCtx m mut => List mut -> m (UntypedSomeList ('ListNormal ('NormalListData 'Sz8)) mut) Source #

rFromListMsg :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> m (UntypedSomeList ('ListNormal ('NormalListData 'Sz8)) mut) Source #

IsListPtrRepr ('ListNormal 'NormalListPtr) Source # 
Instance details

Defined in Capnp.Untyped

Methods

rToList :: forall (mut :: Mutability). UntypedSomeList ('ListNormal 'NormalListPtr) mut -> List mut Source #

rFromList :: forall m (mut :: Mutability). ReadCtx m mut => List mut -> m (UntypedSomeList ('ListNormal 'NormalListPtr) mut) Source #

rFromListMsg :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> m (UntypedSomeList ('ListNormal 'NormalListPtr) mut) Source #

Allocating values

class Allocate (r :: PtrRepr) where Source #

An instace of Allocate specifies how to allocate a value with a given representation. This only makes sense for pointers of course, so it is defined on PtrRepr. Of the well-kinded types, only 'List 'Nothing is missing an instance.

Associated Types

type AllocHint r Source #

Extra information needed to allocate a value:

  • For structs, the sizes of the sections.
  • For capabilities, the client to attach to the messages.
  • For lists, the length, and for composite lists, the struct sizes as well.

Methods

alloc :: RWCtx m s => Message ('Mut s) -> AllocHint r -> m (Unwrapped (UntypedSomePtr r ('Mut s))) Source #

Allocate a value of the given type.

Instances

Instances details
Allocate 'Cap Source # 
Instance details

Defined in Capnp.Untyped

Associated Types

type AllocHint 'Cap Source #

Methods

alloc :: RWCtx m s => Message ('Mut s) -> AllocHint 'Cap -> m (Unwrapped (UntypedSomePtr 'Cap ('Mut s))) Source #

Allocate 'Struct Source # 
Instance details

Defined in Capnp.Untyped

Associated Types

type AllocHint 'Struct Source #

Methods

alloc :: RWCtx m s => Message ('Mut s) -> AllocHint 'Struct -> m (Unwrapped (UntypedSomePtr 'Struct ('Mut s))) Source #

Allocate ('List ('Just 'ListComposite)) Source # 
Instance details

Defined in Capnp.Untyped

Associated Types

type AllocHint ('List ('Just 'ListComposite)) Source #

AllocateNormalList r => Allocate ('List ('Just ('ListNormal r))) Source # 
Instance details

Defined in Capnp.Untyped

Associated Types

type AllocHint ('List ('Just ('ListNormal r))) Source #

Methods

alloc :: RWCtx m s => Message ('Mut s) -> AllocHint ('List ('Just ('ListNormal r))) -> m (Unwrapped (UntypedSomePtr ('List ('Just ('ListNormal r))) ('Mut s))) Source #

class AllocateNormalList (r :: NormalListRepr) where Source #

Like Allocate, but specialized to normal (non-composite) lists.

Instead of an AllocHint type family, the hint is always an Int, which is the number of elements.

Methods

allocNormalList :: RWCtx m s => Message ('Mut s) -> Int -> m (UntypedSomeList ('ListNormal r) ('Mut s)) Source #

Instances

Instances details
AllocateNormalList 'NormalListPtr Source # 
Instance details

Defined in Capnp.Untyped

AllocateNormalList ('NormalListData 'Sz0) Source # 
Instance details

Defined in Capnp.Untyped

AllocateNormalList ('NormalListData 'Sz1) Source # 
Instance details

Defined in Capnp.Untyped

AllocateNormalList ('NormalListData 'Sz16) Source # 
Instance details

Defined in Capnp.Untyped

AllocateNormalList ('NormalListData 'Sz32) Source # 
Instance details

Defined in Capnp.Untyped

AllocateNormalList ('NormalListData 'Sz64) Source # 
Instance details

Defined in Capnp.Untyped

AllocateNormalList ('NormalListData 'Sz8) Source # 
Instance details

Defined in Capnp.Untyped

data Ptr mut Source #

A an absolute pointer to a value (of arbitrary type) in a message. Note that there is no variant for far pointers, which don't make sense with absolute addressing.

Constructors

PtrCap (Cap mut) 
PtrList (List mut) 
PtrStruct (Struct mut) 

Instances

Instances details
MaybeMutable Ptr Source # 
Instance details

Defined in Capnp.Untyped

Methods

thaw :: (PrimMonad m, PrimState m ~ s) => Ptr 'Const -> m (Ptr ('Mut s)) Source #

freeze :: (PrimMonad m, PrimState m ~ s) => Ptr ('Mut s) -> m (Ptr 'Const) Source #

unsafeThaw :: (PrimMonad m, PrimState m ~ s) => Ptr 'Const -> m (Ptr ('Mut s)) Source #

unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Ptr ('Mut s) -> m (Ptr 'Const) Source #

HasMessage Ptr Source # 
Instance details

Defined in Capnp.Untyped

Methods

message :: forall (mut :: Mutability). Unwrapped (Ptr mut) -> Message mut Source #

TraverseMsg Ptr Source # 
Instance details

Defined in Capnp.Untyped

Methods

tMsg :: forall m (mutA :: Mutability) (mutB :: Mutability). TraverseMsgCtx m mutA mutB => (Message mutA -> m (Message mutB)) -> Ptr mutA -> m (Ptr mutB) Source #

type ReprFor (Ptr mut) Source # 
Instance details

Defined in Capnp.Repr

type ReprFor (Ptr mut) = 'Ptr ('Nothing :: Maybe PtrRepr)

data List mut Source #

A list of values (of arbitrary type) in a message.

Constructors

List0 (ListOf ('Data 'Sz0) mut) 
List1 (ListOf ('Data 'Sz1) mut) 
List8 (ListOf ('Data 'Sz8) mut) 
List16 (ListOf ('Data 'Sz16) mut) 
List32 (ListOf ('Data 'Sz32) mut) 
List64 (ListOf ('Data 'Sz64) mut) 
ListPtr (ListOf ('Ptr 'Nothing) mut) 
ListStruct (ListOf ('Ptr ('Just 'Struct)) mut) 

Instances

Instances details
MaybeMutable List Source # 
Instance details

Defined in Capnp.Untyped

Methods

thaw :: (PrimMonad m, PrimState m ~ s) => List 'Const -> m (List ('Mut s)) Source #

freeze :: (PrimMonad m, PrimState m ~ s) => List ('Mut s) -> m (List 'Const) Source #

unsafeThaw :: (PrimMonad m, PrimState m ~ s) => List 'Const -> m (List ('Mut s)) Source #

unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => List ('Mut s) -> m (List 'Const) Source #

HasMessage List Source # 
Instance details

Defined in Capnp.Untyped

Methods

message :: forall (mut :: Mutability). Unwrapped (List mut) -> Message mut Source #

TraverseMsg List Source # 
Instance details

Defined in Capnp.Untyped

Methods

tMsg :: forall m (mutA :: Mutability) (mutB :: Mutability). TraverseMsgCtx m mutA mutB => (Message mutA -> m (Message mutB)) -> List mutA -> m (List mutB) Source #

type ReprFor (List mut) Source # 
Instance details

Defined in Capnp.Repr

type ReprFor (List mut) = 'Ptr ('Just ('List ('Nothing :: Maybe ListRepr)))

data Struct mut Source #

A struct value in a message.

Instances

Instances details
MaybeMutable Struct Source # 
Instance details

Defined in Capnp.Untyped

Methods

thaw :: (PrimMonad m, PrimState m ~ s) => Struct 'Const -> m (Struct ('Mut s)) Source #

freeze :: (PrimMonad m, PrimState m ~ s) => Struct ('Mut s) -> m (Struct 'Const) Source #

unsafeThaw :: (PrimMonad m, PrimState m ~ s) => Struct 'Const -> m (Struct ('Mut s)) Source #

unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Struct ('Mut s) -> m (Struct 'Const) Source #

HasMessage Struct Source # 
Instance details

Defined in Capnp.Untyped

Methods

message :: forall (mut :: Mutability). Unwrapped (Struct mut) -> Message mut Source #

MessageDefault Struct Source # 
Instance details

Defined in Capnp.Untyped

Methods

messageDefault :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> m (Unwrapped (Struct mut)) Source #

TraverseMsg Struct Source # 
Instance details

Defined in Capnp.Untyped

Methods

tMsg :: forall m (mutA :: Mutability) (mutB :: Mutability). TraverseMsgCtx m mutA mutB => (Message mutA -> m (Message mutB)) -> Struct mutA -> m (Struct mutB) Source #

type ReprFor (Struct mut) Source # 
Instance details

Defined in Capnp.Repr

type ReprFor (Struct mut) = 'Ptr ('Just 'Struct)

data ListOf r mut Source #

A list of values with representation r in a message.

Instances

Instances details
MaybeMutable (ListRepOf r) => MaybeMutable (ListOf r) Source # 
Instance details

Defined in Capnp.Untyped

Methods

thaw :: (PrimMonad m, PrimState m ~ s) => ListOf r 'Const -> m (ListOf r ('Mut s)) Source #

freeze :: (PrimMonad m, PrimState m ~ s) => ListOf r ('Mut s) -> m (ListOf r 'Const) Source #

unsafeThaw :: (PrimMonad m, PrimState m ~ s) => ListOf r 'Const -> m (ListOf r ('Mut s)) Source #

unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => ListOf r ('Mut s) -> m (ListOf r 'Const) Source #

HasMessage (ListOf ('Ptr ('Just 'Struct))) Source # 
Instance details

Defined in Capnp.Untyped

Methods

message :: forall (mut :: Mutability). Unwrapped (ListOf ('Ptr ('Just 'Struct)) mut) -> Message mut Source #

ListRepOf r ~ NormalList => HasMessage (ListOf r) Source # 
Instance details

Defined in Capnp.Untyped

Methods

message :: forall (mut :: Mutability). Unwrapped (ListOf r mut) -> Message mut Source #

MessageDefault (ListOf ('Ptr ('Just 'Struct))) Source # 
Instance details

Defined in Capnp.Untyped

Methods

messageDefault :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> m (Unwrapped (ListOf ('Ptr ('Just 'Struct)) mut)) Source #

ListRepOf r ~ NormalList => MessageDefault (ListOf r) Source # 
Instance details

Defined in Capnp.Untyped

Methods

messageDefault :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> m (Unwrapped (ListOf r mut)) Source #

TraverseMsg (ListRepOf r) => TraverseMsg (ListOf r) Source # 
Instance details

Defined in Capnp.Untyped

Methods

tMsg :: forall m (mutA :: Mutability) (mutB :: Mutability). TraverseMsgCtx m mutA mutB => (Message mutA -> m (Message mutB)) -> ListOf r mutA -> m (ListOf r mutB) Source #

type ReprFor (ListOf r mut) Source # 
Instance details

Defined in Capnp.Repr

type ReprFor (ListOf r mut) = 'Ptr ('Just ('List ('Just (ListReprFor r))))

data Cap mut Source #

A Capability in a message.

Instances

Instances details
MaybeMutable Cap Source # 
Instance details

Defined in Capnp.Untyped

Methods

thaw :: (PrimMonad m, PrimState m ~ s) => Cap 'Const -> m (Cap ('Mut s)) Source #

freeze :: (PrimMonad m, PrimState m ~ s) => Cap ('Mut s) -> m (Cap 'Const) Source #

unsafeThaw :: (PrimMonad m, PrimState m ~ s) => Cap 'Const -> m (Cap ('Mut s)) Source #

unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Cap ('Mut s) -> m (Cap 'Const) Source #

HasMessage Cap Source # 
Instance details

Defined in Capnp.Untyped

Methods

message :: forall (mut :: Mutability). Unwrapped (Cap mut) -> Message mut Source #

TraverseMsg Cap Source # 
Instance details

Defined in Capnp.Untyped

Methods

tMsg :: forall m (mutA :: Mutability) (mutB :: Mutability). TraverseMsgCtx m mutA mutB => (Message mutA -> m (Message mutB)) -> Cap mutA -> m (Cap mutB) Source #

type ReprFor (Cap mut) Source # 
Instance details

Defined in Capnp.Repr

type ReprFor (Cap mut) = 'Ptr ('Just 'Cap)

structByteCount :: Struct mut -> ByteCount Source #

Get the size (in bytes) of a struct's data section.

structWordCount :: Struct mut -> WordCount Source #

Get the size (in words) of a struct's data section.

structPtrCount :: Struct mut -> Word16 Source #

Get the size of a struct's pointer section.

structListByteCount :: ListOf ('Ptr ('Just 'Struct)) mut -> ByteCount Source #

Get the size (in words) of the data sections in a struct list.

structListWordCount :: ListOf ('Ptr ('Just 'Struct)) mut -> WordCount Source #

Get the size (in words) of the data sections in a struct list.

structListPtrCount :: ListOf ('Ptr ('Just 'Struct)) mut -> Word16 Source #

Get the size of the pointer sections in a struct list.

getData :: ReadCtx m msg => Int -> Struct msg -> m Word64 Source #

getData i struct gets the ith word from the struct's data section, returning 0 if it is absent.

getPtr :: ReadCtx m msg => Int -> Struct msg -> m (Maybe (Ptr msg)) Source #

getPtr i struct gets the ith word from the struct's pointer section, returning Nothing if it is absent.

setData :: (ReadCtx m ('Mut s), WriteCtx m s) => Word64 -> Int -> Struct ('Mut s) -> m () Source #

setData value i struct sets the ith word in the struct's data section to value.

setPtr :: (ReadCtx m ('Mut s), WriteCtx m s) => Maybe (Ptr ('Mut s)) -> Int -> Struct ('Mut s) -> m () Source #

setData value i struct sets the ith pointer in the struct's pointer section to value.

copyStruct :: RWCtx m s => Struct ('Mut s) -> Struct ('Mut s) -> m () Source #

copyStruct dest src copies the source struct to the destination struct.

copyPtr :: RWCtx m s => Message ('Mut s) -> Maybe (Ptr ('Mut s)) -> m (Maybe (Ptr ('Mut s))) Source #

Make a copy of the value at the pointer, in the target message.

copyList :: RWCtx m s => Message ('Mut s) -> List ('Mut s) -> m (List ('Mut s)) Source #

Make a copy of the list, in the target message.

copyCap :: RWCtx m s => Message ('Mut s) -> Cap ('Mut s) -> m (Cap ('Mut s)) Source #

Make a copy of a capability inside the target message.

getClient :: ReadCtx m mut => Cap mut -> m Client Source #

Extract a client (indepedent of the messsage) from the capability.

get :: ReadCtx m mut => WordPtr mut -> m (Maybe (Ptr mut)) Source #

get ptr returns the Ptr stored at ptr. Deducts 1 from the quota for each word read (which may be multiple in the case of far pointers).

index :: (ReadCtx m mut, ListItem r) => Int -> ListOf r mut -> m (Unwrapped (Untyped r mut)) Source #

index i list returns the ith element in list. Deducts 1 from the quota

setIndex :: (RWCtx m s, ListItem r) => Unwrapped (Untyped r ('Mut s)) -> Int -> ListOf r ('Mut s) -> m () Source #

'setIndex value i list Set the ith element of list to value.

take :: (ListItem r, MonadThrow m) => Int -> ListOf r mut -> m (ListOf r mut) Source #

Return a prefix of the list, of the given length.

rootPtr :: ReadCtx m mut => Message mut -> m (Struct mut) Source #

Returns the root pointer of a message.

setRoot :: WriteCtx m s => Struct ('Mut s) -> m () Source #

Make the given struct the root object of its message.

rawBytes :: ReadCtx m 'Const => ListOf ('Data 'Sz8) 'Const -> m ByteString Source #

rawBytes returns the raw bytes corresponding to the list.

type ReadCtx m mut = (MonadReadMessage mut m, MonadThrow m, MonadLimit m) Source #

Type (constraint) synonym for the constraints needed for most read operations.

type RWCtx m s = (ReadCtx m ('Mut s), WriteCtx m s) Source #

Synonym for ReadCtx + WriteCtx

class HasMessage (f :: Mutability -> Type) where Source #

Types whose storage is owned by a message..

Methods

message :: Unwrapped (f mut) -> Message mut Source #

Get the message in which the value is stored.

Instances

Instances details
HasMessage WordPtr Source # 
Instance details

Defined in Capnp.Untyped

Methods

message :: forall (mut :: Mutability). Unwrapped (WordPtr mut) -> Message mut Source #

HasMessage Cap Source # 
Instance details

Defined in Capnp.Untyped

Methods

message :: forall (mut :: Mutability). Unwrapped (Cap mut) -> Message mut Source #

HasMessage List Source # 
Instance details

Defined in Capnp.Untyped

Methods

message :: forall (mut :: Mutability). Unwrapped (List mut) -> Message mut Source #

HasMessage Ptr Source # 
Instance details

Defined in Capnp.Untyped

Methods

message :: forall (mut :: Mutability). Unwrapped (Ptr mut) -> Message mut Source #

HasMessage Struct Source # 
Instance details

Defined in Capnp.Untyped

Methods

message :: forall (mut :: Mutability). Unwrapped (Struct mut) -> Message mut Source #

HasMessage (Untyped (ReprFor a)) => HasMessage (Raw a) Source # 
Instance details

Defined in Capnp.Repr

Methods

message :: forall (mut :: Mutability). Unwrapped (Raw a mut) -> Message mut Source #

HasMessage (ListOf ('Ptr ('Just 'Struct))) Source # 
Instance details

Defined in Capnp.Untyped

Methods

message :: forall (mut :: Mutability). Unwrapped (ListOf ('Ptr ('Just 'Struct)) mut) -> Message mut Source #

ListRepOf r ~ NormalList => HasMessage (ListOf r) Source # 
Instance details

Defined in Capnp.Untyped

Methods

message :: forall (mut :: Mutability). Unwrapped (ListOf r mut) -> Message mut Source #

class HasMessage f => MessageDefault f where Source #

Types which have a "default" value, but require a message to construct it.

The default is usually conceptually zero-size. This is mostly useful for generated code, so that it can use standard decoding techniques on default values.

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (Unwrapped (f mut)) Source #

Instances

Instances details
MessageDefault Struct Source # 
Instance details

Defined in Capnp.Untyped

Methods

messageDefault :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> m (Unwrapped (Struct mut)) Source #

MessageDefault (Untyped (ReprFor a)) => MessageDefault (Raw a) Source # 
Instance details

Defined in Capnp.Repr

Methods

messageDefault :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> m (Unwrapped (Raw a mut)) Source #

MessageDefault (ListOf ('Ptr ('Just 'Struct))) Source # 
Instance details

Defined in Capnp.Untyped

Methods

messageDefault :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> m (Unwrapped (ListOf ('Ptr ('Just 'Struct)) mut)) Source #

ListRepOf r ~ NormalList => MessageDefault (ListOf r) Source # 
Instance details

Defined in Capnp.Untyped

Methods

messageDefault :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> m (Unwrapped (ListOf r mut)) Source #

allocStruct :: WriteCtx m s => Message ('Mut s) -> Word16 -> Word16 -> m (Struct ('Mut s)) Source #

Allocate a struct in the message.

allocCompositeList Source #

Arguments

:: WriteCtx m s 
=> Message ('Mut s)

The message to allocate in.

-> Word16

The size of the data section

-> Word16

The size of the pointer section

-> Int

The length of the list in elements.

-> m (ListOf ('Ptr ('Just 'Struct)) ('Mut s)) 

Allocate a composite list.

allocList0 :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Data 'Sz0) ('Mut s)) Source #

Allocate a list of capnproto Void values.

allocList1 :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Data 'Sz1) ('Mut s)) Source #

Allocate a list of booleans

allocList8 :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Data 'Sz8) ('Mut s)) Source #

Allocate a list of 8-bit values.

allocList16 :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Data 'Sz16) ('Mut s)) Source #

Allocate a list of 16-bit values.

allocList32 :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Data 'Sz32) ('Mut s)) Source #

Allocate a list of 32-bit values.

allocList64 :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Data 'Sz64) ('Mut s)) Source #

Allocate a list of 64-bit words.

allocListPtr :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Ptr 'Nothing) ('Mut s)) Source #

Allocate a list of pointers.

appendCap :: WriteCtx m s => Message ('Mut s) -> Client -> m (Cap ('Mut s)) Source #

class TraverseMsg f where Source #

N.B. this should mostly be considered an implementation detail, but it is exposed because it is used by generated code.

TraverseMsg is similar to Traversable from the prelude, but the intent is that rather than conceptually being a "container", the instance is a value backed by a message, and the point of the type class is to be able to apply transformations to the underlying message.

We don't just use Traversable for this for two reasons:

  1. While algebraically it makes sense, it would be very unintuitive to e.g. have the Traversable instance for List not traverse over the *elements* of the list.
  2. For the instance for WordPtr, we actually need a stronger constraint than Applicative in order for the implementation to type check. A previous version of the library *did* have tMsg :: Applicative m => ..., but performance considerations eventually forced us to open up the hood a bit.

Methods

tMsg :: TraverseMsgCtx m mutA mutB => (Message mutA -> m (Message mutB)) -> f mutA -> m (f mutB) Source #

Instances

Instances details
TraverseMsg WordPtr Source # 
Instance details

Defined in Capnp.Untyped

Methods

tMsg :: forall m (mutA :: Mutability) (mutB :: Mutability). TraverseMsgCtx m mutA mutB => (Message mutA -> m (Message mutB)) -> WordPtr mutA -> m (WordPtr mutB) Source #

TraverseMsg Cap Source # 
Instance details

Defined in Capnp.Untyped

Methods

tMsg :: forall m (mutA :: Mutability) (mutB :: Mutability). TraverseMsgCtx m mutA mutB => (Message mutA -> m (Message mutB)) -> Cap mutA -> m (Cap mutB) Source #

TraverseMsg List Source # 
Instance details

Defined in Capnp.Untyped

Methods

tMsg :: forall m (mutA :: Mutability) (mutB :: Mutability). TraverseMsgCtx m mutA mutB => (Message mutA -> m (Message mutB)) -> List mutA -> m (List mutB) Source #

TraverseMsg Ptr Source # 
Instance details

Defined in Capnp.Untyped

Methods

tMsg :: forall m (mutA :: Mutability) (mutB :: Mutability). TraverseMsgCtx m mutA mutB => (Message mutA -> m (Message mutB)) -> Ptr mutA -> m (Ptr mutB) Source #

TraverseMsg Struct Source # 
Instance details

Defined in Capnp.Untyped

Methods

tMsg :: forall m (mutA :: Mutability) (mutB :: Mutability). TraverseMsgCtx m mutA mutB => (Message mutA -> m (Message mutB)) -> Struct mutA -> m (Struct mutB) Source #

TraverseMsg (ListRepOf r) => TraverseMsg (ListOf r) Source # 
Instance details

Defined in Capnp.Untyped

Methods

tMsg :: forall m (mutA :: Mutability) (mutB :: Mutability). TraverseMsgCtx m mutA mutB => (Message mutA -> m (Message mutB)) -> ListOf r mutA -> m (ListOf r mutB) Source #