{-# language BangPatterns #-}
{-# language DerivingStrategies #-}
{-# language DuplicateRecordFields #-}
{-# language NamedFieldPuns #-}

module Kafka.Heartbeat.Response.V4
  ( Response(..)
  , parser
  , decode
  ) where

import Prelude hiding (id)

import Control.Applicative (liftA2)
import Data.Bytes (Bytes)
import Data.Bytes.Parser (Parser)
import Data.Int (Int16,Int32,Int64)
import Data.Primitive (SmallArray)
import Kafka.ErrorCode (ErrorCode)
import Kafka.Parser.Context (Context)
import Kafka.TaggedField (TaggedField)

import qualified Data.Bytes.Parser as Parser
import qualified Kafka.Parser.Context as Ctx
import qualified Kafka.TaggedField as TaggedField
import qualified Kafka.Parser

data Response = Response
  { Response -> Int32
throttleTimeMilliseconds :: !Int32
  , Response -> ErrorCode
errorCode :: !ErrorCode
  , Response -> SmallArray TaggedField
taggedFields :: !(SmallArray TaggedField)
  } deriving stock (Int -> Response -> ShowS
[Response] -> ShowS
Response -> String
(Int -> Response -> ShowS)
-> (Response -> String) -> ([Response] -> ShowS) -> Show Response
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Response -> ShowS
showsPrec :: Int -> Response -> ShowS
$cshow :: Response -> String
show :: Response -> String
$cshowList :: [Response] -> ShowS
showList :: [Response] -> ShowS
Show)

decode :: Bytes -> Either Context Response
decode :: Bytes -> Either Context Response
decode !Bytes
b = (forall s. Parser Context s Response)
-> Bytes -> Either Context Response
forall e a. (forall s. Parser e s a) -> Bytes -> Either e a
Parser.parseBytesEither (Context -> Parser Context s Response
forall s. Context -> Parser Context s Response
parser Context
Ctx.Top Parser Context s Response
-> Parser Context s () -> Parser Context s Response
forall a b.
Parser Context s a -> Parser Context s b -> Parser Context s a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Context -> Parser Context s ()
forall e s. e -> Parser e s ()
Parser.endOfInput Context
Ctx.End) Bytes
b

parser :: Context -> Parser Context s Response
parser :: forall s. Context -> Parser Context s Response
parser Context
ctx = do
  Int32
throttleTimeMilliseconds <- Context -> Parser Context s Int32
forall e s. e -> Parser e s Int32
Kafka.Parser.int32 (Field -> Context -> Context
Ctx.Field Field
Ctx.ThrottleTimeMilliseconds Context
ctx)
  ErrorCode
errorCode <- Context -> Parser Context s ErrorCode
forall e s. e -> Parser e s ErrorCode
Kafka.Parser.errorCode (Field -> Context -> Context
Ctx.Field Field
Ctx.ErrorCode Context
ctx)
  SmallArray TaggedField
taggedFields <- Context -> Parser Context s (SmallArray TaggedField)
forall s. Context -> Parser Context s (SmallArray TaggedField)
TaggedField.parserMany (Field -> Context -> Context
Ctx.Field Field
Ctx.TagBuffer Context
ctx)
  Response -> Parser Context s Response
forall a. a -> Parser Context s a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Response{Int32
$sel:throttleTimeMilliseconds:Response :: Int32
throttleTimeMilliseconds :: Int32
throttleTimeMilliseconds,ErrorCode
$sel:errorCode:Response :: ErrorCode
errorCode :: ErrorCode
errorCode,SmallArray TaggedField
$sel:taggedFields:Response :: SmallArray TaggedField
taggedFields :: SmallArray TaggedField
taggedFields}