WANTED: grey line layout boxes in vim and emacs

I'd like some more help from the editors in getting 2d layout right without trying. Here's a mockup of vim with vertical grey bars delimiting layout: http://www.cse.unsw.edu.au/~dons/tmp/haskell+boxes.png Does anyone know how to get this effect in vim (or emacs)? Bonus points if the grey bars are draggable, changing the indenting. More bonus points for box-based navigation. -- Don

dons:
I'd like some more help from the editors in getting 2d layout right without trying. Here's a mockup of vim with vertical grey bars delimiting layout:
http://www.cse.unsw.edu.au/~dons/tmp/haskell+boxes.png
Does anyone know how to get this effect in vim (or emacs)?
Bonus points if the grey bars are draggable, changing the indenting. More bonus points for box-based navigation.
mbishop on #haskell pointed out that Kate can do this: http://img172.imageshack.us/my.php?image=indentbu9.png -- Don

On Thu, Dec 07, 2006 at 11:34:42AM +1100, Donald Bruce Stewart wrote:
I'd like some more help from the editors in getting 2d layout right without trying. Here's a mockup of vim with vertical grey bars delimiting layout:
http://www.cse.unsw.edu.au/~dons/tmp/haskell+boxes.png
Does anyone know how to get this effect in vim (or emacs)?
Bonus points if the grey bars are draggable, changing the indenting. More bonus points for box-based navigation.
Having played with haskell parsers for various reasons, the layout rule is quite tricky due to the rules involving 'parse-error'. if we could come up with a formulation that didn't have those. it would make things a whole lot nicer. something like an unexpected 'in', 'of', ')' '}' ']' might do it. the lexer would have to keep track of matching brackets.. hmmm.. John -- John Meacham - ⑆repetae.net⑆john⑈

On Wed, 2006-12-06 at 16:56 -0800, John Meacham wrote:
Having played with haskell parsers for various reasons, the layout rule is quite tricky due to the rules involving 'parse-error'. if we could come up with a formulation that didn't have those. it would make things a whole lot nicer. something like an unexpected 'in', 'of', ')' '}' ']' might do it. the lexer would have to keep track of matching brackets.. hmmm..
Yes, not having the parser->lexer feedback would be great! And this proposal seems like it should work quite well. Somebody with a lot more spare time than me should code it up and see how much real code it breaks. Carl Witty

On Wed, Dec 06, 2006 at 05:37:01PM -0800, Carl Witty wrote:
On Wed, 2006-12-06 at 16:56 -0800, John Meacham wrote:
Having played with haskell parsers for various reasons, the layout rule is quite tricky due to the rules involving 'parse-error'. if we could come up with a formulation that didn't have those. it would make things a whole lot nicer. something like an unexpected 'in', 'of', ')' '}' ']' might do it. the lexer would have to keep track of matching brackets.. hmmm..
Yes, not having the parser->lexer feedback would be great! And this proposal seems like it should work quite well. Somebody with a lot more spare time than me should code it up and see how much real code it breaks.
there is the helium layout rule: http://www.cs.uu.nl/helium/docs/LayoutRule.html which is similar to what I am thinking of but only has a special case for 'in'. my general thought is to take the layout rule algorithm from the haskell report, and add some more possibiliies to the 'layout stack'. so, right now it is layout :: [Token] -> [Int] -> [Token] where the first argument is the token stream, the next argument is a stack of layout contexts, and the result is the new token stream. now we change it to something like (in semi-psuedo haskell) data LContext = LExpects Token | LLevel Int expectableTokens = ['of','in',')','}',']'] and change the signature to layout :: [Token] -> [LContext] -> [Token] layout = ... now, LLevel nodes will be pushed just like the old algorihm, but whenever a 'case' for instance is encountered, a "LExpects 'of'" node will be pushed. now, whenever we get something in expectableTokens, an 'of' say, either the top of the stack is a LExpects 'of', in which case we pop it add the 'of' to the output stream and continue, or it is a 'LLevel' in which case we insert a '}' then pop the LLevel and continue (with the 'of' still in the input stream) I think something like this could work. the only odd bits I can think of are handling 'let's without 'in's as occur in 'do' blocks, and the comma, but I think we can integrate them too. does something like this seem like it will work? John -- John Meacham - ⑆repetae.net⑆john⑈

Motivated by some recent discussion, I thought I would explore the possibilty of formalizing the haskell layout rule without the dreaded parse-error clause, as in, one that can be completly handled by the lexer. motivated by that I have written a little program that takes a haskell file with layout on stdin and spits out one without layout on stdout. it can be gotten here: darcs get http://repetae.net/repos/getlaid/ the code is designed to make the layout algorithm completly transparent, so that we might experiment with it. The function layout in 'Layout.hs' is the single and complete layout algorithm and the only thing that need be modified by experimentors. I have come up with a simple improvement to the algorithm given in the paper that seems to catch a very large number of layouts. basically, whenever it comes across something that must come in matched pairs (, ), case of, if then. it pushes a special context onto the stack, when it comes across the closing token, it pops every layout context down to the special context. there is a special case for "in" that causes it to pop only up to the last context created with a "let", but not further. here is the complete algorithm (with my modification, sans the parse-error rule):
data Token = Token String | TokenVLCurly String !Int | TokenNL !Int deriving(Show)
data Context = NoLayout | Layout String !Int
-- the string on 'Layout' and 'TokenVLCurly' is the token that -- created the layout, always one of "where", "let", "do", or "of"
layout :: [Token] -> [Context] -> [Token] layout (TokenNL n:rs) (Layout h n':ls) | n == n' = semi:layout rs (Layout h n':ls) | n > n' = layout rs (Layout h n':ls) | n < n' = rbrace:layout (TokenNL n:rs) ls layout (TokenNL _:rs) ls = layout rs ls layout (TokenVLCurly h n:rs) (Layout h' n':ls) | n >= n' = lbrace:layout rs (Layout h n:Layout h' n':ls) | otherwise = error "inner layout can't be shorter than outer one" layout (TokenVLCurly h n:rs) ls = lbrace:layout rs (Layout h n:ls) layout (t@(Token s):rs) ls | s `elem` fsts layoutBrackets = t:layout rs (NoLayout:ls) layout (t@(Token s):rs) ls | s `elem` snds layoutBrackets = case ls of Layout _ _:ls -> rbrace:layout (t:rs) ls NoLayout:ls -> t:layout rs ls [] -> error $ "unexpected " ++ show s layout (t@(Token "in"):rs) ls = case ls of Layout "let" n:ls -> rbrace:t:layout rs ls Layout _ _:ls -> rbrace:layout (t:rs) ls ls -> t:layout rs ls layout (t:rs) ls = t:layout rs ls layout [] (Layout _ n:ls) = rbrace:layout [] ls layout [] [] = []
layoutBrackets = [ ("case","of"), ("if","then"), ("(",")"), ("[","]"), ("{","}") ]
now. there are a few cases it doesn't catch. the hanging case at the end of a guard for instance, I believe this can be solved easily by treating '|' and '=' as opening and closing pairs in lets and wheres '|' and '->' as opening and closing pairs in case bodies. it is easy to see which one you are in by looking at the context stack. commas are trickier and are the only other case I think we need to consider. I welcome people to experiment and send patches or brainstorm ideas, I have what I believe is a full solution percolating in my head, but am unhappy with it, I am going to sleep on it and see if it crystalizes by morning. In the meantime, perhaps someone can come up with something more elegant for dealing with the remaining cases. or at least find some real programs that this code breaks down on! (bug fixes for the lexer and everything are very much welcome. it will probably choke on some ghc extensions that would be trivial to add to the alex grammar) John -- John Meacham - ⑆repetae.net⑆john⑈

I have made some improvements to the algorithm, and I am happy to say that with some minor tweaks, it correctly lays out the programs in the nofib suite. the algorithm is not much more complicated than the current one in the report, but doesn't have the parse-error rule. it does require a single token of lookahead to look for an "in". darcs get http://repetae.net/repos/getlaid/ I have also added a mode so it can work as a ghc preprocesor, allowing very easy testing. just compile with. ghc -pgmF /path/to/getlaid -F --make Main.hs and it will automatically process all your files. Now, it isn't perfect. I can construct pathological examples that the old rule would parse, but this one won't. however, if those examples don't actually occur in practice, then that is not so much an issue. my program doesn't handle many non-haskell 98 extensions, but can probably be easily modified to do so. John -- John Meacham - ⑆repetae.net⑆john⑈

haskell-prime-bounces@haskell.org wrote:
I have made some improvements to the algorithm, and I am happy to say that with some minor tweaks, it correctly lays out the programs in the nofib suite.
the algorithm is not much more complicated than the current one in the report, but doesn't have the parse-error rule. it does require a single token of lookahead to look for an "in".
darcs get http://repetae.net/repos/getlaid/
I have also added a mode so it can work as a ghc preprocesor, allowing very easy testing. just compile with.
ghc -pgmF /path/to/getlaid -F --make Main.hs
and it will automatically process all your files.
Nice! I ran the GHC parser tests using your preprocessor, and get 9 failures out of 27 in the should_compile class. Some of these are bogus (problems with the lexer you're using rather than the layout preprocessor). The should_fail class all failed, but that's because column numbers are different in the preprocessed result, so the error messages changed, I'll need to look at these individually. I've attached a patch that corrects a couple of the failures in the should_compile class. Cheers, Simon

something like the attached vim script might work for small sources
(ignores all layout rules and keywords, just records increase/decrease
of indentation stack; builds up a rather large pattern of positions for
highlighting via :match).
(don't assume that this is the only, let alone the right way to do this,
and please pardon my rusty vimscript;-)
bonus tasks are left as exercises for the reader..
Claus
ps. a good interface for teaching vim about language syntax and
motion would be nice (or at least a dynamically loadable,
position-independent GHC API for use with vim's libcall..),
but I find that with visual highlighting of lines and blocks, Haskell
layout manipulation at least tends to be fairly straightforward
(I do not even use highlightling of the cursor column, which gives
you a vertical ruler)
----- Original Message -----
From: "Donald Bruce Stewart"
I'd like some more help from the editors in getting 2d layout right without trying. Here's a mockup of vim with vertical grey bars delimiting layout:
http://www.cse.unsw.edu.au/~dons/tmp/haskell+boxes.png
Does anyone know how to get this effect in vim (or emacs)?
Bonus points if the grey bars are draggable, changing the indenting. More bonus points for box-based navigation.
-- Don _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (5)
-
Carl Witty
-
Claus Reinke
-
dons@cse.unsw.edu.au
-
John Meacham
-
Simon Marlow