[darcs-devel] [darcs #279] [wish] Use readline for line-editing

David Roundy droundy at abridgegame.org
Sat Mar 19 07:54:11 EST 2005


I'm CCing the libraries list on this, since it looks like it may be a bug
in signal handling with the readline module.  Or at least a highly
unexpected interaction of sorts.

Are we just out of luck, and should we just not use readline? Or is there
some way to interupt execution, and exit cleanly (such that the cleanup
portion of brackets is performed) in response to a sigINT while readline is
running?

I took a quick look at this, and also couldn't figure out what's going
wrong.  I know that signal handlers run in a separate haskell thread, so it
may be that perhaps the signal handler is just waiting until the ffi
function returns before running.  :( I'm feeling pessimistic at the moment,
and thinking that perhaps we simply can't use readline in darcs, since it's
hard to imagine that a thrown asynchronous exception will be able to
interrupt a FFI call...

On Fri, Mar 18, 2005 at 03:15:53PM -0500, Martin Bays via RT wrote:
> * Thursday, 2005-03-17 at 07:39 -0500 - David Roundy via RT <bugs at darcs.net>:
> > A quick look suggests that maybe you can use setCatchSignals? Alas, the
> > readline module seems almost 100% undocumented... :(
> 
> I did try that, to no avail. Which is to be expected, as signals are
> meant to be set to be caught by default.
> 
> There is indeed no documentation, but afaict the bits we're dealing with
> are just straight wrappers round the library calls. In particular
> 
> readline :: String -> IO (Maybe String)
> readline prompt = do
>     ptr <- withCString prompt readlineC
>     flip maybePeek ptr $ \ptr' -> do
>         line <- peekCString ptr'
>         free ptr'
>         return line
> foreign import ccall "readline" readlineC :: Ptr CChar -> IO (Ptr CChar)
> 
> > It may be that the problem is that readline blocks asynchronous
> > exceptions, and if that's the case, I'm not sure what we can do, since
> > darcs responds to sigINT by throwing an asynchronous exception, so that
> > we can use block in sensitive code to make sure hitting ctrl-C doesn't
> > corrupt anything.
> 
> I don't think that's the problem - it appears that the exceptions aren't
> being thrown until too late. What confuses me is just how late that
> is. AFAICT, the signals aren't being handled (in the sense of causing a
> throwDynTo) until some point well after the readline has finished. In
> particular, with the following cheap debugging redefinition in
> SignalHandler.lhs:
> 
> ih :: ThreadId -> Signal -> IO ()
> ih thid s =
>   do installHandler s (Catch $
>                        (\sig -> (print $ "throwing") >>
>                         throwDynTo thid sig) $
>                        SignalException s) Nothing
>      return ()
> 
> we get the following behaviour:
> 
> What is the version name? ^C
> What is the version name? ao^C^Ceu
> "throwing"
> "throwing"
> "throwing"
> Interrupted!
> 
> A signal is thrown for each SIGINT, but not until some point I haven't
> been able to determine. I do not understand this, so can't see how to fix
> it!
> 
> I'm not sure exactly how this fits into the picture, but interestingly
> there are issues even with something as simple as
> 
> import System.Console.Readline ( readline )
> import Maybe ( fromMaybe )
> main = do s <- readline "test"
>           print $ fromMaybe "noda" s
> 
> Here two INTs are required to actually exit... why, I can't figure out.
> 
> I fear I don't know what's going on with any of this, nor how to fix it.
> Hopefully the above will be of some use to someone who does.
-- 
David Roundy
http://www.darcs.net


More information about the Libraries mailing list