Re: Getting the file descriptor of a handle, without closing it

2012-03-12 Thread Simon Marlow

On 11/03/2012 01:31, Volker Wysk wrote:

Hi

This is an addition to my previous post.


This modified version of main seems to work:

main = do

fd- unsafeWithHandleFd stdin return
putStrLn (stdin: fd =  ++ show fd)

fd- unsafeWithHandleFd stdout return
putStrLn (stdout: fd =  ++ show fd)


The way I understand it, unsafeWithHandleFd's job is to keep a reference to
the hande, so it won't be garbage collected, while the action is still
running. Garbage collecting the handle would close it, as well as the
underlying file descriptor, while the latter is still in use by the action.
This can't happen as long as use of the file descriptor is encapsulated in the
action.

This encapsulation can be circumvented by returning the file descriptor, and
that's what the modified main function above does. This should usually never be
done.


Right.  The problem with this:

-- Blocks
   unsafeWithHandleFd stdout $ \fd -
  putStrLn (stdout: fd =  ++ show fd)

is that unsafeWithHandleFd is holding the lock on stdout, while you try 
to write to it with putStrLn.  The implementation of unsafeWithHandleFd 
could probably be fixed to avoid this - as you say, all it needs is to 
hold a reference to the Handle until the function has returned.  The 
usual way to hold a reference to something is to use touch#.



However, I want to use it with stdin, stdout and stderr, only.


Is there some reason you can't just use 0, 1, and 2?

 These three

should never be garbage collected, should they? I think it would be safe to
use unsafeWithHandleFd this way. Am I right?


I wouldn't do that, but you're probably right that it is safe right now. 
(but no guarantees that it will continue to work for ever.)


Cheers,
Simon


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


Re: Getting the file descriptor of a handle, without closing it

2012-03-12 Thread Volker Wysk
Am Montag 12 März 2012, 12:31:27 schrieb Simon Marlow:
 On 11/03/2012 01:31, Volker Wysk wrote:
  However, I want to use it with stdin, stdout and stderr, only.
 
 Is there some reason you can't just use 0, 1, and 2?

This is complicated. I want to be able to fork a child action, and communicate 
with it through stdin/stdout. I also want to be able to replace the child with 
an external program, and communicate with it through a stdout-stdin pipe. 
Something like this:

  subproc (outm Durch die Röhre -|- exec /bin/cat [])

I don't rely on stdin/-out/-err still being open. One might be closed, and the 
file descriptor might be reallocated (for a subsequently opened file or 
whatever). I also don't rely on stdin being fd 0, stdout being fd 1, stderr 
being fd 2.

If you really want to know what's going on, here is the documentation:

http://volker-wysk.de/hsshellscript/apidoc/HsShellScript.html#v%3Aexecute_file
 

  These three
  should never be garbage collected, should they? I think it would be safe
  to use unsafeWithHandleFd this way. Am I right?
 
 I wouldn't do that, but you're probably right that it is safe right now.
 (but no guarantees that it will continue to work for ever.)

So I need a fixed unsafeWithHandleFd, for it to work forever?

I guess, I'll leave it as it is, for now.


Cheers
Volker

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


Getting the file descriptor of a handle, without closing it

2012-03-10 Thread Volker Wysk
Hello!

A few months ago, I started a discussion about how to extract the file 
descriptor of a handle, without the side effect of closing the handle. Bas van 
Dijk kindly provided the following function:

unsafeWithHandleFd :: Handle - (Fd - IO a) - IO a

(The action in the second argument is applied to the file descriptor of the 
handle in the first argument.)

Now I'm trying to use it, but it appears to have a bug. This program shows it:


snip--

import IO
import GHC.IO.Handle.Types-- haType, haDevice
import GHC.IO.Handle.Internals-- withHandle', do_operation
import System.Posix.Types -- Fd
import System.IO.Error-- ioeSetErrorString
import Data.Typeable  -- cast
import GHC.IO.Exception   -- IllegalOperation
import GHC.IO.FD hiding (stdin, stdout, stderr)   -- fdFD
import Foreign.C  -- CInt
import Control.Concurrent.MVar (MVar)


main = do
   -- Works okay
   unsafeWithHandleFd stdin $ \fd -
  putStrLn (stdin: fd =  ++ show fd)
  
   -- Blocks
   unsafeWithHandleFd stdout $ \fd -
  putStrLn (stdout: fd =  ++ show fd)


-- By Bas van Dijk

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 (System.IO.Error.ioeSetErrorString 
  (System.IO.Error.mkIOError IllegalOperation 
   unsafeWithHandleFd (Just h) Nothing)
 handle is not a file descriptor)
  Just fd - do
x - f (Fd (GHC.IO.FD.fdFD fd))
return (h_, x)


snip--

The first call of unsafeWithHandleFd, works as expected. The second one blocks.


I need unsafeWithHandleFd, or something similar, in order to port my 
HsShellScript library (http://volker-wysk.de/hsshellscript/index.html) to the 
current version of GHC. 

If someone who understands the internals of the GHC IO libraries, had a hint, 
or even a fix, I'd be very grateful.


Sincerely,
Volker Wysk

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


Re: Getting the file descriptor of a handle, without closing it

2012-03-10 Thread Volker Wysk
Hi

This is an addition to my previous post.


This modified version of main seems to work:

main = do

   fd - unsafeWithHandleFd stdin return
   putStrLn (stdin: fd =  ++ show fd)
   
   fd - unsafeWithHandleFd stdout return
   putStrLn (stdout: fd =  ++ show fd)


The way I understand it, unsafeWithHandleFd's job is to keep a reference to 
the hande, so it won't be garbage collected, while the action is still 
running. Garbage collecting the handle would close it, as well as the 
underlying file descriptor, while the latter is still in use by the action. 
This can't happen as long as use of the file descriptor is encapsulated in the 
action.

This encapsulation can be circumvented by returning the file descriptor, and 
that's what the modified main function above does. This should usually never be 
done.

However, I want to use it with stdin, stdout and stderr, only. These three 
should never be garbage collected, should they? I think it would be safe to 
use unsafeWithHandleFd this way. Am I right?


unsafeWithHandleFd is still broken (see previous message), but for my purposes 
it wouldn't necessarily need to be fixed.


Happy hacking
Volker Wysk

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


Re: Getting the file descriptor of a handle, without closing it

2012-03-10 Thread John Meacham
Can you use 'dup' to copy the file descriptor and return that version?
That will keep a reference to the file even if haskell closes the
original descriptor.

John


On Sat, Mar 10, 2012 at 5:31 PM, Volker Wysk p...@volker-wysk.de wrote:
 Hi

 This is an addition to my previous post.


 This modified version of main seems to work:

 main = do

   fd - unsafeWithHandleFd stdin return
   putStrLn (stdin: fd =  ++ show fd)

   fd - unsafeWithHandleFd stdout return
   putStrLn (stdout: fd =  ++ show fd)


 The way I understand it, unsafeWithHandleFd's job is to keep a reference to
 the hande, so it won't be garbage collected, while the action is still
 running. Garbage collecting the handle would close it, as well as the
 underlying file descriptor, while the latter is still in use by the action.
 This can't happen as long as use of the file descriptor is encapsulated in the
 action.

 This encapsulation can be circumvented by returning the file descriptor, and
 that's what the modified main function above does. This should usually never 
 be
 done.

 However, I want to use it with stdin, stdout and stderr, only. These three
 should never be garbage collected, should they? I think it would be safe to
 use unsafeWithHandleFd this way. Am I right?


 unsafeWithHandleFd is still broken (see previous message), but for my purposes
 it wouldn't necessarily need to be fixed.


 Happy hacking
 Volker Wysk

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

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


Getting the file descriptor from a handle, without closing it

2011-10-01 Thread Volker Wysk
Hello!

I need to get the file descriptors of some handles, but the handles should not 
be modified. They should not be closed by the operation.

I guess, that the handle gets closed for a reason. But I'm using the revealed 
file descriptors in a way which should pose no problems for the integrity of 
the GHC library.

In order to make a non-closing handleToFd function, I'm studying GHC's library 
source code. But there's a lot which I can't make much sense, because it uses 
non-standard language features (GHC extensions), which I'm not familiar with.

I don't mean you to explain these GHC extensions to me. I just want to give an 
impression of the problems I encounter:


1.

data FD = FD {
  fdFD :: {-# UNPACK #-} !CInt,
  fdIsNonBlocking :: {-# UNPACK #-} !Int
 }

What is that exclamation mark? And that {-# UNPACK #-}?


2.

handleToFd' :: Handle - Handle__ - IO (Handle__, Fd)
handleToFd' h h_@Handle__{haType=_,..} = do
  case cast haDevice of
   -- ...

haDevice should be a function. How could you cast it?


3.

data Handle__
  = forall dev enc_state dec_state . 
  (IODevice dev, BufferedIO dev, Typeable dev) =
Handle__ {
  -- ...
}
deriving Typeable

What's that forall thing?


4.

handleToFd' h h_@Handle__{haType=_,..} = do
  case cast haDevice of
Nothing - -- ...
Just fd - do
  -- ...
  return (Handle__{haType=ClosedHandle,..}, 
 Fd (fromIntegral (FD.fdFD fd)))

What's this .. inside Handle__{haType=ClosedHandle,..}?


If anyone can point out to me, how this non-blocking handleToFd function 
should be made, I would be grateful.

Greetings
Volker Wysk


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


Re: Getting the file descriptor from a handle, without closing it

2011-10-01 Thread Volker Wysk


On Saturday 01 October 2011 08:30:40 Volker Wysk wrote:
 If anyone can point out to me, how this non-blocking handleToFd function
 should be made, I would be grateful.

This should be non-CLOSING handleToFd function. Sorry.

Volker

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


Re: Getting the file descriptor from a handle, without closing it

2011-10-01 Thread Bas van Dijk
On 1 October 2011 08:30, Volker Wysk p...@volker-wysk.de wrote:
 1.

 data FD = FD {
  fdFD :: {-# UNPACK #-} !CInt,
  fdIsNonBlocking :: {-# UNPACK #-} !Int
  }

 What is that exclamation mark?

That's a strictness annotation and is haskell98/2010:

http://www.haskell.org/onlinereport/haskell2010/haskellch4.html#x10-680004.2

And that {-# UNPACK #-}?

To quote:

http://www.haskell.org/ghc/docs/latest/html/users_guide/pragmas.html#unpack-pragma

The UNPACK indicates to the compiler that it should unpack the
contents of a constructor field into the constructor itself, removing
a level of indirection

 2.

 handleToFd' :: Handle - Handle__ - IO (Handle__, Fd)
 handleToFd' h h_@Handle__{haType=_,..} = do
  case cast haDevice of
       -- ...

 haDevice should be a function. How could you cast it?

Note the .. in the record pattern. That is a language extension called
RecordWildCards. It replaces each elided field f by the pattern f = f:

http://www.haskell.org/ghc/docs/latest/html/users_guide/syntax-extns.html#record-wildcards

 3.

 data Handle__
  = forall dev enc_state dec_state .
      (IODevice dev, BufferedIO dev, Typeable dev) =
    Handle__ {
      -- ...
    }
    deriving Typeable

 What's that forall thing?

Handle__ is an existentially quantified data constructors:

http://www.haskell.org/ghc/docs/latest/html/users_guide/data-type-extensions.html#existential-quantification

 4.

 handleToFd' h h_@Handle__{haType=_,..} = do
  case cast haDevice of
    Nothing - -- ...
    Just fd - do
      -- ...
      return (Handle__{haType=ClosedHandle,..},
                                 Fd (fromIntegral (FD.fdFD fd)))

 What's this .. inside Handle__{haType=ClosedHandle,..}?

See answer of 2

Regards,

Bas

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