ghc-mod/Language/Haskell/GhcMod/Lint.hs
Nikolay Yakimov 66c8915ebd Fix sporadic spaces in output on hlint parse error
For some reason, haskell-src-exts now adds space before
ints when pretty-printing source location (probably
an issue with Text.PrettyPrint)

This patch avoids using pretty printer altogether.
2016-05-16 11:41:48 +03:00

35 lines
1.4 KiB
Haskell

module Language.Haskell.GhcMod.Lint where
import Exception (ghandle)
import Control.Exception (SomeException(..))
import Language.Haskell.GhcMod.Logger (checkErrorPrefix)
import Language.Haskell.GhcMod.Convert
import Language.Haskell.GhcMod.Types
import Language.Haskell.GhcMod.Monad
import Language.Haskell.HLint3
import Language.Haskell.GhcMod.Utils (withMappedFile)
import Language.Haskell.Exts.SrcLoc (SrcLoc(..))
import System.IO
-- | Checking syntax of a target file using hlint.
-- Warnings and errors are returned.
lint :: IOish m
=> LintOpts -- ^ Configuration parameters
-> FilePath -- ^ A target file.
-> GhcModT m String
lint opt file = ghandle handler $
withMappedFile file $ \tempfile -> do
(flags, classify, hint) <- liftIO $ argsSettings $ optLintHlintOpts opt
hSrc <- liftIO $ openFile tempfile ReadMode
liftIO $ hSetEncoding hSrc (encoding flags)
res <- liftIO $ parseModuleEx flags file =<< Just `fmap` hGetContents hSrc
case res of
Right m -> pack . map show $ applyHints classify hint [m]
Left ParseError{parseErrorLocation=loc, parseErrorMessage=err} ->
return $ showSrcLoc loc ++ ":Error:" ++ err ++ "\n"
where
pack = convert' . map init -- init drops the last \n.
handler (SomeException e) = return $ checkErrorPrefix ++ show e ++ "\n"
showSrcLoc (SrcLoc f l c) = concat [f, ":", show l, ":", show c]