{-# LINE 1 "Network/Socket/Posix/IOVec.hsc" #-}{-# OPTIONS_GHC -funbox-strict-fields #-}-- | Support module for the POSIX writev system call.moduleNetwork.Socket.Posix.IOVec(IOVec (..),withIOVec )whereimportForeign.Marshal.Array(allocaArray)importNetwork.Socket.Imports dataIOVec =IOVec {IOVec -> Ptr Word8
iovBase ::PtrWord8,IOVec -> CSize
iovLen ::CSize}instanceStorableIOVec wheresizeOf :: IOVec -> Int
sizeOf ~IOVec
_=(Int
16){-# LINE 23 "Network/Socket/Posix/IOVec.hsc" #-}alignment~_=alignment(0::CInt)peek :: Ptr IOVec -> IO IOVec
peek Ptr IOVec
p =doPtr Word8
base <-((\Ptr IOVec
hsc_ptr ->Ptr IOVec -> Int -> IO (Ptr Word8)
forall b. Ptr b -> Int -> IO (Ptr Word8)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOffPtr IOVec
hsc_ptr Int
0))Ptr IOVec
p {-# LINE 27 "Network/Socket/Posix/IOVec.hsc" #-}len<-((\hsc_ptr->peekByteOffhsc_ptr8))p{-# LINE 28 "Network/Socket/Posix/IOVec.hsc" #-}return$IOVecbaselenpoke :: Ptr IOVec -> IOVec -> IO ()
poke Ptr IOVec
p IOVec
iov =do((\Ptr IOVec
hsc_ptr ->Ptr IOVec -> Int -> Ptr Word8 -> IO ()
forall b. Ptr b -> Int -> Ptr Word8 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOffPtr IOVec
hsc_ptr Int
0))Ptr IOVec
p (IOVec -> Ptr Word8
iovBase IOVec
iov ){-# LINE 32 "Network/Socket/Posix/IOVec.hsc" #-}((\hsc_ptr->pokeByteOffhsc_ptr8))p(iovLeniov){-# LINE 33 "Network/Socket/Posix/IOVec.hsc" #-}-- | @withIOVec cs f@ executes the computation @f@, passing as argument a pair-- consisting of a pointer to a temporarily allocated array of pointers to-- IOVec made from @cs@ and the number of pointers (@length cs@).-- /Unix only/.withIOVec ::[(PtrWord8,Int)]->((PtrIOVec ,Int)->IOa )->IOa withIOVec :: forall a. [(Ptr Word8, Int)] -> ((Ptr IOVec, Int) -> IO a) -> IO a
withIOVec [](Ptr IOVec, Int) -> IO a
f =(Ptr IOVec, Int) -> IO a
f (Ptr IOVec
forall a. Ptr a
nullPtr,Int
0)withIOVec [(Ptr Word8, Int)]
cs (Ptr IOVec, Int) -> IO a
f =Int -> (Ptr IOVec -> IO a) -> IO a
forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b
allocaArrayInt
csLen ((Ptr IOVec -> IO a) -> IO a) -> (Ptr IOVec -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$\Ptr IOVec
aPtr ->do(Ptr IOVec -> (Ptr Word8, Int) -> IO ())
-> [Ptr IOVec] -> [(Ptr Word8, Int)] -> IO ()
forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> m c) -> [a] -> [b] -> m ()
zipWithM_Ptr IOVec -> (Ptr Word8, Int) -> IO ()
forall {a}. Integral a => Ptr IOVec -> (Ptr Word8, a) -> IO ()
pokeIov (Ptr IOVec -> [Ptr IOVec]
forall {a}. Ptr a -> [Ptr a]
ptrs Ptr IOVec
aPtr )[(Ptr Word8, Int)]
cs (Ptr IOVec, Int) -> IO a
f (Ptr IOVec
aPtr ,Int
csLen )wherecsLen :: Int
csLen =[(Ptr Word8, Int)] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length[(Ptr Word8, Int)]
cs ptrs :: Ptr a -> [Ptr a]
ptrs =(Ptr a -> Ptr a) -> Ptr a -> [Ptr a]
forall a. (a -> a) -> a -> [a]
iterate(Ptr a -> Int -> Ptr a
forall a b. Ptr a -> Int -> Ptr b
`plusPtr`IOVec -> Int
forall a. Storable a => a -> Int
sizeOf(Ptr Word8 -> CSize -> IOVec
IOVec Ptr Word8
forall a. Ptr a
nullPtrCSize
0))pokeIov :: Ptr IOVec -> (Ptr Word8, a) -> IO ()
pokeIov Ptr IOVec
ptr (Ptr Word8
sPtr ,a
sLen )=Ptr IOVec -> IOVec -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
pokePtr IOVec
ptr (IOVec -> IO ()) -> IOVec -> IO ()
forall a b. (a -> b) -> a -> b
$Ptr Word8 -> CSize -> IOVec
IOVec Ptr Word8
sPtr (a -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegrala
sLen )

AltStyle によって変換されたページ (->オリジナル) /