{-# LANGUAGE RankNTypes #-}

module Pinch.Transport
  ( Transport(..)
  , framedTransport
  , unframedTransport
  , Connection(..)
  , ReadResult(..)
  ) where

import Data.IORef (newIORef, readIORef, writeIORef)
import Network.Socket (Socket)
import Network.Socket.ByteString (sendAll, recv)
import System.IO (Handle)

import qualified Data.ByteString as BS
import qualified Data.Serialize.Get as G

import qualified Pinch.Internal.Builder as B

class Connection c where
  -- | Returns available bytes, or an empty bytestring if EOF was reached.
  cGetSome :: c -> IO BS.ByteString
  -- | Writes the given builder.
  cPut :: c -> B.Builder -> IO ()

instance Connection Handle where
  cPut :: Handle -> Builder -> IO ()
cPut Handle
c Builder
b = Handle -> ByteString -> IO ()
BS.hPut Handle
c (Builder -> ByteString
B.runBuilder Builder
b)
  cGetSome :: Handle -> IO ByteString
cGetSome Handle
h = Handle -> Int -> IO ByteString
BS.hGetSome Handle
h Int
1024

instance Connection Socket where
  cPut :: Socket -> Builder -> IO ()
cPut Socket
c Builder
b = Socket -> ByteString -> IO ()
sendAll Socket
c (Builder -> ByteString
B.runBuilder Builder
b)
  cGetSome :: Socket -> IO ByteString
cGetSome Socket
s = Socket -> Int -> IO ByteString
recv Socket
s Int
4096

data ReadResult a
  = RRSuccess a
  | RRFailure String
  | RREOF
  deriving (ReadResult a -> ReadResult a -> Bool
forall a. Eq a => ReadResult a -> ReadResult a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReadResult a -> ReadResult a -> Bool
$c/= :: forall a. Eq a => ReadResult a -> ReadResult a -> Bool
== :: ReadResult a -> ReadResult a -> Bool
$c== :: forall a. Eq a => ReadResult a -> ReadResult a -> Bool
Eq, Int -> ReadResult a -> ShowS
forall a. Show a => Int -> ReadResult a -> ShowS
forall a. Show a => [ReadResult a] -> ShowS
forall a. Show a => ReadResult a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReadResult a] -> ShowS
$cshowList :: forall a. Show a => [ReadResult a] -> ShowS
show :: ReadResult a -> String
$cshow :: forall a. Show a => ReadResult a -> String
showsPrec :: Int -> ReadResult a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> ReadResult a -> ShowS
Show)

-- | A bidirectional transport to read/write messages from/to.
data Transport
  = Transport
  { Transport -> Builder -> IO ()
writeMessage :: B.Builder -> IO ()
  , Transport -> forall a. Get a -> IO (ReadResult a)
readMessage  :: forall a . G.Get a -> IO (ReadResult a)
  }

-- | Creates a thrift framed transport. See also <https://github.com/apache/thrift/blob/master/doc/specs/thrift-rpc.md#framed-vs-unframed-transport>.
framedTransport :: Connection c => c -> IO Transport
framedTransport :: forall c. Connection c => c -> IO Transport
framedTransport c
c = do
  IORef ByteString
readBuffer <- forall a. a -> IO (IORef a)
newIORef forall a. Monoid a => a
mempty
  forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ (Builder -> IO ())
-> (forall a. Get a -> IO (ReadResult a)) -> Transport
Transport Builder -> IO ()
writeMsg (forall {a}. IORef ByteString -> Get a -> IO (ReadResult a)
readMsg IORef ByteString
readBuffer) where
  writeMsg :: Builder -> IO ()
writeMsg Builder
msg = do
    forall c. Connection c => c -> Builder -> IO ()
cPut c
c forall a b. (a -> b) -> a -> b
$ Int32 -> Builder
B.int32BE (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ Builder -> Int
B.getSize Builder
msg) forall a. Semigroup a => a -> a -> a
<> Builder
msg
  readMsg :: IORef ByteString -> Get a -> IO (ReadResult a)
readMsg IORef ByteString
readBuffer Get a
parser = do
    let 
      frameParser :: Get a
frameParser = do 
        Int32
size <- Get Int32
G.getInt32be
        forall a. Int -> Get a -> Get a
G.isolate (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
size) Get a
parser
    
    ByteString
initial <- forall a. IORef a -> IO a
readIORef IORef ByteString
readBuffer
    (ByteString
leftovers, ReadResult a
r) <- forall a.
IO ByteString
-> Get a -> ByteString -> IO (ByteString, ReadResult a)
runGetWith (forall c. Connection c => c -> IO ByteString
cGetSome c
c) Get a
frameParser ByteString
initial
    forall a. IORef a -> a -> IO ()
writeIORef IORef ByteString
readBuffer forall a b. (a -> b) -> a -> b
$! ByteString
leftovers
    forall (f :: * -> *) a. Applicative f => a -> f a
pure ReadResult a
r

-- | Creates a thrift unframed transport. See also <https://github.com/apache/thrift/blob/master/doc/specs/thrift-rpc.md#framed-vs-unframed-transport>.
unframedTransport :: Connection c => c -> IO Transport
unframedTransport :: forall c. Connection c => c -> IO Transport
unframedTransport c
c = do
  -- As we do not know how long messages are,
  -- we may read more data then the current message needs.
  -- We keep the leftovers in a buffer so that we may use them
  -- when reading the next message.
  IORef ByteString
readBuffer <- forall a. a -> IO (IORef a)
newIORef forall a. Monoid a => a
mempty
  forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ (Builder -> IO ())
-> (forall a. Get a -> IO (ReadResult a)) -> Transport
Transport Builder -> IO ()
writeMsg (forall {a}. IORef ByteString -> Get a -> IO (ReadResult a)
readMsg IORef ByteString
readBuffer)
  where
    writeMsg :: Builder -> IO ()
writeMsg = forall c. Connection c => c -> Builder -> IO ()
cPut c
c

    readMsg :: IORef ByteString -> Get a -> IO (ReadResult a)
readMsg IORef ByteString
buf Get a
p = do
      ByteString
initial <- forall a. IORef a -> IO a
readIORef IORef ByteString
buf
      (ByteString
leftovers, ReadResult a
r) <- forall a.
IO ByteString
-> Get a -> ByteString -> IO (ByteString, ReadResult a)
runGetWith (forall c. Connection c => c -> IO ByteString
cGetSome c
c) Get a
p ByteString
initial
      forall a. IORef a -> a -> IO ()
writeIORef IORef ByteString
buf forall a b. (a -> b) -> a -> b
$! ByteString
leftovers
      forall (f :: * -> *) a. Applicative f => a -> f a
pure ReadResult a
r

-- | Runs a Get parser incrementally, reading more input as necessary until a successful parse
-- has been achieved.
runGetWith :: IO BS.ByteString -> G.Get a -> BS.ByteString -> IO (BS.ByteString, ReadResult a)
runGetWith :: forall a.
IO ByteString
-> Get a -> ByteString -> IO (ByteString, ReadResult a)
runGetWith IO ByteString
getBs Get a
p ByteString
initial = forall {a}. Result a -> IO (ByteString, ReadResult a)
go (forall a. Get a -> ByteString -> Result a
G.runGetPartial Get a
p ByteString
initial)
  where
    go :: Result a -> IO (ByteString, ReadResult a)
go Result a
r = case Result a
r of
      G.Fail String
err ByteString
bs -> do
        forall (f :: * -> *) a. Applicative f => a -> f a
pure (ByteString
bs, forall a. String -> ReadResult a
RRFailure String
err)
      G.Done a
a ByteString
bs -> do
        forall (f :: * -> *) a. Applicative f => a -> f a
pure (ByteString
bs, forall a. a -> ReadResult a
RRSuccess a
a)
      G.Partial ByteString -> Result a
cont -> do
        ByteString
bs <- IO ByteString
getBs
        if ByteString -> Bool
BS.null ByteString
bs
          then
            -- EOF
            forall (f :: * -> *) a. Applicative f => a -> f a
pure (ByteString
bs, forall a. ReadResult a
RREOF)
          else
            Result a -> IO (ByteString, ReadResult a)
go forall a b. (a -> b) -> a -> b
$ ByteString -> Result a
cont ByteString
bs