Opening the same file multiple times

Hello It seems that opening the same file multiple times (one writer and multiple readers) is not supported at least on *nix with GHC. I want to use one Handle to use append data till the end of the file while other Handles perform random access IO with seeks on the file. Sharing the same Handle for all the threads is not possible since they perform seeks and may thus mess each other up. Hiding the Handle behind a mutex would limit concurrency more than I like. Thus I wanted to open multiple Handles to the file, but this seems quite hard. My best guess is to create a function like: #ifdef mingw32_HOST_OS openUnlocked fn mode = openBinaryFile fn mode #else openUnlocked fn mode = withMVar mutex $ do h <- openBinaryFile fn mode fd <- handleToFd h unlockFile $ fromIntegral fd return h {-# NOINLINE mutes #-} mutex = unsafePerformIO $ newMVar () #endif Is there really no simpler solution? - Einar Karttunen

Hello Einar, Monday, December 12, 2005, 8:43:15 AM, you wrote: EK> It seems that opening the same file multiple times (one writer EK> and multiple readers) is not supported at least on *nix with EK> GHC. I want to use one Handle to use append data till the EK> end of the file while other Handles perform random access EK> IO with seeks on the file. EK> Sharing the same Handle for all the threads is not possible EK> since they perform seeks and may thus mess each other up. EK> Hiding the Handle behind a mutex would limit concurrency EK> more than I like. may be you can use some tricks, for example read large binary block from file inside mutex and then parse it in memory? EK> Thus I wanted to open multiple Handles to the file, but EK> this seems quite hard. My best guess is to create a function EK> like: EK> #ifdef mingw32_HOST_OS EK> openUnlocked fn mode = openBinaryFile fn mode EK> #else EK> openUnlocked fn mode = withMVar mutex $ do EK> h <- openBinaryFile fn mode EK> fd <- handleToFd h EK> unlockFile $ fromIntegral fd EK> return h are you read implementation of handleToFd? -- | Extracts the 'Fd' from a 'Handle'. This function has the side effect -- of closing the 'Handle' and flushing its write buffer, if necessary. handleToFd :: Handle -> IO Fd handleToFd h = withHandle "handleToFd" h $ \ h_ -> do -- converting a Handle into an Fd effectively means -- letting go of the Handle; it is put into a closed -- state as a result. let fd = haFD h_ flushWriteBufferOnly h_ unlockFile (fromIntegral fd) -- setting the Handle's fd to (-1) as well as its 'type' -- to closed, is enough to disable the finalizer that -- eventually is run on the Handle. return (h_{haFD= (-1),haType=ClosedHandle}, Fd (fromIntegral fd)) there is also dupHandle but i'm not sure that it will help another possibility is to work with FDs directly. i can give you a mini-lib, which emulates Handle-like functions on FDs, but it will be very inefficient at char-by-char i/o -- Best regards, Bulat mailto:bulatz@HotPOP.com

On Mon, 2005-12-12 at 07:43 +0200, Einar Karttunen wrote:
Hello
It seems that opening the same file multiple times (one writer and multiple readers) is not supported at least on *nix with GHC. I want to use one Handle to use append data till the end of the file while other Handles perform random access IO with seeks on the file.
It states in the Haskell Report 21.2.3: http://haskell.org/onlinereport/io.html Implementations should enforce as far as possible, at least locally to the Haskell process, multiple-reader single-writer locking on files. That is, there may either be many handles on the same file which manage input, or just one handle on the file which manages output. If any open or semi-closed handle is managing a file for output, no new handle can be allocated for that file. If any open or semi-closed handle is managing a file for input, new handles can only be allocated if they do not manage output. Whether two files are the same is implementation-dependent, but they should normally be the same if they have the same absolute path name and neither has been renamed, for example. So yes, what you're trying to do is not supported by the standard IO library. GHC is doing the right thing and hugs is not. I'm not sure which layer implements the file locking so it may be that you can get underneath by using the System.Posix.IO functions. Duncan

On 12.12 12:06, Duncan Coutts wrote:
It states in the Haskell Report 21.2.3:
Thanks, for the pointer, but am looking for an extension in the non-haskell98 API to do it. It seems that things are quite problematic: 1) Use openFile or GHC.Handle.openFd Works in Hugs, fails as the standard mandates in GHC due to locking. This is fine. 2) Use openFile + handleToFd + unlockFile This seems like a good plan. Except handleToFd will close the Handle. 3) Using System.Posix.IO Using the fd{Read,Close,Write} functions from System.Posix.IO could solve the problem - except that there is no way to write binary buffers (Ptr Word8) with the API. Thus no solution. 4) Use System.Posix.IO.openFd + fdToHandle This appears to be nice on surface. Except fdToHandle locks the file, thus back to drawing board. 5) Use System.Posix.IO.openFd + fdToHandle + unlockFile Thus we have: * lock mutex - otherwise there is a race condition * System.Posix.IO.openFd - open the file emulating openFile * fdToHandle - convert the file to Handle locking it * unlockFile (fromIntegral fd) - now unlock the original fd * unlock mutex Is this really the most simple way of doing things? Most of the operations will also hit the disk, and be slow (safe) FFI calls. - Einar Karttunen

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@HotPOP.com
participants (3)
-
Bulat Ziganshin
-
Duncan Coutts
-
Einar Karttunen