[Haskell-cafe] Opening the same file multiple times

Bulat Ziganshin bulatz at HotPOP.com
Tue Dec 13 04:29:51 EST 2005


Hello Einar,

Monday, December 12, 2005, 5:01:20 PM, you wrote:

EK> 3) Using System.Posix.IO

EK> Using the fd{Read,Close,Write} functions from System.Posix.IO
EK> could solve the problem - except that there is no way to
EK> write binary buffers (Ptr Word8) with the API. Thus no
EK> solution.

you can easily import these functions via FFI:

foreign import ccall unsafe "HsBase.h read"
   c_read :: CInt -> Ptr CChar -> CSize -> IO CSsize

moreover, they are already imported by System.Posix.Internals. and
even more - it works both under Windows and Unix


below is a part of file api i proposed for inclusion in ghc. i think
it is exactly what you need:


{-# OPTIONS_GHC -fvia-C -fglasgow-exts -fno-monomorphism-restriction#-}
module FD where

import Control.Monad
import Data.Bits
import Data.Int
import Data.Word
import Foreign.C.Types
import Foreign.C.Error
import Foreign.C.String
import Foreign.Marshal.Alloc
import Foreign.Ptr
import System.IO
import System.IO.Error
import System.Posix.Internals
import System.Posix.Types
import System.Win32

type FD = CInt                -- handle of open file
type CWFilePath   = CString   -- filename in C land
type CWFileOffset = COff      -- filesize or filepos in C land
type FileSize     = Integer   -- filesize or filepos in Haskell land
withCWFilePath = withCString  -- FilePath->CWFilePath conversion
peekCWFilePath = peekCString  -- CWFilePath->FilePath conversion

fdOpen :: String -> CInt -> CMode -> IO FD
fdOpen name access mode =
  modifyIOError (`ioeSetFileName` name) $
    withCWFilePath name $ \ p_name ->
      throwErrnoIfMinus1Retry "fdOpen" $
        c_open p_name access mode

fdClose :: FD -> IO ()
fdClose fd =
  throwErrnoIfMinus1Retry_ "fdClose" $
    c_close fd

fdGetBuf :: FD -> Ptr a -> Int -> IO Int
fdGetBuf fd buf size =
  fromIntegral `liftM`
    (throwErrnoIfMinus1Retry "fdGetBuf" $
      c_read fd (castPtr buf) (fromIntegral size))

fdPutBuf :: FD -> Ptr a -> Int -> IO ()
fdPutBuf fd buf size =
  throwErrnoIfMinus1Retry_ "fdPutBuf" $
    c_write fd (castPtr buf) (fromIntegral size)           -- to do: check that result==size?

fdTell :: FD -> IO FileSize
fdTell fd =
  fromIntegral `liftM`
    throwErrnoIfMinus1Retry "fdTell"
      (c_tell fd)

fdSeek :: FD -> SeekMode -> FileSize -> IO ()
fdSeek fd mode offset =
  throwErrnoIfMinus1Retry_ "fdSeek" $
    c_lseek fd (fromIntegral offset) whence
  where whence = case mode of
                   AbsoluteSeek -> sEEK_SET
                   RelativeSeek -> sEEK_CUR
                   SeekFromEnd  -> sEEK_END

fdFileSize :: FD -> IO FileSize
fdFileSize fd =
  fromIntegral `liftM`
    throwErrnoIfMinus1Retry "fdFileSize"
      (c_filelength fd)

{-open/close/truncate/dup

  new_fd <- throwErrnoIfMinus1 "dupHandle" $
                c_dup (fromIntegral (haFD h_))
  new_fd <- throwErrnoIfMinus1 "dupHandleTo" $
                c_dup2 (fromIntegral (haFD h_)) (fromIntegral (haFD hto_))
-}

foreign import ccall unsafe "HsBase.h tell"
   c_tell :: CInt -> IO COff

foreign import ccall unsafe "HsBase.h filelength"
   c_filelength :: CInt -> IO COff

foreign import ccall unsafe "__hscore_bufsiz"   dEFAULT_BUFFER_SIZE :: Int
foreign import ccall unsafe "__hscore_seek_cur" sEEK_CUR :: CInt
foreign import ccall unsafe "__hscore_seek_set" sEEK_SET :: CInt
foreign import ccall unsafe "__hscore_seek_end" sEEK_END :: CInt

i=fromIntegral





-- 
Best regards,
 Bulat                            mailto:bulatz at HotPOP.com





More information about the Haskell-Cafe mailing list