module Hadolint.Rule.DL3033 (rule) where

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 = Rule ParsedShell
dl3033 forall a. Semigroup a => a -> a -> a
<> forall args. Rule args -> Rule args
onbuild Rule ParsedShell
dl3033
{-# INLINEABLE rule #-}

dl3033 :: Rule Shell.ParsedShell
dl3033 :: Rule ParsedShell
dl3033 = 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
"DL3033"
    severity :: DLSeverity
severity = DLSeverity
DLWarningC
    message :: Text
message = Text
"Specify version with `yum install -y <package>-<version>`."

    check :: Instruction ParsedShell -> Bool
check (Run (RunArgs Arguments ParsedShell
args RunFlags
_)) =
      forall a b. (a -> b) -> Arguments a -> b
foldArguments (forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Text -> Bool
packageVersionFixed forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParsedShell -> [Text]
yumPackages) Arguments ParsedShell
args
        Bool -> Bool -> Bool
&& forall a b. (a -> b) -> Arguments a -> b
foldArguments (forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Text -> Bool
moduleVersionFixed forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParsedShell -> [Text]
yumModules) Arguments ParsedShell
args
    check Instruction ParsedShell
_ = Bool
True
{-# INLINEABLE dl3033 #-}

yumPackages :: Shell.ParsedShell -> [Text.Text]
yumPackages :: ParsedShell -> [Text]
yumPackages ParsedShell
args =
  [ Text
arg
    | Command
cmd <- ParsedShell -> [Command]
Shell.presentCommands ParsedShell
args,
      Bool -> Bool
not (Text -> [Text] -> Command -> Bool
Shell.cmdHasArgs Text
"yum" [Text
"module"] Command
cmd),
      Text
arg <- Command -> [Text]
installFilter Command
cmd
  ]

packageVersionFixed :: Text.Text -> Bool
packageVersionFixed :: Text -> Bool
packageVersionFixed Text
package =
  Text
"-" Text -> Text -> Bool
`Text.isInfixOf` Text
package Bool -> Bool -> Bool
|| Text
".rpm" Text -> Text -> Bool
`Text.isSuffixOf` Text
package

yumModules :: Shell.ParsedShell -> [Text.Text]
yumModules :: ParsedShell -> [Text]
yumModules ParsedShell
args =
  [ Text
arg
    | Command
cmd <- ParsedShell -> [Command]
Shell.presentCommands ParsedShell
args,
      Text -> [Text] -> Command -> Bool
Shell.cmdHasArgs Text
"yum" [Text
"module"] Command
cmd,
      Text
arg <- Command -> [Text]
installFilter Command
cmd
  ]

moduleVersionFixed :: Text.Text -> Bool
moduleVersionFixed :: Text -> Bool
moduleVersionFixed = Text -> Text -> Bool
Text.isInfixOf Text
":"

installFilter :: Shell.Command -> [Text.Text]
installFilter :: Command -> [Text]
installFilter Command
cmd =
  [ Text
arg
    | Text -> [Text] -> Command -> Bool
Shell.cmdHasArgs Text
"yum" [Text
"install"] Command
cmd,
      Text
arg <- Command -> [Text]
Shell.getArgsNoFlags Command
cmd,
      Text
arg forall a. Eq a => a -> a -> Bool
/= Text
"install",
      Text
arg forall a. Eq a => a -> a -> Bool
/= Text
"module"
  ]