module Hadolint.Rule.DL3040 (rule) where

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
"DL3040"
    severity :: DLSeverity
severity = DLSeverity
DLWarningC
    message :: Text
message = Text
"`dnf clean all` missing after dnf command."

    check :: Instruction ParsedShell -> Bool
check (Run (RunArgs Arguments ParsedShell
args RunFlags
_)) = (Text -> Bool) -> [Text] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Arguments ParsedShell -> Text -> Bool
checkMissingClean Arguments ParsedShell
args) [Text]
dnfCmds
    check Instruction ParsedShell
_ = Bool
True

    checkMissingClean :: Arguments ParsedShell -> Text -> Bool
checkMissingClean Arguments ParsedShell
args Text
cmdName =
      (ParsedShell -> Bool) -> Arguments ParsedShell -> Bool
forall a b. (a -> b) -> Arguments a -> b
foldArguments ((Command -> Bool) -> ParsedShell -> Bool
Shell.noCommands ((Command -> Bool) -> ParsedShell -> Bool)
-> (Command -> Bool) -> ParsedShell -> Bool
forall a b. (a -> b) -> a -> b
$ Text -> Command -> Bool
dnfInstall Text
cmdName) Arguments ParsedShell
args
        Bool -> Bool -> Bool
|| ( (ParsedShell -> Bool) -> Arguments ParsedShell -> Bool
forall a b. (a -> b) -> Arguments a -> b
foldArguments ((Command -> Bool) -> ParsedShell -> Bool
Shell.anyCommands ((Command -> Bool) -> ParsedShell -> Bool)
-> (Command -> Bool) -> ParsedShell -> Bool
forall a b. (a -> b) -> a -> b
$ Text -> Command -> Bool
dnfInstall Text
cmdName) Arguments ParsedShell
args
               Bool -> Bool -> Bool
&& (ParsedShell -> Bool) -> Arguments ParsedShell -> Bool
forall a b. (a -> b) -> Arguments a -> b
foldArguments ((Command -> Bool) -> ParsedShell -> Bool
Shell.anyCommands ((Command -> Bool) -> ParsedShell -> Bool)
-> (Command -> Bool) -> ParsedShell -> Bool
forall a b. (a -> b) -> a -> b
$ Text -> Command -> Bool
dnfClean Text
cmdName) Arguments ParsedShell
args
           )

    dnfInstall :: Text -> Command -> Bool
dnfInstall Text
cmdName = Text -> [Text] -> Command -> Bool
Shell.cmdHasArgs Text
cmdName [Text
"install"]
    dnfClean :: Text -> Command -> Bool
dnfClean Text
cmdName = Text -> [Text] -> Command -> Bool
Shell.cmdHasArgs Text
cmdName [Text
"clean", Text
"all"]
    dnfCmds :: [Text]
dnfCmds = [Text
"dnf", Text
"microdnf"]
{-# INLINEABLE rule #-}