{-# LINE 1 "src/Network/Riak/Connection/NoPush.hsc" #-}
{-# LANGUAGE ForeignFunctionInterface #-}

-- |
-- Module:      Network.Riak.Connection.NoPush
-- Copyright:   (c) 2011 MailRank, Inc.
-- License:     Apache
-- Maintainer:  Mark Hibberd <mark@hibberd.id.au>, Nathan Hunter <nhunter@janrain.com>
-- Stability:   experimental
-- Portability: portable
--
-- TCP madness.

module Network.Riak.Connection.NoPush (setNoPush) where





import Foreign.C.Error (throwErrnoIfMinus1_)
import Foreign.C.Types (CInt(..))
import Foreign.Marshal.Utils (with)
import Foreign.Ptr (Ptr)
import Foreign.Storable (sizeOf)
import Network.Socket (Socket, fdSocket)

noPush :: CInt

{-# LINE 33 "src/Network/Riak/Connection/NoPush.hsc" #-}
noPush = 3
{-# LINE 34 "src/Network/Riak/Connection/NoPush.hsc" #-}

{-# LINE 37 "src/Network/Riak/Connection/NoPush.hsc" #-}

setNoPush :: Socket -> Bool -> IO ()
setNoPush _ _ | noPush == 0 = return ()
-- setNoPush (MkSocket fd _ _ _ _) onOff = do
setNoPush s onOff = do
  let v = if onOff then 1 else 0
  with v $ \ptr ->
    throwErrnoIfMinus1_ "setNoPush" $ do
      a <- (fdSocket s)
      c_setsockopt a (6) noPush ptr (fromIntegral (sizeOf v))
{-# LINE 47 "src/Network/Riak/Connection/NoPush.hsc" #-}

foreign import ccall unsafe "setsockopt"
  c_setsockopt :: CInt -> CInt -> CInt -> Ptr CInt -> CInt -> IO CInt