Sven writes:
>
> -- Strange: hClose does *not* really close a file from fdToHandle!!
> -- No idea why. So we have to use this function...
A bug, I'd say. Fixed in the next release - patch appended for
interested parties.
I'm not sure how well documented this feature is, but GHC-2.0x Handles
have finalisers attached to them that will close the underlying
resources. So, if you don't need/want to be explicit about closing,
the garbage collector will do the job for you.
--Sigbjorn
*** hslibs/posix/cbits/libposix.h.~1~ Wed Jul 30 14:58:36 1997
--- hslibs/posix/cbits/libposix.h Thu Oct 16 18:23:16 1997
***************
*** 64,69 ****
--- 64,70 ----
/* For PosixIO only (finaliser for (FILE *) contained in Handles) */
extern void freeStdChannel PROTO((StgForeignObj));
+ extern void freeChannel PROTO((StgForeignObj));
extern I_ nocldstop;
*** hslibs/posix/src/PosixUtil.lhs.~1~ Wed Jul 30 14:58:41 1997
--- hslibs/posix/src/PosixUtil.lhs Thu Oct 16 17:45:22 1997
***************
*** 33,38 ****
--- 33,41 ----
instance CCallable Fd
instance CReturnable Fd
+ instance Eq Fd where
+ (FD# x#) == (FD# y#) = x# ==# y#
+
-- use with care.
intToFd :: Int -> Fd
intToFd (I# fd#) = FD# fd#
*** hslibs/posix/src/PosixIO.lhs.~1~ Wed Jul 30 14:58:40 1997
--- hslibs/posix/src/PosixIO.lhs Thu Oct 16 18:32:18 1997
***************
*** 37,42 ****
--- 37,44 ----
import Foreign
import PosixUtil
+ import PosixFiles ( stdInput, stdOutput, stdError )
+
createPipe :: IO (Fd, Fd)
createPipe =
***************
*** 112,124 ****
in
_ccall_ fdopen fd ft `thenIO_Prim` \ file_struct@(A# ptr#) ->
if file_struct /= (``NULL''::Addr) then
! -- You're asking for trouble if you try to create a Handle
! -- from stdInput, stdOutput, stdError ...
! #ifndef PAR
! makeForeignObj file_struct (``&freeStdChannel''::Addr) `thenIO_Prim` \
fp ->
! newHandle (handle_t fp Nothing False)
#else
! newHandle (handle_t file_struct Nothing False)
#endif
else
syserr "fdToHandle"
--- 114,134 ----
in
_ccall_ fdopen fd ft `thenIO_Prim` \ file_struct@(A# ptr#) ->
if file_struct /= (``NULL''::Addr) then
! {-
! A distinction is made here between std{Input,Output,Error} Fds
! and all others. The standard descriptors have a finaliser
! that will not close the underlying fd, the others have one
! that will. Or rather, the closing of the standard descriptors is
! delayed until the process exits.
! -}
! #ifndef __PARALLEL_HASKELL__
! (if fd == stdInput || fd == stdOutput || fd == stdError then
! makeForeignObj file_struct (``&freeStdChannel''::Addr)
! else
! makeForeignObj file_struct (``&freeChannel''::Addr)) `thenIO_Prim` \ fp
->
! newHandle (handle_t fp Nothing False)
#else
! newHandle (handle_t file_struct Nothing False)
#endif
else
syserr "fdToHandle"