Adapting Store binary serialization decoding for streaming library

20 views
Skip to first unread message

Sal

unread,
Mar 12, 2018, 10:22:55 PM3/12/18
to Haskell Pipes
I posted this to stack overflow in case anyone might be able to help answer it there. The problem that I am trying to solve is how to adapt the following decoding API from Store to `Streaming` library:
decodeMessageBS :: (MonadIO m, Store a) => ByteBuffer -> m (Maybe ByteString) -> m (Maybe (Message a))

I took a shot at it with the code below but am not able to figure it out yet - there are some undefined statements in the code below btw as placeholders - perhaps, there also exists a simpler and efficient way to adapt `decodeMessageBS` to `Streaming`:

{-# LANGUAGE OverloadedStrings,ScopedTypeVariables #-}
import           Data.ByteString (ByteString)
import           System.IO.ByteBuffer (ByteBuffer)
import qualified System.IO.ByteBuffer as BB
import Data.Store.Streaming
import Data.Store (Store)
import Streaming.Prelude as S
import Data.IORef

streamDecodeH :: forall a r. (Store a) => ByteBuffer -> Stream (Of ByteString) IO r -> Stream (Of (Message a)) IO r
streamDecodeH bb inp = do
    ref <- newIORef inp 
    go (popper ref)
    undefined
  where
    go src = do
      r <- (decodeMessageBS :: ByteBuffer -> IO (Maybe ByteString) -> IO (Maybe (Message a))) bb src
      case r of 
        Nothing -> undefined
        Just msg -> (S.yield :: Message a -> Stream (Of (Message a)) IO ()) msg >> go src

    popper :: IORef (Stream (Of ByteString) IO r) -> IO (Maybe ByteString)
    popper ref = do
      chunks <- readIORef ref
      r <- S.uncons chunks
      case r of
        Nothing -> return Nothing
        Just (a,rest) -> writeIORef ref rest >> return (Just a)

Will appreciate help with it, either here or at StackOverflow.
Reply all
Reply to author
Forward
0 new messages