Suppress output of hlint

This commit is contained in:
Kohei Suzuki 2014-03-21 21:40:02 +09:00
parent 5aa5d3cbca
commit 44eff0dcc1
1 changed files with 15 additions and 1 deletions

View File

@ -1,9 +1,13 @@
module Language.Haskell.GhcMod.Lint where module Language.Haskell.GhcMod.Lint where
import Control.Applicative import Control.Applicative
import Control.Exception (finally)
import Data.List import Data.List
import GHC.IO.Handle (hDuplicate, hDuplicateTo)
import Language.Haskell.GhcMod.Types import Language.Haskell.GhcMod.Types
import Language.Haskell.HLint import Language.Haskell.HLint
import System.Directory (getTemporaryDirectory, removeFile)
import System.IO (hClose, openTempFile, stdout)
-- | Checking syntax of a target file using hlint. -- | Checking syntax of a target file using hlint.
-- Warnings and errors are returned. -- Warnings and errors are returned.
@ -18,4 +22,14 @@ lintSyntax opt file = pack <$> lint opt file
lint :: Options lint :: Options
-> FilePath -- ^ A target file. -> FilePath -- ^ A target file.
-> IO [String] -> IO [String]
lint opt file = map show <$> hlint ([file] ++ hlintOpts opt) lint opt file = map show <$> suppressStdout (hlint ([file] ++ hlintOpts opt))
suppressStdout :: IO a -> IO a
suppressStdout f = do
tmpdir <- getTemporaryDirectory
(path, handle) <- openTempFile tmpdir "ghc-mod-hlint"
removeFile path
dup <- hDuplicate stdout
hDuplicateTo handle stdout
hClose handle
f `finally` hDuplicateTo dup stdout