{-# LANGUAGE BangPatterns, DeriveDataTypeable, DeriveGeneric,
  FlexibleInstances, MultiParamTypeClasses #-}

module Network.Monitoring.Riemann.Proto.Query
  ( Query(..)
  ) where

import qualified Data.Data as Prelude'
import qualified GHC.Generics as Prelude'
import qualified Prelude as Prelude'
import qualified Text.ProtocolBuffers.Header as P'

newtype Query = Query
  { Query -> Maybe Utf8
string :: P'.Maybe P'.Utf8
  } deriving ( Int -> Query -> ShowS
[Query] -> ShowS
Query -> String
(Int -> Query -> ShowS)
-> (Query -> String) -> ([Query] -> ShowS) -> Show Query
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Query] -> ShowS
$cshowList :: [Query] -> ShowS
show :: Query -> String
$cshow :: Query -> String
showsPrec :: Int -> Query -> ShowS
$cshowsPrec :: Int -> Query -> ShowS
Prelude'.Show
             , Query -> Query -> Bool
(Query -> Query -> Bool) -> (Query -> Query -> Bool) -> Eq Query
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Query -> Query -> Bool
$c/= :: Query -> Query -> Bool
== :: Query -> Query -> Bool
$c== :: Query -> Query -> Bool
Prelude'.Eq
             , Eq Query
Eq Query
-> (Query -> Query -> Ordering)
-> (Query -> Query -> Bool)
-> (Query -> Query -> Bool)
-> (Query -> Query -> Bool)
-> (Query -> Query -> Bool)
-> (Query -> Query -> Query)
-> (Query -> Query -> Query)
-> Ord Query
Query -> Query -> Bool
Query -> Query -> Ordering
Query -> Query -> Query
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 :: Query -> Query -> Query
$cmin :: Query -> Query -> Query
max :: Query -> Query -> Query
$cmax :: Query -> Query -> Query
>= :: Query -> Query -> Bool
$c>= :: Query -> Query -> Bool
> :: Query -> Query -> Bool
$c> :: Query -> Query -> Bool
<= :: Query -> Query -> Bool
$c<= :: Query -> Query -> Bool
< :: Query -> Query -> Bool
$c< :: Query -> Query -> Bool
compare :: Query -> Query -> Ordering
$ccompare :: Query -> Query -> Ordering
$cp1Ord :: Eq Query
Prelude'.Ord
             , Prelude'.Typeable
             , Typeable Query
DataType
Constr
Typeable Query
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Query -> c Query)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Query)
-> (Query -> Constr)
-> (Query -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Query))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Query))
-> ((forall b. Data b => b -> b) -> Query -> Query)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Query -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Query -> r)
-> (forall u. (forall d. Data d => d -> u) -> Query -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Query -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Query -> m Query)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Query -> m Query)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Query -> m Query)
-> Data Query
Query -> DataType
Query -> Constr
(forall b. Data b => b -> b) -> Query -> Query
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Query -> c Query
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Query
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Query -> u
forall u. (forall d. Data d => d -> u) -> Query -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Query -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Query -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Query -> m Query
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Query -> m Query
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Query
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Query -> c Query
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Query)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Query)
$cQuery :: Constr
$tQuery :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Query -> m Query
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Query -> m Query
gmapMp :: (forall d. Data d => d -> m d) -> Query -> m Query
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Query -> m Query
gmapM :: (forall d. Data d => d -> m d) -> Query -> m Query
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Query -> m Query
gmapQi :: Int -> (forall d. Data d => d -> u) -> Query -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Query -> u
gmapQ :: (forall d. Data d => d -> u) -> Query -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Query -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Query -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Query -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Query -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Query -> r
gmapT :: (forall b. Data b => b -> b) -> Query -> Query
$cgmapT :: (forall b. Data b => b -> b) -> Query -> Query
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Query)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Query)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Query)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Query)
dataTypeOf :: Query -> DataType
$cdataTypeOf :: Query -> DataType
toConstr :: Query -> Constr
$ctoConstr :: Query -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Query
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Query
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Query -> c Query
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Query -> c Query
$cp1Data :: Typeable Query
Prelude'.Data
             , (forall x. Query -> Rep Query x)
-> (forall x. Rep Query x -> Query) -> Generic Query
forall x. Rep Query x -> Query
forall x. Query -> Rep Query x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Query x -> Query
$cfrom :: forall x. Query -> Rep Query x
Prelude'.Generic
             )

instance P'.Mergeable Query where
  mergeAppend :: Query -> Query -> Query
mergeAppend (Query Maybe Utf8
x'1) (Query Maybe Utf8
y'1) = Maybe Utf8 -> Query
Query (Maybe Utf8 -> Maybe Utf8 -> Maybe Utf8
forall a. Mergeable a => a -> a -> a
P'.mergeAppend Maybe Utf8
x'1 Maybe Utf8
y'1)

instance P'.Default Query where
  defaultValue :: Query
defaultValue = Maybe Utf8 -> Query
Query Maybe Utf8
forall a. Default a => a
P'.defaultValue

instance P'.Wire Query where
  wireSize :: FieldType -> Query -> WireSize
wireSize FieldType
ft' self' :: Query
self'@(Query Maybe Utf8
x'1) =
    case FieldType
ft' of
      FieldType
10 -> WireSize
calc'Size
      FieldType
11 -> WireSize -> WireSize
P'.prependMessageSize WireSize
calc'Size
      FieldType
_ -> FieldType -> Query -> WireSize
forall a. Typeable a => FieldType -> a -> WireSize
P'.wireSizeErr FieldType
ft' Query
self'
    where
      calc'Size :: WireSize
calc'Size = WireSize -> FieldType -> Maybe Utf8 -> WireSize
forall v. Wire v => WireSize -> FieldType -> Maybe v -> WireSize
P'.wireSizeOpt WireSize
1 FieldType
9 Maybe Utf8
x'1
  wirePut :: FieldType -> Query -> Put
wirePut FieldType
ft' self' :: Query
self'@(Query Maybe Utf8
x'1) =
    case FieldType
ft' of
      FieldType
10 -> Put
put'Fields
      FieldType
11 -> do
        WireSize -> Put
P'.putSize (FieldType -> Query -> WireSize
forall b. Wire b => FieldType -> b -> WireSize
P'.wireSize FieldType
10 Query
self')
        Put
put'Fields
      FieldType
_ -> FieldType -> Query -> Put
forall a b. Typeable a => FieldType -> a -> PutM b
P'.wirePutErr FieldType
ft' Query
self'
    where
      put'Fields :: Put
put'Fields = WireTag -> FieldType -> Maybe Utf8 -> Put
forall v. Wire v => WireTag -> FieldType -> Maybe v -> Put
P'.wirePutOpt WireTag
10 FieldType
9 Maybe Utf8
x'1
  wireGet :: FieldType -> Get Query
wireGet FieldType
ft' =
    case FieldType
ft' of
      FieldType
10 -> (WireTag -> Query -> Get Query) -> Get Query
forall message.
(Default message, ReflectDescriptor message) =>
(WireTag -> message -> Get message) -> Get message
P'.getBareMessageWith WireTag -> Query -> Get Query
update'Self
      FieldType
11 -> (WireTag -> Query -> Get Query) -> Get Query
forall message.
(Default message, ReflectDescriptor message) =>
(WireTag -> message -> Get message) -> Get message
P'.getMessageWith WireTag -> Query -> Get Query
update'Self
      FieldType
_ -> FieldType -> Get Query
forall a. Typeable a => FieldType -> Get a
P'.wireGetErr FieldType
ft'
    where
      update'Self :: WireTag -> Query -> Get Query
update'Self WireTag
wire'Tag Query
old'Self =
        case WireTag
wire'Tag of
          WireTag
10 ->
            (Utf8 -> Query) -> Get Utf8 -> Get Query
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude'.fmap
              (\ !Utf8
new'Field -> Query
old'Self {string :: Maybe Utf8
string = Utf8 -> Maybe Utf8
forall a. a -> Maybe a
Prelude'.Just Utf8
new'Field})
              (FieldType -> Get Utf8
forall b. Wire b => FieldType -> Get b
P'.wireGet FieldType
9)
          WireTag
_ ->
            let (FieldId
field'Number, WireType
wire'Type) = WireTag -> (FieldId, WireType)
P'.splitWireTag WireTag
wire'Tag
             in FieldId -> WireType -> Query -> Get Query
forall a.
(Typeable a, ReflectDescriptor a) =>
FieldId -> WireType -> a -> Get a
P'.unknown FieldId
field'Number WireType
wire'Type Query
old'Self

instance P'.MessageAPI msg' (msg' -> Query) Query where
  getVal :: msg' -> (msg' -> Query) -> Query
getVal msg'
m' msg' -> Query
f' = msg' -> Query
f' msg'
m'

instance P'.GPB Query

instance P'.ReflectDescriptor Query where
  getMessageInfo :: Query -> GetMessageInfo
getMessageInfo Query
_ =
    Set WireTag -> Set WireTag -> GetMessageInfo
P'.GetMessageInfo ([WireTag] -> Set WireTag
forall a. [a] -> Set a
P'.fromDistinctAscList []) ([WireTag] -> Set WireTag
forall a. [a] -> Set a
P'.fromDistinctAscList [WireTag
10])
  reflectDescriptorInfo :: Query -> DescriptorInfo
reflectDescriptorInfo Query
_ =
    String -> DescriptorInfo
forall a. Read a => String -> a
Prelude'.read
      String
"DescriptorInfo {descName = ProtoName {protobufName = FIName \".Proto.Query\", haskellPrefix = [MName \"Network\",MName \"Monitoring\",MName \"Riemann\"], parentModule = [MName \"Proto\"], baseName = MName \"Query\"}, descFilePath = [\"Network\",\"Monitoring\",\"Riemann\",\"Proto\",\"Query.hs\"], isGroup = False, fields = fromList [FieldInfo {fieldName = ProtoFName {protobufName' = FIName \".Proto.Query.string\", haskellPrefix' = [MName \"Network\",MName \"Monitoring\",MName \"Riemann\"], parentModule' = [MName \"Proto\",MName \"Query\"], baseName' = FName \"string\", baseNamePrefix' = \"\"}, fieldNumber = FieldId {getFieldId = 1}, wireTag = WireTag {getWireTag = 10}, packedTag = Nothing, wireTagLength = 1, isPacked = False, isRequired = False, canRepeat = False, mightPack = False, typeCode = FieldType {getFieldType = 9}, typeName = Nothing, hsRawDefault = Nothing, hsDefault = Nothing}], descOneofs = fromList [], keys = fromList [], extRanges = [], knownKeys = fromList [], storeUnknown = False, lazyFields = False, makeLenses = False}"

instance P'.TextType Query where
  tellT :: String -> Query -> Output
tellT = String -> Query -> Output
forall a. TextMsg a => String -> a -> Output
P'.tellSubMessage
  getT :: String -> Parsec s () Query
getT = String -> Parsec s () Query
forall s a.
(Stream s Identity Char, TextMsg a) =>
String -> Parsec s () a
P'.getSubMessage

instance P'.TextMsg Query where
  textPut :: Query -> Output
textPut Query
msg = String -> Maybe Utf8 -> Output
forall a. TextType a => String -> a -> Output
P'.tellT String
"string" (Query -> Maybe Utf8
string Query
msg)
  textGet :: Parsec s () Query
textGet = do
    [Query -> Query]
mods <- ParsecT s () Identity (Query -> Query)
-> ParsecT s () Identity ()
-> ParsecT s () Identity [Query -> Query]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
P'.sepEndBy ([ParsecT s () Identity (Query -> Query)]
-> ParsecT s () Identity (Query -> Query)
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
P'.choice [ParsecT s () Identity (Query -> Query)
parse'string]) ParsecT s () Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
P'.spaces
    Query -> Parsec s () Query
forall (m :: * -> *) a. Monad m => a -> m a
Prelude'.return ((Query -> (Query -> Query) -> Query)
-> Query -> [Query -> Query] -> Query
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
Prelude'.foldl (\Query
v Query -> Query
f -> Query -> Query
f Query
v) Query
forall a. Default a => a
P'.defaultValue [Query -> Query]
mods)
    where
      parse'string :: ParsecT s () Identity (Query -> Query)
parse'string =
        ParsecT s () Identity (Query -> Query)
-> ParsecT s () Identity (Query -> Query)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
P'.try
          (do Maybe Utf8
v <- String -> Parsec s () (Maybe Utf8)
forall a s.
(TextType a, Stream s Identity Char) =>
String -> Parsec s () a
P'.getT String
"string"
              (Query -> Query) -> ParsecT s () Identity (Query -> Query)
forall (m :: * -> *) a. Monad m => a -> m a
Prelude'.return (\Query
o -> Query
o {string :: Maybe Utf8
string = Maybe Utf8
v}))