-- findExecutable

module Development.Shake.Linters ( tomlcheck
                                 , yamllint
                                 , hlint
                                 , shellcheck
                                 , ghc
                                 , module Development.Shake.FileDetect
                                 ) where

import Development.Shake
import           Development.Shake.FileDetect

checkFiles :: String -> [FilePath] -> Action ()
checkFiles str = mapM_ (cmd_ . ((str ++ " ") ++))

-- | Lint @.sh@ files using
-- [shellcheck](http://hackage.haskell.org/package/ShellCheck).
shellcheck :: [FilePath] -> Action ()
shellcheck = checkFiles "shellcheck"

ghc :: Action ()
ghc = checkFiles "ghc -Wall -Werror -Wincomplete-uni-patterns -Wincomplete-record-updates -fno-code" =<< getHs

-- | Check all @.toml@ files using
-- [tomlcheck](http://hackage.haskell.org/package/tomlcheck).
tomlcheck :: Action ()
tomlcheck = checkFiles "tomlcheck --file" =<< getToml

-- | Lint all @.hs@, @.hsig@, and @.hs-boot@ files using
-- [hlint](http://hackage.haskell.org/package/hlint).
hlint :: Action ()
hlint = checkFiles "hlint" =<< getHs

-- | Lint all files ending in @yaml@ or @yml@ using
-- [yamllint](https://pypi.python.org/pypi/yamllint).
yamllint :: Action ()
yamllint = checkFiles "yamllint -s" =<< getYml