RE: Readline (was Re: state of ghc6 on sparc)

2003-06-22 Thread Mike Thomas
Hi Malcolm.

I tried this on both a Cygwin (environment variable TERM=cygwin) and a
Windows XP console with GHC 6.0.

Under Cygwin, these problems occurred:

1. ^K and ^L both appear as themselves, rather than causing deletion:

prompt> abc^Kefg

2. When editing an item in the history buffer, if I delete a one or more
characters and then move to the end of the line with the cursor, it "runs
off the end" with the same number of characters  added at the end. Those
characters are taken from the characters at what was previously the end of
the line eg:

prompt> hello

  delete 'l'

prompt> helo

  move to end of line:

prompt> heloo

(This does not happen with a new item, only with history items.)

This happens with a normal Windows XP command prompt too (that is, without
any Haskell program running) so I suspect that it is an overprinting of the
Windows terminal handling on your test program's terminal handling.

The interesting result of that is that successive invocations of the same
executable retain the command line history of previous runs.

I would expect substantially different results running under a Win98 command
line as console line editing is not provided on those older versions of the
OS.


Under the Windows XP command line prompt:

1. The stty system call is redundant:

  C:\lang\source\ghc\lineedit>le
'stty' is not recognized as an internal or external command,
operable program or batch file.
prompt>

Checking that the preprocessor symbol "i386_unknown_mingw32_TARGET" is not
defined fixed that.

2. - See points 1 and 2 of the Cygwin problems above and the conclusions
drawn there.


Cheers

Mike Thomas.



| -Original Message-
| From: [EMAIL PROTECTED]
| [mailto:[EMAIL PROTECTED] Behalf Of Malcolm
| Wallace
| Sent: Friday, June 20, 2003 2:39 AM
| To: [EMAIL PROTECTED]
| Cc: [EMAIL PROTECTED]
| Subject: Readline (was Re: state of ghc6 on sparc)
|
|
| Alastair Reid <[EMAIL PROTECTED]> writes:
|
| > It would be nice to have those bindings but just having backspace and
| > left-right cursors work would already be a huge improvement
| over nothing.
|
| OK, here is my contribution.  The attached module SimpleLineEditor
| is API-compatible with readline, and is a slight elaboration of
| the line editor currently distributed as part of hmake interactive.
| It does the basic stuff like backspace and left and right arrows.
| Today's addition was a simple history mechanism using (uggh!) an IORef.
|
| Because of the way I chose to implement a separation of
| keystroke-recognition from interpretation of the associated editing
| command, it should be reasonably straightforward to extend/change
| the keystrokes for different terminal types.  It should also be
| fairly easy to add more editing commands (e.g. there are commands
| for word-movement, and begin/end of line, but no key-binding and no
| interpretation yet either.)
|
| Perhaps we should add something like this to the hierarchical libs,
| in the readline package?  Then we can have some basic line-editing
| functionality available in a portable fashion, independent of whether
| any particular machine has the real readline library installed.
|
| Regards,
| Malcolm
|


___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Readline (was Re: state of ghc6 on sparc)

2003-06-20 Thread Simon Marlow
 
> Alastair Reid <[EMAIL PROTECTED]> writes:
> 
> > It would be nice to have those bindings but just having 
> backspace and 
> > left-right cursors work would already be a huge improvement 
> over nothing.
> 
> OK, here is my contribution.  The attached module SimpleLineEditor
> is API-compatible with readline, and is a slight elaboration of
> the line editor currently distributed as part of hmake interactive.

It seems to behave strangely here:  I can delete the prompt, and if I
move the cursor to the left and delete some characters, the characters
to the right of the cursor don't move.  Also, the backspace key doesn't
work, although C-Backspace does work (backspace works fine with
readline).  This is in an xterm; in a cygwin shell window different
strange things happen.

Cheers,
Simon

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: state of ghc6 on sparc

2003-06-19 Thread John Meacham
'editline' is a (BSD style) free readline clone. it works quite well. of
course a haskell clone might be more convienient. a google search will turn
up various references to it.
John

On Thu, Jun 19, 2003 at 11:46:43AM +0100, Alastair Reid wrote:
> On Thursday 19 June 2003 11:06 am, Malcolm Wallace wrote:
> > As I see it, the main problem is reproducing all the keybindings.
> > I'm certain that every user of readline has their own habitual set
> > of emacs keystrokes that differs slightly from everyone elses, so
> > inevitably the full complement will need to be supported.  Then there
> > is parsing of the .inputrc file which can /re/bind any keystroke.
> > And of course, just to be awkward, there are vi-mode users like me,
> > where the keystroke set is entirely different anyway.
> 
> It would be nice to have those bindings but just having backspace and 
> left-right cursors work would already be a huge improvement over nothing.
> 
> --
> Alastair
> 
> ___
> Glasgow-haskell-users mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
> 

-- 
---
John Meacham - California Institute of Technology, Alum. - [EMAIL PROTECTED]
---
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Readline (was Re: state of ghc6 on sparc)

2003-06-19 Thread Malcolm Wallace
Alastair Reid <[EMAIL PROTECTED]> writes:

> It would be nice to have those bindings but just having backspace and 
> left-right cursors work would already be a huge improvement over nothing.

OK, here is my contribution.  The attached module SimpleLineEditor
is API-compatible with readline, and is a slight elaboration of
the line editor currently distributed as part of hmake interactive.
It does the basic stuff like backspace and left and right arrows.
Today's addition was a simple history mechanism using (uggh!) an IORef.

Because of the way I chose to implement a separation of
keystroke-recognition from interpretation of the associated editing
command, it should be reasonably straightforward to extend/change
the keystrokes for different terminal types.  It should also be
fairly easy to add more editing commands (e.g. there are commands
for word-movement, and begin/end of line, but no key-binding and no
interpretation yet either.)

Perhaps we should add something like this to the hierarchical libs,
in the readline package?  Then we can have some basic line-editing
functionality available in a portable fashion, independent of whether
any particular machine has the real readline library installed.

Regards,
Malcolm
module SimpleLineEditor
  ( initialise  --  :: IO ()
  , getLineEdited   --  :: String -> IO String
  , delChars--  :: String -> IO ()
  ) where

import IO
import Monad (when)
import Char
import System.IO.Unsafe (unsafePerformIO)
import Data.IORef
import Maybe
import System (system)
#if USE_READLINE
import Readline
#endif

initialise :: IO ()
initialise = do
-- Note, we assume the terminal echos all input characters
system("stty cbreak")
hSetBuffering stdout NoBuffering
hSetBuffering stdin  NoBuffering
#if USE_READLINE
Readline.initialize
#endif

delChars :: String -> IO ()
delChars [] = return ()
delChars (_:xs) = do putStr "\BS \BS"
 delChars xs

-- getLineEdited relies on having the terminal in non-buffered mode,
-- therefore please ensure that `hSetBuffering NoBuffering' is called
-- before using this.

#if USE_READLINE

getLineEdited :: String -> IO (Maybe String)
getLineEdited prompt = do
  ms <- readline prompt
  case ms of 
Nothing -> return ms
Just s  -> when (not (all isSpace s)) (addHistory s) >> return ms

#else

-- nasty imperative state holds the command history
history :: IORef [String]
history = unsafePerformIO (newIORef [])

getLineEdited :: String -> IO (Maybe String)
getLineEdited prompt = do
putStr prompt
previous <- readIORef history
ms <- gl "" 0 ([],previous)
case ms of 
  Nothing -> return ms
  Just s  -> do when (not (all isSpace s))
 (writeIORef history (reverse s: previous))
return ms
  where
gl s 0 hist = do-- s is accumulated line (in reverse)
-- 0 is cursor position FROM THE END of the string
  cmd <- lineCmd
  case cmd of
Char c   -> gl (c:s) 0 hist
Accept   -> return (Just (reverse s))
Cancel   -> return Nothing
Delete L -> delChars "_" >> gl (if null s then s else tail s) 0 hist
Delete Begin -> delChars s >> gl "" 0 hist
Move L   -> if not (null s) then putStr ("\BS") >> gl s 1 hist
else gl s 0 hist
History  -> case hist of
  (fut, []) -> gl s 0 hist
  (fut, p:past) -> do delChars s
  putStr (reverse p)
  gl p 0 (s:fut, past)
Future   -> case hist of
  ([], past)-> gl s 0 hist
  (f:fut, past) -> do delChars s
  putStr (reverse f)
  gl f 0 (fut, s:past)
_-> gl s 0 hist

gl s n hist = do-- s is accumulated line, n(/=0) is cursor position
  cmd <- lineCmd
  case cmd of
Char c   -> do putStr (reverse (take n s))
   putStr (replicate n '\BS')
   gl (take n s ++ c: drop n s) n hist
Accept   -> return (Just (reverse s))
Cancel   -> return Nothing
Move R   -> do let n1 = n-1
   putStr (reverse (take n s)++" ")
   putStr (replicate n '\BS')
   gl s n1 hist
Delete R -> do let n1 = n-1
   putStr (reverse (take n1 s) ++ " ")
   putStr (replicate (n1+1) '\BS')
   gl (take n1 s ++ drop n s) n1 hist
Move L   -> do let n1 = n+1
   if n1 <= length s then do
   putStr ('\BS':reverse (take n1 s))
   putStr (replicate n1 '\BS')
   gl s n1 hist
 else do
   putStr (reverse s++" ")
 

Re: state of ghc6 on sparc

2003-06-19 Thread Peter Strand
On Wed, Jun 18, 2003 at 06:09:14PM +0200, Josef Svenningsson wrote:
> The only thing that I don't like is that the dist isn't compiled with
> readline. It makes working in ghci a nightmare (I need to use backspace
> often...).

A nice workaround for programs not supporting readline is to use a
line-editing wrapper such as ledit, which can be found here:

ftp://ftp.inria.fr/INRIA/Projects/cristal/Daniel.de_Rauglaudre/Tools/

It also has the additional feature that you can save the history
between sessions (which would be a nice addition to ghci..)


/Peter

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: state of ghc6 on sparc

2003-06-19 Thread Alastair Reid
On Thursday 19 June 2003 11:06 am, Malcolm Wallace wrote:
> As I see it, the main problem is reproducing all the keybindings.
> I'm certain that every user of readline has their own habitual set
> of emacs keystrokes that differs slightly from everyone elses, so
> inevitably the full complement will need to be supported.  Then there
> is parsing of the .inputrc file which can /re/bind any keystroke.
> And of course, just to be awkward, there are vi-mode users like me,
> where the keystroke set is entirely different anyway.

It would be nice to have those bindings but just having backspace and 
left-right cursors work would already be a huge improvement over nothing.

--
Alastair

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: state of ghc6 on sparc

2003-06-19 Thread Malcolm Wallace
"Simon Marlow" <[EMAIL PROTECTED]> writes:

> > | Making a working readline isn't that simple - you need to know something
> > | about the terminal properties for one, which means being able to use
> > | termcap or terminfo.

I expect that one can avoid termcap/terminfo by sticking to ANSI
terminal control codes for moving the cursor.  It isn't as powerful,
but probably adequate.

> > But if someone produced an adequate one that did the job, and 
> > that we could distribute with GHC, we'd surely use it, right? 
> >  To avoid these perpetual readline problems.
> 
> That would probably be a good idea, yes.

As I see it, the main problem is reproducing all the keybindings.
I'm certain that every user of readline has their own habitual set
of emacs keystrokes that differs slightly from everyone elses, so
inevitably the full complement will need to be supported.  Then there
is parsing of the .inputrc file which can /re/bind any keystroke.
And of course, just to be awkward, there are vi-mode users like me,
where the keystroke set is entirely different anyway.

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: state of ghc6 on sparc

2003-06-19 Thread Simon Marlow
 
> | > often...). The problem around this is in my opinion to make a
> | > Haskell98
> | > compliant trimmed down readline library which doesn't 
> depend on the c
> | > library. It shouldn't be too difficult. I don't expect 
> that people are
> | > using the full power of readline anyway.
> | 
> | Making a working readline isn't that simple - you need to 
> know something
> | about the terminal properties for one, which means being able to use
> | termcap or terminfo.
> 
> But if someone produced an adequate one that did the job, and 
> that we could distribute with GHC, we'd surely use it, right? 
>  To avoid these perpetual readline problems.

That would probably be a good idea, yes.

Cheers,
Simon
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: state of ghc6 on sparc

2003-06-19 Thread Simon Peyton-Jones
| > often...). The problem around this is in my opinion to make a
| > Haskell98
| > compliant trimmed down readline library which doesn't depend on the
c
| > library. It shouldn't be too difficult. I don't expect that people
are
| > using the full power of readline anyway.
| 
| Making a working readline isn't that simple - you need to know
something
| about the terminal properties for one, which means being able to use
| termcap or terminfo.

But if someone produced an adequate one that did the job, and that we
could distribute with GHC, we'd surely use it, right?  To avoid these
perpetual readline problems.

Simon

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: state of ghc6 on sparc

2003-06-18 Thread Simon Marlow
 
> On Wed, 18 Jun 2003, Isaac Jones wrote:
> > Can anyone enlighten me as to the state of the ghc6 sparc
> > distribution?  The file on Hal's web page mentioned some 
> time back is
> > not the same file as on the GHC web page (I note that the filenames
> > are different also).
> >
> > Are any of them known to work if installed in a non-standard place?
> >
> Here at Chalmers we use the first shipped version (I believe 
> this is the
> one on the GHC web page or an even earlier one...). I patched 
> it myself,
> it was very easy. I expect that the version on Hal's web page 
> should work since he said he fixed the bug.

Hal's version still has problems, I believe.  He said that he will try
to fix the problems soon.

> The only thing that I don't like is that the dist isn't compiled with
> readline. It makes working in ghci a nightmare (I need to use 
> backspace
> often...). The problem around this is in my opinion to make a 
> Haskell98
> compliant trimmed down readline library which doesn't depend on the c
> library. It shouldn't be too difficult. I don't expect that people are
> using the full power of readline anyway.

Making a working readline isn't that simple - you need to know something
about the terminal properties for one, which means being able to use
termcap or terminfo.

Cheers,
Simon

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: state of ghc6 on sparc

2003-06-18 Thread Josef Svenningsson
On Wed, 18 Jun 2003, Isaac Jones wrote:

> Hello :)
>
> Can anyone enlighten me as to the state of the ghc6 sparc
> distribution?  The file on Hal's web page mentioned some time back is
> not the same file as on the GHC web page (I note that the filenames
> are different also).
>
> Are any of them known to work if installed in a non-standard place?
>
Here at Chalmers we use the first shipped version (I believe this is the
one on the GHC web page or an even earlier one...). I patched it myself,
it was very easy. I expect that the version on Hal's web page should work
since he said he fixed the bug.

The only thing that I don't like is that the dist isn't compiled with
readline. It makes working in ghci a nightmare (I need to use backspace
often...). The problem around this is in my opinion to make a Haskell98
compliant trimmed down readline library which doesn't depend on the c
library. It shouldn't be too difficult. I don't expect that people are
using the full power of readline anyway.

Cheers,

/Josef

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


state of ghc6 on sparc

2003-06-18 Thread Isaac Jones
Hello :)

Can anyone enlighten me as to the state of the ghc6 sparc
distribution?  The file on Hal's web page mentioned some time back is
not the same file as on the GHC web page (I note that the filenames
are different also).

Are any of them known to work if installed in a non-standard place?


peace,

isaac
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users