Skip to content

Instantly share code, notes, and snippets.

@nkpart
Last active December 19, 2015 08:09
Show Gist options
  • Save nkpart/5923908 to your computer and use it in GitHub Desktop.
Save nkpart/5923908 to your computer and use it in GitHub Desktop.
Pipe SBT compile errors in an errors.err file, that VIM can load into its quickfix list

Ghetto SBT + Vim Quickfix Integration

In combination with SBT ~[action], this script will populate an errors file with any errors at the end of each compile session. I think it's a neat example of the State monad and some simple regular expressions.

The output of SBT needs to be run through the script. Using tee allows you to still see the output in your terminal. User interaction with SBT is unaffected too, woo!

$ sbt ~compile | tee >(runhaskell Sbt.hs)

Then in VIM, just call :cfile, which will (by default) load up 'errors.err' into the quickfix list.

You can also supply an output file as an argument:

$ sbt ~compile | tee >(runhaskell Sbt.hs my_errors)
:cfile my_errors
module Sbt where
import System.FilePath (makeRelative)
import Text.Regex
import Control.Monad.State
import Data.List (isInfixOf)
import System.Environment (getArgs)
import Control.Applicative ((<$>))
import System.Directory (getCurrentDirectory)
main :: IO ()
main = do
base <- getCurrentDirectory
args <- getArgs
let f = case args of
[] -> "errors.err"
(x:_) -> x
void $ flip runStateT [] $ forever $ do
line <- filterAnsi <$> liftIO getLine
if sessionTerminated line
then do
content <- join . map (++"\n") . reverse <$> get
liftIO $ writeFile f content
put []
else
case compileError base line of
Just s -> modify (s:)
Nothing -> return ()
filterAnsi :: String -> String
filterAnsi line = subRegex ansiRegex stripped ""
where stripped = filter (/= '\ESC') line
ansiRegex, compileRegex :: Regex
ansiRegex = mkRegex "\\[[0-9]+m"
compileRegex = mkRegex "^\\[error\\] (.*:[0-9]+:.*)$"
compileError :: FilePath -> String -> Maybe String
compileError b s = let s' = if "Total time" `isInfixOf` s then Nothing else Just s
in (makeRelative b . join) <$> (matchRegex compileRegex =<< s')
sessionTerminated :: String -> Bool
sessionTerminated = ("Waiting for source" `isInfixOf`)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment