Use MultiWayIf instead of case-matching on ()

This commit is contained in:
Joseph C. Sible 2020-04-05 20:14:03 -04:00
parent 9747b1d5c3
commit df4928f4e3
1 changed files with 16 additions and 16 deletions

View File

@ -19,6 +19,7 @@
-} -}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiWayIf #-}
-- This module contains checks that examine specific commands by name. -- This module contains checks that examine specific commands by name.
module ShellCheck.Checks.Commands (checker, optionalChecks, ShellCheck.Checks.Commands.runTests) where module ShellCheck.Checks.Commands (checker, optionalChecks, ShellCheck.Checks.Commands.runTests) where
@ -578,22 +579,21 @@ checkPrintfVar = CommandCheck (Exactly "printf") (f . arguments) where
let formatCount = length formats let formatCount = length formats
let argCount = length more let argCount = length more
return $ return $ if
case () of | argCount == 0 && formatCount == 0 ->
() | argCount == 0 && formatCount == 0 -> return () -- This is fine
return () -- This is fine | formatCount == 0 && argCount > 0 ->
() | formatCount == 0 && argCount > 0 -> err (getId format) 2182
err (getId format) 2182 "This printf format string has no variables. Other arguments are ignored."
"This printf format string has no variables. Other arguments are ignored." | any mayBecomeMultipleArgs more ->
() | any mayBecomeMultipleArgs more -> return () -- We don't know so trust the user
return () -- We don't know so trust the user | argCount < formatCount && onlyTrailingTs formats argCount ->
() | argCount < formatCount && onlyTrailingTs formats argCount -> return () -- Allow trailing %()Ts since they use the current time
return () -- Allow trailing %()Ts since they use the current time | argCount > 0 && argCount `mod` formatCount == 0 ->
() | argCount > 0 && argCount `mod` formatCount == 0 -> return () -- Great: a suitable number of arguments
return () -- Great: a suitable number of arguments | otherwise ->
() -> warn (getId format) 2183 $
warn (getId format) 2183 $ "This format string has " ++ show formatCount ++ " variables, but is passed " ++ show argCount ++ " arguments."
"This format string has " ++ show formatCount ++ " variables, but is passed " ++ show argCount ++ " arguments."
unless ('%' `elem` concat (oversimplify format) || isLiteral format) $ unless ('%' `elem` concat (oversimplify format) || isLiteral format) $
info (getId format) 2059 info (getId format) 2059