License | BSD3 |
---|---|
Stability | experimental |
Portability | type-families, generalized newtype deriving |
Safe Haskell | None |
Language | Haskell2010 |
This module provides a VarInt
wrapper with a Serial
instance
that generates base-128 variable-width ints. Values are encoded 7
bits at a time, with the most significant being a continuation bit.
Thus, the numbers from 0 to 127 require only a single byte to
encode, those from 128 to 16383 require two bytes, etc.
This format is taken from Google's Protocol Buffers, which provides a bit more verbiage on the encoding: https://developers.google.com/protocol-buffers/docs/encoding#varints.
Documentation
Instances
Bounded n => Bounded (VarInt n) Source # | |
Enum n => Enum (VarInt n) Source # | |
Eq n => Eq (VarInt n) Source # | |
Integral n => Integral (VarInt n) Source # | |
Defined in Data.Bytes.VarInt | |
Num n => Num (VarInt n) Source # | |
Ord n => Ord (VarInt n) Source # | |
Defined in Data.Bytes.VarInt | |
Real n => Real (VarInt n) Source # | |
Defined in Data.Bytes.VarInt toRational :: VarInt n -> Rational # | |
Show n => Show (VarInt n) Source # | |
Bits n => Bits (VarInt n) Source # | |
Defined in Data.Bytes.VarInt (.&.) :: VarInt n -> VarInt n -> VarInt n # (.|.) :: VarInt n -> VarInt n -> VarInt n # xor :: VarInt n -> VarInt n -> VarInt n # complement :: VarInt n -> VarInt n # shift :: VarInt n -> Int -> VarInt n # rotate :: VarInt n -> Int -> VarInt n # setBit :: VarInt n -> Int -> VarInt n # clearBit :: VarInt n -> Int -> VarInt n # complementBit :: VarInt n -> Int -> VarInt n # testBit :: VarInt n -> Int -> Bool # bitSizeMaybe :: VarInt n -> Maybe Int # isSigned :: VarInt n -> Bool # shiftL :: VarInt n -> Int -> VarInt n # unsafeShiftL :: VarInt n -> Int -> VarInt n # shiftR :: VarInt n -> Int -> VarInt n # unsafeShiftR :: VarInt n -> Int -> VarInt n # rotateL :: VarInt n -> Int -> VarInt n # | |
(Bits n, Integral n, Bits (Unsigned n), Integral (Unsigned n)) => Serial (VarInt n) Source # | Integer/Word types serialized to base-128 variable-width ints.
|
type Signed (VarInt n) Source # | |
Defined in Data.Bytes.VarInt | |
type Unsigned (VarInt n) Source # | |
Defined in Data.Bytes.VarInt |