| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
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.
Documentation
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.
Instances
| Functor Slice Source # | |
| IsList (Slice a) Source # | |
| (Default a, Eq a) => Eq (Slice a) Source # | |
| (Ord a, Default a) => Ord (Slice a) Source # | |
| Defined in Data.Capnp.Untyped.Pure | |
| Read a => Read (Slice a) Source # | |
| Show a => Show (Slice a) Source # | |
| Generic (Slice a) Source # | |
| Default (Slice a) Source # | |
| Defined in Data.Capnp.Untyped.Pure | |
| type Rep (Slice a) Source # | |
| Defined in Data.Capnp.Untyped.Pure | |
| type Item (Slice a) Source # | |
| Defined in Data.Capnp.Untyped.Pure | |
A capnproto pointer type.
Instances
| Eq PtrType Source # | |
| Read PtrType Source # | |
| Show PtrType Source # | |
| Generic PtrType Source # | |
| Cerialize s (Maybe PtrType) Source # | |
| Decerialize (Maybe PtrType) Source # | |
| type Rep PtrType Source # | |
| Defined in Data.Capnp.Untyped.Pure type Rep PtrType = D1 (MetaData "PtrType" "Data.Capnp.Untyped.Pure" "capnp-0.1.0.0-IBFPKP2JelH5Ibzi4f2YyO" False) (C1 (MetaCons "PtrStruct" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Struct)) :+: (C1 (MetaCons "PtrList" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 List)) :+: C1 (MetaCons "PtrCap" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Cap)))) | |
| type Cerial msg (Maybe PtrType) Source # | |
A capnproto struct.
Constructors
| Struct | |
| Fields 
 | |
Instances
| Eq Struct Source # | |
| Read Struct Source # | |
| Show Struct Source # | |
| Generic Struct Source # | |
| Marshal Struct Source # | |
| Defined in Data.Capnp.Untyped.Pure | |
| Decerialize Struct Source # | |
| Default Struct Source # | |
| Defined in Data.Capnp.Untyped.Pure | |
| Cerialize s Struct Source # | |
| type Rep Struct Source # | |
| Defined in Data.Capnp.Untyped.Pure type Rep Struct = D1 (MetaData "Struct" "Data.Capnp.Untyped.Pure" "capnp-0.1.0.0-IBFPKP2JelH5Ibzi4f2YyO" 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 # | |
| Defined in Data.Capnp.Untyped.Pure | |
An untyped list.
Constructors
| List0 (ListOf ()) | |
| List1 (ListOf Bool) | |
| List8 (ListOf Word8) | |
| List16 (ListOf Word16) | |
| List32 (ListOf Word32) | |
| List64 (ListOf Word64) | |
| ListPtr (ListOf (Maybe PtrType)) | |
| ListStruct (ListOf Struct) | 
Instances
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.
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.