{-# LINE 1 "src/Streamly/Internal/FileSystem/IOVec.hsc" #-}
module Streamly.Internal.FileSystem.IOVec
( IOVec(..)
, c_writev
, c_safe_writev
)
where
import Data.Word (Word8)
{-# LINE 27 "src/Streamly/Internal/FileSystem/IOVec.hsc" #-}
import Data.Word (Word64)
{-# LINE 29 "src/Streamly/Internal/FileSystem/IOVec.hsc" #-}
import Foreign.C.Types (CInt(..))
import Foreign.Ptr (Ptr)
import System.Posix.Types (CSsize(..))
{-# LINE 33 "src/Streamly/Internal/FileSystem/IOVec.hsc" #-}
import Foreign.Storable (Storable(..))
{-# LINE 35 "src/Streamly/Internal/FileSystem/IOVec.hsc" #-}
data IOVec = IOVec
{ IOVec -> Ptr Word8
iovBase :: {-# UNPACK #-} !(Ptr Word8)
{-# LINE 45 "src/Streamly/Internal/FileSystem/IOVec.hsc" #-}
, IOVec -> Word64
iovLen :: {-# UNPACK #-} !Word64
{-# LINE 47 "src/Streamly/Internal/FileSystem/IOVec.hsc" #-}
} deriving (Eq, Show)
{-# LINE 50 "src/Streamly/Internal/FileSystem/IOVec.hsc" #-}
instance Storable IOVec where
sizeOf :: IOVec -> Int
sizeOf IOVec
_ = (Int
16)
{-# LINE 55 "src/Streamly/Internal/FileSystem/IOVec.hsc" #-}
alignment _ = 8
{-# LINE 56 "src/Streamly/Internal/FileSystem/IOVec.hsc" #-}
peek ptr = do
base <- (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr
{-# LINE 58 "src/Streamly/Internal/FileSystem/IOVec.hsc" #-}
len :: Word64 <- (\hsc_ptr -> peekByteOff hsc_ptr 8) ptr
{-# LINE 59 "src/Streamly/Internal/FileSystem/IOVec.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/FileSystem/IOVec.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 0) ptr base
{-# LINE 64 "src/Streamly/Internal/FileSystem/IOVec.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 8) ptr len
{-# LINE 65 "src/Streamly/Internal/FileSystem/IOVec.hsc" #-}
{-# LINE 66 "src/Streamly/Internal/FileSystem/IOVec.hsc" #-}
{-# LINE 78 "src/Streamly/Internal/FileSystem/IOVec.hsc" #-}
c_writev :: CInt -> Ptr IOVec -> CInt -> IO CSsize
c_writev :: CInt -> Ptr IOVec -> CInt -> IO CSsize
c_writev = String -> CInt -> Ptr IOVec -> CInt -> IO CSsize
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 = String -> CInt -> Ptr IOVec -> CInt -> IO CSsize
forall a. HasCallStack => String -> a
error String
"writev not implemented"
{-# LINE 84 "src/Streamly/Internal/FileSystem/IOVec.hsc" #-}