Hello,

Just want to share some results of my weekend hacking.

It is clear that haskell type checker can help to build a list of
suggestions for autocomplete (very old idea). I tried to create a very basic
prototype to play with the idea.

The approach I used:
The task can be divided into the next two parts:
  - find the most general type of the word we are trying to complete
    that will satisfy the type checker
  - find all the symbols that "match" the found type
The first task can be solved using ghc. Just replace the word with "()" and
ghc will tell you something like
  Couldn't match expected type `m String' against inferred type `()'
The second task can be solved using hoogle. Just ask it to find everything
that matches "base :: type", where base -- already known part of the word;
type -- the type that ghc expects.

Source code is attached (linux only at a moment)
haskell.vim -- very basic ftplugin for vim
Place it into your ~/.vim/ftplugin directory (don't forget to backup
an existent file if any)
complete.hs -- simple script that does actual work.

How to use it.
cd to the cabal package you are working on at a moment
mkdir dist/hscomplete
copy complete.hs file to the dist/hscomplete
edit complete.hs (at least change the package name, it is hard coded)
create hoogle database for your package:
  cabal haddock --hoogle
  hoogle --convert=dist/doc/html/<packageName>/<packageName>.hoo +base
+directory +... (all packages you depend on)
start vim (you should be in the directory where <package>.cabal file is placed!)
Use C-X C-O to auto complete

Example:
cabalized package "tmp" contains two modules Data.Tmp and Data.Tmp1
Data.Tmp1 imports Data.Tmp
Data/Tmp.hs contains
  veryLongLongName1 :: Int
  veryLongLongName1 = 1

  veryLongLongName2 :: Char
  veryLongLongName2 = 'c'

  veryLongLongName3 :: String
  veryLongLongName3 = "Hello"

vim src/Data/Tmp1.hs

  import Data.Tmp

  tmp1 :: Monad m => [a] -> m Int
  tmp1 a = very<C-x C-O> suggests veryLongLongName1

  tmp2 :: Monad m => [a] -> m Char
  tmp2 a = very<C-x C-O> suggests veryLongLongName2 and veryLongLongName3

  tmp3 :: Monad m => [a] -> m String
  tmp3 a = very<C-x C-O> suggests veryLongLongName3


Warning: not ready for real use (no error handling, a lot of hard
codes, slow, etc). Just for playing

Yuras

Attachment: haskell.vim
Description: Binary data

module Main
where

import System.IO
import System.Process
import System.Environment
import Text.Regex
import Data.Maybe
import Debug.Trace

basedir = "dist/hscomplete"
logfile = basedir ++ "/log"
inputfile = basedir ++ "/haskell.hs"
outputfile = basedir ++ "/results"
hssourcedir = "src"
packagename = "tmp"
hooglepackages = "+base +directory +process"

main :: IO ()
main = withFile logfile WriteMode complete

complete :: Handle -> IO ()
complete log = do
  hPutStrLn log "log"
  [line', col', base] <- getArgs
  let line = read line' :: Int
  let col = read col' :: Int
  hPutStrLn log $ show line ++ ":" ++ show col ++ ":" ++ base
  content <- fmap (fixContent line col) $ readFile inputfile
  writeFile (basedir ++ "/main.hs") content
  (ec, _, stderr) <- readProcessWithExitCode "ghc" ["--make", basedir ++ "/main.hs", "-i" ++ hssourcedir] []
  hPutStr log stderr
  let re1 = mkRegex "Couldn't match expected type `([^']*)'"
  let re2 = mkRegex "against inferred type `\\(\\)'"
  let m1 = matchRegex re1 stderr
  let m2 = matchRegex re2 stderr
  hPutStrLn log $ "match: " ++ show m1 ++ " " ++ show m2
  if isJust m1 && isJust m2 && length (fromJust m1) == 1
    then do
      (ec, stdout, _) <- readProcessWithExitCode "hoogle" (hoogleOpts ++ [base ++ " :: " ++ (head $ fromJust m1)]) []
      let ls = map (head . drop 1 . take 2 . words) $ lines stdout
      hPutStrLn log (show ls)
      hPutStrLn log $ show (filter (filterBase base) ls)
      withFile outputfile WriteMode (\h -> mapM_ (hPutStrLn h) $ filter (filterBase base) ls)
    else writeFile outputfile ""
  hPutStrLn log "OK"

hoogleOpts = ["--data=dist/doc/html/" ++ packagename ++ "/" ++ packagename ++ ".hoo"] ++ [hooglepackages]

--XXX
fixContent :: Int -> Int -> String -> String
fixContent line col cont = trace (show ln) $ concat $ map (++ "\n") $ pre ++ post
  where
  ls = lines cont
  pre = take (line - 1) ls ++ [ln']
  post = tail post'
  post' = drop (line - 1) ls
  ln = head post'
  ln' = take (col - 1) ln ++ "() " ++ drop col ln

filterBase :: String -> String -> Bool
filterBase base str = ls > lb && str' == base
  where
  lb = length base
  ls = length str
  str' = take lb str

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to