Difference between revisions of "Literate programming/Vim"

From HaskellWiki
Jump to navigation Jump to search
(Add section titles.)
 
Line 3: Line 3:
 
==lhaskell.vim==
 
==lhaskell.vim==
   
For highlighting of Literate Haskell files in vim, here's the latest (as of January 5th, 2008) version of lhaskell.vim for your reference:
+
For highlighting of Literate Haskell files in vim, here's the latest (as of April 29th, 2009) version of lhaskell.vim for your reference:
   
 
<code><pre>
 
<code><pre>
Line 12: Line 12:
 
" Maintainer: Haskell Cafe mailinglist <haskell-cafe@haskell.org>
 
" Maintainer: Haskell Cafe mailinglist <haskell-cafe@haskell.org>
 
" Original Author: Arthur van Leeuwen <arthurvl@cs.uu.nl>
 
" Original Author: Arthur van Leeuwen <arthurvl@cs.uu.nl>
" Last Change: Jan 05, 2008 by Kalman Noel
+
" Last Change: 2009 Apr 29
" Version: 1.02
+
" Version: 1.03
 
"
 
"
 
" Thanks to Ian Lynagh for thoughtful comments on initial versions and
 
" Thanks to Ian Lynagh for thoughtful comments on initial versions and
Line 37: Line 37:
 
" 2004 February 23: Cleaned up syntax highlighting for \begin{code} and
 
" 2004 February 23: Cleaned up syntax highlighting for \begin{code} and
 
" \end{code}, added some clarification to the attributions
 
" \end{code}, added some clarification to the attributions
  +
" 2008 July 1: Removed % from guess list, as it totally breaks plain
" 2008 January 05: Fixed broken highlighting when some totally common TeX
 
" environments or commands are used (document, section, ...)
+
" text markup guessing
  +
" 2009 April 29: Fixed highlighting breakage in TeX mode,
  +
" thanks to Kalman Noel
  +
"
   
   
Line 80: Line 83:
 
" - \part, \chapter, \section, \subsection, \subsubsection, etc
 
" - \part, \chapter, \section, \subsection, \subsubsection, etc
 
if b:lhs_markup == "unknown"
 
if b:lhs_markup == "unknown"
if search('%\|\\documentclass\|\\begin{\(code}\)\@!\|\\\(sub\)*section\|\\chapter|\\part','W') != 0
+
if search('\\documentclass\|\\begin{\(code}\)\@!\|\\\(sub\)*section\|\\chapter|\\part','W') != 0
 
let b:lhs_markup = "tex"
 
let b:lhs_markup = "tex"
 
else
 
else
Line 87: Line 90:
 
endif
 
endif
   
" If user wants us to highlight TeX syntax, read it.
+
" If user wants us to highlight TeX syntax or guess thinks it's TeX, read it.
 
if b:lhs_markup == "tex"
 
if b:lhs_markup == "tex"
 
if version < 600
 
if version < 600
Line 108: Line 111:
 
endif
 
endif
   
 
syntax cluster lhsTeXContainer contains=tex.*Zone,texAbstract
 
 
syntax region lhsHaskellBirdTrack start="^>" end="\%(^[^>]\)\@=" contains=@haskellTop,lhsBirdTrack containedin=@lhsTeXContainer
" Where Haskell is nested within TeX
 
 
syntax region lhsHaskellBeginEndBlock start="^\\begin{code}\s*$" matchgroup=NONE end="\%(^\\end{code}.*$\)\@=" contains=@haskellTop,@beginCode containedin=@lhsTeXContainer
syntax cluster lhstex contains=tex.*Zone,texAbstract
 
 
syntax region lhsHaskellBirdTrack start="^>" end="\%(^[^>]\)\@=" contains=@haskellTop,lhsBirdTrack containedIn=@lhstex
 
syntax region lhsHaskellBeginEndBlock start="^\\begin{code}\s*$" matchgroup=NONE end="\%(^\\end{code}.*$\)\@=" contains=@haskellTop,@beginCode containedIn=@lhstex
 
   
 
syntax match lhsBirdTrack "^>" contained
 
syntax match lhsBirdTrack "^>" contained
Line 154: Line 154:
 
===An alternate lhaskell.vim===
 
===An alternate lhaskell.vim===
   
Here's an alternate version I put together. This doesn't try to highlight tex, it just marks literate comments as regular comments. It does make an extra effort to highlight "part" "section" and "chapter."
+
Here's an alternate version. This doesn't try to highlight tex, it just marks literate comments as regular comments. It does make an extra effort to highlight "part" "section" and "chapter."
   
 
<code><pre>
 
<code><pre>

Latest revision as of 09:59, 29 April 2009

Literate Programming with Vim

lhaskell.vim

For highlighting of Literate Haskell files in vim, here's the latest (as of April 29th, 2009) version of lhaskell.vim for your reference:

" Vim syntax file
" Language:		Haskell with literate comments, Bird style,
"			TeX style and plain text surrounding
"			\begin{code} \end{code} blocks
" Maintainer:		Haskell Cafe mailinglist <haskell-cafe@haskell.org>
" Original Author:	Arthur van Leeuwen <arthurvl@cs.uu.nl>
" Last Change:		2009 Apr 29
" Version:		1.03
"
" Thanks to Ian Lynagh for thoughtful comments on initial versions and
" for the inspiration for writing this in the first place.
"
" This style guesses as to the type of markup used in a literate haskell
" file and will highlight (La)TeX markup if it finds any
" This behaviour can be overridden, both glabally and locally using
" the lhs_markup variable or b:lhs_markup variable respectively.
"
" lhs_markup	    must be set to either  tex	or  none  to indicate that
"		    you always want (La)TeX highlighting or no highlighting
"		    must not be set to let the highlighting be guessed
" b:lhs_markup	    must be set to eiterh  tex	or  none  to indicate that
"		    you want (La)TeX highlighting or no highlighting for
"		    this particular buffer
"		    must not be set to let the highlighting be guessed
"
"
" 2004 February 18: New version, based on Ian Lynagh's TeX guessing
"		    lhaskell.vim, cweb.vim, tex.vim, sh.vim and fortran.vim
" 2004 February 20: Cleaned up the guessing and overriding a bit
" 2004 February 23: Cleaned up syntax highlighting for \begin{code} and
"		    \end{code}, added some clarification to the attributions
" 2008 July 1:      Removed % from guess list, as it totally breaks plain
"                   text markup guessing
" 2009 April 29:    Fixed highlighting breakage in TeX mode, 
"                   thanks to Kalman Noel
"


" For version 5.x: Clear all syntax items
" For version 6.x: Quit when a syntax file was already loaded
if version < 600
  syntax clear
elseif exists("b:current_syntax")
  finish
endif

" First off, see if we can inherit a user preference for lhs_markup
if !exists("b:lhs_markup")
    if exists("lhs_markup")
	if lhs_markup =~ '\<\%(tex\|none\)\>'
	    let b:lhs_markup = matchstr(lhs_markup,'\<\%(tex\|none\)\>')
	else
	    echohl WarningMsg | echo "Unknown value of lhs_markup" | echohl None
	    let b:lhs_markup = "unknown"
	endif
    else
	let b:lhs_markup = "unknown"
    endif
else
    if b:lhs_markup !~ '\<\%(tex\|none\)\>'
	let b:lhs_markup = "unknown"
    endif
endif

" Remember where the cursor is, and go to upperleft
let s:oldline=line(".")
let s:oldcolumn=col(".")
call cursor(1,1)

" If no user preference, scan buffer for our guess of the markup to
" highlight. We only differentiate between TeX and plain markup, where
" plain is not highlighted. The heuristic for finding TeX markup is if
" one of the following occurs anywhere in the file:
"   - \documentclass
"   - \begin{env}       (for env != code)
"   - \part, \chapter, \section, \subsection, \subsubsection, etc
if b:lhs_markup == "unknown"
    if search('\\documentclass\|\\begin{\(code}\)\@!\|\\\(sub\)*section\|\\chapter|\\part','W') != 0
	let b:lhs_markup = "tex"
    else
	let b:lhs_markup = "plain"
    endif
endif

" If user wants us to highlight TeX syntax or guess thinks it's TeX, read it.
if b:lhs_markup == "tex"
    if version < 600
	source <sfile>:p:h/tex.vim
	set isk+=_
    else
	runtime! syntax/tex.vim
	unlet b:current_syntax
	" Tex.vim removes "_" from 'iskeyword', but we need it for Haskell.
	setlocal isk+=_
    endif
endif

" Literate Haskell is Haskell in between text, so at least read Haskell
" highlighting
if version < 600
    syntax include @haskellTop <sfile>:p:h/haskell.vim
else
    syntax include @haskellTop syntax/haskell.vim
endif

syntax cluster lhsTeXContainer contains=tex.*Zone,texAbstract
syntax region lhsHaskellBirdTrack start="^>" end="\%(^[^>]\)\@=" contains=@haskellTop,lhsBirdTrack containedin=@lhsTeXContainer
syntax region lhsHaskellBeginEndBlock start="^\\begin{code}\s*$" matchgroup=NONE end="\%(^\\end{code}.*$\)\@=" contains=@haskellTop,@beginCode containedin=@lhsTeXContainer

syntax match lhsBirdTrack "^>" contained

syntax match beginCodeBegin "^\\begin" nextgroup=beginCodeCode contained
syntax region beginCodeCode  matchgroup=texDelimiter start="{" end="}"
syntax cluster beginCode    contains=beginCodeBegin,beginCodeCode

" Define the default highlighting.
" For version 5.7 and earlier: only when not done already
" For version 5.8 and later: only when an item doesn't have highlighting yet
if version >= 508 || !exists("did_tex_syntax_inits")
  if version < 508
    let did_tex_syntax_inits = 1
    command -nargs=+ HiLink hi link <args>
  else
    command -nargs=+ HiLink hi def link <args>
  endif

  HiLink lhsBirdTrack Comment

  HiLink beginCodeBegin	      texCmdName
  HiLink beginCodeCode	      texSection

  delcommand HiLink
endif

" Restore cursor to original position, as it may have been disturbed
" by the searches in our guessing code
call cursor (s:oldline, s:oldcolumn)

unlet s:oldline
unlet s:oldcolumn

let b:current_syntax = "lhaskell"

" vim: ts=8

An alternate lhaskell.vim

Here's an alternate version. This doesn't try to highlight tex, it just marks literate comments as regular comments. It does make an extra effort to highlight "part" "section" and "chapter."

" Vim syntax file
" Language:     Haskell with literate comments
" Original Author:      John Williams <jrw@pobox.com>
" Maintainer:   Christopher Lane Hinson <lane@downstairspeople.org>
" Changes:      1998 November 7         original
"               2008 February 10        support literate haskell in the latex style

" For version 5.x: Clear all syntax items
" For version 6.x: Quit when a syntax file was already loaded
if version < 600
  syntax clear
elseif exists("b:current_syntax")
  finish
endif

" Include standard Haskell highlighting
syntax include @haskellTop syntax/haskell.vim

" Everything is a comment unless preceeded by > or
" bracketed by \begin{code} and \end{code}
" We have to go back and explicitly label >, \begin{code}, and \end{code} as comments
syn region  hsLiterateComment   start="\%^"     end="\%$" contains=hsBirdTrackLine,hsBeginEndZone,hsSectionHeaders
syn region  hsBirdTrackLine     start="^>"      end="\_$" contained contains=@haskellTop,hsLiterateCommentMarkers
syn region  hsBeginEndZone      start="\\begin{code}"   end="\\end{code}" keepend contained contains=@haskellTop,hsLiterateCommentMarkers
syn match   hsLiterateCommentMarkers "^>\|\\begin{code}\|\\end{code}" contained

syn region  hsSectionHeaders    start="\\\(sub\)\?\(section\|paragraph\){\|\\part{\|\\chapter"  end="}" contained

hi link hsLiterateCommentMarkers Comment

hi link hsSectionHeaders Title

let b:current_syntax = "lhs"