ignore on .netrwhist
[my-vim-dotfolder.git] / PACKAGES / haskellmode-20100622.vba
blob5bbe500cbb96a097aa0120f9b47a8a8d1a9e721a
1 " Vimball Archiver by Charles E. Campbell, Jr., Ph.D.
2 UseVimball
3 finish
4 compiler/ghc.vim        [[[1
5 536
7 " Vim Compiler File
8 " Compiler:     GHC
9 " Maintainer:   Claus Reinke <claus.reinke@talk21.com>
10 " Last Change:  22/06/2010
12 " part of haskell plugins: http://projects.haskell.org/haskellmode-vim
14 " ------------------------------ paths & quickfix settings first
17 if exists("current_compiler") && current_compiler == "ghc"
18   finish
19 endif
20 let current_compiler = "ghc"
22 let s:scriptname = "ghc.vim"
24 if !haskellmode#GHC() | finish | endif
25 if (!exists("b:ghc_staticoptions"))
26   let b:ghc_staticoptions = ''
27 endif
29 " set makeprg (for quickfix mode) 
30 execute 'setlocal makeprg=' . g:ghc . '\ ' . escape(b:ghc_staticoptions,' ') .'\ -e\ :q\ %'
31 "execute 'setlocal makeprg=' . g:ghc .'\ -e\ :q\ %'
32 "execute 'setlocal makeprg=' . g:ghc .'\ --make\ %'
34 " quickfix mode: 
35 " fetch file/line-info from error message
36 " TODO: how to distinguish multiline errors from warnings?
37 "       (both have the same header, and errors have no common id-tag)
38 "       how to get rid of first empty message in result list?
39 setlocal errorformat=
40                     \%-Z\ %#,
41                     \%W%f:%l:%c:\ Warning:\ %m,
42                     \%E%f:%l:%c:\ %m,
43                     \%E%>%f:%l:%c:,
44                     \%+C\ \ %#%m,
45                     \%W%>%f:%l:%c:,
46                     \%+C\ \ %#%tarning:\ %m,
48 " oh, wouldn't you guess it - ghc reports (partially) to stderr..
49 setlocal shellpipe=2>
51 " ------------------------- but ghc can do a lot more for us..
54 " allow map leader override
55 if !exists("maplocalleader")
56   let maplocalleader='_'
57 endif
59 " initialize map of identifiers to their types
60 " associate type map updates to changedtick
61 if !exists("b:ghc_types")
62   let b:ghc_types = {}
63   let b:my_changedtick = b:changedtick
64 endif
66 if exists("g:haskell_functions")
67   finish
68 endif
69 let g:haskell_functions = "ghc"
71 " avoid hit-enter prompts
72 set cmdheight=3
74 " edit static GHC options
75 " TODO: add completion for options/packages?
76 command! GHCStaticOptions call GHC_StaticOptions()
77 function! GHC_StaticOptions()
78   let b:ghc_staticoptions = input('GHC static options: ',b:ghc_staticoptions)
79   execute 'setlocal makeprg=' . g:ghc . '\ ' . escape(b:ghc_staticoptions,' ') .'\ -e\ :q\ %'
80   let b:my_changedtick -=1
81 endfunction
83 map <LocalLeader>T :call GHC_ShowType(1)<cr>
84 map <LocalLeader>t :call GHC_ShowType(0)<cr>
85 function! GHC_ShowType(addTypeDecl)
86   let namsym   = haskellmode#GetNameSymbol(getline('.'),col('.'),0)
87   if namsym==[]
88     redraw
89     echo 'no name/symbol under cursor!'
90     return 0
91   endif
92   let [_,symb,qual,unqual] = namsym
93   let name  = qual=='' ? unqual : qual.'.'.unqual
94   let pname = ( symb ? '('.name.')' : name ) 
95   call GHC_HaveTypes()
96   if !has_key(b:ghc_types,name)
97     redraw
98     echo pname "type not known"
99   else
100     redraw
101     for type in split(b:ghc_types[name],' -- ')
102       echo pname "::" type
103       if a:addTypeDecl
104         call append( line(".")-1, pname . " :: " . type )
105       endif
106     endfor
107   endif
108 endfunction
110 " show type of identifier under mouse pointer in balloon
111 " TODO: it isn't a good idea to tie potentially time-consuming tasks
112 "       (querying GHCi for the types) to cursor movements (#14). Currently,
113 "       we ask the user to call :GHCReload explicitly. Should there be an
114 "       option to reenable the old implicit querying?
115 if has("balloon_eval")
116   set ballooneval
117   set balloondelay=600
118   set balloonexpr=GHC_TypeBalloon()
119   function! GHC_TypeBalloon()
120     if exists("b:current_compiler") && b:current_compiler=="ghc" 
121       let [line] = getbufline(v:beval_bufnr,v:beval_lnum)
122       let namsym = haskellmode#GetNameSymbol(line,v:beval_col,0)
123       if namsym==[]
124         return ''
125       endif
126       let [start,symb,qual,unqual] = namsym
127       let name  = qual=='' ? unqual : qual.'.'.unqual
128       let pname = name " ( symb ? '('.name.')' : name )
129       if b:ghc_types == {} 
130         redraw
131         echo "no type information (try :GHGReload)"
132       elseif (b:my_changedtick != b:changedtick)
133         redraw
134         echo "type information may be out of date (try :GHGReload)"
135       endif
136       " silent call GHC_HaveTypes()
137       if b:ghc_types!={}
138         if has("balloon_multiline")
139           return (has_key(b:ghc_types,pname) ? split(b:ghc_types[pname],' -- ') : '') 
140         else
141           return (has_key(b:ghc_types,pname) ? b:ghc_types[pname] : '') 
142         endif
143       else
144         return ''
145       endif
146     else
147       return ''
148     endif
149   endfunction
150 endif
152 map <LocalLeader>si :call GHC_ShowInfo()<cr>
153 function! GHC_ShowInfo()
154   let namsym   = haskellmode#GetNameSymbol(getline('.'),col('.'),0)
155   if namsym==[]
156     redraw
157     echo 'no name/symbol under cursor!'
158     return 0
159   endif
160   let [_,symb,qual,unqual] = namsym
161   let name = qual=='' ? unqual : (qual.'.'.unqual)
162   let output = GHC_Info(name)
163   pclose | new 
164   setlocal previewwindow
165   setlocal buftype=nofile
166   setlocal noswapfile
167   put =output
168   wincmd w
169   "redraw
170   "echo output
171 endfunction
173 " fill the type map, unless nothing has changed since the last attempt
174 function! GHC_HaveTypes()
175   if b:ghc_types == {} && (b:my_changedtick != b:changedtick)
176     let b:my_changedtick = b:changedtick
177     return GHC_BrowseAll()
178   endif
179 endfunction
181 " update b:ghc_types after successful make
182 au QuickFixCmdPost make if GHC_CountErrors()==0 | silent call GHC_BrowseAll() | endif
184 " count only error entries in quickfix list, ignoring warnings
185 function! GHC_CountErrors()
186   let c=0
187   for e in getqflist() | if e.type=='E' && e.text !~ "^[ \n]*Warning:" | let c+=1 | endif | endfor
188   return c
189 endfunction
191 command! GHCReload call GHC_BrowseAll()
192 function! GHC_BrowseAll()
193   " let imports = haskellmode#GatherImports()
194   " let modules = keys(imports[0]) + keys(imports[1])
195   let b:my_changedtick = b:changedtick
196   let imports = {} " no need for them at the moment
197   let current = GHC_NameCurrent()
198   let module = current==[] ? 'Main' : current[0]
199   if haskellmode#GHC_VersionGE([6,8,1])
200     return GHC_BrowseBangStar(module)
201   else
202     return GHC_BrowseMultiple(imports,['*'.module])
203   endif
204 endfunction
206 function! GHC_NameCurrent()
207   let last = line("$")
208   let l = 1
209   while l<last
210     let ml = matchlist( getline(l), '^module\s*\([^ (]*\)')
211     if ml != []
212       let [_,module;x] = ml
213       return [module]
214     endif
215     let l += 1
216   endwhile
217   redraw
218   echo "cannot find module header for file " . expand("%")
219   return []
220 endfunction
222 function! GHC_BrowseBangStar(module)
223   redraw
224   echo "browsing module " a:module
225   let command = ":browse! *" . a:module
226   let orig_shellredir = &shellredir
227   let &shellredir = ">" " ignore error/warning messages, only output or lack of it
228   let output = system(g:ghc . ' ' . b:ghc_staticoptions . ' -v0 --interactive ' . expand("%") , command )
229   let &shellredir = orig_shellredir
230   return GHC_ProcessBang(a:module,output)
231 endfunction
233 function! GHC_BrowseMultiple(imports,modules)
234   redraw
235   echo "browsing modules " a:modules
236   let command = ":browse " . join( a:modules, " \n :browse ") 
237   let command = substitute(command,'\(:browse \(\S*\)\)','putStrLn "-- \2" \n \1','g')
238   let output = system(g:ghc . ' ' . b:ghc_staticoptions . ' -v0 --interactive ' . expand("%") , command )
239   return GHC_Process(a:imports,output)
240 endfunction
242 function! GHC_Info(what)
243   " call GHC_HaveTypes()
244   let output = system(g:ghc . ' ' . b:ghc_staticoptions . ' -v0 --interactive ' . expand("%"), ":info ". a:what)
245   return output
246 endfunction
248 function! GHC_ProcessBang(module,output)
249   let module      = a:module
250   let b           = a:output
251   let linePat     = '^\(.\{-}\)\n\(.*\)'
252   let contPat     = '\s\+\(.\{-}\)\n\(.*\)'
253   let typePat     = '^\(\)\(\S*\)\s*::\(.*\)'
254   let commentPat  = '^-- \(\S*\)'
255   let definedPat  = '^-- defined locally'
256   let importedPat = '^-- imported via \(.*\)'
257   if !(b=~commentPat)
258     echo s:scriptname.": GHCi reports errors (try :make?)"
259     return 0
260   endif
261   let b:ghc_types = {}
262   let ml = matchlist( b , linePat )
263   while ml != []
264     let [_,l,rest;x] = ml
265     let mlDecl = matchlist( l, typePat )
266     if mlDecl != []
267       let [_,indent,id,type;x] = mlDecl
268       let ml2 = matchlist( rest , '^'.indent.contPat )
269       while ml2 != []
270         let [_,c,rest;x] = ml2
271         let type .= c
272         let ml2 = matchlist( rest , '^'.indent.contPat )
273       endwhile
274       let id   = substitute( id, '^(\(.*\))$', '\1', '')
275       let type = substitute( type, '\s\+', " ", "g" )
276       " using :browse! *<current>, we get both unqualified and qualified ids
277       let qualified = (id =~ '\.') && (id =~ '[A-Z]')
278       let b:ghc_types[id] = type
279       if !qualified
280         for qual in qualifiers
281           let b:ghc_types[qual.'.'.id] = type
282         endfor
283       endif
284     else
285       let mlImported = matchlist( l, importedPat )
286       let mlDefined  = matchlist( l, definedPat )
287       if mlImported != []
288         let [_,modules;x] = mlImported
289         let qualifiers = split( modules, ', ' )
290       elseif mlDefined != []
291         let qualifiers = [module]
292       endif
293     endif
294     let ml = matchlist( rest , linePat )
295   endwhile
296   return 1
297 endfunction
299 function! GHC_Process(imports,output)
300   let b       = a:output
301   let imports = a:imports
302   let linePat = '^\(.\{-}\)\n\(.*\)'
303   let contPat = '\s\+\(.\{-}\)\n\(.*\)'
304   let typePat = '^\(\s*\)\(\S*\)\s*::\(.*\)'
305   let modPat  = '^-- \(\S*\)'
306   " add '-- defined locally' and '-- imported via ..'
307   if !(b=~modPat)
308     echo s:scriptname.": GHCi reports errors (try :make?)"
309     return 0
310   endif
311   let b:ghc_types = {}
312   let ml = matchlist( b , linePat )
313   while ml != []
314     let [_,l,rest;x] = ml
315     let mlDecl = matchlist( l, typePat )
316     if mlDecl != []
317       let [_,indent,id,type;x] = mlDecl
318       let ml2 = matchlist( rest , '^'.indent.contPat )
319       while ml2 != []
320         let [_,c,rest;x] = ml2
321         let type .= c
322         let ml2 = matchlist( rest , '^'.indent.contPat )
323       endwhile
324       let id   = substitute(id, '^(\(.*\))$', '\1', '')
325       let type = substitute( type, '\s\+', " ", "g" )
326       " using :browse *<current>, we get both unqualified and qualified ids
327       if current_module " || has_key(imports[0],module) 
328         if has_key(b:ghc_types,id) && !(matchstr(b:ghc_types[id],escape(type,'[].'))==type)
329           let b:ghc_types[id] .= ' -- '.type
330         else
331           let b:ghc_types[id] = type
332         endif
333       endif
334       if 0 " has_key(imports[1],module) 
335         let qualid = module.'.'.id
336         let b:ghc_types[qualid] = type
337       endif
338     else
339       let mlMod = matchlist( l, modPat )
340       if mlMod != []
341         let [_,module;x] = mlMod
342         let current_module = module[0]=='*'
343         let module = current_module ? module[1:] : module
344       endif
345     endif
346     let ml = matchlist( rest , linePat )
347   endwhile
348   return 1
349 endfunction
351 let s:ghc_templates = ["module _ () where","class _ where","class _ => _ where","instance _ where","instance _ => _ where","type family _","type instance _ = ","data _ = ","newtype _ = ","type _ = "]
353 " use ghci :browse index for insert mode omnicompletion (CTRL-X CTRL-O)
354 function! GHC_CompleteImports(findstart, base)
355   if a:findstart 
356     let namsym   = haskellmode#GetNameSymbol(getline('.'),col('.'),-1) " insert-mode: we're 1 beyond the text
357     if namsym==[]
358       redraw
359       echo 'no name/symbol under cursor!'
360       return -1
361     endif
362     let [start,symb,qual,unqual] = namsym
363     return (start-1)
364   else " find keys matching with "a:base"
365     let res = []
366     let l   = len(a:base)-1
367     call GHC_HaveTypes()
368     for key in keys(b:ghc_types) 
369       if key[0 : l]==a:base
370         let res += [{"word":key,"menu":":: ".b:ghc_types[key],"dup":1}]
371       endif
372     endfor
373     return res
374   endif
375 endfunction
376 set omnifunc=GHC_CompleteImports
378 " Vim's default completeopt is menu,preview
379 " you probably want at least menu, or you won't see alternatives listed
380 " setlocal completeopt+=menu
382 " menuone is useful, but other haskellmode menus will try to follow your choice here in future
383 " setlocal completeopt+=menuone
385 " longest sounds useful, but doesn't seem to do what it says, and interferes with CTRL-E
386 " setlocal completeopt-=longest
388 map <LocalLeader>ct :call GHC_CreateTagfile()<cr>
389 function! GHC_CreateTagfile()
390   redraw
391   echo "creating tags file" 
392   let output = system(g:ghc . ' ' . b:ghc_staticoptions . ' -e ":ctags" ' . expand("%"))
393   " for ghcs older than 6.6, you would need to call another program 
394   " here, such as hasktags
395   echo output
396 endfunction
398 command! -nargs=1 GHCi redraw | echo system(g:ghc. ' ' . b:ghc_staticoptions .' '.expand("%").' -e "'.escape(<f-args>,'"').'"')
400 " use :make 'not in scope' errors to explicitly list imported ids
401 " cursor needs to be on import line, in correctly loadable module
402 map <LocalLeader>ie :call GHC_MkImportsExplicit()<cr>
403 function! GHC_MkImportsExplicit()
404   let save_cursor = getpos(".")
405   let line   = getline('.')
406   let lineno = line('.')
407   let ml     = matchlist(line,'^import\(\s*qualified\)\?\s*\([^( ]\+\)')
408   if ml!=[]
409     let [_,q,mod;x] = ml
410     silent make
411     if getqflist()==[]
412       if line=~"import[^(]*Prelude"
413         call setline(lineno,substitute(line,"(.*","","").'()')
414       else
415         call setline(lineno,'-- '.line)
416       endif
417       silent write
418       silent make
419       let qflist = getqflist()
420       call setline(lineno,line)
421       silent write
422       let ids = {}
423       for d in qflist
424         let ml = matchlist(d.text,'Not in scope: \([^`]*\)`\([^'']*\)''')
425         if ml!=[]
426           let [_,what,qid;x] = ml
427           let id  = ( qid =~ "^[A-Z]" ? substitute(qid,'.*\.\([^.]*\)$','\1','') : qid )
428           let pid = ( id =~ "[a-zA-Z0-9_']\\+" ? id : '('.id.')' )
429           if what =~ "data"
430             call GHC_HaveTypes()
431             if has_key(b:ghc_types,id)
432               let pid = substitute(b:ghc_types[id],'^.*->\s*\(\S*\).*$','\1','').'('.pid.')'
433             else
434               let pid = '???('.pid.')'
435             endif
436           endif
437           let ids[pid] = 1
438         endif
439       endfor
440       call setline(lineno,'import'.q.' '.mod.'('.join(keys(ids),',').')')
441     else
442       copen
443     endif
444   endif
445   call setpos('.', save_cursor)
446 endfunction
448 " no need to ask GHC about its supported languages and
449 " options with every editing session. cache the info in
450 " ~/.vim/haskellmode.config 
451 " TODO: should we store more info (see haskell_doc.vim)?
452 "       move to autoload?
453 "       should we keep a history of GHC versions encountered?
454 function! GHC_SaveConfig()
455   let vimdir = expand('~').'/'.'.vim'
456   let config = vimdir.'/haskellmode.config'
457   if !isdirectory(vimdir)
458     call mkdir(vimdir)
459   endif
460   let entries = ['-- '.g:ghc_version]
461   for l in s:ghc_supported_languages
462     let entries += [l]
463   endfor
464   let entries += ['--']
465   for l in s:opts
466     let entries += [l]
467   endfor
468   call writefile(entries,config)
469 endfunction
471 " reuse cached GHC configuration info, if using the same
472 " GHC version.
473 function! GHC_LoadConfig()
474   let vimdir = expand('~').'/'.'.vim'
475   let config = vimdir.'/haskellmode.config'
476   if filereadable(config)
477     let lines = readfile(config)
478     if lines[0]=='-- '.g:ghc_version
479       let i=1
480       let s:ghc_supported_languages = []
481       while i<len(lines) && lines[i]!='--'
482         let s:ghc_supported_languages += [lines[i]]
483         let i+=1
484       endwhile
485       let i+=1
486       let s:opts = []
487       while i<len(lines)
488         let s:opts += [lines[i]]
489         let i+=1
490       endwhile
491       return 1
492     else
493       return 0
494     endif
495   else
496     return 0
497   endif
498 endfunction
500 let s:GHC_CachedConfig = haskellmode#GHC_VersionGE([6,8]) && GHC_LoadConfig()
502 if haskellmode#GHC_VersionGE([6,8,2])
503   if !s:GHC_CachedConfig
504     let s:opts = filter(split(substitute(system(g:ghc . ' -v0 --interactive', ':set'), '  ', '','g'), '\n'), 'v:val =~ "-f"')
505   endif
506 else
507   let s:opts = ["-fglasgow-exts","-fallow-undecidable-instances","-fallow-overlapping-instances","-fno-monomorphism-restriction","-fno-mono-pat-binds","-fno-cse","-fbang-patterns","-funbox-strict-fields"]
508 endif
509 let s:opts = sort(s:opts)
511 amenu ]OPTIONS_GHC.- :echo '-'<cr>
512 aunmenu ]OPTIONS_GHC
513 for o in s:opts
514   exe 'amenu ]OPTIONS_GHC.'.o.' :call append(0,"{-# OPTIONS_GHC '.o.' #-}")<cr>'
515 endfor
516 if has("gui_running")
517   map <LocalLeader>opt :popup ]OPTIONS_GHC<cr>
518 else
519   map <LocalLeader>opt :emenu ]OPTIONS_GHC.
520 endif
522 amenu ]LANGUAGES_GHC.- :echo '-'<cr>
523 aunmenu ]LANGUAGES_GHC
524 if haskellmode#GHC_VersionGE([6,8])
525   if !s:GHC_CachedConfig
526     let s:ghc_supported_languages = sort(split(system(g:ghc . ' --supported-languages'),'\n'))
527   endif
528   for l in s:ghc_supported_languages
529     exe 'amenu ]LANGUAGES_GHC.'.l.' :call append(0,"{-# LANGUAGE '.l.' #-}")<cr>'
530   endfor
531   if has("gui_running")
532     map <LocalLeader>lang :popup ]LANGUAGES_GHC<cr>
533   else
534     map <LocalLeader>lang :emenu ]LANGUAGES_GHC.
535   endif
536 endif
538 if !s:GHC_CachedConfig
539   call GHC_SaveConfig()
540 endif
542 ftplugin/haskell.vim    [[[1
545 " general Haskell source settings
546 " (shared functions are in autoload/haskellmode.vim)
548 " (Claus Reinke, last modified: 28/04/2009)
550 " part of haskell plugins: http://projects.haskell.org/haskellmode-vim
551 " please send patches to <claus.reinke@talk21.com>
553 " try gf on import line, or ctrl-x ctrl-i, or [I, [i, ..
554 setlocal include=^import\\s*\\(qualified\\)\\?\\s*
555 setlocal includeexpr=substitute(v:fname,'\\.','/','g').'.'
556 setlocal suffixesadd=hs,lhs,hsc
558 ftplugin/haskell_doc.vim        [[[1
561 " use haddock docs and index files
562 " show documentation, complete & qualify identifiers 
564 " (Claus Reinke; last modified: 17/06/2009)
566 " part of haskell plugins: http://projects.haskell.org/haskellmode-vim
567 " please send patches to <claus.reinke@talk21.com>
569 " :Doc <name> and :IDoc <name> open haddocks for <name> in opera
571 "   :Doc needs qualified name (default Prelude) and package (default base)
572 "   :IDoc needs unqualified name, looks up possible links in g:haddock_index
574 "   :DocIndex populates g:haddock_index from haddock's index files
575 "   :ExportDocIndex saves g:haddock_index to cache file
576 "   :ImportDocIndex reloads g:haddock_index from cache file
578 " all the following use the haddock index (g:haddock_index)
580 " _? opens haddocks for unqualified name under cursor, 
581 "    suggesting alternative full qualifications in popup menu
583 " _. fully qualifies unqualified name under cursor,
584 "    suggesting alternative full qualifications in popup menu
586 " _i  add import <module>(<name>) statement for unqualified <name> under cursor,
587 " _im add import <module>         statement for unqualified <name> under cursor,
588 "    suggesting alternative full qualifications in popup menu
589 "    (this currently adds one statement per call, instead of
590 "     merging into existing import statements, but it's a start;-)
592 " CTRL-X CTRL-U (user-defined insert mode completion) 
593 "   suggests completions of unqualified names in popup menu
595 let s:scriptname = "haskell_doc.vim"
597 " script parameters
598 "   g:haddock_browser            *mandatory* which browser to call
599 "   g:haddock_browser_callformat [optional] how to call browser
600 "   g:haddock_indexfiledir       [optional] where to put 'haddock_index.vim'
601 "   g:haddock_docdir             [optional] where to find html docs
602 "   g:ghc                        [optional] which ghc to call
603 "   g:ghc_pkg                    [optional] which ghc_pkg to call
605 " been here before?
606 if exists("g:haddock_index")
607   finish
608 endif
610 " initialise nested dictionary, to be populated 
611 " - from haddock index files via :DocIndex
612 " - from previous cached version via :ImportDocIndex
613 let g:haddock_index = {}
615 " initialise dictionary, mapping modules with haddocks to their packages,
616 " populated via MkHaddockModuleIndex() or HaveModuleIndex()
617 let g:haddock_moduleindex = {}
619 " program to open urls, please set this in your vimrc
620   "examples (for windows):
621   "let g:haddock_browser = "C:/Program Files/Opera/Opera.exe"
622   "let g:haddock_browser = "C:/Program Files/Mozilla Firefox/firefox.exe"
623   "let g:haddock_browser = "C:/Program Files/Internet Explorer/IEXPLORE.exe"
624 if !exists("g:haddock_browser")
625   echoerr s:scriptname." WARNING: please set g:haddock_browser!"
626 endif
628 if !haskellmode#GHC() | finish | endif
630 if (!exists("g:ghc_pkg") || !executable(g:ghc_pkg))
631   let g:ghc_pkg = substitute(g:ghc,'\(.*\)ghc','\1ghc-pkg','')
632 endif
634 if exists("g:haddock_docdir") && isdirectory(g:haddock_docdir)
635   let s:docdir = g:haddock_docdir
636 elseif executable(g:ghc_pkg)
637 " try to figure out location of html docs
638 " first choice: where the base docs are (from the first base listed)
639   let [field;x] = split(system(g:ghc_pkg . ' field base haddock-html'),'\n')
640   " path changes in ghc-6.12.*
641   " let field = substitute(field,'haddock-html: \(.*\)libraries.base','\1','')
642   let field = substitute(field,'haddock-html: \(.*\)lib\(raries\)\?.base.*$','\1','')
643   let field = substitute(field,'\\','/','g')
644   " let alternate = substitute(field,'html','doc/html','')
645   " changes for ghc-6.12.*: check for doc/html/ first
646   let alternate = field.'doc/html/'
647   if isdirectory(alternate)
648     let s:docdir = alternate
649   elseif isdirectory(field)
650     let s:docdir = field
651   endif
652 else
653   echoerr s:scriptname." can't find ghc-pkg (set g:ghc_pkg ?)."
654 endif
656 " second choice: try some known suspects for windows/unix
657 if !exists('s:docdir') || !isdirectory(s:docdir)
658   let s:ghc_libdir = substitute(system(g:ghc . ' --print-libdir'),'\n','','')
659   let location1a = s:ghc_libdir . '/doc/html/'
660   let location1b = s:ghc_libdir . '/doc/'
661   let location2 = '/usr/share/doc/ghc-' . haskellmode#GHC_Version() . '/html/' 
662   if isdirectory(location1a)
663     let s:docdir = location1a
664   elseif isdirectory(location1b)
665     let s:docdir = location1b
666   elseif isdirectory(location2)
667     let s:docdir = location2
668   else " give up
669     echoerr s:scriptname." can't find locaton of html documentation (set g:haddock_docdir)."
670     finish
671   endif
672 endif
674 " todo: can we turn s:docdir into a list of paths, and
675 " include docs for third-party libs as well?
677 let s:libraries         = s:docdir . 'libraries/'
678 let s:guide             = s:docdir . 'users_guide/'
679 let s:index             = 'index.html'
680 if exists("g:haddock_indexfiledir") && filewritable(g:haddock_indexfiledir)
681   let s:haddock_indexfiledir = g:haddock_indexfiledir 
682 elseif filewritable(s:libraries)
683   let s:haddock_indexfiledir = s:libraries
684 elseif filewritable($HOME)
685   let s:haddock_indexfiledir = $HOME.'/'
686 else "give up
687   echoerr s:scriptname." can't locate index file. please set g:haddock_indexfiledir"
688   finish
689 endif
690 let s:haddock_indexfile = s:haddock_indexfiledir . 'haddock_index.vim'
692 " different browser setups require different call formats;
693 " you might want to call the browser synchronously or 
694 " asynchronously, and the latter is os-dependent;
696 " by default, the browser is started in the background when on 
697 " windows or if running in a gui, and in the foreground otherwise
698 " (eg, console-mode for remote sessions, with text-mode browsers).
700 " you can override these defaults in your vimrc, via a format 
701 " string including 2 %s parameters (the first being the browser 
702 " to call, the second being the url).
703 if !exists("g:haddock_browser_callformat")
704   if has("win32") || has("win64")
705     let g:haddock_browser_callformat = 'start %s "%s"'
706   else
707     if has("gui_running")
708       let g:haddock_browser_callformat = '%s %s '.printf(&shellredir,'/dev/null').' &'
709     else
710       let g:haddock_browser_callformat = '%s %s'
711     endif
712   endif
713 endif
715 " allow map leader override
716 if !exists("maplocalleader")
717   let maplocalleader='_'
718 endif
720 command! DocSettings call DocSettings()
721 function! DocSettings()
722   for v in ["g:haddock_browser","g:haddock_browser_callformat","g:haddock_docdir","g:haddock_indexfiledir","s:ghc_libdir","g:ghc_version","s:docdir","s:libraries","s:guide","s:haddock_indexfile"]
723     if exists(v)
724       echo v '=' eval(v)
725     else
726       echo v '='
727     endif
728   endfor
729 endfunction
731 function! DocBrowser(url)
732   "echomsg "DocBrowser(".url.")"
733   if (!exists("g:haddock_browser") || !executable(g:haddock_browser))
734     echoerr s:scriptname." can't find documentation browser. please set g:haddock_browser"
735     return
736   endif
737   " start browser to open url, according to specified format
738   let url = a:url=~'^\(file://\|http://\)' ? a:url : 'file://'.a:url
739   silent exe '!'.printf(g:haddock_browser_callformat,g:haddock_browser,escape(url,'#%')) 
740 endfunction
742 "Doc/Doct are an old interface for documentation lookup
743 "(that is the reason they are not documented!-)
745 "These uses are still fine at the moment, and are the reason 
746 "that this command still exists at all
748 " :Doc -top
749 " :Doc -libs
750 " :Doc -guide
752 "These uses may or may not work, and shouldn't be relied on anymore
753 "(usually, you want _?/_?1/_?2 or :MDoc; there is also :IDoc)
755 " :Doc length
756 " :Doc Control.Monad.when
757 " :Doc Data.List.
758 " :Doc Control.Monad.State.runState mtl
759 command! -nargs=+ Doc  call Doc('v',<f-args>)
760 command! -nargs=+ Doct call Doc('t',<f-args>)
762 function! Doc(kind,qualname,...) 
763   let suffix   = '.html'
764   let relative = '#'.a:kind.'%3A'
766   if a:qualname=="-top"
767     call DocBrowser(s:docdir . s:index)
768     return
769   elseif a:qualname=="-libs"
770     call DocBrowser(s:libraries . s:index)
771     return
772   elseif a:qualname=="-guide"
773     call DocBrowser(s:guide . s:index)
774     return
775   endif
777   if a:0==0 " no package specified
778     let package = 'base/'
779   else
780     let package = a:1 . '/'
781   endif
783   if match(a:qualname,'\.')==-1 " unqualified name
784     let [qual,name] = [['Prelude'],a:qualname]
785     let file = join(qual,'-') . suffix . relative . name
786   elseif a:qualname[-1:]=='.' " module qualifier only
787     let parts = split(a:qualname,'\.')
788     let quallen = len(parts)-1
789     let [qual,name] = [parts[0:quallen],parts[-1]]
790     let file = join(qual,'-') . suffix
791   else " qualified name
792     let parts = split(a:qualname,'\.')
793     let quallen = len(parts)-2
794     let [qual,name] = [parts[0:quallen],parts[-1]]
795     let file = join(qual,'-') . suffix . relative . name
796   endif
798   let path = s:libraries . package . file
799   call DocBrowser(path)
800 endfunction
802 " TODO: add commandline completion for :IDoc
803 "       switch to :emenu instead of inputlist?
804 " indexed variant of Doc, looking up links in g:haddock_index
805 " usage:
806 "  1. :IDoc length
807 "  2. click on one of the choices, or select by number (starting from 0)
808 command! -nargs=+ IDoc call IDoc(<f-args>)
809 function! IDoc(name,...) 
810   let choices = HaddockIndexLookup(a:name)
811   if choices=={} | return | endif
812   if a:0==0
813     let keylist = map(deepcopy(keys(choices)),'substitute(v:val,"\\[.\\]","","")')
814     let choice = inputlist(keylist)
815   else
816     let choice = a:1
817   endif
818   let path = values(choices)[choice] " assumes same order for keys/values..
819   call DocBrowser(path)
820 endfunction
822 let s:flagref = s:guide . 'flag-reference.html'
823 if filereadable(s:flagref)
824   " extract the generated fragment ids for the 
825   " flag reference sections 
826   let s:headerPat     = '.\{-}<h3 class="title"><a name="\([^"]*\)"><\/a>\([^<]*\)<\/h3>\(.*\)'
827   let s:flagheaders   = []
828   let s:flagheaderids = {}
829   let s:contents      = join(readfile(s:flagref))
830   let s:ml = matchlist(s:contents,s:headerPat)
831   while s:ml!=[]
832     let [_,s:id,s:title,s:r;s:x] = s:ml
833     let s:flagheaders            = add(s:flagheaders, s:title)
834     let s:flagheaderids[s:title] = s:id
835     let s:ml = matchlist(s:r,s:headerPat)
836   endwhile
837   command! -nargs=1 -complete=customlist,CompleteFlagHeaders FlagReference call FlagReference(<f-args>)
838   function! FlagReference(section)
839     let relativeUrl = a:section==""||!exists("s:flagheaderids['".a:section."']") ? 
840                     \ "" : "#".s:flagheaderids[a:section]
841     call DocBrowser(s:flagref.relativeUrl)
842   endfunction
843   function! CompleteFlagHeaders(al,cl,cp)
844     let s:choices = s:flagheaders
845     return CompleteAux(a:al,a:cl,a:cp)
846   endfunction
847 endif
849 command! -nargs=1 -complete=customlist,CompleteHaddockModules MDoc call MDoc(<f-args>)
850 function! MDoc(module)
851   let suffix   = '.html'
852   call HaveModuleIndex()
853   if !has_key(g:haddock_moduleindex,a:module)
854     echoerr a:module 'not found in haddock module index'
855     return
856   endif
857   let package = g:haddock_moduleindex[a:module]['package']
858   let file    = substitute(a:module,'\.','-','g') . suffix
859 " let path    = s:libraries . package . '/' . file
860   let path    = g:haddock_moduleindex[a:module]['html']
861   call DocBrowser(path)
862 endfunction
864 function! CompleteHaddockModules(al,cl,cp)
865   call HaveModuleIndex()
866   let s:choices = keys(g:haddock_moduleindex)
867   return CompleteAux(a:al,a:cl,a:cp)
868 endfunction
870 " create a dictionary g:haddock_index, containing the haddoc index
871 command! DocIndex call DocIndex()
872 function! DocIndex()
873   let files   = split(globpath(s:libraries,'doc-index*.html'),'\n')
874   let g:haddock_index = {}
875   call ProcessHaddockIndexes2(s:libraries,files)
876   if haskellmode#GHC_VersionGE([6,8,2])
877     if &shell =~ 'sh' " unix-type shell
878       let s:addon_libraries = split(system(g:ghc_pkg . ' field \* haddock-html'),'\n')
879     else " windows cmd.exe and the like
880       let s:addon_libraries = split(system(g:ghc_pkg . ' field * haddock-html'),'\n')
881     endif
882     for addon in s:addon_libraries
883       let ml = matchlist(addon,'haddock-html: \("\)\?\(file:///\)\?\([^"]*\)\("\)\?')
884       if ml!=[]
885         let [_,quote,file,addon_path;x] = ml
886         let addon_path = substitute(addon_path,'\(\\\\\|\\\)','/','g')
887         let addon_files = split(globpath(addon_path,'doc-index*.html'),'\n')
888         call ProcessHaddockIndexes2(addon_path,addon_files)
889       endif
890     endfor
891   endif
892   return 1
893 endfunction
895 function! ProcessHaddockIndexes(location,files)
896   let entryPat= '.\{-}"indexentry"[^>]*>\([^<]*\)<\(\%([^=]\{-}TD CLASS="\%(indexentry\)\@!.\{-}</TD\)*\)[^=]\{-}\(\%(="indexentry\|TABLE\).*\)'
897   let linkPat = '.\{-}HREF="\([^"]*\)".>\([^<]*\)<\(.*\)'
899   redraw
900   echo 'populating g:haddock_index from haddock index files in ' a:location
901   for f in a:files  
902     echo f[len(a:location):]
903     let contents = join(readfile(f))
904     let ml = matchlist(contents,entryPat)
905     while ml!=[]
906       let [_,entry,links,r;x] = ml
907       "echo entry links
908       let ml2 = matchlist(links,linkPat)
909       let link = {}
910       while ml2!=[]
911         let [_,l,m,links;x] = ml2
912         "echo l m
913         let link[m] = a:location . '/' . l
914         let ml2 = matchlist(links,linkPat)
915       endwhile
916       let g:haddock_index[DeHTML(entry)] = deepcopy(link)
917       "echo entry g:haddock_index[entry]
918       let ml = matchlist(r,entryPat)
919     endwhile
920   endfor
921 endfunction
923 " concatenating all lines is too slow for a big file, process lines directly
924 function! ProcessHaddockIndexes2(location,files)
925   let entryPat= '^>\([^<]*\)</'
926   let linkPat = '.\{-}A HREF="\([^"]*\)"'
927   let kindPat = '#\(.\)'
929   " redraw
930   echo 'populating g:haddock_index from haddock index files in ' a:location
931   for f in a:files  
932     echo f[len(a:location):]
933     let isEntry = 0
934     let isLink  = ''
935     let link    = {}
936     let entry   = ''
937     for line in readfile(f)
938       if line=~'CLASS="indexentry' 
939         if (link!={}) && (entry!='')
940           if has_key(g:haddock_index,DeHTML(entry))
941             let dict = extend(g:haddock_index[DeHTML(entry)],deepcopy(link))
942           else
943             let dict = deepcopy(link)
944           endif
945           let g:haddock_index[DeHTML(entry)] = dict
946           let link  = {}
947           let entry = ''
948         endif
949         let isEntry=1 
950         continue 
951       endif
952       if isEntry==1
953         let ml = matchlist(line,entryPat)
954         if ml!=[] | let [_,entry;x] = ml | let isEntry=0 | continue | endif
955       endif
956       if entry!=''
957         let ml = matchlist(line,linkPat)
958         if ml!=[] | let [_,isLink;x]=ml | continue | endif
959       endif
960       if isLink!=''
961         let ml = matchlist(line,entryPat)
962         if ml!=[] 
963           let [_,module;x] = ml 
964           let [_,kind;x]   = matchlist(isLink,kindPat)
965           let last         = a:location[strlen(a:location)-1]
966           let link[module."[".kind."]"] = a:location . (last=='/'?'':'/') . isLink
967           let isLink='' 
968           continue 
969         endif
970       endif
971     endfor
972     if link!={} 
973       if has_key(g:haddock_index,DeHTML(entry))
974         let dict = extend(g:haddock_index[DeHTML(entry)],deepcopy(link))
975       else
976         let dict = deepcopy(link)
977       endif
978       let g:haddock_index[DeHTML(entry)] = dict
979     endif
980   endfor
981 endfunction
983 command! ExportDocIndex call ExportDocIndex()
984 function! ExportDocIndex()
985   call HaveIndex()
986   let entries = []
987   for key in keys(g:haddock_index)
988     let entries += [key,string(g:haddock_index[key])]
989   endfor
990   call writefile(entries,s:haddock_indexfile)
991   redir end
992 endfunction
994 command! ImportDocIndex call ImportDocIndex()
995 function! ImportDocIndex()
996   if filereadable(s:haddock_indexfile)
997     let lines = readfile(s:haddock_indexfile)
998     let i=0
999     while i<len(lines)
1000       let [key,dict] = [lines[i],lines[i+1]]
1001       sandbox let g:haddock_index[key] = eval(dict) 
1002       let i+=2
1003     endwhile
1004     return 1
1005   else
1006     return 0
1007   endif
1008 endfunction
1010 function! HaveIndex()
1011   return (g:haddock_index!={} || ImportDocIndex() || DocIndex() )
1012 endfunction
1014 function! MkHaddockModuleIndex()
1015   let g:haddock_moduleindex = {}
1016   call HaveIndex()
1017   for key in keys(g:haddock_index)
1018     let dict = g:haddock_index[key]
1019     for module in keys(dict)
1020       let html = dict[module]
1021       let html   = substitute(html  ,'#.*$','','')
1022       let module = substitute(module,'\[.\]','','')
1023       let ml = matchlist(html,'libraries/\([^\/]*\)[\/]')
1024       if ml!=[]
1025         let [_,package;x] = ml
1026         let g:haddock_moduleindex[module] = {'package':package,'html':html}
1027       endif
1028       let ml = matchlist(html,'/\([^\/]*\)\/html/[A-Z]')
1029       if ml!=[]
1030         let [_,package;x] = ml
1031         let g:haddock_moduleindex[module] = {'package':package,'html':html}
1032       endif
1033     endfor
1034   endfor
1035 endfunction
1037 function! HaveModuleIndex()
1038   return (g:haddock_moduleindex!={} || MkHaddockModuleIndex() )
1039 endfunction
1041 " decode HTML symbol encodings (are these all we need?)
1042 function! DeHTML(entry)
1043   let res = a:entry
1044   let decode = { '&lt;': '<', '&gt;': '>', '&amp;': '\\&' }
1045   for enc in keys(decode)
1046     exe 'let res = substitute(res,"'.enc.'","'.decode[enc].'","g")'
1047   endfor
1048   return res
1049 endfunction
1051 " find haddocks for word under cursor
1052 " also lists possible definition sites
1053 " - needs to work for both qualified and unqualified items
1054 " - for 'import qualified M as A', consider M.item as source of A.item
1055 " - offer sources from both type [t] and value [v] namespaces
1056 " - for unqualified items, list all possible sites
1057 " - for qualified items, list imported sites only
1058 " keep track of keys with and without namespace tags:
1059 " the former are needed for lookup, the latter for matching against source
1060 map <LocalLeader>? :call Haddock()<cr>
1061 function! Haddock()
1062   amenu ]Popup.- :echo '-'<cr>
1063   aunmenu ]Popup
1064   let namsym   = haskellmode#GetNameSymbol(getline('.'),col('.'),0)
1065   if namsym==[]
1066     redraw
1067     echo 'no name/symbol under cursor!'
1068     return 0
1069   endif
1070   let [start,symb,qual,unqual] = namsym
1071   let imports = haskellmode#GatherImports()
1072   let asm  = has_key(imports[1],qual) ? imports[1][qual]['modules'] : []
1073   let name = unqual
1074   let dict = HaddockIndexLookup(name)
1075   if dict=={} | return | endif
1076   " for qualified items, narrow results to possible imports that provide qualifier
1077   let filteredKeys = filter(copy(keys(dict))
1078                          \ ,'match(asm,substitute(v:val,''\[.\]'','''',''''))!=-1') 
1079   let keys = (qual!='') ?  filteredKeys : keys(dict)
1080   if (keys==[]) && (qual!='')
1081     echoerr qual.'.'.unqual.' not found in imports'
1082     return 0
1083   endif
1084   " use 'setlocal completeopt+=menuone' if you always want to see menus before
1085   " anything happens (I do, but many users don't..)
1086   if len(keys)==1 && (&completeopt!~'menuone')
1087         call DocBrowser(dict[keys[0]])
1088   elseif has("gui_running")
1089     for key in keys
1090       exe 'amenu ]Popup.'.escape(key,'\.').' :call DocBrowser('''.dict[key].''')<cr>'
1091     endfor
1092     popup ]Popup
1093   else
1094     let s:choices = keys
1095     let key = input('browse docs for '.name.' in: ','','customlist,CompleteAux')
1096     if key!=''
1097       call DocBrowser(dict[key])
1098     endif
1099   endif
1100 endfunction
1102 if !exists("g:haskell_search_engines")
1103   let g:haskell_search_engines = 
1104     \ {'hoogle':'http://www.haskell.org/hoogle/?hoogle=%s'
1105     \ ,'hayoo!':'http://holumbus.fh-wedel.de/hayoo/hayoo.html?query=%s'
1106     \ }
1107 endif
1109 map <LocalLeader>?? :let es=g:haskell_search_engines
1110                  \ \|echo "g:haskell_search_engines"
1111                  \ \|for e in keys(es)
1112                  \ \|echo e.' : '.es[e]
1113                  \ \|endfor<cr>
1114 map <LocalLeader>?1 :call HaskellSearchEngine('hoogle')<cr>
1115 map <LocalLeader>?2 :call HaskellSearchEngine('hayoo!')<cr>
1117 " query one of the Haskell search engines for the thing under cursor
1118 " - unqualified symbols need to be url-escaped
1119 " - qualified ids need to be fed as separate qualifier and id for
1120 "   both hoogle (doesn't handle qualified symbols) and hayoo! (no qualified
1121 "   ids at all)
1122 " - qualified ids referring to import-qualified-as qualifiers need to be
1123 "   translated to the multi-module searches over the list of original modules
1124 function! HaskellSearchEngine(engine)
1125   amenu ]Popup.- :echo '-'<cr>
1126   aunmenu ]Popup
1127   let namsym   = haskellmode#GetNameSymbol(getline('.'),col('.'),0)
1128   if namsym==[]
1129     redraw
1130     echo 'no name/symbol under cursor!'
1131     return 0
1132   endif
1133   let [start,symb,qual,unqual] = namsym
1134   let imports = haskellmode#GatherImports()
1135   let asm  = has_key(imports[1],qual) ? imports[1][qual]['modules'] : []
1136   let unqual = haskellmode#UrlEncode(unqual)
1137   if a:engine=='hoogle'
1138     let name = asm!=[] ? unqual.'+'.join(map(copy(asm),'"%2B".v:val'),'+')
1139            \ : qual!='' ? unqual.'+'.haskellmode#UrlEncode('+').qual
1140            \ : unqual
1141   elseif a:engine=='hayoo!'
1142     let name = asm!=[] ? unqual.'+module:('.join(copy(asm),' OR ').')'
1143            \ : qual!='' ? unqual.'+module:'.qual
1144            \ : unqual
1145   else
1146     let name = qual=="" ? unqual : qual.".".unqual
1147   endif
1148   if has_key(g:haskell_search_engines,a:engine)
1149     call DocBrowser(printf(g:haskell_search_engines[a:engine],name))
1150   else
1151     echoerr "unknown search engine: ".a:engine
1152   endif
1153 endfunction
1155 " used to pass on choices to CompleteAux
1156 let s:choices=[]
1158 " if there's no gui, use commandline completion instead of :popup
1159 " completion function CompleteAux suggests completions for a:al, wrt to s:choices
1160 function! CompleteAux(al,cl,cp)
1161   "echomsg '|'.a:al.'|'.a:cl.'|'.a:cp.'|'
1162   let res = []
1163   let l = len(a:al)-1
1164   for r in s:choices
1165     if l==-1 || r[0 : l]==a:al
1166       let res += [r]
1167     endif
1168   endfor
1169   return res
1170 endfunction
1172 " CamelCase shorthand matching: 
1173 " favour upper-case letters and module qualifier separators (.) for disambiguation
1174 function! CamelCase(shorthand,string)
1175   let s1 = a:shorthand
1176   let s2 = a:string
1177   let notFirst = 0 " don't elide before first pattern letter
1178   while ((s1!="")&&(s2!="")) 
1179     let head1 = s1[0]
1180     let head2 = s2[0]
1181     let elide = notFirst && ( ((head1=~'[A-Z]') && (head2!~'[A-Z.]')) 
1182               \             ||((head1=='.') && (head2!='.')) ) 
1183     if elide
1184       let s2=s2[1:]
1185     elseif (head1==head2) 
1186       let s1=s1[1:]
1187       let s2=s2[1:]
1188     else
1189       return 0
1190     endif
1191     let notFirst = (head1!='.')||(head2!='.') " treat separators as new beginnings
1192   endwhile
1193   return (s1=="")
1194 endfunction
1196 " use haddock name index for insert mode completion (CTRL-X CTRL-U)
1197 function! CompleteHaddock(findstart, base)
1198   if a:findstart 
1199     let namsym   = haskellmode#GetNameSymbol(getline('.'),col('.'),-1) " insert-mode: we're 1 beyond the text
1200     if namsym==[]
1201       redraw
1202       echo 'no name/symbol under cursor!'
1203       return -1
1204     endif
1205     let [start,symb,qual,unqual] = namsym
1206     return (start-1)
1207   else " find keys matching with "a:base"
1208     let res  = []
1209     let l    = len(a:base)-1
1210     let qual = a:base =~ '^[A-Z][a-zA-Z0-9_'']*\(\.[A-Z][a-zA-Z0-9_'']*\)*\(\.[a-zA-Z0-9_'']*\)\?$'
1211     call HaveIndex() 
1212     for key in keys(g:haddock_index)
1213       let keylist = map(deepcopy(keys(g:haddock_index[key])),'substitute(v:val,"\\[.\\]","","")')
1214       if (key[0 : l]==a:base)
1215         for m in keylist
1216           let res += [{"word":key,"menu":m,"dup":1}]
1217         endfor
1218       elseif qual " this tends to be slower
1219         for m in keylist
1220           let word = m . '.' . key
1221           if word[0 : l]==a:base
1222             let res += [{"word":word,"menu":m,"dup":1}]
1223           endif
1224         endfor
1225       endif
1226     endfor
1227     if res==[] " no prefix matches, try CamelCase shortcuts
1228       for key in keys(g:haddock_index)
1229         let keylist = map(deepcopy(keys(g:haddock_index[key])),'substitute(v:val,"\\[.\\]","","")')
1230         if CamelCase(a:base,key)
1231           for m in keylist
1232             let res += [{"word":key,"menu":m,"dup":1}]
1233           endfor
1234         elseif qual " this tends to be slower
1235           for m in keylist
1236             let word = m . '.' . key
1237             if CamelCase(a:base,word)
1238               let res += [{"word":word,"menu":m,"dup":1}]
1239             endif
1240           endfor
1241         endif
1242       endfor
1243     endif
1244     return res
1245   endif
1246 endfunction
1247 setlocal completefunc=CompleteHaddock
1249 " Vim's default completeopt is menu,preview
1250 " you probably want at least menu, or you won't see alternatives listed
1251 " setlocal completeopt+=menu
1253 " menuone is useful, but other haskellmode menus will try to follow your choice here in future
1254 " setlocal completeopt+=menuone
1256 " longest sounds useful, but doesn't seem to do what it says, and interferes with CTRL-E
1257 " setlocal completeopt-=longest
1259 " fully qualify an unqualified name
1260 " TODO: - standardise commandline versions of menus
1261 map <LocalLeader>. :call Qualify()<cr>
1262 function! Qualify()
1263   amenu ]Popup.- :echo '-'<cr>
1264   aunmenu ]Popup
1265   let namsym   = haskellmode#GetNameSymbol(getline('.'),col('.'),0)
1266   if namsym==[]
1267     redraw
1268     echo 'no name/symbol under cursor!'
1269     return 0
1270   endif
1271   let [start,symb,qual,unqual] = namsym
1272   if qual!=''  " TODO: should we support re-qualification?
1273     redraw
1274     echo 'already qualified'
1275     return 0
1276   endif
1277   let name = unqual
1278   let line         = line('.')
1279   let prefix       = (start<=1 ? '' : getline(line)[0:start-2] )
1280   let dict   = HaddockIndexLookup(name)
1281   if dict=={} | return | endif
1282   let keylist = map(deepcopy(keys(dict)),'substitute(v:val,"\\[.\\]","","")')
1283   let imports = haskellmode#GatherImports()
1284   let qualifiedImports = []
1285   for qualifiedImport in keys(imports[1])
1286     let c=0
1287     for module in imports[1][qualifiedImport]['modules']
1288       if haskellmode#ListElem(keylist,module) | let c+=1 | endif
1289     endfor
1290     if c>0 | let qualifiedImports=[qualifiedImport]+qualifiedImports | endif
1291   endfor
1292   "let asm  = has_key(imports[1],qual) ? imports[1][qual]['modules'] : []
1293   let keylist = filter(copy(keylist),'index(qualifiedImports,v:val)==-1')
1294   if has("gui_running")
1295     " amenu ]Popup.-imported- :
1296     for key in qualifiedImports
1297       let lhs=escape(prefix.name,'/.|\')
1298       let rhs=escape(prefix.key.'.'.name,'/&|\')
1299       exe 'amenu ]Popup.'.escape(key,'\.').' :'.line.'s/'.lhs.'/'.rhs.'/<cr>:noh<cr>'
1300     endfor
1301     amenu ]Popup.-not\ imported- :
1302     for key in keylist
1303       let lhs=escape(prefix.name,'/.|\')
1304       let rhs=escape(prefix.key.'.'.name,'/&|\')
1305       exe 'amenu ]Popup.'.escape(key,'\.').' :'.line.'s/'.lhs.'/'.rhs.'/<cr>:noh<cr>'
1306     endfor
1307     popup ]Popup
1308   else
1309     let s:choices = qualifiedImports+keylist
1310     let key = input('qualify '.name.' with: ','','customlist,CompleteAux')
1311     if key!=''
1312       let lhs=escape(prefix.name,'/.\')
1313       let rhs=escape(prefix.key.'.'.name,'/&\')
1314       exe line.'s/'.lhs.'/'.rhs.'/'
1315       noh
1316     endif
1317   endif
1318 endfunction
1320 " create (qualified) import for a (qualified) name
1321 " TODO: refine search patterns, to avoid misinterpretation of
1322 "       oddities like import'Neither or not'module
1323 map <LocalLeader>i :call Import(0,0)<cr>
1324 map <LocalLeader>im :call Import(1,0)<cr>
1325 map <LocalLeader>iq :call Import(0,1)<cr>
1326 map <LocalLeader>iqm :call Import(1,1)<cr>
1327 function! Import(module,qualified)
1328   amenu ]Popup.- :echo '-'<cr>
1329   aunmenu ]Popup
1330   let namsym   = haskellmode#GetNameSymbol(getline('.'),col('.'),0)
1331   if namsym==[]
1332     redraw
1333     echo 'no name/symbol under cursor!'
1334     return 0
1335   endif
1336   let [start,symb,qual,unqual] = namsym
1337   let name       = unqual
1338   let pname      = ( symb ? '('.name.')' : name )
1339   let importlist = a:module ? '' : '('.pname.')'
1340   let qualified  = a:qualified ? 'qualified ' : ''
1342   if qual!=''
1343     exe 'call append(search(''\%1c\(\<import\>\|\<module\>\|{-# OPTIONS\|{-# LANGUAGE\)'',''nb''),''import '.qualified.qual.importlist.''')'
1344     return
1345   endif
1347   let line   = line('.')
1348   let prefix = getline(line)[0:start-1]
1349   let dict   = HaddockIndexLookup(name)
1350   if dict=={} | return | endif
1351   let keylist = map(deepcopy(keys(dict)),'substitute(v:val,"\\[.\\]","","")')
1352   if has("gui_running")
1353     for key in keylist
1354       " exe 'amenu ]Popup.'.escape(key,'\.').' :call append(search("\\%1c\\(import\\\\|module\\\\|{-# OPTIONS\\)","nb"),"import '.key.importlist.'")<cr>'
1355       exe 'amenu ]Popup.'.escape(key,'\.').' :call append(search(''\%1c\(\<import\>\\|\<module\>\\|{-# OPTIONS\\|{-# LANGUAGE\)'',''nb''),''import '.qualified.key.escape(importlist,'|').''')<cr>'
1356     endfor
1357     popup ]Popup
1358   else
1359     let s:choices = keylist
1360     let key = input('import '.name.' from: ','','customlist,CompleteAux')
1361     if key!=''
1362       exe 'call append(search(''\%1c\(\<import\>\|\<module\>\|{-# OPTIONS\|{-# LANGUAGE\)'',''nb''),''import '.qualified.key.importlist.''')'
1363     endif
1364   endif
1365 endfunction
1367 function! HaddockIndexLookup(name)
1368   call HaveIndex()
1369   if !has_key(g:haddock_index,a:name)
1370     echoerr a:name 'not found in haddock index'
1371     return {}
1372   endif
1373   return g:haddock_index[a:name]
1374 endfunction
1376 ftplugin/haskell_hpaste.vim     [[[1
1378 " rudimentary hpaste support for vim
1379 " (using netrw for reading, wget for posting/annotating)
1381 " claus reinke, last modified: 07/04/2009
1383 " part of haskell plugins: http://projects.haskell.org/haskellmode-vim
1385 " unless wget is in your PATH, you need to set g:wget
1386 " before loading this script. windows users are out of 
1387 " luck, unless they have wget installed (such as the 
1388 " cygwin one looked for here), or adapt this script to 
1389 " whatever alternative they have at hand (perhaps using 
1390 " vim's perl/python bindings?)
1391 if !exists("g:wget")
1392   if executable("wget")
1393     let g:wget = "!wget -q"
1394   else
1395     let g:wget = "!c:\\cygwin\\bin\\wget -q"
1396   endif
1397 endif
1399 " read (recent) hpaste files
1400 " show index in new buffer, where ,r will open current entry
1401 " and ,p will annotate current entry with current buffer
1402 command! HpasteIndex call HpasteIndex()
1403 function! HpasteIndex()
1404   new
1405   read http://hpaste.org
1406   %s/\_$\_.//g
1407   %s/<tr[^>]*>//g
1408   %s/<\/tr>/\r/g
1409   g/<\/table>/d
1410   g/DOCTYPE/d
1411   %s/<td>\([^<]*\)<\/td><td><a href="\/fastcgi\/hpaste\.fcgi\/view?id=\([0-9]*\)">\([^<]*\)<\/a><\/td><td>\([^<]*\)<\/td><td>\([^<]*\)<\/td><td>\([^<]*\)<\/td>/\2 [\1] "\3" \4 \5 \6/
1412   map <buffer> ,r 0yE:noh<cr>:call HpasteEditEntry('\x12"')<cr>
1413 endfunction
1415 " load an existing entry for editing
1416 command! -nargs=1 HpasteEditEntry call HpasteEditEntry(<f-args>)
1417 function! HpasteEditEntry(entry)
1418   new
1419   exe 'Nread http://hpaste.org/fastcgi/hpaste.fcgi/raw?id='.a:entry
1420   "exe 'map <buffer> ,p :call HpasteAnnotate('''.a:entry.''')<cr>'
1421 endfunction
1423 " " posting temporarily disabled -- needs someone to look into new
1424 " " hpaste.org structure
1426 " " annotate existing entry (only to be called via ,p in HpasteIndex)
1427 " function! HpasteAnnotate(entry)
1428 "   let nick  = input("nick? ")
1429 "   let title = input("title? ")
1430 "   if nick=='' || title==''
1431 "     echo "nick or title missing. aborting annotation"
1432 "     return
1433 "   endif
1434 "   call HpastePost('annotate/'.a:entry,nick,title)
1435 " endfunction
1437 " " post new hpaste entry
1438 " " using 'wget --post-data' and url-encoded content
1439 " command! HpastePostNew  call HpastePost('new',<args>)
1440 " function! HpastePost(mode,nick,title,...)
1441 "   let lines = getbufline("%",1,"$") 
1442 "   let pat   = '\([^[:alnum:]]\)'
1443 "   let code  = '\=printf("%%%02X",char2nr(submatch(1)))'
1444 "   let lines = map(lines,'substitute(v:val."\r\n",'''.pat.''','''.code.''',''g'')')
1446 "   let url   = 'http://hpaste.org/' . a:mode 
1447 "   let nick  = substitute(a:nick,pat,code,'g')
1448 "   let title = substitute(a:title,pat,code,'g')
1449 "   if a:0==0
1450 "     let announce = 'false'
1451 "   else
1452 "     let announce = a:1
1453 "   endif
1454 "   let cmd = g:wget.' --post-data="content='.join(lines,'').'&nick='.nick.'&title='.title.'&announce='.announce.'" '.url
1455 "   exe escape(cmd,'%')
1456 " endfunction
1457 autoload/haskellmode.vim        [[[1
1460 " utility functions for haskellmode plugins
1462 " (Claus Reinke; last modified: 22/06/2010)
1464 " part of haskell plugins: http://projects.haskell.org/haskellmode-vim
1465 " please send patches to <claus.reinke@talk21.com>
1469 " find start/extent of name/symbol under cursor;
1470 " return start, symbolic flag, qualifier, unqualified id
1471 " (this is used in both haskell_doc.vim and in GHC.vim)
1472 function! haskellmode#GetNameSymbol(line,col,off)
1473   let name    = "[a-zA-Z0-9_']"
1474   let symbol  = "[-!#$%&\*\+/<=>\?@\\^|~:.]"
1475   "let [line]  = getbufline(a:buf,a:lnum)
1476   let line    = a:line
1478   " find the beginning of unqualified id or qualified id component 
1479   let start   = (a:col - 1) + a:off
1480   if line[start] =~ name
1481     let pattern = name
1482   elseif line[start] =~ symbol
1483     let pattern = symbol
1484   else
1485     return []
1486   endif
1487   while start > 0 && line[start - 1] =~ pattern
1488     let start -= 1
1489   endwhile
1490   let id    = matchstr(line[start :],pattern.'*')
1491   " call confirm(id)
1493   " expand id to left and right, to get full id
1494   let idPos = id[0] == '.' ? start+2 : start+1
1495   let posA  = match(line,'\<\(\([A-Z]'.name.'*\.\)\+\)\%'.idPos.'c')
1496   let start = posA>-1 ? posA+1 : idPos
1497   let posB  = matchend(line,'\%'.idPos.'c\(\([A-Z]'.name.'*\.\)*\)\('.name.'\+\|'.symbol.'\+\)')
1498   let end   = posB>-1 ? posB : idPos
1500   " special case: symbolic ids starting with .
1501   if id[0]=='.' && posA==-1 
1502     let start = idPos-1
1503     let end   = posB==-1 ? start : end
1504   endif
1506   " classify full id and split into qualifier and unqualified id
1507   let fullid   = line[ (start>1 ? start-1 : 0) : (end-1) ]
1508   let symbolic = fullid[-1:-1] =~ symbol  " might also be incomplete qualified id ending in .
1509   let qualPos  = matchend(fullid, '\([A-Z]'.name.'*\.\)\+')
1510   let qualifier = qualPos>-1 ? fullid[ 0 : (qualPos-2) ] : ''
1511   let unqualId  = qualPos>-1 ? fullid[ qualPos : -1 ] : fullid
1512   " call confirm(start.'/'.end.'['.symbolic.']:'.qualifier.' '.unqualId)
1514   return [start,symbolic,qualifier,unqualId]
1515 endfunction
1517 function! haskellmode#GatherImports()
1518   let imports={0:{},1:{}}
1519   let i=1
1520   while i<=line('$')
1521     let res = haskellmode#GatherImport(i)
1522     if !empty(res)
1523       let [i,import] = res
1524       let prefixPat = '^import\s*\%({-#\s*SOURCE\s*#-}\)\?\(qualified\)\?\s\+'
1525       let modulePat = '\([A-Z][a-zA-Z0-9_''.]*\)'
1526       let asPat     = '\(\s\+as\s\+'.modulePat.'\)\?'
1527       let hidingPat = '\(\s\+hiding\s*\((.*)\)\)\?'
1528       let listPat   = '\(\s*\((.*)\)\)\?'
1529       let importPat = prefixPat.modulePat.asPat.hidingPat.listPat ".'\s*$'
1531       let ml = matchlist(import,importPat)
1532       if ml!=[]
1533         let [_,qualified,module,_,as,_,hiding,_,explicit;x] = ml
1534         let what = as=='' ? module : as
1535         let hidings   = split(hiding[1:-2],',')
1536         let explicits = split(explicit[1:-2],',')
1537         let empty = {'lines':[],'hiding':hidings,'explicit':[],'modules':[]}
1538         let entry = has_key(imports[1],what) ? imports[1][what] : deepcopy(empty)
1539         let imports[1][what] = haskellmode#MergeImport(deepcopy(entry),i,hidings,explicits,module)
1540         if !(qualified=='qualified')
1541           let imports[0][what] = haskellmode#MergeImport(deepcopy(entry),i,hidings,explicits,module)
1542         endif
1543       else
1544         echoerr "haskellmode#GatherImports doesn't understand: ".import
1545       endif
1546     endif
1547     let i+=1
1548   endwhile
1549   if !has_key(imports[1],'Prelude') 
1550     let imports[0]['Prelude'] = {'lines':[],'hiding':[],'explicit':[],'modules':[]}
1551     let imports[1]['Prelude'] = {'lines':[],'hiding':[],'explicit':[],'modules':[]}
1552   endif
1553   return imports
1554 endfunction
1556 function! haskellmode#ListElem(list,elem)
1557   for e in a:list | if e==a:elem | return 1 | endif | endfor
1558   return 0
1559 endfunction
1561 function! haskellmode#ListIntersect(list1,list2)
1562   let l = []
1563   for e in a:list1 | if index(a:list2,e)!=-1 | let l += [e] | endif | endfor
1564   return l
1565 endfunction
1567 function! haskellmode#ListUnion(list1,list2)
1568   let l = []
1569   for e in a:list2 | if index(a:list1,e)==-1 | let l += [e] | endif | endfor
1570   return a:list1 + l
1571 endfunction
1573 function! haskellmode#ListWithout(list1,list2)
1574   let l = []
1575   for e in a:list1 | if index(a:list2,e)==-1 | let l += [e] | endif | endfor
1576   return l
1577 endfunction
1579 function! haskellmode#MergeImport(entry,line,hiding,explicit,module)
1580   let lines    = a:entry['lines'] + [ a:line ]
1581   let hiding   = a:explicit==[] ? haskellmode#ListIntersect(a:entry['hiding'], a:hiding) 
1582                               \ : haskellmode#ListWithout(a:entry['hiding'],a:explicit)
1583   let explicit = haskellmode#ListUnion(a:entry['explicit'], a:explicit)
1584   let modules  = haskellmode#ListUnion(a:entry['modules'], [ a:module ])
1585   return {'lines':lines,'hiding':hiding,'explicit':explicit,'modules':modules}
1586 endfunction
1588 " collect lines belonging to a single import statement;
1589 " return number of last line and collected import statement
1590 " (assume opening parenthesis, if any, is on the first line)
1591 function! haskellmode#GatherImport(lineno)
1592   let lineno = a:lineno
1593   let import = getline(lineno)
1594   if !(import=~'^import\s') | return [] | endif
1595   let open  = strlen(substitute(import,'[^(]','','g'))
1596   let close = strlen(substitute(import,'[^)]','','g'))
1597   while open!=close
1598     let lineno += 1
1599     let linecont = getline(lineno)
1600     let open  += strlen(substitute(linecont,'[^(]','','g'))
1601     let close += strlen(substitute(linecont,'[^)]','','g'))
1602     let import .= linecont
1603   endwhile
1604   return [lineno,import]
1605 endfunction
1607 function! haskellmode#UrlEncode(string)
1608   let pat  = '\([^[:alnum:]]\)'
1609   let code = '\=printf("%%%02X",char2nr(submatch(1)))'
1610   let url  = substitute(a:string,pat,code,'g')
1611   return url
1612 endfunction
1614 " TODO: we could have buffer-local settings, at the expense of
1615 "       reconfiguring for every new buffer.. do we want to?
1616 function! haskellmode#GHC()
1617   if (!exists("g:ghc") || !executable(g:ghc)) 
1618     if !executable('ghc') 
1619       echoerr s:scriptname.": can't find ghc. please set g:ghc, or extend $PATH"
1620       return 0
1621     else
1622       let g:ghc = 'ghc'
1623     endif
1624   endif    
1625   return 1
1626 endfunction
1628 function! haskellmode#GHC_Version()
1629   if !exists("g:ghc_version")
1630     let g:ghc_version = substitute(system(g:ghc . ' --numeric-version'),'\n','','')
1631   endif
1632   return g:ghc_version
1633 endfunction
1635 function! haskellmode#GHC_VersionGE(target)
1636   let current = split(haskellmode#GHC_Version(), '\.' )
1637   let target  = a:target
1638   for i in current
1639     if ((target==[]) || (i>target[0]))
1640       return 1
1641     elseif (i==target[0])
1642       let target = target[1:]
1643     else
1644       return 0
1645     endif
1646   endfor
1647   return 1
1648 endfunction
1650 doc/haskellmode.txt     [[[1
1652 *haskellmode.txt*       Haskell Mode Plugins    02/05/2009
1654 Authors:
1655     Claus Reinke <claus.reinke@talk21.com> ~
1657 Homepage:
1658     http://projects.haskell.org/haskellmode-vim
1660 CONTENTS                                                         *haskellmode*
1662     1. Overview                                     |haskellmode-overview|
1663         1.1 Runtime Requirements                    |haskellmode-requirements|
1664         1.2 Quick Reference                         |haskellmode-quickref|
1665     2. Settings                                     |haskellmode-settings|
1666       2.1 GHC and web browser                       |haskellmode-settings-main|
1667       2.2 Fine tuning - more configuration options  |haskellmode-settings-fine|
1668     3. GHC Compiler Integration                     |haskellmode-compiler|
1669     4. Haddock Integration                          |haskellmode-haddock|
1670         4.1 Indexing                                |haskellmode-indexing|
1671         4.2 Lookup                                  |haskellmode-lookup|
1672         4.3 Editing                                 |haskellmode-editing|
1673     5. Hpaste Integration                           |haskellmode-hpaste|
1674     6. Additional Resources                         |haskellmode-resources|
1676 ==============================================================================
1677                                                         *haskellmode-overview*
1678 1. Overview ~
1680     The Haskell mode plugins provide advanced support for Haskell development
1681     using GHC/GHCi on Windows and Unix-like systems. The functionality is
1682     based on Haddock-generated library indices, on GHCi's interactive
1683     commands, or on simply activating (some of) Vim's built-in program editing
1684     support in Haskell-relevant fashion. These plugins live side-by-side with
1685     the pre-defined |syntax-highlighting| support for |haskell| sources, and
1686     any other Haskell-related plugins you might want to install (see
1687     |haskellmode-resources|).
1689     The Haskell mode plugins consist of three filetype plugins (haskell.vim,
1690     haskell_doc.vim, haskell_hpaste.vim), which by Vim's |filetype| detection
1691     mechanism will be auto-loaded whenever files with the extension '.hs' are
1692     opened, and one compiler plugin (ghc.vim) which you will need to load from
1693     your vimrc file (see |haskellmode-settings|).
1696                                                     *haskellmode-requirements*
1697 1.1 Runtime Requirements ~
1699     The plugins require a recent installation of GHC/GHCi. The functionality
1700     derived from Haddock-generated library indices also requires a local
1701     installation of the Haddock documentation for GHC's libraries (if there is
1702     no documentation package for your system, you can download a tar-ball from
1703     haskell.org), as well as an HTML browser (see |haddock_browser|). If you 
1704     want to use the experimental hpaste interface, you will also need Wget.
1706     * GHC/GHCi ~
1707       Provides core functionality. http://www.haskell.org/ghc
1709     * HTML library documentation files and indices generated by Haddock ~
1710       These usually come with your GHC installation, possibly as a separate
1711       package. If you cannot get them this way, you can download a tar-ball
1712       matching your GHC version from  http://www.haskell.org/ghc/docs/
1714     * HTML browser with basic CSS support ~
1715       For browsing Haddock docs.
1717     * Wget ~
1718       For interfacing with http://hpaste.org.
1720       Wget is widely available for modern Unix-like operating systems. Several
1721       ports also exist for Windows, including:
1723       - Official GNU Wget (natively compiled for Win32)
1724         http://www.gnu.org/software/wget/#downloading
1726       - UnxUtils Wget (natively compiled for Win32, bundled with other ported
1727         Unix utilities)
1728         http://sourceforge.net/projects/unxutils/
1730       - Cygwin Wget (emulated POSIX in Win32, must be run under Cygwin)
1731         http://cygwin.com/packages/wget/
1733                                                     *haskellmode-quickref*
1734 1.2 Quick Reference ~
1736 |:make|               load into GHCi, show errors (|quickfix| |:copen|)
1737 |_ct|                 create |tags| file 
1738 |_si|                 show info for id under cursor
1739 |_t|                  show type for id under cursor
1740 |_T|                  insert type declaration for id under cursor
1741 |balloon|             show type for id under mouse pointer
1742 |_?|                  browse Haddock entry for id under cursor
1743 |_?1|                 search Hoogle for id under cursor
1744 |_?2|                 search Hayoo! for id under cursor
1745 |:IDoc| {identifier}  browse Haddock entry for unqualified {identifier}
1746 |:MDoc| {module}      browse Haddock entry for {module}
1747 |:FlagReference| {s}  browse Users Guide Flag Reference for section {s}
1748 |_.|                  qualify unqualified id under cursor
1749 |_i|                  add 'import <module>(<identifier>)' for id under cursor
1750 |_im|                 add 'import <module>' for id under cursor
1751 |_iq|                 add 'import qualified <module>(<identifier>)' for id under cursor
1752 |_iqm|                add 'import qualified <module>' for id under cursor
1753 |_ie|                 make imports explit for import statement under cursor
1754 |_opt|                add OPTIONS_GHC pragma
1755 |_lang|               add LANGUAGE pragma
1756 |i_CTRL-X_CTRL-O|     insert-mode completion based on imported ids (|haskellmode-XO|)
1757 |i_CTRL-X_CTRL-U|     insert-mode completion based on documented ids (|haskellmode-XU|)
1758 |i_CTRL-N|            insert-mode completion based on imported sources
1759 |:GHCi|{command/expr} run GHCi command/expr in current module
1761 |:GHCStaticOptions|   edit static GHC options for this buffer
1762 |:DocSettings|        show current Haddock-files-related plugin settings
1763 |:DocIndex|           populate Haddock index 
1764 |:ExportDocIndex|     cache current Haddock index to a file
1765 |:HpasteIndex|        Read index of most recent entries from hpaste.org
1766 |:HpastePostNew|      Submit current buffer as a new hpaste 
1769 ==============================================================================
1770                                                         *haskellmode-settings*
1771 2. Settings ~
1773     The plugins try to find their dependencies in standard locations, so if
1774     you're lucky, you will only need to set |compiler| to ghc, and configure
1775     the location of your favourite web browser. You will also want to make
1776     sure that |filetype| detection and |syntax| highlighting are on. Given the
1777     variety of things to guess, however, some dependencies might not be found
1778     correctly, or the defaults might not be to your liking, in which case you
1779     can do some more fine tuning. All of this configuration should happen in
1780     your |vimrc|.
1782         " enable syntax highlighting
1783         syntax on
1785         " enable filetype detection and plugin loading
1786         filetype plugin on
1789                                                    *haskellmode-settings-main*
1790 2.1 GHC and web browser ~
1792                                                  *compiler-ghc* *ghc-compiler*
1793     To use the features provided by the GHC |compiler| plugin, use the
1794     following |autocommand| in your vimrc:
1796         au BufEnter *.hs compiler ghc
1798                                                                        *g:ghc*
1799     If the compiler plugin can't locate your GHC binary, or if you have
1800     several versions of GHC installed and have a preference as to which binary
1801     is used, set |g:ghc|:
1803         :let g:ghc="/usr/bin/ghc-6.6.1"
1805                                                            *g:haddock_browser*
1806     The preferred HTML browser for viewing Haddock documentation can be set as
1807     follows:
1809         :let g:haddock_browser="/usr/bin/firefox"
1812                                                    *haskellmode-settings-fine*
1813 2.2 Fine tuning - more configuration options ~
1815     Most of the fine tuning is likely to happen for the haskellmode_doc.vim
1816     plugin, so you can check the current settings for this plugin via the
1817     command |:DocSettings|. If all the settings reported there are to your
1818     liking, you probably won't need to do any fine tuning.
1820                                                 *g:haddock_browser_callformat*
1821     By default, the web browser|g:haddock_browser| will be started
1822     asynchronously (in the background) on Windows or when vim is running in a
1823     GUI, and synchronously (in the foreground) otherwise. These settings seem
1824     to work fine if you are using a console mode browser (eg, when editing in
1825     a remote session), or if you are starting a GUI browser that will launch
1826     itself in the background. But if these settings do not work for you, you
1827     can change the default browser launching behavior.
1829     This is controlled by |g:haddock_browser_callformat|. It specifies a
1830     format string which uses two '%s' parameters, the first representing the
1831     path of the browser to launch, and the second is the documentation URL
1832     (minus the protocol specifier, i.e. file://) passed to it by the Haddock
1833     plugin.  For instance, to launch a GUI browser on Unix-like systems and
1834     force it to the background (see also |shellredir|):
1836         :let g:haddock_browser_callformat = '%s file://%s '.printf(&shellredir,'/dev/null').' &'
1838                                                             *g:haddock_docdir*
1839     Your system's installed Haddock documentation for GHC and its libraries
1840     should be automatically detected. If the plugin can't locate them, you
1841     must point |g:haddock_docdir| to the path containing the master index.html
1842     file for the subdirectories 'libraries', 'Cabal', 'users_guide', etc.:
1844         :let g:haddock_docdir="/usr/local/share/doc/ghc/html/"
1846                                                       *g:haddock_indexfiledir*
1847     The information gathered from Haddock's index files will be stored in a
1848     file called 'haddock_index.vim' in a directory derived from the Haddock
1849     location, or in $HOME. To configure another directory for the index file,
1850     use: 
1852         :let g:haddock_indexfiledir="~/.vim/"
1854                                                                       *g:wget*
1855     If you also want to try the experimental hpaste functionality, you might
1856     you need to set |g:wget| before the |hpaste| plugin is loaded (unless wget
1857     is in your PATH):
1859         :let g:wget="C:\Program Files\wget\wget.exe"
1862     Finally, the mappings actually use|<LocalLeader>|behind the scenes, so if
1863     you have to, you can redefine|maplocalleader|to something other than '_'.
1864     Just remember that the docs still refer to mappings starting with '_', to
1865     avoid confusing the majority of users!-)
1867 ==============================================================================
1868                                                   *haskellmode-compiler* *ghc*
1869 3. GHC Compiler Integration ~
1871     The GHC |compiler| plugin sets the basic |errorformat| and |makeprg| to
1872     enable |quickfix| mode using GHCi, and provides functionality for show
1873     info (|_si|), show type (|_t| or mouse |balloon|), add type declaration
1874     (|_T|), create tag file (|_ct|), and insert-mode completion
1875     (|i_CTRL-X_CTRL-O|) based on GHCi browsing of the current and imported
1876     modules. 
1878     To avoid frequent calls to GHCi, type information is cached in Vim. The
1879     cache will be populated the first time a command depends on it, and will
1880     be refreshed every time a |:make| goes through without generating errors
1881     (if the |:make| does not succeed, the old types will remain available in
1882     Vim).  You can also unconditionally force reloading of type info using
1883     |:GHCReload| (if GHCi cannot load your file, the type info will be empty).
1886     In addition to the standard|quickfix| commands, the GHC compiler plugin
1887     provides:
1889                                                                   *:GHCReload*
1890 :GHCReload              Reload modules and unconditionally refresh cache of
1891                         type info. Usually, |:make| is prefered, as that will
1892                         refresh the cache only if GHCi reports no errors, and
1893                         show the errors otherwise.
1895                                                            *:GHCStaticOptions*
1896 :GHCStaticOptions       Edit the static GHC options (more generally, options
1897                         that cannot be set by in-file OPTIONS_GHC pragmas)
1898                         for the current buffer. Useful for adding hidden 
1899                         packages (-package ghc), or additional import paths
1900                         (-isrc; you will then also want to augment |path|).
1901                         If you have static options you want to set as
1902                         defaults, you could use b:ghc_staticoptions, eg:
1904                         au FileType haskell let b:ghc_staticoptions = '-isrc'
1905                         au FileType haskell setlocal path += src
1908                                                                        *:GHCi*
1909 :GHCi {command/expr}    Run GHCi commands/expressions in the current module.                  
1911                                                                          *_ct*
1912 _ct                     Create |tags| file for the current Haskell source
1913                         file. This uses GHCi's :ctags command, so it will work
1914                         recursively, but will only list tags for exported
1915                         entities.
1917                                                                         *_opt*
1918 _opt                    Shows a menu of frequently used GHC compiler options 
1919                         (selecting an entry adds the option as a pragma to the
1920                         start of the file). Uses popup menu (GUI) or :emenu
1921                         and command-line completion (CLI).
1923                                                                        *_lang*
1924 _lang                   Shows a menu of the LANGUAGE options supported by GHC
1925                         (selecting an entry adds the language as a pragma to 
1926                         the start of the file). Uses popup menu (GUI) or
1927                         :emenu and command-line completion (CLI).
1929                                                                          *_si*
1930 _si                     Show extended information for the name under the
1931                         cursor. Uses GHCi's :info command. Output appears in
1932                         |preview-window| (when done, close with |:pclose|).
1934                                                                           *_t*
1935 _t                      Show type for the name under the cursor. Uses cached
1936                         info from GHCi's :browse command.
1938                                                                           *_T*
1939 _T                      Insert type declaration for the name under the cursor.
1940                         Uses cached info from GHCi's :browse command.
1942                                 *haskellmode-XO* *haskellmode-omni-completion*
1943 CTRL-X CTRL-O           Standard insert-mode omni-completion based on the
1944                         cached type info from GHCi browsing current and
1945                         imported modules. Only names from the current and from
1946                         imported modules are included (the completion menu
1947                         also show the type of each identifier).
1949 ==============================================================================
1950                                                *haskellmode-haddock* *haddock*
1951 4. Haddock Integration ~
1953     Haskell mode integrates with Haddock-generated HTML documentation,
1954     providing features such as navigating to the Haddock entry for the
1955     identifier under the cursor (|_?|), completion for the identifier under
1956     the cursor (|i_CTRL-X_CTRL-U|), and adding import statements (|_i| |_im|
1957     |_iq| |_iqm|) or module qualifier (|_.|) for the identifier under the
1958     cursor.
1960     These commands operate on an internal Haddock index built from the
1961     platform's installed Haddock documentation for GHC's libraries. Since
1962     populating this index takes several seconds, it should be stored as a 
1963     file called 'haddock_index.vim' in the directory specified by
1964     |g:haddock_indexfiledir|.
1966     Some commands present a different interface (popup menu or command-line
1967     completion) according to whether the current Vim instance is graphical or
1968     console-based (actually: whether or not the GUI is running). Such
1969     differences are marked below with the annotations (GUI) and (CLI),
1970     respectively.
1972     |:DocSettings| shows the settings for this plugin. If you are happy with
1973     them, you can call |:ExportDocIndex| to populate and write out the
1974     documentation index (should be called once for every new version of GHC).
1976                                                                 *:DocSettings*
1977 :DocSettings            Show current Haddock-files-related plugin settings.
1980                                                         *haskellmode-indexing*
1981 4.1 Indexing ~
1983                                                                    *:DocIndex*
1984 :DocIndex               Populate the Haddock index from the GHC library
1985                         documentation.
1987                                                              *:ExportDocIndex*
1988 :ExportDocIndex         Cache the current Haddock index to a file (populate
1989                         index first, if empty).
1992                                                           *haskellmode-lookup*
1993 4.2 Lookup ~
1995                                                                           *_?*
1996 _?                      Open the Haddock entry (in |haddock_browser|) for an
1997                         identifier under the cursor, selecting full
1998                         qualifications from a popup menu (GUI) or via
1999                         command-line completion (CLI), if the identifier is
2000                         not qualified.
2002                                                                          *_?1*
2003 _?1                     Search Hoogle (using |haddock_browser|) for an
2004                         identifier under the cursor.
2007                                                                          *_?2*
2008 _?2                     Search Hayoo! (using |haddock_browser|) for an
2009                         identifier under the cursor.
2011                                                                        *:IDoc*
2012 :IDoc {identifier}      Open the Haddock entry for the unqualified
2013                         {identifier} in |haddock_browser|, suggesting possible
2014                         full qualifications.
2016                                                                        *:MDoc*
2017 :MDoc {module}          Open the Haddock entry for {module} in
2018                         |haddock_browser| (with command-line completion for
2019                         the fully qualified module name).
2021                                                               *:FlagReference*
2022 :FlagReference {s}      Browse Users Guide Flag Reference for section {s}
2023                         (with command-line completion for section headers).
2026                                                          *haskellmode-editing*
2027 4.3 Editing ~
2029                                                                           *_.*
2030 _.                      Fully qualify the unqualified name under the cursor
2031                         selecting full qualifications from a popup menu (GUI)
2032                         or via command-line completion (CLI).
2034                                                                     *_iq* *_i*
2035 _i _iq                  Add 'import [qualified] <module>(<identifier>)'
2036                         statement for the identifier under the cursor,
2037                         selecting fully qualified modules from a popup menu
2038                         (GUI) or via command-line completion (CLI), if the
2039                         identifier is not qualified.  This currently adds one
2040                         import statement per call instead of merging into
2041                         existing import statements.
2043                                                                   *_iqm* *_im*
2044 _im                     Add 'import [qualified] <module>' statement for the
2045                         identifier under the cursor, selecting fully qualified
2046                         modules from a popup menu (GUI) or via command-line
2047                         completion (CLI), if the identifier is not qualified.
2048                         This currently adds one import statement per call
2049                         instead of merging into existing import statements.
2051                                                                          *_ie*
2052 _ie                     On an 'import <module>' line, in a correctly loadable
2053                         module, temporarily comment out import and use :make
2054                         'not in scope' errors to explicitly list imported
2055                         identifiers.
2057                                 *haskellmode-XU* *haskellmode-user-completion*
2058 CTRL-X CTRL-U           User-defined insert mode name completion based on all
2059                         names known to the Haddock index, including package
2060                         names. Completions are presented in a popup menu which
2061                         also displays the fully qualified module from which
2062                         each entry may be imported. 
2064                         CamelCode shortcuts are supported, meaning that
2065                         lower-case letters can be elided, using only
2066                         upper-case letters and module qualifier separators (.)
2067                         for disambiguation:
2069                           pSL    -> putStrLn
2070                           C.E.t  -> Control.Exception.t
2071                           C.M.MP -> Control.Monad.MonadPlus
2073                         To reduce unwanted matches, the first letter of such
2074                         shortcuts and the first letter after each '.' have to
2075                         match directly.
2077 ==============================================================================
2078                                                  *haskellmode-hpaste* *hpaste*
2079 5. Hpaste Integration ~
2081     This experimental feature allows browsing and posting to
2082     http://hpaste.org, a Web-based pastebin tailored for Haskell code.
2085                                                                 *:HpasteIndex*
2086 :HpasteIndex            Read the most recent entries from hpaste.org. Show an
2087                         index of the entries in a new buffer, where ',r' will
2088                         open the current highlighted entry [and ',p' will
2089                         annotate it with the current buffer].
2091                                                               *:HpastePostNew*
2092 :HpastePostNew          Submit current buffer as a new hpaste entry.
2093                         [This, and ',p' above, are temporarily disabled, 
2094                          needs update to new hpaste.org layout]
2096 ==============================================================================
2097                                                        *haskellmode-resources*
2098 6. Additional Resources ~
2100     An quick screencast tour through of these plugins is available at:
2102     http://projects.haskell.org/haskellmode-vim/screencasts.html
2104     Other Haskell-related Vim plugins can be found here:
2106     http://www.haskell.org/haskellwiki/Libraries_and_tools/Program_development#Vim
2108     Make sure to read about Vim's other program-editing features in its online
2109     |user-manual|. Also have a look at Vim tips and plugins at www.vim.org -
2110     two other plugins I tend to use when editing Haskell are AlignPlugin.vim
2111     (to line up regexps for definitions, keywords, comments, etc. in
2112     consecutive lines) and surround.vim (to surround text with quotes,
2113     brackets, parentheses, comments, etc.).
2115 ==============================================================================
2116  vim:tw=78:ts=8:ft=help: