Skip to content

Commit 2ace3fc

Browse files
author
Philipp Hausmann
committed
Use ByteString instead of String for stats callback
This avoids the round-trip via String if one wants to pass the statistics JSON to aeson for further parsing.
1 parent 18be9e6 commit 2ace3fc

File tree

2 files changed

+8
-5
lines changed

2 files changed

+8
-5
lines changed

src/Kafka/Callbacks.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,7 @@ module Kafka.Callbacks
55
)
66
where
77

8+
import Data.ByteString (ByteString)
89
import Kafka.Internal.RdKafka (rdKafkaConfSetErrorCb, rdKafkaConfSetLogCb, rdKafkaConfSetStatsCb)
910
import Kafka.Internal.Setup (HasKafkaConf(..), getRdKafkaConf)
1011
import Kafka.Types (KafkaError(..), KafkaLogLevel(..))
@@ -39,7 +40,7 @@ logCallback callback k =
3940
let realCb _ = callback . toEnum
4041
in rdKafkaConfSetLogCb (getRdKafkaConf k) realCb
4142

42-
-- | Add a callback for stats.
43+
-- | Add a callback for stats. The passed ByteString contains an UTF-8 encoded JSON document and can e.g. be parsed using Data.Aeson.decodeStrict. For more information about the content of the JSON document see <https://github.com/edenhill/librdkafka/blob/master/STATISTICS.md>.
4344
--
4445
-- ==== __Examples__
4546
--
@@ -49,7 +50,7 @@ logCallback callback k =
4950
-- >
5051
-- > myStatsCallback :: String -> IO ()
5152
-- > myStatsCallback stats = print $ show stats
52-
statsCallback :: HasKafkaConf k => (String -> IO ()) -> k -> IO ()
53+
statsCallback :: HasKafkaConf k => (ByteString -> IO ()) -> k -> IO ()
5354
statsCallback callback k =
5455
let realCb _ = callback
5556
in rdKafkaConfSetStatsCb (getRdKafkaConf k) realCb

src/Kafka/Internal/RdKafka.chs

Lines changed: 5 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,8 @@
33

44
module Kafka.Internal.RdKafka where
55

6+
import Data.ByteString (ByteString)
7+
import qualified Data.ByteString as BS
68
import Data.Text (Text)
79
import qualified Data.Text as Text
810
import Control.Monad (liftM)
@@ -15,7 +17,7 @@ import Foreign.Storable (Storable(..))
1517
import Foreign.Ptr (Ptr, FunPtr, castPtr, nullPtr)
1618
import Foreign.ForeignPtr (FinalizerPtr, addForeignPtrFinalizer, newForeignPtr_, withForeignPtr)
1719
import Foreign.C.Error (Errno(..), getErrno)
18-
import Foreign.C.String (CString, newCString, withCAString, peekCAString, peekCAStringLen, peekCString)
20+
import Foreign.C.String (CString, newCString, withCAString, peekCAString, peekCString)
1921
import Foreign.C.Types (CFile, CInt(..), CSize, CChar)
2022
import System.IO (Handle, stdin, stdout, stderr)
2123
import System.Posix.IO (handleToFd)
@@ -414,7 +416,7 @@ rdKafkaConfSetLogCb conf cb = do
414416

415417
---- Stats Callback
416418
type StatsCallback' = Ptr RdKafkaT -> CString -> CSize -> Word8Ptr -> IO ()
417-
type StatsCallback = Ptr RdKafkaT -> String -> IO ()
419+
type StatsCallback = Ptr RdKafkaT -> ByteString -> IO ()
418420

419421
foreign import ccall safe "wrapper"
420422
mkStatsCallback :: StatsCallback' -> IO (FunPtr StatsCallback')
@@ -424,7 +426,7 @@ foreign import ccall safe "rd_kafka.h rd_kafka_conf_set_stats_cb"
424426

425427
rdKafkaConfSetStatsCb :: RdKafkaConfTPtr -> StatsCallback -> IO ()
426428
rdKafkaConfSetStatsCb conf cb = do
427-
cb' <- mkStatsCallback $ \k j jl _ -> peekCAStringLen (j, cIntConv jl) >>= cb k
429+
cb' <- mkStatsCallback $ \k j jl _ -> BS.packCStringLen (j, cIntConv jl) >>= cb k
428430
withForeignPtr conf $ \c -> rdKafkaConfSetStatsCb' c cb'
429431
return ()
430432

0 commit comments

Comments
 (0)