{-# LINE 1 "src/Streamly/FileSystem/IOVec.hsc" #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CApiFFI #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Streamly.FileSystem.IOVec
( IOVec(..)
, c_writev
, c_safe_writev
)
where
import Data.Word (Word8, Word64)
import Foreign.C.Types (CInt(..))
import Foreign.Ptr (Ptr)
import System.Posix.Types (CSsize(..))
{-# LINE 30 "src/Streamly/FileSystem/IOVec.hsc" #-}
import Foreign.Storable (Storable(..))
{-# LINE 32 "src/Streamly/FileSystem/IOVec.hsc" #-}
data IOVec = IOVec
{ iovBase :: {-# UNPACK #-} !(Ptr Word8)
, iovLen :: {-# UNPACK #-} !Word64
} deriving (Eq, Show)
{-# LINE 43 "src/Streamly/FileSystem/IOVec.hsc" #-}
{-# LINE 49 "src/Streamly/FileSystem/IOVec.hsc" #-}
instance Storable IOVec where
sizeOf _ = (16)
{-# LINE 52 "src/Streamly/FileSystem/IOVec.hsc" #-}
alignment _ = 8
{-# LINE 53 "src/Streamly/FileSystem/IOVec.hsc" #-}
peek ptr = do
base <- (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr
{-# LINE 55 "src/Streamly/FileSystem/IOVec.hsc" #-}
len :: Word64 <- (\hsc_ptr -> peekByteOff hsc_ptr 8) ptr
{-# LINE 56 "src/Streamly/FileSystem/IOVec.hsc" #-}
return $ IOVec base len
poke ptr vec = do
let base = iovBase vec
len :: Word64 = iovLen vec
{-# LINE 60 "src/Streamly/FileSystem/IOVec.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 0) ptr base
{-# LINE 61 "src/Streamly/FileSystem/IOVec.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 8) ptr len
{-# LINE 62 "src/Streamly/FileSystem/IOVec.hsc" #-}
{-# LINE 63 "src/Streamly/FileSystem/IOVec.hsc" #-}
{-# LINE 75 "src/Streamly/FileSystem/IOVec.hsc" #-}
c_writev :: CInt -> Ptr IOVec -> CInt -> IO CSsize
c_writev = error "writev not implemented"
c_safe_writev :: CInt -> Ptr IOVec -> CInt -> IO CSsize
c_safe_writev = error "writev not implemented"
{-# LINE 81 "src/Streamly/FileSystem/IOVec.hsc" #-}