{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module Thrift.Transport.Framed
    ( module Thrift.Transport
    , FramedTransport
    , openFramedTransport
    ) where
import Thrift.Transport
import Thrift.Transport.IOBuffer
import Data.Int (Int32)
import qualified Data.Binary as B
import qualified Data.ByteString.Lazy as LBS
data FramedTransport t = FramedTransport {
      wrappedTrans :: t,           
      writeBuffer  :: WriteBuffer, 
      readBuffer   :: ReadBuffer   
    }
openFramedTransport :: Transport t => t -> IO (FramedTransport t)
openFramedTransport trans = do
  wbuf <- newWriteBuffer
  rbuf <- newReadBuffer
  return FramedTransport{ wrappedTrans = trans, writeBuffer = wbuf, readBuffer = rbuf }
instance Transport t => Transport (FramedTransport t) where
    tClose = tClose . wrappedTrans
    tRead trans n = do
      
      bs <- readBuf (readBuffer trans) n
      if LBS.null bs
         then
         
         
           do len <- readFrame trans
              if len > 0
                 then tRead trans n
                 else return bs
         else return bs
    tPeek trans = do
      mw <- peekBuf (readBuffer trans)
      case mw of
        Just _ -> return mw
        Nothing -> do
          len <- readFrame trans
          if len > 0
             then tPeek trans
             else return Nothing
    tWrite = writeBuf . writeBuffer
    tFlush trans = do
      bs <- flushBuf (writeBuffer trans)
      let szBs = B.encode $ (fromIntegral $ LBS.length bs :: Int32)
      tWrite (wrappedTrans trans) szBs
      tWrite (wrappedTrans trans) bs
      tFlush (wrappedTrans trans)
    tIsOpen = tIsOpen . wrappedTrans
readFrame :: Transport t => FramedTransport t -> IO Int
readFrame trans = do
  
  szBs <- tRead (wrappedTrans trans) 4
  let sz = fromIntegral (B.decode szBs :: Int32)
  
  bs <- tRead (wrappedTrans trans) sz
  fillBuf (readBuffer trans) bs
  
  
  return sz