module Hadolint.Rule.DL3038 (rule) where

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


rule :: Rule Shell.ParsedShell
rule :: Rule ParsedShell
rule = Rule ParsedShell
dl3038 Rule ParsedShell -> Rule ParsedShell -> Rule ParsedShell
forall a. Semigroup a => a -> a -> a
<> Rule ParsedShell -> Rule ParsedShell
forall args. Rule args -> Rule args
onbuild Rule ParsedShell
dl3038
{-# INLINEABLE rule #-}

dl3038 :: Rule Shell.ParsedShell
dl3038 :: Rule ParsedShell
dl3038 = 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
"DL3038"
    severity :: DLSeverity
severity = DLSeverity
DLWarningC
    message :: Text
message = Text
"Use the -y switch to avoid manual input `dnf install -y <package`"

    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 ((Command -> Bool) -> ParsedShell -> Bool
Shell.noCommands Command -> Bool
forgotDnfYesOption) Arguments ParsedShell
args
    check Instruction ParsedShell
_ = Bool
True

    forgotDnfYesOption :: Command -> Bool
forgotDnfYesOption Command
cmd = Command -> Bool
isDnfInstall Command
cmd Bool -> Bool -> Bool
&& Bool -> Bool
not (Command -> Bool
hasYesOption Command
cmd)
    isDnfInstall :: Command -> Bool
isDnfInstall = [Text] -> [Text] -> Command -> Bool
Shell.cmdsHaveArgs [Text]
dnfCmds [Text
"install", Text
"groupinstall", Text
"localinstall"]
    hasYesOption :: Command -> Bool
hasYesOption = [Text] -> Command -> Bool
Shell.hasAnyFlag [Text
"y", Text
"assumeyes"]
    dnfCmds :: [Text]
dnfCmds = [Text
"dnf", Text
"microdnf"]
{-# INLINEABLE dl3038 #-}