Skip to content

Commit

Permalink
Fixes haskell#35: fd{Read,Write} with ByteString payload
Browse files Browse the repository at this point in the history
This commit addes two new functions: fdReadBytes and fdWriteBytes.
They are like fdRead and fdWrite respectively but instead of
reading/writing String they use ByteStrings.
  • Loading branch information
mmhat committed May 15, 2021
1 parent 948326c commit aeda473
Show file tree
Hide file tree
Showing 3 changed files with 27 additions and 1 deletion.
1 change: 1 addition & 0 deletions System/Posix/IO.hsc
Original file line number Diff line number Diff line change
Expand Up @@ -35,6 +35,7 @@ module System.Posix.IO (
-- EAGAIN exceptions may occur for non-blocking IO!

fdRead, fdWrite,
fdReadBytes, fdWriteBytes,
fdReadBuf, fdWriteBuf,

-- ** Seeking
Expand Down
1 change: 1 addition & 0 deletions System/Posix/IO/ByteString.hsc
Original file line number Diff line number Diff line change
Expand Up @@ -35,6 +35,7 @@ module System.Posix.IO.ByteString (
-- EAGAIN exceptions may occur for non-blocking IO!

fdRead, fdWrite,
fdReadBytes, fdWriteBytes,
fdReadBuf, fdWriteBuf,

-- ** Seeking
Expand Down
26 changes: 25 additions & 1 deletion System/Posix/IO/Common.hsc
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
{-# LANGUAGE CApiFFI #-}
{-# LANGUAGE NondecreasingIndentation #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE Safe #-}
{-# LANGUAGE Trustworthy #-}

-----------------------------------------------------------------------------
-- |
Expand Down Expand Up @@ -32,6 +32,7 @@ module System.Posix.IO.Common (
-- EAGAIN exceptions may occur for non-blocking IO!

fdRead, fdWrite,
fdReadBytes, fdWriteBytes,
fdReadBuf, fdWriteBuf,

-- ** Seeking
Expand Down Expand Up @@ -60,6 +61,9 @@ module System.Posix.IO.Common (

) where

import Data.ByteString.Char8 as BC
import Data.ByteString.Internal as BI
import Data.ByteString.Unsafe as BU
import System.IO
import System.IO.Error
import System.Posix.Types
Expand Down Expand Up @@ -412,6 +416,20 @@ fdRead fd nbytes = do
s <- peekCStringLen (castPtr buf, fromIntegral n)
return (s, n)

-- | Read data from an 'Fd'.
-- Throws an exception if this is an invalid descriptor, or EOF has been
-- reached.
fdReadBytes :: Fd
-> ByteCount -- ^How many bytes to read
-> IO (ByteString, ByteCount) -- ^The bytes read, how many bytes were read.
fdReadBytes _fd 0 = return (BC.empty, 0)
fdReadBytes fd nbytes = do
BI.createUptoN' (fromIntegral nbytes) $ \ buf -> do
rc <- fdReadBuf fd buf nbytes
case rc of
0 -> ioError (ioeSetErrorString (mkIOError EOF "fdRead" Nothing Nothing) "EOF")
n -> return (fromIntegral n, n)

-- | Read data from an 'Fd' into memory. This is exactly equivalent
-- to the POSIX @read@ function.
fdReadBuf :: Fd
Expand All @@ -433,6 +451,12 @@ fdWrite fd str =
withCStringLen str $ \ (buf,len) ->
fdWriteBuf fd (castPtr buf) (fromIntegral len)

-- | Write a 'ByteString' to an 'Fd'.
fdWriteBytes :: Fd -> ByteString -> IO ByteCount
fdWriteBytes fd bs =
BU.unsafeUseAsCStringLen bs $ \ (buf,len) ->
fdWriteBuf fd (castPtr buf) (fromIntegral len)

-- | Write data from memory to an 'Fd'. This is exactly equivalent
-- to the POSIX @write@ function.
fdWriteBuf :: Fd
Expand Down

0 comments on commit aeda473

Please sign in to comment.