module Hadolint.Rule.DL3008 (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 = Rule ParsedShell
dl3008 Rule ParsedShell -> Rule ParsedShell -> Rule ParsedShell
forall a. Semigroup a => a -> a -> a
<> Rule ParsedShell -> Rule ParsedShell
forall args. Rule args -> Rule args
onbuild Rule ParsedShell
dl3008
{-# INLINEABLE rule #-}

dl3008 :: Rule ParsedShell
dl3008 :: Rule ParsedShell
dl3008 = 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
"DL3008"
    severity :: DLSeverity
severity = DLSeverity
DLWarningC
    message :: Text
message =
      Text
"Pin versions in apt get install. Instead of `apt-get install <package>` use `apt-get \
      \install <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 ((Text -> Bool) -> [Text] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Text -> Bool
versionFixed ([Text] -> Bool) -> (ParsedShell -> [Text]) -> ParsedShell -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParsedShell -> [Text]
aptGetPackages) Arguments ParsedShell
args
    check Instruction ParsedShell
_ = Bool
True
    versionFixed :: Text -> Bool
versionFixed Text
package = Text
"=" Text -> Text -> Bool
`Text.isInfixOf` Text
package Bool -> Bool -> Bool
|| (Text
"/" Text -> Text -> Bool
`Text.isInfixOf` Text
package Bool -> Bool -> Bool
|| Text
".deb" Text -> Text -> Bool
`Text.isSuffixOf` Text
package)
{-# INLINEABLE dl3008 #-}

aptGetPackages :: ParsedShell -> [Text.Text]
aptGetPackages :: ParsedShell -> [Text]
aptGetPackages ParsedShell
args =
  [ Text
arg
    | Command
cmd <- ParsedShell -> [Command]
Shell.presentCommands ParsedShell
args,
      Text -> [Text] -> Command -> Bool
Shell.cmdHasArgs Text
"apt-get" [Text
"install"] 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
"install"
  ]
  where
    dropTarget :: Command -> Command
dropTarget = [Text] -> Command -> Command
Shell.dropFlagArg [Text
"t", Text
"target-release"]