Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type ReadError = String
- newtype TableIndex = TableIndex {}
- newtype VOffset = VOffset {}
- newtype OffsetFromRoot = OffsetFromRoot Int32
- data Table a = Table {
- vtable :: !Position
- tablePos :: !PositionInfo
- newtype Struct a = Struct {}
- data Union a
- = Union !a
- | UnionNone
- | UnionUnknown !Word8
- type Position = ByteString
- data PositionInfo = PositionInfo {}
- class HasPosition a where
- getPosition :: a -> Position
- move :: Integral i => a -> i -> a
- decode :: ByteString -> Either ReadError (Table a)
- checkFileIdentifier :: forall a. HasFileIdentifier a => ByteString -> Bool
- checkFileIdentifier' :: FileIdentifier -> ByteString -> Bool
- newtype Positive a = Positive {
- getPositive :: a
- positive :: (Num a, Ord a) => a -> Maybe (Positive a)
- moveToElem :: HasPosition pos => pos -> Int32 -> Int32 -> pos
- checkIndexBounds :: Int32 -> Int32 -> Int32
- inlineVectorToList :: Get a -> Int32 -> Position -> Either ReadError [a]
- clamp :: Int32 -> Int32 -> Int32
- class VectorElement a where
- index :: VectorElement a => Vector a -> Int32 -> Either ReadError a
- toByteString :: Vector Word8 -> ByteString
- readStructField :: (Position -> a) -> VOffset -> Struct s -> a
- readTableFieldOpt :: (PositionInfo -> Either ReadError a) -> TableIndex -> Table t -> Either ReadError (Maybe a)
- readTableFieldReq :: (PositionInfo -> Either ReadError a) -> TableIndex -> String -> Table t -> Either ReadError a
- readTableFieldWithDef :: (PositionInfo -> Either ReadError a) -> TableIndex -> a -> Table t -> Either ReadError a
- readTableFieldUnion :: (Positive Word8 -> PositionInfo -> Either ReadError (Union a)) -> TableIndex -> Table t -> Either ReadError (Union a)
- readTableFieldUnionVectorOpt :: (Positive Word8 -> PositionInfo -> Either ReadError (Union a)) -> TableIndex -> Table t -> Either ReadError (Maybe (Vector (Union a)))
- readTableFieldUnionVectorReq :: (Positive Word8 -> PositionInfo -> Either ReadError (Union a)) -> TableIndex -> String -> Table t -> Either ReadError (Vector (Union a))
- readInt8 :: HasPosition a => a -> Either ReadError Int8
- readInt16 :: HasPosition a => a -> Either ReadError Int16
- readInt32 :: HasPosition a => a -> Either ReadError Int32
- readInt64 :: HasPosition a => a -> Either ReadError Int64
- readWord8 :: HasPosition a => a -> Either ReadError Word8
- readWord16 :: HasPosition a => a -> Either ReadError Word16
- readWord32 :: HasPosition a => a -> Either ReadError Word32
- readWord64 :: HasPosition a => a -> Either ReadError Word64
- readFloat :: HasPosition a => a -> Either ReadError Float
- readDouble :: HasPosition a => a -> Either ReadError Double
- readBool :: HasPosition a => a -> Either ReadError Bool
- word8ToBool :: Word8 -> Bool
- readPrimVector :: (Int32 -> Position -> Vector a) -> PositionInfo -> Either ReadError (Vector a)
- readTableVector :: PositionInfo -> Either ReadError (Vector (Table a))
- readUnionVector :: (Positive Word8 -> PositionInfo -> Either ReadError (Union a)) -> PositionInfo -> PositionInfo -> Either ReadError (Vector (Union a))
- readText :: HasPosition a => a -> Either ReadError Text
- readText' :: Get (Either ReadError Text)
- readTable :: PositionInfo -> Either ReadError (Table t)
- readTable' :: PositionInfo -> Either ReadError (Table t)
- readStruct :: HasPosition a => a -> Struct s
- tableIndexToVOffset :: Table t -> TableIndex -> Either ReadError (Maybe VOffset)
- readUOffsetAndSkip :: HasPosition pos => pos -> Either ReadError pos
- runGet :: ByteString -> Get a -> Either ReadError a
- missingField :: String -> Either ReadError a
- byteStringSafeIndex :: ByteString -> Int32 -> Either ReadError Word8
Documentation
newtype TableIndex Source #
Instances
Num TableIndex Source # | |
Defined in FlatBuffers.Internal.Read (+) :: TableIndex -> TableIndex -> TableIndex # (-) :: TableIndex -> TableIndex -> TableIndex # (*) :: TableIndex -> TableIndex -> TableIndex # negate :: TableIndex -> TableIndex # abs :: TableIndex -> TableIndex # signum :: TableIndex -> TableIndex # fromInteger :: Integer -> TableIndex # | |
Show TableIndex Source # | |
Defined in FlatBuffers.Internal.Read showsPrec :: Int -> TableIndex -> ShowS # show :: TableIndex -> String # showList :: [TableIndex] -> ShowS # |
Instances
Enum VOffset Source # | |
Eq VOffset Source # | |
Integral VOffset Source # | |
Defined in FlatBuffers.Internal.Read | |
Num VOffset Source # | |
Ord VOffset Source # | |
Real VOffset Source # | |
Defined in FlatBuffers.Internal.Read toRational :: VOffset -> Rational # | |
Show VOffset Source # | |
newtype OffsetFromRoot Source #
Instances
A table that is being read from a flatbuffer.
Table | |
|
Instances
VectorElement (Table a) Source # | |
Defined in FlatBuffers.Internal.Read length :: Vector (Table a) -> Int32 Source # unsafeIndex :: Vector (Table a) -> Int32 -> Either ReadError (Table a) Source # toList :: Vector (Table a) -> Either ReadError [Table a] Source # take :: Int32 -> Vector (Table a) -> Vector (Table a) Source # drop :: Int32 -> Vector (Table a) -> Vector (Table a) Source # | |
data Vector (Table a) Source # | |
Defined in FlatBuffers.Internal.Read |
A struct that is being read from a flatbuffer.
Instances
IsStruct a => VectorElement (Struct a) Source # | |
Defined in FlatBuffers.Internal.Read length :: Vector (Struct a) -> Int32 Source # unsafeIndex :: Vector (Struct a) -> Int32 -> Either ReadError (Struct a) Source # toList :: Vector (Struct a) -> Either ReadError [Struct a] Source # take :: Int32 -> Vector (Struct a) -> Vector (Struct a) Source # drop :: Int32 -> Vector (Struct a) -> Vector (Struct a) Source # | |
data Vector (Struct a) Source # | |
Defined in FlatBuffers.Internal.Read |
A union that is being read from a flatbuffer.
Instances
VectorElement (Union a) Source # | |
Defined in FlatBuffers.Internal.Read length :: Vector (Union a) -> Int32 Source # unsafeIndex :: Vector (Union a) -> Int32 -> Either ReadError (Union a) Source # toList :: Vector (Union a) -> Either ReadError [Union a] Source # take :: Int32 -> Vector (Union a) -> Vector (Union a) Source # drop :: Int32 -> Vector (Union a) -> Vector (Union a) Source # | |
data Vector (Union a) Source # | |
Defined in FlatBuffers.Internal.Read data Vector (Union a) = VectorUnion {
|
type Position = ByteString Source #
data PositionInfo Source #
Current position in the buffer
PositionInfo | |
|
Instances
HasPosition PositionInfo Source # | |
Defined in FlatBuffers.Internal.Read getPosition :: PositionInfo -> Position Source # move :: Integral i => PositionInfo -> i -> PositionInfo Source # |
class HasPosition a where Source #
Instances
HasPosition ByteString Source # | |
Defined in FlatBuffers.Internal.Read getPosition :: ByteString -> Position Source # move :: Integral i => ByteString -> i -> ByteString Source # | |
HasPosition PositionInfo Source # | |
Defined in FlatBuffers.Internal.Read getPosition :: PositionInfo -> Position Source # move :: Integral i => PositionInfo -> i -> PositionInfo 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
checkFileIdentifier' :: FileIdentifier -> ByteString -> Bool Source #
Proof that a number is strictly positive.
Positive | |
|
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 #
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
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
.
toByteString :: 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
readTableFieldOpt :: (PositionInfo -> Either ReadError a) -> TableIndex -> Table t -> Either ReadError (Maybe a) Source #
readTableFieldReq :: (PositionInfo -> Either ReadError a) -> TableIndex -> String -> Table t -> Either ReadError a Source #
readTableFieldWithDef :: (PositionInfo -> Either ReadError a) -> TableIndex -> a -> Table t -> Either ReadError a Source #
readTableFieldUnion :: (Positive Word8 -> PositionInfo -> Either ReadError (Union a)) -> TableIndex -> Table t -> Either ReadError (Union a) Source #
readTableFieldUnionVectorOpt :: (Positive Word8 -> PositionInfo -> Either ReadError (Union a)) -> TableIndex -> Table t -> Either ReadError (Maybe (Vector (Union a))) Source #
readTableFieldUnionVectorReq :: (Positive Word8 -> PositionInfo -> Either ReadError (Union a)) -> TableIndex -> String -> Table t -> Either ReadError (Vector (Union a)) Source #
readWord16 :: HasPosition a => a -> Either ReadError Word16 Source #
readWord32 :: HasPosition a => a -> Either ReadError Word32 Source #
readWord64 :: HasPosition a => a -> Either ReadError Word64 Source #
readDouble :: HasPosition a => a -> Either ReadError Double Source #
word8ToBool :: Word8 -> Bool Source #
readPrimVector :: (Int32 -> Position -> Vector a) -> PositionInfo -> Either ReadError (Vector a) Source #
readTableVector :: PositionInfo -> Either ReadError (Vector (Table a)) Source #
readUnionVector :: (Positive Word8 -> PositionInfo -> Either ReadError (Union a)) -> PositionInfo -> PositionInfo -> Either ReadError (Vector (Union a)) Source #
readText :: HasPosition a => a -> Either ReadError Text Source #
Follow a pointer to the position of a string and read it.
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.
readStruct :: HasPosition a => a -> Struct s Source #
tableIndexToVOffset :: Table t -> TableIndex -> Either ReadError (Maybe VOffset) Source #
readUOffsetAndSkip :: HasPosition pos => pos -> Either ReadError pos Source #
byteStringSafeIndex :: ByteString -> Int32 -> Either ReadError Word8 Source #
Safer version of index
that doesn't throw when index is too large.
Assumes i > 0
.