{-# LINE 1 "src/Streamly/Internal/System/IOVec/Type.hsc" #-}


-- |
-- Module      : Streamly.Internal.System.IOVec.Type
-- Copyright   : (c) 2019 Composewell Technologies
--
-- License     : BSD3
-- Maintainer  : streamly@composewell.com
-- Stability   : experimental
-- Portability : GHC
--
-- Low level IO routines interfacing the operating system.
--

module Streamly.Internal.System.IOVec.Type
    ( IOVec(..)
    , c_writev
    , c_safe_writev
    )
where


import Data.Word (Word8)

{-# LINE 27 "src/Streamly/Internal/System/IOVec/Type.hsc" #-}
import Data.Word (Word64)

{-# LINE 29 "src/Streamly/Internal/System/IOVec/Type.hsc" #-}
import Foreign.C.Types (CInt(..))
import Foreign.Ptr (Ptr)
import System.Posix.Types (CSsize(..))

{-# LINE 33 "src/Streamly/Internal/System/IOVec/Type.hsc" #-}
import Foreign.Storable (Storable(..))

{-# LINE 35 "src/Streamly/Internal/System/IOVec/Type.hsc" #-}

-------------------------------------------------------------------------------
-- IOVec
-------------------------------------------------------------------------------

data IOVec = IOVec
  { IOVec -> Ptr Word8
iovBase :: {-# UNPACK #-} !(Ptr Word8)

{-# LINE 45 "src/Streamly/Internal/System/IOVec/Type.hsc" #-}
  , IOVec -> Word64
iovLen  :: {-# UNPACK #-} !Word64

{-# LINE 47 "src/Streamly/Internal/System/IOVec/Type.hsc" #-}
  } deriving (Eq, Show)


{-# LINE 50 "src/Streamly/Internal/System/IOVec/Type.hsc" #-}



instance Storable IOVec where
  sizeOf :: IOVec -> Int
sizeOf IOVec
_ = (Int
16)
{-# LINE 55 "src/Streamly/Internal/System/IOVec/Type.hsc" #-}
  alignment _ = 8
{-# LINE 56 "src/Streamly/Internal/System/IOVec/Type.hsc" #-}
  peek ptr = do
      base <- (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr
{-# LINE 58 "src/Streamly/Internal/System/IOVec/Type.hsc" #-}
      len  :: Word64 <- (\hsc_ptr -> peekByteOff hsc_ptr 8)  ptr
{-# LINE 59 "src/Streamly/Internal/System/IOVec/Type.hsc" #-}
      return $ IOVec base len
  poke :: Ptr IOVec -> IOVec -> IO ()
poke Ptr IOVec
ptr IOVec
vec = do
      let base :: Ptr Word8
base = IOVec -> Ptr Word8
iovBase IOVec
vec
          Word64
len  :: Word64 = IOVec -> Word64
iovLen IOVec
vec
{-# LINE 63 "src/Streamly/Internal/System/IOVec/Type.hsc" #-}
      (\hsc_ptr -> pokeByteOff hsc_ptr 0) ptr base
{-# LINE 64 "src/Streamly/Internal/System/IOVec/Type.hsc" #-}
      (\hsc_ptr -> pokeByteOff hsc_ptr 8)  ptr len
{-# LINE 65 "src/Streamly/Internal/System/IOVec/Type.hsc" #-}

{-# LINE 66 "src/Streamly/Internal/System/IOVec/Type.hsc" #-}

-- capi calling convention does not work without -fobject-code option with GHCi
-- so using this in DEVBUILD only for now.
--

{-# LINE 78 "src/Streamly/Internal/System/IOVec/Type.hsc" #-}
c_writev :: CInt -> Ptr IOVec -> CInt -> IO CSsize
c_writev :: CInt -> Ptr IOVec -> CInt -> IO CSsize
c_writev = forall a. HasCallStack => String -> a
error String
"writev not implemented"

c_safe_writev :: CInt -> Ptr IOVec -> CInt -> IO CSsize
c_safe_writev :: CInt -> Ptr IOVec -> CInt -> IO CSsize
c_safe_writev = forall a. HasCallStack => String -> a
error String
"writev not implemented"

{-# LINE 84 "src/Streamly/Internal/System/IOVec/Type.hsc" #-}