protocol-buffers-2.4.1: Parse Google Protocol Buffer specifications

Safe HaskellNone
LanguageHaskell98

Text.ProtocolBuffers.Basic

Contents

Description

Text.ProtocolBuffers.Basic defines or re-exports most of the basic field types; Maybe,Bool, Double, and Float come from the Prelude instead. This module also defines the Mergeable and Default classes. The Wire class is not defined here to avoid orphans.

Synopsis

Basic types for protocol buffer fields in Haskell

data Double :: * #

Double-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE double-precision type.

Instances

Eq Double 

Methods

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

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

Floating Double 
Data Double 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Double -> c Double #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Double #

toConstr :: Double -> Constr #

dataTypeOf :: Double -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Double) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Double) #

gmapT :: (forall b. Data b => b -> b) -> Double -> Double #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Double -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Double -> r #

gmapQ :: (forall d. Data d => d -> u) -> Double -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Double -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Double -> m Double #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Double -> m Double #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Double -> m Double #

Ord Double 
Read Double 
RealFloat Double 
PrintfArg Double 
Storable Double 
Default Double Source # 
Mergeable Double Source # 
TextType Double Source # 

Methods

tellT :: String -> Double -> Output Source #

getT :: Stream s Identity Char => String -> Parsec s () Double Source #

Wire Double Source # 
GPB Double Source # 
IArray UArray Double 

Methods

bounds :: Ix i => UArray i Double -> (i, i) #

numElements :: Ix i => UArray i Double -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Double)] -> UArray i Double

unsafeAt :: Ix i => UArray i Double -> Int -> Double

unsafeReplace :: Ix i => UArray i Double -> [(Int, Double)] -> UArray i Double

unsafeAccum :: Ix i => (Double -> e' -> Double) -> UArray i Double -> [(Int, e')] -> UArray i Double

unsafeAccumArray :: Ix i => (Double -> e' -> Double) -> Double -> (i, i) -> [(Int, e')] -> UArray i Double

MessageAPI msg (msg -> Double) Double Source # 

Methods

getVal :: msg -> (msg -> Double) -> Double Source #

isSet :: msg -> (msg -> Double) -> Bool Source #

Functor (URec Double) 

Methods

fmap :: (a -> b) -> URec Double a -> URec Double b #

(<$) :: a -> URec Double b -> URec Double a #

Foldable (URec Double) 

Methods

fold :: Monoid m => URec Double m -> m #

foldMap :: Monoid m => (a -> m) -> URec Double a -> m #

foldr :: (a -> b -> b) -> b -> URec Double a -> b #

foldr' :: (a -> b -> b) -> b -> URec Double a -> b #

foldl :: (b -> a -> b) -> b -> URec Double a -> b #

foldl' :: (b -> a -> b) -> b -> URec Double a -> b #

foldr1 :: (a -> a -> a) -> URec Double a -> a #

foldl1 :: (a -> a -> a) -> URec Double a -> a #

toList :: URec Double a -> [a] #

null :: URec Double a -> Bool #

length :: URec Double a -> Int #

elem :: Eq a => a -> URec Double a -> Bool #

maximum :: Ord a => URec Double a -> a #

minimum :: Ord a => URec Double a -> a #

sum :: Num a => URec Double a -> a #

product :: Num a => URec Double a -> a #

Traversable (URec Double) 

Methods

traverse :: Applicative f => (a -> f b) -> URec Double a -> f (URec Double b) #

sequenceA :: Applicative f => URec Double (f a) -> f (URec Double a) #

mapM :: Monad m => (a -> m b) -> URec Double a -> m (URec Double b) #

sequence :: Monad m => URec Double (m a) -> m (URec Double a) #

Generic1 (URec Double) 

Associated Types

type Rep1 (URec Double :: * -> *) :: * -> * #

Methods

from1 :: URec Double a -> Rep1 (URec Double) a #

to1 :: Rep1 (URec Double) a -> URec Double a #

MArray (STUArray s) Double (ST s) 

Methods

getBounds :: Ix i => STUArray s i Double -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Double -> ST s Int

newArray :: Ix i => (i, i) -> Double -> ST s (STUArray s i Double) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Double) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Double)

unsafeRead :: Ix i => STUArray s i Double -> Int -> ST s Double

unsafeWrite :: Ix i => STUArray s i Double -> Int -> Double -> ST s ()

Eq (URec Double p) 

Methods

(==) :: URec Double p -> URec Double p -> Bool #

(/=) :: URec Double p -> URec Double p -> Bool #

Ord (URec Double p) 

Methods

compare :: URec Double p -> URec Double p -> Ordering #

(<) :: URec Double p -> URec Double p -> Bool #

(<=) :: URec Double p -> URec Double p -> Bool #

(>) :: URec Double p -> URec Double p -> Bool #

(>=) :: URec Double p -> URec Double p -> Bool #

max :: URec Double p -> URec Double p -> URec Double p #

min :: URec Double p -> URec Double p -> URec Double p #

Show (URec Double p) 

Methods

showsPrec :: Int -> URec Double p -> ShowS #

show :: URec Double p -> String #

showList :: [URec Double p] -> ShowS #

Generic (URec Double p) 

Associated Types

type Rep (URec Double p) :: * -> * #

Methods

from :: URec Double p -> Rep (URec Double p) x #

to :: Rep (URec Double p) x -> URec Double p #

data URec Double

Used for marking occurrences of Double#

type Rep1 (URec Double) 
type Rep1 (URec Double) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UDouble" PrefixI True) (S1 (MetaSel (Just Symbol "uDouble#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UDouble))
type Rep (URec Double p) 
type Rep (URec Double p) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UDouble" PrefixI True) (S1 (MetaSel (Just Symbol "uDouble#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UDouble))

data Float :: * #

Single-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE single-precision type.

Instances

Eq Float 

Methods

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

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

Floating Float 
Data Float 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Float -> c Float #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Float #

toConstr :: Float -> Constr #

dataTypeOf :: Float -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Float) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Float) #

gmapT :: (forall b. Data b => b -> b) -> Float -> Float #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Float -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Float -> r #

gmapQ :: (forall d. Data d => d -> u) -> Float -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Float -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Float -> m Float #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Float -> m Float #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Float -> m Float #

Ord Float 

Methods

compare :: Float -> Float -> Ordering #

(<) :: Float -> Float -> Bool #

(<=) :: Float -> Float -> Bool #

(>) :: Float -> Float -> Bool #

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

max :: Float -> Float -> Float #

min :: Float -> Float -> Float #

Read Float 
RealFloat Float 
PrintfArg Float 
Storable Float 

Methods

sizeOf :: Float -> Int #

alignment :: Float -> Int #

peekElemOff :: Ptr Float -> Int -> IO Float #

pokeElemOff :: Ptr Float -> Int -> Float -> IO () #

peekByteOff :: Ptr b -> Int -> IO Float #

pokeByteOff :: Ptr b -> Int -> Float -> IO () #

peek :: Ptr Float -> IO Float #

poke :: Ptr Float -> Float -> IO () #

Default Float Source # 
Mergeable Float Source # 
TextType Float Source # 

Methods

tellT :: String -> Float -> Output Source #

getT :: Stream s Identity Char => String -> Parsec s () Float Source #

Wire Float Source # 
GPB Float Source # 
IArray UArray Float 

Methods

bounds :: Ix i => UArray i Float -> (i, i) #

numElements :: Ix i => UArray i Float -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Float)] -> UArray i Float

unsafeAt :: Ix i => UArray i Float -> Int -> Float

unsafeReplace :: Ix i => UArray i Float -> [(Int, Float)] -> UArray i Float

unsafeAccum :: Ix i => (Float -> e' -> Float) -> UArray i Float -> [(Int, e')] -> UArray i Float

unsafeAccumArray :: Ix i => (Float -> e' -> Float) -> Float -> (i, i) -> [(Int, e')] -> UArray i Float

MessageAPI msg (msg -> Float) Float Source # 

Methods

getVal :: msg -> (msg -> Float) -> Float Source #

isSet :: msg -> (msg -> Float) -> Bool Source #

Functor (URec Float) 

Methods

fmap :: (a -> b) -> URec Float a -> URec Float b #

(<$) :: a -> URec Float b -> URec Float a #

Foldable (URec Float) 

Methods

fold :: Monoid m => URec Float m -> m #

foldMap :: Monoid m => (a -> m) -> URec Float a -> m #

foldr :: (a -> b -> b) -> b -> URec Float a -> b #

foldr' :: (a -> b -> b) -> b -> URec Float a -> b #

foldl :: (b -> a -> b) -> b -> URec Float a -> b #

foldl' :: (b -> a -> b) -> b -> URec Float a -> b #

foldr1 :: (a -> a -> a) -> URec Float a -> a #

foldl1 :: (a -> a -> a) -> URec Float a -> a #

toList :: URec Float a -> [a] #

null :: URec Float a -> Bool #

length :: URec Float a -> Int #

elem :: Eq a => a -> URec Float a -> Bool #

maximum :: Ord a => URec Float a -> a #

minimum :: Ord a => URec Float a -> a #

sum :: Num a => URec Float a -> a #

product :: Num a => URec Float a -> a #

Traversable (URec Float) 

Methods

traverse :: Applicative f => (a -> f b) -> URec Float a -> f (URec Float b) #

sequenceA :: Applicative f => URec Float (f a) -> f (URec Float a) #

mapM :: Monad m => (a -> m b) -> URec Float a -> m (URec Float b) #

sequence :: Monad m => URec Float (m a) -> m (URec Float a) #

Generic1 (URec Float) 

Associated Types

type Rep1 (URec Float :: * -> *) :: * -> * #

Methods

from1 :: URec Float a -> Rep1 (URec Float) a #

to1 :: Rep1 (URec Float) a -> URec Float a #

MArray (STUArray s) Float (ST s) 

Methods

getBounds :: Ix i => STUArray s i Float -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Float -> ST s Int

newArray :: Ix i => (i, i) -> Float -> ST s (STUArray s i Float) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Float) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Float)

unsafeRead :: Ix i => STUArray s i Float -> Int -> ST s Float

unsafeWrite :: Ix i => STUArray s i Float -> Int -> Float -> ST s ()

Eq (URec Float p) 

Methods

(==) :: URec Float p -> URec Float p -> Bool #

(/=) :: URec Float p -> URec Float p -> Bool #

Ord (URec Float p) 

Methods

compare :: URec Float p -> URec Float p -> Ordering #

(<) :: URec Float p -> URec Float p -> Bool #

(<=) :: URec Float p -> URec Float p -> Bool #

(>) :: URec Float p -> URec Float p -> Bool #

(>=) :: URec Float p -> URec Float p -> Bool #

max :: URec Float p -> URec Float p -> URec Float p #

min :: URec Float p -> URec Float p -> URec Float p #

Show (URec Float p) 

Methods

showsPrec :: Int -> URec Float p -> ShowS #

show :: URec Float p -> String #

showList :: [URec Float p] -> ShowS #

Generic (URec Float p) 

Associated Types

type Rep (URec Float p) :: * -> * #

Methods

from :: URec Float p -> Rep (URec Float p) x #

to :: Rep (URec Float p) x -> URec Float p #

data URec Float

Used for marking occurrences of Float#

type Rep1 (URec Float) 
type Rep1 (URec Float) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UFloat" PrefixI True) (S1 (MetaSel (Just Symbol "uFloat#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UFloat))
type Rep (URec Float p) 
type Rep (URec Float p) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UFloat" PrefixI True) (S1 (MetaSel (Just Symbol "uFloat#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UFloat))

data Bool :: * #

Instances

Bounded Bool 
Enum Bool 

Methods

succ :: Bool -> Bool #

pred :: Bool -> Bool #

toEnum :: Int -> Bool #

fromEnum :: Bool -> Int #

enumFrom :: Bool -> [Bool] #

enumFromThen :: Bool -> Bool -> [Bool] #

enumFromTo :: Bool -> Bool -> [Bool] #

enumFromThenTo :: Bool -> Bool -> Bool -> [Bool] #

Eq Bool 

Methods

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

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

Data Bool 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bool -> c Bool #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Bool #

toConstr :: Bool -> Constr #

dataTypeOf :: Bool -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Bool) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bool) #

gmapT :: (forall b. Data b => b -> b) -> Bool -> Bool #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bool -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bool -> r #

gmapQ :: (forall d. Data d => d -> u) -> Bool -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Bool -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bool -> m Bool #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bool -> m Bool #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bool -> m Bool #

Ord Bool 

Methods

compare :: Bool -> Bool -> Ordering #

(<) :: Bool -> Bool -> Bool #

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

(>) :: Bool -> Bool -> Bool #

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

max :: Bool -> Bool -> Bool #

min :: Bool -> Bool -> Bool #

Read Bool 
Show Bool 

Methods

showsPrec :: Int -> Bool -> ShowS #

show :: Bool -> String #

showList :: [Bool] -> ShowS #

Ix Bool 

Methods

range :: (Bool, Bool) -> [Bool] #

index :: (Bool, Bool) -> Bool -> Int #

unsafeIndex :: (Bool, Bool) -> Bool -> Int

inRange :: (Bool, Bool) -> Bool -> Bool #

rangeSize :: (Bool, Bool) -> Int #

unsafeRangeSize :: (Bool, Bool) -> Int

Generic Bool 

Associated Types

type Rep Bool :: * -> * #

Methods

from :: Bool -> Rep Bool x #

to :: Rep Bool x -> Bool #

Storable Bool 

Methods

sizeOf :: Bool -> Int #

alignment :: Bool -> Int #

peekElemOff :: Ptr Bool -> Int -> IO Bool #

pokeElemOff :: Ptr Bool -> Int -> Bool -> IO () #

peekByteOff :: Ptr b -> Int -> IO Bool #

pokeByteOff :: Ptr b -> Int -> Bool -> IO () #

peek :: Ptr Bool -> IO Bool #

poke :: Ptr Bool -> Bool -> IO () #

Bits Bool 
FiniteBits Bool 
Default Bool Source # 
Mergeable Bool Source # 
TextType Bool Source # 

Methods

tellT :: String -> Bool -> Output Source #

getT :: Stream s Identity Char => String -> Parsec s () Bool Source #

Wire Bool Source # 
GPB Bool Source # 
IArray UArray Bool 

Methods

bounds :: Ix i => UArray i Bool -> (i, i) #

numElements :: Ix i => UArray i Bool -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Bool)] -> UArray i Bool

unsafeAt :: Ix i => UArray i Bool -> Int -> Bool

unsafeReplace :: Ix i => UArray i Bool -> [(Int, Bool)] -> UArray i Bool

unsafeAccum :: Ix i => (Bool -> e' -> Bool) -> UArray i Bool -> [(Int, e')] -> UArray i Bool

unsafeAccumArray :: Ix i => (Bool -> e' -> Bool) -> Bool -> (i, i) -> [(Int, e')] -> UArray i Bool

SingI Bool False 

Methods

sing :: Sing False a

SingI Bool True 

Methods

sing :: Sing True a

SingKind Bool (KProxy Bool) 

Associated Types

type DemoteRep (KProxy Bool) (kparam :: KProxy (KProxy Bool)) :: *

Methods

fromSing :: Sing (KProxy Bool) a -> DemoteRep (KProxy Bool) kparam

MArray (STUArray s) Bool (ST s) 

Methods

getBounds :: Ix i => STUArray s i Bool -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Bool -> ST s Int

newArray :: Ix i => (i, i) -> Bool -> ST s (STUArray s i Bool) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Bool) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Bool)

unsafeRead :: Ix i => STUArray s i Bool -> Int -> ST s Bool

unsafeWrite :: Ix i => STUArray s i Bool -> Int -> Bool -> ST s ()

type Rep Bool 
type Rep Bool = D1 (MetaData "Bool" "GHC.Types" "ghc-prim" False) ((:+:) (C1 (MetaCons "False" PrefixI False) U1) (C1 (MetaCons "True" PrefixI False) U1))
data Sing Bool 
data Sing Bool where
type (==) Bool a b 
type (==) Bool a b = EqBool a b
type DemoteRep Bool (KProxy Bool) 
type DemoteRep Bool (KProxy Bool) = Bool

data Maybe a :: * -> * #

The Maybe type encapsulates an optional value. A value of type Maybe a either contains a value of type a (represented as Just a), or it is empty (represented as Nothing). Using Maybe is a good way to deal with errors or exceptional cases without resorting to drastic measures such as error.

The Maybe type is also a monad. It is a simple kind of error monad, where all errors are represented by Nothing. A richer error monad can be built using the Either type.

Instances

Monad Maybe 

Methods

(>>=) :: Maybe a -> (a -> Maybe b) -> Maybe b #

(>>) :: Maybe a -> Maybe b -> Maybe b #

return :: a -> Maybe a #

fail :: String -> Maybe a #

Functor Maybe 

Methods

fmap :: (a -> b) -> Maybe a -> Maybe b #

(<$) :: a -> Maybe b -> Maybe a #

Applicative Maybe 

Methods

pure :: a -> Maybe a #

(<*>) :: Maybe (a -> b) -> Maybe a -> Maybe b #

(*>) :: Maybe a -> Maybe b -> Maybe b #

(<*) :: Maybe a -> Maybe b -> Maybe a #

Foldable Maybe 

Methods

fold :: Monoid m => Maybe m -> m #

foldMap :: Monoid m => (a -> m) -> Maybe a -> m #

foldr :: (a -> b -> b) -> b -> Maybe a -> b #

foldr' :: (a -> b -> b) -> b -> Maybe a -> b #

foldl :: (b -> a -> b) -> b -> Maybe a -> b #

foldl' :: (b -> a -> b) -> b -> Maybe a -> b #

foldr1 :: (a -> a -> a) -> Maybe a -> a #

foldl1 :: (a -> a -> a) -> Maybe a -> a #

toList :: Maybe a -> [a] #

null :: Maybe a -> Bool #

length :: Maybe a -> Int #

elem :: Eq a => a -> Maybe a -> Bool #

maximum :: Ord a => Maybe a -> a #

minimum :: Ord a => Maybe a -> a #

sum :: Num a => Maybe a -> a #

product :: Num a => Maybe a -> a #

Traversable Maybe 

Methods

traverse :: Applicative f => (a -> f b) -> Maybe a -> f (Maybe b) #

sequenceA :: Applicative f => Maybe (f a) -> f (Maybe a) #

mapM :: Monad m => (a -> m b) -> Maybe a -> m (Maybe b) #

sequence :: Monad m => Maybe (m a) -> m (Maybe a) #

Generic1 Maybe 

Associated Types

type Rep1 (Maybe :: * -> *) :: * -> * #

Methods

from1 :: Maybe a -> Rep1 Maybe a #

to1 :: Rep1 Maybe a -> Maybe a #

Eq1 Maybe 

Methods

liftEq :: (a -> b -> Bool) -> Maybe a -> Maybe b -> Bool #

Ord1 Maybe 

Methods

liftCompare :: (a -> b -> Ordering) -> Maybe a -> Maybe b -> Ordering #

Read1 Maybe 

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Maybe a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Maybe a] #

Show1 Maybe 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Maybe a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Maybe a] -> ShowS #

Alternative Maybe 

Methods

empty :: Maybe a #

(<|>) :: Maybe a -> Maybe a -> Maybe a #

some :: Maybe a -> Maybe [a] #

many :: Maybe a -> Maybe [a] #

MonadPlus Maybe 

Methods

mzero :: Maybe a #

mplus :: Maybe a -> Maybe a -> Maybe a #

ExtKey Maybe Source # 

Methods

putExt :: Key Maybe msg v -> Maybe v -> msg -> msg Source #

getExt :: Key Maybe msg v -> msg -> Either String (Maybe v) Source #

clearExt :: Key Maybe msg v -> msg -> msg Source #

wireGetKey :: Key Maybe msg v -> msg -> Get msg Source #

(Default msg, Default a) => MessageAPI msg (msg -> Maybe a) a Source # 

Methods

getVal :: msg -> (msg -> Maybe a) -> a Source #

isSet :: msg -> (msg -> Maybe a) -> Bool Source #

Default v => MessageAPI msg (Key Maybe msg v) v Source # 

Methods

getVal :: msg -> Key Maybe msg v -> v Source #

isSet :: msg -> Key Maybe msg v -> Bool Source #

Eq a => Eq (Maybe a) 

Methods

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

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

Data a => Data (Maybe a) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Maybe a -> c (Maybe a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Maybe a) #

toConstr :: Maybe a -> Constr #

dataTypeOf :: Maybe a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Maybe a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Maybe a)) #

gmapT :: (forall b. Data b => b -> b) -> Maybe a -> Maybe a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Maybe a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Maybe a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Maybe a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Maybe a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Maybe a -> m (Maybe a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Maybe a -> m (Maybe a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Maybe a -> m (Maybe a) #

Ord a => Ord (Maybe a) 

Methods

compare :: Maybe a -> Maybe a -> Ordering #

(<) :: Maybe a -> Maybe a -> Bool #

(<=) :: Maybe a -> Maybe a -> Bool #

(>) :: Maybe a -> Maybe a -> Bool #

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

max :: Maybe a -> Maybe a -> Maybe a #

min :: Maybe a -> Maybe a -> Maybe a #

Read a => Read (Maybe a) 
Show a => Show (Maybe a) 

Methods

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

show :: Maybe a -> String #

showList :: [Maybe a] -> ShowS #

Generic (Maybe a) 

Associated Types

type Rep (Maybe a) :: * -> * #

Methods

from :: Maybe a -> Rep (Maybe a) x #

to :: Rep (Maybe a) x -> Maybe a #

Semigroup a => Semigroup (Maybe a) 

Methods

(<>) :: Maybe a -> Maybe a -> Maybe a #

sconcat :: NonEmpty (Maybe a) -> Maybe a #

stimes :: Integral b => b -> Maybe a -> Maybe a #

Monoid a => Monoid (Maybe a)

Lift a semigroup into Maybe forming a Monoid according to http://en.wikipedia.org/wiki/Monoid: "Any semigroup S may be turned into a monoid simply by adjoining an element e not in S and defining e*e = e and e*s = s = s*e for all s ∈ S." Since there is no "Semigroup" typeclass providing just mappend, we use Monoid instead.

Methods

mempty :: Maybe a #

mappend :: Maybe a -> Maybe a -> Maybe a #

mconcat :: [Maybe a] -> Maybe a #

Default (Maybe a) Source # 
Mergeable a => Mergeable (Maybe a) Source # 

Methods

mergeAppend :: Maybe a -> Maybe a -> Maybe a Source #

mergeConcat :: Foldable t => t (Maybe a) -> Maybe a Source #

TextType a => TextType (Maybe a) Source # 

Methods

tellT :: String -> Maybe a -> Output Source #

getT :: Stream s Identity Char => String -> Parsec s () (Maybe a) Source #

SingI (Maybe a) (Nothing a) 

Methods

sing :: Sing (Nothing a) a

SingKind a (KProxy a) => SingKind (Maybe a) (KProxy (Maybe a)) 

Associated Types

type DemoteRep (KProxy (Maybe a)) (kparam :: KProxy (KProxy (Maybe a))) :: *

Methods

fromSing :: Sing (KProxy (Maybe a)) a -> DemoteRep (KProxy (Maybe a)) kparam

SingI a a1 => SingI (Maybe a) (Just a a1) 

Methods

sing :: Sing (Just a a1) a

type Rep1 Maybe 
type Rep (Maybe a) 
data Sing (Maybe a) 
data Sing (Maybe a) where
type (==) (Maybe k) a b 
type (==) (Maybe k) a b = EqMaybe k a b
type DemoteRep (Maybe a) (KProxy (Maybe a)) 
type DemoteRep (Maybe a) (KProxy (Maybe a)) = Maybe (DemoteRep a (KProxy a))

data Seq a :: * -> * #

General-purpose finite sequences.

Instances

Monad Seq 

Methods

(>>=) :: Seq a -> (a -> Seq b) -> Seq b #

(>>) :: Seq a -> Seq b -> Seq b #

return :: a -> Seq a #

fail :: String -> Seq a #

Functor Seq 

Methods

fmap :: (a -> b) -> Seq a -> Seq b #

(<$) :: a -> Seq b -> Seq a #

Applicative Seq 

Methods

pure :: a -> Seq a #

(<*>) :: Seq (a -> b) -> Seq a -> Seq b #

(*>) :: Seq a -> Seq b -> Seq b #

(<*) :: Seq a -> Seq b -> Seq a #

Foldable Seq 

Methods

fold :: Monoid m => Seq m -> m #

foldMap :: Monoid m => (a -> m) -> Seq a -> m #

foldr :: (a -> b -> b) -> b -> Seq a -> b #

foldr' :: (a -> b -> b) -> b -> Seq a -> b #

foldl :: (b -> a -> b) -> b -> Seq a -> b #

foldl' :: (b -> a -> b) -> b -> Seq a -> b #

foldr1 :: (a -> a -> a) -> Seq a -> a #

foldl1 :: (a -> a -> a) -> Seq a -> a #

toList :: Seq a -> [a] #

null :: Seq a -> Bool #

length :: Seq a -> Int #

elem :: Eq a => a -> Seq a -> Bool #

maximum :: Ord a => Seq a -> a #

minimum :: Ord a => Seq a -> a #

sum :: Num a => Seq a -> a #

product :: Num a => Seq a -> a #

Traversable Seq 

Methods

traverse :: Applicative f => (a -> f b) -> Seq a -> f (Seq b) #

sequenceA :: Applicative f => Seq (f a) -> f (Seq a) #

mapM :: Monad m => (a -> m b) -> Seq a -> m (Seq b) #

sequence :: Monad m => Seq (m a) -> m (Seq a) #

Alternative Seq 

Methods

empty :: Seq a #

(<|>) :: Seq a -> Seq a -> Seq a #

some :: Seq a -> Seq [a] #

many :: Seq a -> Seq [a] #

MonadPlus Seq 

Methods

mzero :: Seq a #

mplus :: Seq a -> Seq a -> Seq a #

ExtKey Seq Source # 

Methods

putExt :: Key Seq msg v -> Seq v -> msg -> msg Source #

getExt :: Key Seq msg v -> msg -> Either String (Seq v) Source #

clearExt :: Key Seq msg v -> msg -> msg Source #

wireGetKey :: Key Seq msg v -> msg -> Get msg Source #

MessageAPI msg (msg -> Seq a) (Seq a) Source # 

Methods

getVal :: msg -> (msg -> Seq a) -> Seq a Source #

isSet :: msg -> (msg -> Seq a) -> Bool Source #

Default v => MessageAPI msg (Key Seq msg v) (Seq v) Source # 

Methods

getVal :: msg -> Key Seq msg v -> Seq v Source #

isSet :: msg -> Key Seq msg v -> Bool Source #

IsList (Seq a) 

Associated Types

type Item (Seq a) :: * #

Methods

fromList :: [Item (Seq a)] -> Seq a #

fromListN :: Int -> [Item (Seq a)] -> Seq a #

toList :: Seq a -> [Item (Seq a)] #

Eq a => Eq (Seq a) 

Methods

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

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

Data a => Data (Seq a) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Seq a -> c (Seq a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Seq a) #

toConstr :: Seq a -> Constr #

dataTypeOf :: Seq a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Seq a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Seq a)) #

gmapT :: (forall b. Data b => b -> b) -> Seq a -> Seq a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Seq a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Seq a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Seq a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Seq a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Seq a -> m (Seq a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Seq a -> m (Seq a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Seq a -> m (Seq a) #

Ord a => Ord (Seq a) 

Methods

compare :: Seq a -> Seq a -> Ordering #

(<) :: Seq a -> Seq a -> Bool #

(<=) :: Seq a -> Seq a -> Bool #

(>) :: Seq a -> Seq a -> Bool #

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

max :: Seq a -> Seq a -> Seq a #

min :: Seq a -> Seq a -> Seq a #

Read a => Read (Seq a) 
Show a => Show (Seq a) 

Methods

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

show :: Seq a -> String #

showList :: [Seq a] -> ShowS #

IsString (Seq Char) 

Methods

fromString :: String -> Seq Char #

Semigroup (Seq a) 

Methods

(<>) :: Seq a -> Seq a -> Seq a #

sconcat :: NonEmpty (Seq a) -> Seq a #

stimes :: Integral b => b -> Seq a -> Seq a #

Monoid (Seq a) 

Methods

mempty :: Seq a #

mappend :: Seq a -> Seq a -> Seq a #

mconcat :: [Seq a] -> Seq a #

NFData a => NFData (Seq a) 

Methods

rnf :: Seq a -> () #

Default (Seq a) Source # 

Methods

defaultValue :: Seq a Source #

Mergeable (Seq a) Source # 

Methods

mergeAppend :: Seq a -> Seq a -> Seq a Source #

mergeConcat :: Foldable t => t (Seq a) -> Seq a Source #

TextType a => TextType (Seq a) Source # 

Methods

tellT :: String -> Seq a -> Output Source #

getT :: Stream s Identity Char => String -> Parsec s () (Seq a) Source #

type Item (Seq a) 
type Item (Seq a) = a

newtype Utf8 Source #

Utf8 is used to mark ByteString values that (should) contain valid utf8 encoded strings. This type is used to represent TYPE_STRING values.

Constructors

Utf8 ByteString 

Instances

Eq Utf8 Source # 

Methods

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

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

Data Utf8 Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Utf8 -> c Utf8 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Utf8 #

toConstr :: Utf8 -> Constr #

dataTypeOf :: Utf8 -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Utf8) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Utf8) #

gmapT :: (forall b. Data b => b -> b) -> Utf8 -> Utf8 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Utf8 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Utf8 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Utf8 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Utf8 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Utf8 -> m Utf8 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Utf8 -> m Utf8 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Utf8 -> m Utf8 #

Ord Utf8 Source # 

Methods

compare :: Utf8 -> Utf8 -> Ordering #

(<) :: Utf8 -> Utf8 -> Bool #

(<=) :: Utf8 -> Utf8 -> Bool #

(>) :: Utf8 -> Utf8 -> Bool #

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

max :: Utf8 -> Utf8 -> Utf8 #

min :: Utf8 -> Utf8 -> Utf8 #

Read Utf8 Source # 
Show Utf8 Source # 

Methods

showsPrec :: Int -> Utf8 -> ShowS #

show :: Utf8 -> String #

showList :: [Utf8] -> ShowS #

Monoid Utf8 Source # 

Methods

mempty :: Utf8 #

mappend :: Utf8 -> Utf8 -> Utf8 #

mconcat :: [Utf8] -> Utf8 #

Default Utf8 Source # 
Mergeable Utf8 Source # 
Dotted Utf8 Source # 
TextType Utf8 Source # 

Methods

tellT :: String -> Utf8 -> Output Source #

getT :: Stream s Identity Char => String -> Parsec s () Utf8 Source #

Wire Utf8 Source # 
GPB Utf8 Source # 
MessageAPI msg (msg -> Utf8) Utf8 Source # 

Methods

getVal :: msg -> (msg -> Utf8) -> Utf8 Source #

isSet :: msg -> (msg -> Utf8) -> Bool Source #

Mangle (FIName Utf8) (PFName String) Source # 
Mangle (FIName Utf8) (PMName String) Source # 
Mangle (DIName Utf8) (PFName String) Source # 
Mangle (DIName Utf8) (PMName String) Source # 
Mangle (IName Utf8) (FName String) Source # 
Mangle (IName Utf8) (MName String) Source # 

data ByteString :: * #

A space-efficient representation of a Word8 vector, supporting many efficient operations.

A lazy ByteString contains 8-bit bytes, or by using the operations from Data.ByteString.Lazy.Char8 it can be interpreted as containing 8-bit characters.

Instances

Eq ByteString 
Data ByteString 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ByteString -> c ByteString #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ByteString #

toConstr :: ByteString -> Constr #

dataTypeOf :: ByteString -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ByteString) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ByteString) #

gmapT :: (forall b. Data b => b -> b) -> ByteString -> ByteString #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ByteString -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ByteString -> r #

gmapQ :: (forall d. Data d => d -> u) -> ByteString -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ByteString -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString #

Ord ByteString 
Read ByteString 
Show ByteString 
IsString ByteString 
Semigroup ByteString 
Monoid ByteString 
NFData ByteString 

Methods

rnf :: ByteString -> () #

Default ByteString Source # 
Mergeable ByteString Source # 
TextType ByteString Source # 
Wire ByteString Source # 
GPB ByteString Source # 
Monad m => Stream ByteString m Char 

Methods

uncons :: ByteString -> m (Maybe (Char, ByteString)) #

MessageAPI msg (msg -> ByteString) ByteString Source # 

Methods

getVal :: msg -> (msg -> ByteString) -> ByteString Source #

isSet :: msg -> (msg -> ByteString) -> Bool Source #

data Int32 :: * #

32-bit signed integer type

Instances

Bounded Int32 
Enum Int32 
Eq Int32 

Methods

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

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

Integral Int32 
Data Int32 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int32 -> c Int32 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int32 #

toConstr :: Int32 -> Constr #

dataTypeOf :: Int32 -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Int32) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int32) #

gmapT :: (forall b. Data b => b -> b) -> Int32 -> Int32 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int32 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int32 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Int32 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Int32 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int32 -> m Int32 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int32 -> m Int32 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int32 -> m Int32 #

Num Int32 
Ord Int32 

Methods

compare :: Int32 -> Int32 -> Ordering #

(<) :: Int32 -> Int32 -> Bool #

(<=) :: Int32 -> Int32 -> Bool #

(>) :: Int32 -> Int32 -> Bool #

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

max :: Int32 -> Int32 -> Int32 #

min :: Int32 -> Int32 -> Int32 #

Read Int32 
Real Int32 

Methods

toRational :: Int32 -> Rational #

Show Int32 

Methods

showsPrec :: Int -> Int32 -> ShowS #

show :: Int32 -> String #

showList :: [Int32] -> ShowS #

Ix Int32 
PrintfArg Int32 
Storable Int32 

Methods

sizeOf :: Int32 -> Int #

alignment :: Int32 -> Int #

peekElemOff :: Ptr Int32 -> Int -> IO Int32 #

pokeElemOff :: Ptr Int32 -> Int -> Int32 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int32 #

pokeByteOff :: Ptr b -> Int -> Int32 -> IO () #

peek :: Ptr Int32 -> IO Int32 #

poke :: Ptr Int32 -> Int32 -> IO () #

Bits Int32 
FiniteBits Int32 
Default Int32 Source # 
Mergeable Int32 Source # 
TextType Int32 Source # 

Methods

tellT :: String -> Int32 -> Output Source #

getT :: Stream s Identity Char => String -> Parsec s () Int32 Source #

Wire Int32 Source # 
GPB Int32 Source # 
IArray UArray Int32 

Methods

bounds :: Ix i => UArray i Int32 -> (i, i) #

numElements :: Ix i => UArray i Int32 -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Int32)] -> UArray i Int32

unsafeAt :: Ix i => UArray i Int32 -> Int -> Int32

unsafeReplace :: Ix i => UArray i Int32 -> [(Int, Int32)] -> UArray i Int32

unsafeAccum :: Ix i => (Int32 -> e' -> Int32) -> UArray i Int32 -> [(Int, e')] -> UArray i Int32

unsafeAccumArray :: Ix i => (Int32 -> e' -> Int32) -> Int32 -> (i, i) -> [(Int, e')] -> UArray i Int32

MessageAPI msg (msg -> Int32) Int32 Source # 

Methods

getVal :: msg -> (msg -> Int32) -> Int32 Source #

isSet :: msg -> (msg -> Int32) -> Bool Source #

MArray (STUArray s) Int32 (ST s) 

Methods

getBounds :: Ix i => STUArray s i Int32 -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Int32 -> ST s Int

newArray :: Ix i => (i, i) -> Int32 -> ST s (STUArray s i Int32) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int32) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int32)

unsafeRead :: Ix i => STUArray s i Int32 -> Int -> ST s Int32

unsafeWrite :: Ix i => STUArray s i Int32 -> Int -> Int32 -> ST s ()

data Int64 :: * #

64-bit signed integer type

Instances

Bounded Int64 
Enum Int64 
Eq Int64 

Methods

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

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

Integral Int64 
Data Int64 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int64 -> c Int64 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int64 #

toConstr :: Int64 -> Constr #

dataTypeOf :: Int64 -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Int64) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int64) #

gmapT :: (forall b. Data b => b -> b) -> Int64 -> Int64 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int64 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int64 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Int64 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Int64 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int64 -> m Int64 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int64 -> m Int64 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int64 -> m Int64 #

Num Int64 
Ord Int64 

Methods

compare :: Int64 -> Int64 -> Ordering #

(<) :: Int64 -> Int64 -> Bool #

(<=) :: Int64 -> Int64 -> Bool #

(>) :: Int64 -> Int64 -> Bool #

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

max :: Int64 -> Int64 -> Int64 #

min :: Int64 -> Int64 -> Int64 #

Read Int64 
Real Int64 

Methods

toRational :: Int64 -> Rational #

Show Int64 

Methods

showsPrec :: Int -> Int64 -> ShowS #

show :: Int64 -> String #

showList :: [Int64] -> ShowS #

Ix Int64 
PrintfArg Int64 
Storable Int64 

Methods

sizeOf :: Int64 -> Int #

alignment :: Int64 -> Int #

peekElemOff :: Ptr Int64 -> Int -> IO Int64 #

pokeElemOff :: Ptr Int64 -> Int -> Int64 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int64 #

pokeByteOff :: Ptr b -> Int -> Int64 -> IO () #

peek :: Ptr Int64 -> IO Int64 #

poke :: Ptr Int64 -> Int64 -> IO () #

Bits Int64 
FiniteBits Int64 
Default Int64 Source # 
Mergeable Int64 Source # 
TextType Int64 Source # 

Methods

tellT :: String -> Int64 -> Output Source #

getT :: Stream s Identity Char => String -> Parsec s () Int64 Source #

Wire Int64 Source # 
GPB Int64 Source # 
IArray UArray Int64 

Methods

bounds :: Ix i => UArray i Int64 -> (i, i) #

numElements :: Ix i => UArray i Int64 -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Int64)] -> UArray i Int64

unsafeAt :: Ix i => UArray i Int64 -> Int -> Int64

unsafeReplace :: Ix i => UArray i Int64 -> [(Int, Int64)] -> UArray i Int64

unsafeAccum :: Ix i => (Int64 -> e' -> Int64) -> UArray i Int64 -> [(Int, e')] -> UArray i Int64

unsafeAccumArray :: Ix i => (Int64 -> e' -> Int64) -> Int64 -> (i, i) -> [(Int, e')] -> UArray i Int64

MessageAPI msg (msg -> Int64) Int64 Source # 

Methods

getVal :: msg -> (msg -> Int64) -> Int64 Source #

isSet :: msg -> (msg -> Int64) -> Bool Source #

MArray (STUArray s) Int64 (ST s) 

Methods

getBounds :: Ix i => STUArray s i Int64 -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Int64 -> ST s Int

newArray :: Ix i => (i, i) -> Int64 -> ST s (STUArray s i Int64) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int64) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int64)

unsafeRead :: Ix i => STUArray s i Int64 -> Int -> ST s Int64

unsafeWrite :: Ix i => STUArray s i Int64 -> Int -> Int64 -> ST s ()

data Word32 :: * #

32-bit unsigned integer type

Instances

Bounded Word32 
Enum Word32 
Eq Word32 

Methods

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

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

Integral Word32 
Data Word32 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Word32 -> c Word32 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word32 #

toConstr :: Word32 -> Constr #

dataTypeOf :: Word32 -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Word32) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word32) #

gmapT :: (forall b. Data b => b -> b) -> Word32 -> Word32 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word32 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word32 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Word32 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Word32 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word32 -> m Word32 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word32 -> m Word32 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word32 -> m Word32 #

Num Word32 
Ord Word32 
Read Word32 
Real Word32 
Show Word32 
Ix Word32 
PrintfArg Word32 
Storable Word32 
Bits Word32 
FiniteBits Word32 
Default Word32 Source # 
Mergeable Word32 Source # 
TextType Word32 Source # 

Methods

tellT :: String -> Word32 -> Output Source #

getT :: Stream s Identity Char => String -> Parsec s () Word32 Source #

Wire Word32 Source # 
GPB Word32 Source # 
IArray UArray Word32 

Methods

bounds :: Ix i => UArray i Word32 -> (i, i) #

numElements :: Ix i => UArray i Word32 -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Word32)] -> UArray i Word32

unsafeAt :: Ix i => UArray i Word32 -> Int -> Word32

unsafeReplace :: Ix i => UArray i Word32 -> [(Int, Word32)] -> UArray i Word32

unsafeAccum :: Ix i => (Word32 -> e' -> Word32) -> UArray i Word32 -> [(Int, e')] -> UArray i Word32

unsafeAccumArray :: Ix i => (Word32 -> e' -> Word32) -> Word32 -> (i, i) -> [(Int, e')] -> UArray i Word32

MessageAPI msg (msg -> Word32) Word32 Source # 

Methods

getVal :: msg -> (msg -> Word32) -> Word32 Source #

isSet :: msg -> (msg -> Word32) -> Bool Source #

MArray (STUArray s) Word32 (ST s) 

Methods

getBounds :: Ix i => STUArray s i Word32 -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Word32 -> ST s Int

newArray :: Ix i => (i, i) -> Word32 -> ST s (STUArray s i Word32) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word32) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word32)

unsafeRead :: Ix i => STUArray s i Word32 -> Int -> ST s Word32

unsafeWrite :: Ix i => STUArray s i Word32 -> Int -> Word32 -> ST s ()

data Word64 :: * #

64-bit unsigned integer type

Instances

Bounded Word64 
Enum Word64 
Eq Word64 

Methods

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

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

Integral Word64 
Data Word64 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Word64 -> c Word64 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word64 #

toConstr :: Word64 -> Constr #

dataTypeOf :: Word64 -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Word64) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word64) #

gmapT :: (forall b. Data b => b -> b) -> Word64 -> Word64 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word64 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word64 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Word64 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Word64 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word64 -> m Word64 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word64 -> m Word64 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word64 -> m Word64 #

Num Word64 
Ord Word64 
Read Word64 
Real Word64 
Show Word64 
Ix Word64 
PrintfArg Word64 
Storable Word64 
Bits Word64 
FiniteBits Word64 
Default Word64 Source # 
Mergeable Word64 Source # 
TextType Word64 Source # 

Methods

tellT :: String -> Word64 -> Output Source #

getT :: Stream s Identity Char => String -> Parsec s () Word64 Source #

Wire Word64 Source # 
GPB Word64 Source # 
IArray UArray Word64 

Methods

bounds :: Ix i => UArray i Word64 -> (i, i) #

numElements :: Ix i => UArray i Word64 -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Word64)] -> UArray i Word64

unsafeAt :: Ix i => UArray i Word64 -> Int -> Word64

unsafeReplace :: Ix i => UArray i Word64 -> [(Int, Word64)] -> UArray i Word64

unsafeAccum :: Ix i => (Word64 -> e' -> Word64) -> UArray i Word64 -> [(Int, e')] -> UArray i Word64

unsafeAccumArray :: Ix i => (Word64 -> e' -> Word64) -> Word64 -> (i, i) -> [(Int, e')] -> UArray i Word64

MessageAPI msg (msg -> Word64) Word64 Source # 

Methods

getVal :: msg -> (msg -> Word64) -> Word64 Source #

isSet :: msg -> (msg -> Word64) -> Bool Source #

MArray (STUArray s) Word64 (ST s) 

Methods

getBounds :: Ix i => STUArray s i Word64 -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Word64 -> ST s Int

newArray :: Ix i => (i, i) -> Word64 -> ST s (STUArray s i Word64) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word64) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word64)

unsafeRead :: Ix i => STUArray s i Word64 -> Int -> ST s Word64

unsafeWrite :: Ix i => STUArray s i Word64 -> Int -> Word64 -> ST s ()

Haskell types that act in the place of DescritorProto values

newtype WireTag Source #

WireTag is the 32 bit value with the upper 29 bits being the FieldId and the lower 3 bits being the WireType

Constructors

WireTag 

Fields

Instances

Bounded WireTag Source # 
Enum WireTag Source # 
Eq WireTag Source # 

Methods

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

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

Data WireTag Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WireTag -> c WireTag #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WireTag #

toConstr :: WireTag -> Constr #

dataTypeOf :: WireTag -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c WireTag) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WireTag) #

gmapT :: (forall b. Data b => b -> b) -> WireTag -> WireTag #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WireTag -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WireTag -> r #

gmapQ :: (forall d. Data d => d -> u) -> WireTag -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WireTag -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WireTag -> m WireTag #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WireTag -> m WireTag #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WireTag -> m WireTag #

Num WireTag Source # 
Ord WireTag Source # 
Read WireTag Source # 
Show WireTag Source # 
Bits WireTag Source # 

newtype FieldId Source #

FieldId is the field number which can be in the range 1 to 2^29-1 but the value from 19000 to 19999 are forbidden (so sayeth Google).

Constructors

FieldId 

Fields

Instances

Bounded FieldId Source # 
Enum FieldId Source # 
Eq FieldId Source # 

Methods

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

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

Data FieldId Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldId -> c FieldId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FieldId #

toConstr :: FieldId -> Constr #

dataTypeOf :: FieldId -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FieldId) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FieldId) #

gmapT :: (forall b. Data b => b -> b) -> FieldId -> FieldId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldId -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldId -> r #

gmapQ :: (forall d. Data d => d -> u) -> FieldId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldId -> m FieldId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldId -> m FieldId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldId -> m FieldId #

Num FieldId Source # 
Ord FieldId Source # 
Read FieldId Source # 
Show FieldId Source # 
Ix FieldId Source # 

newtype WireType Source #

WireType is the 3 bit wire encoding value, and is currently in the range 0 to 5, leaving 6 and 7 currently invalid.

  • 0 Varint : int32, int64, uint32, uint64, sint32, sint64, bool, enum
  • 1 64-bit : fixed64, sfixed64, double
  • 2 Length-delimited : string, bytes, embedded messages
  • 3 Start group : groups (deprecated)
  • 4 End group : groups (deprecated)
  • 5 32-bit : fixed32, sfixed32, float

Constructors

WireType 

Fields

Instances

Bounded WireType Source # 
Enum WireType Source # 
Eq WireType Source # 
Data WireType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WireType -> c WireType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WireType #

toConstr :: WireType -> Constr #

dataTypeOf :: WireType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c WireType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WireType) #

gmapT :: (forall b. Data b => b -> b) -> WireType -> WireType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WireType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WireType -> r #

gmapQ :: (forall d. Data d => d -> u) -> WireType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WireType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WireType -> m WireType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WireType -> m WireType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WireType -> m WireType #

Num WireType Source # 
Ord WireType Source # 
Read WireType Source # 
Show WireType Source # 

newtype FieldType Source #

FieldType is the integer associated with the FieldDescriptorProto's Type. The allowed range is currently 1 to 18, as shown below (excerpt from descritor.proto)

   // 0 is reserved for errors.
   // Order is weird for historical reasons.
   TYPE_DOUBLE         = 1;
   TYPE_FLOAT          = 2;
   TYPE_INT64          = 3;   // Not ZigZag encoded.  Negative numbers
                              // take 10 bytes.  Use TYPE_SINT64 if negative
                              // values are likely.
   TYPE_UINT64         = 4;
   TYPE_INT32          = 5;   // Not ZigZag encoded.  Negative numbers
                              // take 10 bytes.  Use TYPE_SINT32 if negative
                              // values are likely.
   TYPE_FIXED64        = 6;
   TYPE_FIXED32        = 7;
   TYPE_BOOL           = 8;
   TYPE_STRING         = 9;
   TYPE_GROUP          = 10;  // Tag-delimited aggregate.
   TYPE_MESSAGE        = 11;  // Length-delimited aggregate.

   // New in version 2.
   TYPE_BYTES          = 12;
   TYPE_UINT32         = 13;
   TYPE_ENUM           = 14;
   TYPE_SFIXED32       = 15;
   TYPE_SFIXED64       = 16;
   TYPE_SINT32         = 17;  // Uses ZigZag encoding.
   TYPE_SINT64         = 18;  // Uses ZigZag encoding.

Constructors

FieldType 

Fields

Instances

Bounded FieldType Source # 
Enum FieldType Source # 
Eq FieldType Source # 
Data FieldType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldType -> c FieldType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FieldType #

toConstr :: FieldType -> Constr #

dataTypeOf :: FieldType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FieldType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FieldType) #

gmapT :: (forall b. Data b => b -> b) -> FieldType -> FieldType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldType -> r #

gmapQ :: (forall d. Data d => d -> u) -> FieldType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldType -> m FieldType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldType -> m FieldType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldType -> m FieldType #

Num FieldType Source # 
Ord FieldType Source # 
Read FieldType Source # 
Show FieldType Source # 

newtype EnumCode Source #

EnumCode is the Int32 assoicated with a EnumValueDescriptorProto and is in the range 0 to 2^31-1.

Constructors

EnumCode 

Fields

Instances

Bounded EnumCode Source # 
Eq EnumCode Source # 
Data EnumCode Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EnumCode -> c EnumCode #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EnumCode #

toConstr :: EnumCode -> Constr #

dataTypeOf :: EnumCode -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c EnumCode) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EnumCode) #

gmapT :: (forall b. Data b => b -> b) -> EnumCode -> EnumCode #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EnumCode -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EnumCode -> r #

gmapQ :: (forall d. Data d => d -> u) -> EnumCode -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EnumCode -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EnumCode -> m EnumCode #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EnumCode -> m EnumCode #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EnumCode -> m EnumCode #

Num EnumCode Source # 
Ord EnumCode Source # 
Read EnumCode Source # 
Show EnumCode Source # 

type WireSize = Int64 Source #

WireSize is the Int64 size type associated with the lazy bytestrings used in the Put and Get monads.

Some of the type classes implemented messages and fields

class Default a => Mergeable a where Source #

The Mergeable class is not a Monoid, mergeEmpty is not a left or right unit like mempty. The default mergeAppend is to take the second parameter and discard the first one. The mergeConcat defaults to foldl associativity.

NOTE: mergeEmpty has been removed in protocol buffers version 2. Use defaultValue instead. New strict fields would mean that required fields in messages will be automatic errors with mergeEmpty.

Methods

mergeAppend :: a -> a -> a Source #

mergeAppend is the right-biased merge of two values. A message (or group) is merged recursively. Required field are always taken from the second message. Optional field values are taken from the most defined message or the second message if both are set. Repeated fields have the sequences concatenated. Note that strings and bytes are NOT concatenated.

mergeConcat :: Foldable t => t a -> a Source #

mergeConcat is F.foldl mergeAppend defaultValue and this default definition is not overridden in any of the code except for the (Seq a) instance.

Instances

Mergeable Bool Source # 
Mergeable Double Source # 
Mergeable Float Source # 
Mergeable Int32 Source # 
Mergeable Int64 Source # 
Mergeable Word32 Source # 
Mergeable Word64 Source # 
Mergeable ByteString Source # 
Mergeable Utf8 Source # 
Mergeable ExtField Source # 
Mergeable UnknownField Source # 
Mergeable a => Mergeable (Maybe a) Source # 

Methods

mergeAppend :: Maybe a -> Maybe a -> Maybe a Source #

mergeConcat :: Foldable t => t (Maybe a) -> Maybe a Source #

Mergeable (Seq a) Source # 

Methods

mergeAppend :: Seq a -> Seq a -> Seq a Source #

mergeConcat :: Foldable t => t (Seq a) -> Seq a Source #

class Default a where Source #

The Default class has the default-default values of types. See http://code.google.com/apis/protocolbuffers/docs/proto.html#optional and also note that Enum types have a defaultValue that is the first one in the .proto file (there is always at least one value). Instances of this for messages hold any default value defined in the .proto file. defaultValue is where the MessageAPI function getVal looks when an optional field is not set.

Minimal complete definition

defaultValue

Methods

defaultValue :: a Source #

The defaultValue is never undefined or an error to evalute. This makes it much more useful compared to mergeEmpty. In a default message all Optional field values are set to Nothing and Repeated field values are empty.