module Hadolint.Rule.DL3013 (rule) where

import Data.List (isInfixOf)
import qualified Data.Text as Text
import Hadolint.Rule
import Hadolint.Shell (ParsedShell)
import qualified Hadolint.Shell as Shell
import Language.Docker.Syntax

rule :: Rule 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
"DL3013"
    severity :: DLSeverity
severity = DLSeverity
DLWarningC
    message :: Text
message =
      Text
"Pin versions in pip. Instead of `pip install <package>` use `pip install \
      \<package>==<version>` or `pip install --requirement <requirements file>`"
    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
forgotToPinVersion) Arguments ParsedShell
args
    check Instruction ParsedShell
_ = Bool
True

    forgotToPinVersion :: Command -> Bool
forgotToPinVersion Command
cmd =
      Command -> Bool
isPipInstall Command
cmd
        Bool -> Bool -> Bool
&& Bool -> Bool
not (Command -> Bool
hasBuildConstraint Command
cmd)
        Bool -> Bool -> Bool
&& Bool -> Bool
not ((Text -> Bool) -> [Text] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Text -> Bool
versionFixed (Command -> [Text]
packages Command
cmd))

    -- Check if the command is a pip* install command, and that specific packages are being listed
    isPipInstall :: Command -> Bool
isPipInstall Command
cmd =
      ( Command -> Bool
Shell.isPipInstall Command
cmd
          Bool -> Bool -> Bool
&& Bool -> Bool
not (Command -> Bool
hasBuildConstraint Command
cmd)
          Bool -> Bool -> Bool
&& Bool -> Bool
not ((Text -> Bool) -> [Text] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Text -> Bool
versionFixed (Command -> [Text]
packages Command
cmd))
      )
        Bool -> Bool -> Bool
&& Bool -> Bool
not (Command -> Bool
requirementInstall Command
cmd)

    -- If the user is installing requirements from a file or just the local module, then we are not interested
    -- in running this rule
    requirementInstall :: Command -> Bool
requirementInstall Command
cmd =
      [Text
"--requirement"] [Text] -> [Text] -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isInfixOf` Command -> [Text]
Shell.getArgs Command
cmd
        Bool -> Bool -> Bool
|| [Text
"-r"] [Text] -> [Text] -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isInfixOf` Command -> [Text]
Shell.getArgs Command
cmd
        Bool -> Bool -> Bool
|| [Text
"."] [Text] -> [Text] -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isInfixOf` Command -> [Text]
Shell.getArgs Command
cmd

    hasBuildConstraint :: Command -> Bool
hasBuildConstraint Command
cmd = Text -> Command -> Bool
Shell.hasFlag Text
"constraint" Command
cmd Bool -> Bool -> Bool
|| Text -> Command -> Bool
Shell.hasFlag Text
"c" Command
cmd
    versionFixed :: Text -> Bool
versionFixed Text
package = Text -> Bool
hasVersionSymbol Text
package Bool -> Bool -> Bool
|| Text -> Bool
isVersionedGit Text
package Bool -> Bool -> Bool
|| Text -> Bool
isLocalPackage Text
package
    isVersionedGit :: Text -> Bool
isVersionedGit Text
package = Text
"git+http" Text -> Text -> Bool
`Text.isInfixOf` Text
package Bool -> Bool -> Bool
&& Text
"@" Text -> Text -> Bool
`Text.isInfixOf` Text
package
    versionSymbols :: [Text]
versionSymbols = [Text
"==", Text
">=", Text
"<=", Text
">", Text
"<", Text
"!=", Text
"~=", Text
"==="]
    hasVersionSymbol :: Text -> Bool
hasVersionSymbol Text
package = [Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
or [Text
s Text -> Text -> Bool
`Text.isInfixOf` Text
package | Text
s <- [Text]
versionSymbols]
    localPackageFileExtensions :: [Text]
localPackageFileExtensions = [Text
".whl", Text
".tar.gz"]
    isLocalPackage :: Text -> Bool
isLocalPackage Text
package = [Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
or [Text
s Text -> Text -> Bool
`Text.isSuffixOf` Text
package | Text
s <- [Text]
localPackageFileExtensions]
{-# INLINEABLE rule #-}

packages :: Shell.Command -> [Text.Text]
packages :: Command -> [Text]
packages Command
cmd =
  [Text] -> [Text]
stripInstallPrefix ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$
    Command -> [Text]
Shell.getArgsNoFlags (Command -> [Text]) -> Command -> [Text]
forall a b. (a -> b) -> a -> b
$
      [Text] -> Command -> Command
Shell.dropFlagArg
        [ Text
"abi",
          Text
"b",
          Text
"build",
          Text
"e",
          Text
"editable",
          Text
"extra-index-url",
          Text
"f",
          Text
"find-links",
          Text
"i",
          Text
"index-url",
          Text
"implementation",
          Text
"no-binary",
          Text
"only-binary",
          Text
"platform",
          Text
"prefix",
          Text
"progress-bar",
          Text
"proxy",
          Text
"python-version",
          Text
"root",
          Text
"src",
          Text
"t",
          Text
"target",
          Text
"trusted-host",
          Text
"upgrade-strategy"
        ]
        Command
cmd

stripInstallPrefix :: [Text.Text] -> [Text.Text]
stripInstallPrefix :: [Text] -> [Text]
stripInstallPrefix [Text]
cmd = (Text -> Bool) -> [Text] -> [Text]
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"install") ((Text -> Bool) -> [Text] -> [Text]
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
"install") [Text]
cmd)