module Yi.Hoogle where
import Prelude ()
import Control.Arrow ((&&&))
import Data.Char (isUpper)
import Data.List (isInfixOf, nub, filter, lines, words, map, (!!))
import System.Exit (ExitCode(ExitFailure))
import Yi.Core
import Yi.Process (runProgCommand)
import Yi.Buffer (replaceRegionB, unitWord)
caseSensitize :: [String] -> [String]
caseSensitize = filter (not . isUpper . head)
gv :: [String] -> [String]
gv = filter f
where f x = not $ any (`isInfixOf` x) ["module ", " type ", "package ", " data ", " keyword "]
hoogleRaw :: String -> String -> IO [String]
hoogleRaw srch opts = do (out,_err,status) <- runProgCommand "hoogle" [opts, srch]
when (status == ExitFailure 1) $
fail "Error running hoogle command. Is hoogle on path?"
let results = lines out
if results == ["No results found"] then fail "No Hoogle results"
else return results
hoogleFunctions :: String -> IO [String]
hoogleFunctions a = caseSensitize . gv . nub . map ((!!1) . words) <$> hoogleRaw a ""
hoogleFunModule :: String -> IO [(String, String)]
hoogleFunModule a = map ((head &&& (!! 1)) . words) . gv <$> hoogleRaw a ""
hoogle :: YiM String
hoogle = do
(wordRegion,word) <- withBuffer $ do wordRegion <- regionOfB unitWord
word <- readRegionB wordRegion
return (wordRegion, word)
((modl,fun):_) <- io $ hoogleFunModule word
withBuffer $ replaceRegionB wordRegion fun
return modl
hoogleSearch :: YiM ()
hoogleSearch = do
word <- withBuffer $ do wordRegion <- regionOfB unitWord
readRegionB wordRegion
results <- io $ hoogleRaw word ""
withEditor $ printMsgs $ map show results