{-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE NoImplicitPrelude #-} -- : out lint module Biz.Lint (main) where import Alpha import qualified Biz.Cli as Cli import qualified Biz.Log as Log import Biz.Namespace (Ext (..), Namespace (..)) import qualified Biz.Namespace as Namespace import Biz.Test ((@=?)) import qualified Biz.Test as Test import Data.Maybe (fromJust) import qualified Data.String as String import qualified Data.Text as Text import qualified System.Directory as Directory import qualified System.Environment as Environment import qualified System.Exit as Exit import System.FilePath (()) import qualified System.Process as Process main :: IO () main = Cli.main <| Cli.Plan help move test pure move :: Cli.Arguments -> IO () move args = case Cli.getAllArgs args (Cli.argument "file") of [] -> changedFiles +> run shouldFix +> exit files -> files |> filter notcab |> filterM Directory.doesFileExist +> run shouldFix +> exit where shouldFix = Cli.has args (Cli.longOption "fix") test :: Test.Tree test = Test.group "Biz.Lint" [ Test.unit "haskell files return two Results" <| do results <- run False ["Biz/Lint.hs"] length results @=? 2 ] notcab :: FilePath -> Bool notcab ('_' : _) = False notcab _ = True help :: Cli.Docopt help = [Cli.docopt| all your lint are belong to us Usage: lint --help lint test lint [--fix] [...] |] exit :: [Result] -> IO () exit results = Exit.exitWith <| if n > 0 then Exit.ExitFailure n else Exit.ExitSuccess where n = length <| filter bad results bad = \case (Warn _) -> False Ok {status = Bad _} -> True _ -> False printResult :: Result -> IO Result printResult r@(Warn err) = Log.warn ["lint", err] >> Log.br >> pure r printResult r@(Ok path_ Linter {..} (Bad err)) = Log.fail ["lint", exe, Text.pack path_] >> Log.br >> if err == "" then pure r else putText (Text.pack err) >> pure r printResult r@(Ok path_ Linter {..} Good) = Log.good ["lint", exe, Text.pack path_] >> Log.br >> pure r printResult r@(NoOp path_) = Log.info ["lint", "noop", Text.pack path_] >> Log.br >> pure r changedFiles :: IO [FilePath] changedFiles = mergeBase +> changed where git args = Process.readProcess "git" args "" mergeBase = git ["merge-base", "HEAD", "origin/master"] /> filter (/= '\n') changed mb = String.lines [FilePath] -> IO [Result] run shouldFix paths = do cwd <- Directory.getCurrentDirectory root <- Environment.getEnv "BIZ_ROOT" concat FilePath -> FilePath -> FilePath -> IO [Result] runOne shouldFix root cwd path_ = results +> traverse_ printResult >> results where results = sequence <| case Namespace.fromPath root (cwd path_) of Nothing -> [pure <. Warn <| "could not get namespace for " <> Text.pack path_] Just (Namespace _ Hs) -> [ lint shouldFix ormolu path_, lint shouldFix hlint path_ ] Just (Namespace _ Py) -> [lint shouldFix pylint path_] Just (Namespace _ Sh) -> [pure <| NoOp path_] -- [lint "shellcheck" [] path_] Just (Namespace _ Nix) -> [pure <| NoOp path_] Just (Namespace _ Scm) -> [pure <| NoOp path_] Just _ -> [pure <. Warn <| "no linter for " <> Text.pack path_] lint :: Bool -> Linter -> FilePath -> IO Result lint shouldFix linter@Linter {..} path_ = Process.readProcessWithExitCode (Text.unpack exe) (args_ ++ [path_]) "" +> \case (Exit.ExitSuccess, _, _) -> pure <| Ok path_ linter Good (Exit.ExitFailure _, msg, _) -> pure <| Ok path_ linter <| Bad msg where args_ = map Text.unpack <| if shouldFix && isJust fixArgs then fromJust fixArgs else args