module Hadolint.Rule.DL3033 (rule) where

import qualified Data.Text as Text
import Hadolint.Rule
import qualified Hadolint.Shell as Shell
import Language.Docker.Syntax

rule :: Rule Shell.ParsedShell
rule :: Rule ParsedShell
rule = RuleCode
-> DLSeverity
-> Text
-> (Instruction ParsedShell -> Bool)
-> Rule ParsedShell
forall args.
RuleCode
-> DLSeverity -> Text -> (Instruction args -> Bool) -> Rule args
simpleRule RuleCode
code DLSeverity
severity Text
message Instruction ParsedShell -> Bool
check
  where
    code :: RuleCode
code = RuleCode
"DL3033"
    severity :: DLSeverity
severity = DLSeverity
DLWarningC
    message :: Text
message = Text
"Specify version with `yum install -y <package>-<version>`."

    check :: Instruction ParsedShell -> Bool
check (Run (RunArgs Arguments ParsedShell
args RunFlags
_)) = (ParsedShell -> Bool) -> Arguments ParsedShell -> Bool
forall a b. (a -> b) -> Arguments a -> b
foldArguments ((Text -> Bool) -> [Text] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Text -> Bool
versionFixed ([Text] -> Bool) -> (ParsedShell -> [Text]) -> ParsedShell -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParsedShell -> [Text]
yumPackages) Arguments ParsedShell
args
    check Instruction ParsedShell
_ = Bool
True

    versionFixed :: Text -> Bool
versionFixed Text
package =
      Text
"-" Text -> Text -> Bool
`Text.isInfixOf` Text
package
        Bool -> Bool -> Bool
|| Text
".rpm" Text -> Text -> Bool
`Text.isSuffixOf` Text
package
{-# INLINEABLE rule #-}

yumPackages :: Shell.ParsedShell -> [Text.Text]
yumPackages :: ParsedShell -> [Text]
yumPackages ParsedShell
args =
  [ Text
arg | Command
cmd <- ParsedShell -> [Command]
Shell.presentCommands ParsedShell
args, Text -> [Text] -> Command -> Bool
Shell.cmdHasArgs Text
"yum" [Text
"install"] Command
cmd, Text
arg <- Command -> [Text]
Shell.getArgsNoFlags Command
cmd, Text
arg Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
"install"
  ]