proto3-wire-1.4.0: A low-level implementation of the Protocol Buffers (version 3) wire format
Safe HaskellNone
LanguageHaskell2010

Proto3.Wire.Reverse.Prim

Description

Implementation details of the Data.ByteString.Reverse module. Breaking changes will be more frequent in this module; use with caution.

Synopsis

Combine types such as BoundedPrim and FixedPrim.

class AssocPlusNat n u v w where Source #

Associativity of + in type parameters.

Methods

assocLPlusNat :: Proxy# '(u, v, w) -> PNullary n (u + (v + w)) -> PNullary n ((u + v) + w) Source #

assocRPlusNat :: Proxy# '(u, v, w) -> PNullary n ((u + v) + w) -> PNullary n (u + (v + w)) Source #

Instances

Instances details
AssocPlusNat FixedPrim u v w Source # 
Instance details

Defined in Proto3.Wire.Reverse.Prim

Methods

assocLPlusNat :: Proxy# '(u, v, w) -> PNullary FixedPrim (u + (v + w)) -> PNullary FixedPrim ((u + v) + w) Source #

assocRPlusNat :: Proxy# '(u, v, w) -> PNullary FixedPrim ((u + v) + w) -> PNullary FixedPrim (u + (v + w)) Source #

AssocPlusNat BoundedPrim u v w Source # 
Instance details

Defined in Proto3.Wire.Reverse.Prim

Methods

assocLPlusNat :: Proxy# '(u, v, w) -> PNullary BoundedPrim (u + (v + w)) -> PNullary BoundedPrim ((u + v) + w) Source #

assocRPlusNat :: Proxy# '(u, v, w) -> PNullary BoundedPrim ((u + v) + w) -> PNullary BoundedPrim (u + (v + w)) Source #

class CommPlusNat n u v where Source #

Commutativity of + in type parameters.

Methods

commPlusNat :: Proxy# '(u, v) -> PNullary n (u + v) -> PNullary n (v + u) Source #

Instances

Instances details
CommPlusNat FixedPrim u v Source # 
Instance details

Defined in Proto3.Wire.Reverse.Prim

Methods

commPlusNat :: Proxy# '(u, v) -> PNullary FixedPrim (u + v) -> PNullary FixedPrim (v + u) Source #

CommPlusNat BoundedPrim u v Source # 
Instance details

Defined in Proto3.Wire.Reverse.Prim

Methods

commPlusNat :: Proxy# '(u, v) -> PNullary BoundedPrim (u + v) -> PNullary BoundedPrim (v + u) Source #

class PChoose n f t w | f t -> w where Source #

Chooses between alternatives based on a condition, adjusting a type-level parameter appropriately.

Note that while this type class makes sense for bounded builder primitives, it should not be instantiated for fixed-width primitives of differing widths (at least, not without padding to equalize the widths) because the choice between alternatives introduces a run-time variation in width. Instead please use ordinary bool or if _ then _ else _.

Minimal complete definition

pbool | pif

Methods

pbool :: PNullary n f -> PNullary n t -> Bool -> PNullary n w Source #

Like bool, chooses the first argument on False and the second on True, either way promoting the type-level Nat to the larger of the given Nats.

Defaults to the natural implementation in terms of pif.

pif :: Bool -> PNullary n t -> PNullary n f -> PNullary n w Source #

Like if _ then _ else, chooses the first argument on True and the second on False, either way promoting the type-level Nat to the larger of the given Nats.

Defaults to the natural implementation in terms of pbool.

Instances

Instances details
Max u v ~ w => PChoose BoundedPrim (u :: Nat) (v :: Nat) (w :: Nat) Source # 
Instance details

Defined in Proto3.Wire.Reverse.Prim

type Max u v = If (v <=? u) u v Source #

The larger of two Nats.

class AssocMaxNat n u v w where Source #

Associativity of Max in type parameters.

Methods

assocLMaxNat :: Proxy# '(u, v, w) -> PNullary n (Max u (Max v w)) -> PNullary n (Max (Max u v) w) Source #

assocRMaxNat :: Proxy# '(u, v, w) -> PNullary n (Max (Max u v) w) -> PNullary n (Max u (Max v w)) Source #

Instances

Instances details
AssocMaxNat BoundedPrim u v w Source # 
Instance details

Defined in Proto3.Wire.Reverse.Prim

Methods

assocLMaxNat :: Proxy# '(u, v, w) -> PNullary BoundedPrim (Max u (Max v w)) -> PNullary BoundedPrim (Max (Max u v) w) Source #

assocRMaxNat :: Proxy# '(u, v, w) -> PNullary BoundedPrim (Max (Max u v) w) -> PNullary BoundedPrim (Max u (Max v w)) Source #

class CommMaxNat n u v where Source #

Commutativity of Max in type parameters.

Methods

commMaxNat :: Proxy# '(u, v) -> PNullary n (Max u v) -> PNullary n (Max v u) Source #

Instances

Instances details
CommMaxNat BoundedPrim u v Source # 
Instance details

Defined in Proto3.Wire.Reverse.Prim

Methods

commMaxNat :: Proxy# '(u, v) -> PNullary BoundedPrim (Max u v) -> PNullary BoundedPrim (Max v u) Source #

Architectural attributes.

data StoreMethod Source #

Are we restricted to aligned writes only?

Instances

Instances details
Eq StoreMethod Source # 
Instance details

Defined in Proto3.Wire.Reverse.Prim

Show StoreMethod Source # 
Instance details

Defined in Proto3.Wire.Reverse.Prim

storeMethod :: StoreMethod Source #

StoreUnaligned if the Cabal file defines 1, which it does on architectures where that approach is known to be safe and faster then writing bytes one by one. Otherwise StoreAligned.

data ByteOrder Source #

Specifies order in which the bytes of an integer are encoded.

Constructors

BigEndian

Most significant byte first.

LittleEndian

Least significant byte first.

Instances

Instances details
Eq ByteOrder Source # 
Instance details

Defined in Proto3.Wire.Reverse.Prim

Show ByteOrder Source # 
Instance details

Defined in Proto3.Wire.Reverse.Prim

systemByteOrder :: ByteOrder Source #

The ByteOrder native to the current architecture.

For example, the order of the bytes when you poke a Word32.

Bounded primitives.

newtype BoundedPrim (w :: Nat) Source #

A BuildR together with a type-level bound on the number of bytes written and a requirement that the current buffer already contain at least that many bytes.

As in the "bytestring" package, the purpose of a bounded primitive is to improve speed by consolidating the space checks of several small builders.

Constructors

BoundedPrim BuildR 

Instances

Instances details
PMEmpty BoundedPrim 0 Source # 
Instance details

Defined in Proto3.Wire.Reverse.Prim

CommMaxNat BoundedPrim u v Source # 
Instance details

Defined in Proto3.Wire.Reverse.Prim

Methods

commMaxNat :: Proxy# '(u, v) -> PNullary BoundedPrim (Max u v) -> PNullary BoundedPrim (Max v u) Source #

CommPlusNat BoundedPrim u v Source # 
Instance details

Defined in Proto3.Wire.Reverse.Prim

Methods

commPlusNat :: Proxy# '(u, v) -> PNullary BoundedPrim (u + v) -> PNullary BoundedPrim (v + u) Source #

AssocMaxNat BoundedPrim u v w Source # 
Instance details

Defined in Proto3.Wire.Reverse.Prim

Methods

assocLMaxNat :: Proxy# '(u, v, w) -> PNullary BoundedPrim (Max u (Max v w)) -> PNullary BoundedPrim (Max (Max u v) w) Source #

assocRMaxNat :: Proxy# '(u, v, w) -> PNullary BoundedPrim (Max (Max u v) w) -> PNullary BoundedPrim (Max u (Max v w)) Source #

AssocPlusNat BoundedPrim u v w Source # 
Instance details

Defined in Proto3.Wire.Reverse.Prim

Methods

assocLPlusNat :: Proxy# '(u, v, w) -> PNullary BoundedPrim (u + (v + w)) -> PNullary BoundedPrim ((u + v) + w) Source #

assocRPlusNat :: Proxy# '(u, v, w) -> PNullary BoundedPrim ((u + v) + w) -> PNullary BoundedPrim (u + (v + w)) Source #

(w1 + w2) ~ w3 => PSemigroup BoundedPrim (w1 :: Nat) (w2 :: Nat) (w3 :: Nat) Source # 
Instance details

Defined in Proto3.Wire.Reverse.Prim

Max u v ~ w => PChoose BoundedPrim (u :: Nat) (v :: Nat) (w :: Nat) Source # 
Instance details

Defined in Proto3.Wire.Reverse.Prim

type PNullary BoundedPrim (width :: Nat) Source # 
Instance details

Defined in Proto3.Wire.Reverse.Prim

type PNullary BoundedPrim (width :: Nat) = BoundedPrim width

liftBoundedPrim :: forall w. KnownNat w => BoundedPrim w -> BuildR Source #

Executes the given bounded primitive after obtaining the space it requires.

composeBoundedPrim :: BoundedPrim v -> BoundedPrim w -> BoundedPrim (v + w) Source #

Needed for rewrite rules; normally you would use pmappend or (&<>).

unsafeBuildBoundedPrim :: BoundedPrim w -> BuildR Source #

Executes the bounded primitive WITHOUT first ensuring it has enough space.

Fixed-width primitives.

data FixedPrim (w :: Nat) Source #

Similar to a BoundedPrim but also consolidates address updates in order to take advantage of machine instructions that write at an offset.

The additional input is an offset from the current address that specifies the beginning of the region being encoded.

(If GHC learns to consolidate address offsets automatically then we might be able to just use BoundedPrim instead.)

Instances

Instances details
PMEmpty FixedPrim 0 Source # 
Instance details

Defined in Proto3.Wire.Reverse.Prim

CommPlusNat FixedPrim u v Source # 
Instance details

Defined in Proto3.Wire.Reverse.Prim

Methods

commPlusNat :: Proxy# '(u, v) -> PNullary FixedPrim (u + v) -> PNullary FixedPrim (v + u) Source #

AssocPlusNat FixedPrim u v w Source # 
Instance details

Defined in Proto3.Wire.Reverse.Prim

Methods

assocLPlusNat :: Proxy# '(u, v, w) -> PNullary FixedPrim (u + (v + w)) -> PNullary FixedPrim ((u + v) + w) Source #

assocRPlusNat :: Proxy# '(u, v, w) -> PNullary FixedPrim ((u + v) + w) -> PNullary FixedPrim (u + (v + w)) Source #

((w1 + w2) ~ w3, KnownNat w1) => PSemigroup FixedPrim (w1 :: Nat) (w2 :: Nat) (w3 :: Nat) Source # 
Instance details

Defined in Proto3.Wire.Reverse.Prim

type PNullary FixedPrim (width :: Nat) Source # 
Instance details

Defined in Proto3.Wire.Reverse.Prim

type PNullary FixedPrim (width :: Nat) = FixedPrim width

liftFixedPrim :: forall w. KnownNat w => FixedPrim w -> BoundedPrim w Source #

Executes the given fixed primitive and adjusts the current address.

word8 :: Word8 -> FixedPrim 1 Source #

Fixed-width primitive that writes a single byte as-is.

word16 :: ByteOrder -> Word16 -> FixedPrim 2 Source #

Fixed-width primitive that writes a 16-bit word in the specified byte order.

word16Native :: Word16 -> FixedPrim 2 Source #

Fixed-width primitive that writes a 16-bit word in native byte order.

word16BE :: Word16 -> FixedPrim 2 Source #

Fixed-width primitive that writes a 16-bit word in big-endian byte order.

word16LE :: Word16 -> FixedPrim 2 Source #

Fixed-width primitive that writes a 16-bit word in little-endian byte order.

word32 :: ByteOrder -> Word32 -> FixedPrim 4 Source #

Fixed-width primitive that writes a 32-bit word in the specified byte order.

word32Native :: Word32 -> FixedPrim 4 Source #

Fixed-width primitive that writes a 32-bit word in native byte order.

word32BE :: Word32 -> FixedPrim 4 Source #

Fixed-width primitive that writes a 32-bit word in big-endian byte order.

word32LE :: Word32 -> FixedPrim 4 Source #

Fixed-width primitive that writes a 32-bit word in little-endian byte order.

word64 :: ByteOrder -> Word64 -> FixedPrim 8 Source #

Fixed-width primitive that writes a 64-bit word in the specified byte order.

word64Native :: Word64 -> FixedPrim 8 Source #

Fixed-width primitive that writes a 64-bit word in native byte order.

word64BE :: Word64 -> FixedPrim 8 Source #

Fixed-width primitive that writes a 64-bit word in big-endian byte order.

word64LE :: Word64 -> FixedPrim 8 Source #

Fixed-width primitive that writes a 64-bit word in little-endian byte order.

float :: ByteOrder -> Float -> FixedPrim 4 Source #

Fixed-width primitive that writes a Float in the specified byte order.

floatNative :: Float -> FixedPrim 4 Source #

Fixed-width primitive that writes a Float in native byte order.

floatBE :: Float -> FixedPrim 4 Source #

Fixed-width primitive that writes a Float in big-endian byte order.

floatLE :: Float -> FixedPrim 4 Source #

Fixed-width primitive that writes a Float in little-endian byte order.

double :: ByteOrder -> Double -> FixedPrim 8 Source #

Fixed-width primitive that writes a Double in the specified byte order.

doubleNative :: Double -> FixedPrim 8 Source #

Fixed-width primitive that writes a Double in native byte order.

doubleBE :: Double -> FixedPrim 8 Source #

Fixed-width primitive that writes a Double in big-endian byte order.

doubleLE :: Double -> FixedPrim 8 Source #

Fixed-width primitive that writes a Double in little-endian byte order.

charUtf8 :: Char -> BoundedPrim 4 Source #

Bounded-width primitive that writes a Char according to the UTF-8 encoding.

wordBase128LEVar :: Word -> BoundedPrim 10 Source #

The bounded primitive implementing wordBase128LEVar.

wordBase128LEVar_inline :: Word -> BoundedPrim 10 Source #

Like wordBase128LEVar but inlined, possibly bloating your code. On the other hand, inlining an application to a constant may shrink your code.

word32Base128LEVar :: Word32 -> BoundedPrim 5 Source #

The bounded primitive implementing word32Base128LEVar.

word32Base128LEVar_inline :: Word32 -> BoundedPrim 5 Source #

Like word32Base128LEVar but inlined, which currently means that it is just the same as word32Base128LEVar, which we inline.

word64Base128LEVar :: Word64 -> BoundedPrim 10 Source #

The bounded primitive implementing word64Base128LEVar.

word64Base128LEVar_inline :: Word64 -> BoundedPrim 10 Source #

Like word64Base128LEVar but inlined, possibly bloating your code. On the other hand, inlining an application to a constant may shrink your code.

vectorFixedPrim :: forall w v a. (KnownNat w, Vector v a) => (a -> FixedPrim w) -> v a -> BuildR Source #

The analog of vectorBuildR for when fixed-width primitives encode the elements of the vector. In this special case we can predict the overall length.