{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE CPP #-}
module System.IO.ByteBuffer
( ByteBuffer
, new, free, with
, totalSize, isEmpty, availableBytes
, copyByteString
#ifndef mingw32_HOST_OS
, fillFromFd
#endif
, consume, unsafeConsume
, ByteBufferException (..)
) where
import Control.Applicative
import Control.Exception (SomeException, throwIO)
import Control.Exception.Lifted (Exception, bracket, catch)
import qualified Control.Monad.Fail as Fail
import Control.Monad.IO.Class (MonadIO, liftIO)
import Control.Monad.Trans.Control (MonadBaseControl)
import Data.ByteString (ByteString)
import qualified Data.ByteString.Internal as BS
import Data.IORef
import Data.Maybe (fromMaybe)
import Data.Typeable (Typeable)
import Data.Word
import Foreign.ForeignPtr
import qualified Foreign.Marshal.Alloc as Alloc
import Foreign.Marshal.Utils (copyBytes, moveBytes)
import GHC.Ptr
import Prelude
import qualified Foreign.C.Error as CE
import Foreign.C.Types
import System.Posix.Types (Fd (..))
data BBRef = BBRef {
BBRef -> Int
size :: {-# UNPACK #-} !Int
, BBRef -> Int
contained :: {-# UNPACK #-} !Int
, BBRef -> Int
consumed :: {-# UNPACK #-} !Int
, BBRef -> Ptr Word8
ptr :: {-# UNPACK #-} !(Ptr Word8)
}
data ByteBufferException = ByteBufferException
{ ByteBufferException -> String
_bbeLocation :: !String
, ByteBufferException -> String
_bbeException :: !String
}
deriving (Typeable, ByteBufferException -> ByteBufferException -> Bool
(ByteBufferException -> ByteBufferException -> Bool)
-> (ByteBufferException -> ByteBufferException -> Bool)
-> Eq ByteBufferException
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ByteBufferException -> ByteBufferException -> Bool
$c/= :: ByteBufferException -> ByteBufferException -> Bool
== :: ByteBufferException -> ByteBufferException -> Bool
$c== :: ByteBufferException -> ByteBufferException -> Bool
Eq)
instance Show ByteBufferException where
show :: ByteBufferException -> String
show (ByteBufferException String
loc String
e) = [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[String
"ByteBufferException: ByteBuffer was invalidated because of Exception thrown in "
, String
loc , String
": ", String
e]
instance Exception ByteBufferException
type ByteBuffer = IORef (Either ByteBufferException BBRef)
bbHandler :: MonadIO m
=> String
-> ByteBuffer
-> (BBRef -> IO a)
-> m a
bbHandler :: String -> ByteBuffer -> (BBRef -> IO a) -> m a
bbHandler String
loc ByteBuffer
bb BBRef -> IO a
f = IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO a -> m a) -> IO a -> m a
forall a b. (a -> b) -> a -> b
$ (BBRef -> IO a) -> ByteBuffer -> IO a
forall a. (BBRef -> IO a) -> ByteBuffer -> IO a
useBBRef BBRef -> IO a
f ByteBuffer
bb IO a -> (SomeException -> IO a) -> IO a
forall (m :: * -> *) e a.
(MonadBaseControl IO m, Exception e) =>
m a -> (e -> m a) -> m a
`catch` \(SomeException
e :: SomeException) -> do
ByteBuffer -> IO (Either ByteBufferException BBRef)
forall a. IORef a -> IO a
readIORef ByteBuffer
bb IO (Either ByteBufferException BBRef)
-> (Either ByteBufferException BBRef -> IO ()) -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Right BBRef
bbref -> do
Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
Alloc.free (BBRef -> Ptr Word8
ptr BBRef
bbref)
ByteBuffer -> Either ByteBufferException BBRef -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef ByteBuffer
bb (ByteBufferException -> Either ByteBufferException BBRef
forall a b. a -> Either a b
Left (ByteBufferException -> Either ByteBufferException BBRef)
-> ByteBufferException -> Either ByteBufferException BBRef
forall a b. (a -> b) -> a -> b
$ String -> String -> ByteBufferException
ByteBufferException String
loc (SomeException -> String
forall a. Show a => a -> String
show SomeException
e))
Left ByteBufferException
_ -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
SomeException -> IO a
forall e a. Exception e => e -> IO a
throwIO SomeException
e
useBBRef :: (BBRef -> IO a) -> ByteBuffer -> IO a
useBBRef :: (BBRef -> IO a) -> ByteBuffer -> IO a
useBBRef BBRef -> IO a
f ByteBuffer
bb = ByteBuffer -> IO (Either ByteBufferException BBRef)
forall a. IORef a -> IO a
readIORef ByteBuffer
bb IO (Either ByteBufferException BBRef)
-> (Either ByteBufferException BBRef -> IO a) -> IO a
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ByteBufferException -> IO a)
-> (BBRef -> IO a) -> Either ByteBufferException BBRef -> IO a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either ByteBufferException -> IO a
forall e a. Exception e => e -> IO a
throwIO BBRef -> IO a
f
{-# INLINE useBBRef #-}
totalSize :: MonadIO m => ByteBuffer -> m Int
totalSize :: ByteBuffer -> m Int
totalSize = IO Int -> m Int
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int -> m Int) -> (ByteBuffer -> IO Int) -> ByteBuffer -> m Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BBRef -> IO Int) -> ByteBuffer -> IO Int
forall a. (BBRef -> IO a) -> ByteBuffer -> IO a
useBBRef (Int -> IO Int
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> IO Int) -> (BBRef -> Int) -> BBRef -> IO Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BBRef -> Int
size)
{-# INLINE totalSize #-}
isEmpty :: MonadIO m => ByteBuffer -> m Bool
isEmpty :: ByteBuffer -> m Bool
isEmpty ByteBuffer
bb = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ (Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
==Int
0) (Int -> Bool) -> IO Int -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteBuffer -> IO Int
forall (m :: * -> *). MonadIO m => ByteBuffer -> m Int
availableBytes ByteBuffer
bb
{-# INLINE isEmpty #-}
availableBytes :: MonadIO m => ByteBuffer -> m Int
availableBytes :: ByteBuffer -> m Int
availableBytes = IO Int -> m Int
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int -> m Int) -> (ByteBuffer -> IO Int) -> ByteBuffer -> m Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BBRef -> IO Int) -> ByteBuffer -> IO Int
forall a. (BBRef -> IO a) -> ByteBuffer -> IO a
useBBRef (\BBRef{Int
Ptr Word8
ptr :: Ptr Word8
consumed :: Int
contained :: Int
size :: Int
ptr :: BBRef -> Ptr Word8
consumed :: BBRef -> Int
contained :: BBRef -> Int
size :: BBRef -> Int
..} -> Int -> IO Int
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
contained Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
consumed))
{-# INLINE availableBytes #-}
new :: MonadIO m
=> Maybe Int
-> m ByteBuffer
new :: Maybe Int -> m ByteBuffer
new Maybe Int
ml = IO ByteBuffer -> m ByteBuffer
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ByteBuffer -> m ByteBuffer) -> IO ByteBuffer -> m ByteBuffer
forall a b. (a -> b) -> a -> b
$ do
let l :: Int
l = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
0 (Int -> Int) -> (Maybe Int -> Int) -> Maybe Int -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe (Int
4Int -> Int -> Int
forall a. Num a => a -> a -> a
*Int
1024Int -> Int -> Int
forall a. Num a => a -> a -> a
*Int
1024) (Maybe Int -> Int) -> Maybe Int -> Int
forall a b. (a -> b) -> a -> b
$ Maybe Int
ml
Ptr Word8
newPtr <- Int -> IO (Ptr Word8)
forall a. Int -> IO (Ptr a)
Alloc.mallocBytes Int
l
Either ByteBufferException BBRef -> IO ByteBuffer
forall a. a -> IO (IORef a)
newIORef (Either ByteBufferException BBRef -> IO ByteBuffer)
-> Either ByteBufferException BBRef -> IO ByteBuffer
forall a b. (a -> b) -> a -> b
$ BBRef -> Either ByteBufferException BBRef
forall a b. b -> Either a b
Right BBRef :: Int -> Int -> Int -> Ptr Word8 -> BBRef
BBRef
{ ptr :: Ptr Word8
ptr = Ptr Word8
newPtr
, size :: Int
size = Int
l
, contained :: Int
contained = Int
0
, consumed :: Int
consumed = Int
0
}
free :: MonadIO m => ByteBuffer -> m ()
free :: ByteBuffer -> m ()
free ByteBuffer
bb = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ ByteBuffer -> IO (Either ByteBufferException BBRef)
forall a. IORef a -> IO a
readIORef ByteBuffer
bb IO (Either ByteBufferException BBRef)
-> (Either ByteBufferException BBRef -> IO ()) -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Right BBRef
bbref -> do
Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
Alloc.free (Ptr Word8 -> IO ()) -> Ptr Word8 -> IO ()
forall a b. (a -> b) -> a -> b
$ BBRef -> Ptr Word8
ptr BBRef
bbref
ByteBuffer -> Either ByteBufferException BBRef -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef ByteBuffer
bb (Either ByteBufferException BBRef -> IO ())
-> Either ByteBufferException BBRef -> IO ()
forall a b. (a -> b) -> a -> b
$
ByteBufferException -> Either ByteBufferException BBRef
forall a b. a -> Either a b
Left (String -> String -> ByteBufferException
ByteBufferException String
"free" String
"ByteBuffer has explicitly been freed and is no longer valid.")
Left ByteBufferException
_ -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
with :: (MonadIO m, MonadBaseControl IO m)
=> Maybe Int
-> (ByteBuffer -> m a)
-> m a
with :: Maybe Int -> (ByteBuffer -> m a) -> m a
with Maybe Int
l ByteBuffer -> m a
action =
m ByteBuffer -> (ByteBuffer -> m ()) -> (ByteBuffer -> m a) -> m a
forall (m :: * -> *) a b c.
MonadBaseControl IO m =>
m a -> (a -> m b) -> (a -> m c) -> m c
bracket
(Maybe Int -> m ByteBuffer
forall (m :: * -> *). MonadIO m => Maybe Int -> m ByteBuffer
new Maybe Int
l)
ByteBuffer -> m ()
forall (m :: * -> *). MonadIO m => ByteBuffer -> m ()
free
ByteBuffer -> m a
action
{-# INLINE with #-}
resetBBRef :: BBRef -> IO BBRef
resetBBRef :: BBRef -> IO BBRef
resetBBRef BBRef
bbref = do
let available :: Int
available = BBRef -> Int
contained BBRef
bbref Int -> Int -> Int
forall a. Num a => a -> a -> a
- BBRef -> Int
consumed BBRef
bbref
Ptr Word8 -> Ptr Word8 -> Int -> IO ()
forall a. Ptr a -> Ptr a -> Int -> IO ()
moveBytes (BBRef -> Ptr Word8
ptr BBRef
bbref) (BBRef -> Ptr Word8
ptr BBRef
bbref Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` BBRef -> Int
consumed BBRef
bbref) Int
available
BBRef -> IO BBRef
forall (m :: * -> *) a. Monad m => a -> m a
return BBRef :: Int -> Int -> Int -> Ptr Word8 -> BBRef
BBRef { size :: Int
size = BBRef -> Int
size BBRef
bbref
, contained :: Int
contained = Int
available
, consumed :: Int
consumed = Int
0
, ptr :: Ptr Word8
ptr = BBRef -> Ptr Word8
ptr BBRef
bbref
}
enlargeBBRef :: BBRef -> Int -> IO BBRef
enlargeBBRef :: BBRef -> Int -> IO BBRef
enlargeBBRef BBRef
bbref Int
minSize = do
let getNewSize :: Int -> Int
getNewSize Int
s | Int
s Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
minSize = Int
s
getNewSize Int
s = Int -> Int
getNewSize (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ (Double -> Int
forall a b. (RealFrac a, Integral b) => a -> b
ceiling (Double -> Int) -> (Int -> Double) -> Int -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Double -> Double -> Double
forall a. Num a => a -> a -> a
*(Double
1.5 :: Double)) (Double -> Double) -> (Int -> Double) -> Int -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral) (Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
1 Int
s)
newSize :: Int
newSize = Int -> Int
getNewSize (BBRef -> Int
size BBRef
bbref)
Ptr Word8
ptr' <- Ptr Word8 -> Int -> IO (Ptr Word8)
forall a. Ptr a -> Int -> IO (Ptr a)
Alloc.reallocBytes (BBRef -> Ptr Word8
ptr BBRef
bbref) Int
newSize
BBRef -> IO BBRef
forall (m :: * -> *) a. Monad m => a -> m a
return BBRef :: Int -> Int -> Int -> Ptr Word8 -> BBRef
BBRef { size :: Int
size = Int
newSize
, contained :: Int
contained = BBRef -> Int
contained BBRef
bbref
, consumed :: Int
consumed = BBRef -> Int
consumed BBRef
bbref
, ptr :: Ptr Word8
ptr = Ptr Word8
ptr'
}
copyByteString :: MonadIO m => ByteBuffer -> ByteString -> m ()
copyByteString :: ByteBuffer -> ByteString -> m ()
copyByteString ByteBuffer
bb ByteString
bs =
String -> ByteBuffer -> (BBRef -> IO ()) -> m ()
forall (m :: * -> *) a.
MonadIO m =>
String -> ByteBuffer -> (BBRef -> IO a) -> m a
bbHandler String
"copyByteString" ByteBuffer
bb BBRef -> IO ()
go
where
go :: BBRef -> IO ()
go BBRef
bbref = do
let (ForeignPtr Word8
bsFptr, Int
bsOffset, Int
bsSize) = ByteString -> (ForeignPtr Word8, Int, Int)
BS.toForeignPtr ByteString
bs
let available :: Int
available = BBRef -> Int
contained BBRef
bbref Int -> Int -> Int
forall a. Num a => a -> a -> a
- BBRef -> Int
consumed BBRef
bbref
BBRef
bbref' <- if BBRef -> Int
size BBRef
bbref Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
bsSize Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
available
then BBRef -> Int -> IO BBRef
enlargeBBRef BBRef
bbref (Int
bsSize Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
available)
else BBRef -> IO BBRef
forall (m :: * -> *) a. Monad m => a -> m a
return BBRef
bbref
BBRef
bbref'' <- if Int
bsSize Int -> Int -> Int
forall a. Num a => a -> a -> a
+ BBRef -> Int
contained BBRef
bbref' Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> BBRef -> Int
size BBRef
bbref'
then BBRef -> IO BBRef
resetBBRef BBRef
bbref'
else BBRef -> IO BBRef
forall (m :: * -> *) a. Monad m => a -> m a
return BBRef
bbref'
ForeignPtr Word8 -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Word8
bsFptr ((Ptr Word8 -> IO ()) -> IO ()) -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ Ptr Word8
bsPtr ->
Ptr Any -> Ptr Any -> Int -> IO ()
forall a. Ptr a -> Ptr a -> Int -> IO ()
copyBytes (BBRef -> Ptr Word8
ptr BBRef
bbref'' Ptr Word8 -> Int -> Ptr Any
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` BBRef -> Int
contained BBRef
bbref'')
(Ptr Word8
bsPtr Ptr Word8 -> Int -> Ptr Any
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
bsOffset)
Int
bsSize
ByteBuffer -> Either ByteBufferException BBRef -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef ByteBuffer
bb (Either ByteBufferException BBRef -> IO ())
-> Either ByteBufferException BBRef -> IO ()
forall a b. (a -> b) -> a -> b
$ BBRef -> Either ByteBufferException BBRef
forall a b. b -> Either a b
Right BBRef :: Int -> Int -> Int -> Ptr Word8 -> BBRef
BBRef {
size :: Int
size = BBRef -> Int
size BBRef
bbref''
, contained :: Int
contained = BBRef -> Int
contained BBRef
bbref'' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
bsSize
, consumed :: Int
consumed = BBRef -> Int
consumed BBRef
bbref''
, ptr :: Ptr Word8
ptr = BBRef -> Ptr Word8
ptr BBRef
bbref''}
#ifndef mingw32_HOST_OS
fillFromFd :: (MonadIO m, Fail.MonadFail m) => ByteBuffer -> Fd -> Int -> m Int
fillFromFd :: ByteBuffer -> Fd -> Int -> m Int
fillFromFd ByteBuffer
bb Fd
sock Int
maxBytes = if Int
maxBytes Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0
then String -> m Int
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String
"fillFromFd: negative argument (" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
maxBytes String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
")")
else String -> ByteBuffer -> (BBRef -> IO Int) -> m Int
forall (m :: * -> *) a.
MonadIO m =>
String -> ByteBuffer -> (BBRef -> IO a) -> m a
bbHandler String
"fillFromFd" ByteBuffer
bb BBRef -> IO Int
go
where
go :: BBRef -> IO Int
go BBRef
bbref = do
(BBRef
bbref', Int
readBytes) <- Fd -> BBRef -> Int -> IO (BBRef, Int)
fillBBRefFromFd Fd
sock BBRef
bbref Int
maxBytes
ByteBuffer -> Either ByteBufferException BBRef -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef ByteBuffer
bb (Either ByteBufferException BBRef -> IO ())
-> Either ByteBufferException BBRef -> IO ()
forall a b. (a -> b) -> a -> b
$ BBRef -> Either ByteBufferException BBRef
forall a b. b -> Either a b
Right BBRef
bbref'
Int -> IO Int
forall (m :: * -> *) a. Monad m => a -> m a
return Int
readBytes
fillBBRefFromFd :: Fd -> BBRef -> Int -> IO (BBRef, Int)
fillBBRefFromFd :: Fd -> BBRef -> Int -> IO (BBRef, Int)
fillBBRefFromFd (Fd CInt
sock) BBRef
bbref0 Int
maxBytes = do
BBRef
bbref1 <- BBRef -> IO BBRef
prepareSpace BBRef
bbref0
Int -> BBRef -> IO (BBRef, Int)
go Int
0 BBRef
bbref1
where
prepareSpace :: BBRef -> IO BBRef
prepareSpace :: BBRef -> IO BBRef
prepareSpace BBRef
bbref = do
let space :: Int
space = BBRef -> Int
size BBRef
bbref Int -> Int -> Int
forall a. Num a => a -> a -> a
- BBRef -> Int
contained BBRef
bbref
if Int
space Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
maxBytes
then if BBRef -> Int
consumed BBRef
bbref Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
then BBRef -> IO BBRef
prepareSpace (BBRef -> IO BBRef) -> IO BBRef -> IO BBRef
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< BBRef -> IO BBRef
resetBBRef BBRef
bbref
else BBRef -> Int -> IO BBRef
enlargeBBRef BBRef
bbref (BBRef -> Int
contained BBRef
bbref Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
maxBytes)
else BBRef -> IO BBRef
forall (m :: * -> *) a. Monad m => a -> m a
return BBRef
bbref
go :: Int -> BBRef -> IO (BBRef, Int)
go :: Int -> BBRef -> IO (BBRef, Int)
go Int
readBytes bbref :: BBRef
bbref@BBRef{Int
Ptr Word8
ptr :: Ptr Word8
consumed :: Int
contained :: Int
size :: Int
ptr :: BBRef -> Ptr Word8
consumed :: BBRef -> Int
contained :: BBRef -> Int
size :: BBRef -> Int
..} = if Int
readBytes Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
maxBytes
then (BBRef, Int) -> IO (BBRef, Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (BBRef
bbref, Int
readBytes)
else do
Int
bytes <- CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CInt -> Int) -> IO CInt -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CInt -> Ptr CChar -> CSize -> CInt -> IO CInt
c_recv CInt
sock (Ptr Any -> Ptr CChar
forall a b. Ptr a -> Ptr b
castPtr (Ptr Word8
ptr Ptr Word8 -> Int -> Ptr Any
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
contained)) (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int
maxBytes Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
readBytes)) CInt
0
if Int
bytes Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== -Int
1
then do
Errno
err <- IO Errno
CE.getErrno
if Errno
err Errno -> Errno -> Bool
forall a. Eq a => a -> a -> Bool
== Errno
CE.eAGAIN Bool -> Bool -> Bool
|| Errno
err Errno -> Errno -> Bool
forall a. Eq a => a -> a -> Bool
== Errno
CE.eWOULDBLOCK
then (BBRef, Int) -> IO (BBRef, Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (BBRef
bbref, Int
readBytes)
else IOError -> IO (BBRef, Int)
forall e a. Exception e => e -> IO a
throwIO (IOError -> IO (BBRef, Int)) -> IOError -> IO (BBRef, Int)
forall a b. (a -> b) -> a -> b
$ String -> Errno -> Maybe Handle -> Maybe String -> IOError
CE.errnoToIOError String
"ByteBuffer.fillBBRefFromFd: " Errno
err Maybe Handle
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
else do
let bbref' :: BBRef
bbref' = BBRef
bbref{ contained :: Int
contained = Int
contained Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
bytes }
Int -> BBRef -> IO (BBRef, Int)
go (Int
readBytes Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
bytes) BBRef
bbref'
foreign import ccall unsafe "recv"
c_recv :: CInt -> Ptr CChar -> CSize -> CInt -> IO CInt
#endif
unsafeConsume :: MonadIO m
=> ByteBuffer
-> Int
-> m (Either Int (Ptr Word8))
unsafeConsume :: ByteBuffer -> Int -> m (Either Int (Ptr Word8))
unsafeConsume ByteBuffer
bb Int
n =
String
-> ByteBuffer
-> (BBRef -> IO (Either Int (Ptr Word8)))
-> m (Either Int (Ptr Word8))
forall (m :: * -> *) a.
MonadIO m =>
String -> ByteBuffer -> (BBRef -> IO a) -> m a
bbHandler String
"unsafeConsume" ByteBuffer
bb BBRef -> IO (Either Int (Ptr Word8))
forall b. BBRef -> IO (Either Int (Ptr b))
go
where
go :: BBRef -> IO (Either Int (Ptr b))
go BBRef
bbref = do
let available :: Int
available = BBRef -> Int
contained BBRef
bbref Int -> Int -> Int
forall a. Num a => a -> a -> a
- BBRef -> Int
consumed BBRef
bbref
if Int
available Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
n
then Either Int (Ptr b) -> IO (Either Int (Ptr b))
forall (m :: * -> *) a. Monad m => a -> m a
return (Either Int (Ptr b) -> IO (Either Int (Ptr b)))
-> Either Int (Ptr b) -> IO (Either Int (Ptr b))
forall a b. (a -> b) -> a -> b
$ Int -> Either Int (Ptr b)
forall a b. a -> Either a b
Left (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
available)
else do
ByteBuffer -> Either ByteBufferException BBRef -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef ByteBuffer
bb (Either ByteBufferException BBRef -> IO ())
-> Either ByteBufferException BBRef -> IO ()
forall a b. (a -> b) -> a -> b
$ BBRef -> Either ByteBufferException BBRef
forall a b. b -> Either a b
Right BBRef
bbref { consumed :: Int
consumed = BBRef -> Int
consumed BBRef
bbref Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
n }
Either Int (Ptr b) -> IO (Either Int (Ptr b))
forall (m :: * -> *) a. Monad m => a -> m a
return (Either Int (Ptr b) -> IO (Either Int (Ptr b)))
-> Either Int (Ptr b) -> IO (Either Int (Ptr b))
forall a b. (a -> b) -> a -> b
$ Ptr b -> Either Int (Ptr b)
forall a b. b -> Either a b
Right (BBRef -> Ptr Word8
ptr BBRef
bbref Ptr Word8 -> Int -> Ptr b
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` BBRef -> Int
consumed BBRef
bbref)
consume :: MonadIO m
=> ByteBuffer
-> Int
-> m (Either Int ByteString)
consume :: ByteBuffer -> Int -> m (Either Int ByteString)
consume ByteBuffer
bb Int
n = do
Either Int (Ptr Word8)
mPtr <- ByteBuffer -> Int -> m (Either Int (Ptr Word8))
forall (m :: * -> *).
MonadIO m =>
ByteBuffer -> Int -> m (Either Int (Ptr Word8))
unsafeConsume ByteBuffer
bb Int
n
case Either Int (Ptr Word8)
mPtr of
Right Ptr Word8
ptr -> do
ByteString
bs <- IO ByteString -> m ByteString
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ByteString -> m ByteString) -> IO ByteString -> m ByteString
forall a b. (a -> b) -> a -> b
$ Ptr Word8 -> Int -> IO ByteString
createBS Ptr Word8
ptr Int
n
Either Int ByteString -> m (Either Int ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> Either Int ByteString
forall a b. b -> Either a b
Right ByteString
bs)
Left Int
missing -> Either Int ByteString -> m (Either Int ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> Either Int ByteString
forall a b. a -> Either a b
Left Int
missing)
createBS :: Ptr Word8 -> Int -> IO ByteString
createBS :: Ptr Word8 -> Int -> IO ByteString
createBS Ptr Word8
ptr Int
n = do
ForeignPtr Word8
fp <- Int -> IO (ForeignPtr Word8)
forall a. Int -> IO (ForeignPtr a)
mallocForeignPtrBytes Int
n
ForeignPtr Word8 -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Word8
fp (\Ptr Word8
p -> Ptr Word8 -> Ptr Word8 -> Int -> IO ()
forall a. Ptr a -> Ptr a -> Int -> IO ()
copyBytes Ptr Word8
p Ptr Word8
ptr Int
n)
ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return (ForeignPtr Word8 -> Int -> Int -> ByteString
BS.PS ForeignPtr Word8
fp Int
0 Int
n)
_get1 :: (a,b,c) -> a
_get1 :: (a, b, c) -> a
_get1 (a
x,b
_,c
_) = a
x
_get2 :: (a,b,c) -> b
_get2 :: (a, b, c) -> b
_get2 (a
_,b
x,c
_) = b
x
_get3 :: (a,b,c) -> c
_get3 :: (a, b, c) -> c
_get3 (a
_,b
_,c
x) = c
x