flatbuffers-0.3.0.0: Haskell implementation of the FlatBuffers protocol.
Safe HaskellNone
LanguageHaskell2010

FlatBuffers.Internal.Read

Synopsis

Documentation

newtype VOffset Source #

Constructors

VOffset 

Fields

Instances

Instances details
Enum VOffset Source # 
Instance details

Defined in FlatBuffers.Internal.Read

Eq VOffset Source # 
Instance details

Defined in FlatBuffers.Internal.Read

Methods

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

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

Integral VOffset Source # 
Instance details

Defined in FlatBuffers.Internal.Read

Num VOffset Source # 
Instance details

Defined in FlatBuffers.Internal.Read

Ord VOffset Source # 
Instance details

Defined in FlatBuffers.Internal.Read

Real VOffset Source # 
Instance details

Defined in FlatBuffers.Internal.Read

Show VOffset Source # 
Instance details

Defined in FlatBuffers.Internal.Read

newtype OffsetFromRoot Source #

Constructors

OffsetFromRoot Int32 

Instances

Instances details
Enum OffsetFromRoot Source # 
Instance details

Defined in FlatBuffers.Internal.Read

Eq OffsetFromRoot Source # 
Instance details

Defined in FlatBuffers.Internal.Read

Integral OffsetFromRoot Source # 
Instance details

Defined in FlatBuffers.Internal.Read

Num OffsetFromRoot Source # 
Instance details

Defined in FlatBuffers.Internal.Read

Ord OffsetFromRoot Source # 
Instance details

Defined in FlatBuffers.Internal.Read

Real OffsetFromRoot Source # 
Instance details

Defined in FlatBuffers.Internal.Read

Show OffsetFromRoot Source # 
Instance details

Defined in FlatBuffers.Internal.Read

data Table a Source #

A table that is being read from a flatbuffer.

Constructors

Table 

Instances

Instances details
VectorElement (Table a) Source # 
Instance details

Defined in FlatBuffers.Internal.Read

Associated Types

data Vector (Table a) Source #

data Vector (Table a) Source # 
Instance details

Defined in FlatBuffers.Internal.Read

newtype Struct a Source #

A struct that is being read from a flatbuffer.

Constructors

Struct 

Fields

Instances

Instances details
IsStruct a => VectorElement (Struct a) Source # 
Instance details

Defined in FlatBuffers.Internal.Read

Associated Types

data Vector (Struct a) Source #

data Vector (Struct a) Source # 
Instance details

Defined in FlatBuffers.Internal.Read

data Union a Source #

A union that is being read from a flatbuffer.

Constructors

Union !a 
UnionNone 
UnionUnknown !Word8 

data PositionInfo Source #

Current position in the buffer

Constructors

PositionInfo 

Fields

Instances

Instances details
HasPosition PositionInfo Source # 
Instance details

Defined in FlatBuffers.Internal.Read

class HasPosition a where Source #

Methods

getPosition :: a -> Position Source #

move :: Integral i => a -> i -> a Source #

decode :: ByteString -> Either ReadError (Table a) Source #

Deserializes a flatbuffer from a lazy ByteString.

checkFileIdentifier :: forall a. HasFileIdentifier a => ByteString -> Bool Source #

Checks if a buffer contains the file identifier for a root table a, to see if it's safe to decode it to a Table. It should be used in conjunction with -XTypeApplications.

{-# LANGUAGE TypeApplications #-}

if checkFileIdentifier @Monster bs
  then decode @Monster bs
  else return someMonster

newtype Positive a Source #

Proof that a number is strictly positive.

Constructors

Positive 

Fields

Instances

Instances details
Eq a => Eq (Positive a) Source # 
Instance details

Defined in FlatBuffers.Internal.Read

Methods

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

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

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

Defined in FlatBuffers.Internal.Read

Methods

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

show :: Positive a -> String #

showList :: [Positive a] -> ShowS #

positive :: (Num a, Ord a) => a -> Maybe (Positive a) Source #

moveToElem :: HasPosition pos => pos -> Int32 -> Int32 -> pos Source #

clamp :: Int32 -> Int32 -> Int32 Source #

clamp n upperBound truncates a value to stay between 0 and upperBound.

class VectorElement a where Source #

Associated Types

data Vector a Source #

A vector that is being read from a flatbuffer.

Methods

length :: Vector a -> Int32 Source #

Returns the size of the vector.

O(1).

unsafeIndex :: Vector a -> Int32 -> Either ReadError a Source #

Returns the item at the given index without performing the bounds check.

Given an invalid index, unsafeIndex will likely read garbage data or return a ReadError. In the case of Vector Word8, using a negative index carries the same risks as unsafeIndex (i.e. reading from outside the buffer's boundaries).

O(c), where c is the number of chunks in the underlying ByteString.

toList :: Vector a -> Either ReadError [a] Source #

Converts the vector to a list.

O(n).

take :: Int32 -> Vector a -> Vector a Source #

take n xs returns the prefix of xs of length n, or xs itself if n > length xs.

O(1).

Since: 0.2.0.0

drop :: Int32 -> Vector a -> Vector a Source #

drop n xs returns the suffix of xs after the first n elements, or [] if n > length xs.

O(c), where c is the number of chunks in the underlying ByteString.

Since: 0.2.0.0

Instances

Instances details
VectorElement Bool Source # 
Instance details

Defined in FlatBuffers.Internal.Read

Associated Types

data Vector Bool Source #

VectorElement Double Source # 
Instance details

Defined in FlatBuffers.Internal.Read

Associated Types

data Vector Double Source #

VectorElement Float Source # 
Instance details

Defined in FlatBuffers.Internal.Read

Associated Types

data Vector Float Source #

VectorElement Int8 Source # 
Instance details

Defined in FlatBuffers.Internal.Read

Associated Types

data Vector Int8 Source #

VectorElement Int16 Source # 
Instance details

Defined in FlatBuffers.Internal.Read

Associated Types

data Vector Int16 Source #

VectorElement Int32 Source # 
Instance details

Defined in FlatBuffers.Internal.Read

Associated Types

data Vector Int32 Source #

VectorElement Int64 Source # 
Instance details

Defined in FlatBuffers.Internal.Read

Associated Types

data Vector Int64 Source #

VectorElement Word8 Source # 
Instance details

Defined in FlatBuffers.Internal.Read

Associated Types

data Vector Word8 Source #

VectorElement Word16 Source # 
Instance details

Defined in FlatBuffers.Internal.Read

Associated Types

data Vector Word16 Source #

VectorElement Word32 Source # 
Instance details

Defined in FlatBuffers.Internal.Read

Associated Types

data Vector Word32 Source #

VectorElement Word64 Source # 
Instance details

Defined in FlatBuffers.Internal.Read

Associated Types

data Vector Word64 Source #

VectorElement Text Source # 
Instance details

Defined in FlatBuffers.Internal.Read

Associated Types

data Vector Text Source #

VectorElement (Union a) Source # 
Instance details

Defined in FlatBuffers.Internal.Read

Associated Types

data Vector (Union a) Source #

IsStruct a => VectorElement (Struct a) Source # 
Instance details

Defined in FlatBuffers.Internal.Read

Associated Types

data Vector (Struct a) Source #

VectorElement (Table a) Source # 
Instance details

Defined in FlatBuffers.Internal.Read

Associated Types

data Vector (Table a) Source #

index :: VectorElement a => Vector a -> Int32 -> Either ReadError a Source #

Returns the item at the given index. If the given index is negative or too large, an error is thrown.

O(c), where c is the number of chunks in the underlying ByteString.

toLazyByteString :: Vector Word8 -> ByteString Source #

Convert the vector to a lazy ByteString.

O(c), where c is the number of chunks in the underlying ByteString.

Since: 0.2.0.0

readText :: HasPosition a => a -> Either ReadError Text Source #

Follow a pointer to the position of a string and read it.

readText' :: Get (Either ReadError Text) Source #

Read a string from the current buffer position.

readTable :: PositionInfo -> Either ReadError (Table t) Source #

Follow a pointer to the position of a table and read it.

readTable' :: PositionInfo -> Either ReadError (Table t) Source #

Read a table from the current buffer position.

byteStringSafeIndex :: ByteString -> Int32 -> Either ReadError Word8 Source #

Safer version of index that doesn't throw when index is too large. Assumes i > 0.