{-# 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 Jaeger_Types 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
data TagType = STRING|DOUBLE|BOOL|LONG|BINARY deriving (Int -> TagType -> ShowS
[TagType] -> ShowS
TagType -> String
(Int -> TagType -> ShowS)
-> (TagType -> String) -> ([TagType] -> ShowS) -> Show TagType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TagType] -> ShowS
$cshowList :: [TagType] -> ShowS
show :: TagType -> String
$cshow :: TagType -> String
showsPrec :: Int -> TagType -> ShowS
$cshowsPrec :: Int -> TagType -> ShowS
P.Show, TagType -> TagType -> Bool
(TagType -> TagType -> Bool)
-> (TagType -> TagType -> Bool) -> Eq TagType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TagType -> TagType -> Bool
$c/= :: TagType -> TagType -> Bool
== :: TagType -> TagType -> Bool
$c== :: TagType -> TagType -> Bool
P.Eq, (forall x. TagType -> Rep TagType x)
-> (forall x. Rep TagType x -> TagType) -> Generic TagType
forall x. Rep TagType x -> TagType
forall x. TagType -> Rep TagType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TagType x -> TagType
$cfrom :: forall x. TagType -> Rep TagType x
G.Generic, TY.Typeable, Eq TagType
Eq TagType
-> (TagType -> TagType -> Ordering)
-> (TagType -> TagType -> Bool)
-> (TagType -> TagType -> Bool)
-> (TagType -> TagType -> Bool)
-> (TagType -> TagType -> Bool)
-> (TagType -> TagType -> TagType)
-> (TagType -> TagType -> TagType)
-> Ord TagType
TagType -> TagType -> Bool
TagType -> TagType -> Ordering
TagType -> TagType -> TagType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TagType -> TagType -> TagType
$cmin :: TagType -> TagType -> TagType
max :: TagType -> TagType -> TagType
$cmax :: TagType -> TagType -> TagType
>= :: TagType -> TagType -> Bool
$c>= :: TagType -> TagType -> Bool
> :: TagType -> TagType -> Bool
$c> :: TagType -> TagType -> Bool
<= :: TagType -> TagType -> Bool
$c<= :: TagType -> TagType -> Bool
< :: TagType -> TagType -> Bool
$c< :: TagType -> TagType -> Bool
compare :: TagType -> TagType -> Ordering
$ccompare :: TagType -> TagType -> Ordering
$cp1Ord :: Eq TagType
P.Ord, TagType
TagType -> TagType -> Bounded TagType
forall a. a -> a -> Bounded a
maxBound :: TagType
$cmaxBound :: TagType
minBound :: TagType
$cminBound :: TagType
P.Bounded)
instance P.Enum TagType where
fromEnum :: TagType -> Int
fromEnum TagType
t = case TagType
t of
TagType
STRING -> Int
0
TagType
DOUBLE -> Int
1
TagType
BOOL -> Int
2
TagType
LONG -> Int
3
TagType
BINARY -> Int
4
toEnum :: Int -> TagType
toEnum Int
t = case Int
t of
Int
0 -> TagType
STRING
Int
1 -> TagType
DOUBLE
Int
2 -> TagType
BOOL
Int
3 -> TagType
LONG
Int
4 -> TagType
BINARY
Int
_ -> ThriftException -> TagType
forall a e. Exception e => e -> a
X.throw ThriftException
T.ThriftException
instance H.Hashable TagType where
hashWithSalt :: Int -> TagType -> Int
hashWithSalt Int
salt = Int -> Int -> Int
forall a. Hashable a => Int -> a -> Int
H.hashWithSalt Int
salt (Int -> Int) -> (TagType -> Int) -> TagType -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
P.. TagType -> Int
forall a. Enum a => a -> Int
P.fromEnum
instance QC.Arbitrary TagType where
arbitrary :: Gen TagType
arbitrary = [TagType] -> Gen TagType
forall a. [a] -> Gen a
QC.elements (TagType -> TagType -> [TagType]
forall a. Enum a => a -> a -> [a]
P.enumFromTo TagType
forall a. Bounded a => a
P.minBound TagType
forall a. Bounded a => a
P.maxBound)
data SpanRefType = CHILD_OF|FOLLOWS_FROM deriving (Int -> SpanRefType -> ShowS
[SpanRefType] -> ShowS
SpanRefType -> String
(Int -> SpanRefType -> ShowS)
-> (SpanRefType -> String)
-> ([SpanRefType] -> ShowS)
-> Show SpanRefType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SpanRefType] -> ShowS
$cshowList :: [SpanRefType] -> ShowS
show :: SpanRefType -> String
$cshow :: SpanRefType -> String
showsPrec :: Int -> SpanRefType -> ShowS
$cshowsPrec :: Int -> SpanRefType -> ShowS
P.Show, SpanRefType -> SpanRefType -> Bool
(SpanRefType -> SpanRefType -> Bool)
-> (SpanRefType -> SpanRefType -> Bool) -> Eq SpanRefType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SpanRefType -> SpanRefType -> Bool
$c/= :: SpanRefType -> SpanRefType -> Bool
== :: SpanRefType -> SpanRefType -> Bool
$c== :: SpanRefType -> SpanRefType -> Bool
P.Eq, (forall x. SpanRefType -> Rep SpanRefType x)
-> (forall x. Rep SpanRefType x -> SpanRefType)
-> Generic SpanRefType
forall x. Rep SpanRefType x -> SpanRefType
forall x. SpanRefType -> Rep SpanRefType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SpanRefType x -> SpanRefType
$cfrom :: forall x. SpanRefType -> Rep SpanRefType x
G.Generic, TY.Typeable, Eq SpanRefType
Eq SpanRefType
-> (SpanRefType -> SpanRefType -> Ordering)
-> (SpanRefType -> SpanRefType -> Bool)
-> (SpanRefType -> SpanRefType -> Bool)
-> (SpanRefType -> SpanRefType -> Bool)
-> (SpanRefType -> SpanRefType -> Bool)
-> (SpanRefType -> SpanRefType -> SpanRefType)
-> (SpanRefType -> SpanRefType -> SpanRefType)
-> Ord SpanRefType
SpanRefType -> SpanRefType -> Bool
SpanRefType -> SpanRefType -> Ordering
SpanRefType -> SpanRefType -> SpanRefType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SpanRefType -> SpanRefType -> SpanRefType
$cmin :: SpanRefType -> SpanRefType -> SpanRefType
max :: SpanRefType -> SpanRefType -> SpanRefType
$cmax :: SpanRefType -> SpanRefType -> SpanRefType
>= :: SpanRefType -> SpanRefType -> Bool
$c>= :: SpanRefType -> SpanRefType -> Bool
> :: SpanRefType -> SpanRefType -> Bool
$c> :: SpanRefType -> SpanRefType -> Bool
<= :: SpanRefType -> SpanRefType -> Bool
$c<= :: SpanRefType -> SpanRefType -> Bool
< :: SpanRefType -> SpanRefType -> Bool
$c< :: SpanRefType -> SpanRefType -> Bool
compare :: SpanRefType -> SpanRefType -> Ordering
$ccompare :: SpanRefType -> SpanRefType -> Ordering
$cp1Ord :: Eq SpanRefType
P.Ord, SpanRefType
SpanRefType -> SpanRefType -> Bounded SpanRefType
forall a. a -> a -> Bounded a
maxBound :: SpanRefType
$cmaxBound :: SpanRefType
minBound :: SpanRefType
$cminBound :: SpanRefType
P.Bounded)
instance P.Enum SpanRefType where
fromEnum :: SpanRefType -> Int
fromEnum SpanRefType
t = case SpanRefType
t of
SpanRefType
CHILD_OF -> Int
0
SpanRefType
FOLLOWS_FROM -> Int
1
toEnum :: Int -> SpanRefType
toEnum Int
t = case Int
t of
Int
0 -> SpanRefType
CHILD_OF
Int
1 -> SpanRefType
FOLLOWS_FROM
Int
_ -> ThriftException -> SpanRefType
forall a e. Exception e => e -> a
X.throw ThriftException
T.ThriftException
instance H.Hashable SpanRefType where
hashWithSalt :: Int -> SpanRefType -> Int
hashWithSalt Int
salt = Int -> Int -> Int
forall a. Hashable a => Int -> a -> Int
H.hashWithSalt Int
salt (Int -> Int) -> (SpanRefType -> Int) -> SpanRefType -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
P.. SpanRefType -> Int
forall a. Enum a => a -> Int
P.fromEnum
instance QC.Arbitrary SpanRefType where
arbitrary :: Gen SpanRefType
arbitrary = [SpanRefType] -> Gen SpanRefType
forall a. [a] -> Gen a
QC.elements (SpanRefType -> SpanRefType -> [SpanRefType]
forall a. Enum a => a -> a -> [a]
P.enumFromTo SpanRefType
forall a. Bounded a => a
P.minBound SpanRefType
forall a. Bounded a => a
P.maxBound)
data Tag = Tag { Tag -> Text
tag_key :: LT.Text
, Tag -> TagType
tag_vType :: TagType
, Tag -> Maybe Text
tag_vStr :: P.Maybe LT.Text
, Tag -> Maybe Double
tag_vDouble :: P.Maybe P.Double
, Tag -> Maybe Bool
tag_vBool :: P.Maybe P.Bool
, Tag -> Maybe Int64
tag_vLong :: P.Maybe I.Int64
, Tag -> Maybe ByteString
tag_vBinary :: P.Maybe LBS.ByteString
} deriving (Int -> Tag -> ShowS
[Tag] -> ShowS
Tag -> String
(Int -> Tag -> ShowS)
-> (Tag -> String) -> ([Tag] -> ShowS) -> Show Tag
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Tag] -> ShowS
$cshowList :: [Tag] -> ShowS
show :: Tag -> String
$cshow :: Tag -> String
showsPrec :: Int -> Tag -> ShowS
$cshowsPrec :: Int -> Tag -> ShowS
P.Show,Tag -> Tag -> Bool
(Tag -> Tag -> Bool) -> (Tag -> Tag -> Bool) -> Eq Tag
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Tag -> Tag -> Bool
$c/= :: Tag -> Tag -> Bool
== :: Tag -> Tag -> Bool
$c== :: Tag -> Tag -> Bool
P.Eq,(forall x. Tag -> Rep Tag x)
-> (forall x. Rep Tag x -> Tag) -> Generic Tag
forall x. Rep Tag x -> Tag
forall x. Tag -> Rep Tag x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Tag x -> Tag
$cfrom :: forall x. Tag -> Rep Tag x
G.Generic,TY.Typeable)
instance H.Hashable Tag where
hashWithSalt :: Int -> Tag -> Int
hashWithSalt Int
salt Tag
record = Int
salt Int -> Text -> Int
forall a. Hashable a => Int -> a -> Int
`H.hashWithSalt` Tag -> Text
tag_key Tag
record Int -> TagType -> Int
forall a. Hashable a => Int -> a -> Int
`H.hashWithSalt` Tag -> TagType
tag_vType Tag
record Int -> Maybe Text -> Int
forall a. Hashable a => Int -> a -> Int
`H.hashWithSalt` Tag -> Maybe Text
tag_vStr Tag
record Int -> Maybe Double -> Int
forall a. Hashable a => Int -> a -> Int
`H.hashWithSalt` Tag -> Maybe Double
tag_vDouble Tag
record Int -> Maybe Bool -> Int
forall a. Hashable a => Int -> a -> Int
`H.hashWithSalt` Tag -> Maybe Bool
tag_vBool Tag
record Int -> Maybe Int64 -> Int
forall a. Hashable a => Int -> a -> Int
`H.hashWithSalt` Tag -> Maybe Int64
tag_vLong Tag
record Int -> Maybe ByteString -> Int
forall a. Hashable a => Int -> a -> Int
`H.hashWithSalt` Tag -> Maybe ByteString
tag_vBinary Tag
record
instance QC.Arbitrary Tag where
arbitrary :: Gen Tag
arbitrary = (Text
-> TagType
-> Maybe Text
-> Maybe Double
-> Maybe Bool
-> Maybe Int64
-> Maybe ByteString
-> Tag)
-> Gen Text
-> Gen
(TagType
-> Maybe Text
-> Maybe Double
-> Maybe Bool
-> Maybe Int64
-> Maybe ByteString
-> Tag)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
M.liftM Text
-> TagType
-> Maybe Text
-> Maybe Double
-> Maybe Bool
-> Maybe Int64
-> Maybe ByteString
-> Tag
Tag (Gen Text
forall a. Arbitrary a => Gen a
QC.arbitrary)
Gen
(TagType
-> Maybe Text
-> Maybe Double
-> Maybe Bool
-> Maybe Int64
-> Maybe ByteString
-> Tag)
-> Gen TagType
-> Gen
(Maybe Text
-> Maybe Double
-> Maybe Bool
-> Maybe Int64
-> Maybe ByteString
-> Tag)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`M.ap`(Gen TagType
forall a. Arbitrary a => Gen a
QC.arbitrary)
Gen
(Maybe Text
-> Maybe Double
-> Maybe Bool
-> Maybe Int64
-> Maybe ByteString
-> Tag)
-> Gen (Maybe Text)
-> Gen
(Maybe Double
-> Maybe Bool -> Maybe Int64 -> Maybe ByteString -> Tag)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`M.ap`((Text -> Maybe Text) -> Gen Text -> Gen (Maybe Text)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
M.liftM Text -> Maybe Text
forall a. a -> Maybe a
P.Just Gen Text
forall a. Arbitrary a => Gen a
QC.arbitrary)
Gen
(Maybe Double
-> Maybe Bool -> Maybe Int64 -> Maybe ByteString -> Tag)
-> Gen (Maybe Double)
-> Gen (Maybe Bool -> Maybe Int64 -> Maybe ByteString -> Tag)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`M.ap`((Double -> Maybe Double) -> Gen Double -> Gen (Maybe Double)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
M.liftM Double -> Maybe Double
forall a. a -> Maybe a
P.Just Gen Double
forall a. Arbitrary a => Gen a
QC.arbitrary)
Gen (Maybe Bool -> Maybe Int64 -> Maybe ByteString -> Tag)
-> Gen (Maybe Bool) -> Gen (Maybe Int64 -> Maybe ByteString -> Tag)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`M.ap`((Bool -> Maybe Bool) -> Gen Bool -> Gen (Maybe Bool)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
M.liftM Bool -> Maybe Bool
forall a. a -> Maybe a
P.Just Gen Bool
forall a. Arbitrary a => Gen a
QC.arbitrary)
Gen (Maybe Int64 -> Maybe ByteString -> Tag)
-> Gen (Maybe Int64) -> Gen (Maybe ByteString -> Tag)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`M.ap`((Int64 -> Maybe Int64) -> Gen Int64 -> Gen (Maybe Int64)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
M.liftM Int64 -> Maybe Int64
forall a. a -> Maybe a
P.Just Gen Int64
forall a. Arbitrary a => Gen a
QC.arbitrary)
Gen (Maybe ByteString -> Tag) -> Gen (Maybe ByteString) -> Gen Tag
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`M.ap`((ByteString -> Maybe ByteString)
-> Gen ByteString -> Gen (Maybe ByteString)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
M.liftM ByteString -> Maybe ByteString
forall a. a -> Maybe a
P.Just Gen ByteString
forall a. Arbitrary a => Gen a
QC.arbitrary)
shrink :: Tag -> [Tag]
shrink Tag
obj | Tag
obj Tag -> Tag -> Bool
forall a. Eq a => a -> a -> Bool
== Tag
default_Tag = []
| Bool
P.otherwise = [Maybe Tag] -> [Tag]
forall a. [Maybe a] -> [a]
M.catMaybes
[ if Tag
obj Tag -> Tag -> Bool
forall a. Eq a => a -> a -> Bool
== Tag
default_Tag{tag_key :: Text
tag_key = Tag -> Text
tag_key Tag
obj} then Maybe Tag
forall a. Maybe a
P.Nothing else Tag -> Maybe Tag
forall a. a -> Maybe a
P.Just (Tag -> Maybe Tag) -> Tag -> Maybe Tag
forall a b. (a -> b) -> a -> b
$ Tag
default_Tag{tag_key :: Text
tag_key = Tag -> Text
tag_key Tag
obj}
, if Tag
obj Tag -> Tag -> Bool
forall a. Eq a => a -> a -> Bool
== Tag
default_Tag{tag_vType :: TagType
tag_vType = Tag -> TagType
tag_vType Tag
obj} then Maybe Tag
forall a. Maybe a
P.Nothing else Tag -> Maybe Tag
forall a. a -> Maybe a
P.Just (Tag -> Maybe Tag) -> Tag -> Maybe Tag
forall a b. (a -> b) -> a -> b
$ Tag
default_Tag{tag_vType :: TagType
tag_vType = Tag -> TagType
tag_vType Tag
obj}
, if Tag
obj Tag -> Tag -> Bool
forall a. Eq a => a -> a -> Bool
== Tag
default_Tag{tag_vStr :: Maybe Text
tag_vStr = Tag -> Maybe Text
tag_vStr Tag
obj} then Maybe Tag
forall a. Maybe a
P.Nothing else Tag -> Maybe Tag
forall a. a -> Maybe a
P.Just (Tag -> Maybe Tag) -> Tag -> Maybe Tag
forall a b. (a -> b) -> a -> b
$ Tag
default_Tag{tag_vStr :: Maybe Text
tag_vStr = Tag -> Maybe Text
tag_vStr Tag
obj}
, if Tag
obj Tag -> Tag -> Bool
forall a. Eq a => a -> a -> Bool
== Tag
default_Tag{tag_vDouble :: Maybe Double
tag_vDouble = Tag -> Maybe Double
tag_vDouble Tag
obj} then Maybe Tag
forall a. Maybe a
P.Nothing else Tag -> Maybe Tag
forall a. a -> Maybe a
P.Just (Tag -> Maybe Tag) -> Tag -> Maybe Tag
forall a b. (a -> b) -> a -> b
$ Tag
default_Tag{tag_vDouble :: Maybe Double
tag_vDouble = Tag -> Maybe Double
tag_vDouble Tag
obj}
, if Tag
obj Tag -> Tag -> Bool
forall a. Eq a => a -> a -> Bool
== Tag
default_Tag{tag_vBool :: Maybe Bool
tag_vBool = Tag -> Maybe Bool
tag_vBool Tag
obj} then Maybe Tag
forall a. Maybe a
P.Nothing else Tag -> Maybe Tag
forall a. a -> Maybe a
P.Just (Tag -> Maybe Tag) -> Tag -> Maybe Tag
forall a b. (a -> b) -> a -> b
$ Tag
default_Tag{tag_vBool :: Maybe Bool
tag_vBool = Tag -> Maybe Bool
tag_vBool Tag
obj}
, if Tag
obj Tag -> Tag -> Bool
forall a. Eq a => a -> a -> Bool
== Tag
default_Tag{tag_vLong :: Maybe Int64
tag_vLong = Tag -> Maybe Int64
tag_vLong Tag
obj} then Maybe Tag
forall a. Maybe a
P.Nothing else Tag -> Maybe Tag
forall a. a -> Maybe a
P.Just (Tag -> Maybe Tag) -> Tag -> Maybe Tag
forall a b. (a -> b) -> a -> b
$ Tag
default_Tag{tag_vLong :: Maybe Int64
tag_vLong = Tag -> Maybe Int64
tag_vLong Tag
obj}
, if Tag
obj Tag -> Tag -> Bool
forall a. Eq a => a -> a -> Bool
== Tag
default_Tag{tag_vBinary :: Maybe ByteString
tag_vBinary = Tag -> Maybe ByteString
tag_vBinary Tag
obj} then Maybe Tag
forall a. Maybe a
P.Nothing else Tag -> Maybe Tag
forall a. a -> Maybe a
P.Just (Tag -> Maybe Tag) -> Tag -> Maybe Tag
forall a b. (a -> b) -> a -> b
$ Tag
default_Tag{tag_vBinary :: Maybe ByteString
tag_vBinary = Tag -> Maybe ByteString
tag_vBinary Tag
obj}
]
from_Tag :: Tag -> T.ThriftVal
from_Tag :: Tag -> ThriftVal
from_Tag Tag
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
[ (\Text
_v2 -> (Int16, (Text, ThriftVal)) -> Maybe (Int16, (Text, ThriftVal))
forall a. a -> Maybe a
P.Just (Int16
1, (Text
"key",ByteString -> ThriftVal
T.TString (ByteString -> ThriftVal) -> ByteString -> ThriftVal
forall a b. (a -> b) -> a -> b
$ Text -> ByteString
E.encodeUtf8 Text
_v2))) (Text -> Maybe (Int16, (Text, ThriftVal)))
-> Text -> Maybe (Int16, (Text, ThriftVal))
forall a b. (a -> b) -> a -> b
$ Tag -> Text
tag_key Tag
record
, (\TagType
_v2 -> (Int16, (Text, ThriftVal)) -> Maybe (Int16, (Text, ThriftVal))
forall a. a -> Maybe a
P.Just (Int16
2, (Text
"vType",Int32 -> ThriftVal
T.TI32 (Int32 -> ThriftVal) -> Int32 -> ThriftVal
forall a b. (a -> b) -> a -> b
$ Int -> Int32
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> Int32) -> Int -> Int32
forall a b. (a -> b) -> a -> b
$ TagType -> Int
forall a. Enum a => a -> Int
P.fromEnum TagType
_v2))) (TagType -> Maybe (Int16, (Text, ThriftVal)))
-> TagType -> Maybe (Int16, (Text, ThriftVal))
forall a b. (a -> b) -> a -> b
$ Tag -> TagType
tag_vType Tag
record
, (\Text
_v2 -> (Int16
3, (Text
"vStr",ByteString -> ThriftVal
T.TString (ByteString -> ThriftVal) -> ByteString -> ThriftVal
forall a b. (a -> b) -> a -> b
$ Text -> ByteString
E.encodeUtf8 Text
_v2))) (Text -> (Int16, (Text, ThriftVal)))
-> Maybe Text -> Maybe (Int16, (Text, ThriftVal))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Tag -> Maybe Text
tag_vStr Tag
record
, (\Double
_v2 -> (Int16
4, (Text
"vDouble",Double -> ThriftVal
T.TDouble Double
_v2))) (Double -> (Int16, (Text, ThriftVal)))
-> Maybe Double -> Maybe (Int16, (Text, ThriftVal))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Tag -> Maybe Double
tag_vDouble Tag
record
, (\Bool
_v2 -> (Int16
5, (Text
"vBool",Bool -> ThriftVal
T.TBool Bool
_v2))) (Bool -> (Int16, (Text, ThriftVal)))
-> Maybe Bool -> Maybe (Int16, (Text, ThriftVal))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Tag -> Maybe Bool
tag_vBool Tag
record
, (\Int64
_v2 -> (Int16
6, (Text
"vLong",Int64 -> ThriftVal
T.TI64 Int64
_v2))) (Int64 -> (Int16, (Text, ThriftVal)))
-> Maybe Int64 -> Maybe (Int16, (Text, ThriftVal))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Tag -> Maybe Int64
tag_vLong Tag
record
, (\ByteString
_v2 -> (Int16
7, (Text
"vBinary",ByteString -> ThriftVal
T.TBinary ByteString
_v2))) (ByteString -> (Int16, (Text, ThriftVal)))
-> Maybe ByteString -> Maybe (Int16, (Text, ThriftVal))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Tag -> Maybe ByteString
tag_vBinary Tag
record
]
write_Tag :: T.Protocol p => p -> Tag -> P.IO ()
write_Tag :: p -> Tag -> IO ()
write_Tag p
oprot Tag
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
$ Tag -> ThriftVal
from_Tag Tag
record
encode_Tag :: T.StatelessProtocol p => p -> Tag -> LBS.ByteString
encode_Tag :: p -> Tag -> ByteString
encode_Tag p
oprot Tag
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
$ Tag -> ThriftVal
from_Tag Tag
record
to_Tag :: T.ThriftVal -> Tag
to_Tag :: ThriftVal -> Tag
to_Tag (T.TStruct HashMap Int16 (Text, ThriftVal)
fields) = Tag :: Text
-> TagType
-> Maybe Text
-> Maybe Double
-> Maybe Bool
-> Maybe Int64
-> Maybe ByteString
-> Tag
Tag{
tag_key :: Text
tag_key = Text
-> ((Text, ThriftVal) -> Text) -> Maybe (Text, ThriftVal) -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (String -> Text
forall a. HasCallStack => String -> a
P.error String
"Missing required field: key") (\(Text
_,ThriftVal
_val4) -> (case ThriftVal
_val4 of {T.TString ByteString
_val5 -> ByteString -> Text
E.decodeUtf8 ByteString
_val5; ThriftVal
_ -> String -> Text
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),
tag_vType :: TagType
tag_vType = TagType
-> ((Text, ThriftVal) -> TagType)
-> Maybe (Text, ThriftVal)
-> TagType
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (String -> TagType
forall a. HasCallStack => String -> a
P.error String
"Missing required field: vType") (\(Text
_,ThriftVal
_val4) -> (case ThriftVal
_val4 of {T.TI32 Int32
_val6 -> Int -> TagType
forall a. Enum a => Int -> a
P.toEnum (Int -> TagType) -> Int -> TagType
forall a b. (a -> b) -> a -> b
$ Int32 -> Int
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral Int32
_val6; ThriftVal
_ -> String -> TagType
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
2) HashMap Int16 (Text, ThriftVal)
fields),
tag_vStr :: Maybe Text
tag_vStr = Maybe Text
-> ((Text, ThriftVal) -> Maybe Text)
-> Maybe (Text, ThriftVal)
-> Maybe Text
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (Maybe Text
forall a. Maybe a
P.Nothing) (\(Text
_,ThriftVal
_val4) -> Text -> Maybe Text
forall a. a -> Maybe a
P.Just (case ThriftVal
_val4 of {T.TString ByteString
_val7 -> ByteString -> Text
E.decodeUtf8 ByteString
_val7; ThriftVal
_ -> String -> Text
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
3) HashMap Int16 (Text, ThriftVal)
fields),
tag_vDouble :: Maybe Double
tag_vDouble = Maybe Double
-> ((Text, ThriftVal) -> Maybe Double)
-> Maybe (Text, ThriftVal)
-> Maybe Double
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (Maybe Double
forall a. Maybe a
P.Nothing) (\(Text
_,ThriftVal
_val4) -> Double -> Maybe Double
forall a. a -> Maybe a
P.Just (case ThriftVal
_val4 of {T.TDouble Double
_val8 -> Double
_val8; ThriftVal
_ -> String -> Double
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
4) HashMap Int16 (Text, ThriftVal)
fields),
tag_vBool :: Maybe Bool
tag_vBool = Maybe Bool
-> ((Text, ThriftVal) -> Maybe Bool)
-> Maybe (Text, ThriftVal)
-> Maybe Bool
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (Maybe Bool
forall a. Maybe a
P.Nothing) (\(Text
_,ThriftVal
_val4) -> Bool -> Maybe Bool
forall a. a -> Maybe a
P.Just (case ThriftVal
_val4 of {T.TBool Bool
_val9 -> Bool
_val9; ThriftVal
_ -> String -> Bool
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
5) HashMap Int16 (Text, ThriftVal)
fields),
tag_vLong :: Maybe Int64
tag_vLong = Maybe Int64
-> ((Text, ThriftVal) -> Maybe Int64)
-> Maybe (Text, ThriftVal)
-> Maybe Int64
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (Maybe Int64
forall a. Maybe a
P.Nothing) (\(Text
_,ThriftVal
_val4) -> Int64 -> Maybe Int64
forall a. a -> Maybe a
P.Just (case ThriftVal
_val4 of {T.TI64 Int64
_val10 -> Int64
_val10; ThriftVal
_ -> String -> Int64
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
6) HashMap Int16 (Text, ThriftVal)
fields),
tag_vBinary :: Maybe ByteString
tag_vBinary = Maybe ByteString
-> ((Text, ThriftVal) -> Maybe ByteString)
-> Maybe (Text, ThriftVal)
-> Maybe ByteString
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (Maybe ByteString
forall a. Maybe a
P.Nothing) (\(Text
_,ThriftVal
_val4) -> ByteString -> Maybe ByteString
forall a. a -> Maybe a
P.Just (case ThriftVal
_val4 of {T.TBinary ByteString
_val11 -> ByteString
_val11; T.TString ByteString
_val11 -> ByteString
_val11; ThriftVal
_ -> String -> ByteString
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
7) HashMap Int16 (Text, ThriftVal)
fields)
}
to_Tag ThriftVal
_ = String -> Tag
forall a. HasCallStack => String -> a
P.error String
"not a struct"
read_Tag :: T.Protocol p => p -> P.IO Tag
read_Tag :: p -> IO Tag
read_Tag p
iprot = ThriftVal -> Tag
to_Tag (ThriftVal -> Tag) -> IO ThriftVal -> IO Tag
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_Tag)
decode_Tag :: T.StatelessProtocol p => p -> LBS.ByteString -> Tag
decode_Tag :: p -> ByteString -> Tag
decode_Tag p
iprot ByteString
bs = ThriftVal -> Tag
to_Tag (ThriftVal -> Tag) -> ThriftVal -> Tag
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_Tag) ByteString
bs
typemap_Tag :: T.TypeMap
typemap_Tag :: TypeMap
typemap_Tag = [(Int16, (Text, ThriftType))] -> TypeMap
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
Map.fromList [(Int16
1,(Text
"key",ThriftType
T.T_STRING)),(Int16
2,(Text
"vType",ThriftType
T.T_I32)),(Int16
3,(Text
"vStr",ThriftType
T.T_STRING)),(Int16
4,(Text
"vDouble",ThriftType
T.T_DOUBLE)),(Int16
5,(Text
"vBool",ThriftType
T.T_BOOL)),(Int16
6,(Text
"vLong",ThriftType
T.T_I64)),(Int16
7,(Text
"vBinary",ThriftType
T.T_BINARY))]
default_Tag :: Tag
default_Tag :: Tag
default_Tag = Tag :: Text
-> TagType
-> Maybe Text
-> Maybe Double
-> Maybe Bool
-> Maybe Int64
-> Maybe ByteString
-> Tag
Tag{
tag_key :: Text
tag_key = Text
"",
tag_vType :: TagType
tag_vType = (Int -> TagType
forall a. Enum a => Int -> a
P.toEnum Int
0),
tag_vStr :: Maybe Text
tag_vStr = Maybe Text
forall a. Maybe a
P.Nothing,
tag_vDouble :: Maybe Double
tag_vDouble = Maybe Double
forall a. Maybe a
P.Nothing,
tag_vBool :: Maybe Bool
tag_vBool = Maybe Bool
forall a. Maybe a
P.Nothing,
tag_vLong :: Maybe Int64
tag_vLong = Maybe Int64
forall a. Maybe a
P.Nothing,
tag_vBinary :: Maybe ByteString
tag_vBinary = Maybe ByteString
forall a. Maybe a
P.Nothing}
data Log = Log { Log -> Int64
log_timestamp :: I.Int64
, Log -> Vector Tag
log_fields :: (Vector.Vector Tag)
} deriving (Int -> Log -> ShowS
[Log] -> ShowS
Log -> String
(Int -> Log -> ShowS)
-> (Log -> String) -> ([Log] -> ShowS) -> Show Log
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Log] -> ShowS
$cshowList :: [Log] -> ShowS
show :: Log -> String
$cshow :: Log -> String
showsPrec :: Int -> Log -> ShowS
$cshowsPrec :: Int -> Log -> ShowS
P.Show,Log -> Log -> Bool
(Log -> Log -> Bool) -> (Log -> Log -> Bool) -> Eq Log
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Log -> Log -> Bool
$c/= :: Log -> Log -> Bool
== :: Log -> Log -> Bool
$c== :: Log -> Log -> Bool
P.Eq,(forall x. Log -> Rep Log x)
-> (forall x. Rep Log x -> Log) -> Generic Log
forall x. Rep Log x -> Log
forall x. Log -> Rep Log x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Log x -> Log
$cfrom :: forall x. Log -> Rep Log x
G.Generic,TY.Typeable)
instance H.Hashable Log where
hashWithSalt :: Int -> Log -> Int
hashWithSalt Int
salt Log
record = Int
salt Int -> Int64 -> Int
forall a. Hashable a => Int -> a -> Int
`H.hashWithSalt` Log -> Int64
log_timestamp Log
record Int -> Vector Tag -> Int
forall a. Hashable a => Int -> a -> Int
`H.hashWithSalt` Log -> Vector Tag
log_fields Log
record
instance QC.Arbitrary Log where
arbitrary :: Gen Log
arbitrary = (Int64 -> Vector Tag -> Log)
-> Gen Int64 -> Gen (Vector Tag -> Log)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
M.liftM Int64 -> Vector Tag -> Log
Log (Gen Int64
forall a. Arbitrary a => Gen a
QC.arbitrary)
Gen (Vector Tag -> Log) -> Gen (Vector Tag) -> Gen Log
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`M.ap`(Gen (Vector Tag)
forall a. Arbitrary a => Gen a
QC.arbitrary)
shrink :: Log -> [Log]
shrink Log
obj | Log
obj Log -> Log -> Bool
forall a. Eq a => a -> a -> Bool
== Log
default_Log = []
| Bool
P.otherwise = [Maybe Log] -> [Log]
forall a. [Maybe a] -> [a]
M.catMaybes
[ if Log
obj Log -> Log -> Bool
forall a. Eq a => a -> a -> Bool
== Log
default_Log{log_timestamp :: Int64
log_timestamp = Log -> Int64
log_timestamp Log
obj} then Maybe Log
forall a. Maybe a
P.Nothing else Log -> Maybe Log
forall a. a -> Maybe a
P.Just (Log -> Maybe Log) -> Log -> Maybe Log
forall a b. (a -> b) -> a -> b
$ Log
default_Log{log_timestamp :: Int64
log_timestamp = Log -> Int64
log_timestamp Log
obj}
, if Log
obj Log -> Log -> Bool
forall a. Eq a => a -> a -> Bool
== Log
default_Log{log_fields :: Vector Tag
log_fields = Log -> Vector Tag
log_fields Log
obj} then Maybe Log
forall a. Maybe a
P.Nothing else Log -> Maybe Log
forall a. a -> Maybe a
P.Just (Log -> Maybe Log) -> Log -> Maybe Log
forall a b. (a -> b) -> a -> b
$ Log
default_Log{log_fields :: Vector Tag
log_fields = Log -> Vector Tag
log_fields Log
obj}
]
from_Log :: Log -> T.ThriftVal
from_Log :: Log -> ThriftVal
from_Log Log
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
[ (\Int64
_v14 -> (Int16, (Text, ThriftVal)) -> Maybe (Int16, (Text, ThriftVal))
forall a. a -> Maybe a
P.Just (Int16
1, (Text
"timestamp",Int64 -> ThriftVal
T.TI64 Int64
_v14))) (Int64 -> Maybe (Int16, (Text, ThriftVal)))
-> Int64 -> Maybe (Int16, (Text, ThriftVal))
forall a b. (a -> b) -> a -> b
$ Log -> Int64
log_timestamp Log
record
, (\Vector Tag
_v14 -> (Int16, (Text, ThriftVal)) -> Maybe (Int16, (Text, ThriftVal))
forall a. a -> Maybe a
P.Just (Int16
2, (Text
"fields",ThriftType -> [ThriftVal] -> ThriftVal
T.TList (TypeMap -> ThriftType
T.T_STRUCT TypeMap
typemap_Tag) ([ThriftVal] -> ThriftVal) -> [ThriftVal] -> ThriftVal
forall a b. (a -> b) -> a -> b
$ (Tag -> ThriftVal) -> [Tag] -> [ThriftVal]
forall a b. (a -> b) -> [a] -> [b]
P.map (\Tag
_v16 -> Tag -> ThriftVal
from_Tag Tag
_v16) ([Tag] -> [ThriftVal]) -> [Tag] -> [ThriftVal]
forall a b. (a -> b) -> a -> b
$ Vector Tag -> [Tag]
forall a. Vector a -> [a]
Vector.toList Vector Tag
_v14))) (Vector Tag -> Maybe (Int16, (Text, ThriftVal)))
-> Vector Tag -> Maybe (Int16, (Text, ThriftVal))
forall a b. (a -> b) -> a -> b
$ Log -> Vector Tag
log_fields Log
record
]
write_Log :: T.Protocol p => p -> Log -> P.IO ()
write_Log :: p -> Log -> IO ()
write_Log p
oprot Log
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
$ Log -> ThriftVal
from_Log Log
record
encode_Log :: T.StatelessProtocol p => p -> Log -> LBS.ByteString
encode_Log :: p -> Log -> ByteString
encode_Log p
oprot Log
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
$ Log -> ThriftVal
from_Log Log
record
to_Log :: T.ThriftVal -> Log
to_Log :: ThriftVal -> Log
to_Log (T.TStruct HashMap Int16 (Text, ThriftVal)
fields) = Log :: Int64 -> Vector Tag -> Log
Log{
log_timestamp :: Int64
log_timestamp = Int64
-> ((Text, ThriftVal) -> Int64) -> Maybe (Text, ThriftVal) -> Int64
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (String -> Int64
forall a. HasCallStack => String -> a
P.error String
"Missing required field: timestamp") (\(Text
_,ThriftVal
_val18) -> (case ThriftVal
_val18 of {T.TI64 Int64
_val19 -> Int64
_val19; ThriftVal
_ -> String -> Int64
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),
log_fields :: Vector Tag
log_fields = Vector Tag
-> ((Text, ThriftVal) -> Vector Tag)
-> Maybe (Text, ThriftVal)
-> Vector Tag
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (String -> Vector Tag
forall a. HasCallStack => String -> a
P.error String
"Missing required field: fields") (\(Text
_,ThriftVal
_val18) -> (case ThriftVal
_val18 of {T.TList ThriftType
_ [ThriftVal]
_val20 -> ([Tag] -> Vector Tag
forall a. [a] -> Vector a
Vector.fromList ([Tag] -> Vector Tag) -> [Tag] -> Vector Tag
forall a b. (a -> b) -> a -> b
$ (ThriftVal -> Tag) -> [ThriftVal] -> [Tag]
forall a b. (a -> b) -> [a] -> [b]
P.map (\ThriftVal
_v21 -> (case ThriftVal
_v21 of {T.TStruct HashMap Int16 (Text, ThriftVal)
_val22 -> (ThriftVal -> Tag
to_Tag (HashMap Int16 (Text, ThriftVal) -> ThriftVal
T.TStruct HashMap Int16 (Text, ThriftVal)
_val22)); ThriftVal
_ -> String -> Tag
forall a. HasCallStack => String -> a
P.error String
"wrong type"})) [ThriftVal]
_val20); ThriftVal
_ -> String -> Vector Tag
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
2) HashMap Int16 (Text, ThriftVal)
fields)
}
to_Log ThriftVal
_ = String -> Log
forall a. HasCallStack => String -> a
P.error String
"not a struct"
read_Log :: T.Protocol p => p -> P.IO Log
read_Log :: p -> IO Log
read_Log p
iprot = ThriftVal -> Log
to_Log (ThriftVal -> Log) -> IO ThriftVal -> IO Log
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_Log)
decode_Log :: T.StatelessProtocol p => p -> LBS.ByteString -> Log
decode_Log :: p -> ByteString -> Log
decode_Log p
iprot ByteString
bs = ThriftVal -> Log
to_Log (ThriftVal -> Log) -> ThriftVal -> Log
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_Log) ByteString
bs
typemap_Log :: T.TypeMap
typemap_Log :: TypeMap
typemap_Log = [(Int16, (Text, ThriftType))] -> TypeMap
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
Map.fromList [(Int16
1,(Text
"timestamp",ThriftType
T.T_I64)),(Int16
2,(Text
"fields",(ThriftType -> ThriftType
T.T_LIST (TypeMap -> ThriftType
T.T_STRUCT TypeMap
typemap_Tag))))]
default_Log :: Log
default_Log :: Log
default_Log = Log :: Int64 -> Vector Tag -> Log
Log{
log_timestamp :: Int64
log_timestamp = Int64
0,
log_fields :: Vector Tag
log_fields = Vector Tag
forall a. Vector a
Vector.empty}
data SpanRef = SpanRef { SpanRef -> SpanRefType
spanRef_refType :: SpanRefType
, SpanRef -> Int64
spanRef_traceIdLow :: I.Int64
, SpanRef -> Int64
spanRef_traceIdHigh :: I.Int64
, SpanRef -> Int64
spanRef_spanId :: I.Int64
} deriving (Int -> SpanRef -> ShowS
[SpanRef] -> ShowS
SpanRef -> String
(Int -> SpanRef -> ShowS)
-> (SpanRef -> String) -> ([SpanRef] -> ShowS) -> Show SpanRef
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SpanRef] -> ShowS
$cshowList :: [SpanRef] -> ShowS
show :: SpanRef -> String
$cshow :: SpanRef -> String
showsPrec :: Int -> SpanRef -> ShowS
$cshowsPrec :: Int -> SpanRef -> ShowS
P.Show,SpanRef -> SpanRef -> Bool
(SpanRef -> SpanRef -> Bool)
-> (SpanRef -> SpanRef -> Bool) -> Eq SpanRef
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SpanRef -> SpanRef -> Bool
$c/= :: SpanRef -> SpanRef -> Bool
== :: SpanRef -> SpanRef -> Bool
$c== :: SpanRef -> SpanRef -> Bool
P.Eq,(forall x. SpanRef -> Rep SpanRef x)
-> (forall x. Rep SpanRef x -> SpanRef) -> Generic SpanRef
forall x. Rep SpanRef x -> SpanRef
forall x. SpanRef -> Rep SpanRef x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SpanRef x -> SpanRef
$cfrom :: forall x. SpanRef -> Rep SpanRef x
G.Generic,TY.Typeable)
instance H.Hashable SpanRef where
hashWithSalt :: Int -> SpanRef -> Int
hashWithSalt Int
salt SpanRef
record = Int
salt Int -> SpanRefType -> Int
forall a. Hashable a => Int -> a -> Int
`H.hashWithSalt` SpanRef -> SpanRefType
spanRef_refType SpanRef
record Int -> Int64 -> Int
forall a. Hashable a => Int -> a -> Int
`H.hashWithSalt` SpanRef -> Int64
spanRef_traceIdLow SpanRef
record Int -> Int64 -> Int
forall a. Hashable a => Int -> a -> Int
`H.hashWithSalt` SpanRef -> Int64
spanRef_traceIdHigh SpanRef
record Int -> Int64 -> Int
forall a. Hashable a => Int -> a -> Int
`H.hashWithSalt` SpanRef -> Int64
spanRef_spanId SpanRef
record
instance QC.Arbitrary SpanRef where
arbitrary :: Gen SpanRef
arbitrary = (SpanRefType -> Int64 -> Int64 -> Int64 -> SpanRef)
-> Gen SpanRefType -> Gen (Int64 -> Int64 -> Int64 -> SpanRef)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
M.liftM SpanRefType -> Int64 -> Int64 -> Int64 -> SpanRef
SpanRef (Gen SpanRefType
forall a. Arbitrary a => Gen a
QC.arbitrary)
Gen (Int64 -> Int64 -> Int64 -> SpanRef)
-> Gen Int64 -> Gen (Int64 -> Int64 -> SpanRef)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`M.ap`(Gen Int64
forall a. Arbitrary a => Gen a
QC.arbitrary)
Gen (Int64 -> Int64 -> SpanRef)
-> Gen Int64 -> Gen (Int64 -> SpanRef)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`M.ap`(Gen Int64
forall a. Arbitrary a => Gen a
QC.arbitrary)
Gen (Int64 -> SpanRef) -> Gen Int64 -> Gen SpanRef
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`M.ap`(Gen Int64
forall a. Arbitrary a => Gen a
QC.arbitrary)
shrink :: SpanRef -> [SpanRef]
shrink SpanRef
obj | SpanRef
obj SpanRef -> SpanRef -> Bool
forall a. Eq a => a -> a -> Bool
== SpanRef
default_SpanRef = []
| Bool
P.otherwise = [Maybe SpanRef] -> [SpanRef]
forall a. [Maybe a] -> [a]
M.catMaybes
[ if SpanRef
obj SpanRef -> SpanRef -> Bool
forall a. Eq a => a -> a -> Bool
== SpanRef
default_SpanRef{spanRef_refType :: SpanRefType
spanRef_refType = SpanRef -> SpanRefType
spanRef_refType SpanRef
obj} then Maybe SpanRef
forall a. Maybe a
P.Nothing else SpanRef -> Maybe SpanRef
forall a. a -> Maybe a
P.Just (SpanRef -> Maybe SpanRef) -> SpanRef -> Maybe SpanRef
forall a b. (a -> b) -> a -> b
$ SpanRef
default_SpanRef{spanRef_refType :: SpanRefType
spanRef_refType = SpanRef -> SpanRefType
spanRef_refType SpanRef
obj}
, if SpanRef
obj SpanRef -> SpanRef -> Bool
forall a. Eq a => a -> a -> Bool
== SpanRef
default_SpanRef{spanRef_traceIdLow :: Int64
spanRef_traceIdLow = SpanRef -> Int64
spanRef_traceIdLow SpanRef
obj} then Maybe SpanRef
forall a. Maybe a
P.Nothing else SpanRef -> Maybe SpanRef
forall a. a -> Maybe a
P.Just (SpanRef -> Maybe SpanRef) -> SpanRef -> Maybe SpanRef
forall a b. (a -> b) -> a -> b
$ SpanRef
default_SpanRef{spanRef_traceIdLow :: Int64
spanRef_traceIdLow = SpanRef -> Int64
spanRef_traceIdLow SpanRef
obj}
, if SpanRef
obj SpanRef -> SpanRef -> Bool
forall a. Eq a => a -> a -> Bool
== SpanRef
default_SpanRef{spanRef_traceIdHigh :: Int64
spanRef_traceIdHigh = SpanRef -> Int64
spanRef_traceIdHigh SpanRef
obj} then Maybe SpanRef
forall a. Maybe a
P.Nothing else SpanRef -> Maybe SpanRef
forall a. a -> Maybe a
P.Just (SpanRef -> Maybe SpanRef) -> SpanRef -> Maybe SpanRef
forall a b. (a -> b) -> a -> b
$ SpanRef
default_SpanRef{spanRef_traceIdHigh :: Int64
spanRef_traceIdHigh = SpanRef -> Int64
spanRef_traceIdHigh SpanRef
obj}
, if SpanRef
obj SpanRef -> SpanRef -> Bool
forall a. Eq a => a -> a -> Bool
== SpanRef
default_SpanRef{spanRef_spanId :: Int64
spanRef_spanId = SpanRef -> Int64
spanRef_spanId SpanRef
obj} then Maybe SpanRef
forall a. Maybe a
P.Nothing else SpanRef -> Maybe SpanRef
forall a. a -> Maybe a
P.Just (SpanRef -> Maybe SpanRef) -> SpanRef -> Maybe SpanRef
forall a b. (a -> b) -> a -> b
$ SpanRef
default_SpanRef{spanRef_spanId :: Int64
spanRef_spanId = SpanRef -> Int64
spanRef_spanId SpanRef
obj}
]
from_SpanRef :: SpanRef -> T.ThriftVal
from_SpanRef :: SpanRef -> ThriftVal
from_SpanRef SpanRef
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
[ (\SpanRefType
_v25 -> (Int16, (Text, ThriftVal)) -> Maybe (Int16, (Text, ThriftVal))
forall a. a -> Maybe a
P.Just (Int16
1, (Text
"refType",Int32 -> ThriftVal
T.TI32 (Int32 -> ThriftVal) -> Int32 -> ThriftVal
forall a b. (a -> b) -> a -> b
$ Int -> Int32
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> Int32) -> Int -> Int32
forall a b. (a -> b) -> a -> b
$ SpanRefType -> Int
forall a. Enum a => a -> Int
P.fromEnum SpanRefType
_v25))) (SpanRefType -> Maybe (Int16, (Text, ThriftVal)))
-> SpanRefType -> Maybe (Int16, (Text, ThriftVal))
forall a b. (a -> b) -> a -> b
$ SpanRef -> SpanRefType
spanRef_refType SpanRef
record
, (\Int64
_v25 -> (Int16, (Text, ThriftVal)) -> Maybe (Int16, (Text, ThriftVal))
forall a. a -> Maybe a
P.Just (Int16
2, (Text
"traceIdLow",Int64 -> ThriftVal
T.TI64 Int64
_v25))) (Int64 -> Maybe (Int16, (Text, ThriftVal)))
-> Int64 -> Maybe (Int16, (Text, ThriftVal))
forall a b. (a -> b) -> a -> b
$ SpanRef -> Int64
spanRef_traceIdLow SpanRef
record
, (\Int64
_v25 -> (Int16, (Text, ThriftVal)) -> Maybe (Int16, (Text, ThriftVal))
forall a. a -> Maybe a
P.Just (Int16
3, (Text
"traceIdHigh",Int64 -> ThriftVal
T.TI64 Int64
_v25))) (Int64 -> Maybe (Int16, (Text, ThriftVal)))
-> Int64 -> Maybe (Int16, (Text, ThriftVal))
forall a b. (a -> b) -> a -> b
$ SpanRef -> Int64
spanRef_traceIdHigh SpanRef
record
, (\Int64
_v25 -> (Int16, (Text, ThriftVal)) -> Maybe (Int16, (Text, ThriftVal))
forall a. a -> Maybe a
P.Just (Int16
4, (Text
"spanId",Int64 -> ThriftVal
T.TI64 Int64
_v25))) (Int64 -> Maybe (Int16, (Text, ThriftVal)))
-> Int64 -> Maybe (Int16, (Text, ThriftVal))
forall a b. (a -> b) -> a -> b
$ SpanRef -> Int64
spanRef_spanId SpanRef
record
]
write_SpanRef :: T.Protocol p => p -> SpanRef -> P.IO ()
write_SpanRef :: p -> SpanRef -> IO ()
write_SpanRef p
oprot SpanRef
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
$ SpanRef -> ThriftVal
from_SpanRef SpanRef
record
encode_SpanRef :: T.StatelessProtocol p => p -> SpanRef -> LBS.ByteString
encode_SpanRef :: p -> SpanRef -> ByteString
encode_SpanRef p
oprot SpanRef
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
$ SpanRef -> ThriftVal
from_SpanRef SpanRef
record
to_SpanRef :: T.ThriftVal -> SpanRef
to_SpanRef :: ThriftVal -> SpanRef
to_SpanRef (T.TStruct HashMap Int16 (Text, ThriftVal)
fields) = SpanRef :: SpanRefType -> Int64 -> Int64 -> Int64 -> SpanRef
SpanRef{
spanRef_refType :: SpanRefType
spanRef_refType = SpanRefType
-> ((Text, ThriftVal) -> SpanRefType)
-> Maybe (Text, ThriftVal)
-> SpanRefType
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (String -> SpanRefType
forall a. HasCallStack => String -> a
P.error String
"Missing required field: refType") (\(Text
_,ThriftVal
_val27) -> (case ThriftVal
_val27 of {T.TI32 Int32
_val28 -> Int -> SpanRefType
forall a. Enum a => Int -> a
P.toEnum (Int -> SpanRefType) -> Int -> SpanRefType
forall a b. (a -> b) -> a -> b
$ Int32 -> Int
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral Int32
_val28; ThriftVal
_ -> String -> SpanRefType
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),
spanRef_traceIdLow :: Int64
spanRef_traceIdLow = Int64
-> ((Text, ThriftVal) -> Int64) -> Maybe (Text, ThriftVal) -> Int64
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (String -> Int64
forall a. HasCallStack => String -> a
P.error String
"Missing required field: traceIdLow") (\(Text
_,ThriftVal
_val27) -> (case ThriftVal
_val27 of {T.TI64 Int64
_val29 -> Int64
_val29; ThriftVal
_ -> String -> Int64
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
2) HashMap Int16 (Text, ThriftVal)
fields),
spanRef_traceIdHigh :: Int64
spanRef_traceIdHigh = Int64
-> ((Text, ThriftVal) -> Int64) -> Maybe (Text, ThriftVal) -> Int64
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (String -> Int64
forall a. HasCallStack => String -> a
P.error String
"Missing required field: traceIdHigh") (\(Text
_,ThriftVal
_val27) -> (case ThriftVal
_val27 of {T.TI64 Int64
_val30 -> Int64
_val30; ThriftVal
_ -> String -> Int64
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
3) HashMap Int16 (Text, ThriftVal)
fields),
spanRef_spanId :: Int64
spanRef_spanId = Int64
-> ((Text, ThriftVal) -> Int64) -> Maybe (Text, ThriftVal) -> Int64
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (String -> Int64
forall a. HasCallStack => String -> a
P.error String
"Missing required field: spanId") (\(Text
_,ThriftVal
_val27) -> (case ThriftVal
_val27 of {T.TI64 Int64
_val31 -> Int64
_val31; ThriftVal
_ -> String -> Int64
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
4) HashMap Int16 (Text, ThriftVal)
fields)
}
to_SpanRef ThriftVal
_ = String -> SpanRef
forall a. HasCallStack => String -> a
P.error String
"not a struct"
read_SpanRef :: T.Protocol p => p -> P.IO SpanRef
read_SpanRef :: p -> IO SpanRef
read_SpanRef p
iprot = ThriftVal -> SpanRef
to_SpanRef (ThriftVal -> SpanRef) -> IO ThriftVal -> IO SpanRef
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_SpanRef)
decode_SpanRef :: T.StatelessProtocol p => p -> LBS.ByteString -> SpanRef
decode_SpanRef :: p -> ByteString -> SpanRef
decode_SpanRef p
iprot ByteString
bs = ThriftVal -> SpanRef
to_SpanRef (ThriftVal -> SpanRef) -> ThriftVal -> SpanRef
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_SpanRef) ByteString
bs
typemap_SpanRef :: T.TypeMap
typemap_SpanRef :: TypeMap
typemap_SpanRef = [(Int16, (Text, ThriftType))] -> TypeMap
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
Map.fromList [(Int16
1,(Text
"refType",ThriftType
T.T_I32)),(Int16
2,(Text
"traceIdLow",ThriftType
T.T_I64)),(Int16
3,(Text
"traceIdHigh",ThriftType
T.T_I64)),(Int16
4,(Text
"spanId",ThriftType
T.T_I64))]
default_SpanRef :: SpanRef
default_SpanRef :: SpanRef
default_SpanRef = SpanRef :: SpanRefType -> Int64 -> Int64 -> Int64 -> SpanRef
SpanRef{
spanRef_refType :: SpanRefType
spanRef_refType = (Int -> SpanRefType
forall a. Enum a => Int -> a
P.toEnum Int
0),
spanRef_traceIdLow :: Int64
spanRef_traceIdLow = Int64
0,
spanRef_traceIdHigh :: Int64
spanRef_traceIdHigh = Int64
0,
spanRef_spanId :: Int64
spanRef_spanId = Int64
0}
data Span = Span { Span -> Int64
span_traceIdLow :: I.Int64
, Span -> Int64
span_traceIdHigh :: I.Int64
, Span -> Int64
span_spanId :: I.Int64
, Span -> Int64
span_parentSpanId :: I.Int64
, Span -> Text
span_operationName :: LT.Text
, Span -> Maybe (Vector SpanRef)
span_references :: P.Maybe (Vector.Vector SpanRef)
, Span -> Int32
span_flags :: I.Int32
, Span -> Int64
span_startTime :: I.Int64
, Span -> Int64
span_duration :: I.Int64
, Span -> Maybe (Vector Tag)
span_tags :: P.Maybe (Vector.Vector Tag)
, Span -> Maybe (Vector Log)
span_logs :: P.Maybe (Vector.Vector Log)
, Span -> Maybe Bool
span_incomplete :: P.Maybe P.Bool
} deriving (Int -> Span -> ShowS
[Span] -> ShowS
Span -> String
(Int -> Span -> ShowS)
-> (Span -> String) -> ([Span] -> ShowS) -> Show Span
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Span] -> ShowS
$cshowList :: [Span] -> ShowS
show :: Span -> String
$cshow :: Span -> String
showsPrec :: Int -> Span -> ShowS
$cshowsPrec :: Int -> Span -> ShowS
P.Show,Span -> Span -> Bool
(Span -> Span -> Bool) -> (Span -> Span -> Bool) -> Eq Span
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Span -> Span -> Bool
$c/= :: Span -> Span -> Bool
== :: Span -> Span -> Bool
$c== :: Span -> Span -> Bool
P.Eq,(forall x. Span -> Rep Span x)
-> (forall x. Rep Span x -> Span) -> Generic Span
forall x. Rep Span x -> Span
forall x. Span -> Rep Span x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Span x -> Span
$cfrom :: forall x. Span -> Rep Span x
G.Generic,TY.Typeable)
instance H.Hashable Span where
hashWithSalt :: Int -> Span -> Int
hashWithSalt Int
salt Span
record = Int
salt Int -> Int64 -> Int
forall a. Hashable a => Int -> a -> Int
`H.hashWithSalt` Span -> Int64
span_traceIdLow Span
record Int -> Int64 -> Int
forall a. Hashable a => Int -> a -> Int
`H.hashWithSalt` Span -> Int64
span_traceIdHigh Span
record Int -> Int64 -> Int
forall a. Hashable a => Int -> a -> Int
`H.hashWithSalt` Span -> Int64
span_spanId Span
record Int -> Int64 -> Int
forall a. Hashable a => Int -> a -> Int
`H.hashWithSalt` Span -> Int64
span_parentSpanId Span
record Int -> Text -> Int
forall a. Hashable a => Int -> a -> Int
`H.hashWithSalt` Span -> Text
span_operationName Span
record Int -> Maybe (Vector SpanRef) -> Int
forall a. Hashable a => Int -> a -> Int
`H.hashWithSalt` Span -> Maybe (Vector SpanRef)
span_references Span
record Int -> Int32 -> Int
forall a. Hashable a => Int -> a -> Int
`H.hashWithSalt` Span -> Int32
span_flags Span
record Int -> Int64 -> Int
forall a. Hashable a => Int -> a -> Int
`H.hashWithSalt` Span -> Int64
span_startTime Span
record Int -> Int64 -> Int
forall a. Hashable a => Int -> a -> Int
`H.hashWithSalt` Span -> Int64
span_duration Span
record Int -> Maybe (Vector Tag) -> Int
forall a. Hashable a => Int -> a -> Int
`H.hashWithSalt` Span -> Maybe (Vector Tag)
span_tags Span
record Int -> Maybe (Vector Log) -> Int
forall a. Hashable a => Int -> a -> Int
`H.hashWithSalt` Span -> Maybe (Vector Log)
span_logs Span
record Int -> Maybe Bool -> Int
forall a. Hashable a => Int -> a -> Int
`H.hashWithSalt` Span -> Maybe Bool
span_incomplete Span
record
instance QC.Arbitrary Span where
arbitrary :: Gen Span
arbitrary = (Int64
-> Int64
-> Int64
-> Int64
-> Text
-> Maybe (Vector SpanRef)
-> Int32
-> Int64
-> Int64
-> Maybe (Vector Tag)
-> Maybe (Vector Log)
-> Maybe Bool
-> Span)
-> Gen Int64
-> Gen
(Int64
-> Int64
-> Int64
-> Text
-> Maybe (Vector SpanRef)
-> Int32
-> Int64
-> Int64
-> Maybe (Vector Tag)
-> Maybe (Vector Log)
-> Maybe Bool
-> Span)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
M.liftM Int64
-> Int64
-> Int64
-> Int64
-> Text
-> Maybe (Vector SpanRef)
-> Int32
-> Int64
-> Int64
-> Maybe (Vector Tag)
-> Maybe (Vector Log)
-> Maybe Bool
-> Span
Span (Gen Int64
forall a. Arbitrary a => Gen a
QC.arbitrary)
Gen
(Int64
-> Int64
-> Int64
-> Text
-> Maybe (Vector SpanRef)
-> Int32
-> Int64
-> Int64
-> Maybe (Vector Tag)
-> Maybe (Vector Log)
-> Maybe Bool
-> Span)
-> Gen Int64
-> Gen
(Int64
-> Int64
-> Text
-> Maybe (Vector SpanRef)
-> Int32
-> Int64
-> Int64
-> Maybe (Vector Tag)
-> Maybe (Vector Log)
-> Maybe Bool
-> Span)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`M.ap`(Gen Int64
forall a. Arbitrary a => Gen a
QC.arbitrary)
Gen
(Int64
-> Int64
-> Text
-> Maybe (Vector SpanRef)
-> Int32
-> Int64
-> Int64
-> Maybe (Vector Tag)
-> Maybe (Vector Log)
-> Maybe Bool
-> Span)
-> Gen Int64
-> Gen
(Int64
-> Text
-> Maybe (Vector SpanRef)
-> Int32
-> Int64
-> Int64
-> Maybe (Vector Tag)
-> Maybe (Vector Log)
-> Maybe Bool
-> Span)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`M.ap`(Gen Int64
forall a. Arbitrary a => Gen a
QC.arbitrary)
Gen
(Int64
-> Text
-> Maybe (Vector SpanRef)
-> Int32
-> Int64
-> Int64
-> Maybe (Vector Tag)
-> Maybe (Vector Log)
-> Maybe Bool
-> Span)
-> Gen Int64
-> Gen
(Text
-> Maybe (Vector SpanRef)
-> Int32
-> Int64
-> Int64
-> Maybe (Vector Tag)
-> Maybe (Vector Log)
-> Maybe Bool
-> Span)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`M.ap`(Gen Int64
forall a. Arbitrary a => Gen a
QC.arbitrary)
Gen
(Text
-> Maybe (Vector SpanRef)
-> Int32
-> Int64
-> Int64
-> Maybe (Vector Tag)
-> Maybe (Vector Log)
-> Maybe Bool
-> Span)
-> Gen Text
-> Gen
(Maybe (Vector SpanRef)
-> Int32
-> Int64
-> Int64
-> Maybe (Vector Tag)
-> Maybe (Vector Log)
-> Maybe Bool
-> Span)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`M.ap`(Gen Text
forall a. Arbitrary a => Gen a
QC.arbitrary)
Gen
(Maybe (Vector SpanRef)
-> Int32
-> Int64
-> Int64
-> Maybe (Vector Tag)
-> Maybe (Vector Log)
-> Maybe Bool
-> Span)
-> Gen (Maybe (Vector SpanRef))
-> Gen
(Int32
-> Int64
-> Int64
-> Maybe (Vector Tag)
-> Maybe (Vector Log)
-> Maybe Bool
-> Span)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`M.ap`((Vector SpanRef -> Maybe (Vector SpanRef))
-> Gen (Vector SpanRef) -> Gen (Maybe (Vector SpanRef))
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
M.liftM Vector SpanRef -> Maybe (Vector SpanRef)
forall a. a -> Maybe a
P.Just Gen (Vector SpanRef)
forall a. Arbitrary a => Gen a
QC.arbitrary)
Gen
(Int32
-> Int64
-> Int64
-> Maybe (Vector Tag)
-> Maybe (Vector Log)
-> Maybe Bool
-> Span)
-> Gen Int32
-> Gen
(Int64
-> Int64
-> Maybe (Vector Tag)
-> Maybe (Vector Log)
-> Maybe Bool
-> Span)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`M.ap`(Gen Int32
forall a. Arbitrary a => Gen a
QC.arbitrary)
Gen
(Int64
-> Int64
-> Maybe (Vector Tag)
-> Maybe (Vector Log)
-> Maybe Bool
-> Span)
-> Gen Int64
-> Gen
(Int64
-> Maybe (Vector Tag) -> Maybe (Vector Log) -> Maybe Bool -> Span)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`M.ap`(Gen Int64
forall a. Arbitrary a => Gen a
QC.arbitrary)
Gen
(Int64
-> Maybe (Vector Tag) -> Maybe (Vector Log) -> Maybe Bool -> Span)
-> Gen Int64
-> Gen
(Maybe (Vector Tag) -> Maybe (Vector Log) -> Maybe Bool -> Span)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`M.ap`(Gen Int64
forall a. Arbitrary a => Gen a
QC.arbitrary)
Gen
(Maybe (Vector Tag) -> Maybe (Vector Log) -> Maybe Bool -> Span)
-> Gen (Maybe (Vector Tag))
-> Gen (Maybe (Vector Log) -> Maybe Bool -> Span)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`M.ap`((Vector Tag -> Maybe (Vector Tag))
-> Gen (Vector Tag) -> Gen (Maybe (Vector Tag))
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
M.liftM Vector Tag -> Maybe (Vector Tag)
forall a. a -> Maybe a
P.Just Gen (Vector Tag)
forall a. Arbitrary a => Gen a
QC.arbitrary)
Gen (Maybe (Vector Log) -> Maybe Bool -> Span)
-> Gen (Maybe (Vector Log)) -> Gen (Maybe Bool -> Span)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`M.ap`((Vector Log -> Maybe (Vector Log))
-> Gen (Vector Log) -> Gen (Maybe (Vector Log))
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
M.liftM Vector Log -> Maybe (Vector Log)
forall a. a -> Maybe a
P.Just Gen (Vector Log)
forall a. Arbitrary a => Gen a
QC.arbitrary)
Gen (Maybe Bool -> Span) -> Gen (Maybe Bool) -> Gen Span
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`M.ap`((Bool -> Maybe Bool) -> Gen Bool -> Gen (Maybe Bool)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
M.liftM Bool -> Maybe Bool
forall a. a -> Maybe a
P.Just Gen Bool
forall a. Arbitrary a => Gen a
QC.arbitrary)
shrink :: Span -> [Span]
shrink Span
obj | Span
obj Span -> Span -> Bool
forall a. Eq a => a -> a -> Bool
== Span
default_Span = []
| Bool
P.otherwise = [Maybe Span] -> [Span]
forall a. [Maybe a] -> [a]
M.catMaybes
[ if Span
obj Span -> Span -> Bool
forall a. Eq a => a -> a -> Bool
== Span
default_Span{span_traceIdLow :: Int64
span_traceIdLow = Span -> Int64
span_traceIdLow Span
obj} then Maybe Span
forall a. Maybe a
P.Nothing else Span -> Maybe Span
forall a. a -> Maybe a
P.Just (Span -> Maybe Span) -> Span -> Maybe Span
forall a b. (a -> b) -> a -> b
$ Span
default_Span{span_traceIdLow :: Int64
span_traceIdLow = Span -> Int64
span_traceIdLow Span
obj}
, if Span
obj Span -> Span -> Bool
forall a. Eq a => a -> a -> Bool
== Span
default_Span{span_traceIdHigh :: Int64
span_traceIdHigh = Span -> Int64
span_traceIdHigh Span
obj} then Maybe Span
forall a. Maybe a
P.Nothing else Span -> Maybe Span
forall a. a -> Maybe a
P.Just (Span -> Maybe Span) -> Span -> Maybe Span
forall a b. (a -> b) -> a -> b
$ Span
default_Span{span_traceIdHigh :: Int64
span_traceIdHigh = Span -> Int64
span_traceIdHigh Span
obj}
, if Span
obj Span -> Span -> Bool
forall a. Eq a => a -> a -> Bool
== Span
default_Span{span_spanId :: Int64
span_spanId = Span -> Int64
span_spanId Span
obj} then Maybe Span
forall a. Maybe a
P.Nothing else Span -> Maybe Span
forall a. a -> Maybe a
P.Just (Span -> Maybe Span) -> Span -> Maybe Span
forall a b. (a -> b) -> a -> b
$ Span
default_Span{span_spanId :: Int64
span_spanId = Span -> Int64
span_spanId Span
obj}
, if Span
obj Span -> Span -> Bool
forall a. Eq a => a -> a -> Bool
== Span
default_Span{span_parentSpanId :: Int64
span_parentSpanId = Span -> Int64
span_parentSpanId Span
obj} then Maybe Span
forall a. Maybe a
P.Nothing else Span -> Maybe Span
forall a. a -> Maybe a
P.Just (Span -> Maybe Span) -> Span -> Maybe Span
forall a b. (a -> b) -> a -> b
$ Span
default_Span{span_parentSpanId :: Int64
span_parentSpanId = Span -> Int64
span_parentSpanId Span
obj}
, if Span
obj Span -> Span -> Bool
forall a. Eq a => a -> a -> Bool
== Span
default_Span{span_operationName :: Text
span_operationName = Span -> Text
span_operationName Span
obj} then Maybe Span
forall a. Maybe a
P.Nothing else Span -> Maybe Span
forall a. a -> Maybe a
P.Just (Span -> Maybe Span) -> Span -> Maybe Span
forall a b. (a -> b) -> a -> b
$ Span
default_Span{span_operationName :: Text
span_operationName = Span -> Text
span_operationName Span
obj}
, if Span
obj Span -> Span -> Bool
forall a. Eq a => a -> a -> Bool
== Span
default_Span{span_references :: Maybe (Vector SpanRef)
span_references = Span -> Maybe (Vector SpanRef)
span_references Span
obj} then Maybe Span
forall a. Maybe a
P.Nothing else Span -> Maybe Span
forall a. a -> Maybe a
P.Just (Span -> Maybe Span) -> Span -> Maybe Span
forall a b. (a -> b) -> a -> b
$ Span
default_Span{span_references :: Maybe (Vector SpanRef)
span_references = Span -> Maybe (Vector SpanRef)
span_references Span
obj}
, if Span
obj Span -> Span -> Bool
forall a. Eq a => a -> a -> Bool
== Span
default_Span{span_flags :: Int32
span_flags = Span -> Int32
span_flags Span
obj} then Maybe Span
forall a. Maybe a
P.Nothing else Span -> Maybe Span
forall a. a -> Maybe a
P.Just (Span -> Maybe Span) -> Span -> Maybe Span
forall a b. (a -> b) -> a -> b
$ Span
default_Span{span_flags :: Int32
span_flags = Span -> Int32
span_flags Span
obj}
, if Span
obj Span -> Span -> Bool
forall a. Eq a => a -> a -> Bool
== Span
default_Span{span_startTime :: Int64
span_startTime = Span -> Int64
span_startTime Span
obj} then Maybe Span
forall a. Maybe a
P.Nothing else Span -> Maybe Span
forall a. a -> Maybe a
P.Just (Span -> Maybe Span) -> Span -> Maybe Span
forall a b. (a -> b) -> a -> b
$ Span
default_Span{span_startTime :: Int64
span_startTime = Span -> Int64
span_startTime Span
obj}
, if Span
obj Span -> Span -> Bool
forall a. Eq a => a -> a -> Bool
== Span
default_Span{span_duration :: Int64
span_duration = Span -> Int64
span_duration Span
obj} then Maybe Span
forall a. Maybe a
P.Nothing else Span -> Maybe Span
forall a. a -> Maybe a
P.Just (Span -> Maybe Span) -> Span -> Maybe Span
forall a b. (a -> b) -> a -> b
$ Span
default_Span{span_duration :: Int64
span_duration = Span -> Int64
span_duration Span
obj}
, if Span
obj Span -> Span -> Bool
forall a. Eq a => a -> a -> Bool
== Span
default_Span{span_tags :: Maybe (Vector Tag)
span_tags = Span -> Maybe (Vector Tag)
span_tags Span
obj} then Maybe Span
forall a. Maybe a
P.Nothing else Span -> Maybe Span
forall a. a -> Maybe a
P.Just (Span -> Maybe Span) -> Span -> Maybe Span
forall a b. (a -> b) -> a -> b
$ Span
default_Span{span_tags :: Maybe (Vector Tag)
span_tags = Span -> Maybe (Vector Tag)
span_tags Span
obj}
, if Span
obj Span -> Span -> Bool
forall a. Eq a => a -> a -> Bool
== Span
default_Span{span_logs :: Maybe (Vector Log)
span_logs = Span -> Maybe (Vector Log)
span_logs Span
obj} then Maybe Span
forall a. Maybe a
P.Nothing else Span -> Maybe Span
forall a. a -> Maybe a
P.Just (Span -> Maybe Span) -> Span -> Maybe Span
forall a b. (a -> b) -> a -> b
$ Span
default_Span{span_logs :: Maybe (Vector Log)
span_logs = Span -> Maybe (Vector Log)
span_logs Span
obj}
, if Span
obj Span -> Span -> Bool
forall a. Eq a => a -> a -> Bool
== Span
default_Span{span_incomplete :: Maybe Bool
span_incomplete = Span -> Maybe Bool
span_incomplete Span
obj} then Maybe Span
forall a. Maybe a
P.Nothing else Span -> Maybe Span
forall a. a -> Maybe a
P.Just (Span -> Maybe Span) -> Span -> Maybe Span
forall a b. (a -> b) -> a -> b
$ Span
default_Span{span_incomplete :: Maybe Bool
span_incomplete = Span -> Maybe Bool
span_incomplete Span
obj}
]
from_Span :: Span -> T.ThriftVal
from_Span :: Span -> ThriftVal
from_Span Span
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
[ (\Int64
_v34 -> (Int16, (Text, ThriftVal)) -> Maybe (Int16, (Text, ThriftVal))
forall a. a -> Maybe a
P.Just (Int16
1, (Text
"traceIdLow",Int64 -> ThriftVal
T.TI64 Int64
_v34))) (Int64 -> Maybe (Int16, (Text, ThriftVal)))
-> Int64 -> Maybe (Int16, (Text, ThriftVal))
forall a b. (a -> b) -> a -> b
$ Span -> Int64
span_traceIdLow Span
record
, (\Int64
_v34 -> (Int16, (Text, ThriftVal)) -> Maybe (Int16, (Text, ThriftVal))
forall a. a -> Maybe a
P.Just (Int16
2, (Text
"traceIdHigh",Int64 -> ThriftVal
T.TI64 Int64
_v34))) (Int64 -> Maybe (Int16, (Text, ThriftVal)))
-> Int64 -> Maybe (Int16, (Text, ThriftVal))
forall a b. (a -> b) -> a -> b
$ Span -> Int64
span_traceIdHigh Span
record
, (\Int64
_v34 -> (Int16, (Text, ThriftVal)) -> Maybe (Int16, (Text, ThriftVal))
forall a. a -> Maybe a
P.Just (Int16
3, (Text
"spanId",Int64 -> ThriftVal
T.TI64 Int64
_v34))) (Int64 -> Maybe (Int16, (Text, ThriftVal)))
-> Int64 -> Maybe (Int16, (Text, ThriftVal))
forall a b. (a -> b) -> a -> b
$ Span -> Int64
span_spanId Span
record
, (\Int64
_v34 -> (Int16, (Text, ThriftVal)) -> Maybe (Int16, (Text, ThriftVal))
forall a. a -> Maybe a
P.Just (Int16
4, (Text
"parentSpanId",Int64 -> ThriftVal
T.TI64 Int64
_v34))) (Int64 -> Maybe (Int16, (Text, ThriftVal)))
-> Int64 -> Maybe (Int16, (Text, ThriftVal))
forall a b. (a -> b) -> a -> b
$ Span -> Int64
span_parentSpanId Span
record
, (\Text
_v34 -> (Int16, (Text, ThriftVal)) -> Maybe (Int16, (Text, ThriftVal))
forall a. a -> Maybe a
P.Just (Int16
5, (Text
"operationName",ByteString -> ThriftVal
T.TString (ByteString -> ThriftVal) -> ByteString -> ThriftVal
forall a b. (a -> b) -> a -> b
$ Text -> ByteString
E.encodeUtf8 Text
_v34))) (Text -> Maybe (Int16, (Text, ThriftVal)))
-> Text -> Maybe (Int16, (Text, ThriftVal))
forall a b. (a -> b) -> a -> b
$ Span -> Text
span_operationName Span
record
, (\Vector SpanRef
_v34 -> (Int16
6, (Text
"references",ThriftType -> [ThriftVal] -> ThriftVal
T.TList (TypeMap -> ThriftType
T.T_STRUCT TypeMap
typemap_SpanRef) ([ThriftVal] -> ThriftVal) -> [ThriftVal] -> ThriftVal
forall a b. (a -> b) -> a -> b
$ (SpanRef -> ThriftVal) -> [SpanRef] -> [ThriftVal]
forall a b. (a -> b) -> [a] -> [b]
P.map (\SpanRef
_v36 -> SpanRef -> ThriftVal
from_SpanRef SpanRef
_v36) ([SpanRef] -> [ThriftVal]) -> [SpanRef] -> [ThriftVal]
forall a b. (a -> b) -> a -> b
$ Vector SpanRef -> [SpanRef]
forall a. Vector a -> [a]
Vector.toList Vector SpanRef
_v34))) (Vector SpanRef -> (Int16, (Text, ThriftVal)))
-> Maybe (Vector SpanRef) -> Maybe (Int16, (Text, ThriftVal))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Span -> Maybe (Vector SpanRef)
span_references Span
record
, (\Int32
_v34 -> (Int16, (Text, ThriftVal)) -> Maybe (Int16, (Text, ThriftVal))
forall a. a -> Maybe a
P.Just (Int16
7, (Text
"flags",Int32 -> ThriftVal
T.TI32 Int32
_v34))) (Int32 -> Maybe (Int16, (Text, ThriftVal)))
-> Int32 -> Maybe (Int16, (Text, ThriftVal))
forall a b. (a -> b) -> a -> b
$ Span -> Int32
span_flags Span
record
, (\Int64
_v34 -> (Int16, (Text, ThriftVal)) -> Maybe (Int16, (Text, ThriftVal))
forall a. a -> Maybe a
P.Just (Int16
8, (Text
"startTime",Int64 -> ThriftVal
T.TI64 Int64
_v34))) (Int64 -> Maybe (Int16, (Text, ThriftVal)))
-> Int64 -> Maybe (Int16, (Text, ThriftVal))
forall a b. (a -> b) -> a -> b
$ Span -> Int64
span_startTime Span
record
, (\Int64
_v34 -> (Int16, (Text, ThriftVal)) -> Maybe (Int16, (Text, ThriftVal))
forall a. a -> Maybe a
P.Just (Int16
9, (Text
"duration",Int64 -> ThriftVal
T.TI64 Int64
_v34))) (Int64 -> Maybe (Int16, (Text, ThriftVal)))
-> Int64 -> Maybe (Int16, (Text, ThriftVal))
forall a b. (a -> b) -> a -> b
$ Span -> Int64
span_duration Span
record
, (\Vector Tag
_v34 -> (Int16
10, (Text
"tags",ThriftType -> [ThriftVal] -> ThriftVal
T.TList (TypeMap -> ThriftType
T.T_STRUCT TypeMap
typemap_Tag) ([ThriftVal] -> ThriftVal) -> [ThriftVal] -> ThriftVal
forall a b. (a -> b) -> a -> b
$ (Tag -> ThriftVal) -> [Tag] -> [ThriftVal]
forall a b. (a -> b) -> [a] -> [b]
P.map (\Tag
_v38 -> Tag -> ThriftVal
from_Tag Tag
_v38) ([Tag] -> [ThriftVal]) -> [Tag] -> [ThriftVal]
forall a b. (a -> b) -> a -> b
$ Vector Tag -> [Tag]
forall a. Vector a -> [a]
Vector.toList Vector Tag
_v34))) (Vector Tag -> (Int16, (Text, ThriftVal)))
-> Maybe (Vector Tag) -> Maybe (Int16, (Text, ThriftVal))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Span -> Maybe (Vector Tag)
span_tags Span
record
, (\Vector Log
_v34 -> (Int16
11, (Text
"logs",ThriftType -> [ThriftVal] -> ThriftVal
T.TList (TypeMap -> ThriftType
T.T_STRUCT TypeMap
typemap_Log) ([ThriftVal] -> ThriftVal) -> [ThriftVal] -> ThriftVal
forall a b. (a -> b) -> a -> b
$ (Log -> ThriftVal) -> [Log] -> [ThriftVal]
forall a b. (a -> b) -> [a] -> [b]
P.map (\Log
_v40 -> Log -> ThriftVal
from_Log Log
_v40) ([Log] -> [ThriftVal]) -> [Log] -> [ThriftVal]
forall a b. (a -> b) -> a -> b
$ Vector Log -> [Log]
forall a. Vector a -> [a]
Vector.toList Vector Log
_v34))) (Vector Log -> (Int16, (Text, ThriftVal)))
-> Maybe (Vector Log) -> Maybe (Int16, (Text, ThriftVal))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Span -> Maybe (Vector Log)
span_logs Span
record
, (\Bool
_v34 -> (Int16
12, (Text
"incomplete",Bool -> ThriftVal
T.TBool Bool
_v34))) (Bool -> (Int16, (Text, ThriftVal)))
-> Maybe Bool -> Maybe (Int16, (Text, ThriftVal))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Span -> Maybe Bool
span_incomplete Span
record
]
write_Span :: T.Protocol p => p -> Span -> P.IO ()
write_Span :: p -> Span -> IO ()
write_Span p
oprot Span
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
$ Span -> ThriftVal
from_Span Span
record
encode_Span :: T.StatelessProtocol p => p -> Span -> LBS.ByteString
encode_Span :: p -> Span -> ByteString
encode_Span p
oprot Span
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
$ Span -> ThriftVal
from_Span Span
record
to_Span :: T.ThriftVal -> Span
to_Span :: ThriftVal -> Span
to_Span (T.TStruct HashMap Int16 (Text, ThriftVal)
fields) = Span :: Int64
-> Int64
-> Int64
-> Int64
-> Text
-> Maybe (Vector SpanRef)
-> Int32
-> Int64
-> Int64
-> Maybe (Vector Tag)
-> Maybe (Vector Log)
-> Maybe Bool
-> Span
Span{
span_traceIdLow :: Int64
span_traceIdLow = Int64
-> ((Text, ThriftVal) -> Int64) -> Maybe (Text, ThriftVal) -> Int64
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (String -> Int64
forall a. HasCallStack => String -> a
P.error String
"Missing required field: traceIdLow") (\(Text
_,ThriftVal
_val42) -> (case ThriftVal
_val42 of {T.TI64 Int64
_val43 -> Int64
_val43; ThriftVal
_ -> String -> Int64
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),
span_traceIdHigh :: Int64
span_traceIdHigh = Int64
-> ((Text, ThriftVal) -> Int64) -> Maybe (Text, ThriftVal) -> Int64
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (String -> Int64
forall a. HasCallStack => String -> a
P.error String
"Missing required field: traceIdHigh") (\(Text
_,ThriftVal
_val42) -> (case ThriftVal
_val42 of {T.TI64 Int64
_val44 -> Int64
_val44; ThriftVal
_ -> String -> Int64
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
2) HashMap Int16 (Text, ThriftVal)
fields),
span_spanId :: Int64
span_spanId = Int64
-> ((Text, ThriftVal) -> Int64) -> Maybe (Text, ThriftVal) -> Int64
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (String -> Int64
forall a. HasCallStack => String -> a
P.error String
"Missing required field: spanId") (\(Text
_,ThriftVal
_val42) -> (case ThriftVal
_val42 of {T.TI64 Int64
_val45 -> Int64
_val45; ThriftVal
_ -> String -> Int64
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
3) HashMap Int16 (Text, ThriftVal)
fields),
span_parentSpanId :: Int64
span_parentSpanId = Int64
-> ((Text, ThriftVal) -> Int64) -> Maybe (Text, ThriftVal) -> Int64
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (String -> Int64
forall a. HasCallStack => String -> a
P.error String
"Missing required field: parentSpanId") (\(Text
_,ThriftVal
_val42) -> (case ThriftVal
_val42 of {T.TI64 Int64
_val46 -> Int64
_val46; ThriftVal
_ -> String -> Int64
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
4) HashMap Int16 (Text, ThriftVal)
fields),
span_operationName :: Text
span_operationName = Text
-> ((Text, ThriftVal) -> Text) -> Maybe (Text, ThriftVal) -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (String -> Text
forall a. HasCallStack => String -> a
P.error String
"Missing required field: operationName") (\(Text
_,ThriftVal
_val42) -> (case ThriftVal
_val42 of {T.TString ByteString
_val47 -> ByteString -> Text
E.decodeUtf8 ByteString
_val47; ThriftVal
_ -> String -> Text
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
5) HashMap Int16 (Text, ThriftVal)
fields),
span_references :: Maybe (Vector SpanRef)
span_references = Maybe (Vector SpanRef)
-> ((Text, ThriftVal) -> Maybe (Vector SpanRef))
-> Maybe (Text, ThriftVal)
-> Maybe (Vector SpanRef)
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (Maybe (Vector SpanRef)
forall a. Maybe a
P.Nothing) (\(Text
_,ThriftVal
_val42) -> Vector SpanRef -> Maybe (Vector SpanRef)
forall a. a -> Maybe a
P.Just (case ThriftVal
_val42 of {T.TList ThriftType
_ [ThriftVal]
_val48 -> ([SpanRef] -> Vector SpanRef
forall a. [a] -> Vector a
Vector.fromList ([SpanRef] -> Vector SpanRef) -> [SpanRef] -> Vector SpanRef
forall a b. (a -> b) -> a -> b
$ (ThriftVal -> SpanRef) -> [ThriftVal] -> [SpanRef]
forall a b. (a -> b) -> [a] -> [b]
P.map (\ThriftVal
_v49 -> (case ThriftVal
_v49 of {T.TStruct HashMap Int16 (Text, ThriftVal)
_val50 -> (ThriftVal -> SpanRef
to_SpanRef (HashMap Int16 (Text, ThriftVal) -> ThriftVal
T.TStruct HashMap Int16 (Text, ThriftVal)
_val50)); ThriftVal
_ -> String -> SpanRef
forall a. HasCallStack => String -> a
P.error String
"wrong type"})) [ThriftVal]
_val48); ThriftVal
_ -> String -> Vector SpanRef
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
6) HashMap Int16 (Text, ThriftVal)
fields),
span_flags :: Int32
span_flags = Int32
-> ((Text, ThriftVal) -> Int32) -> Maybe (Text, ThriftVal) -> Int32
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (String -> Int32
forall a. HasCallStack => String -> a
P.error String
"Missing required field: flags") (\(Text
_,ThriftVal
_val42) -> (case ThriftVal
_val42 of {T.TI32 Int32
_val51 -> Int32
_val51; ThriftVal
_ -> String -> Int32
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
7) HashMap Int16 (Text, ThriftVal)
fields),
span_startTime :: Int64
span_startTime = Int64
-> ((Text, ThriftVal) -> Int64) -> Maybe (Text, ThriftVal) -> Int64
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (String -> Int64
forall a. HasCallStack => String -> a
P.error String
"Missing required field: startTime") (\(Text
_,ThriftVal
_val42) -> (case ThriftVal
_val42 of {T.TI64 Int64
_val52 -> Int64
_val52; ThriftVal
_ -> String -> Int64
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
8) HashMap Int16 (Text, ThriftVal)
fields),
span_duration :: Int64
span_duration = Int64
-> ((Text, ThriftVal) -> Int64) -> Maybe (Text, ThriftVal) -> Int64
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (String -> Int64
forall a. HasCallStack => String -> a
P.error String
"Missing required field: duration") (\(Text
_,ThriftVal
_val42) -> (case ThriftVal
_val42 of {T.TI64 Int64
_val53 -> Int64
_val53; ThriftVal
_ -> String -> Int64
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
9) HashMap Int16 (Text, ThriftVal)
fields),
span_tags :: Maybe (Vector Tag)
span_tags = Maybe (Vector Tag)
-> ((Text, ThriftVal) -> Maybe (Vector Tag))
-> Maybe (Text, ThriftVal)
-> Maybe (Vector Tag)
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (Maybe (Vector Tag)
forall a. Maybe a
P.Nothing) (\(Text
_,ThriftVal
_val42) -> Vector Tag -> Maybe (Vector Tag)
forall a. a -> Maybe a
P.Just (case ThriftVal
_val42 of {T.TList ThriftType
_ [ThriftVal]
_val54 -> ([Tag] -> Vector Tag
forall a. [a] -> Vector a
Vector.fromList ([Tag] -> Vector Tag) -> [Tag] -> Vector Tag
forall a b. (a -> b) -> a -> b
$ (ThriftVal -> Tag) -> [ThriftVal] -> [Tag]
forall a b. (a -> b) -> [a] -> [b]
P.map (\ThriftVal
_v55 -> (case ThriftVal
_v55 of {T.TStruct HashMap Int16 (Text, ThriftVal)
_val56 -> (ThriftVal -> Tag
to_Tag (HashMap Int16 (Text, ThriftVal) -> ThriftVal
T.TStruct HashMap Int16 (Text, ThriftVal)
_val56)); ThriftVal
_ -> String -> Tag
forall a. HasCallStack => String -> a
P.error String
"wrong type"})) [ThriftVal]
_val54); ThriftVal
_ -> String -> Vector Tag
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
10) HashMap Int16 (Text, ThriftVal)
fields),
span_logs :: Maybe (Vector Log)
span_logs = Maybe (Vector Log)
-> ((Text, ThriftVal) -> Maybe (Vector Log))
-> Maybe (Text, ThriftVal)
-> Maybe (Vector Log)
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (Maybe (Vector Log)
forall a. Maybe a
P.Nothing) (\(Text
_,ThriftVal
_val42) -> Vector Log -> Maybe (Vector Log)
forall a. a -> Maybe a
P.Just (case ThriftVal
_val42 of {T.TList ThriftType
_ [ThriftVal]
_val57 -> ([Log] -> Vector Log
forall a. [a] -> Vector a
Vector.fromList ([Log] -> Vector Log) -> [Log] -> Vector Log
forall a b. (a -> b) -> a -> b
$ (ThriftVal -> Log) -> [ThriftVal] -> [Log]
forall a b. (a -> b) -> [a] -> [b]
P.map (\ThriftVal
_v58 -> (case ThriftVal
_v58 of {T.TStruct HashMap Int16 (Text, ThriftVal)
_val59 -> (ThriftVal -> Log
to_Log (HashMap Int16 (Text, ThriftVal) -> ThriftVal
T.TStruct HashMap Int16 (Text, ThriftVal)
_val59)); ThriftVal
_ -> String -> Log
forall a. HasCallStack => String -> a
P.error String
"wrong type"})) [ThriftVal]
_val57); ThriftVal
_ -> String -> Vector Log
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
11) HashMap Int16 (Text, ThriftVal)
fields),
span_incomplete :: Maybe Bool
span_incomplete = Maybe Bool
-> ((Text, ThriftVal) -> Maybe Bool)
-> Maybe (Text, ThriftVal)
-> Maybe Bool
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (Maybe Bool
forall a. Maybe a
P.Nothing) (\(Text
_,ThriftVal
_val42) -> Bool -> Maybe Bool
forall a. a -> Maybe a
P.Just (case ThriftVal
_val42 of {T.TBool Bool
_val60 -> Bool
_val60; ThriftVal
_ -> String -> Bool
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
12) HashMap Int16 (Text, ThriftVal)
fields)
}
to_Span ThriftVal
_ = String -> Span
forall a. HasCallStack => String -> a
P.error String
"not a struct"
read_Span :: T.Protocol p => p -> P.IO Span
read_Span :: p -> IO Span
read_Span p
iprot = ThriftVal -> Span
to_Span (ThriftVal -> Span) -> IO ThriftVal -> IO Span
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_Span)
decode_Span :: T.StatelessProtocol p => p -> LBS.ByteString -> Span
decode_Span :: p -> ByteString -> Span
decode_Span p
iprot ByteString
bs = ThriftVal -> Span
to_Span (ThriftVal -> Span) -> ThriftVal -> Span
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_Span) ByteString
bs
typemap_Span :: T.TypeMap
typemap_Span :: TypeMap
typemap_Span = [(Int16, (Text, ThriftType))] -> TypeMap
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
Map.fromList [(Int16
1,(Text
"traceIdLow",ThriftType
T.T_I64)),(Int16
2,(Text
"traceIdHigh",ThriftType
T.T_I64)),(Int16
3,(Text
"spanId",ThriftType
T.T_I64)),(Int16
4,(Text
"parentSpanId",ThriftType
T.T_I64)),(Int16
5,(Text
"operationName",ThriftType
T.T_STRING)),(Int16
6,(Text
"references",(ThriftType -> ThriftType
T.T_LIST (TypeMap -> ThriftType
T.T_STRUCT TypeMap
typemap_SpanRef)))),(Int16
7,(Text
"flags",ThriftType
T.T_I32)),(Int16
8,(Text
"startTime",ThriftType
T.T_I64)),(Int16
9,(Text
"duration",ThriftType
T.T_I64)),(Int16
10,(Text
"tags",(ThriftType -> ThriftType
T.T_LIST (TypeMap -> ThriftType
T.T_STRUCT TypeMap
typemap_Tag)))),(Int16
11,(Text
"logs",(ThriftType -> ThriftType
T.T_LIST (TypeMap -> ThriftType
T.T_STRUCT TypeMap
typemap_Log)))),(Int16
12,(Text
"incomplete",ThriftType
T.T_BOOL))]
default_Span :: Span
default_Span :: Span
default_Span = Span :: Int64
-> Int64
-> Int64
-> Int64
-> Text
-> Maybe (Vector SpanRef)
-> Int32
-> Int64
-> Int64
-> Maybe (Vector Tag)
-> Maybe (Vector Log)
-> Maybe Bool
-> Span
Span{
span_traceIdLow :: Int64
span_traceIdLow = Int64
0,
span_traceIdHigh :: Int64
span_traceIdHigh = Int64
0,
span_spanId :: Int64
span_spanId = Int64
0,
span_parentSpanId :: Int64
span_parentSpanId = Int64
0,
span_operationName :: Text
span_operationName = Text
"",
span_references :: Maybe (Vector SpanRef)
span_references = Maybe (Vector SpanRef)
forall a. Maybe a
P.Nothing,
span_flags :: Int32
span_flags = Int32
0,
span_startTime :: Int64
span_startTime = Int64
0,
span_duration :: Int64
span_duration = Int64
0,
span_tags :: Maybe (Vector Tag)
span_tags = Maybe (Vector Tag)
forall a. Maybe a
P.Nothing,
span_logs :: Maybe (Vector Log)
span_logs = Maybe (Vector Log)
forall a. Maybe a
P.Nothing,
span_incomplete :: Maybe Bool
span_incomplete = Maybe Bool
forall a. Maybe a
P.Nothing}
data Process = Process { Process -> Text
process_serviceName :: LT.Text
, Process -> Maybe (Vector Tag)
process_tags :: P.Maybe (Vector.Vector Tag)
} deriving (Int -> Process -> ShowS
[Process] -> ShowS
Process -> String
(Int -> Process -> ShowS)
-> (Process -> String) -> ([Process] -> ShowS) -> Show Process
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Process] -> ShowS
$cshowList :: [Process] -> ShowS
show :: Process -> String
$cshow :: Process -> String
showsPrec :: Int -> Process -> ShowS
$cshowsPrec :: Int -> Process -> ShowS
P.Show,Process -> Process -> Bool
(Process -> Process -> Bool)
-> (Process -> Process -> Bool) -> Eq Process
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Process -> Process -> Bool
$c/= :: Process -> Process -> Bool
== :: Process -> Process -> Bool
$c== :: Process -> Process -> Bool
P.Eq,(forall x. Process -> Rep Process x)
-> (forall x. Rep Process x -> Process) -> Generic Process
forall x. Rep Process x -> Process
forall x. Process -> Rep Process x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Process x -> Process
$cfrom :: forall x. Process -> Rep Process x
G.Generic,TY.Typeable)
instance H.Hashable Process where
hashWithSalt :: Int -> Process -> Int
hashWithSalt Int
salt Process
record = Int
salt Int -> Text -> Int
forall a. Hashable a => Int -> a -> Int
`H.hashWithSalt` Process -> Text
process_serviceName Process
record Int -> Maybe (Vector Tag) -> Int
forall a. Hashable a => Int -> a -> Int
`H.hashWithSalt` Process -> Maybe (Vector Tag)
process_tags Process
record
instance QC.Arbitrary Process where
arbitrary :: Gen Process
arbitrary = (Text -> Maybe (Vector Tag) -> Process)
-> Gen Text -> Gen (Maybe (Vector Tag) -> Process)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
M.liftM Text -> Maybe (Vector Tag) -> Process
Process (Gen Text
forall a. Arbitrary a => Gen a
QC.arbitrary)
Gen (Maybe (Vector Tag) -> Process)
-> Gen (Maybe (Vector Tag)) -> Gen Process
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`M.ap`((Vector Tag -> Maybe (Vector Tag))
-> Gen (Vector Tag) -> Gen (Maybe (Vector Tag))
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
M.liftM Vector Tag -> Maybe (Vector Tag)
forall a. a -> Maybe a
P.Just Gen (Vector Tag)
forall a. Arbitrary a => Gen a
QC.arbitrary)
shrink :: Process -> [Process]
shrink Process
obj | Process
obj Process -> Process -> Bool
forall a. Eq a => a -> a -> Bool
== Process
default_Process = []
| Bool
P.otherwise = [Maybe Process] -> [Process]
forall a. [Maybe a] -> [a]
M.catMaybes
[ if Process
obj Process -> Process -> Bool
forall a. Eq a => a -> a -> Bool
== Process
default_Process{process_serviceName :: Text
process_serviceName = Process -> Text
process_serviceName Process
obj} then Maybe Process
forall a. Maybe a
P.Nothing else Process -> Maybe Process
forall a. a -> Maybe a
P.Just (Process -> Maybe Process) -> Process -> Maybe Process
forall a b. (a -> b) -> a -> b
$ Process
default_Process{process_serviceName :: Text
process_serviceName = Process -> Text
process_serviceName Process
obj}
, if Process
obj Process -> Process -> Bool
forall a. Eq a => a -> a -> Bool
== Process
default_Process{process_tags :: Maybe (Vector Tag)
process_tags = Process -> Maybe (Vector Tag)
process_tags Process
obj} then Maybe Process
forall a. Maybe a
P.Nothing else Process -> Maybe Process
forall a. a -> Maybe a
P.Just (Process -> Maybe Process) -> Process -> Maybe Process
forall a b. (a -> b) -> a -> b
$ Process
default_Process{process_tags :: Maybe (Vector Tag)
process_tags = Process -> Maybe (Vector Tag)
process_tags Process
obj}
]
from_Process :: Process -> T.ThriftVal
from_Process :: Process -> ThriftVal
from_Process Process
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
[ (\Text
_v63 -> (Int16, (Text, ThriftVal)) -> Maybe (Int16, (Text, ThriftVal))
forall a. a -> Maybe a
P.Just (Int16
1, (Text
"serviceName",ByteString -> ThriftVal
T.TString (ByteString -> ThriftVal) -> ByteString -> ThriftVal
forall a b. (a -> b) -> a -> b
$ Text -> ByteString
E.encodeUtf8 Text
_v63))) (Text -> Maybe (Int16, (Text, ThriftVal)))
-> Text -> Maybe (Int16, (Text, ThriftVal))
forall a b. (a -> b) -> a -> b
$ Process -> Text
process_serviceName Process
record
, (\Vector Tag
_v63 -> (Int16
2, (Text
"tags",ThriftType -> [ThriftVal] -> ThriftVal
T.TList (TypeMap -> ThriftType
T.T_STRUCT TypeMap
typemap_Tag) ([ThriftVal] -> ThriftVal) -> [ThriftVal] -> ThriftVal
forall a b. (a -> b) -> a -> b
$ (Tag -> ThriftVal) -> [Tag] -> [ThriftVal]
forall a b. (a -> b) -> [a] -> [b]
P.map (\Tag
_v65 -> Tag -> ThriftVal
from_Tag Tag
_v65) ([Tag] -> [ThriftVal]) -> [Tag] -> [ThriftVal]
forall a b. (a -> b) -> a -> b
$ Vector Tag -> [Tag]
forall a. Vector a -> [a]
Vector.toList Vector Tag
_v63))) (Vector Tag -> (Int16, (Text, ThriftVal)))
-> Maybe (Vector Tag) -> Maybe (Int16, (Text, ThriftVal))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Process -> Maybe (Vector Tag)
process_tags Process
record
]
write_Process :: T.Protocol p => p -> Process -> P.IO ()
write_Process :: p -> Process -> IO ()
write_Process p
oprot Process
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
$ Process -> ThriftVal
from_Process Process
record
encode_Process :: T.StatelessProtocol p => p -> Process -> LBS.ByteString
encode_Process :: p -> Process -> ByteString
encode_Process p
oprot Process
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
$ Process -> ThriftVal
from_Process Process
record
to_Process :: T.ThriftVal -> Process
to_Process :: ThriftVal -> Process
to_Process (T.TStruct HashMap Int16 (Text, ThriftVal)
fields) = Process :: Text -> Maybe (Vector Tag) -> Process
Process{
process_serviceName :: Text
process_serviceName = Text
-> ((Text, ThriftVal) -> Text) -> Maybe (Text, ThriftVal) -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (String -> Text
forall a. HasCallStack => String -> a
P.error String
"Missing required field: serviceName") (\(Text
_,ThriftVal
_val67) -> (case ThriftVal
_val67 of {T.TString ByteString
_val68 -> ByteString -> Text
E.decodeUtf8 ByteString
_val68; ThriftVal
_ -> String -> Text
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),
process_tags :: Maybe (Vector Tag)
process_tags = Maybe (Vector Tag)
-> ((Text, ThriftVal) -> Maybe (Vector Tag))
-> Maybe (Text, ThriftVal)
-> Maybe (Vector Tag)
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (Maybe (Vector Tag)
forall a. Maybe a
P.Nothing) (\(Text
_,ThriftVal
_val67) -> Vector Tag -> Maybe (Vector Tag)
forall a. a -> Maybe a
P.Just (case ThriftVal
_val67 of {T.TList ThriftType
_ [ThriftVal]
_val69 -> ([Tag] -> Vector Tag
forall a. [a] -> Vector a
Vector.fromList ([Tag] -> Vector Tag) -> [Tag] -> Vector Tag
forall a b. (a -> b) -> a -> b
$ (ThriftVal -> Tag) -> [ThriftVal] -> [Tag]
forall a b. (a -> b) -> [a] -> [b]
P.map (\ThriftVal
_v70 -> (case ThriftVal
_v70 of {T.TStruct HashMap Int16 (Text, ThriftVal)
_val71 -> (ThriftVal -> Tag
to_Tag (HashMap Int16 (Text, ThriftVal) -> ThriftVal
T.TStruct HashMap Int16 (Text, ThriftVal)
_val71)); ThriftVal
_ -> String -> Tag
forall a. HasCallStack => String -> a
P.error String
"wrong type"})) [ThriftVal]
_val69); ThriftVal
_ -> String -> Vector Tag
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
2) HashMap Int16 (Text, ThriftVal)
fields)
}
to_Process ThriftVal
_ = String -> Process
forall a. HasCallStack => String -> a
P.error String
"not a struct"
read_Process :: T.Protocol p => p -> P.IO Process
read_Process :: p -> IO Process
read_Process p
iprot = ThriftVal -> Process
to_Process (ThriftVal -> Process) -> IO ThriftVal -> IO Process
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_Process)
decode_Process :: T.StatelessProtocol p => p -> LBS.ByteString -> Process
decode_Process :: p -> ByteString -> Process
decode_Process p
iprot ByteString
bs = ThriftVal -> Process
to_Process (ThriftVal -> Process) -> ThriftVal -> Process
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_Process) ByteString
bs
typemap_Process :: T.TypeMap
typemap_Process :: TypeMap
typemap_Process = [(Int16, (Text, ThriftType))] -> TypeMap
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
Map.fromList [(Int16
1,(Text
"serviceName",ThriftType
T.T_STRING)),(Int16
2,(Text
"tags",(ThriftType -> ThriftType
T.T_LIST (TypeMap -> ThriftType
T.T_STRUCT TypeMap
typemap_Tag))))]
default_Process :: Process
default_Process :: Process
default_Process = Process :: Text -> Maybe (Vector Tag) -> Process
Process{
process_serviceName :: Text
process_serviceName = Text
"",
process_tags :: Maybe (Vector Tag)
process_tags = Maybe (Vector Tag)
forall a. Maybe a
P.Nothing}
data Batch = Batch { Batch -> Process
batch_process :: Process
, Batch -> Vector Span
batch_spans :: (Vector.Vector Span)
} deriving (Int -> Batch -> ShowS
[Batch] -> ShowS
Batch -> String
(Int -> Batch -> ShowS)
-> (Batch -> String) -> ([Batch] -> ShowS) -> Show Batch
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Batch] -> ShowS
$cshowList :: [Batch] -> ShowS
show :: Batch -> String
$cshow :: Batch -> String
showsPrec :: Int -> Batch -> ShowS
$cshowsPrec :: Int -> Batch -> ShowS
P.Show,Batch -> Batch -> Bool
(Batch -> Batch -> Bool) -> (Batch -> Batch -> Bool) -> Eq Batch
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Batch -> Batch -> Bool
$c/= :: Batch -> Batch -> Bool
== :: Batch -> Batch -> Bool
$c== :: Batch -> Batch -> Bool
P.Eq,(forall x. Batch -> Rep Batch x)
-> (forall x. Rep Batch x -> Batch) -> Generic Batch
forall x. Rep Batch x -> Batch
forall x. Batch -> Rep Batch x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Batch x -> Batch
$cfrom :: forall x. Batch -> Rep Batch x
G.Generic,TY.Typeable)
instance H.Hashable Batch where
hashWithSalt :: Int -> Batch -> Int
hashWithSalt Int
salt Batch
record = Int
salt Int -> Process -> Int
forall a. Hashable a => Int -> a -> Int
`H.hashWithSalt` Batch -> Process
batch_process Batch
record Int -> Vector Span -> Int
forall a. Hashable a => Int -> a -> Int
`H.hashWithSalt` Batch -> Vector Span
batch_spans Batch
record
instance QC.Arbitrary Batch where
arbitrary :: Gen Batch
arbitrary = (Process -> Vector Span -> Batch)
-> Gen Process -> Gen (Vector Span -> Batch)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
M.liftM Process -> Vector Span -> Batch
Batch (Gen Process
forall a. Arbitrary a => Gen a
QC.arbitrary)
Gen (Vector Span -> Batch) -> Gen (Vector Span) -> Gen Batch
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`M.ap`(Gen (Vector Span)
forall a. Arbitrary a => Gen a
QC.arbitrary)
shrink :: Batch -> [Batch]
shrink Batch
obj | Batch
obj Batch -> Batch -> Bool
forall a. Eq a => a -> a -> Bool
== Batch
default_Batch = []
| Bool
P.otherwise = [Maybe Batch] -> [Batch]
forall a. [Maybe a] -> [a]
M.catMaybes
[ if Batch
obj Batch -> Batch -> Bool
forall a. Eq a => a -> a -> Bool
== Batch
default_Batch{batch_process :: Process
batch_process = Batch -> Process
batch_process Batch
obj} then Maybe Batch
forall a. Maybe a
P.Nothing else Batch -> Maybe Batch
forall a. a -> Maybe a
P.Just (Batch -> Maybe Batch) -> Batch -> Maybe Batch
forall a b. (a -> b) -> a -> b
$ Batch
default_Batch{batch_process :: Process
batch_process = Batch -> Process
batch_process Batch
obj}
, if Batch
obj Batch -> Batch -> Bool
forall a. Eq a => a -> a -> Bool
== Batch
default_Batch{batch_spans :: Vector Span
batch_spans = Batch -> Vector Span
batch_spans Batch
obj} then Maybe Batch
forall a. Maybe a
P.Nothing else Batch -> Maybe Batch
forall a. a -> Maybe a
P.Just (Batch -> Maybe Batch) -> Batch -> Maybe Batch
forall a b. (a -> b) -> a -> b
$ Batch
default_Batch{batch_spans :: Vector Span
batch_spans = Batch -> Vector Span
batch_spans Batch
obj}
]
from_Batch :: Batch -> T.ThriftVal
from_Batch :: Batch -> ThriftVal
from_Batch Batch
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
[ (\Process
_v74 -> (Int16, (Text, ThriftVal)) -> Maybe (Int16, (Text, ThriftVal))
forall a. a -> Maybe a
P.Just (Int16
1, (Text
"process",Process -> ThriftVal
from_Process Process
_v74))) (Process -> Maybe (Int16, (Text, ThriftVal)))
-> Process -> Maybe (Int16, (Text, ThriftVal))
forall a b. (a -> b) -> a -> b
$ Batch -> Process
batch_process Batch
record
, (\Vector Span
_v74 -> (Int16, (Text, ThriftVal)) -> Maybe (Int16, (Text, ThriftVal))
forall a. a -> Maybe a
P.Just (Int16
2, (Text
"spans",ThriftType -> [ThriftVal] -> ThriftVal
T.TList (TypeMap -> ThriftType
T.T_STRUCT TypeMap
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
_v76 -> Span -> ThriftVal
from_Span Span
_v76) ([Span] -> [ThriftVal]) -> [Span] -> [ThriftVal]
forall a b. (a -> b) -> a -> b
$ Vector Span -> [Span]
forall a. Vector a -> [a]
Vector.toList Vector Span
_v74))) (Vector Span -> Maybe (Int16, (Text, ThriftVal)))
-> Vector Span -> Maybe (Int16, (Text, ThriftVal))
forall a b. (a -> b) -> a -> b
$ Batch -> Vector Span
batch_spans Batch
record
]
write_Batch :: T.Protocol p => p -> Batch -> P.IO ()
write_Batch :: p -> Batch -> IO ()
write_Batch p
oprot Batch
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
$ Batch -> ThriftVal
from_Batch Batch
record
encode_Batch :: T.StatelessProtocol p => p -> Batch -> LBS.ByteString
encode_Batch :: p -> Batch -> ByteString
encode_Batch p
oprot Batch
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
$ Batch -> ThriftVal
from_Batch Batch
record
to_Batch :: T.ThriftVal -> Batch
to_Batch :: ThriftVal -> Batch
to_Batch (T.TStruct HashMap Int16 (Text, ThriftVal)
fields) = Batch :: Process -> Vector Span -> Batch
Batch{
batch_process :: Process
batch_process = Process
-> ((Text, ThriftVal) -> Process)
-> Maybe (Text, ThriftVal)
-> Process
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (String -> Process
forall a. HasCallStack => String -> a
P.error String
"Missing required field: process") (\(Text
_,ThriftVal
_val78) -> (case ThriftVal
_val78 of {T.TStruct HashMap Int16 (Text, ThriftVal)
_val79 -> (ThriftVal -> Process
to_Process (HashMap Int16 (Text, ThriftVal) -> ThriftVal
T.TStruct HashMap Int16 (Text, ThriftVal)
_val79)); ThriftVal
_ -> String -> Process
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),
batch_spans :: Vector Span
batch_spans = Vector Span
-> ((Text, ThriftVal) -> Vector Span)
-> Maybe (Text, ThriftVal)
-> Vector Span
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (String -> Vector Span
forall a. HasCallStack => String -> a
P.error String
"Missing required field: spans") (\(Text
_,ThriftVal
_val78) -> (case ThriftVal
_val78 of {T.TList ThriftType
_ [ThriftVal]
_val80 -> ([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
_v81 -> (case ThriftVal
_v81 of {T.TStruct HashMap Int16 (Text, ThriftVal)
_val82 -> (ThriftVal -> Span
to_Span (HashMap Int16 (Text, ThriftVal) -> ThriftVal
T.TStruct HashMap Int16 (Text, ThriftVal)
_val82)); ThriftVal
_ -> String -> Span
forall a. HasCallStack => String -> a
P.error String
"wrong type"})) [ThriftVal]
_val80); 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
2) HashMap Int16 (Text, ThriftVal)
fields)
}
to_Batch ThriftVal
_ = String -> Batch
forall a. HasCallStack => String -> a
P.error String
"not a struct"
read_Batch :: T.Protocol p => p -> P.IO Batch
read_Batch :: p -> IO Batch
read_Batch p
iprot = ThriftVal -> Batch
to_Batch (ThriftVal -> Batch) -> IO ThriftVal -> IO Batch
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_Batch)
decode_Batch :: T.StatelessProtocol p => p -> LBS.ByteString -> Batch
decode_Batch :: p -> ByteString -> Batch
decode_Batch p
iprot ByteString
bs = ThriftVal -> Batch
to_Batch (ThriftVal -> Batch) -> ThriftVal -> Batch
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_Batch) ByteString
bs
typemap_Batch :: T.TypeMap
typemap_Batch :: TypeMap
typemap_Batch = [(Int16, (Text, ThriftType))] -> TypeMap
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
Map.fromList [(Int16
1,(Text
"process",(TypeMap -> ThriftType
T.T_STRUCT TypeMap
typemap_Process))),(Int16
2,(Text
"spans",(ThriftType -> ThriftType
T.T_LIST (TypeMap -> ThriftType
T.T_STRUCT TypeMap
typemap_Span))))]
default_Batch :: Batch
default_Batch :: Batch
default_Batch = Batch :: Process -> Vector Span -> Batch
Batch{
batch_process :: Process
batch_process = Process
default_Process,
batch_spans :: Vector Span
batch_spans = Vector Span
forall a. Vector a
Vector.empty}
data BatchSubmitResponse = BatchSubmitResponse { BatchSubmitResponse -> Bool
batchSubmitResponse_ok :: P.Bool
} deriving (Int -> BatchSubmitResponse -> ShowS
[BatchSubmitResponse] -> ShowS
BatchSubmitResponse -> String
(Int -> BatchSubmitResponse -> ShowS)
-> (BatchSubmitResponse -> String)
-> ([BatchSubmitResponse] -> ShowS)
-> Show BatchSubmitResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchSubmitResponse] -> ShowS
$cshowList :: [BatchSubmitResponse] -> ShowS
show :: BatchSubmitResponse -> String
$cshow :: BatchSubmitResponse -> String
showsPrec :: Int -> BatchSubmitResponse -> ShowS
$cshowsPrec :: Int -> BatchSubmitResponse -> ShowS
P.Show,BatchSubmitResponse -> BatchSubmitResponse -> Bool
(BatchSubmitResponse -> BatchSubmitResponse -> Bool)
-> (BatchSubmitResponse -> BatchSubmitResponse -> Bool)
-> Eq BatchSubmitResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BatchSubmitResponse -> BatchSubmitResponse -> Bool
$c/= :: BatchSubmitResponse -> BatchSubmitResponse -> Bool
== :: BatchSubmitResponse -> BatchSubmitResponse -> Bool
$c== :: BatchSubmitResponse -> BatchSubmitResponse -> Bool
P.Eq,(forall x. BatchSubmitResponse -> Rep BatchSubmitResponse x)
-> (forall x. Rep BatchSubmitResponse x -> BatchSubmitResponse)
-> Generic BatchSubmitResponse
forall x. Rep BatchSubmitResponse x -> BatchSubmitResponse
forall x. BatchSubmitResponse -> Rep BatchSubmitResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BatchSubmitResponse x -> BatchSubmitResponse
$cfrom :: forall x. BatchSubmitResponse -> Rep BatchSubmitResponse x
G.Generic,TY.Typeable)
instance H.Hashable BatchSubmitResponse where
hashWithSalt :: Int -> BatchSubmitResponse -> Int
hashWithSalt Int
salt BatchSubmitResponse
record = Int
salt Int -> Bool -> Int
forall a. Hashable a => Int -> a -> Int
`H.hashWithSalt` BatchSubmitResponse -> Bool
batchSubmitResponse_ok BatchSubmitResponse
record
instance QC.Arbitrary BatchSubmitResponse where
arbitrary :: Gen BatchSubmitResponse
arbitrary = (Bool -> BatchSubmitResponse)
-> Gen Bool -> Gen BatchSubmitResponse
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
M.liftM Bool -> BatchSubmitResponse
BatchSubmitResponse (Gen Bool
forall a. Arbitrary a => Gen a
QC.arbitrary)
shrink :: BatchSubmitResponse -> [BatchSubmitResponse]
shrink BatchSubmitResponse
obj | BatchSubmitResponse
obj BatchSubmitResponse -> BatchSubmitResponse -> Bool
forall a. Eq a => a -> a -> Bool
== BatchSubmitResponse
default_BatchSubmitResponse = []
| Bool
P.otherwise = [Maybe BatchSubmitResponse] -> [BatchSubmitResponse]
forall a. [Maybe a] -> [a]
M.catMaybes
[ if BatchSubmitResponse
obj BatchSubmitResponse -> BatchSubmitResponse -> Bool
forall a. Eq a => a -> a -> Bool
== BatchSubmitResponse
default_BatchSubmitResponse{batchSubmitResponse_ok :: Bool
batchSubmitResponse_ok = BatchSubmitResponse -> Bool
batchSubmitResponse_ok BatchSubmitResponse
obj} then Maybe BatchSubmitResponse
forall a. Maybe a
P.Nothing else BatchSubmitResponse -> Maybe BatchSubmitResponse
forall a. a -> Maybe a
P.Just (BatchSubmitResponse -> Maybe BatchSubmitResponse)
-> BatchSubmitResponse -> Maybe BatchSubmitResponse
forall a b. (a -> b) -> a -> b
$ BatchSubmitResponse
default_BatchSubmitResponse{batchSubmitResponse_ok :: Bool
batchSubmitResponse_ok = BatchSubmitResponse -> Bool
batchSubmitResponse_ok BatchSubmitResponse
obj}
]
from_BatchSubmitResponse :: BatchSubmitResponse -> T.ThriftVal
from_BatchSubmitResponse :: BatchSubmitResponse -> ThriftVal
from_BatchSubmitResponse BatchSubmitResponse
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
[ (\Bool
_v85 -> (Int16, (Text, ThriftVal)) -> Maybe (Int16, (Text, ThriftVal))
forall a. a -> Maybe a
P.Just (Int16
1, (Text
"ok",Bool -> ThriftVal
T.TBool Bool
_v85))) (Bool -> Maybe (Int16, (Text, ThriftVal)))
-> Bool -> Maybe (Int16, (Text, ThriftVal))
forall a b. (a -> b) -> a -> b
$ BatchSubmitResponse -> Bool
batchSubmitResponse_ok BatchSubmitResponse
record
]
write_BatchSubmitResponse :: T.Protocol p => p -> BatchSubmitResponse -> P.IO ()
write_BatchSubmitResponse :: p -> BatchSubmitResponse -> IO ()
write_BatchSubmitResponse p
oprot BatchSubmitResponse
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
$ BatchSubmitResponse -> ThriftVal
from_BatchSubmitResponse BatchSubmitResponse
record
encode_BatchSubmitResponse :: T.StatelessProtocol p => p -> BatchSubmitResponse -> LBS.ByteString
encode_BatchSubmitResponse :: p -> BatchSubmitResponse -> ByteString
encode_BatchSubmitResponse p
oprot BatchSubmitResponse
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
$ BatchSubmitResponse -> ThriftVal
from_BatchSubmitResponse BatchSubmitResponse
record
to_BatchSubmitResponse :: T.ThriftVal -> BatchSubmitResponse
to_BatchSubmitResponse :: ThriftVal -> BatchSubmitResponse
to_BatchSubmitResponse (T.TStruct HashMap Int16 (Text, ThriftVal)
fields) = BatchSubmitResponse :: Bool -> BatchSubmitResponse
BatchSubmitResponse{
batchSubmitResponse_ok :: Bool
batchSubmitResponse_ok = Bool
-> ((Text, ThriftVal) -> Bool) -> Maybe (Text, ThriftVal) -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (String -> Bool
forall a. HasCallStack => String -> a
P.error String
"Missing required field: ok") (\(Text
_,ThriftVal
_val87) -> (case ThriftVal
_val87 of {T.TBool Bool
_val88 -> Bool
_val88; ThriftVal
_ -> String -> Bool
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_BatchSubmitResponse ThriftVal
_ = String -> BatchSubmitResponse
forall a. HasCallStack => String -> a
P.error String
"not a struct"
read_BatchSubmitResponse :: T.Protocol p => p -> P.IO BatchSubmitResponse
read_BatchSubmitResponse :: p -> IO BatchSubmitResponse
read_BatchSubmitResponse p
iprot = ThriftVal -> BatchSubmitResponse
to_BatchSubmitResponse (ThriftVal -> BatchSubmitResponse)
-> IO ThriftVal -> IO BatchSubmitResponse
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_BatchSubmitResponse)
decode_BatchSubmitResponse :: T.StatelessProtocol p => p -> LBS.ByteString -> BatchSubmitResponse
decode_BatchSubmitResponse :: p -> ByteString -> BatchSubmitResponse
decode_BatchSubmitResponse p
iprot ByteString
bs = ThriftVal -> BatchSubmitResponse
to_BatchSubmitResponse (ThriftVal -> BatchSubmitResponse)
-> ThriftVal -> BatchSubmitResponse
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_BatchSubmitResponse) ByteString
bs
typemap_BatchSubmitResponse :: T.TypeMap
typemap_BatchSubmitResponse :: TypeMap
typemap_BatchSubmitResponse = [(Int16, (Text, ThriftType))] -> TypeMap
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
Map.fromList [(Int16
1,(Text
"ok",ThriftType
T.T_BOOL))]
default_BatchSubmitResponse :: BatchSubmitResponse
default_BatchSubmitResponse :: BatchSubmitResponse
default_BatchSubmitResponse = BatchSubmitResponse :: Bool -> BatchSubmitResponse
BatchSubmitResponse{
batchSubmitResponse_ok :: Bool
batchSubmitResponse_ok = Bool
P.False}