module Hadolint.Rule.DL3042 (rule) where

import Data.List (isInfixOf)
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
"DL3042"
    severity :: DLSeverity
severity = DLSeverity
DLWarningC
    message :: Text
message =
      Text
"Avoid use of cache directory with pip. Use `pip install --no-cache-dir <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
forgotNoCacheDir) Arguments ParsedShell
args
    check Instruction ParsedShell
_ = Bool
True
    forgotNoCacheDir :: Command -> Bool
forgotNoCacheDir Command
cmd =
      Command -> Bool
Shell.isPipInstall Command
cmd Bool -> Bool -> Bool
&& Bool -> Bool
not (Command -> Bool
usesNoCacheDir Command
cmd) Bool -> Bool -> Bool
&& Bool -> Bool
not (Command -> Bool
isPipWrapper Command
cmd)
    usesNoCacheDir :: Command -> Bool
usesNoCacheDir Command
cmd = Text
"--no-cache-dir" Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` Command -> [Text]
Shell.getArgs Command
cmd
{-# INLINEABLE rule #-}

isPipWrapper :: Shell.Command -> Bool
isPipWrapper :: Command -> Bool
isPipWrapper cmd :: Command
cmd@(Shell.Command Text
name [CmdPart]
_ [CmdPart]
_) = Text -> Bool
isWrapper Text
"pipx" Bool -> Bool -> Bool
|| Text -> Bool
isWrapper Text
"pipenv"
  where
    isWrapper :: Text.Text -> Bool
    isWrapper :: Text -> Bool
isWrapper Text
w =
      Text
w Text -> Text -> Bool
`Text.isInfixOf` Text
name
        Bool -> Bool -> Bool
|| (Text
"python" Text -> Text -> Bool
`Text.isPrefixOf` Text
name Bool -> Bool -> Bool
&& [Text
"-m", Text
w] [Text] -> [Text] -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isInfixOf` Command -> [Text]
Shell.getArgs Command
cmd)