module System.IO.Uniform.File (
FileIO,
openFile
) where
import System.IO.Uniform
import System.IO.Uniform.External
import Foreign
import Foreign.C.String
import Foreign.C.Error
import qualified Data.ByteString as BS
import Control.Applicative ((<$>))
import System.Posix.Types (Fd(..))
instance UniformIO FileIO where
uRead s n = do
allocaArray n (
\b -> do
count <- c_recv (fd s) b $ fromIntegral n
if count < 0
then throwErrno "could not read"
else BS.packCStringLen (b, fromIntegral count)
)
uPut s t = do
BS.useAsCStringLen t (
\(str, n) -> do
count <- c_send (fd s) str $ fromIntegral n
if count < 0
then throwErrno "could not write"
else return ()
)
uClose s = do
f <- Fd <$> c_prepareToClose (fd s)
closeFd f
startTls _ _ = return . TlsIO $ nullPtr
isSecure _ = False
openFile :: String -> IO FileIO
openFile fileName = do
r <- withCString fileName (
\f -> fmap FileIO $ c_createFile f
)
if fd r == nullPtr
then throwErrno "could not open file"
else return r