{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -fno-warn-missing-fields #-}
{-# OPTIONS_GHC -fno-warn-missing-signatures #-}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}
module Agent where
import Prelude (($), (.), (>>=), (==), (++))
import qualified Prelude as P
import qualified Control.Exception as X
import qualified Control.Monad as M ( liftM, ap, when )
import Data.Functor ( (<$>) )
import qualified Data.ByteString.Lazy as LBS
import qualified Data.Hashable as H
import qualified Data.Int as I
import qualified Data.Maybe as M (catMaybes)
import qualified Data.Text.Lazy.Encoding as E ( decodeUtf8, encodeUtf8 )
import qualified Data.Text.Lazy as LT
import qualified GHC.Generics as G (Generic)
import qualified Data.Typeable as TY ( Typeable )
import qualified Data.HashMap.Strict as Map
import qualified Data.HashSet as Set
import qualified Data.Vector as Vector
import qualified Test.QuickCheck.Arbitrary as QC ( Arbitrary(..) )
import qualified Test.QuickCheck as QC ( elements )
import qualified Thrift as T
import qualified Thrift.Types as T
import qualified Thrift.Arbitraries as T
import qualified Jaeger_Types
import qualified Zipkincore_Types
import Agent_Types
import qualified Agent_Iface as Iface
data EmitZipkinBatch_args = EmitZipkinBatch_args  { EmitZipkinBatch_args -> Vector Span
emitZipkinBatch_args_spans :: (Vector.Vector Zipkincore_Types.Span)
  } deriving (Int -> EmitZipkinBatch_args -> ShowS
[EmitZipkinBatch_args] -> ShowS
EmitZipkinBatch_args -> String
(Int -> EmitZipkinBatch_args -> ShowS)
-> (EmitZipkinBatch_args -> String)
-> ([EmitZipkinBatch_args] -> ShowS)
-> Show EmitZipkinBatch_args
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EmitZipkinBatch_args] -> ShowS
$cshowList :: [EmitZipkinBatch_args] -> ShowS
show :: EmitZipkinBatch_args -> String
$cshow :: EmitZipkinBatch_args -> String
showsPrec :: Int -> EmitZipkinBatch_args -> ShowS
$cshowsPrec :: Int -> EmitZipkinBatch_args -> ShowS
P.Show,EmitZipkinBatch_args -> EmitZipkinBatch_args -> Bool
(EmitZipkinBatch_args -> EmitZipkinBatch_args -> Bool)
-> (EmitZipkinBatch_args -> EmitZipkinBatch_args -> Bool)
-> Eq EmitZipkinBatch_args
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EmitZipkinBatch_args -> EmitZipkinBatch_args -> Bool
$c/= :: EmitZipkinBatch_args -> EmitZipkinBatch_args -> Bool
== :: EmitZipkinBatch_args -> EmitZipkinBatch_args -> Bool
$c== :: EmitZipkinBatch_args -> EmitZipkinBatch_args -> Bool
P.Eq,(forall x. EmitZipkinBatch_args -> Rep EmitZipkinBatch_args x)
-> (forall x. Rep EmitZipkinBatch_args x -> EmitZipkinBatch_args)
-> Generic EmitZipkinBatch_args
forall x. Rep EmitZipkinBatch_args x -> EmitZipkinBatch_args
forall x. EmitZipkinBatch_args -> Rep EmitZipkinBatch_args x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EmitZipkinBatch_args x -> EmitZipkinBatch_args
$cfrom :: forall x. EmitZipkinBatch_args -> Rep EmitZipkinBatch_args x
G.Generic,TY.Typeable)
instance H.Hashable EmitZipkinBatch_args where
  hashWithSalt :: Int -> EmitZipkinBatch_args -> Int
hashWithSalt Int
salt EmitZipkinBatch_args
record = Int
salt   Int -> Vector Span -> Int
forall a. Hashable a => Int -> a -> Int
`H.hashWithSalt` EmitZipkinBatch_args -> Vector Span
emitZipkinBatch_args_spans EmitZipkinBatch_args
record  
instance QC.Arbitrary EmitZipkinBatch_args where 
  arbitrary :: Gen EmitZipkinBatch_args
arbitrary = (Vector Span -> EmitZipkinBatch_args)
-> Gen (Vector Span) -> Gen EmitZipkinBatch_args
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
M.liftM Vector Span -> EmitZipkinBatch_args
EmitZipkinBatch_args (Gen (Vector Span)
forall a. Arbitrary a => Gen a
QC.arbitrary)
  shrink :: EmitZipkinBatch_args -> [EmitZipkinBatch_args]
shrink EmitZipkinBatch_args
obj | EmitZipkinBatch_args
obj EmitZipkinBatch_args -> EmitZipkinBatch_args -> Bool
forall a. Eq a => a -> a -> Bool
== EmitZipkinBatch_args
default_EmitZipkinBatch_args = []
             | Bool
P.otherwise = [Maybe EmitZipkinBatch_args] -> [EmitZipkinBatch_args]
forall a. [Maybe a] -> [a]
M.catMaybes
    [ if EmitZipkinBatch_args
obj EmitZipkinBatch_args -> EmitZipkinBatch_args -> Bool
forall a. Eq a => a -> a -> Bool
== EmitZipkinBatch_args
default_EmitZipkinBatch_args{emitZipkinBatch_args_spans :: Vector Span
emitZipkinBatch_args_spans = EmitZipkinBatch_args -> Vector Span
emitZipkinBatch_args_spans EmitZipkinBatch_args
obj} then Maybe EmitZipkinBatch_args
forall a. Maybe a
P.Nothing else EmitZipkinBatch_args -> Maybe EmitZipkinBatch_args
forall a. a -> Maybe a
P.Just (EmitZipkinBatch_args -> Maybe EmitZipkinBatch_args)
-> EmitZipkinBatch_args -> Maybe EmitZipkinBatch_args
forall a b. (a -> b) -> a -> b
$ EmitZipkinBatch_args
default_EmitZipkinBatch_args{emitZipkinBatch_args_spans :: Vector Span
emitZipkinBatch_args_spans = EmitZipkinBatch_args -> Vector Span
emitZipkinBatch_args_spans EmitZipkinBatch_args
obj}
    ]
from_EmitZipkinBatch_args :: EmitZipkinBatch_args -> T.ThriftVal
from_EmitZipkinBatch_args :: EmitZipkinBatch_args -> ThriftVal
from_EmitZipkinBatch_args EmitZipkinBatch_args
record = HashMap Int16 (Text, ThriftVal) -> ThriftVal
T.TStruct (HashMap Int16 (Text, ThriftVal) -> ThriftVal)
-> HashMap Int16 (Text, ThriftVal) -> ThriftVal
forall a b. (a -> b) -> a -> b
$ [(Int16, (Text, ThriftVal))] -> HashMap Int16 (Text, ThriftVal)
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
Map.fromList ([(Int16, (Text, ThriftVal))] -> HashMap Int16 (Text, ThriftVal))
-> [(Int16, (Text, ThriftVal))] -> HashMap Int16 (Text, ThriftVal)
forall a b. (a -> b) -> a -> b
$ [Maybe (Int16, (Text, ThriftVal))] -> [(Int16, (Text, ThriftVal))]
forall a. [Maybe a] -> [a]
M.catMaybes
  [ (\Vector Span
_v2 -> (Int16, (Text, ThriftVal)) -> Maybe (Int16, (Text, ThriftVal))
forall a. a -> Maybe a
P.Just (Int16
1, (Text
"spans",ThriftType -> [ThriftVal] -> ThriftVal
T.TList (TypeMap -> ThriftType
T.T_STRUCT TypeMap
Zipkincore_Types.typemap_Span) ([ThriftVal] -> ThriftVal) -> [ThriftVal] -> ThriftVal
forall a b. (a -> b) -> a -> b
$ (Span -> ThriftVal) -> [Span] -> [ThriftVal]
forall a b. (a -> b) -> [a] -> [b]
P.map (\Span
_v4 -> Span -> ThriftVal
Zipkincore_Types.from_Span Span
_v4) ([Span] -> [ThriftVal]) -> [Span] -> [ThriftVal]
forall a b. (a -> b) -> a -> b
$ Vector Span -> [Span]
forall a. Vector a -> [a]
Vector.toList Vector Span
_v2))) (Vector Span -> Maybe (Int16, (Text, ThriftVal)))
-> Vector Span -> Maybe (Int16, (Text, ThriftVal))
forall a b. (a -> b) -> a -> b
$ EmitZipkinBatch_args -> Vector Span
emitZipkinBatch_args_spans EmitZipkinBatch_args
record
  ]
write_EmitZipkinBatch_args :: T.Protocol p => p -> EmitZipkinBatch_args -> P.IO ()
write_EmitZipkinBatch_args :: p -> EmitZipkinBatch_args -> IO ()
write_EmitZipkinBatch_args p
oprot EmitZipkinBatch_args
record = p -> ThriftVal -> IO ()
forall a. Protocol a => a -> ThriftVal -> IO ()
T.writeVal p
oprot (ThriftVal -> IO ()) -> ThriftVal -> IO ()
forall a b. (a -> b) -> a -> b
$ EmitZipkinBatch_args -> ThriftVal
from_EmitZipkinBatch_args EmitZipkinBatch_args
record
encode_EmitZipkinBatch_args :: T.StatelessProtocol p => p -> EmitZipkinBatch_args -> LBS.ByteString
encode_EmitZipkinBatch_args :: p -> EmitZipkinBatch_args -> ByteString
encode_EmitZipkinBatch_args p
oprot EmitZipkinBatch_args
record = p -> ThriftVal -> ByteString
forall a. StatelessProtocol a => a -> ThriftVal -> ByteString
T.serializeVal p
oprot (ThriftVal -> ByteString) -> ThriftVal -> ByteString
forall a b. (a -> b) -> a -> b
$ EmitZipkinBatch_args -> ThriftVal
from_EmitZipkinBatch_args EmitZipkinBatch_args
record
to_EmitZipkinBatch_args :: T.ThriftVal -> EmitZipkinBatch_args
to_EmitZipkinBatch_args :: ThriftVal -> EmitZipkinBatch_args
to_EmitZipkinBatch_args (T.TStruct HashMap Int16 (Text, ThriftVal)
fields) = EmitZipkinBatch_args :: Vector Span -> EmitZipkinBatch_args
EmitZipkinBatch_args{
  emitZipkinBatch_args_spans :: Vector Span
emitZipkinBatch_args_spans = Vector Span
-> ((Text, ThriftVal) -> Vector Span)
-> Maybe (Text, ThriftVal)
-> Vector Span
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (EmitZipkinBatch_args -> Vector Span
emitZipkinBatch_args_spans EmitZipkinBatch_args
default_EmitZipkinBatch_args) (\(Text
_,ThriftVal
_val6) -> (case ThriftVal
_val6 of {T.TList ThriftType
_ [ThriftVal]
_val7 -> ([Span] -> Vector Span
forall a. [a] -> Vector a
Vector.fromList ([Span] -> Vector Span) -> [Span] -> Vector Span
forall a b. (a -> b) -> a -> b
$ (ThriftVal -> Span) -> [ThriftVal] -> [Span]
forall a b. (a -> b) -> [a] -> [b]
P.map (\ThriftVal
_v8 -> (case ThriftVal
_v8 of {T.TStruct HashMap Int16 (Text, ThriftVal)
_val9 -> (ThriftVal -> Span
Zipkincore_Types.to_Span (HashMap Int16 (Text, ThriftVal) -> ThriftVal
T.TStruct HashMap Int16 (Text, ThriftVal)
_val9)); ThriftVal
_ -> String -> Span
forall a. HasCallStack => String -> a
P.error String
"wrong type"})) [ThriftVal]
_val7); ThriftVal
_ -> String -> Vector Span
forall a. HasCallStack => String -> a
P.error String
"wrong type"})) (Int16 -> HashMap Int16 (Text, ThriftVal) -> Maybe (Text, ThriftVal)
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
Map.lookup (Int16
1) HashMap Int16 (Text, ThriftVal)
fields)
  }
to_EmitZipkinBatch_args ThriftVal
_ = String -> EmitZipkinBatch_args
forall a. HasCallStack => String -> a
P.error String
"not a struct"
read_EmitZipkinBatch_args :: T.Protocol p => p -> P.IO EmitZipkinBatch_args
read_EmitZipkinBatch_args :: p -> IO EmitZipkinBatch_args
read_EmitZipkinBatch_args p
iprot = ThriftVal -> EmitZipkinBatch_args
to_EmitZipkinBatch_args (ThriftVal -> EmitZipkinBatch_args)
-> IO ThriftVal -> IO EmitZipkinBatch_args
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> p -> ThriftType -> IO ThriftVal
forall a. Protocol a => a -> ThriftType -> IO ThriftVal
T.readVal p
iprot (TypeMap -> ThriftType
T.T_STRUCT TypeMap
typemap_EmitZipkinBatch_args)
decode_EmitZipkinBatch_args :: T.StatelessProtocol p => p -> LBS.ByteString -> EmitZipkinBatch_args
decode_EmitZipkinBatch_args :: p -> ByteString -> EmitZipkinBatch_args
decode_EmitZipkinBatch_args p
iprot ByteString
bs = ThriftVal -> EmitZipkinBatch_args
to_EmitZipkinBatch_args (ThriftVal -> EmitZipkinBatch_args)
-> ThriftVal -> EmitZipkinBatch_args
forall a b. (a -> b) -> a -> b
$ p -> ThriftType -> ByteString -> ThriftVal
forall a.
StatelessProtocol a =>
a -> ThriftType -> ByteString -> ThriftVal
T.deserializeVal p
iprot (TypeMap -> ThriftType
T.T_STRUCT TypeMap
typemap_EmitZipkinBatch_args) ByteString
bs
typemap_EmitZipkinBatch_args :: T.TypeMap
typemap_EmitZipkinBatch_args :: TypeMap
typemap_EmitZipkinBatch_args = [(Int16, (Text, ThriftType))] -> TypeMap
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
Map.fromList [(Int16
1,(Text
"spans",(ThriftType -> ThriftType
T.T_LIST (TypeMap -> ThriftType
T.T_STRUCT TypeMap
Zipkincore_Types.typemap_Span))))]
default_EmitZipkinBatch_args :: EmitZipkinBatch_args
default_EmitZipkinBatch_args :: EmitZipkinBatch_args
default_EmitZipkinBatch_args = EmitZipkinBatch_args :: Vector Span -> EmitZipkinBatch_args
EmitZipkinBatch_args{
  emitZipkinBatch_args_spans :: Vector Span
emitZipkinBatch_args_spans = Vector Span
forall a. Vector a
Vector.empty}
data EmitZipkinBatch_result = EmitZipkinBatch_result deriving (Int -> EmitZipkinBatch_result -> ShowS
[EmitZipkinBatch_result] -> ShowS
EmitZipkinBatch_result -> String
(Int -> EmitZipkinBatch_result -> ShowS)
-> (EmitZipkinBatch_result -> String)
-> ([EmitZipkinBatch_result] -> ShowS)
-> Show EmitZipkinBatch_result
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EmitZipkinBatch_result] -> ShowS
$cshowList :: [EmitZipkinBatch_result] -> ShowS
show :: EmitZipkinBatch_result -> String
$cshow :: EmitZipkinBatch_result -> String
showsPrec :: Int -> EmitZipkinBatch_result -> ShowS
$cshowsPrec :: Int -> EmitZipkinBatch_result -> ShowS
P.Show,EmitZipkinBatch_result -> EmitZipkinBatch_result -> Bool
(EmitZipkinBatch_result -> EmitZipkinBatch_result -> Bool)
-> (EmitZipkinBatch_result -> EmitZipkinBatch_result -> Bool)
-> Eq EmitZipkinBatch_result
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EmitZipkinBatch_result -> EmitZipkinBatch_result -> Bool
$c/= :: EmitZipkinBatch_result -> EmitZipkinBatch_result -> Bool
== :: EmitZipkinBatch_result -> EmitZipkinBatch_result -> Bool
$c== :: EmitZipkinBatch_result -> EmitZipkinBatch_result -> Bool
P.Eq,(forall x. EmitZipkinBatch_result -> Rep EmitZipkinBatch_result x)
-> (forall x.
    Rep EmitZipkinBatch_result x -> EmitZipkinBatch_result)
-> Generic EmitZipkinBatch_result
forall x. Rep EmitZipkinBatch_result x -> EmitZipkinBatch_result
forall x. EmitZipkinBatch_result -> Rep EmitZipkinBatch_result x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EmitZipkinBatch_result x -> EmitZipkinBatch_result
$cfrom :: forall x. EmitZipkinBatch_result -> Rep EmitZipkinBatch_result x
G.Generic,TY.Typeable)
instance H.Hashable EmitZipkinBatch_result where
  hashWithSalt :: Int -> EmitZipkinBatch_result -> Int
hashWithSalt Int
salt EmitZipkinBatch_result
record = Int
salt  
instance QC.Arbitrary EmitZipkinBatch_result where 
  arbitrary :: Gen EmitZipkinBatch_result
arbitrary = [EmitZipkinBatch_result] -> Gen EmitZipkinBatch_result
forall a. [a] -> Gen a
QC.elements [EmitZipkinBatch_result
EmitZipkinBatch_result]
from_EmitZipkinBatch_result :: EmitZipkinBatch_result -> T.ThriftVal
from_EmitZipkinBatch_result :: EmitZipkinBatch_result -> ThriftVal
from_EmitZipkinBatch_result EmitZipkinBatch_result
record = HashMap Int16 (Text, ThriftVal) -> ThriftVal
T.TStruct (HashMap Int16 (Text, ThriftVal) -> ThriftVal)
-> HashMap Int16 (Text, ThriftVal) -> ThriftVal
forall a b. (a -> b) -> a -> b
$ [(Int16, (Text, ThriftVal))] -> HashMap Int16 (Text, ThriftVal)
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
Map.fromList ([(Int16, (Text, ThriftVal))] -> HashMap Int16 (Text, ThriftVal))
-> [(Int16, (Text, ThriftVal))] -> HashMap Int16 (Text, ThriftVal)
forall a b. (a -> b) -> a -> b
$ [Maybe (Int16, (Text, ThriftVal))] -> [(Int16, (Text, ThriftVal))]
forall a. [Maybe a] -> [a]
M.catMaybes
  []
write_EmitZipkinBatch_result :: T.Protocol p => p -> EmitZipkinBatch_result -> P.IO ()
write_EmitZipkinBatch_result :: p -> EmitZipkinBatch_result -> IO ()
write_EmitZipkinBatch_result p
oprot EmitZipkinBatch_result
record = p -> ThriftVal -> IO ()
forall a. Protocol a => a -> ThriftVal -> IO ()
T.writeVal p
oprot (ThriftVal -> IO ()) -> ThriftVal -> IO ()
forall a b. (a -> b) -> a -> b
$ EmitZipkinBatch_result -> ThriftVal
from_EmitZipkinBatch_result EmitZipkinBatch_result
record
encode_EmitZipkinBatch_result :: T.StatelessProtocol p => p -> EmitZipkinBatch_result -> LBS.ByteString
encode_EmitZipkinBatch_result :: p -> EmitZipkinBatch_result -> ByteString
encode_EmitZipkinBatch_result p
oprot EmitZipkinBatch_result
record = p -> ThriftVal -> ByteString
forall a. StatelessProtocol a => a -> ThriftVal -> ByteString
T.serializeVal p
oprot (ThriftVal -> ByteString) -> ThriftVal -> ByteString
forall a b. (a -> b) -> a -> b
$ EmitZipkinBatch_result -> ThriftVal
from_EmitZipkinBatch_result EmitZipkinBatch_result
record
to_EmitZipkinBatch_result :: T.ThriftVal -> EmitZipkinBatch_result
to_EmitZipkinBatch_result :: ThriftVal -> EmitZipkinBatch_result
to_EmitZipkinBatch_result (T.TStruct HashMap Int16 (Text, ThriftVal)
fields) = EmitZipkinBatch_result :: EmitZipkinBatch_result
EmitZipkinBatch_result{
  }
to_EmitZipkinBatch_result ThriftVal
_ = String -> EmitZipkinBatch_result
forall a. HasCallStack => String -> a
P.error String
"not a struct"
read_EmitZipkinBatch_result :: T.Protocol p => p -> P.IO EmitZipkinBatch_result
read_EmitZipkinBatch_result :: p -> IO EmitZipkinBatch_result
read_EmitZipkinBatch_result p
iprot = ThriftVal -> EmitZipkinBatch_result
to_EmitZipkinBatch_result (ThriftVal -> EmitZipkinBatch_result)
-> IO ThriftVal -> IO EmitZipkinBatch_result
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> p -> ThriftType -> IO ThriftVal
forall a. Protocol a => a -> ThriftType -> IO ThriftVal
T.readVal p
iprot (TypeMap -> ThriftType
T.T_STRUCT TypeMap
typemap_EmitZipkinBatch_result)
decode_EmitZipkinBatch_result :: T.StatelessProtocol p => p -> LBS.ByteString -> EmitZipkinBatch_result
decode_EmitZipkinBatch_result :: p -> ByteString -> EmitZipkinBatch_result
decode_EmitZipkinBatch_result p
iprot ByteString
bs = ThriftVal -> EmitZipkinBatch_result
to_EmitZipkinBatch_result (ThriftVal -> EmitZipkinBatch_result)
-> ThriftVal -> EmitZipkinBatch_result
forall a b. (a -> b) -> a -> b
$ p -> ThriftType -> ByteString -> ThriftVal
forall a.
StatelessProtocol a =>
a -> ThriftType -> ByteString -> ThriftVal
T.deserializeVal p
iprot (TypeMap -> ThriftType
T.T_STRUCT TypeMap
typemap_EmitZipkinBatch_result) ByteString
bs
typemap_EmitZipkinBatch_result :: T.TypeMap
typemap_EmitZipkinBatch_result :: TypeMap
typemap_EmitZipkinBatch_result = [(Int16, (Text, ThriftType))] -> TypeMap
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
Map.fromList []
default_EmitZipkinBatch_result :: EmitZipkinBatch_result
default_EmitZipkinBatch_result :: EmitZipkinBatch_result
default_EmitZipkinBatch_result = EmitZipkinBatch_result :: EmitZipkinBatch_result
EmitZipkinBatch_result{
}
data EmitBatch_args = EmitBatch_args  { EmitBatch_args -> Batch
emitBatch_args_batch :: Jaeger_Types.Batch
  } deriving (Int -> EmitBatch_args -> ShowS
[EmitBatch_args] -> ShowS
EmitBatch_args -> String
(Int -> EmitBatch_args -> ShowS)
-> (EmitBatch_args -> String)
-> ([EmitBatch_args] -> ShowS)
-> Show EmitBatch_args
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EmitBatch_args] -> ShowS
$cshowList :: [EmitBatch_args] -> ShowS
show :: EmitBatch_args -> String
$cshow :: EmitBatch_args -> String
showsPrec :: Int -> EmitBatch_args -> ShowS
$cshowsPrec :: Int -> EmitBatch_args -> ShowS
P.Show,EmitBatch_args -> EmitBatch_args -> Bool
(EmitBatch_args -> EmitBatch_args -> Bool)
-> (EmitBatch_args -> EmitBatch_args -> Bool) -> Eq EmitBatch_args
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EmitBatch_args -> EmitBatch_args -> Bool
$c/= :: EmitBatch_args -> EmitBatch_args -> Bool
== :: EmitBatch_args -> EmitBatch_args -> Bool
$c== :: EmitBatch_args -> EmitBatch_args -> Bool
P.Eq,(forall x. EmitBatch_args -> Rep EmitBatch_args x)
-> (forall x. Rep EmitBatch_args x -> EmitBatch_args)
-> Generic EmitBatch_args
forall x. Rep EmitBatch_args x -> EmitBatch_args
forall x. EmitBatch_args -> Rep EmitBatch_args x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EmitBatch_args x -> EmitBatch_args
$cfrom :: forall x. EmitBatch_args -> Rep EmitBatch_args x
G.Generic,TY.Typeable)
instance H.Hashable EmitBatch_args where
  hashWithSalt :: Int -> EmitBatch_args -> Int
hashWithSalt Int
salt EmitBatch_args
record = Int
salt   Int -> Batch -> Int
forall a. Hashable a => Int -> a -> Int
`H.hashWithSalt` EmitBatch_args -> Batch
emitBatch_args_batch EmitBatch_args
record  
instance QC.Arbitrary EmitBatch_args where 
  arbitrary :: Gen EmitBatch_args
arbitrary = (Batch -> EmitBatch_args) -> Gen Batch -> Gen EmitBatch_args
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
M.liftM Batch -> EmitBatch_args
EmitBatch_args (Gen Batch
forall a. Arbitrary a => Gen a
QC.arbitrary)
  shrink :: EmitBatch_args -> [EmitBatch_args]
shrink EmitBatch_args
obj | EmitBatch_args
obj EmitBatch_args -> EmitBatch_args -> Bool
forall a. Eq a => a -> a -> Bool
== EmitBatch_args
default_EmitBatch_args = []
             | Bool
P.otherwise = [Maybe EmitBatch_args] -> [EmitBatch_args]
forall a. [Maybe a] -> [a]
M.catMaybes
    [ if EmitBatch_args
obj EmitBatch_args -> EmitBatch_args -> Bool
forall a. Eq a => a -> a -> Bool
== EmitBatch_args
default_EmitBatch_args{emitBatch_args_batch :: Batch
emitBatch_args_batch = EmitBatch_args -> Batch
emitBatch_args_batch EmitBatch_args
obj} then Maybe EmitBatch_args
forall a. Maybe a
P.Nothing else EmitBatch_args -> Maybe EmitBatch_args
forall a. a -> Maybe a
P.Just (EmitBatch_args -> Maybe EmitBatch_args)
-> EmitBatch_args -> Maybe EmitBatch_args
forall a b. (a -> b) -> a -> b
$ EmitBatch_args
default_EmitBatch_args{emitBatch_args_batch :: Batch
emitBatch_args_batch = EmitBatch_args -> Batch
emitBatch_args_batch EmitBatch_args
obj}
    ]
from_EmitBatch_args :: EmitBatch_args -> T.ThriftVal
from_EmitBatch_args :: EmitBatch_args -> ThriftVal
from_EmitBatch_args EmitBatch_args
record = HashMap Int16 (Text, ThriftVal) -> ThriftVal
T.TStruct (HashMap Int16 (Text, ThriftVal) -> ThriftVal)
-> HashMap Int16 (Text, ThriftVal) -> ThriftVal
forall a b. (a -> b) -> a -> b
$ [(Int16, (Text, ThriftVal))] -> HashMap Int16 (Text, ThriftVal)
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
Map.fromList ([(Int16, (Text, ThriftVal))] -> HashMap Int16 (Text, ThriftVal))
-> [(Int16, (Text, ThriftVal))] -> HashMap Int16 (Text, ThriftVal)
forall a b. (a -> b) -> a -> b
$ [Maybe (Int16, (Text, ThriftVal))] -> [(Int16, (Text, ThriftVal))]
forall a. [Maybe a] -> [a]
M.catMaybes
  [ (\Batch
_v17 -> (Int16, (Text, ThriftVal)) -> Maybe (Int16, (Text, ThriftVal))
forall a. a -> Maybe a
P.Just (Int16
1, (Text
"batch",Batch -> ThriftVal
Jaeger_Types.from_Batch Batch
_v17))) (Batch -> Maybe (Int16, (Text, ThriftVal)))
-> Batch -> Maybe (Int16, (Text, ThriftVal))
forall a b. (a -> b) -> a -> b
$ EmitBatch_args -> Batch
emitBatch_args_batch EmitBatch_args
record
  ]
write_EmitBatch_args :: T.Protocol p => p -> EmitBatch_args -> P.IO ()
write_EmitBatch_args :: p -> EmitBatch_args -> IO ()
write_EmitBatch_args p
oprot EmitBatch_args
record = p -> ThriftVal -> IO ()
forall a. Protocol a => a -> ThriftVal -> IO ()
T.writeVal p
oprot (ThriftVal -> IO ()) -> ThriftVal -> IO ()
forall a b. (a -> b) -> a -> b
$ EmitBatch_args -> ThriftVal
from_EmitBatch_args EmitBatch_args
record
encode_EmitBatch_args :: T.StatelessProtocol p => p -> EmitBatch_args -> LBS.ByteString
encode_EmitBatch_args :: p -> EmitBatch_args -> ByteString
encode_EmitBatch_args p
oprot EmitBatch_args
record = p -> ThriftVal -> ByteString
forall a. StatelessProtocol a => a -> ThriftVal -> ByteString
T.serializeVal p
oprot (ThriftVal -> ByteString) -> ThriftVal -> ByteString
forall a b. (a -> b) -> a -> b
$ EmitBatch_args -> ThriftVal
from_EmitBatch_args EmitBatch_args
record
to_EmitBatch_args :: T.ThriftVal -> EmitBatch_args
to_EmitBatch_args :: ThriftVal -> EmitBatch_args
to_EmitBatch_args (T.TStruct HashMap Int16 (Text, ThriftVal)
fields) = EmitBatch_args :: Batch -> EmitBatch_args
EmitBatch_args{
  emitBatch_args_batch :: Batch
emitBatch_args_batch = Batch
-> ((Text, ThriftVal) -> Batch) -> Maybe (Text, ThriftVal) -> Batch
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (EmitBatch_args -> Batch
emitBatch_args_batch EmitBatch_args
default_EmitBatch_args) (\(Text
_,ThriftVal
_val19) -> (case ThriftVal
_val19 of {T.TStruct HashMap Int16 (Text, ThriftVal)
_val20 -> (ThriftVal -> Batch
Jaeger_Types.to_Batch (HashMap Int16 (Text, ThriftVal) -> ThriftVal
T.TStruct HashMap Int16 (Text, ThriftVal)
_val20)); ThriftVal
_ -> String -> Batch
forall a. HasCallStack => String -> a
P.error String
"wrong type"})) (Int16 -> HashMap Int16 (Text, ThriftVal) -> Maybe (Text, ThriftVal)
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
Map.lookup (Int16
1) HashMap Int16 (Text, ThriftVal)
fields)
  }
to_EmitBatch_args ThriftVal
_ = String -> EmitBatch_args
forall a. HasCallStack => String -> a
P.error String
"not a struct"
read_EmitBatch_args :: T.Protocol p => p -> P.IO EmitBatch_args
read_EmitBatch_args :: p -> IO EmitBatch_args
read_EmitBatch_args p
iprot = ThriftVal -> EmitBatch_args
to_EmitBatch_args (ThriftVal -> EmitBatch_args) -> IO ThriftVal -> IO EmitBatch_args
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> p -> ThriftType -> IO ThriftVal
forall a. Protocol a => a -> ThriftType -> IO ThriftVal
T.readVal p
iprot (TypeMap -> ThriftType
T.T_STRUCT TypeMap
typemap_EmitBatch_args)
decode_EmitBatch_args :: T.StatelessProtocol p => p -> LBS.ByteString -> EmitBatch_args
decode_EmitBatch_args :: p -> ByteString -> EmitBatch_args
decode_EmitBatch_args p
iprot ByteString
bs = ThriftVal -> EmitBatch_args
to_EmitBatch_args (ThriftVal -> EmitBatch_args) -> ThriftVal -> EmitBatch_args
forall a b. (a -> b) -> a -> b
$ p -> ThriftType -> ByteString -> ThriftVal
forall a.
StatelessProtocol a =>
a -> ThriftType -> ByteString -> ThriftVal
T.deserializeVal p
iprot (TypeMap -> ThriftType
T.T_STRUCT TypeMap
typemap_EmitBatch_args) ByteString
bs
typemap_EmitBatch_args :: T.TypeMap
typemap_EmitBatch_args :: TypeMap
typemap_EmitBatch_args = [(Int16, (Text, ThriftType))] -> TypeMap
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
Map.fromList [(Int16
1,(Text
"batch",(TypeMap -> ThriftType
T.T_STRUCT TypeMap
Jaeger_Types.typemap_Batch)))]
default_EmitBatch_args :: EmitBatch_args
default_EmitBatch_args :: EmitBatch_args
default_EmitBatch_args = EmitBatch_args :: Batch -> EmitBatch_args
EmitBatch_args{
  emitBatch_args_batch :: Batch
emitBatch_args_batch = Batch
Jaeger_Types.default_Batch}
data EmitBatch_result = EmitBatch_result deriving (Int -> EmitBatch_result -> ShowS
[EmitBatch_result] -> ShowS
EmitBatch_result -> String
(Int -> EmitBatch_result -> ShowS)
-> (EmitBatch_result -> String)
-> ([EmitBatch_result] -> ShowS)
-> Show EmitBatch_result
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EmitBatch_result] -> ShowS
$cshowList :: [EmitBatch_result] -> ShowS
show :: EmitBatch_result -> String
$cshow :: EmitBatch_result -> String
showsPrec :: Int -> EmitBatch_result -> ShowS
$cshowsPrec :: Int -> EmitBatch_result -> ShowS
P.Show,EmitBatch_result -> EmitBatch_result -> Bool
(EmitBatch_result -> EmitBatch_result -> Bool)
-> (EmitBatch_result -> EmitBatch_result -> Bool)
-> Eq EmitBatch_result
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EmitBatch_result -> EmitBatch_result -> Bool
$c/= :: EmitBatch_result -> EmitBatch_result -> Bool
== :: EmitBatch_result -> EmitBatch_result -> Bool
$c== :: EmitBatch_result -> EmitBatch_result -> Bool
P.Eq,(forall x. EmitBatch_result -> Rep EmitBatch_result x)
-> (forall x. Rep EmitBatch_result x -> EmitBatch_result)
-> Generic EmitBatch_result
forall x. Rep EmitBatch_result x -> EmitBatch_result
forall x. EmitBatch_result -> Rep EmitBatch_result x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EmitBatch_result x -> EmitBatch_result
$cfrom :: forall x. EmitBatch_result -> Rep EmitBatch_result x
G.Generic,TY.Typeable)
instance H.Hashable EmitBatch_result where
  hashWithSalt :: Int -> EmitBatch_result -> Int
hashWithSalt Int
salt EmitBatch_result
record = Int
salt  
instance QC.Arbitrary EmitBatch_result where 
  arbitrary :: Gen EmitBatch_result
arbitrary = [EmitBatch_result] -> Gen EmitBatch_result
forall a. [a] -> Gen a
QC.elements [EmitBatch_result
EmitBatch_result]
from_EmitBatch_result :: EmitBatch_result -> T.ThriftVal
from_EmitBatch_result :: EmitBatch_result -> ThriftVal
from_EmitBatch_result EmitBatch_result
record = HashMap Int16 (Text, ThriftVal) -> ThriftVal
T.TStruct (HashMap Int16 (Text, ThriftVal) -> ThriftVal)
-> HashMap Int16 (Text, ThriftVal) -> ThriftVal
forall a b. (a -> b) -> a -> b
$ [(Int16, (Text, ThriftVal))] -> HashMap Int16 (Text, ThriftVal)
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
Map.fromList ([(Int16, (Text, ThriftVal))] -> HashMap Int16 (Text, ThriftVal))
-> [(Int16, (Text, ThriftVal))] -> HashMap Int16 (Text, ThriftVal)
forall a b. (a -> b) -> a -> b
$ [Maybe (Int16, (Text, ThriftVal))] -> [(Int16, (Text, ThriftVal))]
forall a. [Maybe a] -> [a]
M.catMaybes
  []
write_EmitBatch_result :: T.Protocol p => p -> EmitBatch_result -> P.IO ()
write_EmitBatch_result :: p -> EmitBatch_result -> IO ()
write_EmitBatch_result p
oprot EmitBatch_result
record = p -> ThriftVal -> IO ()
forall a. Protocol a => a -> ThriftVal -> IO ()
T.writeVal p
oprot (ThriftVal -> IO ()) -> ThriftVal -> IO ()
forall a b. (a -> b) -> a -> b
$ EmitBatch_result -> ThriftVal
from_EmitBatch_result EmitBatch_result
record
encode_EmitBatch_result :: T.StatelessProtocol p => p -> EmitBatch_result -> LBS.ByteString
encode_EmitBatch_result :: p -> EmitBatch_result -> ByteString
encode_EmitBatch_result p
oprot EmitBatch_result
record = p -> ThriftVal -> ByteString
forall a. StatelessProtocol a => a -> ThriftVal -> ByteString
T.serializeVal p
oprot (ThriftVal -> ByteString) -> ThriftVal -> ByteString
forall a b. (a -> b) -> a -> b
$ EmitBatch_result -> ThriftVal
from_EmitBatch_result EmitBatch_result
record
to_EmitBatch_result :: T.ThriftVal -> EmitBatch_result
to_EmitBatch_result :: ThriftVal -> EmitBatch_result
to_EmitBatch_result (T.TStruct HashMap Int16 (Text, ThriftVal)
fields) = EmitBatch_result :: EmitBatch_result
EmitBatch_result{
  }
to_EmitBatch_result ThriftVal
_ = String -> EmitBatch_result
forall a. HasCallStack => String -> a
P.error String
"not a struct"
read_EmitBatch_result :: T.Protocol p => p -> P.IO EmitBatch_result
read_EmitBatch_result :: p -> IO EmitBatch_result
read_EmitBatch_result p
iprot = ThriftVal -> EmitBatch_result
to_EmitBatch_result (ThriftVal -> EmitBatch_result)
-> IO ThriftVal -> IO EmitBatch_result
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> p -> ThriftType -> IO ThriftVal
forall a. Protocol a => a -> ThriftType -> IO ThriftVal
T.readVal p
iprot (TypeMap -> ThriftType
T.T_STRUCT TypeMap
typemap_EmitBatch_result)
decode_EmitBatch_result :: T.StatelessProtocol p => p -> LBS.ByteString -> EmitBatch_result
decode_EmitBatch_result :: p -> ByteString -> EmitBatch_result
decode_EmitBatch_result p
iprot ByteString
bs = ThriftVal -> EmitBatch_result
to_EmitBatch_result (ThriftVal -> EmitBatch_result) -> ThriftVal -> EmitBatch_result
forall a b. (a -> b) -> a -> b
$ p -> ThriftType -> ByteString -> ThriftVal
forall a.
StatelessProtocol a =>
a -> ThriftType -> ByteString -> ThriftVal
T.deserializeVal p
iprot (TypeMap -> ThriftType
T.T_STRUCT TypeMap
typemap_EmitBatch_result) ByteString
bs
typemap_EmitBatch_result :: T.TypeMap
typemap_EmitBatch_result :: TypeMap
typemap_EmitBatch_result = [(Int16, (Text, ThriftType))] -> TypeMap
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
Map.fromList []
default_EmitBatch_result :: EmitBatch_result
default_EmitBatch_result :: EmitBatch_result
default_EmitBatch_result = EmitBatch_result :: EmitBatch_result
EmitBatch_result{
}
process_emitZipkinBatch :: (a, p, c, a) -> IO ()
process_emitZipkinBatch (a
seqid, p
iprot, c
oprot, a
handler) = do
  EmitZipkinBatch_args
args <- p -> IO EmitZipkinBatch_args
forall p. Protocol p => p -> IO EmitZipkinBatch_args
read_EmitZipkinBatch_args p
iprot
  (IO () -> (SomeException -> IO ()) -> IO ()
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
X.catch
    (do
      a -> Vector Span -> IO ()
forall a. Agent_Iface a => a -> Vector Span -> IO ()
Iface.emitZipkinBatch a
handler (EmitZipkinBatch_args -> Vector Span
emitZipkinBatch_args_spans EmitZipkinBatch_args
args)
      () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
P.return ())
    ((\SomeException
_ -> do
      () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
P.return ()) :: X.SomeException -> P.IO ()))
process_emitBatch :: (a, p, c, a) -> IO ()
process_emitBatch (a
seqid, p
iprot, c
oprot, a
handler) = do
  EmitBatch_args
args <- p -> IO EmitBatch_args
forall p. Protocol p => p -> IO EmitBatch_args
read_EmitBatch_args p
iprot
  (IO () -> (SomeException -> IO ()) -> IO ()
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
X.catch
    (do
      a -> Batch -> IO ()
forall a. Agent_Iface a => a -> Batch -> IO ()
Iface.emitBatch a
handler (EmitBatch_args -> Batch
emitBatch_args_batch EmitBatch_args
args)
      () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
P.return ())
    ((\SomeException
_ -> do
      () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
P.return ()) :: X.SomeException -> P.IO ()))
proc_ :: a -> (a, p) -> (Text, b, Int32) -> IO ()
proc_ a
handler (a
iprot,p
oprot) (Text
name,b
typ,Int32
seqid) = case Text
name of
  Text
"emitZipkinBatch" -> (Int32, a, p, a) -> IO ()
forall p a a c.
(Protocol p, Agent_Iface a) =>
(a, p, c, a) -> IO ()
process_emitZipkinBatch (Int32
seqid,a
iprot,p
oprot,a
handler)
  Text
"emitBatch" -> (Int32, a, p, a) -> IO ()
forall p a a c.
(Protocol p, Agent_Iface a) =>
(a, p, c, a) -> IO ()
process_emitBatch (Int32
seqid,a
iprot,p
oprot,a
handler)
  Text
_ -> do
    ThriftVal
_ <- a -> ThriftType -> IO ThriftVal
forall a. Protocol a => a -> ThriftType -> IO ThriftVal
T.readVal a
iprot (TypeMap -> ThriftType
T.T_STRUCT TypeMap
forall k v. HashMap k v
Map.empty)
    p -> (Text, MessageType, Int32) -> IO () -> IO ()
forall a.
Protocol a =>
a -> (Text, MessageType, Int32) -> IO () -> IO ()
T.writeMessage p
oprot (Text
name,MessageType
T.M_EXCEPTION,Int32
seqid) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
      p -> AppExn -> IO ()
forall p. Protocol p => p -> AppExn -> IO ()
T.writeAppExn p
oprot (AppExnType -> String -> AppExn
T.AppExn AppExnType
T.AE_UNKNOWN_METHOD (String
"Unknown function " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
LT.unpack Text
name))
process :: a -> (a, p) -> IO Bool
process a
handler (a
iprot, p
oprot) = do
  a -> ((Text, MessageType, Int32) -> IO ()) -> IO ()
forall a b.
Protocol a =>
a -> ((Text, MessageType, Int32) -> IO b) -> IO b
T.readMessage a
iprot (
    a -> (a, p) -> (Text, MessageType, Int32) -> IO ()
forall a a p b.
(Agent_Iface a, Protocol a, Protocol p) =>
a -> (a, p) -> (Text, b, Int32) -> IO ()
proc_ a
handler (a
iprot,p
oprot))
  Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
P.return Bool
P.True