capnp-0.11.0.0: Cap'n Proto for Haskell
Safe HaskellNone
LanguageHaskell2010

Capnp.Untyped.Pure

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 Capnp.Untyped.

Synopsis

Documentation

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

Instances details
Functor Slice Source # 
Instance details

Defined in Capnp.Untyped.Pure

Methods

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

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

IsList (Slice a) Source # 
Instance details

Defined in 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 Capnp.Untyped.Pure

Methods

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

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

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

Defined in 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 #

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

Defined in 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 Capnp.Untyped.Pure

Associated Types

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

Methods

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

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

Default (Slice a) Source # 
Instance details

Defined in Capnp.Untyped.Pure

Methods

def :: Slice a #

type Rep (Slice a) Source # 
Instance details

Defined in Capnp.Untyped.Pure

type Rep (Slice a) = D1 ('MetaData "Slice" "Capnp.Untyped.Pure" "capnp-0.11.0.0-50ovYl0NjrHDYHPSniP5DX" '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 Capnp.Untyped.Pure

type Item (Slice a) = Item (Vector a)

data Ptr Source #

A capnproto pointer type.

Instances

Instances details
Eq Ptr Source # 
Instance details

Defined in Capnp.Untyped.Pure

Methods

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

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

Show Ptr Source # 
Instance details

Defined in Capnp.Untyped.Pure

Methods

showsPrec :: Int -> Ptr -> ShowS #

show :: Ptr -> String #

showList :: [Ptr] -> ShowS #

Generic Ptr Source # 
Instance details

Defined in Capnp.Untyped.Pure

Associated Types

type Rep Ptr :: Type -> Type #

Methods

from :: Ptr -> Rep Ptr x #

to :: Rep Ptr x -> Ptr #

Cerialize s (Maybe Ptr) Source # 
Instance details

Defined in Capnp.Untyped.Pure

Methods

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

Decerialize (Maybe Ptr) Source # 
Instance details

Defined in Capnp.Untyped.Pure

Associated Types

type Cerial mut (Maybe Ptr) Source #

type Rep Ptr Source # 
Instance details

Defined in Capnp.Untyped.Pure

type Cerial msg (Maybe Ptr) Source # 
Instance details

Defined in Capnp.Untyped.Pure

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

data Struct Source #

A capnproto struct.

Constructors

Struct 

Fields

Instances

Instances details
Eq Struct Source # 
Instance details

Defined in Capnp.Untyped.Pure

Methods

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

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

Show Struct Source # 
Instance details

Defined in Capnp.Untyped.Pure

Generic Struct Source # 
Instance details

Defined in Capnp.Untyped.Pure

Associated Types

type Rep Struct :: Type -> Type #

Methods

from :: Struct -> Rep Struct x #

to :: Rep Struct x -> Struct #

Default Struct Source # 
Instance details

Defined in Capnp.Untyped.Pure

Methods

def :: Struct #

Decerialize Struct Source # 
Instance details

Defined in Capnp.Untyped.Pure

Associated Types

type Cerial mut Struct Source #

FromStruct 'Const Struct Source # 
Instance details

Defined in Capnp.Untyped.Pure

Cerialize s Struct Source # 
Instance details

Defined in Capnp.Untyped.Pure

Methods

cerialize :: RWCtx m s => Message ('Mut s) -> Struct -> m (Cerial ('Mut s) Struct) Source #

Marshal s Struct Source # 
Instance details

Defined in Capnp.Untyped.Pure

Methods

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

type Rep Struct Source # 
Instance details

Defined in Capnp.Untyped.Pure

type Rep Struct = D1 ('MetaData "Struct" "Capnp.Untyped.Pure" "capnp-0.11.0.0-50ovYl0NjrHDYHPSniP5DX" '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 Ptr)))))
type Cerial msg Struct Source # 
Instance details

Defined in Capnp.Untyped.Pure

type Cerial msg Struct = Struct msg

data List Source #

An untyped list.

Instances

Instances details
Eq List Source # 
Instance details

Defined in Capnp.Untyped.Pure

Methods

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

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

Show List Source # 
Instance details

Defined in Capnp.Untyped.Pure

Methods

showsPrec :: Int -> List -> ShowS #

show :: List -> String #

showList :: [List] -> ShowS #

Generic List Source # 
Instance details

Defined in Capnp.Untyped.Pure

Associated Types

type Rep List :: Type -> Type #

Methods

from :: List -> Rep List x #

to :: Rep List x -> List #

Decerialize List Source # 
Instance details

Defined in Capnp.Untyped.Pure

Associated Types

type Cerial mut List Source #

Cerialize s List Source # 
Instance details

Defined in Capnp.Untyped.Pure

Methods

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

type Rep List Source # 
Instance details

Defined in Capnp.Untyped.Pure

type Cerial msg List Source # 
Instance details

Defined in 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.