On 6 October 2011 14:58, Simon Marlow <marlo...@gmail.com> wrote:
> ... What you can do is make a withHandleFD:
>
>  withHandleFD :: Handle -> (FD -> IO a) -> IO a
>
> it's still quite dodgy, depending on what you do with the FD.  Perhaps it
> should be called unsafeWithHandleFD.
>
> Anyway, patches gratefully accepted...

Maybe something like this together with a big warning message
explaining the danger:

{-# LANGUAGE NamedFieldPuns #-}

module System.Posix.IO where

import Control.Concurrent.MVar (MVar)

unsafeWithHandleFd :: Handle -> (Fd -> IO a) -> IO a
unsafeWithHandleFd h@(FileHandle _ m)     f = unsafeWithHandleFd' h m f
unsafeWithHandleFd h@(DuplexHandle _ _ w) f = unsafeWithHandleFd' h w f

unsafeWithHandleFd' :: Handle -> MVar Handle__ -> (Fd -> IO a) -> IO a
unsafeWithHandleFd' h m f =
  withHandle' "unsafeWithHandleFd" h m $ \h_@Handle__{haDevice} ->
    case cast haDevice of
      Nothing -> ioError (ioeSetErrorString (mkIOError IllegalOperation
                                             "unsafeWithHandleFd"
(Just h) Nothing)
                          "handle is not a file descriptor")
      Just fd -> do
        x <- f (Fd (FD.fdFD fd))
        return (h_, x)

I'm not sure about the DuplexHandle case. I mimicked handleToFd by
only converting the write side but I have no idea why that is correct.

Bas

_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to