Hi devs,
I see in CI that we're now linting the GHC source code. In order to avoid CI
failure, I would like to lint locally, and I somehow know (though I forget
where I learned it) that hadrian/build lint:compiler is the way to do this.
After building hlint, I am able to do this. But the output is surprising; here
is the tail:
# hlint (for lint:compiler)
compiler/GHC/Tc/Utils/Unify.hs:2:1-36: Warning: Unused LANGUAGE pragma
Found:
{-# LANGUAGE MultiWayIf #-}
Perhaps you should remove it.
compiler/stage1/build/GHC/Parser.hs:6:1-29: Warning: Unused LANGUAGE pragma
Found:
{-# LANGUAGE ViewPatterns #-}
Perhaps you should remove it.
compiler/stage1/build/GHC/Parser.hs:8:1-27: Warning: Unused LANGUAGE pragma
Found:
{-# LANGUAGE LambdaCase #-}
Perhaps you should remove it.
compiler/stage1/build/GHC/Parser.hs:38:1-54: Warning: Use fewer imports
Found:
import Control.Monad ( unless, liftM, when, (<=<) )
import Control.Monad ( ap )
Perhaps:
import Control.Monad ( unless, liftM, when, (<=<), ap )
compiler/stage1/build/GHC/Parser.hs:43:1-18: Warning: Use fewer imports
Found:
import GHC.Prelude
import GHC.Prelude
Perhaps:
import GHC.Prelude
compiler/stage1/build/GHC/Cmm/Parser.hs:17:1-24: Warning: Use fewer imports
Found:
import GHC.StgToCmm.Prof
import GHC.StgToCmm.Prof
Perhaps:
import GHC.StgToCmm.Prof
compiler/stage1/build/GHC/Cmm/Parser.hs:71:1-20: Warning: Use fewer imports
Found:
import Control.Monad
import Control.Monad ( ap )
Perhaps:
import Control.Monad
compiler/stage2/build/GHC/Parser.hs:6:1-29: Warning: Unused LANGUAGE pragma
Found:
{-# LANGUAGE ViewPatterns #-}
Perhaps you should remove it.
compiler/stage2/build/GHC/Parser.hs:8:1-27: Warning: Unused LANGUAGE pragma
Found:
{-# LANGUAGE LambdaCase #-}
Perhaps you should remove it.
compiler/stage2/build/GHC/Parser.hs:38:1-54: Warning: Use fewer imports
Found:
import Control.Monad ( unless, liftM, when, (<=<) )
import Control.Monad ( ap )
Perhaps:
import Control.Monad ( unless, liftM, when, (<=<), ap )
compiler/stage2/build/GHC/Parser.hs:43:1-18: Warning: Use fewer imports
Found:
import GHC.Prelude
import GHC.Prelude
Perhaps:
import GHC.Prelude
compiler/stage2/build/GHC/Cmm/Parser.hs:17:1-24: Warning: Use fewer imports
Found:
import GHC.StgToCmm.Prof
import GHC.StgToCmm.Prof
Perhaps:
import GHC.StgToCmm.Prof
compiler/stage2/build/GHC/Cmm/Parser.hs:71:1-20: Warning: Use fewer imports
Found:
import Control.Monad
import Control.Monad ( ap )
Perhaps:
import Control.Monad
13 hints
Error when running Shake build system:
at want, called at src/Main.hs:104:30 in main:Main
* Depends on: lint:compiler
at cmd_, called at src/Rules/Lint.hs:70:3 in main:Rules.Lint
* Raised the exception:
Development.Shake.cmd, system command failed
Command line: hlint -j --cpp-define x86_64_HOST_ARCH --cpp-include=includes
--cpp-include=_build/stage1/lib --cpp-include=compiler
--cpp-include=_build/stage1/lib/ghcplatform.h
--cpp-include=_build/stage1/compiler/build -h compiler/.hlint.yaml compiler
Exit code: 1
Stderr:
There are several curiosities here:
* I introduced one of these errors, in GHC.Tc.Utils.Unify; the other errors are
in files I have not modified. Will these affect CI?
* Hadrian crashes at the end. Is that expected? It says "system command failed"
with a bunch of gobbledegook. Is this an error within Hadrian? Or is this just
Hadrian's way of saying that it encountered an error when linting? If it's the
latter, the current message is hard to read.
* As you may be able to see, I use a dark-background terminal window. The
colors output by the hlint process are nigh impossible to read when describing
redundant LANGUAGE pragmas. Are these colors configurable?
Thanks!
Richard
_______________________________________________
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs