module Hadolint.Rule.DL3018 (rule) where

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
"DL3018"
    severity :: DLSeverity
severity = DLSeverity
DLWarningC
    message :: Text
message =
      Text
"Pin versions in apk add. Instead of `apk add <package>` \
      \use `apk add <package>=<version>`"
    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
        ( \ParsedShell
as ->
            [Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
and
              [ Text -> Bool
versionFixed Text
p Bool -> Bool -> Bool
|| Text -> Bool
packageFile Text
p
                | Text
p <- ParsedShell -> [Text]
apkAddPackages ParsedShell
as
              ]
        )
        Arguments ParsedShell
args
    check Instruction ParsedShell
_ = Bool
True
    versionFixed :: Text -> Bool
versionFixed Text
package = Text
"=" Text -> Text -> Bool
`Text.isInfixOf` Text
package
    packageFile :: Text -> Bool
packageFile Text
package = Text
".apk" Text -> Text -> Bool
`Text.isSuffixOf` Text
package
{-# INLINEABLE rule #-}

apkAddPackages :: ParsedShell -> [Text.Text]
apkAddPackages :: ParsedShell -> [Text]
apkAddPackages ParsedShell
args =
  [ Text
arg
    | Command
cmd <- ParsedShell -> [Command]
Shell.presentCommands ParsedShell
args,
      Text -> [Text] -> Command -> Bool
Shell.cmdHasArgs Text
"apk" [Text
"add"] Command
cmd,
      Text
arg <- Command -> [Text]
Shell.getArgsNoFlags (Command -> Command
dropTarget Command
cmd),
      Text
arg Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
"add"
  ]
  where
    dropTarget :: Command -> Command
dropTarget = [Text] -> Command -> Command
Shell.dropFlagArg [Text
"t", Text
"virtual", Text
"repository", Text
"X"]