module Hadolint.Rule.DL3015 (rule) where

import Hadolint.Rule
import Hadolint.Shell (ParsedShell)
import qualified Hadolint.Shell as Shell
import Language.Docker.Syntax


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

dl3015 :: Rule ParsedShell
dl3015 :: Rule ParsedShell
dl3015 = 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
"DL3015"
    severity :: DLSeverity
severity = DLSeverity
DLInfoC
    message :: Text
message = Text
"Avoid additional packages by specifying `--no-install-recommends`"

    check :: Instruction ParsedShell -> Bool
check (Run (RunArgs Arguments ParsedShell
args RunFlags
_)) = forall a b. (a -> b) -> Arguments a -> b
foldArguments ((Command -> Bool) -> ParsedShell -> Bool
Shell.noCommands Command -> Bool
forgotNoInstallRecommends) Arguments ParsedShell
args
    check Instruction ParsedShell
_ = Bool
True

    forgotNoInstallRecommends :: Command -> Bool
forgotNoInstallRecommends Command
cmd = Command -> Bool
isAptGetInstall Command
cmd Bool -> Bool -> Bool
&& Bool -> Bool
not (Command -> Bool
disablesRecommendOption Command
cmd)
    isAptGetInstall :: Command -> Bool
isAptGetInstall = Text -> [Text] -> Command -> Bool
Shell.cmdHasArgs Text
"apt-get" [Text
"install"]
    disablesRecommendOption :: Command -> Bool
disablesRecommendOption Command
cmd =
      Text -> Command -> Bool
Shell.hasFlag Text
"no-install-recommends" Command
cmd
        Bool -> Bool -> Bool
|| Text -> Command -> Bool
Shell.hasArg Text
"APT::Install-Recommends=false" Command
cmd
{-# INLINEABLE dl3015 #-}