capnp-0.2.0.0: Cap'n Proto for Haskell

Safe HaskellNone
LanguageHaskell2010

Data.Capnp.Untyped.Pure

Contents

Description

This module provides an idiomatic Haskell interface for untyped capnp data, based on algebraic datatypes. It forgoes some of the benefits of the capnp wire format in favor of a more convienient API.

In addition to the algebraic data types themselves, this module also provides support for converting from the lower-level types in Data.Capnp.Untyped.

Synopsis

Documentation

type Cap = Word32 Source #

A capability in the wire format.

newtype Slice a Source #

A one of a struct's sections (data or pointer).

This is just a newtype wrapper around ListOf (which is itself just Vector), but critically the notion of equality is different. Two slices are considered equal if all of their elements are equal, but If the slices are different lengths, missing elements are treated as having default values. Accordingly, equality is only defined if the element type is an instance of Default.

Constructors

Slice (ListOf a) 
Instances
Functor Slice Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

Methods

fmap :: (a -> b) -> Slice a -> Slice b #

(<$) :: a -> Slice b -> Slice a #

IsList (Slice a) Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

Associated Types

type Item (Slice a) :: * #

Methods

fromList :: [Item (Slice a)] -> Slice a #

fromListN :: Int -> [Item (Slice a)] -> Slice a #

toList :: Slice a -> [Item (Slice a)] #

(Default a, Eq a) => Eq (Slice a) Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

Methods

(==) :: Slice a -> Slice a -> Bool #

(/=) :: Slice a -> Slice a -> Bool #

(Ord a, Default a) => Ord (Slice a) Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

Methods

compare :: Slice a -> Slice a -> Ordering #

(<) :: Slice a -> Slice a -> Bool #

(<=) :: Slice a -> Slice a -> Bool #

(>) :: Slice a -> Slice a -> Bool #

(>=) :: Slice a -> Slice a -> Bool #

max :: Slice a -> Slice a -> Slice a #

min :: Slice a -> Slice a -> Slice a #

Read a => Read (Slice a) Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

Show a => Show (Slice a) Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

Methods

showsPrec :: Int -> Slice a -> ShowS #

show :: Slice a -> String #

showList :: [Slice a] -> ShowS #

Generic (Slice a) Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

Associated Types

type Rep (Slice a) :: * -> * #

Methods

from :: Slice a -> Rep (Slice a) x #

to :: Rep (Slice a) x -> Slice a #

Default (Slice a) Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

Methods

def :: Slice a #

type Rep (Slice a) Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

type Rep (Slice a) = D1 (MetaData "Slice" "Data.Capnp.Untyped.Pure" "capnp-0.2.0.0-GVlOuXtocAy6sjd7SXWbQY" True) (C1 (MetaCons "Slice" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ListOf a))))
type Item (Slice a) Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

type Item (Slice a) = a

data PtrType Source #

A capnproto pointer type.

Constructors

PtrStruct !Struct 
PtrList !List 
PtrCap !Cap 
Instances
Eq PtrType Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

Methods

(==) :: PtrType -> PtrType -> Bool #

(/=) :: PtrType -> PtrType -> Bool #

Read PtrType Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

Show PtrType Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

Generic PtrType Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

Associated Types

type Rep PtrType :: * -> * #

Methods

from :: PtrType -> Rep PtrType x #

to :: Rep PtrType x -> PtrType #

Cerialize s (Maybe PtrType) Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> Maybe PtrType -> m (Cerial (MutMsg s) (Maybe PtrType)) Source #

Decerialize (Maybe PtrType) Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

Associated Types

type Cerial msg (Maybe PtrType) :: * Source #

type Rep PtrType Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

type Cerial msg (Maybe PtrType) Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

type Cerial msg (Maybe PtrType) = Maybe (Ptr msg)

data Struct Source #

A capnproto struct.

Constructors

Struct 

Fields

Instances
Eq Struct Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

Methods

(==) :: Struct -> Struct -> Bool #

(/=) :: Struct -> Struct -> Bool #

Read Struct Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

Show Struct Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

Generic Struct Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

Associated Types

type Rep Struct :: * -> * #

Methods

from :: Struct -> Rep Struct x #

to :: Rep Struct x -> Struct #

Default Struct Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

Methods

def :: Struct #

Marshal Struct Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

Methods

marshalInto :: RWCtx m s => Cerial (MutMsg s) Struct -> Struct -> m () Source #

Decerialize Struct Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

Associated Types

type Cerial msg Struct :: * Source #

Cerialize s Struct Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> Struct -> m (Cerial (MutMsg s) Struct) Source #

type Rep Struct Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

type Rep Struct = D1 (MetaData "Struct" "Data.Capnp.Untyped.Pure" "capnp-0.2.0.0-GVlOuXtocAy6sjd7SXWbQY" False) (C1 (MetaCons "Struct" PrefixI True) (S1 (MetaSel (Just "structData") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Slice Word64)) :*: S1 (MetaSel (Just "structPtrs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Slice (Maybe PtrType)))))
type Cerial msg Struct Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

type Cerial msg Struct = Struct msg

data List Source #

An untyped list.

Instances
Eq List Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

Methods

(==) :: List -> List -> Bool #

(/=) :: List -> List -> Bool #

Read List Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

Show List Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

Methods

showsPrec :: Int -> List -> ShowS #

show :: List -> String #

showList :: [List] -> ShowS #

Generic List Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

Associated Types

type Rep List :: * -> * #

Methods

from :: List -> Rep List x #

to :: Rep List x -> List #

Decerialize List Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

Associated Types

type Cerial msg List :: * Source #

Cerialize s List Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> List -> m (Cerial (MutMsg s) List) Source #

type Rep List Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

type Cerial msg List Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

type Cerial msg List = List msg

type ListOf a = Vector a Source #

Alias for Vector. Using this alias may make upgrading to future versions of the library easier, as we will likely switch to a more efficient representation at some point.

length :: ListOf a -> Int Source #

Alias for vector's length.

sliceIndex :: Default a => Int -> Slice a -> a Source #

Index into a slice, returning a default value if the the index is past the end of the array.

Orphan instances

(ListElem ConstMsg (Cerial ConstMsg a), Decerialize a) => Decerialize (ListOf a) Source # 
Instance details

Associated Types

type Cerial msg (ListOf a) :: * Source #