module Network.Transport.Internal
(
encodeWord32
, decodeWord32
, encodeEnum32
, decodeNum32
, encodeWord16
, decodeWord16
, encodeEnum16
, decodeNum16
, prependLength
, mapIOException
, tryIO
, tryToEnum
, timeoutMaybe
, asyncWhenCancelled
, void
, forkIOWithUnmask
, tlog
) where
#if ! MIN_VERSION_base(4,6,0)
import Prelude hiding (catch)
#endif
import Foreign.Storable (pokeByteOff, peekByteOff)
import Foreign.ForeignPtr (withForeignPtr)
import Data.ByteString (ByteString)
import Data.List (foldl')
import qualified Data.ByteString as BS (length)
import qualified Data.ByteString.Internal as BSI
( unsafeCreate
, toForeignPtr
)
import Data.Word (Word32, Word16)
import Control.Applicative ((<$>))
import Control.Monad.IO.Class (MonadIO, liftIO)
import Control.Exception
( IOException
, SomeException
, AsyncException
, Exception
, catch
, try
, throw
, throwIO
, mask_
)
import Control.Concurrent (ThreadId, forkIO)
import Control.Concurrent.MVar (MVar, newEmptyMVar, takeMVar, putMVar)
import GHC.IO (unsafeUnmask)
import System.IO.Unsafe (unsafeDupablePerformIO)
import System.Timeout (timeout)
#ifdef mingw32_HOST_OS
foreign import stdcall unsafe "htonl" htonl :: Word32 -> Word32
foreign import stdcall unsafe "ntohl" ntohl :: Word32 -> Word32
foreign import stdcall unsafe "htons" htons :: Word16 -> Word16
foreign import stdcall unsafe "ntohs" ntohs :: Word16 -> Word16
#else
foreign import ccall unsafe "htonl" htonl :: Word32 -> Word32
foreign import ccall unsafe "ntohl" ntohl :: Word32 -> Word32
foreign import ccall unsafe "htons" htons :: Word16 -> Word16
foreign import ccall unsafe "ntohs" ntohs :: Word16 -> Word16
#endif
encodeWord32 :: Word32 -> ByteString
encodeWord32 w32 =
BSI.unsafeCreate 4 $ \p ->
pokeByteOff p 0 (htonl w32)
decodeWord32 :: ByteString -> Word32
decodeWord32 bs
| BS.length bs /= 4 = throw $ userError "decodeWord32: not 4 bytes"
| otherwise = unsafeDupablePerformIO $ do
let (fp, offset, _) = BSI.toForeignPtr bs
withForeignPtr fp $ \p -> ntohl <$> peekByteOff p offset
encodeWord16 :: Word16 -> ByteString
encodeWord16 w16 =
BSI.unsafeCreate 2 $ \p ->
pokeByteOff p 0 (htons w16)
decodeWord16 :: ByteString -> Word16
decodeWord16 bs
| BS.length bs /= 2 = throw $ userError "decodeWord16: not 2 bytes"
| otherwise = unsafeDupablePerformIO $ do
let (fp, offset, _) = BSI.toForeignPtr bs
withForeignPtr fp $ \p -> ntohs <$> peekByteOff p offset
encodeEnum32 :: Enum a => a -> ByteString
encodeEnum32 = encodeWord32 . fromIntegral . fromEnum
decodeNum32 :: Num a => ByteString -> a
decodeNum32 = fromIntegral . decodeWord32
encodeEnum16 :: Enum a => a -> ByteString
encodeEnum16 = encodeWord16 . fromIntegral . fromEnum
decodeNum16 :: Num a => ByteString -> a
decodeNum16 = fromIntegral . decodeWord16
prependLength :: [ByteString] -> [ByteString]
prependLength bss = case word32Length of
Nothing -> overflow
Just w32 -> encodeWord32 w32 : bss
where
intLength :: Int
intLength = foldl' safeAdd 0 . map BS.length $ bss
word32Length :: Maybe Word32
word32Length = tryToEnum intLength
safeAdd :: Int -> Int -> Int
safeAdd i j
| r >= 0 = r
| otherwise = overflow
where
r = i + j
overflow = throw $ userError "prependLength: input is too long (overflow)"
mapIOException :: Exception e => (IOException -> e) -> IO a -> IO a
mapIOException f p = catch p (throwIO . f)
tryIO :: MonadIO m => IO a -> m (Either IOException a)
tryIO = liftIO . try
tlog :: MonadIO m => String -> m ()
tlog _ = return ()
void :: Monad m => m a -> m ()
void p = p >> return ()
forkIOWithUnmask :: ((forall a . IO a -> IO a) -> IO ()) -> IO ThreadId
forkIOWithUnmask io = forkIO (io unsafeUnmask)
tryToEnum :: (Enum a, Bounded a) => Int -> Maybe a
tryToEnum = go minBound maxBound
where
go :: Enum b => b -> b -> Int -> Maybe b
go lo hi n = if fromEnum lo <= n && n <= fromEnum hi then Just (toEnum n) else Nothing
timeoutMaybe :: Exception e => Maybe Int -> e -> IO a -> IO a
timeoutMaybe Nothing _ f = f
timeoutMaybe (Just n) e f = do
ma <- timeout n f
case ma of
Nothing -> throwIO e
Just a -> return a
asyncWhenCancelled :: forall a. (a -> IO ()) -> IO a -> IO a
asyncWhenCancelled g f = mask_ $ do
mvar <- newEmptyMVar
forkIO $ try f >>= putMVar mvar
catch (takeMVar mvar) (exceptionHandler mvar) >>= either throwIO return
where
exceptionHandler :: MVar (Either SomeException a)
-> AsyncException
-> IO (Either SomeException a)
exceptionHandler mvar ex = do
forkIO $ takeMVar mvar >>= either (const $ return ()) g
throwIO ex