module Development.Shake.Linters ( tomlcheck
, yamllint
, hlint
, shellcheck
, ghc
, atsfmt
, module Development.Shake.FileDetect
) where
import Control.Composition
import Data.Char (isSpace)
import Development.Shake
import Development.Shake.FileDetect
trim :: String -> String
trim = join fmap f
where f = reverse . dropWhile isSpace
checkIdempotent :: String -> FilePath -> Action ()
checkIdempotent s p = do
contents <- liftIO $ readFile p
(Stdout out) <- cmd (s ++ " " ++ p)
if trim contents == trim out then pure () else error "formatter is not fully applied!"
atsfmt :: [FilePath] -> Action ()
atsfmt = mapM_ (checkIdempotent "atsfmt")
checkFiles :: String -> [FilePath] -> Action ()
checkFiles str = mapM_ (cmd_ . ((str ++ " ") ++))
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