{-# LINE 1 "src/Network/Socket/Splice/Internal.hsc" #-}
-- | Implementation.
{-# LINE 2 "src/Network/Socket/Splice/Internal.hsc" #-}


{-# LINE 6 "src/Network/Socket/Splice/Internal.hsc" #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE ForeignFunctionInterface #-}


module Network.Socket.Splice.Internal (

  -- * Cross-platform API for Socket to Socket Data Transfer Loops
  {- | 'splice' is the cross-platform API for continous, uni-directional
       data transfer between two network sockets.

       It is an /infinite loop/ that is intended to be used with
       'Control.Concurrent.forkIO':

       > void . forkIO . try_ $ splice 1024 sourceSocket targetSocket
       > void . forkIO . try_ $ splice 1024 targetSocket sourceSocket
  -}

    splice
  , ChunkSize
  , zeroCopy

  -- * Combinators for Exception Handling
  , try_

  ) where


import Data.Word
import Foreign.Ptr

import Network.Socket
import Control.Monad
import Control.Exception


{-# LINE 50 "src/Network/Socket/Splice/Internal.hsc" #-}
import System.IO
import GHC.IO.Handle.FD
import Foreign.Marshal.Alloc

{-# LINE 54 "src/Network/Socket/Splice/Internal.hsc" #-}


--------------------------------------------------------------------------------


-- | Indicates whether 'splice' uses zero-copy system calls or the portable user 
--   space Haskell implementation.
zeroCopy :: Bool -- ^ @True@ if 'splice' uses zero-copy system calls;
                 --   otherwise, false.
zeroCopy =

{-# LINE 67 "src/Network/Socket/Splice/Internal.hsc" #-}
  False

{-# LINE 69 "src/Network/Socket/Splice/Internal.hsc" #-}


-- | The numeric type to recommend chunk sizes for moving data between sockets
--   used by both zero-copy and portable implementations of 'splice'.
type ChunkSize =

{-# LINE 77 "src/Network/Socket/Splice/Internal.hsc" #-}
  Int

{-# LINE 79 "src/Network/Socket/Splice/Internal.hsc" #-}


-- | Pipes data from one socket to another in an /infinite loop/.
--
--   On Linux this uses the @splice()@ system call and eliminates copying
--   between kernel and user address spaces.
--
--   On other operating systems, a portable Haskell implementation utilizes a
--   user space buffer.
splice
  :: ChunkSize -- ^ chunk size.
  -> Socket    -- ^ source socket.
  -> Socket    -- ^ target socket.
  -> IO ()     -- ^ infinite loop.
splice len sIn sOut = do

  let throwRecv0 = error "Network.Socket.Splice.splice ended"

  let fdIn  = fdSocket sIn
  let fdOut = fdSocket sOut 


{-# LINE 124 "src/Network/Socket/Splice/Internal.hsc" #-}

  s <- fdToHandle fdIn
  t <- fdToHandle fdOut
  hSetBuffering s NoBuffering
  hSetBuffering t NoBuffering
  a <- mallocBytes len :: IO (Ptr Word8)

  finally
    (forever $ do
       bytes <-   hGetBufSome s a len
       if bytes > 0
         then     hPutBuf     t a bytes
         else     throwRecv0)
    (do free a
        try_ $ hClose s
        try_ $ hClose t)


{-# LINE 142 "src/Network/Socket/Splice/Internal.hsc" #-}


-- | Similar to 'Control.Exception.Base.try' but used when an obvious exception
--   is expected which can be safely ignored.
try_
  :: IO () -- ^ action to run which can throw /any/ exception.
  -> IO () -- ^ new action where exceptions are silenced.
try_ a = (try a :: IO (Either SomeException ())) >> return ()