module Development.Shake.Linters ( tomlcheck
, yamllint
, hlint
, shellcheck
, ghc
, dhall
, madlang
, clangFormat
, atsfmt
, stylishHaskell
, cFormat
, module Development.Shake.FileDetect
) where
import Control.Monad (when)
import Data.Char (isSpace)
import Data.Foldable (traverse_)
import Development.Shake
import Development.Shake.FileDetect
dhall :: Action ()
dhall = traverse_ checkDhall =<< getDhall
checkDhall :: FilePath -> Action ()
checkDhall dh = do
contents <- liftIO $ readFile dh
command [Stdin contents] "dhall" []
trim :: String -> String
trim = f . f
where f = reverse . dropWhile isSpace
checkIdempotent :: String -> FilePath -> Action ()
checkIdempotent s p = do
contents <- liftIO $ readFile p
(Stdout out) <- cmd (s ++ " " ++ p)
when (trim contents /= trim out) (error $ "formatter " ++ s ++ " is not fully applied to file " ++ p ++ "!")
stylishHaskell :: [FilePath] -> Action ()
stylishHaskell = traverse_ (checkIdempotent "stylish-haskell")
atsfmt :: [FilePath] -> Action ()
atsfmt = traverse_ (checkIdempotent "atsfmt")
clangFormat :: [FilePath] -> Action ()
clangFormat = traverse_ (checkIdempotent "clang-format")
cFormat :: Action ()
cFormat = clangFormat =<< getC
checkFiles :: String -> [FilePath] -> Action ()
checkFiles str = traverse_ (cmd_ . ((str ++ " ") ++))
madlang :: [FilePath] -> Action ()
madlang = checkFiles "madlang check"
shellcheck :: [FilePath] -> Action ()
shellcheck = checkFiles "shellcheck"
ghc :: [FilePath] -> Action ()
ghc dirs = checkFiles "ghc -Wall -Werror -Wincomplete-uni-patterns -Wincomplete-record-updates -fno-code" =<< getHs dirs
tomlcheck :: Action ()
tomlcheck = checkFiles "tomlcheck --file" =<< getToml
hlint :: [FilePath] -> Action ()
hlint dirs = checkFiles "hlint" =<< getHs dirs
yamllint :: Action ()
yamllint = checkFiles "yamllint -s" =<< getYml